{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.Casr.Logbook.Reports.SimulatorTimeReport( SimulatorTimeReport(..) , HasSimulatorTimeReport(..) , singleSimulatorTimeReport , getSimulatorTimeReport ) where import Control.Category((.)) import Control.Lens(makeClassy, (^.)) import Data.Aviation.Casr.Logbook.Types ( TimeAmount , Logbook(Logbook) , Entry(SimulatorFlightEntry) , Entries(Entries) , simulatorTime , instrumentsimulatorTime ) import Data.Eq(Eq) import Data.Foldable(foldl') import Data.Monoid(Monoid(mappend, mempty)) import Data.Ord(Ord) import Data.Semigroup(Semigroup((<>))) import Prelude(Show) data SimulatorTimeReport = SimulatorTimeReport { SimulatorTimeReport -> TimeAmount _hoursTotalSimulator :: TimeAmount , SimulatorTimeReport -> TimeAmount _hoursInstrumentSimulator :: TimeAmount } deriving (SimulatorTimeReport -> SimulatorTimeReport -> Bool (SimulatorTimeReport -> SimulatorTimeReport -> Bool) -> (SimulatorTimeReport -> SimulatorTimeReport -> Bool) -> Eq SimulatorTimeReport forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: SimulatorTimeReport -> SimulatorTimeReport -> Bool == :: SimulatorTimeReport -> SimulatorTimeReport -> Bool $c/= :: SimulatorTimeReport -> SimulatorTimeReport -> Bool /= :: SimulatorTimeReport -> SimulatorTimeReport -> Bool Eq, Eq SimulatorTimeReport Eq SimulatorTimeReport => (SimulatorTimeReport -> SimulatorTimeReport -> Ordering) -> (SimulatorTimeReport -> SimulatorTimeReport -> Bool) -> (SimulatorTimeReport -> SimulatorTimeReport -> Bool) -> (SimulatorTimeReport -> SimulatorTimeReport -> Bool) -> (SimulatorTimeReport -> SimulatorTimeReport -> Bool) -> (SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport) -> (SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport) -> Ord SimulatorTimeReport SimulatorTimeReport -> SimulatorTimeReport -> Bool SimulatorTimeReport -> SimulatorTimeReport -> Ordering SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport 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 :: SimulatorTimeReport -> SimulatorTimeReport -> Ordering compare :: SimulatorTimeReport -> SimulatorTimeReport -> Ordering $c< :: SimulatorTimeReport -> SimulatorTimeReport -> Bool < :: SimulatorTimeReport -> SimulatorTimeReport -> Bool $c<= :: SimulatorTimeReport -> SimulatorTimeReport -> Bool <= :: SimulatorTimeReport -> SimulatorTimeReport -> Bool $c> :: SimulatorTimeReport -> SimulatorTimeReport -> Bool > :: SimulatorTimeReport -> SimulatorTimeReport -> Bool $c>= :: SimulatorTimeReport -> SimulatorTimeReport -> Bool >= :: SimulatorTimeReport -> SimulatorTimeReport -> Bool $cmax :: SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport max :: SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport $cmin :: SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport min :: SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport Ord, Int -> SimulatorTimeReport -> ShowS [SimulatorTimeReport] -> ShowS SimulatorTimeReport -> String (Int -> SimulatorTimeReport -> ShowS) -> (SimulatorTimeReport -> String) -> ([SimulatorTimeReport] -> ShowS) -> Show SimulatorTimeReport forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> SimulatorTimeReport -> ShowS showsPrec :: Int -> SimulatorTimeReport -> ShowS $cshow :: SimulatorTimeReport -> String show :: SimulatorTimeReport -> String $cshowList :: [SimulatorTimeReport] -> ShowS showList :: [SimulatorTimeReport] -> ShowS Show) makeClassy ''SimulatorTimeReport instance Semigroup SimulatorTimeReport where SimulatorTimeReport TimeAmount t1 TimeAmount i1 <> :: SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport <> SimulatorTimeReport TimeAmount t2 TimeAmount i2 = TimeAmount -> TimeAmount -> SimulatorTimeReport SimulatorTimeReport (TimeAmount t1 TimeAmount -> TimeAmount -> TimeAmount forall a. Semigroup a => a -> a -> a <> TimeAmount t2) (TimeAmount i1 TimeAmount -> TimeAmount -> TimeAmount forall a. Semigroup a => a -> a -> a <> TimeAmount i2) instance Monoid SimulatorTimeReport where mempty :: SimulatorTimeReport mempty = TimeAmount -> TimeAmount -> SimulatorTimeReport SimulatorTimeReport TimeAmount forall a. Monoid a => a mempty TimeAmount forall a. Monoid a => a mempty mappend :: SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport mappend = SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport forall a. Semigroup a => a -> a -> a (<>) singleSimulatorTimeReport :: Entry a b c d -> SimulatorTimeReport singleSimulatorTimeReport :: forall a b c d. Entry a b c d -> SimulatorTimeReport singleSimulatorTimeReport (SimulatorFlightEntry SimulatorFlight fl b _) = TimeAmount -> TimeAmount -> SimulatorTimeReport SimulatorTimeReport (SimulatorFlight fl SimulatorFlight -> Getting TimeAmount SimulatorFlight TimeAmount -> TimeAmount forall s a. s -> Getting a s a -> a ^. Getting TimeAmount SimulatorFlight TimeAmount forall c. HasSimulatorFlight c => Lens' c TimeAmount Lens' SimulatorFlight TimeAmount simulatorTime) (SimulatorFlight fl SimulatorFlight -> Getting TimeAmount SimulatorFlight TimeAmount -> TimeAmount forall s a. s -> Getting a s a -> a ^. Getting TimeAmount SimulatorFlight TimeAmount forall c. HasSimulatorFlight c => Lens' c TimeAmount Lens' SimulatorFlight TimeAmount instrumentsimulatorTime) singleSimulatorTimeReport Entry a b c d _ = SimulatorTimeReport forall a. Monoid a => a mempty getSimulatorTimeReport :: Logbook a b c d -> SimulatorTimeReport getSimulatorTimeReport :: forall a b c d. Logbook a b c d -> SimulatorTimeReport getSimulatorTimeReport (Logbook Aviator _ (Entries [Entry a b c d] es)) = (SimulatorTimeReport -> Entry a b c d -> SimulatorTimeReport) -> SimulatorTimeReport -> [Entry a b c d] -> SimulatorTimeReport forall b a. (b -> a -> b) -> b -> [a] -> b forall (t :: * -> *) b a. Foldable t => (b -> a -> b) -> b -> t a -> b foldl' (\SimulatorTimeReport a -> SimulatorTimeReport -> SimulatorTimeReport -> SimulatorTimeReport forall a. Monoid a => a -> a -> a mappend SimulatorTimeReport a (SimulatorTimeReport -> SimulatorTimeReport) -> (Entry a b c d -> SimulatorTimeReport) -> Entry a b c d -> SimulatorTimeReport 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 . Entry a b c d -> SimulatorTimeReport forall a b c d. Entry a b c d -> SimulatorTimeReport singleSimulatorTimeReport) SimulatorTimeReport forall a. Monoid a => a mempty [Entry a b c d] es