-- | Audit Log models
module Calamity.Types.Model.Guild.AuditLog (
  AuditLog (..),
  AuditLogEntry (..),
  AuditLogEntryInfo (..),
  AuditLogChange (..),
  AuditLogAction (..),
) where

import Calamity.Internal.AesonThings
import Calamity.Internal.SnowflakeMap (SnowflakeMap)
import Calamity.Types.Model.Channel
import Calamity.Types.Model.User
import Calamity.Types.Snowflake

import Data.Aeson
import Data.Scientific
import Data.Text (Text)

import GHC.Generics

import TextShow
import qualified TextShow.Generic as TSG

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
showList :: [AuditLog] -> ShowS
$cshowList :: [AuditLog] -> ShowS
show :: AuditLog -> String
$cshow :: AuditLog -> String
showsPrec :: Int -> AuditLog -> ShowS
$cshowsPrec :: Int -> AuditLog -> ShowS
Show, (forall x. AuditLog -> Rep AuditLog x)
-> (forall x. Rep AuditLog x -> AuditLog) -> Generic AuditLog
forall x. Rep AuditLog x -> AuditLog
forall x. AuditLog -> Rep AuditLog x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuditLog x -> AuditLog
$cfrom :: forall x. AuditLog -> Rep AuditLog x
Generic)
  deriving (Int -> AuditLog -> Builder
Int -> AuditLog -> Text
Int -> AuditLog -> Text
[AuditLog] -> Builder
[AuditLog] -> Text
[AuditLog] -> Text
AuditLog -> Builder
AuditLog -> Text
AuditLog -> Text
(Int -> AuditLog -> Builder)
-> (AuditLog -> Builder)
-> ([AuditLog] -> Builder)
-> (Int -> AuditLog -> Text)
-> (AuditLog -> Text)
-> ([AuditLog] -> Text)
-> (Int -> AuditLog -> Text)
-> (AuditLog -> Text)
-> ([AuditLog] -> Text)
-> TextShow AuditLog
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 :: [AuditLog] -> Text
$cshowtlList :: [AuditLog] -> Text
showtl :: AuditLog -> Text
$cshowtl :: AuditLog -> Text
showtlPrec :: Int -> AuditLog -> Text
$cshowtlPrec :: Int -> AuditLog -> Text
showtList :: [AuditLog] -> Text
$cshowtList :: [AuditLog] -> Text
showt :: AuditLog -> Text
$cshowt :: AuditLog -> Text
showtPrec :: Int -> AuditLog -> Text
$cshowtPrec :: Int -> AuditLog -> Text
showbList :: [AuditLog] -> Builder
$cshowbList :: [AuditLog] -> Builder
showb :: AuditLog -> Builder
$cshowb :: AuditLog -> Builder
showbPrec :: Int -> AuditLog -> Builder
$cshowbPrec :: Int -> AuditLog -> Builder
TextShow) via TSG.FromGeneric AuditLog
  deriving (Value -> Parser [AuditLog]
Value -> Parser AuditLog
(Value -> Parser AuditLog)
-> (Value -> Parser [AuditLog]) -> FromJSON AuditLog
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AuditLog]
$cparseJSONList :: Value -> Parser [AuditLog]
parseJSON :: Value -> Parser AuditLog
$cparseJSON :: Value -> Parser AuditLog
FromJSON) via CalamityJSON AuditLog

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
showList :: [AuditLogEntry] -> ShowS
$cshowList :: [AuditLogEntry] -> ShowS
show :: AuditLogEntry -> String
$cshow :: AuditLogEntry -> String
showsPrec :: Int -> AuditLogEntry -> ShowS
$cshowsPrec :: Int -> AuditLogEntry -> ShowS
Show, (forall x. AuditLogEntry -> Rep AuditLogEntry x)
-> (forall x. Rep AuditLogEntry x -> AuditLogEntry)
-> Generic AuditLogEntry
forall x. Rep AuditLogEntry x -> AuditLogEntry
forall x. AuditLogEntry -> Rep AuditLogEntry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuditLogEntry x -> AuditLogEntry
$cfrom :: forall x. AuditLogEntry -> Rep AuditLogEntry x
Generic)
  deriving (Int -> AuditLogEntry -> Builder
Int -> AuditLogEntry -> Text
Int -> AuditLogEntry -> Text
[AuditLogEntry] -> Builder
[AuditLogEntry] -> Text
[AuditLogEntry] -> Text
AuditLogEntry -> Builder
AuditLogEntry -> Text
AuditLogEntry -> Text
(Int -> AuditLogEntry -> Builder)
-> (AuditLogEntry -> Builder)
-> ([AuditLogEntry] -> Builder)
-> (Int -> AuditLogEntry -> Text)
-> (AuditLogEntry -> Text)
-> ([AuditLogEntry] -> Text)
-> (Int -> AuditLogEntry -> Text)
-> (AuditLogEntry -> Text)
-> ([AuditLogEntry] -> Text)
-> TextShow AuditLogEntry
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 :: [AuditLogEntry] -> Text
$cshowtlList :: [AuditLogEntry] -> Text
showtl :: AuditLogEntry -> Text
$cshowtl :: AuditLogEntry -> Text
showtlPrec :: Int -> AuditLogEntry -> Text
$cshowtlPrec :: Int -> AuditLogEntry -> Text
showtList :: [AuditLogEntry] -> Text
$cshowtList :: [AuditLogEntry] -> Text
showt :: AuditLogEntry -> Text
$cshowt :: AuditLogEntry -> Text
showtPrec :: Int -> AuditLogEntry -> Text
$cshowtPrec :: Int -> AuditLogEntry -> Text
showbList :: [AuditLogEntry] -> Builder
$cshowbList :: [AuditLogEntry] -> Builder
showb :: AuditLogEntry -> Builder
$cshowb :: AuditLogEntry -> Builder
showbPrec :: Int -> AuditLogEntry -> Builder
$cshowbPrec :: Int -> AuditLogEntry -> Builder
TextShow) via TSG.FromGeneric AuditLogEntry
  deriving (Value -> Parser [AuditLogEntry]
Value -> Parser AuditLogEntry
(Value -> Parser AuditLogEntry)
-> (Value -> Parser [AuditLogEntry]) -> FromJSON AuditLogEntry
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AuditLogEntry]
$cparseJSONList :: Value -> Parser [AuditLogEntry]
parseJSON :: Value -> Parser AuditLogEntry
$cparseJSON :: Value -> Parser AuditLogEntry
FromJSON) via CalamityJSON AuditLogEntry
  deriving (HasID User) via HasIDField "userID" AuditLogEntry
  deriving (HasID AuditLogEntry) via HasIDField "id" AuditLogEntry

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
showList :: [AuditLogEntryInfo] -> ShowS
$cshowList :: [AuditLogEntryInfo] -> ShowS
show :: AuditLogEntryInfo -> String
$cshow :: AuditLogEntryInfo -> String
showsPrec :: Int -> AuditLogEntryInfo -> ShowS
$cshowsPrec :: Int -> AuditLogEntryInfo -> ShowS
Show, (forall x. AuditLogEntryInfo -> Rep AuditLogEntryInfo x)
-> (forall x. Rep AuditLogEntryInfo x -> AuditLogEntryInfo)
-> Generic AuditLogEntryInfo
forall x. Rep AuditLogEntryInfo x -> AuditLogEntryInfo
forall x. AuditLogEntryInfo -> Rep AuditLogEntryInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuditLogEntryInfo x -> AuditLogEntryInfo
$cfrom :: forall x. AuditLogEntryInfo -> Rep AuditLogEntryInfo x
Generic)
  deriving (Int -> AuditLogEntryInfo -> Builder
Int -> AuditLogEntryInfo -> Text
Int -> AuditLogEntryInfo -> Text
[AuditLogEntryInfo] -> Builder
[AuditLogEntryInfo] -> Text
[AuditLogEntryInfo] -> Text
AuditLogEntryInfo -> Builder
AuditLogEntryInfo -> Text
AuditLogEntryInfo -> Text
(Int -> AuditLogEntryInfo -> Builder)
-> (AuditLogEntryInfo -> Builder)
-> ([AuditLogEntryInfo] -> Builder)
-> (Int -> AuditLogEntryInfo -> Text)
-> (AuditLogEntryInfo -> Text)
-> ([AuditLogEntryInfo] -> Text)
-> (Int -> AuditLogEntryInfo -> Text)
-> (AuditLogEntryInfo -> Text)
-> ([AuditLogEntryInfo] -> Text)
-> TextShow AuditLogEntryInfo
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 :: [AuditLogEntryInfo] -> Text
$cshowtlList :: [AuditLogEntryInfo] -> Text
showtl :: AuditLogEntryInfo -> Text
$cshowtl :: AuditLogEntryInfo -> Text
showtlPrec :: Int -> AuditLogEntryInfo -> Text
$cshowtlPrec :: Int -> AuditLogEntryInfo -> Text
showtList :: [AuditLogEntryInfo] -> Text
$cshowtList :: [AuditLogEntryInfo] -> Text
showt :: AuditLogEntryInfo -> Text
$cshowt :: AuditLogEntryInfo -> Text
showtPrec :: Int -> AuditLogEntryInfo -> Text
$cshowtPrec :: Int -> AuditLogEntryInfo -> Text
showbList :: [AuditLogEntryInfo] -> Builder
$cshowbList :: [AuditLogEntryInfo] -> Builder
showb :: AuditLogEntryInfo -> Builder
$cshowb :: AuditLogEntryInfo -> Builder
showbPrec :: Int -> AuditLogEntryInfo -> Builder
$cshowbPrec :: Int -> AuditLogEntryInfo -> Builder
TextShow) via TSG.FromGeneric AuditLogEntryInfo
  deriving (Value -> Parser [AuditLogEntryInfo]
Value -> Parser AuditLogEntryInfo
(Value -> Parser AuditLogEntryInfo)
-> (Value -> Parser [AuditLogEntryInfo])
-> FromJSON AuditLogEntryInfo
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AuditLogEntryInfo]
$cparseJSONList :: Value -> Parser [AuditLogEntryInfo]
parseJSON :: Value -> Parser AuditLogEntryInfo
$cparseJSON :: Value -> Parser AuditLogEntryInfo
FromJSON) via CalamityJSON AuditLogEntryInfo

