{-# LANGUAGE TemplateHaskell #-}
module Calamity.Types.Model.Guild.AuditLog (
AuditLog (..),
AuditLogEntry (..),
AuditLogEntryInfo (..),
AuditLogChange (..),
AuditLogAction (..),
) where
import Calamity.Internal.SnowflakeMap (SnowflakeMap)
import Calamity.Types.Model.Channel
import Calamity.Types.Model.User
import Calamity.Types.Snowflake
import Data.Aeson ((.:), (.:?))
import Data.Aeson qualified as Aeson
import Data.Scientific
import Data.Text (Text)
import Optics.TH
import TextShow qualified
import TextShow.TH
data AuditLog = AuditLog
{ AuditLog -> SnowflakeMap Webhook
webhooks :: SnowflakeMap Webhook
, AuditLog -> SnowflakeMap User
users :: SnowflakeMap User
, AuditLog -> SnowflakeMap AuditLogEntry
auditLogEntries :: SnowflakeMap AuditLogEntry
}
deriving (Int -> AuditLog -> ShowS
[AuditLog] -> ShowS
AuditLog -> String
(Int -> AuditLog -> ShowS)
-> (AuditLog -> String) -> ([AuditLog] -> ShowS) -> Show AuditLog
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AuditLog -> ShowS
showsPrec :: Int -> AuditLog -> ShowS
$cshow :: AuditLog -> String
show :: AuditLog -> String
$cshowList :: [AuditLog] -> ShowS
showList :: [AuditLog] -> ShowS
Show)
data AuditLogEntry = AuditLogEntry
{ AuditLogEntry -> Maybe (Snowflake ())
targetID :: Maybe (Snowflake ())
, AuditLogEntry -> [AuditLogChange]
changes :: [AuditLogChange]
, AuditLogEntry -> Snowflake User
userID :: Snowflake User
, AuditLogEntry -> Snowflake AuditLogEntry
id :: Snowflake AuditLogEntry
, AuditLogEntry -> AuditLogAction
actionType :: AuditLogAction
, AuditLogEntry -> Maybe AuditLogEntryInfo
options :: Maybe AuditLogEntryInfo
, AuditLogEntry -> Maybe Text
reason :: Maybe Text
}
deriving (Int -> AuditLogEntry -> ShowS
[AuditLogEntry] -> ShowS
AuditLogEntry -> String
(Int -> AuditLogEntry -> ShowS)
-> (AuditLogEntry -> String)
-> ([AuditLogEntry] -> ShowS)
-> Show AuditLogEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AuditLogEntry -> ShowS
showsPrec :: Int -> AuditLogEntry -> ShowS
$cshow :: AuditLogEntry -> String
show :: AuditLogEntry -> String
$cshowList :: [AuditLogEntry] -> ShowS
showList :: [AuditLogEntry] -> ShowS
Show)
deriving (HasID User) via HasIDField "userID" AuditLogEntry
deriving (HasID AuditLogEntry) via HasIDField "id" AuditLogEntry
instance Aeson.FromJSON AuditLogEntry where
parseJSON :: Value -> Parser AuditLogEntry
parseJSON = String
-> (Object -> Parser AuditLogEntry)
-> Value
-> Parser AuditLogEntry
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"AuditLogEntry" ((Object -> Parser AuditLogEntry) -> Value -> Parser AuditLogEntry)
-> (Object -> Parser AuditLogEntry)
-> Value
-> Parser AuditLogEntry
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Maybe (Snowflake ())
-> [AuditLogChange]
-> Snowflake User
-> Snowflake AuditLogEntry
-> AuditLogAction
-> Maybe AuditLogEntryInfo
-> Maybe Text
-> AuditLogEntry
AuditLogEntry
(Maybe (Snowflake ())
-> [AuditLogChange]
-> Snowflake User
-> Snowflake AuditLogEntry
-> AuditLogAction
-> Maybe AuditLogEntryInfo
-> Maybe Text
-> AuditLogEntry)
-> Parser (Maybe (Snowflake ()))
-> Parser
([AuditLogChange]
-> Snowflake User
-> Snowflake AuditLogEntry
-> AuditLogAction
-> Maybe AuditLogEntryInfo
-> Maybe Text
-> AuditLogEntry)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe (Snowflake ()))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"target_id"
Parser
([AuditLogChange]
-> Snowflake User
-> Snowflake AuditLogEntry
-> AuditLogAction
-> Maybe AuditLogEntryInfo
-> Maybe Text
-> AuditLogEntry)
-> Parser [AuditLogChange]
-> Parser
(Snowflake User
-> Snowflake AuditLogEntry
-> AuditLogAction
-> Maybe AuditLogEntryInfo
-> Maybe Text
-> AuditLogEntry)
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 [AuditLogChange]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"changes"
Parser
(Snowflake User
-> Snowflake AuditLogEntry
-> AuditLogAction
-> Maybe AuditLogEntryInfo
-> Maybe Text
-> AuditLogEntry)
-> Parser (Snowflake User)
-> Parser
(Snowflake AuditLogEntry
-> AuditLogAction
-> Maybe AuditLogEntryInfo
-> Maybe Text
-> AuditLogEntry)
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 User)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user_id"
Parser
(Snowflake AuditLogEntry
-> AuditLogAction
-> Maybe AuditLogEntryInfo
-> Maybe Text
-> AuditLogEntry)
-> Parser (Snowflake AuditLogEntry)
-> Parser
(AuditLogAction
-> Maybe AuditLogEntryInfo -> Maybe Text -> AuditLogEntry)
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 AuditLogEntry)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Parser
(AuditLogAction
-> Maybe AuditLogEntryInfo -> Maybe Text -> AuditLogEntry)
-> Parser AuditLogAction
-> Parser (Maybe AuditLogEntryInfo -> Maybe Text -> AuditLogEntry)
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 AuditLogAction
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"action_type"
Parser (Maybe AuditLogEntryInfo -> Maybe Text -> AuditLogEntry)
-> Parser (Maybe AuditLogEntryInfo)
-> Parser (Maybe Text -> AuditLogEntry)
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 AuditLogEntryInfo)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"options"
Parser (Maybe Text -> AuditLogEntry)
-> Parser (Maybe Text) -> Parser AuditLogEntry
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
"reason"
data AuditLogEntryInfo = AuditLogEntryInfo
{ AuditLogEntryInfo -> Maybe Text
deleteMemberDays :: Maybe Text
, AuditLogEntryInfo -> Maybe Text
membersRemoved :: Maybe Text
, AuditLogEntryInfo -> Maybe (Snowflake Channel)
channelID :: Maybe (Snowflake Channel)
, AuditLogEntryInfo -> Maybe (Snowflake Message)
messageID :: Maybe (Snowflake Message)
, AuditLogEntryInfo -> Maybe Text
count :: Maybe Text
, AuditLogEntryInfo -> Maybe (Snowflake ())
id :: Maybe (Snowflake ())
, AuditLogEntryInfo -> Maybe Text
type_ :: Maybe Text
, AuditLogEntryInfo -> Maybe Text
roleName :: Maybe Text
}
deriving (Int -> AuditLogEntryInfo -> ShowS
[AuditLogEntryInfo] -> ShowS
AuditLogEntryInfo -> String
(Int -> AuditLogEntryInfo -> ShowS)
-> (AuditLogEntryInfo -> String)
-> ([AuditLogEntryInfo] -> ShowS)
-> Show AuditLogEntryInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AuditLogEntryInfo -> ShowS
showsPrec :: Int -> AuditLogEntryInfo -> ShowS
$cshow :: AuditLogEntryInfo -> String
show :: AuditLogEntryInfo -> String
$cshowList :: [AuditLogEntryInfo] -> ShowS
showList :: [AuditLogEntryInfo] -> ShowS
Show)
instance Aeson.FromJSON AuditLogEntryInfo where
parseJSON :: Value -> Parser AuditLogEntryInfo
parseJSON = String
-> (Object -> Parser AuditLogEntryInfo)
-> Value
-> Parser AuditLogEntryInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"AudotLogEntryInfo" ((Object -> Parser AuditLogEntryInfo)
-> Value -> Parser AuditLogEntryInfo)
-> (Object -> Parser AuditLogEntryInfo)
-> Value
-> Parser AuditLogEntryInfo
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Maybe Text
-> Maybe Text
-> Maybe (Snowflake Channel)
-> Maybe (Snowflake Message)
-> Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo
AuditLogEntryInfo
(Maybe Text
-> Maybe Text
-> Maybe (Snowflake Channel)
-> Maybe (Snowflake Message)
-> Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe (Snowflake Channel)
-> Maybe (Snowflake Message)
-> Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo)
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
"delete_member_days"
Parser
(Maybe Text
-> Maybe (Snowflake Channel)
-> Maybe (Snowflake Message)
-> Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo)
-> Parser (Maybe Text)
-> Parser
(Maybe (Snowflake Channel)
-> Maybe (Snowflake Message)
-> Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo)
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
"members_removed"
Parser
(Maybe (Snowflake Channel)
-> Maybe (Snowflake Message)
-> Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo)
-> Parser (Maybe (Snowflake Channel))
-> Parser
(Maybe (Snowflake Message)
-> Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo)
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 (Snowflake Channel))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"channel_id"
Parser
(Maybe (Snowflake Message)
-> Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo)
-> Parser (Maybe (Snowflake Message))
-> Parser
(Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo)
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 (Snowflake Message))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"message_id"
Parser
(Maybe Text
-> Maybe (Snowflake ())
-> Maybe Text
-> Maybe Text
-> AuditLogEntryInfo)
-> Parser (Maybe Text)
-> Parser
(Maybe (Snowflake ())
-> Maybe Text -> Maybe Text -> AuditLogEntryInfo)
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
"count"
Parser
(Maybe (Snowflake ())
-> Maybe Text -> Maybe Text -> AuditLogEntryInfo)
-> Parser (Maybe (Snowflake ()))
-> Parser (Maybe Text -> Maybe Text -> AuditLogEntryInfo)
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 (Snowflake ()))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"id"
Parser (Maybe Text -> Maybe Text -> AuditLogEntryInfo)
-> Parser (Maybe Text) -> Parser (Maybe Text -> AuditLogEntryInfo)
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
"type"
Parser (Maybe Text -> AuditLogEntryInfo)
-> Parser (Maybe Text) -> Parser AuditLogEntryInfo
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
"role_name"
data AuditLogChange = AuditLogChange
{ AuditLogChange -> Maybe Value
newValue :: Maybe Aeson.Value
, AuditLogChange -> Maybe Value
oldValue :: Maybe Aeson.Value
, AuditLogChange -> Text
key :: Text
}
deriving (Int -> AuditLogChange -> ShowS
[AuditLogChange] -> ShowS
AuditLogChange -> String
(Int -> AuditLogChange -> ShowS)
-> (AuditLogChange -> String)
-> ([AuditLogChange] -> ShowS)
-> Show AuditLogChange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AuditLogChange -> ShowS
showsPrec :: Int -> AuditLogChange -> ShowS
$cshow :: AuditLogChange -> String
show :: AuditLogChange -> String
$cshowList :: [AuditLogChange] -> ShowS
showList :: [AuditLogChange] -> ShowS
Show)
deriving (Int -> AuditLogChange -> Text
Int -> AuditLogChange -> Builder
Int -> AuditLogChange -> Text
[AuditLogChange] -> Text
[AuditLogChange] -> Builder
[AuditLogChange] -> Text
AuditLogChange -> Text
AuditLogChange -> Builder
AuditLogChange -> Text
(Int -> AuditLogChange -> Builder)
-> (AuditLogChange -> Builder)
-> ([AuditLogChange] -> Builder)
-> (Int -> AuditLogChange -> Text)
-> (AuditLogChange -> Text)
-> ([AuditLogChange] -> Text)
-> (Int -> AuditLogChange -> Text)
-> (AuditLogChange -> Text)
-> ([AuditLogChange] -> Text)
-> TextShow AuditLogChange
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 -> AuditLogChange -> Builder
showbPrec :: Int -> AuditLogChange -> Builder
$cshowb :: AuditLogChange -> Builder
showb :: AuditLogChange -> Builder
$cshowbList :: [AuditLogChange] -> Builder
showbList :: [AuditLogChange] -> Builder
$cshowtPrec :: Int -> AuditLogChange -> Text
showtPrec :: Int -> AuditLogChange -> Text
$cshowt :: AuditLogChange -> Text
showt :: AuditLogChange -> Text
$cshowtList :: [AuditLogChange] -> Text
showtList :: [AuditLogChange] -> Text
$cshowtlPrec :: Int -> AuditLogChange -> Text
showtlPrec :: Int -> AuditLogChange -> Text
$cshowtl :: AuditLogChange -> Text
showtl :: AuditLogChange -> Text
$cshowtlList :: [AuditLogChange] -> Text
showtlList :: [AuditLogChange] -> Text
TextShow.TextShow) via TextShow.FromStringShow AuditLogChange
instance Aeson.FromJSON AuditLogChange where
parseJSON :: Value -> Parser AuditLogChange
parseJSON = String
-> (Object -> Parser AuditLogChange)
-> Value
-> Parser AuditLogChange
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"AudotLogChange" ((Object -> Parser AuditLogChange)
-> Value -> Parser AuditLogChange)
-> (Object -> Parser AuditLogChange)
-> Value
-> Parser AuditLogChange
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Maybe Value -> Maybe Value -> Text -> AuditLogChange
AuditLogChange
(Maybe Value -> Maybe Value -> Text -> AuditLogChange)
-> Parser (Maybe Value)
-> Parser (Maybe Value -> Text -> AuditLogChange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"new_value"
Parser (Maybe Value -> Text -> AuditLogChange)
-> Parser (Maybe Value) -> Parser (Text -> AuditLogChange)
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 Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"old_value"
Parser (Text -> AuditLogChange)
-> Parser Text -> Parser AuditLogChange
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
"key"
data AuditLogAction
= GUILD_UPDATE
| CHANNEL_CREATE
| CHANNEL_UPDATE
| CHANNEL_DELETE
| CHANNEL_OVERWRITE_CREATE
| CHANNEL_OVERWRITE_UPDATE
| CHANNEL_OVERWRITE_DELETE
| MEMBER_KICK
| MEMBER_PRUNE
| MEMBER_BAN_ADD
| MEMBER_BAN_REMOVE
| MEMBER_UPDATE
| MEMBER_ROLE_UPDATE
| MEMBER_MOVE
| MEMBER_DISCONNECT
| BOT_ADD
| ROLE_CREATE
| ROLE_UPDATE
| ROLE_DELETE
| INVITE_CREATE
| INVITE_UPDATE
| INVITE_DELETE
| WEBHOOK_CREATE
| WEBHOOK_UPDATE
| WEBHOOK_DELETE
| EMOJI_CREATE
| EMOJI_UPDATE
| EMOJI_DELETE
| MESSAGE_DELETE
| MESSAGE_BULK_DELETE
| MESSAGE_PIN
| MESSAGE_UNPIN
| INTEGRATION_CREATE
| INTEGRATION_UPDATE
| INTEGRATION_DELETE
deriving (Int -> AuditLogAction -> ShowS
[AuditLogAction] -> ShowS
AuditLogAction -> String
(Int -> AuditLogAction -> ShowS)
-> (AuditLogAction -> String)
-> ([AuditLogAction] -> ShowS)
-> Show AuditLogAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AuditLogAction -> ShowS
showsPrec :: Int -> AuditLogAction -> ShowS
$cshow :: AuditLogAction -> String
show :: AuditLogAction -> String
$cshowList :: [AuditLogAction] -> ShowS
showList :: [AuditLogAction] -> ShowS
Show)
instance Enum AuditLogAction where
toEnum :: Int -> AuditLogAction
toEnum Int
v = case Int
v of
Int
1 -> AuditLogAction
GUILD_UPDATE
Int
10 -> AuditLogAction
CHANNEL_CREATE
Int
11 -> AuditLogAction
CHANNEL_UPDATE
Int
12 -> AuditLogAction
CHANNEL_DELETE
Int
13 -> AuditLogAction
CHANNEL_OVERWRITE_CREATE
Int
14 -> AuditLogAction
CHANNEL_OVERWRITE_UPDATE
Int
15 -> AuditLogAction
CHANNEL_OVERWRITE_DELETE
Int
20 -> AuditLogAction
MEMBER_KICK
Int
21 -> AuditLogAction
MEMBER_PRUNE
Int
22 -> AuditLogAction
MEMBER_BAN_ADD
Int
23 -> AuditLogAction
MEMBER_BAN_REMOVE
Int
24 -> AuditLogAction
MEMBER_UPDATE
Int
25 -> AuditLogAction
MEMBER_ROLE_UPDATE
Int
26 -> AuditLogAction
MEMBER_MOVE
Int
27 -> AuditLogAction
MEMBER_DISCONNECT
Int
28 -> AuditLogAction
BOT_ADD
Int
30 -> AuditLogAction
ROLE_CREATE
Int
31 -> AuditLogAction
ROLE_UPDATE
Int
32 -> AuditLogAction
ROLE_DELETE
Int
40 -> AuditLogAction
INVITE_CREATE
Int
41 -> AuditLogAction
INVITE_UPDATE
Int
42 -> AuditLogAction
INVITE_DELETE
Int
50 -> AuditLogAction
WEBHOOK_CREATE
Int
51 -> AuditLogAction
WEBHOOK_UPDATE
Int
52 -> AuditLogAction
WEBHOOK_DELETE
Int
60 -> AuditLogAction
EMOJI_CREATE
Int
61 -> AuditLogAction
EMOJI_UPDATE
Int
62 -> AuditLogAction
EMOJI_DELETE
Int
72 -> AuditLogAction
MESSAGE_DELETE
Int
73 -> AuditLogAction
MESSAGE_BULK_DELETE
Int
74 -> AuditLogAction
MESSAGE_PIN
Int
75 -> AuditLogAction
MESSAGE_UNPIN
Int
80 -> AuditLogAction
INTEGRATION_CREATE
Int
81 -> AuditLogAction
INTEGRATION_UPDATE
Int
82 -> AuditLogAction
INTEGRATION_DELETE
Int
_ -> String -> AuditLogAction
forall a. HasCallStack => String -> a
error (String -> AuditLogAction) -> String -> AuditLogAction
forall a b. (a -> b) -> a -> b
$ String
"Invalid AuditLogAction: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
v
fromEnum :: AuditLogAction -> Int
fromEnum AuditLogAction
v = case AuditLogAction
v of
AuditLogAction
GUILD_UPDATE -> Int
1
AuditLogAction
CHANNEL_CREATE -> Int
10
AuditLogAction
CHANNEL_UPDATE -> Int
11
AuditLogAction
CHANNEL_DELETE -> Int
12
AuditLogAction
CHANNEL_OVERWRITE_CREATE -> Int
13
AuditLogAction
CHANNEL_OVERWRITE_UPDATE -> Int
14
AuditLogAction
CHANNEL_OVERWRITE_DELETE -> Int
15
AuditLogAction
MEMBER_KICK -> Int
20
AuditLogAction
MEMBER_PRUNE -> Int
21
AuditLogAction
MEMBER_BAN_ADD -> Int
22
AuditLogAction
MEMBER_BAN_REMOVE -> Int
23
AuditLogAction
MEMBER_UPDATE -> Int
24
AuditLogAction
MEMBER_ROLE_UPDATE -> Int
25
AuditLogAction
MEMBER_MOVE -> Int
26
AuditLogAction
MEMBER_DISCONNECT -> Int
27
AuditLogAction
BOT_ADD -> Int
28
AuditLogAction
ROLE_CREATE -> Int
30
AuditLogAction
ROLE_UPDATE -> Int
31
AuditLogAction
ROLE_DELETE -> Int
32
AuditLogAction
INVITE_CREATE -> Int
40
AuditLogAction
INVITE_UPDATE -> Int
41
AuditLogAction
INVITE_DELETE -> Int
42
AuditLogAction
WEBHOOK_CREATE -> Int
50
AuditLogAction
WEBHOOK_UPDATE -> Int
51
AuditLogAction
WEBHOOK_DELETE -> Int
52
AuditLogAction
EMOJI_CREATE -> Int
60
AuditLogAction
EMOJI_UPDATE -> Int
61
AuditLogAction
EMOJI_DELETE -> Int
62
AuditLogAction
MESSAGE_DELETE -> Int
72
AuditLogAction
MESSAGE_BULK_DELETE -> Int
73
AuditLogAction
MESSAGE_PIN -> Int
74
AuditLogAction
MESSAGE_UNPIN -> Int
75
AuditLogAction
INTEGRATION_CREATE -> Int
80
AuditLogAction
INTEGRATION_UPDATE -> Int
81
AuditLogAction
INTEGRATION_DELETE -> Int
82
instance Aeson.FromJSON AuditLogAction where
parseJSON :: Value -> Parser AuditLogAction
parseJSON = String
-> (Scientific -> Parser AuditLogAction)
-> Value
-> Parser AuditLogAction
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
Aeson.withScientific String
"AuditLogAction" ((Scientific -> Parser AuditLogAction)
-> Value -> Parser AuditLogAction)
-> (Scientific -> Parser AuditLogAction)
-> Value
-> Parser AuditLogAction
forall a b. (a -> b) -> a -> b
$ \Scientific
n -> case forall i. (Integral i, Bounded i) => Scientific -> Maybe i
toBoundedInteger @Int Scientific
n of
Just Int
v -> case Int
v of
Int
1 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
GUILD_UPDATE
Int
10 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_CREATE
Int
11 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_UPDATE
Int
12 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_DELETE
Int
13 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_OVERWRITE_CREATE
Int
14 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_OVERWRITE_UPDATE
Int
15 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_OVERWRITE_DELETE
Int
20 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_KICK
Int
21 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_PRUNE
Int
22 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_BAN_ADD
Int
23 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_BAN_REMOVE
Int
24 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_UPDATE
Int
25 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_ROLE_UPDATE
Int
26 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_MOVE
Int
27 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_DISCONNECT
Int
28 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
BOT_ADD
Int
30 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
ROLE_CREATE
Int
31 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
ROLE_UPDATE
Int
32 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
ROLE_DELETE
Int
40 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INVITE_CREATE
Int
41 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INVITE_UPDATE
Int
42 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INVITE_DELETE
Int
50 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
WEBHOOK_CREATE
Int
51 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
WEBHOOK_UPDATE
Int
52 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
WEBHOOK_DELETE
Int
60 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
EMOJI_CREATE
Int
61 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
EMOJI_UPDATE
Int
62 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
EMOJI_DELETE
Int
72 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MESSAGE_DELETE
Int
73 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MESSAGE_BULK_DELETE
Int
74 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MESSAGE_PIN
Int
75 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MESSAGE_UNPIN
Int
80 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INTEGRATION_CREATE
Int
81 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INTEGRATION_UPDATE
Int
82 -> AuditLogAction -> Parser AuditLogAction
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INTEGRATION_DELETE
Int
_ -> String -> Parser AuditLogAction
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser AuditLogAction)
-> String -> Parser AuditLogAction
forall a b. (a -> b) -> a -> b
$ String
"Invalid AuditLogAction: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Scientific -> String
forall a. Show a => a -> String
show Scientific
n
Maybe Int
Nothing -> String -> Parser AuditLogAction
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser AuditLogAction)
-> String -> Parser AuditLogAction
forall a b. (a -> b) -> a -> b
$ String
"Invalid AuditLogAction: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Scientific -> String
forall a. Show a => a -> String
show Scientific
n
instance Aeson.ToJSON AuditLogAction where
toJSON :: AuditLogAction -> Value
toJSON = forall a. ToJSON a => a -> Value
Aeson.toJSON @Int (Int -> Value)
-> (AuditLogAction -> Int) -> AuditLogAction -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AuditLogAction -> Int
forall a. Enum a => a -> Int
fromEnum
toEncoding :: AuditLogAction -> Encoding
toEncoding = forall a. ToJSON a => a -> Encoding
Aeson.toEncoding @Int (Int -> Encoding)
-> (AuditLogAction -> Int) -> AuditLogAction -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AuditLogAction -> Int
forall a. Enum a => a -> Int
fromEnum
$(deriveTextShow ''AuditLogAction)
$(deriveTextShow ''AuditLogEntryInfo)
$(deriveTextShow ''AuditLogEntry)
$(deriveTextShow ''AuditLog)
$(makeFieldLabelsNoPrefix ''AuditLog)
$(makeFieldLabelsNoPrefix ''AuditLogEntry)
$(makeFieldLabelsNoPrefix ''AuditLogEntryInfo)
$(makeFieldLabelsNoPrefix ''AuditLogChange)