{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.Casr.Logbook.Meta.TrackLogType( TrackLogType(Gpx, Kml, Kmz, ImageTrackLog) , AsTrackLogType(..) , gpx , kml , kmz ) where import Control.Lens(makeClassyPrisms, ( # )) import Data.Aviation.Casr.Logbook.Meta.ImageType ( ImageType ) import Data.Eq(Eq) import Data.Ord(Ord) import Prelude(Show) data TrackLogType = Gpx | Kml | Kmz | ImageTrackLog ImageType deriving (TrackLogType -> TrackLogType -> Bool (TrackLogType -> TrackLogType -> Bool) -> (TrackLogType -> TrackLogType -> Bool) -> Eq TrackLogType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: TrackLogType -> TrackLogType -> Bool == :: TrackLogType -> TrackLogType -> Bool $c/= :: TrackLogType -> TrackLogType -> Bool /= :: TrackLogType -> TrackLogType -> Bool Eq, Eq TrackLogType Eq TrackLogType => (TrackLogType -> TrackLogType -> Ordering) -> (TrackLogType -> TrackLogType -> Bool) -> (TrackLogType -> TrackLogType -> Bool) -> (TrackLogType -> TrackLogType -> Bool) -> (TrackLogType -> TrackLogType -> Bool) -> (TrackLogType -> TrackLogType -> TrackLogType) -> (TrackLogType -> TrackLogType -> TrackLogType) -> Ord TrackLogType TrackLogType -> TrackLogType -> Bool TrackLogType -> TrackLogType -> Ordering TrackLogType -> TrackLogType -> TrackLogType 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 :: TrackLogType -> TrackLogType -> Ordering compare :: TrackLogType -> TrackLogType -> Ordering $c< :: TrackLogType -> TrackLogType -> Bool < :: TrackLogType -> TrackLogType -> Bool $c<= :: TrackLogType -> TrackLogType -> Bool <= :: TrackLogType -> TrackLogType -> Bool $c> :: TrackLogType -> TrackLogType -> Bool > :: TrackLogType -> TrackLogType -> Bool $c>= :: TrackLogType -> TrackLogType -> Bool >= :: TrackLogType -> TrackLogType -> Bool $cmax :: TrackLogType -> TrackLogType -> TrackLogType max :: TrackLogType -> TrackLogType -> TrackLogType $cmin :: TrackLogType -> TrackLogType -> TrackLogType min :: TrackLogType -> TrackLogType -> TrackLogType Ord, Int -> TrackLogType -> ShowS [TrackLogType] -> ShowS TrackLogType -> String (Int -> TrackLogType -> ShowS) -> (TrackLogType -> String) -> ([TrackLogType] -> ShowS) -> Show TrackLogType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> TrackLogType -> ShowS showsPrec :: Int -> TrackLogType -> ShowS $cshow :: TrackLogType -> String show :: TrackLogType -> String $cshowList :: [TrackLogType] -> ShowS showList :: [TrackLogType] -> ShowS Show) makeClassyPrisms ''TrackLogType gpx :: AsTrackLogType t => t gpx :: forall t. AsTrackLogType t => t gpx = Tagged () (Identity ()) -> Tagged t (Identity t) forall r. AsTrackLogType r => Prism' r () Prism' t () _Gpx (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t forall t b. AReview t b -> b -> t # () kml :: AsTrackLogType t => t kml :: forall t. AsTrackLogType t => t kml = Tagged () (Identity ()) -> Tagged t (Identity t) forall r. AsTrackLogType r => Prism' r () Prism' t () _Kml (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t forall t b. AReview t b -> b -> t # () kmz :: AsTrackLogType t => t kmz :: forall t. AsTrackLogType t => t kmz = Tagged () (Identity ()) -> Tagged t (Identity t) forall r. AsTrackLogType r => Prism' r () Prism' t () _Kmz (Tagged () (Identity ()) -> Tagged t (Identity t)) -> () -> t forall t b. AReview t b -> b -> t # ()