{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE OverloadedStrings #-} module Data.Aviation.Stratux.Types.Settings( Settings(..) , HasSettings(..) ) where import Control.Applicative((<*>)) import Control.Lens(makeClassy) import Data.Aeson(FromJSON(parseJSON), ToJSON(toJSON), (.:), (.=), object, withObject) import Data.Aviation.Stratux.Types.NetworkConnection import Data.Bool(Bool) import Data.Eq(Eq) import Data.Functor((<$>)) import Data.Int(Int) import Data.Ord(Ord) import Data.String(String) import Prelude(Show) -- $setup -- >>> :set -XOverloadedStrings -- >>> import Control.Lens -- >>> import Data.Aeson(decode, encode) -- >>> import Data.Maybe(Maybe) -- >>> import Data.Time -- >>> import Prelude data Settings = Settings { _uatEnabled :: Bool , _esEnabled :: Bool , _gpsEnabled :: Bool , _networkOutputs :: [NetworkConnection] , _ahrsEnabled :: Bool , _debug :: Bool , _replayLog :: Bool , _ppm :: Int , _ownshipModeS :: String , _watchList :: String } deriving (Eq, Ord, Show) makeClassy ''Settings -- | -- -- >>> decode "{\"UAT_Enabled\":true,\"ES_Enabled\":true,\"GPS_Enabled\":true,\"NetworkOutputs\":[{\"Conn\":null,\"Ip\":\"\",\"Port\":4000,\"Capability\":5,\"LastUnreachable\":\"0001-01-01T00:00:00Z\",\"SleepFlag\":false}],\"AHRS_Enabled\":false,\"DEBUG\":false,\"ReplayLog\":true,\"PPM\":0,\"OwnshipModeS\":\"F00000\",\"WatchList\":\"\"}" :: Maybe Settings -- Just (Settings {_uatEnabled = True, _esEnabled = True, _gpsEnabled = True, _networkOutputs = [NetworkConnection {_conn = Nothing, _ip = "", _port = 4000, _capability = 5, _lastUnreachable = 0001-01-01 00:00:00 UTC, _sleepFlag = False}], _ahrsEnabled = False, _debug = False, _replayLog = True, _ppm = 0, _ownshipModeS = "F00000", _watchList = ""}) instance FromJSON Settings where parseJSON = withObject "Settings" (\x -> Settings <$> x .: "UAT_Enabled" <*> x .: "ES_Enabled" <*> x .: "GPS_Enabled" <*> x .: "NetworkOutputs" <*> x .: "AHRS_Enabled" <*> x .: "DEBUG" <*> x .: "ReplayLog" <*> x .: "PPM" <*> x .: "OwnshipModeS" <*> x .: "WatchList" ) -- | -- -- >>> encode (Settings True True True [NetworkConnection Nothing "" 4000 5 (UTCTime (fromGregorian 1 1 1) 597) False] False False True 0 "F00000" "") -- "{\"OwnshipModeS\":\"F00000\",\"AHRS_Enabled\":false,\"NetworkOutputs\":[{\"Ip\":\"\",\"Conn\":null,\"Capability\":5,\"SleepFlag\":false,\"LastUnreachable\":\"0001-01-01T00:09:57Z\",\"Port\":4000}],\"PPM\":0,\"GPS_Enabled\":true,\"DEBUG\":false,\"ES_Enabled\":true,\"ReplayLog\":true,\"UAT_Enabled\":true,\"WatchList\":\"\"}" instance ToJSON Settings where toJSON (Settings uatEnabled_ esEnabled_ gpsEnabled_ networkOutputs_ ahrsEnabled_ debug_ replayLog_ ppm_ ownshipModeS_ watchList_) = object [ "UAT_Enabled" .= uatEnabled_ , "ES_Enabled" .= esEnabled_ , "GPS_Enabled" .= gpsEnabled_ , "NetworkOutputs" .= networkOutputs_ , "AHRS_Enabled" .= ahrsEnabled_ , "DEBUG" .= debug_ , "ReplayLog" .= replayLog_ , "PPM" .= ppm_ , "OwnshipModeS" .= ownshipModeS_ , "WatchList" .= watchList_ ]