data AuditLogChange = AuditLogChange
  { AuditLogChange -> Maybe Value
newValue :: Maybe Value
  , AuditLogChange -> Maybe Value
oldValue :: Maybe 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
showList :: [AuditLogChange] -> ShowS
$cshowList :: [AuditLogChange] -> ShowS
show :: AuditLogChange -> String
$cshow :: AuditLogChange -> String
showsPrec :: Int -> AuditLogChange -> ShowS
$cshowsPrec :: Int -> AuditLogChange -> ShowS
Show, (forall x. AuditLogChange -> Rep AuditLogChange x)
-> (forall x. Rep AuditLogChange x -> AuditLogChange)
-> Generic AuditLogChange
forall x. Rep AuditLogChange x -> AuditLogChange
forall x. AuditLogChange -> Rep AuditLogChange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuditLogChange x -> AuditLogChange
$cfrom :: forall x. AuditLogChange -> Rep AuditLogChange x
Generic)
  deriving (Int -> AuditLogChange -> Builder
Int -> AuditLogChange -> Text
Int -> AuditLogChange -> Text
[AuditLogChange] -> Builder
[AuditLogChange] -> Text
[AuditLogChange] -> Text
AuditLogChange -> Builder
AuditLogChange -> Text
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
showtlList :: [AuditLogChange] -> Text
$cshowtlList :: [AuditLogChange] -> Text
showtl :: AuditLogChange -> Text
$cshowtl :: AuditLogChange -> Text
showtlPrec :: Int -> AuditLogChange -> Text
$cshowtlPrec :: Int -> AuditLogChange -> Text
showtList :: [AuditLogChange] -> Text
$cshowtList :: [AuditLogChange] -> Text
showt :: AuditLogChange -> Text
$cshowt :: AuditLogChange -> Text
showtPrec :: Int -> AuditLogChange -> Text
$cshowtPrec :: Int -> AuditLogChange -> Text
showbList :: [AuditLogChange] -> Builder
$cshowbList :: [AuditLogChange] -> Builder
showb :: AuditLogChange -> Builder
$cshowb :: AuditLogChange -> Builder
showbPrec :: Int -> AuditLogChange -> Builder
$cshowbPrec :: Int -> AuditLogChange -> Builder
TextShow) via FromStringShow AuditLogChange
  deriving (Value -> Parser [AuditLogChange]
Value -> Parser AuditLogChange
(Value -> Parser AuditLogChange)
-> (Value -> Parser [AuditLogChange]) -> FromJSON AuditLogChange
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AuditLogChange]
$cparseJSONList :: Value -> Parser [AuditLogChange]
parseJSON :: Value -> Parser AuditLogChange
$cparseJSON :: Value -> Parser AuditLogChange
FromJSON) via CalamityJSON AuditLogChange

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
showList :: [AuditLogAction] -> ShowS
$cshowList :: [AuditLogAction] -> ShowS
show :: AuditLogAction -> String
$cshow :: AuditLogAction -> String
showsPrec :: Int -> AuditLogAction -> ShowS
$cshowsPrec :: Int -> AuditLogAction -> ShowS
Show, (forall x. AuditLogAction -> Rep AuditLogAction x)
-> (forall x. Rep AuditLogAction x -> AuditLogAction)
-> Generic AuditLogAction
forall x. Rep AuditLogAction x -> AuditLogAction
forall x. AuditLogAction -> Rep AuditLogAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuditLogAction x -> AuditLogAction
$cfrom :: forall x. AuditLogAction -> Rep AuditLogAction x
Generic)
  deriving (Int -> AuditLogAction -> Builder
Int -> AuditLogAction -> Text
Int -> AuditLogAction -> Text
[AuditLogAction] -> Builder
[AuditLogAction] -> Text
[AuditLogAction] -> Text
AuditLogAction -> Builder
AuditLogAction -> Text
AuditLogAction -> Text
(Int -> AuditLogAction -> Builder)
-> (AuditLogAction -> Builder)
-> ([AuditLogAction] -> Builder)
-> (Int -> AuditLogAction -> Text)
-> (AuditLogAction -> Text)
-> ([AuditLogAction] -> Text)
-> (Int -> AuditLogAction -> Text)
-> (AuditLogAction -> Text)
-> ([AuditLogAction] -> Text)
-> TextShow AuditLogAction
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 :: [AuditLogAction] -> Text
$cshowtlList :: [AuditLogAction] -> Text
showtl :: AuditLogAction -> Text
$cshowtl :: AuditLogAction -> Text
showtlPrec :: Int -> AuditLogAction -> Text
$cshowtlPrec :: Int -> AuditLogAction -> Text
showtList :: [AuditLogAction] -> Text
$cshowtList :: [AuditLogAction] -> Text
showt :: AuditLogAction -> Text
$cshowt :: AuditLogAction -> Text
showtPrec :: Int -> AuditLogAction -> Text
$cshowtPrec :: Int -> AuditLogAction -> Text
showbList :: [AuditLogAction] -> Builder
$cshowbList :: [AuditLogAction] -> Builder
showb :: AuditLogAction -> Builder
$cshowb :: AuditLogAction -> Builder
showbPrec :: Int -> AuditLogAction -> Builder
$cshowbPrec :: Int -> AuditLogAction -> Builder
TextShow) via TSG.FromGeneric AuditLogAction

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 FromJSON AuditLogAction where
  parseJSON :: Value -> Parser AuditLogAction
