{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE LambdaCase #-} module Data.Aviation.Casr.Logbook.Types.Command( Command(..) , AsCommand(..) , getUnderInstructionPic , _InCommandIncludingInstructing ) where import Control.Applicative ( Alternative((<|>)) ) import Control.Lens ( Prism', preview, makeClassyPrisms, prism', (#) ) import Data.Aviation.Casr.Logbook.Types.Aviator(Aviator) import Data.Aviation.Casr.Logbook.Types.Instruction ( Instruction, InstructionRating ) import Data.Eq(Eq) import Data.Functor ( Functor((<$)), (<$>) ) import Data.Maybe(Maybe(Just, Nothing)) import Data.Ord(Ord) import Prelude(Show) data Command = ICUS Aviator | Dual Aviator | InCommand | InCommandInstructing Instruction | ApprovedSolo Aviator InstructionRating deriving (Command -> Command -> Bool (Command -> Command -> Bool) -> (Command -> Command -> Bool) -> Eq Command forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Command -> Command -> Bool == :: Command -> Command -> Bool $c/= :: Command -> Command -> Bool /= :: Command -> Command -> Bool Eq, Eq Command Eq Command => (Command -> Command -> Ordering) -> (Command -> Command -> Bool) -> (Command -> Command -> Bool) -> (Command -> Command -> Bool) -> (Command -> Command -> Bool) -> (Command -> Command -> Command) -> (Command -> Command -> Command) -> Ord Command Command -> Command -> Bool Command -> Command -> Ordering Command -> Command -> Command 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 :: Command -> Command -> Ordering compare :: Command -> Command -> Ordering $c< :: Command -> Command -> Bool < :: Command -> Command -> Bool $c<= :: Command -> Command -> Bool <= :: Command -> Command -> Bool $c> :: Command -> Command -> Bool > :: Command -> Command -> Bool $c>= :: Command -> Command -> Bool >= :: Command -> Command -> Bool $cmax :: Command -> Command -> Command max :: Command -> Command -> Command $cmin :: Command -> Command -> Command min :: Command -> Command -> Command Ord, Int -> Command -> ShowS [Command] -> ShowS Command -> String (Int -> Command -> ShowS) -> (Command -> String) -> ([Command] -> ShowS) -> Show Command forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Command -> ShowS showsPrec :: Int -> Command -> ShowS $cshow :: Command -> String show :: Command -> String $cshowList :: [Command] -> ShowS showList :: [Command] -> ShowS Show) makeClassyPrisms ''Command getUnderInstructionPic :: Command -> Maybe Aviator getUnderInstructionPic :: Command -> Maybe Aviator getUnderInstructionPic (ICUS Aviator a) = Aviator -> Maybe Aviator forall a. a -> Maybe a Just Aviator a getUnderInstructionPic (Dual Aviator a) = Aviator -> Maybe Aviator forall a. a -> Maybe a Just Aviator a getUnderInstructionPic Command InCommand = Maybe Aviator forall a. Maybe a Nothing getUnderInstructionPic (InCommandInstructing Instruction _) = Maybe Aviator forall a. Maybe a Nothing getUnderInstructionPic (ApprovedSolo Aviator a InstructionRating _)= Aviator -> Maybe Aviator forall a. a -> Maybe a Just Aviator a _InCommandIncludingInstructing :: AsCommand c => Prism' c (Maybe Instruction) _InCommandIncludingInstructing :: forall c. AsCommand c => Prism' c (Maybe Instruction) _InCommandIncludingInstructing = (Maybe Instruction -> c) -> (c -> Maybe (Maybe Instruction)) -> Prism c c (Maybe Instruction) (Maybe Instruction) forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b prism' (\case Maybe Instruction Nothing -> Tagged () (Identity ()) -> Tagged c (Identity c) forall r. AsCommand r => Prism' r () Prism' c () _InCommand (Tagged () (Identity ()) -> Tagged c (Identity c)) -> () -> c forall t b. AReview t b -> b -> t # () Just Instruction i -> Tagged Instruction (Identity Instruction) -> Tagged c (Identity c) forall r. AsCommand r => Prism' r Instruction Prism' c Instruction _InCommandInstructing (Tagged Instruction (Identity Instruction) -> Tagged c (Identity c)) -> Instruction -> c forall t b. AReview t b -> b -> t # Instruction i ) ( \c c -> (Maybe Instruction forall a. Maybe a Nothing Maybe Instruction -> Maybe () -> Maybe (Maybe Instruction) forall a b. a -> Maybe b -> Maybe a forall (f :: * -> *) a b. Functor f => a -> f b -> f a <$ Getting (First ()) c () -> c -> Maybe () forall s (m :: * -> *) a. MonadReader s m => Getting (First a) s a -> m (Maybe a) preview Getting (First ()) c () forall r. AsCommand r => Prism' r () Prism' c () _InCommand c c) Maybe (Maybe Instruction) -> Maybe (Maybe Instruction) -> Maybe (Maybe Instruction) forall a. Maybe a -> Maybe a -> Maybe a forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> (Instruction -> Maybe Instruction forall a. a -> Maybe a Just (Instruction -> Maybe Instruction) -> Maybe Instruction -> Maybe (Maybe Instruction) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Getting (First Instruction) c Instruction -> c -> Maybe Instruction forall s (m :: * -> *) a. MonadReader s m => Getting (First a) s a -> m (Maybe a) preview Getting (First Instruction) c Instruction forall r. AsCommand r => Prism' r Instruction Prism' c Instruction _InCommandInstructing c c) )