{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.Casr.Logbook.Types.Instruction where import Control.Category ( Category((.)) ) import Control.Lens ( makeClassyPrisms, Traversal', _Just, isn't, makeClassy ) import Data.Aviation.Casr.Logbook.Types.Aviator ( Aviator ) import Data.Bool ( Bool, (&&) ) import Data.Eq(Eq) import Data.Functor ( Functor(fmap) ) import Data.Maybe ( Maybe ) import Data.Ord(Ord) import Data.String(String) import Prelude(Show) data InstructionLesson = InstructionLesson { InstructionLesson -> Aviator _student :: Aviator , InstructionLesson -> Maybe String _lesson :: Maybe String } deriving (InstructionLesson -> InstructionLesson -> Bool (InstructionLesson -> InstructionLesson -> Bool) -> (InstructionLesson -> InstructionLesson -> Bool) -> Eq InstructionLesson forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: InstructionLesson -> InstructionLesson -> Bool == :: InstructionLesson -> InstructionLesson -> Bool $c/= :: InstructionLesson -> InstructionLesson -> Bool /= :: InstructionLesson -> InstructionLesson -> Bool Eq, Eq InstructionLesson Eq InstructionLesson => (InstructionLesson -> InstructionLesson -> Ordering) -> (InstructionLesson -> InstructionLesson -> Bool) -> (InstructionLesson -> InstructionLesson -> Bool) -> (InstructionLesson -> InstructionLesson -> Bool) -> (InstructionLesson -> InstructionLesson -> Bool) -> (InstructionLesson -> InstructionLesson -> InstructionLesson) -> (InstructionLesson -> InstructionLesson -> InstructionLesson) -> Ord InstructionLesson InstructionLesson -> InstructionLesson -> Bool InstructionLesson -> InstructionLesson -> Ordering InstructionLesson -> InstructionLesson -> InstructionLesson 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 :: InstructionLesson -> InstructionLesson -> Ordering compare :: InstructionLesson -> InstructionLesson -> Ordering $c< :: InstructionLesson -> InstructionLesson -> Bool < :: InstructionLesson -> InstructionLesson -> Bool $c<= :: InstructionLesson -> InstructionLesson -> Bool <= :: InstructionLesson -> InstructionLesson -> Bool $c> :: InstructionLesson -> InstructionLesson -> Bool > :: InstructionLesson -> InstructionLesson -> Bool $c>= :: InstructionLesson -> InstructionLesson -> Bool >= :: InstructionLesson -> InstructionLesson -> Bool $cmax :: InstructionLesson -> InstructionLesson -> InstructionLesson max :: InstructionLesson -> InstructionLesson -> InstructionLesson $cmin :: InstructionLesson -> InstructionLesson -> InstructionLesson min :: InstructionLesson -> InstructionLesson -> InstructionLesson Ord, Int -> InstructionLesson -> ShowS [InstructionLesson] -> ShowS InstructionLesson -> String (Int -> InstructionLesson -> ShowS) -> (InstructionLesson -> String) -> ([InstructionLesson] -> ShowS) -> Show InstructionLesson forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> InstructionLesson -> ShowS showsPrec :: Int -> InstructionLesson -> ShowS $cshow :: InstructionLesson -> String show :: InstructionLesson -> String $cshowList :: [InstructionLesson] -> ShowS showList :: [InstructionLesson] -> ShowS Show) makeClassy ''InstructionLesson lesson' :: HasInstructionLesson c => Traversal' c String lesson' :: forall c. HasInstructionLesson c => Traversal' c String lesson' = (Maybe String -> f (Maybe String)) -> c -> f c forall c. HasInstructionLesson c => Lens' c (Maybe String) Lens' c (Maybe String) lesson ((Maybe String -> f (Maybe String)) -> c -> f c) -> ((String -> f String) -> Maybe String -> f (Maybe String)) -> (String -> f String) -> 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 . (String -> f String) -> Maybe String -> f (Maybe String) forall a b (p :: * -> * -> *) (f :: * -> *). (Choice p, Applicative f) => p a (f b) -> p (Maybe a) (f (Maybe b)) _Just data InstructionRating = GA3InstructionRating | GA2InstructionRating | GA1InstructionRating | RAInstructionRating | RASIInstructionRating deriving (InstructionRating -> InstructionRating -> Bool (InstructionRating -> InstructionRating -> Bool) -> (InstructionRating -> InstructionRating -> Bool) -> Eq InstructionRating forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: InstructionRating -> InstructionRating -> Bool == :: InstructionRating -> InstructionRating -> Bool $c/= :: InstructionRating -> InstructionRating -> Bool /= :: InstructionRating -> InstructionRating -> Bool Eq, Eq InstructionRating Eq InstructionRating => (InstructionRating -> InstructionRating -> Ordering) -> (InstructionRating -> InstructionRating -> Bool) -> (InstructionRating -> InstructionRating -> Bool) -> (InstructionRating -> InstructionRating -> Bool) -> (InstructionRating -> InstructionRating -> Bool) -> (InstructionRating -> InstructionRating -> InstructionRating) -> (InstructionRating -> InstructionRating -> InstructionRating) -> Ord InstructionRating InstructionRating -> InstructionRating -> Bool InstructionRating -> InstructionRating -> Ordering InstructionRating -> InstructionRating -> InstructionRating 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 :: InstructionRating -> InstructionRating -> Ordering compare :: InstructionRating -> InstructionRating -> Ordering $c< :: InstructionRating -> InstructionRating -> Bool < :: InstructionRating -> InstructionRating -> Bool $c<= :: InstructionRating -> InstructionRating -> Bool <= :: InstructionRating -> InstructionRating -> Bool $c> :: InstructionRating -> InstructionRating -> Bool > :: InstructionRating -> InstructionRating -> Bool $c>= :: InstructionRating -> InstructionRating -> Bool >= :: InstructionRating -> InstructionRating -> Bool $cmax :: InstructionRating -> InstructionRating -> InstructionRating max :: InstructionRating -> InstructionRating -> InstructionRating $cmin :: InstructionRating -> InstructionRating -> InstructionRating min :: InstructionRating -> InstructionRating -> InstructionRating Ord, Int -> InstructionRating -> ShowS [InstructionRating] -> ShowS InstructionRating -> String (Int -> InstructionRating -> ShowS) -> (InstructionRating -> String) -> ([InstructionRating] -> ShowS) -> Show InstructionRating forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> InstructionRating -> ShowS showsPrec :: Int -> InstructionRating -> ShowS $cshow :: InstructionRating -> String show :: InstructionRating -> String $cshowList :: [InstructionRating] -> ShowS showList :: [InstructionRating] -> ShowS Show) makeClassy ''InstructionRating makeClassyPrisms ''InstructionRating isRAInstruction :: AsInstructionRating a => a -> Bool isRAInstruction :: forall a. AsInstructionRating a => a -> Bool isRAInstruction a x = APrism a a () () -> a -> Bool forall s t a b. APrism s t a b -> s -> Bool isn't APrism a a () () forall r. AsInstructionRating r => Prism' r () Prism' a () _GA1InstructionRating a x Bool -> Bool -> Bool && APrism a a () () -> a -> Bool forall s t a b. APrism s t a b -> s -> Bool isn't APrism a a () () forall r. AsInstructionRating r => Prism' r () Prism' a () _GA2InstructionRating a x Bool -> Bool -> Bool && APrism a a () () -> a -> Bool forall s t a b. APrism s t a b -> s -> Bool isn't APrism a a () () forall r. AsInstructionRating r => Prism' r () Prism' a () _GA3InstructionRating a x isGAInstruction :: AsInstructionRating a => a -> Bool isGAInstruction :: forall a. AsInstructionRating a => a -> Bool isGAInstruction a x = APrism a a () () -> a -> Bool forall s t a b. APrism s t a b -> s -> Bool isn't APrism a a () () forall r. AsInstructionRating r => Prism' r () Prism' a () _RAInstructionRating a x Bool -> Bool -> Bool && APrism a a () () -> a -> Bool forall s t a b. APrism s t a b -> s -> Bool isn't APrism a a () () forall r. AsInstructionRating r => Prism' r () Prism' a () _RASIInstructionRating a x shortStringRating :: InstructionRating -> String shortStringRating :: InstructionRating -> String shortStringRating InstructionRating GA3InstructionRating = String "GA3" shortStringRating InstructionRating GA2InstructionRating = String "GA3" shortStringRating InstructionRating GA1InstructionRating = String "GA1" shortStringRating InstructionRating RAInstructionRating = String "RA" shortStringRating InstructionRating RASIInstructionRating = String "RA SI" data Instruction = Instruction { Instruction -> InstructionLesson __instructionLesson :: InstructionLesson , Instruction -> InstructionRating __instructionWithRating :: InstructionRating } deriving (Instruction -> Instruction -> Bool (Instruction -> Instruction -> Bool) -> (Instruction -> Instruction -> Bool) -> Eq Instruction forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Instruction -> Instruction -> Bool == :: Instruction -> Instruction -> Bool $c/= :: Instruction -> Instruction -> Bool /= :: Instruction -> Instruction -> Bool Eq, Eq Instruction Eq Instruction => (Instruction -> Instruction -> Ordering) -> (Instruction -> Instruction -> Bool) -> (Instruction -> Instruction -> Bool) -> (Instruction -> Instruction -> Bool) -> (Instruction -> Instruction -> Bool) -> (Instruction -> Instruction -> Instruction) -> (Instruction -> Instruction -> Instruction) -> Ord Instruction Instruction -> Instruction -> Bool Instruction -> Instruction -> Ordering Instruction -> Instruction -> Instruction 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 :: Instruction -> Instruction -> Ordering compare :: Instruction -> Instruction -> Ordering $c< :: Instruction -> Instruction -> Bool < :: Instruction -> Instruction -> Bool $c<= :: Instruction -> Instruction -> Bool <= :: Instruction -> Instruction -> Bool $c> :: Instruction -> Instruction -> Bool > :: Instruction -> Instruction -> Bool $c>= :: Instruction -> Instruction -> Bool >= :: Instruction -> Instruction -> Bool $cmax :: Instruction -> Instruction -> Instruction max :: Instruction -> Instruction -> Instruction $cmin :: Instruction -> Instruction -> Instruction min :: Instruction -> Instruction -> Instruction Ord, Int -> Instruction -> ShowS [Instruction] -> ShowS Instruction -> String (Int -> Instruction -> ShowS) -> (Instruction -> String) -> ([Instruction] -> ShowS) -> Show Instruction forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Instruction -> ShowS showsPrec :: Int -> Instruction -> ShowS $cshow :: Instruction -> String show :: Instruction -> String $cshowList :: [Instruction] -> ShowS showList :: [Instruction] -> ShowS Show) makeClassy ''Instruction instance HasInstructionLesson Instruction where instructionLesson :: Lens' Instruction InstructionLesson instructionLesson InstructionLesson -> f InstructionLesson f (Instruction InstructionLesson l InstructionRating r) = (InstructionLesson -> Instruction) -> f InstructionLesson -> f Instruction forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (InstructionLesson -> InstructionRating -> Instruction `Instruction` InstructionRating r) (InstructionLesson -> f InstructionLesson f InstructionLesson l) instance HasInstructionRating Instruction where instructionRating :: Lens' Instruction InstructionRating instructionRating InstructionRating -> f InstructionRating f (Instruction InstructionLesson l InstructionRating r) = (InstructionRating -> Instruction) -> f InstructionRating -> f Instruction forall a b. (a -> b) -> f a -> f b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (InstructionLesson -> InstructionRating -> Instruction Instruction InstructionLesson l) (InstructionRating -> f InstructionRating f InstructionRating r)