{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.Casr.Logbook.Meta.ImageType( ImageType(Jpg, Png, Gif) , AsImageType(..) , jpg , png , gif ) where import Control.Lens(makeClassyPrisms, ( # )) import Data.Eq(Eq) import Data.Ord(Ord) import Prelude(Show) data ImageType = Jpg | Png | Gif deriving (ImageType -> ImageType -> Bool (ImageType -> ImageType -> Bool) -> (ImageType -> ImageType -> Bool) -> Eq ImageType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: ImageType -> ImageType -> Bool == :: ImageType -> ImageType -> Bool $c/= :: ImageType -> ImageType -> Bool /= :: ImageType -> ImageType -> Bool Eq, Eq ImageType Eq ImageType => (ImageType -> ImageType -> Ordering) -> (ImageType -> ImageType -> Bool) -> (ImageType -> ImageType -> Bool) -> (ImageType -> ImageType -> Bool) -> (ImageType -> ImageType -> Bool) -> (ImageType -> ImageType -> ImageType) -> (ImageType -> ImageType -> ImageType) -> Ord ImageType ImageType -> ImageType -> Bool ImageType -> ImageType -> Ordering ImageType -> ImageType -> ImageType 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 :: ImageType -> ImageType -> Ordering compare :: ImageType -> ImageType -> Ordering $c< :: ImageType -> ImageType -> Bool < :: ImageType -> ImageType -> Bool $c<= :: ImageType -> ImageType -> Bool <= :: ImageType -> ImageType -> Bool $c> :: ImageType -> ImageType -> Bool > :: ImageType -> ImageType -> Bool $c>= :: ImageType -> ImageType -> Bool >= :: ImageType -> ImageType -> Bool $cmax :: ImageType -> ImageType -> ImageType max :: ImageType -> ImageType -> ImageType $cmin :: ImageType -> ImageType -> ImageType min :: ImageType -> ImageType -> ImageType Ord, Int -> ImageType -> ShowS [ImageType] -> ShowS ImageType -> String (Int -> ImageType -> ShowS) -> (ImageType -> String) -> ([ImageType] -> ShowS) -> Show ImageType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> ImageType -> ShowS showsPrec :: Int -> ImageType -> ShowS $cshow :: ImageType -> String show :: ImageType -> String $cshowList :: [ImageType] -> ShowS showList :: [ImageType] -> ShowS Show) makeClassyPrisms ''ImageType jpg :: AsImageType t => t jpg :: forall t. AsImageType t => t jpg = Tagged () (Identity ()) -> Tagged t (Identity t) forall r. AsImageType r => Prism' r () Prism' t () _Jpg (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t forall t b. AReview t b -> b -> t # () png :: AsImageType t => t png :: forall t. AsImageType t => t png = Tagged () (Identity ()) -> Tagged t (Identity t) forall r. AsImageType r => Prism' r () Prism' t () _Png (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t forall t b. AReview t b -> b -> t # () gif :: AsImageType t => t gif :: forall t. AsImageType t => t gif = Tagged () (Identity ()) -> Tagged t (Identity t) forall r. AsImageType r => Prism' r () Prism' t () _Gif (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t forall t b. AReview t b -> b -> t # ()