{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE OverloadedStrings #-} module Data.Aviation.Stratux.Types.GpsSolution( GpsSolution(..) , AsGpsSolution(..) ) where import Control.Lens(makeClassyPrisms) import Control.Monad(Monad(return), mzero) import Data.Aeson(FromJSON(parseJSON), ToJSON(toJSON), withText, Value(String)) import Data.Eq(Eq) import Data.Ord(Ord) import Prelude(Show) -- $setup -- >>> :set -XOverloadedStrings -- >>> import Control.Lens -- >>> import Data.Aeson(decode, encode) -- >>> import Data.Maybe(Maybe) data GpsSolution = GpsSbas -- GPS + SBAS (WAAS / EGNOS) | ThreeDGPS -- 3D GPS | DeadReckoning -- Dead Reckoning | NoFix -- No Fix | Unknown -- Unknown deriving (Eq, Ord, Show) makeClassyPrisms ''GpsSolution -- | -- -- >>> decode "\"GPS + SBAS (WAAS / EGNOS)\"" :: Maybe GpsSolution -- Just GpsSbas -- -- >>> decode "\"3D GPS\"" :: Maybe GpsSolution -- Just ThreeDGPS -- -- >>> decode "\"Dead Reckoning\"" :: Maybe GpsSolution -- Just DeadReckoning -- -- >>> decode "\"No Fix\"" :: Maybe GpsSolution -- Just NoFix -- -- >>> decode "\"Unknown\"" :: Maybe GpsSolution -- Just Unknown instance FromJSON GpsSolution where parseJSON = withText "GPS_solution" (\t -> case t of "GPS + SBAS (WAAS / EGNOS)" -> return GpsSbas "3D GPS" -> return ThreeDGPS "Dead Reckoning" -> return DeadReckoning "No Fix" -> return NoFix "Unknown" -> return Unknown _ -> mzero) -- | -- -- >>> encode GpsSbas -- "\"GPS + SBAS (WAAS / EGNOS)\"" -- -- >>> encode ThreeDGPS -- "\"3D GPS\"" -- -- >>> encode DeadReckoning -- "\"Dead Reckoning\"" -- -- >>> encode NoFix -- "\"No Fix\"" -- -- >>> encode Unknown -- "\"Unknown\"" instance ToJSON GpsSolution where toJSON x = String ( case x of GpsSbas -> "GPS + SBAS (WAAS / EGNOS)" ThreeDGPS -> "3D GPS" DeadReckoning -> "Dead Reckoning" NoFix -> "No Fix" Unknown -> "Unknown" )