module Calamity.Types.Model.Guild.Invite (Invite (..)) where
import Calamity.Internal.AesonThings
import Calamity.Types.Model.Channel
import Calamity.Types.Model.Guild.Guild
import Calamity.Types.Model.User
import Calamity.Types.Snowflake
import Data.Aeson
import Data.Text (Text)
import GHC.Generics
import TextShow
import qualified TextShow.Generic as TSG
data Invite = Invite
{ Invite -> Text
code :: Text
, Invite -> Maybe (Partial Guild)
guild :: Maybe (Partial Guild)
, Invite -> Maybe (Partial Channel)
channel :: Maybe (Partial Channel)
, Invite -> Maybe (Snowflake User)
targetUser :: Maybe (Snowflake User)
, Invite -> Maybe Int
targetUserType :: Maybe Int
, Invite -> Maybe Int
approximatePresenceCount :: Maybe Int
, Invite -> Maybe Int
approximateMemberCount :: Maybe Int
}
deriving (Invite -> Invite -> Bool
(Invite -> Invite -> Bool)
-> (Invite -> Invite -> Bool) -> Eq Invite
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Invite -> Invite -> Bool
$c/= :: Invite -> Invite -> Bool
== :: Invite -> Invite -> Bool
$c== :: Invite -> Invite -> Bool
Eq, Int -> Invite -> ShowS
[Invite] -> ShowS
Invite -> String
(Int -> Invite -> ShowS)
-> (Invite -> String) -> ([Invite] -> ShowS) -> Show Invite
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Invite] -> ShowS
$cshowList :: [Invite] -> ShowS
show :: Invite -> String
$cshow :: Invite -> String
showsPrec :: Int -> Invite -> ShowS
$cshowsPrec :: Int -> Invite -> ShowS
Show, (forall x. Invite -> Rep Invite x)
-> (forall x. Rep Invite x -> Invite) -> Generic Invite
forall x. Rep Invite x -> Invite
forall x. Invite -> Rep Invite x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Invite x -> Invite
$cfrom :: forall x. Invite -> Rep Invite x
Generic)
deriving (Int -> Invite -> Builder
Int -> Invite -> Text
Int -> Invite -> Text
[Invite] -> Builder
[Invite] -> Text
[Invite] -> Text
Invite -> Builder
Invite -> Text
Invite -> Text
(Int -> Invite -> Builder)
-> (Invite -> Builder)
-> ([Invite] -> Builder)
-> (Int -> Invite -> Text)
-> (Invite -> Text)
-> ([Invite] -> Text)
-> (Int -> Invite -> Text)
-> (Invite -> Text)
-> ([Invite] -> Text)
-> TextShow Invite
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 :: [Invite] -> Text
$cshowtlList :: [Invite] -> Text
showtl :: Invite -> Text
$cshowtl :: Invite -> Text
showtlPrec :: Int -> Invite -> Text
$cshowtlPrec :: Int -> Invite -> Text
showtList :: [Invite] -> Text
$cshowtList :: [Invite] -> Text
showt :: Invite -> Text
$cshowt :: Invite -> Text
showtPrec :: Int -> Invite -> Text
$cshowtPrec :: Int -> Invite -> Text
showbList :: [Invite] -> Builder
$cshowbList :: [Invite] -> Builder
showb :: Invite -> Builder
$cshowb :: Invite -> Builder
showbPrec :: Int -> Invite -> Builder
$cshowbPrec :: Int -> Invite -> Builder
TextShow) via TSG.FromGeneric Invite
deriving ([Invite] -> Encoding
[Invite] -> Value
Invite -> Encoding
Invite -> Value
(Invite -> Value)
-> (Invite -> Encoding)
-> ([Invite] -> Value)
-> ([Invite] -> Encoding)
-> ToJSON Invite
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Invite] -> Encoding
$ctoEncodingList :: [Invite] -> Encoding
toJSONList :: [Invite] -> Value
$ctoJSONList :: [Invite] -> Value
toEncoding :: Invite -> Encoding
$ctoEncoding :: Invite -> Encoding
toJSON :: Invite -> Value
$ctoJSON :: Invite -> Value
ToJSON) via CalamityJSON Invite
deriving (Value -> Parser [Invite]
Value -> Parser Invite
(Value -> Parser Invite)
-> (Value -> Parser [Invite]) -> FromJSON Invite
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Invite]
$cparseJSONList :: Value -> Parser [Invite]
parseJSON :: Value -> Parser Invite
$cparseJSON :: Value -> Parser Invite
FromJSON) via WithSpecialCases '["targetUser" `ExtractFieldFrom` "id"] Invite