{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module Data.Aviation.Casr.Logbook.Meta.TrackLogs( TrackLogs(TrackLogs) , HasTrackLogs(..) ) where import Control.Lens(makeClassy, makeWrapped) import Data.Aviation.Casr.Logbook.Meta.TrackLog ( TrackLog ) import Data.Eq(Eq) import Data.Monoid ( (<>), Monoid(mempty) ) import Data.Ord(Ord) import Data.Semigroup ( Semigroup ) import Prelude(Show) newtype TrackLogs = TrackLogs [TrackLog] deriving (TrackLogs -> TrackLogs -> Bool (TrackLogs -> TrackLogs -> Bool) -> (TrackLogs -> TrackLogs -> Bool) -> Eq TrackLogs forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: TrackLogs -> TrackLogs -> Bool == :: TrackLogs -> TrackLogs -> Bool $c/= :: TrackLogs -> TrackLogs -> Bool /= :: TrackLogs -> TrackLogs -> Bool Eq, Eq TrackLogs Eq TrackLogs => (TrackLogs -> TrackLogs -> Ordering) -> (TrackLogs -> TrackLogs -> Bool) -> (TrackLogs -> TrackLogs -> Bool) -> (TrackLogs -> TrackLogs -> Bool) -> (TrackLogs -> TrackLogs -> Bool) -> (TrackLogs -> TrackLogs -> TrackLogs) -> (TrackLogs -> TrackLogs -> TrackLogs) -> Ord TrackLogs TrackLogs -> TrackLogs -> Bool TrackLogs -> TrackLogs -> Ordering TrackLogs -> TrackLogs -> TrackLogs 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 :: TrackLogs -> TrackLogs -> Ordering compare :: TrackLogs -> TrackLogs -> Ordering $c< :: TrackLogs -> TrackLogs -> Bool < :: TrackLogs -> TrackLogs -> Bool $c<= :: TrackLogs -> TrackLogs -> Bool <= :: TrackLogs -> TrackLogs -> Bool $c> :: TrackLogs -> TrackLogs -> Bool > :: TrackLogs -> TrackLogs -> Bool $c>= :: TrackLogs -> TrackLogs -> Bool >= :: TrackLogs -> TrackLogs -> Bool $cmax :: TrackLogs -> TrackLogs -> TrackLogs max :: TrackLogs -> TrackLogs -> TrackLogs $cmin :: TrackLogs -> TrackLogs -> TrackLogs min :: TrackLogs -> TrackLogs -> TrackLogs Ord, Int -> TrackLogs -> ShowS [TrackLogs] -> ShowS TrackLogs -> String (Int -> TrackLogs -> ShowS) -> (TrackLogs -> String) -> ([TrackLogs] -> ShowS) -> Show TrackLogs forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> TrackLogs -> ShowS showsPrec :: Int -> TrackLogs -> ShowS $cshow :: TrackLogs -> String show :: TrackLogs -> String $cshowList :: [TrackLogs] -> ShowS showList :: [TrackLogs] -> ShowS Show) makeClassy ''TrackLogs makeWrapped ''TrackLogs instance Semigroup TrackLogs where TrackLogs [TrackLog] x <> :: TrackLogs -> TrackLogs -> TrackLogs <> TrackLogs [TrackLog] y = [TrackLog] -> TrackLogs TrackLogs ([TrackLog] x [TrackLog] -> [TrackLog] -> [TrackLog] forall a. Semigroup a => a -> a -> a <> [TrackLog] y) instance Monoid TrackLogs where mempty :: TrackLogs mempty = [TrackLog] -> TrackLogs TrackLogs [TrackLog] forall a. Monoid a => a mempty