{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.Casr.Logbook.Types.FlightPath( FlightPath(..) , HasFlightPath(..) , directflightpath , directcircuit , pointsatdate , flightPathList , circuitsatdate ) where import Control.Lens(makeClassy) import Data.Aviation.Casr.Logbook.Types.FlightPoint(FlightPoint, pointatdate) import Data.Eq(Eq) import Data.Functor((<$>)) import Data.Int(Int) import Data.List((++), replicate) import Data.Ord(Ord) import Data.String(String) import Data.Time(Day) import Prelude(Show) data FlightPath = FlightPath { FlightPath -> FlightPoint _flightStart :: FlightPoint , FlightPath -> [FlightPoint] _flightIntermediate :: [FlightPoint] , FlightPath -> FlightPoint _flightEnd :: FlightPoint } deriving (FlightPath -> FlightPath -> Bool (FlightPath -> FlightPath -> Bool) -> (FlightPath -> FlightPath -> Bool) -> Eq FlightPath forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: FlightPath -> FlightPath -> Bool == :: FlightPath -> FlightPath -> Bool $c/= :: FlightPath -> FlightPath -> Bool /= :: FlightPath -> FlightPath -> Bool Eq, Eq FlightPath Eq FlightPath => (FlightPath -> FlightPath -> Ordering) -> (FlightPath -> FlightPath -> Bool) -> (FlightPath -> FlightPath -> Bool) -> (FlightPath -> FlightPath -> Bool) -> (FlightPath -> FlightPath -> Bool) -> (FlightPath -> FlightPath -> FlightPath) -> (FlightPath -> FlightPath -> FlightPath) -> Ord FlightPath FlightPath -> FlightPath -> Bool FlightPath -> FlightPath -> Ordering FlightPath -> FlightPath -> FlightPath 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 :: FlightPath -> FlightPath -> Ordering compare :: FlightPath -> FlightPath -> Ordering $c< :: FlightPath -> FlightPath -> Bool < :: FlightPath -> FlightPath -> Bool $c<= :: FlightPath -> FlightPath -> Bool <= :: FlightPath -> FlightPath -> Bool $c> :: FlightPath -> FlightPath -> Bool > :: FlightPath -> FlightPath -> Bool $c>= :: FlightPath -> FlightPath -> Bool >= :: FlightPath -> FlightPath -> Bool $cmax :: FlightPath -> FlightPath -> FlightPath max :: FlightPath -> FlightPath -> FlightPath $cmin :: FlightPath -> FlightPath -> FlightPath min :: FlightPath -> FlightPath -> FlightPath Ord, Int -> FlightPath -> ShowS [FlightPath] -> ShowS FlightPath -> String (Int -> FlightPath -> ShowS) -> (FlightPath -> String) -> ([FlightPath] -> ShowS) -> Show FlightPath forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> FlightPath -> ShowS showsPrec :: Int -> FlightPath -> ShowS $cshow :: FlightPath -> String show :: FlightPath -> String $cshowList :: [FlightPath] -> ShowS showList :: [FlightPath] -> ShowS Show) makeClassy ''FlightPath directflightpath :: FlightPoint -> FlightPoint -> FlightPath directflightpath :: FlightPoint -> FlightPoint -> FlightPath directflightpath FlightPoint x FlightPoint y = FlightPoint -> [FlightPoint] -> FlightPoint -> FlightPath FlightPath FlightPoint x [] FlightPoint y directcircuit :: FlightPoint -> FlightPath directcircuit :: FlightPoint -> FlightPath directcircuit FlightPoint x = FlightPoint -> FlightPoint -> FlightPath directflightpath FlightPoint x FlightPoint x pointsatdate :: String -> [String] -> String -> Day -> FlightPath pointsatdate :: String -> [String] -> String -> Day -> FlightPath pointsatdate String x [String] i String y Day d = FlightPoint -> [FlightPoint] -> FlightPoint -> FlightPath FlightPath (String -> Day -> FlightPoint pointatdate String x Day d) ((\String s -> String -> Day -> FlightPoint pointatdate String s Day d) (String -> FlightPoint) -> [String] -> [FlightPoint] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> [String] i) (String -> Day -> FlightPoint pointatdate String y Day d) flightPathList :: FlightPath -> [FlightPoint] flightPathList :: FlightPath -> [FlightPoint] flightPathList (FlightPath FlightPoint s [FlightPoint] x FlightPoint e) = FlightPoint s FlightPoint -> [FlightPoint] -> [FlightPoint] forall a. a -> [a] -> [a] : [FlightPoint] x [FlightPoint] -> [FlightPoint] -> [FlightPoint] forall a. [a] -> [a] -> [a] ++ [FlightPoint e] circuitsatdate :: String -> Int -> Day -> FlightPath circuitsatdate :: String -> Int -> Day -> FlightPath circuitsatdate String x Int n Day d = FlightPoint -> [FlightPoint] -> FlightPoint -> FlightPath FlightPath (String -> Day -> FlightPoint pointatdate String x Day d) (Int -> FlightPoint -> [FlightPoint] forall a. Int -> a -> [a] replicate Int n (String -> Day -> FlightPoint pointatdate String x Day d)) (String -> Day -> FlightPoint pointatdate String x Day d)