{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.Casr.Logbook.Types.Exam( Exam(..) , HasExam(..) , dayonlyexam ) where import Control.Category((.)) import Control.Lens(makeClassy) import Data.Aviation.Casr.Logbook.Types.Aviator(Aviator, HasAviator(aviator)) import Data.Aviation.Casr.Logbook.Types.Time(Time, HasTime(time), dayonly) import Data.Aviation.Casr.Logbook.Types.Location(Location, HasLocation(location)) import Data.Eq(Eq) import Data.Int(Int) import Data.Ord(Ord) import Data.String(String) import Data.Time(Day) import Prelude(Show) data Exam = Exam { Exam -> String _examName :: String , Exam -> Location _examLocation :: Location , Exam -> Time _examTime :: Time , Exam -> Aviator _examDelegate :: Aviator , Exam -> Int _examResult :: Int , Exam -> Int _examResultMaximum :: Int } deriving (Exam -> Exam -> Bool (Exam -> Exam -> Bool) -> (Exam -> Exam -> Bool) -> Eq Exam forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Exam -> Exam -> Bool == :: Exam -> Exam -> Bool $c/= :: Exam -> Exam -> Bool /= :: Exam -> Exam -> Bool Eq, Eq Exam Eq Exam => (Exam -> Exam -> Ordering) -> (Exam -> Exam -> Bool) -> (Exam -> Exam -> Bool) -> (Exam -> Exam -> Bool) -> (Exam -> Exam -> Bool) -> (Exam -> Exam -> Exam) -> (Exam -> Exam -> Exam) -> Ord Exam Exam -> Exam -> Bool Exam -> Exam -> Ordering Exam -> Exam -> Exam 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 :: Exam -> Exam -> Ordering compare :: Exam -> Exam -> Ordering $c< :: Exam -> Exam -> Bool < :: Exam -> Exam -> Bool $c<= :: Exam -> Exam -> Bool <= :: Exam -> Exam -> Bool $c> :: Exam -> Exam -> Bool > :: Exam -> Exam -> Bool $c>= :: Exam -> Exam -> Bool >= :: Exam -> Exam -> Bool $cmax :: Exam -> Exam -> Exam max :: Exam -> Exam -> Exam $cmin :: Exam -> Exam -> Exam min :: Exam -> Exam -> Exam Ord, Int -> Exam -> ShowS [Exam] -> ShowS Exam -> String (Int -> Exam -> ShowS) -> (Exam -> String) -> ([Exam] -> ShowS) -> Show Exam forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Exam -> ShowS showsPrec :: Int -> Exam -> ShowS $cshow :: Exam -> String show :: Exam -> String $cshowList :: [Exam] -> ShowS showList :: [Exam] -> ShowS Show) makeClassy ''Exam instance HasLocation Exam where location :: Lens' Exam Location location = (Location -> f Location) -> Exam -> f Exam forall c. HasExam c => Lens' c Location Lens' Exam Location examLocation ((Location -> f Location) -> Exam -> f Exam) -> ((Location -> f Location) -> Location -> f Location) -> (Location -> f Location) -> Exam -> f Exam 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 . (Location -> f Location) -> Location -> f Location forall c. HasLocation c => Lens' c Location Lens' Location Location location instance HasTime Exam where time :: Lens' Exam Time time = (Time -> f Time) -> Exam -> f Exam forall c. HasExam c => Lens' c Time Lens' Exam Time examTime ((Time -> f Time) -> Exam -> f Exam) -> ((Time -> f Time) -> Time -> f Time) -> (Time -> f Time) -> Exam -> f Exam 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 . (Time -> f Time) -> Time -> f Time forall c. HasTime c => Lens' c Time Lens' Time Time time instance HasAviator Exam where aviator :: Lens' Exam Aviator aviator = (Aviator -> f Aviator) -> Exam -> f Exam forall c. HasExam c => Lens' c Aviator Lens' Exam Aviator examDelegate ((Aviator -> f Aviator) -> Exam -> f Exam) -> ((Aviator -> f Aviator) -> Aviator -> f Aviator) -> (Aviator -> f Aviator) -> Exam -> f Exam 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 . (Aviator -> f Aviator) -> Aviator -> f Aviator forall c. HasAviator c => Lens' c Aviator Lens' Aviator Aviator aviator dayonlyexam :: String -> Location -> Day -> Aviator -> Int -> Int -> Exam dayonlyexam :: String -> Location -> Day -> Aviator -> Int -> Int -> Exam dayonlyexam String n Location l Day d = String -> Location -> Time -> Aviator -> Int -> Int -> Exam Exam String n Location l (Day -> Time dayonly Day d)