-- | A User
module Calamity.Types.Model.User (
  User (..),
  Partial (PartialUser),
  StatusType (..),
) where

import Calamity.Internal.AesonThings
import {-# SOURCE #-} Calamity.Types.Model.Guild.Member
import Calamity.Types.Partial
import Calamity.Types.Snowflake
import Control.DeepSeq
import Data.Aeson
import Data.Text (Text)
import Data.Word
import GHC.Generics
import TextShow
import qualified TextShow.Generic as TSG

data User = User
  { User -> Snowflake User
id :: Snowflake User
  , User -> Text
username :: Text
  , User -> Text
discriminator :: Text
  , User -> Maybe Bool
bot :: Maybe Bool
  , User -> Maybe Text
avatar :: Maybe Text
  , User -> Maybe Bool
mfaEnabled :: Maybe Bool
  , 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
showList :: [User] -> ShowS
$cshowList :: [User] -> ShowS
show :: User -> String
$cshow :: User -> String
showsPrec :: Int -> User -> ShowS
$cshowsPrec :: Int -> User -> ShowS
Show, User -> User -> Bool
(User -> User -> Bool) -> (User -> User -> Bool) -> Eq User
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: User -> User -> Bool
$c/= :: User -> User -> Bool
== :: User -> User -> Bool
$c== :: User -> User -> Bool
Eq, (forall x. User -> Rep User x)
-> (forall x. Rep User x -> User) -> Generic User
forall x. Rep User x -> User
forall x. User -> Rep User x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep User x -> User
$cfrom :: forall x. User -> Rep User x
Generic, User -> ()
(User -> ()) -> NFData User
forall a. (a -> ()) -> NFData a
rnf :: User -> ()
$crnf :: User -> ()
NFData)
  deriving (Int -> User -> Builder
Int -> User -> Text
Int -> User -> Text
[User] -> Builder
[User] -> Text
[User] -> Text
User -> Builder
User -> Text
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
showtlList :: [User] -> Text
$cshowtlList :: [User] -> Text
showtl :: User -> Text
$cshowtl :: User -> Text
showtlPrec :: Int -> User -> Text
$cshowtlPrec :: Int -> User -> Text
showtList :: [User] -> Text
$cshowtList :: [User] -> Text
showt :: User -> Text
$cshowt :: User -> Text
showtPrec :: Int -> User -> Text
$cshowtPrec :: Int -> User -> Text
showbList :: [User] -> Builder
$cshowbList :: [User] -> Builder
showb :: User -> Builder
$cshowb :: User -> Builder
showbPrec :: Int -> User -> Builder
$cshowbPrec :: Int -> User -> Builder
TextShow) via TSG.FromGeneric User
  deriving ([User] -> Encoding
[User] -> Value
User -> Encoding
User -> Value
(User -> Value)
-> (User -> Encoding)
-> ([User] -> Value)
-> ([User] -> Encoding)
-> ToJSON User
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [User] -> Encoding
$ctoEncodingList :: [User] -> Encoding
toJSONList :: [User] -> Value
$ctoJSONList :: [User] -> Value
toEncoding :: User -> Encoding
$ctoEncoding :: User -> Encoding
toJSON :: User -> Value
$ctoJSON :: User -> Value
ToJSON, Value -> Parser [User]
Value -> Parser User
(Value -> Parser User) -> (Value -> Parser [User]) -> FromJSON User
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [User]
$cparseJSONList :: Value -> Parser [User]
parseJSON :: Value -> Parser User
$cparseJSON :: Value -> Parser User
FromJSON) via CalamityJSON User
  deriving (HasID User) via HasIDField "id" User
  deriving (HasID Member) via HasIDFieldCoerce' "id" User

newtype instance Partial User = PartialUser
  { Partial User -> Snowflake User
id :: Snowflake User
  }
  deriving (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
showList :: [Partial User] -> ShowS
$cshowList :: [Partial User] -> ShowS
show :: Partial User -> String
$cshow :: Partial User -> String
showsPrec :: Int -> Partial User -> ShowS
$cshowsPrec :: Int -> 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
/= :: Partial User -> Partial User -> Bool
$c/= :: Partial User -> Partial User -> Bool
== :: Partial User -> Partial User -> Bool
$c== :: Partial User -> Partial User -> Bool
Eq, (forall x. Partial User -> Rep (Partial User) x)
-> (forall x. Rep (Partial User) x -> Partial User)
-> Generic (Partial User)
forall x. Rep (Partial User) x -> Partial User
forall x. Partial User -> Rep (Partial User) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (Partial User) x -> Partial User
$cfrom :: forall x. Partial User -> Rep (Partial User) x
Generic)
  deriving (Int -> Partial User -> Builder
Int -> Partial User -> Text
Int -> Partial User -> Text
[Partial User] -> Builder
[Partial User] -> Text
[Partial User] -> Text
Partial User -> Builder
Partial User -> Text
Partial User -> Text
(Int -> Partial User -> Builder)
-> (Partial User -> Builder)
-> ([Partial User] -> Builder)
-> (Int -> Partial User -> Text)
-> (Partial User -> Text)
-> ([Partial User] -> Text)
-> (Int -> Partial User -> Text)
-> (Partial User -> Text)
-> ([Partial User] -> Text)
-> TextShow (Partial 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
showtlList :: [Partial User] -> Text
$cshowtlList :: [Partial User] -> Text
showtl :: Partial User -> Text
$cshowtl :: Partial User -> Text
showtlPrec :: Int -> Partial User -> Text
$cshowtlPrec :: Int -> Partial User -> Text
showtList :: [Partial User] -> Text
$cshowtList :: [Partial User] -> Text
showt :: Partial User -> Text
$cshowt :: Partial User -> Text
showtPrec :: Int -> Partial User -> Text
$cshowtPrec :: Int -> Partial User -> Text
showbList :: [Partial User] -> Builder
$cshowbList :: [Partial User] -> Builder
showb :: Partial User -> Builder
$cshowb :: Partial User -> Builder
showbPrec :: Int -> Partial User -> Builder
$cshowbPrec :: Int -> Partial User -> Builder
TextShow) via TSG.FromGeneric (Partial User)
  deriving ([Partial User] -> Encoding
[Partial User] -> Value
Partial User -> Encoding
Partial User -> Value
(Partial User -> Value)
-> (Partial User -> Encoding)
-> ([Partial User] -> Value)
-> ([Partial User] -> Encoding)
-> ToJSON (Partial User)
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Partial User] -> Encoding
$ctoEncodingList :: [Partial User] -> Encoding
toJSONList :: [Partial User] -> Value
$ctoJSONList :: [Partial User] -> Value
toEncoding :: Partial User -> Encoding
$ctoEncoding :: Partial User -> Encoding
toJSON :: Partial User -> Value
$ctoJSON :: Partial User -> Value
ToJSON, Value -> Parser [Partial User]
Value -> Parser (Partial User)
(Value -> Parser (Partial User))
-> (Value -> Parser [Partial User]) -> FromJSON (Partial User)
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Partial User]
$cparseJSONList :: Value -> Parser [Partial User]
parseJSON :: Value -> Parser (Partial User)
$cparseJSON :: Value -> Parser (Partial User)
FromJSON) via CalamityJSON (Partial User)
  deriving (HasID User) via HasIDField "id" (Partial User)

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
/= :: StatusType -> StatusType -> Bool
$c/= :: StatusType -> StatusType -> Bool
== :: StatusType -> StatusType -> Bool
$c== :: 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
showList :: [StatusType] -> ShowS
$cshowList :: [StatusType] -> ShowS
show :: StatusType -> String
$cshow :: StatusType -> String
showsPrec :: Int -> StatusType -> ShowS
$cshowsPrec :: Int -> 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
enumFromThenTo :: StatusType -> StatusType -> StatusType -> [StatusType]
$cenumFromThenTo :: StatusType -> StatusType -> StatusType -> [StatusType]
enumFromTo :: StatusType -> StatusType -> [StatusType]
$cenumFromTo :: StatusType -> StatusType -> [StatusType]
enumFromThen :: StatusType -> StatusType -> [StatusType]
$cenumFromThen :: StatusType -> StatusType -> [StatusType]
enumFrom :: StatusType -> [StatusType]
$cenumFrom :: StatusType -> [StatusType]
fromEnum :: StatusType -> Int
$cfromEnum :: StatusType -> Int
toEnum :: Int -> StatusType
$ctoEnum :: Int -> StatusType
pred :: StatusType -> StatusType
$cpred :: StatusType -> StatusType
succ :: StatusType -> StatusType
$csucc :: StatusType -> StatusType
Enum, (forall x. StatusType -> Rep StatusType x)
-> (forall x. Rep StatusType x -> StatusType) -> Generic StatusType
forall x. Rep StatusType x -> StatusType
forall x. StatusType -> Rep StatusType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StatusType x -> StatusType
$cfrom :: forall x. StatusType -> Rep StatusType x
Generic, StatusType -> ()
(StatusType -> ()) -> NFData StatusType
forall a. (a -> ()) -> NFData a
rnf :: StatusType -> ()
$crnf :: StatusType -> ()
NFData)
  deriving (Int -> StatusType -> Builder
Int -> StatusType -> Text
Int -> StatusType -> Text
[StatusType] -> Builder
[StatusType] -> Text
[StatusType] -> Text
StatusType -> Builder
StatusType -> Text
StatusType -> Text
(Int -> StatusType -> Builder)
-> (StatusType -> Builder)
-> ([StatusType] -> Builder)
-> (Int -> StatusType -> Text)
-> (StatusType -> Text)
-> ([StatusType] -> Text)
-> (Int -> StatusType -> Text)
-> (StatusType -> Text)
-> ([StatusType] -> Text)
-> TextShow StatusType
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
showtlList :: [StatusType] -> Text
$cshowtlList :: [StatusType] -> Text
showtl :: StatusType -> Text
$cshowtl :: StatusType -> Text
showtlPrec :: Int -> StatusType -> Text
$cshowtlPrec :: Int -> StatusType -> Text
showtList :: [StatusType] -> Text
$cshowtList :: [StatusType] -> Text
showt :: StatusType -> Text
$cshowt :: StatusType -> Text
showtPrec :: Int -> StatusType -> Text
$cshowtPrec :: Int -> StatusType -> Text
showbList :: [StatusType] -> Builder
$cshowbList :: [StatusType] -> Builder
showb :: StatusType -> Builder
$cshowb :: StatusType -> Builder
showbPrec :: Int -> StatusType -> Builder
$cshowbPrec :: Int -> StatusType -> Builder
TextShow) via TSG.FromGeneric StatusType

instance FromJSON StatusType where
  parseJSON :: Value -> Parser StatusType
parseJSON = String -> (Text -> Parser StatusType) -> Value -> Parser StatusType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
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 (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
Idle
    Text
"dnd" -> StatusType -> Parser StatusType
forall (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
DND
    Text
"online" -> StatusType -> Parser StatusType
forall (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
Online
    Text
"offline" -> StatusType -> Parser StatusType
forall (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
Offline
    Text
"invisible" -> StatusType -> Parser StatusType
forall (f :: * -> *) a. Applicative f => a -> f a
pure StatusType
Invisible
    Text
_ -> String -> Parser StatusType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unknown status type"

instance ToJSON StatusType where
  toJSON :: StatusType -> Value
toJSON =
    Text -> Value
String (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"