parseJSON = String
-> (Scientific -> Parser AuditLogAction)
-> Value
-> Parser AuditLogAction
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
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 Scientific -> Maybe Int
forall i. (Integral i, Bounded i) => Scientific -> Maybe i
toBoundedInteger @Int Scientific
n of
    Just Int
v -> case Int
v of --  no safe toEnum :S
      Int
1 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
GUILD_UPDATE
      Int
10 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_CREATE
      Int
11 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_UPDATE
      Int
12 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_DELETE
      Int
13 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_OVERWRITE_CREATE
      Int
14 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_OVERWRITE_UPDATE
      Int
15 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
CHANNEL_OVERWRITE_DELETE
      Int
20 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_KICK
      Int
21 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_PRUNE
      Int
22 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_BAN_ADD
      Int
23 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_BAN_REMOVE
      Int
24 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_UPDATE
      Int
25 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_ROLE_UPDATE
      Int
26 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_MOVE
      Int
27 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MEMBER_DISCONNECT
      Int
28 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
BOT_ADD
      Int
30 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
ROLE_CREATE
      Int
31 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
ROLE_UPDATE
      Int
32 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
ROLE_DELETE
      Int
40 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INVITE_CREATE
      Int
41 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INVITE_UPDATE
      Int
42 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INVITE_DELETE
      Int
50 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
WEBHOOK_CREATE
      Int
51 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
WEBHOOK_UPDATE
      Int
52 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
WEBHOOK_DELETE
      Int
60 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
EMOJI_CREATE
      Int
61 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
EMOJI_UPDATE
      Int
62 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
EMOJI_DELETE
      Int
72 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MESSAGE_DELETE
      Int
73 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MESSAGE_BULK_DELETE
      Int
74 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MESSAGE_PIN
      Int
75 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
MESSAGE_UNPIN
      Int
80 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INTEGRATION_CREATE
      Int
81 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INTEGRATION_UPDATE
      Int
82 -> AuditLogAction -> Parser AuditLogAction
forall (f :: * -> *) a. Applicative f => a -> f a
pure AuditLogAction
INTEGRATION_DELETE
      Int
_ -> String -> Parser AuditLogAction
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 (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 ToJSON AuditLogAction where
  toJSON :: AuditLogAction -> Value
toJSON = ToJSON Int => Int -> Value
forall a. ToJSON a => a -> Value
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