{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.Casr.Logbook.Types.Time( Time(..) , HasTime(..) , dayonly , dayandtime , timeofday' ) where import Control.Category ( Category((.)) ) import Control.Lens(makeClassy, Traversal', _Just) import Data.Eq(Eq) import Data.Ord(Ord) import Data.Maybe(Maybe(Nothing, Just)) import Data.Time(Day, TimeOfDay) import Prelude(Show) data Time = Time { Time -> Day _daytime :: Day , Time -> Maybe TimeOfDay _timeofday :: Maybe TimeOfDay } deriving (Time -> Time -> Bool (Time -> Time -> Bool) -> (Time -> Time -> Bool) -> Eq Time forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Time -> Time -> Bool == :: Time -> Time -> Bool $c/= :: Time -> Time -> Bool /= :: Time -> Time -> Bool Eq, Eq Time Eq Time => (Time -> Time -> Ordering) -> (Time -> Time -> Bool) -> (Time -> Time -> Bool) -> (Time -> Time -> Bool) -> (Time -> Time -> Bool) -> (Time -> Time -> Time) -> (Time -> Time -> Time) -> Ord Time Time -> Time -> Bool Time -> Time -> Ordering Time -> Time -> Time 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 :: Time -> Time -> Ordering compare :: Time -> Time -> Ordering $c< :: Time -> Time -> Bool < :: Time -> Time -> Bool $c<= :: Time -> Time -> Bool <= :: Time -> Time -> Bool $c> :: Time -> Time -> Bool > :: Time -> Time -> Bool $c>= :: Time -> Time -> Bool >= :: Time -> Time -> Bool $cmax :: Time -> Time -> Time max :: Time -> Time -> Time $cmin :: Time -> Time -> Time min :: Time -> Time -> Time Ord, Int -> Time -> ShowS [Time] -> ShowS Time -> String (Int -> Time -> ShowS) -> (Time -> String) -> ([Time] -> ShowS) -> Show Time forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Time -> ShowS showsPrec :: Int -> Time -> ShowS $cshow :: Time -> String show :: Time -> String $cshowList :: [Time] -> ShowS showList :: [Time] -> ShowS Show) makeClassy ''Time timeofday' :: HasTime c => Traversal' c TimeOfDay timeofday' :: forall c. HasTime c => Traversal' c TimeOfDay timeofday' = (Maybe TimeOfDay -> f (Maybe TimeOfDay)) -> c -> f c forall c. HasTime c => Lens' c (Maybe TimeOfDay) Lens' c (Maybe TimeOfDay) timeofday ((Maybe TimeOfDay -> f (Maybe TimeOfDay)) -> c -> f c) -> ((TimeOfDay -> f TimeOfDay) -> Maybe TimeOfDay -> f (Maybe TimeOfDay)) -> (TimeOfDay -> f TimeOfDay) -> c -> f c forall b c a. (b -> c) -> (a -> b) -> a -> c forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (TimeOfDay -> f TimeOfDay) -> Maybe TimeOfDay -> f (Maybe TimeOfDay) forall a b (p :: * -> * -> *) (f :: * -> *). (Choice p, Applicative f) => p a (f b) -> p (Maybe a) (f (Maybe b)) _Just dayonly :: Day -> Time dayonly :: Day -> Time dayonly Day d = Day -> Maybe TimeOfDay -> Time Time Day d Maybe TimeOfDay forall a. Maybe a Nothing dayandtime :: Day -> TimeOfDay -> Time dayandtime :: Day -> TimeOfDay -> Time dayandtime Day d TimeOfDay t = Day -> Maybe TimeOfDay -> Time Time Day d (TimeOfDay -> Maybe TimeOfDay forall a. a -> Maybe a Just TimeOfDay t)