{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.Casr.Logbook.Meta.VideoType( VideoType(YouTube, Vimeo, Bambuser) , AsVideoType(..) , linkVideoType , iframeVideoType , youtube , vimeo , bambuser ) where import Control.Lens(makeClassyPrisms, ( # )) import Data.Eq(Eq) import Data.List((++)) import Data.Ord(Ord) import Data.String(String) import Prelude(Show) data VideoType = YouTube | Vimeo | Bambuser deriving (VideoType -> VideoType -> Bool (VideoType -> VideoType -> Bool) -> (VideoType -> VideoType -> Bool) -> Eq VideoType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: VideoType -> VideoType -> Bool == :: VideoType -> VideoType -> Bool $c/= :: VideoType -> VideoType -> Bool /= :: VideoType -> VideoType -> Bool Eq, Eq VideoType Eq VideoType => (VideoType -> VideoType -> Ordering) -> (VideoType -> VideoType -> Bool) -> (VideoType -> VideoType -> Bool) -> (VideoType -> VideoType -> Bool) -> (VideoType -> VideoType -> Bool) -> (VideoType -> VideoType -> VideoType) -> (VideoType -> VideoType -> VideoType) -> Ord VideoType VideoType -> VideoType -> Bool VideoType -> VideoType -> Ordering VideoType -> VideoType -> VideoType forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: VideoType -> VideoType -> Ordering compare :: VideoType -> VideoType -> Ordering $c< :: VideoType -> VideoType -> Bool < :: VideoType -> VideoType -> Bool $c<= :: VideoType -> VideoType -> Bool <= :: VideoType -> VideoType -> Bool $c> :: VideoType -> VideoType -> Bool > :: VideoType -> VideoType -> Bool $c>= :: VideoType -> VideoType -> Bool >= :: VideoType -> VideoType -> Bool $cmax :: VideoType -> VideoType -> VideoType max :: VideoType -> VideoType -> VideoType $cmin :: VideoType -> VideoType -> VideoType min :: VideoType -> VideoType -> VideoType Ord, Int -> VideoType -> ShowS [VideoType] -> ShowS VideoType -> String (Int -> VideoType -> ShowS) -> (VideoType -> String) -> ([VideoType] -> ShowS) -> Show VideoType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> VideoType -> ShowS showsPrec :: Int -> VideoType -> ShowS $cshow :: VideoType -> String show :: VideoType -> String $cshowList :: [VideoType] -> ShowS showList :: [VideoType] -> ShowS Show) makeClassyPrisms ''VideoType youtube :: AsVideoType t => t youtube :: forall t. AsVideoType t => t youtube = Tagged () (Identity ()) -> Tagged t (Identity t) forall r. AsVideoType r => Prism' r () Prism' t () _YouTube (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t forall t b. AReview t b -> b -> t # () vimeo :: AsVideoType t => t vimeo :: forall t. AsVideoType t => t vimeo = Tagged () (Identity ()) -> Tagged t (Identity t) forall r. AsVideoType r => Prism' r () Prism' t () _Vimeo (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t forall t b. AReview t b -> b -> t # () bambuser :: AsVideoType t => t bambuser :: forall t. AsVideoType t => t bambuser = Tagged () (Identity ()) -> Tagged t (Identity t) forall r. AsVideoType r => Prism' r () Prism' t () _Bambuser (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t forall t b. AReview t b -> b -> t # () linkVideoType :: VideoType -> String -> String linkVideoType :: VideoType -> ShowS linkVideoType VideoType YouTube String u = String "https://www.youtube.com/watch?v=" String -> ShowS forall a. [a] -> [a] -> [a] ++ String u linkVideoType VideoType Vimeo String u = String "https://bambuser.com/v/" String -> ShowS forall a. [a] -> [a] -> [a] ++ String u linkVideoType VideoType Bambuser String u = String "https://vimeo.com/" String -> ShowS forall a. [a] -> [a] -> [a] ++ String u iframeVideoType :: VideoType -> String -> String iframeVideoType :: VideoType -> ShowS iframeVideoType VideoType YouTube String u = String "http://www.youtube.com/embed/" String -> ShowS forall a. [a] -> [a] -> [a] ++ String u String -> ShowS forall a. [a] -> [a] -> [a] ++ String "?autohide=1&cc_load_policy=1&color=white&controls=1&disablekb=0&fs=1&iv_load_policy=0&loop=0&modestbranding=1&rel=0&showinfo=0" iframeVideoType VideoType Vimeo String u = String "https://player.vimeo.com/video/" String -> ShowS forall a. [a] -> [a] -> [a] ++ String u iframeVideoType VideoType Bambuser String u = String "https://embed.bambuser.com/broadcast/" String -> ShowS forall a. [a] -> [a] -> [a] ++ String u String -> ShowS forall a. [a] -> [a] -> [a] ++ String "?chat=1&mute=0"