{-# LANGUAGE TemplateHaskell #-}
module Calamity.Types.Model.User (
User (..),
UserBanner (..),
Partial (PartialUser),
StatusType (..),
) where
import Calamity.Internal.IntColour
import Calamity.Types.CDNAsset (CDNAsset (..))
import Calamity.Types.Model.Avatar
import {-# SOURCE #-} Calamity.Types.Model.Guild.Member
import Calamity.Types.Partial
import Calamity.Types.Snowflake
import Calamity.Utils.CDNUrl (assetHashFile, cdnURL)
import Data.Aeson ((.:), (.:?))
import Data.Aeson qualified as Aeson
import Data.Colour (Colour)
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.Read (decimal)
import Data.Word
import Network.HTTP.Req ((/:), (/~))
import Optics.TH
import TextShow qualified
import TextShow.TH
data UserBanner = UserBanner
{ UserBanner -> Snowflake User
userID :: Snowflake User
, UserBanner -> Text
hash :: T.Text
}
deriving (Int -> UserBanner -> ShowS
[UserBanner] -> ShowS
UserBanner -> String
(Int -> UserBanner -> ShowS)
-> (UserBanner -> String)
-> ([UserBanner] -> ShowS)
-> Show UserBanner
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserBanner -> ShowS
showsPrec :: Int -> UserBanner -> ShowS
$cshow :: UserBanner -> String
show :: UserBanner -> String
$cshowList :: [UserBanner] -> ShowS
showList :: [UserBanner] -> ShowS
Show, UserBanner -> UserBanner -> Bool
(UserBanner -> UserBanner -> Bool)
-> (UserBanner -> UserBanner -> Bool) -> Eq UserBanner
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UserBanner -> UserBanner -> Bool
== :: UserBanner -> UserBanner -> Bool
$c/= :: UserBanner -> UserBanner -> Bool
/= :: UserBanner -> UserBanner -> Bool
Eq)
instance CDNAsset UserBanner where
assetURL :: UserBanner -> Url 'Https
assetURL UserBanner {Text
$sel:hash:UserBanner :: UserBanner -> Text
hash :: Text
hash, Snowflake User
$sel:userID:UserBanner :: UserBanner -> Snowflake User
userID :: Snowflake User
userID} =
Url 'Https
cdnURL Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text
"banners" Url 'Https -> Snowflake User -> Url 'Https
forall a (scheme :: Scheme).
ToHttpApiData a =>
Url scheme -> a -> Url scheme
/~ Snowflake User
userID Url 'Https -> Text -> Url 'Https
forall (scheme :: Scheme). Url scheme -> Text -> Url scheme
/: Text -> Text
assetHashFile Text
hash
data User = User
{ User -> Snowflake User
id :: Snowflake User
, User -> Text
username :: Text
, User -> Text
discriminator :: Text
, User -> Maybe Bool
bot :: Maybe Bool
, User -> Avatar
avatar :: Avatar
, User -> Maybe Bool
mfaEnabled :: Maybe Bool
, User -> Maybe UserBanner
banner :: Maybe UserBanner
, User -> Maybe (Colour Double)
accentColour :: Maybe (Colour Double)
, User -> Maybe Text
locale :: Maybe Text
, User -> Maybe Bool
verified :: Maybe Bool
, User -> Maybe Text
email :: Maybe Text
, User -> Maybe Word64
flags :: Maybe Word64
, User -> Maybe Word64
premiumType :: Maybe Word64
}
deriving (Int -> User -> ShowS
[User] -> ShowS
User -> String
(Int -> User -> ShowS)
-> (User -> String) -> ([User] -> ShowS) -> Show User
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> User -> ShowS
showsPrec :: Int -> User -> ShowS
$cshow :: User -> String
show :: User -> String
$cshowList :: [User] -> ShowS
showList :: [User] -> ShowS
Show, User -> User -> Bool
(User -> User -> Bool) -> (User -> User -> Bool) -> Eq User
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: User -> User -> Bool
== :: User -> User -> Bool
$c/= :: User -> User -> Bool
/= :: User -> User -> Bool
Eq)
deriving (Int -> User -> Text
Int -> User -> Builder
Int -> User -> Text
[User] -> Text
[User] -> Builder
[User] -> Text
User -> Text
User -> Builder
User -> Text
(Int -> User -> Builder)
-> (User -> Builder)
-> ([User] -> Builder)
-> (Int -> User -> Text)
-> (User -> Text)
-> ([User] -> Text)
-> (Int -> User -> Text)
-> (User -> Text)
-> ([User] -> Text)
-> TextShow User
forall a.
(Int -> a -> Builder)
-> (a -> Builder)
-> ([a] -> Builder)
-> (Int -> a -> Text)
-> (a -> Text)
-> ([a] -> Text)
-> (Int -> a -> Text)
-> (a -> Text)
-> ([a] -> Text)
-> TextShow a
$cshowbPrec :: Int -> User -> Builder
showbPrec :: Int -> User -> Builder
$cshowb :: User -> Builder
showb :: User -> Builder
$cshowbList :: [User] -> Builder
showbList :: [User] -> Builder
$cshowtPrec :: Int -> User -> Text
showtPrec :: Int -> User -> Text
$cshowt :: User -> Text
showt :: User -> Text
$cshowtList :: [User] -> Text
showtList :: [User] -> Text
$cshowtlPrec :: Int -> User -> Text
showtlPrec :: Int -> User -> Text
$cshowtl :: User -> Text
showtl :: User -> Text
$cshowtlList :: [User] -> Text
showtlList :: [User] -> Text
TextShow.TextShow) via TextShow.FromStringShow User
deriving (HasID User) via HasIDField "id" User
deriving (HasID Member) via HasIDFieldCoerce' "id" User
instance Aeson.FromJSON User where
parseJSON :: Value -> Parser User
parseJSON = String -> (Object -> Parser User) -> Value -> Parser User
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"User" ((Object -> Parser User) -> Value -> Parser User)
-> (Object -> Parser User) -> Value -> Parser User
forall a b. (a -> b) -> a -> b
$ \Object
v -> do
Snowflake User
uid <- Object
v Object -> Key -> Parser (Snowflake User)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Maybe Text
avatarHash <- Object
v Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"avatar"
Text
discrim <- Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"discriminator"
Int
discrim' <- case Reader Int
forall a. Integral a => Reader a
decimal Text
discrim of
Right (Int
n, Text
_) -> Int -> Parser Int
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
n
Left String
e -> String -> Parser Int
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
e
let avatar :: Avatar
avatar = Maybe Text -> Snowflake User -> Int -> Avatar
Avatar Maybe Text
avatarHash Snowflake User
uid Int
discrim'
Maybe UserBanner
banner <- (Snowflake User -> Text -> UserBanner
UserBanner Snowflake User
uid (Text -> UserBanner) -> Maybe Text -> Maybe UserBanner
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Maybe Text -> Maybe UserBanner)
-> Parser (Maybe Text) -> Parser (Maybe UserBanner)
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
"banner"
Snowflake User
-> Text
-> Text
-> Maybe Bool
-> Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User
User
(Snowflake User
-> Text
-> Text
-> Maybe Bool
-> Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
-> Parser (Snowflake User)
-> Parser
(Text
-> Text
-> Maybe Bool
-> Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Snowflake User -> Parser (Snowflake User)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Snowflake User
uid
Parser
(Text
-> Text
-> Maybe Bool
-> Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
-> Parser Text
-> Parser
(Text
-> Maybe Bool
-> Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
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 Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"username"
Parser
(Text
-> Maybe Bool
-> Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
-> Parser Text
-> Parser
(Maybe Bool
-> Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
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 Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"discriminator"
Parser
(Maybe Bool
-> Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
-> Parser (Maybe Bool)
-> Parser
(Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
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 Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"bot"
Parser
(Avatar
-> Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
-> Parser Avatar
-> Parser
(Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Avatar -> Parser Avatar
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Avatar
avatar
Parser
(Maybe Bool
-> Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
-> Parser (Maybe Bool)
-> Parser
(Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
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 Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"mfa_enabled"
Parser
(Maybe UserBanner
-> Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
-> Parser (Maybe UserBanner)
-> Parser
(Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe UserBanner -> Parser (Maybe UserBanner)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe UserBanner
banner
Parser
(Maybe (Colour Double)
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
-> Parser (Maybe (Colour Double))
-> Parser
(Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((IntColour -> Colour Double)
-> Maybe IntColour -> Maybe (Colour Double)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IntColour -> Colour Double
fromIntColour (Maybe IntColour -> Maybe (Colour Double))
-> Parser (Maybe IntColour) -> Parser (Maybe (Colour Double))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe IntColour)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"accent_color")
Parser
(Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Word64
-> Maybe Word64
-> User)
-> Parser (Maybe Text)
-> Parser
(Maybe Bool -> Maybe Text -> Maybe Word64 -> Maybe Word64 -> User)
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
"locale"
Parser
(Maybe Bool -> Maybe Text -> Maybe Word64 -> Maybe Word64 -> User)
-> Parser (Maybe Bool)
-> Parser (Maybe Text -> Maybe Word64 -> Maybe Word64 -> User)
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 Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"verified"
Parser (Maybe Text -> Maybe Word64 -> Maybe Word64 -> User)
-> Parser (Maybe Text)
-> Parser (Maybe Word64 -> Maybe Word64 -> User)
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
"email"
Parser (Maybe Word64 -> Maybe Word64 -> User)
-> Parser (Maybe Word64) -> Parser (Maybe Word64 -> User)
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 Word64)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"flags"
Parser (Maybe Word64 -> User)
-> Parser (Maybe Word64) -> Parser User
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 Word64)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"premium_type"
newtype instance Partial User = PartialUser
{ Partial User -> Snowflake User
id :: Snowflake User
}
deriving stock (Int -> Partial User -> ShowS
[Partial User] -> ShowS
Partial User -> String
(Int -> Partial User -> ShowS)
-> (Partial User -> String)
-> ([Partial User] -> ShowS)
-> Show (Partial User)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Partial User -> ShowS
showsPrec :: Int -> Partial User -> ShowS
$cshow :: Partial User -> String
show :: Partial User -> String
$cshowList :: [Partial User] -> ShowS
showList :: [Partial User] -> ShowS
Show, Partial User -> Partial User -> Bool
(Partial User -> Partial User -> Bool)
-> (Partial User -> Partial User -> Bool) -> Eq (Partial User)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Partial User -> Partial User -> Bool
== :: Partial User -> Partial User -> Bool
$c/= :: Partial User -> Partial User -> Bool
/= :: Partial User -> Partial User -> Bool
Eq)
deriving (HasID User) via HasIDField "id" (Partial User)
instance Aeson.FromJSON (Partial User) where
parseJSON :: Value -> Parser (Partial User)
parseJSON = String
-> (Object -> Parser (Partial User))
-> Value
-> Parser (Partial User)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"Partial User" ((Object -> Parser (Partial User))
-> Value -> Parser (Partial User))
-> (Object -> Parser (Partial User))
-> Value
-> Parser (Partial User)
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Snowflake User -> Partial User
PartialUser (Snowflake User -> Partial User)
-> Parser (Snowflake User) -> Parser (Partial User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Snowflake User)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
data StatusType
= Idle
| DND
| Online
| Offline
| Invisible
deriving (StatusType -> StatusType -> Bool
(StatusType -> StatusType -> Bool)
-> (StatusType -> StatusType -> Bool) -> Eq StatusType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StatusType -> StatusType -> Bool
== :: StatusType -> StatusType -> Bool
$c/= :: StatusType -> StatusType -> Bool
/= :: StatusType -> StatusType -> Bool
Eq, Int -> StatusType -> ShowS
[StatusType] -> ShowS
StatusType -> String
(Int -> StatusType -> ShowS)
-> (StatusType -> String)
-> ([StatusType] -> ShowS)
-> Show StatusType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StatusType -> ShowS
showsPrec :: Int -> StatusType -> ShowS
$cshow :: StatusType -> String
show :: StatusType -> String
$cshowList :: [StatusType] -> ShowS
showList :: [StatusType] -> ShowS
Show, Int -> StatusType
StatusType -> Int
StatusType -> [StatusType]
StatusType -> StatusType
StatusType -> StatusType -> [StatusType]
StatusType -> StatusType -> StatusType -> [StatusType]
(StatusType -> StatusType)
-> (StatusType -> StatusType)
-> (Int -> StatusType)
-> (StatusType -> Int)
-> (StatusType -> [StatusType])
-> (StatusType -> StatusType -> [StatusType])
-> (StatusType -> StatusType -> [StatusType])
-> (StatusType -> StatusType -> StatusType -> [StatusType])
-> Enum StatusType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: StatusType -> StatusType
succ :: StatusType -> StatusType
$cpred :: StatusType -> StatusType
pred :: StatusType -> StatusType
$ctoEnum :: Int -> StatusType
toEnum :: Int -> StatusType
$cfromEnum :: StatusType -> Int
fromEnum :: StatusType -> Int
$cenumFrom :: StatusType -> [StatusType]
enumFrom :: StatusType -> [StatusType]
$cenumFromThen :: StatusType -> StatusType -> [StatusType]
enumFromThen :: StatusType -> StatusType -> [StatusType]
$cenumFromTo :: StatusType -> StatusType -> [StatusType]
enumFromTo :: StatusType -> StatusType -> [StatusType]
$cenumFromThenTo :: StatusType -> StatusType -> StatusType -> [StatusType]
enumFromThenTo :: StatusType -> StatusType -> StatusType -> [StatusType]
Enum)
instance Aeson.FromJSON StatusType where
parseJSON :: Value -> Parser StatusType
parseJSON = String -> (Text -> Parser StatusType) -> Value -> Parser StatusType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
Aeson.withText String
"StatusType" ((Text -> Parser StatusType) -> Value -> Parser StatusType)
-> (Text -> Parser StatusType) -> Value -> Parser StatusType
forall a b. (a -> b) -> a -> b
$ \case
Text
"idle" -> StatusType -> Parser StatusType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
Idle
Text
"dnd" -> StatusType -> Parser StatusType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
DND
Text
"online" -> StatusType -> Parser StatusType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
Online
Text
"offline" -> StatusType -> Parser StatusType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
Offline
Text
"invisible" -> StatusType -> Parser StatusType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
Invisible
Text
_ -> String -> Parser StatusType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unknown status type"
instance Aeson.ToJSON StatusType where
toJSON :: StatusType -> Value
toJSON =
forall a. ToJSON a => a -> Value
Aeson.toJSON @Text (Text -> Value) -> (StatusType -> Text) -> StatusType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
StatusType
Idle -> Text
"idle"
StatusType
DND -> Text
"dnd"
StatusType
Online -> Text
"online"
StatusType
Offline -> Text
"offline"
StatusType
Invisible -> Text
"invisible"
$(deriveTextShow 'PartialUser)
$(deriveTextShow ''StatusType)
$(makeFieldLabelsNoPrefix ''User)
$(makeFieldLabelsNoPrefix 'PartialUser)
$(makeFieldLabelsNoPrefix ''StatusType)