{-# LANGUAGE TemplateHaskell #-}
module Calamity.Types.Model.Presence.Presence (
Presence (..),
ClientStatus (..),
) where
import Calamity.Internal.Utils
import {-# SOURCE #-} Calamity.Types.Model.Guild.Guild
import Calamity.Types.Model.Presence.Activity
import Calamity.Types.Model.User
import Calamity.Types.Snowflake
import Data.Aeson ((.:), (.:?))
import Data.Aeson qualified as Aeson
import Data.Text (Text)
import Optics.TH
import TextShow.TH
data Presence = Presence
{ Presence -> Snowflake User
user :: Snowflake User
, Presence -> Snowflake Guild
guildID :: Snowflake Guild
, Presence -> StatusType
status :: StatusType
, Presence -> [Activity]
activities :: [Activity]
, Presence -> ClientStatus
clientStatus :: ClientStatus
}
deriving (Presence -> Presence -> Bool
(Presence -> Presence -> Bool)
-> (Presence -> Presence -> Bool) -> Eq Presence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Presence -> Presence -> Bool
== :: Presence -> Presence -> Bool
$c/= :: Presence -> Presence -> Bool
/= :: Presence -> Presence -> Bool
Eq, Int -> Presence -> ShowS
[Presence] -> ShowS
Presence -> String
(Int -> Presence -> ShowS)
-> (Presence -> String) -> ([Presence] -> ShowS) -> Show Presence
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Presence -> ShowS
showsPrec :: Int -> Presence -> ShowS
$cshow :: Presence -> String
show :: Presence -> String
$cshowList :: [Presence] -> ShowS
showList :: [Presence] -> ShowS
Show)
deriving (HasID User) via HasIDField "user" Presence
deriving (HasID Guild) via HasIDField "guildID" Presence
instance Aeson.FromJSON Presence where
parseJSON :: Value -> Parser Presence
parseJSON = String -> (Object -> Parser Presence) -> Value -> Parser Presence
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"Presence" ((Object -> Parser Presence) -> Value -> Parser Presence)
-> (Object -> Parser Presence) -> Value -> Parser Presence
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
Object
u :: Aeson.Object <- Object
v Object -> Key -> Parser Object
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user"
Snowflake User
-> Snowflake Guild
-> StatusType
-> [Activity]
-> ClientStatus
-> Presence
Presence
(Snowflake User
-> Snowflake Guild
-> StatusType
-> [Activity]
-> ClientStatus
-> Presence)
-> Parser (Snowflake User)
-> Parser
(Snowflake Guild
-> StatusType -> [Activity] -> ClientStatus -> Presence)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
u Object -> Key -> Parser (Snowflake User)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser
(Snowflake Guild
-> StatusType -> [Activity] -> ClientStatus -> Presence)
-> Parser (Snowflake Guild)
-> Parser (StatusType -> [Activity] -> ClientStatus -> Presence)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Snowflake Guild)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"guild_id"
Parser (StatusType -> [Activity] -> ClientStatus -> Presence)
-> Parser StatusType
-> Parser ([Activity] -> ClientStatus -> Presence)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser StatusType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"status"
Parser ([Activity] -> ClientStatus -> Presence)
-> Parser [Activity] -> Parser (ClientStatus -> Presence)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser [Activity]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"activities"
Parser (ClientStatus -> Presence)
-> Parser ClientStatus -> Parser Presence
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser ClientStatus
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"client_status"
data ClientStatus = ClientStatus
{ ClientStatus -> Maybe Text
desktop :: Maybe Text
, ClientStatus -> Maybe Text
mobile :: Maybe Text
, ClientStatus -> Maybe Text
web :: Maybe Text
}
deriving (ClientStatus -> ClientStatus -> Bool
(ClientStatus -> ClientStatus -> Bool)
-> (ClientStatus -> ClientStatus -> Bool) -> Eq ClientStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClientStatus -> ClientStatus -> Bool
== :: ClientStatus -> ClientStatus -> Bool
$c/= :: ClientStatus -> ClientStatus -> Bool
/= :: ClientStatus -> ClientStatus -> Bool
Eq, Int -> ClientStatus -> ShowS
[ClientStatus] -> ShowS
ClientStatus -> String
(Int -> ClientStatus -> ShowS)
-> (ClientStatus -> String)
-> ([ClientStatus] -> ShowS)
-> Show ClientStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClientStatus -> ShowS
showsPrec :: Int -> ClientStatus -> ShowS
$cshow :: ClientStatus -> String
show :: ClientStatus -> String
$cshowList :: [ClientStatus] -> ShowS
showList :: [ClientStatus] -> ShowS
Show)
deriving ([ClientStatus] -> Value
[ClientStatus] -> Encoding
ClientStatus -> Value
ClientStatus -> Encoding
(ClientStatus -> Value)
-> (ClientStatus -> Encoding)
-> ([ClientStatus] -> Value)
-> ([ClientStatus] -> Encoding)
-> ToJSON ClientStatus
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: ClientStatus -> Value
toJSON :: ClientStatus -> Value
$ctoEncoding :: ClientStatus -> Encoding
toEncoding :: ClientStatus -> Encoding
$ctoJSONList :: [ClientStatus] -> Value
toJSONList :: [ClientStatus] -> Value
$ctoEncodingList :: [ClientStatus] -> Encoding
toEncodingList :: [ClientStatus] -> Encoding
Aeson.ToJSON) via CalamityToJSON ClientStatus
instance CalamityToJSON' ClientStatus where
toPairs :: forall kv. KeyValue kv => ClientStatus -> [Maybe kv]
toPairs ClientStatus {Maybe Text
$sel:desktop:ClientStatus :: ClientStatus -> Maybe Text
$sel:mobile:ClientStatus :: ClientStatus -> Maybe Text
$sel:web:ClientStatus :: ClientStatus -> Maybe Text
desktop :: Maybe Text
mobile :: Maybe Text
web :: Maybe Text
..} =
[ Key
"desktop" Key -> Maybe Text -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe Text
desktop
, Key
"mobile" Key -> Maybe Text -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe Text
mobile
, Key
"web" Key -> Maybe Text -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe Text
web
]
instance Aeson.FromJSON ClientStatus where
parseJSON :: Value -> Parser ClientStatus
parseJSON = String
-> (Object -> Parser ClientStatus) -> Value -> Parser ClientStatus
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"ClientStatus" ((Object -> Parser ClientStatus) -> Value -> Parser ClientStatus)
-> (Object -> Parser ClientStatus) -> Value -> Parser ClientStatus
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Maybe Text -> Maybe Text -> Maybe Text -> ClientStatus
ClientStatus
(Maybe Text -> Maybe Text -> Maybe Text -> ClientStatus)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Maybe Text -> ClientStatus)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"desktop"
Parser (Maybe Text -> Maybe Text -> ClientStatus)
-> Parser (Maybe Text) -> Parser (Maybe Text -> ClientStatus)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"mobile"
Parser (Maybe Text -> ClientStatus)
-> Parser (Maybe Text) -> Parser ClientStatus
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"web"
$(deriveTextShow ''ClientStatus)
$(deriveTextShow ''Presence)
$(makeFieldLabelsNoPrefix ''Presence)
$(makeFieldLabelsNoPrefix ''ClientStatus)