{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} module Data.Aviation.Casr.Logbook.Types.Location( Location(..) , HasLocation(..) ) where import Control.Lens(makeClassy) import Data.Eq(Eq) import Data.Ord(Ord) import Data.String(String) import Prelude(Show, Double) data Location = Location { Location -> String _locationname :: String , Location -> Double _locationlatitude :: Double , Location -> Double _locationlongitude :: Double } deriving (Location -> Location -> Bool (Location -> Location -> Bool) -> (Location -> Location -> Bool) -> Eq Location forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Location -> Location -> Bool == :: Location -> Location -> Bool $c/= :: Location -> Location -> Bool /= :: Location -> Location -> Bool Eq, Eq Location Eq Location => (Location -> Location -> Ordering) -> (Location -> Location -> Bool) -> (Location -> Location -> Bool) -> (Location -> Location -> Bool) -> (Location -> Location -> Bool) -> (Location -> Location -> Location) -> (Location -> Location -> Location) -> Ord Location Location -> Location -> Bool Location -> Location -> Ordering Location -> Location -> Location 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 :: Location -> Location -> Ordering compare :: Location -> Location -> Ordering $c< :: Location -> Location -> Bool < :: Location -> Location -> Bool $c<= :: Location -> Location -> Bool <= :: Location -> Location -> Bool $c> :: Location -> Location -> Bool > :: Location -> Location -> Bool $c>= :: Location -> Location -> Bool >= :: Location -> Location -> Bool $cmax :: Location -> Location -> Location max :: Location -> Location -> Location $cmin :: Location -> Location -> Location min :: Location -> Location -> Location Ord, Int -> Location -> ShowS [Location] -> ShowS Location -> String (Int -> Location -> ShowS) -> (Location -> String) -> ([Location] -> ShowS) -> Show Location forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Location -> ShowS showsPrec :: Int -> Location -> ShowS $cshow :: Location -> String show :: Location -> String $cshowList :: [Location] -> ShowS showList :: [Location] -> ShowS Show) makeClassy ''Location