module HomeAssistant.Types (
JSONOptions,
UnitSystem(..),
Config(..),
Service(..),
ServiceDomain(..)
) where
import Data.Aeson
import Data.Text
import Data.Map.Lazy qualified as M
import Deriving.Aeson
import GHC.TypeLits
type JSONOptions (prefix :: Symbol) =
'[OmitNothingFields, FieldLabelModifier '[StripPrefix prefix, CamelToSnake]]
data UnitSystem = MkUnitSystem {
UnitSystem -> Text
unitSystemLength :: Text,
UnitSystem -> Text
unitSystemMass :: Text,
UnitSystem -> Text
unitSystemTemperature :: Text,
UnitSystem -> Text
unitSystemVolume :: Text
} deriving ((forall x. UnitSystem -> Rep UnitSystem x)
-> (forall x. Rep UnitSystem x -> UnitSystem) -> Generic UnitSystem
forall x. Rep UnitSystem x -> UnitSystem
forall x. UnitSystem -> Rep UnitSystem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UnitSystem -> Rep UnitSystem x
from :: forall x. UnitSystem -> Rep UnitSystem x
$cto :: forall x. Rep UnitSystem x -> UnitSystem
to :: forall x. Rep UnitSystem x -> UnitSystem
Generic, UnitSystem -> UnitSystem -> Bool
(UnitSystem -> UnitSystem -> Bool)
-> (UnitSystem -> UnitSystem -> Bool) -> Eq UnitSystem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnitSystem -> UnitSystem -> Bool
== :: UnitSystem -> UnitSystem -> Bool
$c/= :: UnitSystem -> UnitSystem -> Bool
/= :: UnitSystem -> UnitSystem -> Bool
Eq, Int -> UnitSystem -> ShowS
[UnitSystem] -> ShowS
UnitSystem -> String
(Int -> UnitSystem -> ShowS)
-> (UnitSystem -> String)
-> ([UnitSystem] -> ShowS)
-> Show UnitSystem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnitSystem -> ShowS
showsPrec :: Int -> UnitSystem -> ShowS
$cshow :: UnitSystem -> String
show :: UnitSystem -> String
$cshowList :: [UnitSystem] -> ShowS
showList :: [UnitSystem] -> ShowS
Show)
deriving (Maybe UnitSystem
Value -> Parser [UnitSystem]
Value -> Parser UnitSystem
(Value -> Parser UnitSystem)
-> (Value -> Parser [UnitSystem])
-> Maybe UnitSystem
-> FromJSON UnitSystem
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UnitSystem
parseJSON :: Value -> Parser UnitSystem
$cparseJSONList :: Value -> Parser [UnitSystem]
parseJSONList :: Value -> Parser [UnitSystem]
$comittedField :: Maybe UnitSystem
omittedField :: Maybe UnitSystem
FromJSON, [UnitSystem] -> Value
[UnitSystem] -> Encoding
UnitSystem -> Bool
UnitSystem -> Value
UnitSystem -> Encoding
(UnitSystem -> Value)
-> (UnitSystem -> Encoding)
-> ([UnitSystem] -> Value)
-> ([UnitSystem] -> Encoding)
-> (UnitSystem -> Bool)
-> ToJSON UnitSystem
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UnitSystem -> Value
toJSON :: UnitSystem -> Value
$ctoEncoding :: UnitSystem -> Encoding
toEncoding :: UnitSystem -> Encoding
$ctoJSONList :: [UnitSystem] -> Value
toJSONList :: [UnitSystem] -> Value
$ctoEncodingList :: [UnitSystem] -> Encoding
toEncodingList :: [UnitSystem] -> Encoding
$comitField :: UnitSystem -> Bool
omitField :: UnitSystem -> Bool
ToJSON) via CustomJSON (JSONOptions "unitSystem") UnitSystem
data Config = MkConfig {
Config -> [Text]
configComponents :: [Text],
Config -> Text
configConfigDir :: Text,
Config -> Text
configLocationName :: Text,
Config -> Text
configTimeZone :: Text,
Config -> Int
configElevation :: Int,
Config -> Double
configLatitude :: Double,
Config -> Double
configLongitude :: Double,
Config -> UnitSystem
configUnitSystem :: UnitSystem,
Config -> Text
configVersion :: Text,
Config -> [Text]
configWhitelistExternalDirs :: [Text]
} deriving ((forall x. Config -> Rep Config x)
-> (forall x. Rep Config x -> Config) -> Generic Config
forall x. Rep Config x -> Config
forall x. Config -> Rep Config x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Config -> Rep Config x
from :: forall x. Config -> Rep Config x
$cto :: forall x. Rep Config x -> Config
to :: forall x. Rep Config x -> Config
Generic, Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
/= :: Config -> Config -> Bool
Eq, Int -> Config -> ShowS
[Config] -> ShowS
Config -> String
(Int -> Config -> ShowS)
-> (Config -> String) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Config -> ShowS
showsPrec :: Int -> Config -> ShowS
$cshow :: Config -> String
show :: Config -> String
$cshowList :: [Config] -> ShowS
showList :: [Config] -> ShowS
Show)
deriving (Maybe Config
Value -> Parser [Config]
Value -> Parser Config
(Value -> Parser Config)
-> (Value -> Parser [Config]) -> Maybe Config -> FromJSON Config
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Config
parseJSON :: Value -> Parser Config
$cparseJSONList :: Value -> Parser [Config]
parseJSONList :: Value -> Parser [Config]
$comittedField :: Maybe Config
omittedField :: Maybe Config
FromJSON, [Config] -> Value
[Config] -> Encoding
Config -> Bool
Config -> Value
Config -> Encoding
(Config -> Value)
-> (Config -> Encoding)
-> ([Config] -> Value)
-> ([Config] -> Encoding)
-> (Config -> Bool)
-> ToJSON Config
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Config -> Value
toJSON :: Config -> Value
$ctoEncoding :: Config -> Encoding
toEncoding :: Config -> Encoding
$ctoJSONList :: [Config] -> Value
toJSONList :: [Config] -> Value
$ctoEncodingList :: [Config] -> Encoding
toEncodingList :: [Config] -> Encoding
$comitField :: Config -> Bool
omitField :: Config -> Bool
ToJSON) via CustomJSON (JSONOptions "config") Config
data Service = MkService {
Service -> Text
serviceName :: Text,
Service -> Text
serviceDescription :: Text,
Service -> Map Text Value
serviceFields :: M.Map Text Value
} deriving ((forall x. Service -> Rep Service x)
-> (forall x. Rep Service x -> Service) -> Generic Service
forall x. Rep Service x -> Service
forall x. Service -> Rep Service x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Service -> Rep Service x
from :: forall x. Service -> Rep Service x
$cto :: forall x. Rep Service x -> Service
to :: forall x. Rep Service x -> Service
Generic, Service -> Service -> Bool
(Service -> Service -> Bool)
-> (Service -> Service -> Bool) -> Eq Service
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Service -> Service -> Bool
== :: Service -> Service -> Bool
$c/= :: Service -> Service -> Bool
/= :: Service -> Service -> Bool
Eq, Int -> Service -> ShowS
[Service] -> ShowS
Service -> String
(Int -> Service -> ShowS)
-> (Service -> String) -> ([Service] -> ShowS) -> Show Service
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Service -> ShowS
showsPrec :: Int -> Service -> ShowS
$cshow :: Service -> String
show :: Service -> String
$cshowList :: [Service] -> ShowS
showList :: [Service] -> ShowS
Show)
deriving (Maybe Service
Value -> Parser [Service]
Value -> Parser Service
(Value -> Parser Service)
-> (Value -> Parser [Service]) -> Maybe Service -> FromJSON Service
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Service
parseJSON :: Value -> Parser Service
$cparseJSONList :: Value -> Parser [Service]
parseJSONList :: Value -> Parser [Service]
$comittedField :: Maybe Service
omittedField :: Maybe Service
FromJSON, [Service] -> Value
[Service] -> Encoding
Service -> Bool
Service -> Value
Service -> Encoding
(Service -> Value)
-> (Service -> Encoding)
-> ([Service] -> Value)
-> ([Service] -> Encoding)
-> (Service -> Bool)
-> ToJSON Service
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Service -> Value
toJSON :: Service -> Value
$ctoEncoding :: Service -> Encoding
toEncoding :: Service -> Encoding
$ctoJSONList :: [Service] -> Value
toJSONList :: [Service] -> Value
$ctoEncodingList :: [Service] -> Encoding
toEncodingList :: [Service] -> Encoding
$comitField :: Service -> Bool
omitField :: Service -> Bool
ToJSON) via CustomJSON (JSONOptions "service") Service
data ServiceDomain = MkServiceDomain {
ServiceDomain -> Text
sdDomain :: Text,
ServiceDomain -> Map Text Service
sdServices :: M.Map Text Service
} deriving ((forall x. ServiceDomain -> Rep ServiceDomain x)
-> (forall x. Rep ServiceDomain x -> ServiceDomain)
-> Generic ServiceDomain
forall x. Rep ServiceDomain x -> ServiceDomain
forall x. ServiceDomain -> Rep ServiceDomain x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ServiceDomain -> Rep ServiceDomain x
from :: forall x. ServiceDomain -> Rep ServiceDomain x
$cto :: forall x. Rep ServiceDomain x -> ServiceDomain
to :: forall x. Rep ServiceDomain x -> ServiceDomain
Generic, ServiceDomain -> ServiceDomain -> Bool
(ServiceDomain -> ServiceDomain -> Bool)
-> (ServiceDomain -> ServiceDomain -> Bool) -> Eq ServiceDomain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServiceDomain -> ServiceDomain -> Bool
== :: ServiceDomain -> ServiceDomain -> Bool
$c/= :: ServiceDomain -> ServiceDomain -> Bool
/= :: ServiceDomain -> ServiceDomain -> Bool
Eq, Int -> ServiceDomain -> ShowS
[ServiceDomain] -> ShowS
ServiceDomain -> String
(Int -> ServiceDomain -> ShowS)
-> (ServiceDomain -> String)
-> ([ServiceDomain] -> ShowS)
-> Show ServiceDomain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServiceDomain -> ShowS
showsPrec :: Int -> ServiceDomain -> ShowS
$cshow :: ServiceDomain -> String
show :: ServiceDomain -> String
$cshowList :: [ServiceDomain] -> ShowS
showList :: [ServiceDomain] -> ShowS
Show)
deriving (Maybe ServiceDomain
Value -> Parser [ServiceDomain]
Value -> Parser ServiceDomain
(Value -> Parser ServiceDomain)
-> (Value -> Parser [ServiceDomain])
-> Maybe ServiceDomain
-> FromJSON ServiceDomain
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ServiceDomain
parseJSON :: Value -> Parser ServiceDomain
$cparseJSONList :: Value -> Parser [ServiceDomain]
parseJSONList :: Value -> Parser [ServiceDomain]
$comittedField :: Maybe ServiceDomain
omittedField :: Maybe ServiceDomain
FromJSON, [ServiceDomain] -> Value
[ServiceDomain] -> Encoding
ServiceDomain -> Bool
ServiceDomain -> Value
ServiceDomain -> Encoding
(ServiceDomain -> Value)
-> (ServiceDomain -> Encoding)
-> ([ServiceDomain] -> Value)
-> ([ServiceDomain] -> Encoding)
-> (ServiceDomain -> Bool)
-> ToJSON ServiceDomain
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ServiceDomain -> Value
toJSON :: ServiceDomain -> Value
$ctoEncoding :: ServiceDomain -> Encoding
toEncoding :: ServiceDomain -> Encoding
$ctoJSONList :: [ServiceDomain] -> Value
toJSONList :: [ServiceDomain] -> Value
$ctoEncodingList :: [ServiceDomain] -> Encoding
toEncodingList :: [ServiceDomain] -> Encoding
$comitField :: ServiceDomain -> Bool
omitField :: ServiceDomain -> Bool
ToJSON) via CustomJSON (JSONOptions "sd") ServiceDomain