{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}

module Discord.Internal.Types.ApplicationCommands
  ( ApplicationCommand (..),
    Options (..),
    OptionSubcommandOrGroup (..),
    OptionSubcommand (..),
    OptionValue (..),
    createChatInput,
    createUser,
    createMessage,
    CreateApplicationCommand (..),
    EditApplicationCommand (..),
    defaultEditApplicationCommand,
    Choice (..),
    ApplicationCommandChannelType (..),
    GuildApplicationCommandPermissions (..),
    ApplicationCommandPermissions (..),
    Number,
    AutocompleteOrChoice,
    LocalizedText,
    Locale
  )
where

import Data.Aeson (FromJSON (parseJSON), ToJSON (toJSON), Value (Number, Object), object, withArray, withObject, (.!=), (.:), (.:!), (.:?))
import Data.Aeson.Types (Pair, Parser)
import Data.Data (Data)
import Data.Foldable (Foldable (toList))
import Data.Scientific (Scientific)
import qualified Data.Text as T
import Discord.Internal.Types.Prelude (ApplicationCommandId, ApplicationId, GuildId, InternalDiscordEnum (..), Snowflake, discordTypeParseJSON, objectFromMaybes, (.==), (.=?))
import Data.Map.Strict (Map)

type Number = Scientific

-- | The structure for an application command.
data ApplicationCommand
  = ApplicationCommandUser
      { -- | The id of the application command.
        ApplicationCommand -> ApplicationCommandId
applicationCommandId :: ApplicationCommandId,
        -- | The id of the application the command comes from.
        ApplicationCommand -> ApplicationId
applicationCommandApplicationId :: ApplicationId,
        -- | The guild the application command is registered in.
        ApplicationCommand -> Maybe GuildId
applicationCommandGuildId :: Maybe GuildId,
        -- | The name of the application command.
        ApplicationCommand -> Text
applicationCommandName :: T.Text,
        -- | The localized names of the application command.
        ApplicationCommand -> Maybe LocalizedText
applicationCommandLocalizedName :: Maybe LocalizedText,
        -- | What permissions are required to use this command by default.
        ApplicationCommand -> Maybe Text
applicationCommandDefaultMemberPermissions :: Maybe T.Text,
        -- | Whether the command is available in DMs.
        ApplicationCommand -> Maybe Bool
applicationCommandDMPermission :: Maybe Bool,
        -- | Autoincrementing version identifier updated during substantial record changes.
        ApplicationCommand -> Snowflake
applicationCommandVersion :: Snowflake
      }
  | ApplicationCommandMessage
      { -- | The id of the application command.
        applicationCommandId :: ApplicationCommandId,
        -- | The id of the application the command comes from.
        applicationCommandApplicationId :: ApplicationId,
        -- | The guild the application command is registered in.
        applicationCommandGuildId :: Maybe GuildId,
        -- | The name of the application command.
        applicationCommandName :: T.Text,
        -- | The localized names of the application command.
        applicationCommandLocalizedName :: Maybe LocalizedText,
        -- | What permissions are required to use this command by default.
        applicationCommandDefaultMemberPermissions :: Maybe T.Text,
        -- | Whether the command is available in DMs.
        applicationCommandDMPermission :: Maybe Bool,
        -- | Autoincrementing version identifier updated during substantial record changes.
        applicationCommandVersion :: Snowflake
      }
  | ApplicationCommandChatInput
      { -- | The id of the application command.
        applicationCommandId :: ApplicationCommandId,
        -- | The id of the application the command comes from.
        applicationCommandApplicationId :: ApplicationId,
        -- | The guild the application command is registered in.
        applicationCommandGuildId :: Maybe GuildId,
        -- | The name of the application command.
        applicationCommandName :: T.Text,
        -- | The localized names of the application command.
        applicationCommandLocalizedName :: Maybe LocalizedText,
        -- | The description of the application command.
        ApplicationCommand -> Text
applicationCommandDescription :: T.Text,
        -- | The localized descriptions of the application command.
        ApplicationCommand -> Maybe LocalizedText
applicationCommandLocalizedDescription :: Maybe LocalizedText,
        -- | The parameters for the command.
        ApplicationCommand -> Maybe Options
applicationCommandOptions :: Maybe Options,
        -- | What permissions are required to use this command by default.
        applicationCommandDefaultMemberPermissions :: Maybe T.Text,
        -- | Whether the command is available in DMs.
        applicationCommandDMPermission :: Maybe Bool,
        -- | Autoincrementing version identifier updated during substantial record changes.
        applicationCommandVersion :: Snowflake
      }
  deriving (Int -> ApplicationCommand -> ShowS
[ApplicationCommand] -> ShowS
ApplicationCommand -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplicationCommand] -> ShowS
$cshowList :: [ApplicationCommand] -> ShowS
show :: ApplicationCommand -> String
$cshow :: ApplicationCommand -> String
showsPrec :: Int -> ApplicationCommand -> ShowS
$cshowsPrec :: Int -> ApplicationCommand -> ShowS
Show, ApplicationCommand -> ApplicationCommand -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplicationCommand -> ApplicationCommand -> Bool
$c/= :: ApplicationCommand -> ApplicationCommand -> Bool
== :: ApplicationCommand -> ApplicationCommand -> Bool
$c== :: ApplicationCommand -> ApplicationCommand -> Bool
Eq, ReadPrec [ApplicationCommand]
ReadPrec ApplicationCommand
Int -> ReadS ApplicationCommand
ReadS [ApplicationCommand]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplicationCommand]
$creadListPrec :: ReadPrec [ApplicationCommand]
readPrec :: ReadPrec ApplicationCommand
$creadPrec :: ReadPrec ApplicationCommand
readList :: ReadS [ApplicationCommand]
$creadList :: ReadS [ApplicationCommand]
readsPrec :: Int -> ReadS ApplicationCommand
$creadsPrec :: Int -> ReadS ApplicationCommand
Read)

instance FromJSON ApplicationCommand where
  parseJSON :: Value -> Parser ApplicationCommand
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"ApplicationCommand"
      ( \Object
v -> do
          ApplicationCommandId
acid <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
          ApplicationId
aid <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"application_id"
          Maybe GuildId
gid <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"guild_id"
          Text
name <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
          Maybe LocalizedText
lname <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name_localizations"
          Maybe Text
defPerm <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"default_member_permissions"
          Maybe Bool
dmPerm <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"dm_permission"
          Snowflake
version <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version"
          Maybe Int
t <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"type" :: Parser (Maybe Int)
          case Maybe Int
t of
            (Just Int
2) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ApplicationCommandId
-> ApplicationId
-> Maybe GuildId
-> Text
-> Maybe LocalizedText
-> Maybe Text
-> Maybe Bool
-> Snowflake
-> ApplicationCommand
ApplicationCommandUser ApplicationCommandId
acid ApplicationId
aid Maybe GuildId
gid Text
name Maybe LocalizedText
lname Maybe Text
defPerm Maybe Bool
dmPerm Snowflake
version
            (Just Int
3) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ApplicationCommandId
-> ApplicationId
-> Maybe GuildId
-> Text
-> Maybe LocalizedText
-> Maybe Text
-> Maybe Bool
-> Snowflake
-> ApplicationCommand
ApplicationCommandMessage ApplicationCommandId
acid ApplicationId
aid Maybe GuildId
gid Text
name Maybe LocalizedText
lname Maybe Text
defPerm Maybe Bool
dmPerm Snowflake
version
            Maybe Int
_ -> do
              Text
desc <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description"
              Maybe Options
options <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"options"
              Maybe LocalizedText
ldesc <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description_localizations"
              forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ApplicationCommandId
-> ApplicationId
-> Maybe GuildId
-> Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Maybe Options
-> Maybe Text
-> Maybe Bool
-> Snowflake
-> ApplicationCommand
ApplicationCommandChatInput ApplicationCommandId
acid ApplicationId
aid Maybe GuildId
gid Text
name Maybe LocalizedText
lname Text
desc Maybe LocalizedText
ldesc Maybe Options
options Maybe Text
defPerm Maybe Bool
dmPerm Snowflake
version
      )

-- | Either subcommands and groups, or values.
data Options
  = OptionsSubcommands [OptionSubcommandOrGroup]
  | OptionsValues [OptionValue]
  deriving (Int -> Options -> ShowS
[Options] -> ShowS
Options -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Options] -> ShowS
$cshowList :: [Options] -> ShowS
show :: Options -> String
$cshow :: Options -> String
showsPrec :: Int -> Options -> ShowS
$cshowsPrec :: Int -> Options -> ShowS
Show, Options -> Options -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Options -> Options -> Bool
$c/= :: Options -> Options -> Bool
== :: Options -> Options -> Bool
$c== :: Options -> Options -> Bool
Eq, ReadPrec [Options]
ReadPrec Options
Int -> ReadS Options
ReadS [Options]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Options]
$creadListPrec :: ReadPrec [Options]
readPrec :: ReadPrec Options
$creadPrec :: ReadPrec Options
readList :: ReadS [Options]
$creadList :: ReadS [Options]
readsPrec :: Int -> ReadS Options
$creadsPrec :: Int -> ReadS Options
Read)

instance FromJSON Options where
  parseJSON :: Value -> Parser Options
parseJSON =
    forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray
      String
"Options"
      ( \Array
a -> do
          let a' :: [Value]
a' = forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Array
a
          case [Value]
a' of
            [] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [OptionValue] -> Options
OptionsValues []
            (Value
v' : [Value]
_) ->
              forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
                String
"Options item"
                ( \Object
v -> do
                    Int
t <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type" :: Parser Int
                    if Int
t forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
|| Int
t forall a. Eq a => a -> a -> Bool
== Int
2
                      then [OptionSubcommandOrGroup] -> Options
OptionsSubcommands forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall a. FromJSON a => Value -> Parser a
parseJSON [Value]
a'
                      else [OptionValue] -> Options
OptionsValues forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall a. FromJSON a => Value -> Parser a
parseJSON [Value]
a'
                )
                Value
v'
      )

instance ToJSON Options where
  toJSON :: Options -> Value
toJSON (OptionsSubcommands [OptionSubcommandOrGroup]
o) = forall a. ToJSON a => a -> Value
toJSON [OptionSubcommandOrGroup]
o
  toJSON (OptionsValues [OptionValue]
o) = forall a. ToJSON a => a -> Value
toJSON [OptionValue]
o

-- | Either a subcommand group or a subcommand.
data OptionSubcommandOrGroup
  = OptionSubcommandGroup
      { -- | The name of the subcommand group
        OptionSubcommandOrGroup -> Text
optionSubcommandGroupName :: T.Text,
        -- | The localized name of the subcommand group
        OptionSubcommandOrGroup -> Maybe LocalizedText
optionSubcommandGroupLocalizedName :: Maybe LocalizedText,
        -- | The description of the subcommand group
        OptionSubcommandOrGroup -> Text
optionSubcommandGroupDescription :: T.Text,
        -- | The localized description of the subcommand group
        OptionSubcommandOrGroup -> Maybe LocalizedText
optionSubcommandGroupLocalizedDescription :: Maybe LocalizedText,
        -- | The subcommands in this subcommand group
        OptionSubcommandOrGroup -> [OptionSubcommand]
optionSubcommandGroupOptions :: [OptionSubcommand]
      }
  | OptionSubcommandOrGroupSubcommand OptionSubcommand
  deriving (Int -> OptionSubcommandOrGroup -> ShowS
[OptionSubcommandOrGroup] -> ShowS
OptionSubcommandOrGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionSubcommandOrGroup] -> ShowS
$cshowList :: [OptionSubcommandOrGroup] -> ShowS
show :: OptionSubcommandOrGroup -> String
$cshow :: OptionSubcommandOrGroup -> String
showsPrec :: Int -> OptionSubcommandOrGroup -> ShowS
$cshowsPrec :: Int -> OptionSubcommandOrGroup -> ShowS
Show, OptionSubcommandOrGroup -> OptionSubcommandOrGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionSubcommandOrGroup -> OptionSubcommandOrGroup -> Bool
$c/= :: OptionSubcommandOrGroup -> OptionSubcommandOrGroup -> Bool
== :: OptionSubcommandOrGroup -> OptionSubcommandOrGroup -> Bool
$c== :: OptionSubcommandOrGroup -> OptionSubcommandOrGroup -> Bool
Eq, ReadPrec [OptionSubcommandOrGroup]
ReadPrec OptionSubcommandOrGroup
Int -> ReadS OptionSubcommandOrGroup
ReadS [OptionSubcommandOrGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OptionSubcommandOrGroup]
$creadListPrec :: ReadPrec [OptionSubcommandOrGroup]
readPrec :: ReadPrec OptionSubcommandOrGroup
$creadPrec :: ReadPrec OptionSubcommandOrGroup
readList :: ReadS [OptionSubcommandOrGroup]
$creadList :: ReadS [OptionSubcommandOrGroup]
readsPrec :: Int -> ReadS OptionSubcommandOrGroup
$creadsPrec :: Int -> ReadS OptionSubcommandOrGroup
Read)

instance FromJSON OptionSubcommandOrGroup where
  parseJSON :: Value -> Parser OptionSubcommandOrGroup
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"OptionSubcommandOrGroup"
      ( \Object
v -> do
          Int
t <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type" :: Parser Int
          case Int
t of
            Int
2 ->
              Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> [OptionSubcommand]
-> OptionSubcommandOrGroup
OptionSubcommandGroup
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name_localizations"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description_localizations"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"options"
            Int
1 -> OptionSubcommand -> OptionSubcommandOrGroup
OptionSubcommandOrGroupSubcommand forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
v)
            Int
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unexpected subcommand group type"
      )

instance ToJSON OptionSubcommandOrGroup where
  toJSON :: OptionSubcommandOrGroup -> Value
toJSON OptionSubcommandGroup {[OptionSubcommand]
Maybe LocalizedText
Text
optionSubcommandGroupOptions :: [OptionSubcommand]
optionSubcommandGroupLocalizedDescription :: Maybe LocalizedText
optionSubcommandGroupDescription :: Text
optionSubcommandGroupLocalizedName :: Maybe LocalizedText
optionSubcommandGroupName :: Text
optionSubcommandGroupOptions :: OptionSubcommandOrGroup -> [OptionSubcommand]
optionSubcommandGroupLocalizedDescription :: OptionSubcommandOrGroup -> Maybe LocalizedText
optionSubcommandGroupDescription :: OptionSubcommandOrGroup -> Text
optionSubcommandGroupLocalizedName :: OptionSubcommandOrGroup -> Maybe LocalizedText
optionSubcommandGroupName :: OptionSubcommandOrGroup -> Text
..} =
    [Pair] -> Value
object
      [ (Key
"type", Scientific -> Value
Number Scientific
2),
        (Key
"name", forall a. ToJSON a => a -> Value
toJSON Text
optionSubcommandGroupName),
        (Key
"name_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionSubcommandGroupLocalizedName),
        (Key
"description", forall a. ToJSON a => a -> Value
toJSON Text
optionSubcommandGroupDescription),
        (Key
"description_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionSubcommandGroupLocalizedDescription),
        (Key
"options", forall a. ToJSON a => a -> Value
toJSON [OptionSubcommand]
optionSubcommandGroupOptions)
      ]
  toJSON (OptionSubcommandOrGroupSubcommand OptionSubcommand
a) = forall a. ToJSON a => a -> Value
toJSON OptionSubcommand
a

-- | Data for a single subcommand.
data OptionSubcommand = OptionSubcommand
  { -- | The name of the subcommand
    OptionSubcommand -> Text
optionSubcommandName :: T.Text,
    -- | The localized name of the subcommand
    OptionSubcommand -> Maybe LocalizedText
optionSubcommandLocalizedName :: Maybe LocalizedText,
    -- | The description of the subcommand
    OptionSubcommand -> Text
optionSubcommandDescription :: T.Text,
    -- | The localized description of the subcommand
    OptionSubcommand -> Maybe LocalizedText
optionSubcommandLocalizedDescription :: Maybe LocalizedText,
    -- | What options are there in this subcommand
    OptionSubcommand -> [OptionValue]
optionSubcommandOptions :: [OptionValue]
  }
  deriving (Int -> OptionSubcommand -> ShowS
[OptionSubcommand] -> ShowS
OptionSubcommand -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionSubcommand] -> ShowS
$cshowList :: [OptionSubcommand] -> ShowS
show :: OptionSubcommand -> String
$cshow :: OptionSubcommand -> String
showsPrec :: Int -> OptionSubcommand -> ShowS
$cshowsPrec :: Int -> OptionSubcommand -> ShowS
Show, OptionSubcommand -> OptionSubcommand -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionSubcommand -> OptionSubcommand -> Bool
$c/= :: OptionSubcommand -> OptionSubcommand -> Bool
== :: OptionSubcommand -> OptionSubcommand -> Bool
$c== :: OptionSubcommand -> OptionSubcommand -> Bool
Eq, ReadPrec [OptionSubcommand]
ReadPrec OptionSubcommand
Int -> ReadS OptionSubcommand
ReadS [OptionSubcommand]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OptionSubcommand]
$creadListPrec :: ReadPrec [OptionSubcommand]
readPrec :: ReadPrec OptionSubcommand
$creadPrec :: ReadPrec OptionSubcommand
readList :: ReadS [OptionSubcommand]
$creadList :: ReadS [OptionSubcommand]
readsPrec :: Int -> ReadS OptionSubcommand
$creadsPrec :: Int -> ReadS OptionSubcommand
Read)

instance FromJSON OptionSubcommand where
  parseJSON :: Value -> Parser OptionSubcommand
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"OptionSubcommand"
      ( \Object
v -> do
          Int
t <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type" :: Parser Int
          case Int
t of
            Int
1 ->
              Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> [OptionValue]
-> OptionSubcommand
OptionSubcommand
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name_localizations"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description_localizations"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"options" forall a. Parser (Maybe a) -> a -> Parser a
.!= []
            Int
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unexpected subcommand type"
      )

instance ToJSON OptionSubcommand where
  toJSON :: OptionSubcommand -> Value
toJSON OptionSubcommand {[OptionValue]
Maybe LocalizedText
Text
optionSubcommandOptions :: [OptionValue]
optionSubcommandLocalizedDescription :: Maybe LocalizedText
optionSubcommandDescription :: Text
optionSubcommandLocalizedName :: Maybe LocalizedText
optionSubcommandName :: Text
optionSubcommandOptions :: OptionSubcommand -> [OptionValue]
optionSubcommandLocalizedDescription :: OptionSubcommand -> Maybe LocalizedText
optionSubcommandDescription :: OptionSubcommand -> Text
optionSubcommandLocalizedName :: OptionSubcommand -> Maybe LocalizedText
optionSubcommandName :: OptionSubcommand -> Text
..} =
    [Pair] -> Value
object
      [ (Key
"type", Scientific -> Value
Number Scientific
1),
        (Key
"name", forall a. ToJSON a => a -> Value
toJSON Text
optionSubcommandName),
        (Key
"name_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionSubcommandLocalizedName),
        (Key
"description", forall a. ToJSON a => a -> Value
toJSON Text
optionSubcommandDescription),
        (Key
"description_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionSubcommandLocalizedDescription),
        (Key
"options", forall a. ToJSON a => a -> Value
toJSON [OptionValue]
optionSubcommandOptions)
      ]

-- | Data for a single value.
data OptionValue
  = OptionValueString
      { -- | The name of the value
        OptionValue -> Text
optionValueName :: T.Text,
        -- | The localized name of the value
        OptionValue -> Maybe LocalizedText
optionValueLocalizedName :: Maybe LocalizedText,
        -- | The description of the value
        OptionValue -> Text
optionValueDescription :: T.Text,
        -- | The localized description of the value
        OptionValue -> Maybe LocalizedText
optionValueLocalizedDescription :: Maybe LocalizedText,
        -- | Whether this option is required
        OptionValue -> Bool
optionValueRequired :: Bool,
        -- | Whether to autocomplete or have a list of named choices. For neither option, use `Left False`
        OptionValue -> AutocompleteOrChoice Text
optionValueStringChoices :: AutocompleteOrChoice T.Text,
        -- | The minimum length of the string (minimum 0)
        OptionValue -> Maybe Integer
optionValueStringMinLen :: Maybe Integer,
        -- | The maximum length of the string (minimum 1)
        OptionValue -> Maybe Integer
optionValueStringMaxLen :: Maybe Integer
      }
  | OptionValueInteger
      { -- | The name of the value
        optionValueName :: T.Text,
        -- | The localized name of the value
        optionValueLocalizedName :: Maybe LocalizedText,
        -- | The description of the value
        optionValueDescription :: T.Text,
        -- | The localized description of the value
        optionValueLocalizedDescription :: Maybe LocalizedText,
        -- | Whether this option is required
        optionValueRequired :: Bool,
        -- | Whether to autocomplete or have a list of named choices. For neither option, use `Left False`
        OptionValue -> AutocompleteOrChoice Integer
optionValueIntegerChoices :: AutocompleteOrChoice Integer,
        -- | The lower bound of values permitted. If choices are provided or autocomplete is on, this can be ignored
        OptionValue -> Maybe Integer
optionValueIntegerMinVal :: Maybe Integer,
        -- | The upper bound of values permitted. If choices are provided or autocomplete is on, this can be ignored
        OptionValue -> Maybe Integer
optionValueIntegerMaxVal :: Maybe Integer
      }
  | OptionValueBoolean
      { -- | The name of the value
        optionValueName :: T.Text,
        -- | The localized name of the value
        optionValueLocalizedName :: Maybe LocalizedText,
        -- | The description of the value
        optionValueDescription :: T.Text,
        -- | The localized description of the value
        optionValueLocalizedDescription :: Maybe LocalizedText,
        -- | Whether this option is required
        optionValueRequired :: Bool
      }
  | OptionValueUser
      { -- | The name of the value
        optionValueName :: T.Text,
        -- | The localized name of the value
        optionValueLocalizedName :: Maybe LocalizedText,
        -- | The description of the value
        optionValueDescription :: T.Text,
        -- | The localized description of the value
        optionValueLocalizedDescription :: Maybe LocalizedText,
        -- | Whether this option is required
        optionValueRequired :: Bool
      }
  | OptionValueChannel
      { -- | The name of the value
        optionValueName :: T.Text,
        -- | The localized name of the value
        optionValueLocalizedName :: Maybe LocalizedText,
        -- | The description of the value
        optionValueDescription :: T.Text,
        -- | The localized description of the value
        optionValueLocalizedDescription :: Maybe LocalizedText,
        -- | Whether this option is required
        optionValueRequired :: Bool,
        -- | What type of channel can be put in here
        OptionValue -> Maybe [ApplicationCommandChannelType]
optionValueChannelTypes :: Maybe [ApplicationCommandChannelType]
      }
  | OptionValueRole
      { -- | The name of the value
        optionValueName :: T.Text,
        -- | The localized name of the value
        optionValueLocalizedName :: Maybe LocalizedText,
        -- | The description of the value
        optionValueDescription :: T.Text,
        -- | The localized description of the value
        optionValueLocalizedDescription :: Maybe LocalizedText,
        -- | Whether this option is required
        optionValueRequired :: Bool
      }
  | OptionValueMentionable
      { -- | The name of the value
        optionValueName :: T.Text,
        -- | The localized name of the value
        optionValueLocalizedName :: Maybe LocalizedText,
        -- | The description of the value
        optionValueDescription :: T.Text,
        -- | The localized description of the value
        optionValueLocalizedDescription :: Maybe LocalizedText,
        -- | Whether this option is required
        optionValueRequired :: Bool
      }
  | OptionValueNumber
      { -- | The name of the value
        optionValueName :: T.Text,
        -- | The localized name of the value
        optionValueLocalizedName :: Maybe LocalizedText,
        -- | The description of the value
        optionValueDescription :: T.Text,
        -- | The localized description of the value
        optionValueLocalizedDescription :: Maybe LocalizedText,
        -- | Whether this option is required
        optionValueRequired :: Bool,
        -- | Whether to autocomplete or have a list of named choices. For neither option, use `Left False`
        OptionValue -> AutocompleteOrChoice Scientific
optionValueNumberChoices :: AutocompleteOrChoice Number,
        -- | The lower bound of values permitted. If choices are provided or autocomplete is on, this can be ignored
        OptionValue -> Maybe Scientific
optionValueNumberMinVal :: Maybe Number,
        -- | The upper bound of values permitted. If choices are provided or autocomplete is on, this can be ignored
        OptionValue -> Maybe Scientific
optionValueNumberMaxVal :: Maybe Number
      }
  deriving (Int -> OptionValue -> ShowS
[OptionValue] -> ShowS
OptionValue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionValue] -> ShowS
$cshowList :: [OptionValue] -> ShowS
show :: OptionValue -> String
$cshow :: OptionValue -> String
showsPrec :: Int -> OptionValue -> ShowS
$cshowsPrec :: Int -> OptionValue -> ShowS
Show, OptionValue -> OptionValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionValue -> OptionValue -> Bool
$c/= :: OptionValue -> OptionValue -> Bool
== :: OptionValue -> OptionValue -> Bool
$c== :: OptionValue -> OptionValue -> Bool
Eq, ReadPrec [OptionValue]
ReadPrec OptionValue
Int -> ReadS OptionValue
ReadS [OptionValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OptionValue]
$creadListPrec :: ReadPrec [OptionValue]
readPrec :: ReadPrec OptionValue
$creadPrec :: ReadPrec OptionValue
readList :: ReadS [OptionValue]
$creadList :: ReadS [OptionValue]
readsPrec :: Int -> ReadS OptionValue
$creadsPrec :: Int -> ReadS OptionValue
Read)

instance FromJSON OptionValue where
  parseJSON :: Value -> Parser OptionValue
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"OptionValue"
      ( \Object
v -> do
          Text
name <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
          Maybe LocalizedText
lname <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name_localizations"
          Text
desc <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"description"
          Maybe LocalizedText
ldesc <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description_localizations"
          Bool
required <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"required" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
          Int
t <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type" :: Parser Int
          case Int
t of
            Int
3 ->
              Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Bool
-> AutocompleteOrChoice Text
-> Maybe Integer
-> Maybe Integer
-> OptionValue
OptionValueString Text
name Maybe LocalizedText
lname Text
desc Maybe LocalizedText
ldesc Bool
required
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
v)
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"min_length"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"max_length"
            Int
4 ->
              Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Bool
-> AutocompleteOrChoice Integer
-> Maybe Integer
-> Maybe Integer
-> OptionValue
OptionValueInteger Text
name Maybe LocalizedText
lname Text
desc Maybe LocalizedText
ldesc Bool
required
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
v)
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"min_value"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"max_value"
            Int
10 ->
              Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Bool
-> AutocompleteOrChoice Scientific
-> Maybe Scientific
-> Maybe Scientific
-> OptionValue
OptionValueNumber Text
name Maybe LocalizedText
lname Text
desc Maybe LocalizedText
ldesc Bool
required
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
v)
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"min_value"
                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"max_value"
            Int
7 ->
              Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Bool
-> Maybe [ApplicationCommandChannelType]
-> OptionValue
OptionValueChannel Text
name Maybe LocalizedText
lname Text
desc Maybe LocalizedText
ldesc Bool
required
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"channel_types"
            Int
5 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Bool
-> OptionValue
OptionValueBoolean Text
name Maybe LocalizedText
lname Text
desc Maybe LocalizedText
ldesc Bool
required
            Int
6 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Bool
-> OptionValue
OptionValueUser Text
name Maybe LocalizedText
lname Text
desc Maybe LocalizedText
ldesc Bool
required
            Int
8 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Bool
-> OptionValue
OptionValueRole Text
name Maybe LocalizedText
lname Text
desc Maybe LocalizedText
ldesc Bool
required
            Int
9 -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Bool
-> OptionValue
OptionValueMentionable Text
name Maybe LocalizedText
lname Text
desc Maybe LocalizedText
ldesc Bool
required
            Int
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unknown application command option value type"
      )

instance ToJSON OptionValue where
  toJSON :: OptionValue -> Value
toJSON OptionValueString {Bool
Maybe Integer
Maybe LocalizedText
AutocompleteOrChoice Text
Text
optionValueStringMaxLen :: Maybe Integer
optionValueStringMinLen :: Maybe Integer
optionValueStringChoices :: AutocompleteOrChoice Text
optionValueRequired :: Bool
optionValueLocalizedDescription :: Maybe LocalizedText
optionValueDescription :: Text
optionValueLocalizedName :: Maybe LocalizedText
optionValueName :: Text
optionValueStringMaxLen :: OptionValue -> Maybe Integer
optionValueStringMinLen :: OptionValue -> Maybe Integer
optionValueStringChoices :: OptionValue -> AutocompleteOrChoice Text
optionValueRequired :: OptionValue -> Bool
optionValueLocalizedDescription :: OptionValue -> Maybe LocalizedText
optionValueDescription :: OptionValue -> Text
optionValueLocalizedName :: OptionValue -> Maybe LocalizedText
optionValueName :: OptionValue -> Text
..} =
    [Pair] -> Value
object
      [ (Key
"type", Scientific -> Value
Number Scientific
3),
        (Key
"name", forall a. ToJSON a => a -> Value
toJSON Text
optionValueName),
        (Key
"description", forall a. ToJSON a => a -> Value
toJSON Text
optionValueDescription),
        (Key
"name_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionValueLocalizedName),
        (Key
"description_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionValueLocalizedDescription),
        (Key
"required", forall a. ToJSON a => a -> Value
toJSON Bool
optionValueRequired),
        (Key
"min_length", forall a. ToJSON a => a -> Value
toJSON Maybe Integer
optionValueStringMinLen),
        (Key
"max_length", forall a. ToJSON a => a -> Value
toJSON Maybe Integer
optionValueStringMaxLen),
        forall a. ToJSON a => AutocompleteOrChoice a -> Pair
choiceOrAutocompleteToJSON AutocompleteOrChoice Text
optionValueStringChoices
      ]
  toJSON OptionValueInteger {Bool
Maybe Integer
Maybe LocalizedText
AutocompleteOrChoice Integer
Text
optionValueIntegerMaxVal :: Maybe Integer
optionValueIntegerMinVal :: Maybe Integer
optionValueIntegerChoices :: AutocompleteOrChoice Integer
optionValueRequired :: Bool
optionValueLocalizedDescription :: Maybe LocalizedText
optionValueDescription :: Text
optionValueLocalizedName :: Maybe LocalizedText
optionValueName :: Text
optionValueIntegerMaxVal :: OptionValue -> Maybe Integer
optionValueIntegerMinVal :: OptionValue -> Maybe Integer
optionValueIntegerChoices :: OptionValue -> AutocompleteOrChoice Integer
optionValueRequired :: OptionValue -> Bool
optionValueLocalizedDescription :: OptionValue -> Maybe LocalizedText
optionValueDescription :: OptionValue -> Text
optionValueLocalizedName :: OptionValue -> Maybe LocalizedText
optionValueName :: OptionValue -> Text
..} =
    [Pair] -> Value
object
      [ (Key
"type", Scientific -> Value
Number Scientific
4),
        (Key
"name", forall a. ToJSON a => a -> Value
toJSON Text
optionValueName),
        (Key
"description", forall a. ToJSON a => a -> Value
toJSON Text
optionValueDescription),
        (Key
"name_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionValueLocalizedName),
        (Key
"description_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionValueLocalizedDescription),
        (Key
"required", forall a. ToJSON a => a -> Value
toJSON Bool
optionValueRequired),
        (Key
"min_value", forall a. ToJSON a => a -> Value
toJSON Maybe Integer
optionValueIntegerMinVal),
        (Key
"max_value", forall a. ToJSON a => a -> Value
toJSON Maybe Integer
optionValueIntegerMaxVal),
        forall a. ToJSON a => AutocompleteOrChoice a -> Pair
choiceOrAutocompleteToJSON AutocompleteOrChoice Integer
optionValueIntegerChoices
      ]
  toJSON OptionValueNumber {Bool
Maybe Scientific
Maybe LocalizedText
AutocompleteOrChoice Scientific
Text
optionValueNumberMaxVal :: Maybe Scientific
optionValueNumberMinVal :: Maybe Scientific
optionValueNumberChoices :: AutocompleteOrChoice Scientific
optionValueRequired :: Bool
optionValueLocalizedDescription :: Maybe LocalizedText
optionValueDescription :: Text
optionValueLocalizedName :: Maybe LocalizedText
optionValueName :: Text
optionValueNumberMaxVal :: OptionValue -> Maybe Scientific
optionValueNumberMinVal :: OptionValue -> Maybe Scientific
optionValueNumberChoices :: OptionValue -> AutocompleteOrChoice Scientific
optionValueRequired :: OptionValue -> Bool
optionValueLocalizedDescription :: OptionValue -> Maybe LocalizedText
optionValueDescription :: OptionValue -> Text
optionValueLocalizedName :: OptionValue -> Maybe LocalizedText
optionValueName :: OptionValue -> Text
..} =
    [Pair] -> Value
object
      [ (Key
"type", Scientific -> Value
Number Scientific
10),
        (Key
"name", forall a. ToJSON a => a -> Value
toJSON Text
optionValueName),
        (Key
"description", forall a. ToJSON a => a -> Value
toJSON Text
optionValueDescription),
        (Key
"name_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionValueLocalizedName),
        (Key
"description_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionValueLocalizedDescription),
        (Key
"required", forall a. ToJSON a => a -> Value
toJSON Bool
optionValueRequired),
        (Key
"min_value", forall a. ToJSON a => a -> Value
toJSON Maybe Scientific
optionValueNumberMinVal),
        (Key
"max_value", forall a. ToJSON a => a -> Value
toJSON Maybe Scientific
optionValueNumberMaxVal),
        forall a. ToJSON a => AutocompleteOrChoice a -> Pair
choiceOrAutocompleteToJSON AutocompleteOrChoice Scientific
optionValueNumberChoices
      ]
  toJSON OptionValueChannel {Bool
Maybe [ApplicationCommandChannelType]
Maybe LocalizedText
Text
optionValueChannelTypes :: Maybe [ApplicationCommandChannelType]
optionValueRequired :: Bool
optionValueLocalizedDescription :: Maybe LocalizedText
optionValueDescription :: Text
optionValueLocalizedName :: Maybe LocalizedText
optionValueName :: Text
optionValueChannelTypes :: OptionValue -> Maybe [ApplicationCommandChannelType]
optionValueRequired :: OptionValue -> Bool
optionValueLocalizedDescription :: OptionValue -> Maybe LocalizedText
optionValueDescription :: OptionValue -> Text
optionValueLocalizedName :: OptionValue -> Maybe LocalizedText
optionValueName :: OptionValue -> Text
..} =
    [Pair] -> Value
object
      [ (Key
"type", Scientific -> Value
Number Scientific
7),
        (Key
"name", forall a. ToJSON a => a -> Value
toJSON Text
optionValueName),
        (Key
"description", forall a. ToJSON a => a -> Value
toJSON Text
optionValueDescription),
        (Key
"name_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionValueLocalizedName),
        (Key
"description_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
optionValueLocalizedDescription),
        (Key
"required", forall a. ToJSON a => a -> Value
toJSON Bool
optionValueRequired),
        (Key
"channel_types", forall a. ToJSON a => a -> Value
toJSON Maybe [ApplicationCommandChannelType]
optionValueChannelTypes)
      ]
  toJSON OptionValue
acov =
    [Pair] -> Value
object
      [ (Key
"type", Scientific -> Value
Number (forall {a}. Num a => OptionValue -> a
t OptionValue
acov)),
        (Key
"name", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ OptionValue -> Text
optionValueName OptionValue
acov),
        (Key
"description", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ OptionValue -> Text
optionValueDescription OptionValue
acov),
        (Key
"name_localizations", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ OptionValue -> Maybe LocalizedText
optionValueLocalizedName OptionValue
acov),
        (Key
"description_localizations", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ OptionValue -> Maybe LocalizedText
optionValueLocalizedDescription OptionValue
acov),
        (Key
"required", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ OptionValue -> Bool
optionValueRequired OptionValue
acov)
      ]
    where
      t :: OptionValue -> a
t OptionValueBoolean {} = a
5
      t OptionValueUser {} = a
6
      t OptionValueRole {} = a
8
      t OptionValueMentionable {} = a
9
      t OptionValue
_ = -a
1

-- | Data type to be used when creating application commands. The specification
-- is below.
--
-- If a command of the same type and and name is sent to the server, it will
-- overwrite any command that already exists in the same scope (guild vs
-- global).
--
-- The description has to be empty for non-slash command application
-- commands, as do the options. The options need to be `Nothing` for non-slash
-- commands, too. If one of the options is a subcommand or subcommand group,
-- the base command will no longer be usable.
--
-- A subcommand group can have subcommands within it. This is the maximum amount
-- of command nesting permitted.
--
-- https://discord.com/developers/docs/interactions/application-commands#create-global-application-command
data CreateApplicationCommand
  = CreateApplicationCommandChatInput
      { -- | The application command name (1-32 chars).
        CreateApplicationCommand -> Text
createName :: T.Text,
        -- | The localized application name
        CreateApplicationCommand -> Maybe LocalizedText
createLocalizedName :: Maybe LocalizedText,
        -- | The application command description (1-100 chars).
        CreateApplicationCommand -> Text
createDescription :: T.Text,
        -- | The localized application command description.
        CreateApplicationCommand -> Maybe LocalizedText
createLocalizedDescription :: Maybe LocalizedText,
        -- | What options the application (max length 25).
        CreateApplicationCommand -> Maybe Options
createOptions :: Maybe Options,
        -- | The default permissions required for members set when using the command
        -- in a guild.
        -- Set of permissions represented as a bit set.
        CreateApplicationCommand -> Maybe Text
createDefaultMemberPermissions :: Maybe T.Text,
        -- | Whether the command is available in DMs.
        CreateApplicationCommand -> Maybe Bool
createDMPermission :: Maybe Bool
      }
  | CreateApplicationCommandUser
      { -- | The application command name (1-32 chars).
        createName :: T.Text,
        -- | The localized application name
        createLocalizedName :: Maybe LocalizedText,
        -- | The default permissions required for members set when using the command
        -- in a guild.
        -- Set of permissions represented as a bit set.
        createDefaultMemberPermissions :: Maybe T.Text,
        -- | Whether the command is available in DMs.
        createDMPermission :: Maybe Bool
      }
  | CreateApplicationCommandMessage
      { -- | The application command name (1-32 chars).
        createName :: T.Text,
        -- | The localized application name
        createLocalizedName :: Maybe LocalizedText,
        -- | The default permissions required for members set when using the command
        -- in a guild.
        -- Set of permissions represented as a bit set.
        createDefaultMemberPermissions :: Maybe T.Text,
        -- | Whether the command is available in DMs.
        createDMPermission :: Maybe Bool
      }
  deriving (Int -> CreateApplicationCommand -> ShowS
[CreateApplicationCommand] -> ShowS
CreateApplicationCommand -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateApplicationCommand] -> ShowS
$cshowList :: [CreateApplicationCommand] -> ShowS
show :: CreateApplicationCommand -> String
$cshow :: CreateApplicationCommand -> String
showsPrec :: Int -> CreateApplicationCommand -> ShowS
$cshowsPrec :: Int -> CreateApplicationCommand -> ShowS
Show, CreateApplicationCommand -> CreateApplicationCommand -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateApplicationCommand -> CreateApplicationCommand -> Bool
$c/= :: CreateApplicationCommand -> CreateApplicationCommand -> Bool
== :: CreateApplicationCommand -> CreateApplicationCommand -> Bool
$c== :: CreateApplicationCommand -> CreateApplicationCommand -> Bool
Eq, ReadPrec [CreateApplicationCommand]
ReadPrec CreateApplicationCommand
Int -> ReadS CreateApplicationCommand
ReadS [CreateApplicationCommand]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateApplicationCommand]
$creadListPrec :: ReadPrec [CreateApplicationCommand]
readPrec :: ReadPrec CreateApplicationCommand
$creadPrec :: ReadPrec CreateApplicationCommand
readList :: ReadS [CreateApplicationCommand]
$creadList :: ReadS [CreateApplicationCommand]
readsPrec :: Int -> ReadS CreateApplicationCommand
$creadsPrec :: Int -> ReadS CreateApplicationCommand
Read)

instance ToJSON CreateApplicationCommand where
  toJSON :: CreateApplicationCommand -> Value
toJSON CreateApplicationCommandChatInput {Maybe Bool
Maybe Text
Maybe LocalizedText
Maybe Options
Text
createDMPermission :: Maybe Bool
createDefaultMemberPermissions :: Maybe Text
createOptions :: Maybe Options
createLocalizedDescription :: Maybe LocalizedText
createDescription :: Text
createLocalizedName :: Maybe LocalizedText
createName :: Text
createDMPermission :: CreateApplicationCommand -> Maybe Bool
createDefaultMemberPermissions :: CreateApplicationCommand -> Maybe Text
createOptions :: CreateApplicationCommand -> Maybe Options
createLocalizedDescription :: CreateApplicationCommand -> Maybe LocalizedText
createDescription :: CreateApplicationCommand -> Text
createLocalizedName :: CreateApplicationCommand -> Maybe LocalizedText
createName :: CreateApplicationCommand -> Text
..} =
    [Maybe Pair] -> Value
objectFromMaybes
      [ Key
"name" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Text
createName,
        Key
"name_localizations" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe LocalizedText
createLocalizedName,
        Key
"description" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Text
createDescription,
        Key
"description_localizations" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe LocalizedText
createLocalizedDescription,
        Key
"options" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Options
createOptions,
        Key
"default_member_permissions" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Maybe Text
createDefaultMemberPermissions,
        Key
"dm_permission" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Maybe Bool
createDMPermission,
        Key
"type" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Scientific -> Value
Number Scientific
1
      ]
  toJSON CreateApplicationCommandUser {Maybe Bool
Maybe Text
Maybe LocalizedText
Text
createDMPermission :: Maybe Bool
createDefaultMemberPermissions :: Maybe Text
createLocalizedName :: Maybe LocalizedText
createName :: Text
createDMPermission :: CreateApplicationCommand -> Maybe Bool
createDefaultMemberPermissions :: CreateApplicationCommand -> Maybe Text
createLocalizedName :: CreateApplicationCommand -> Maybe LocalizedText
createName :: CreateApplicationCommand -> Text
..} =
    [Maybe Pair] -> Value
objectFromMaybes
      [ Key
"name" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Text
createName,
        Key
"name_localizations" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe LocalizedText
createLocalizedName,
        Key
"default_member_permissions" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Maybe Text
createDefaultMemberPermissions,
        Key
"dm_permission" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Maybe Bool
createDMPermission,
        Key
"type" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Scientific -> Value
Number Scientific
2
      ]
  toJSON CreateApplicationCommandMessage {Maybe Bool
Maybe Text
Maybe LocalizedText
Text
createDMPermission :: Maybe Bool
createDefaultMemberPermissions :: Maybe Text
createLocalizedName :: Maybe LocalizedText
createName :: Text
createDMPermission :: CreateApplicationCommand -> Maybe Bool
createDefaultMemberPermissions :: CreateApplicationCommand -> Maybe Text
createLocalizedName :: CreateApplicationCommand -> Maybe LocalizedText
createName :: CreateApplicationCommand -> Text
..} =
    [Maybe Pair] -> Value
objectFromMaybes
      [ Key
"name" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Text
createName,
        Key
"name_localizations" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe LocalizedText
createLocalizedName,
        Key
"default_member_permissions" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Maybe Text
createDefaultMemberPermissions,
        Key
"dm_permission" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Maybe Bool
createDMPermission,
        Key
"type" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Scientific -> Value
Number Scientific
3
      ]

nameIsValid :: Bool -> T.Text -> Bool
nameIsValid :: Bool -> Text -> Bool
nameIsValid Bool
isChatInput Text
name = Int
l forall a. Ord a => a -> a -> Bool
>= Int
1 Bool -> Bool -> Bool
&& Int
l forall a. Ord a => a -> a -> Bool
<= Int
32 Bool -> Bool -> Bool
&& Bool
isChatInput forall a. Ord a => a -> a -> Bool
<= (Char -> Bool) -> Text -> Bool
T.all (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
validChars) Text
name
  where
    l :: Int
l = Text -> Int
T.length Text
name
    validChars :: String
validChars = Char
'-' forall a. a -> [a] -> [a]
: [Char
'a' .. Char
'z']

-- | Create the basics for a chat input (slash command). Use record overwriting
-- to enter the other values. The name needs to be all lower case letters, and
-- between 1 and 32 characters. The description has to be non-empty and less
-- than or equal to 100 characters.
createChatInput :: T.Text -> T.Text -> Maybe CreateApplicationCommand
createChatInput :: Text -> Text -> Maybe CreateApplicationCommand
createChatInput Text
name Text
desc
  | Bool -> Text -> Bool
nameIsValid Bool
True Text
name Bool -> Bool -> Bool
&& Bool -> Bool
not (Text -> Bool
T.null Text
desc) Bool -> Bool -> Bool
&& Text -> Int
T.length Text
desc forall a. Ord a => a -> a -> Bool
<= Int
100 = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text
-> Maybe LocalizedText
-> Text
-> Maybe LocalizedText
-> Maybe Options
-> Maybe Text
-> Maybe Bool
-> CreateApplicationCommand
CreateApplicationCommandChatInput Text
name forall a. Maybe a
Nothing Text
desc forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  | Bool
otherwise = forall a. Maybe a
Nothing

-- | Create the basics for a user command. Use record overwriting to enter the
-- other values. The name needs to be between 1 and 32 characters.
createUser :: T.Text -> Maybe CreateApplicationCommand
createUser :: Text -> Maybe CreateApplicationCommand
createUser Text
name
  | Bool -> Text -> Bool
nameIsValid Bool
False Text
name = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text
-> Maybe LocalizedText
-> Maybe Text
-> Maybe Bool
-> CreateApplicationCommand
CreateApplicationCommandUser Text
name forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  | Bool
otherwise = forall a. Maybe a
Nothing

-- | Create the basics for a message command. Use record overwriting to enter
-- the other values. The name needs to be between 1 and 32 characters.
createMessage :: T.Text -> Maybe CreateApplicationCommand
createMessage :: Text -> Maybe CreateApplicationCommand
createMessage Text
name
  | Bool -> Text -> Bool
nameIsValid Bool
False Text
name = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text
-> Maybe LocalizedText
-> Maybe Text
-> Maybe Bool
-> CreateApplicationCommand
CreateApplicationCommandMessage Text
name forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  | Bool
otherwise = forall a. Maybe a
Nothing

-- | Data type to be used when editing application commands. The specification
-- is below. See `CreateApplicationCommand` for an explanation for the
-- parameters.
--
-- https://discord.com/developers/docs/interactions/application-commands#edit-global-application-command
data EditApplicationCommand
  = EditApplicationCommandChatInput
      { EditApplicationCommand -> Maybe Text
editName :: Maybe T.Text,
        EditApplicationCommand -> Maybe LocalizedText
editLocalizedName :: Maybe LocalizedText,
        EditApplicationCommand -> Maybe Text
editDescription :: Maybe T.Text,
        EditApplicationCommand -> Maybe LocalizedText
editLocalizedDescription :: Maybe LocalizedText,
        EditApplicationCommand -> Maybe Options
editOptions :: Maybe Options,
        EditApplicationCommand -> Maybe Text
editDefaultMemberPermissions :: Maybe T.Text,
        EditApplicationCommand -> Maybe Bool
editDMPermission :: Maybe Bool
      }
  | EditApplicationCommandUser
      { editName :: Maybe T.Text,
        editLocalizedName :: Maybe LocalizedText,
        editDefaultMemberPermissions :: Maybe T.Text,
        editDMPermission :: Maybe Bool
      }
  | EditApplicationCommandMessage
      { editName :: Maybe T.Text,
        editLocalizedName :: Maybe LocalizedText,
        editDefaultMemberPermissions :: Maybe T.Text,
        editDMPermission :: Maybe Bool
      }

defaultEditApplicationCommand :: Int -> EditApplicationCommand
defaultEditApplicationCommand :: Int -> EditApplicationCommand
defaultEditApplicationCommand Int
2 = Maybe Text
-> Maybe LocalizedText
-> Maybe Text
-> Maybe Bool
-> EditApplicationCommand
EditApplicationCommandUser forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
defaultEditApplicationCommand Int
3 = Maybe Text
-> Maybe LocalizedText
-> Maybe Text
-> Maybe Bool
-> EditApplicationCommand
EditApplicationCommandMessage forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
defaultEditApplicationCommand Int
_ = Maybe Text
-> Maybe LocalizedText
-> Maybe Text
-> Maybe LocalizedText
-> Maybe Options
-> Maybe Text
-> Maybe Bool
-> EditApplicationCommand
EditApplicationCommandChatInput forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing

instance ToJSON EditApplicationCommand where
  toJSON :: EditApplicationCommand -> Value
toJSON EditApplicationCommandChatInput {Maybe Bool
Maybe Text
Maybe LocalizedText
Maybe Options
editDMPermission :: Maybe Bool
editDefaultMemberPermissions :: Maybe Text
editOptions :: Maybe Options
editLocalizedDescription :: Maybe LocalizedText
editDescription :: Maybe Text
editLocalizedName :: Maybe LocalizedText
editName :: Maybe Text
editDMPermission :: EditApplicationCommand -> Maybe Bool
editDefaultMemberPermissions :: EditApplicationCommand -> Maybe Text
editOptions :: EditApplicationCommand -> Maybe Options
editLocalizedDescription :: EditApplicationCommand -> Maybe LocalizedText
editDescription :: EditApplicationCommand -> Maybe Text
editLocalizedName :: EditApplicationCommand -> Maybe LocalizedText
editName :: EditApplicationCommand -> Maybe Text
..} =
    [Maybe Pair] -> Value
objectFromMaybes
      [ Key
"name" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Text
editName,
        Key
"name_localization" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe LocalizedText
editLocalizedName,
        Key
"description" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Text
editDescription,
        Key
"description_localization" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe LocalizedText
editLocalizedDescription,
        Key
"options" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Options
editOptions,
        Key
"default_member_permissions" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Text
editDefaultMemberPermissions,
        Key
"dm_permission" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Bool
editDMPermission,
        Key
"type" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Scientific -> Value
Number Scientific
1
      ]
  toJSON EditApplicationCommandUser {Maybe Bool
Maybe Text
Maybe LocalizedText
editDMPermission :: Maybe Bool
editDefaultMemberPermissions :: Maybe Text
editLocalizedName :: Maybe LocalizedText
editName :: Maybe Text
editDMPermission :: EditApplicationCommand -> Maybe Bool
editDefaultMemberPermissions :: EditApplicationCommand -> Maybe Text
editLocalizedName :: EditApplicationCommand -> Maybe LocalizedText
editName :: EditApplicationCommand -> Maybe Text
..} =
    [Maybe Pair] -> Value
objectFromMaybes
      [ Key
"name" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Text
editName,
        Key
"name_localization" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe LocalizedText
editLocalizedName,
        Key
"default_member_permissions" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Text
editDefaultMemberPermissions,
        Key
"dm_permission" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Bool
editDMPermission,
        Key
"type" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Scientific -> Value
Number Scientific
2
      ]
  toJSON EditApplicationCommandMessage {Maybe Bool
Maybe Text
Maybe LocalizedText
editDMPermission :: Maybe Bool
editDefaultMemberPermissions :: Maybe Text
editLocalizedName :: Maybe LocalizedText
editName :: Maybe Text
editDMPermission :: EditApplicationCommand -> Maybe Bool
editDefaultMemberPermissions :: EditApplicationCommand -> Maybe Text
editLocalizedName :: EditApplicationCommand -> Maybe LocalizedText
editName :: EditApplicationCommand -> Maybe Text
..} =
    [Maybe Pair] -> Value
objectFromMaybes
      [ Key
"name" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Text
editName,
        Key
"name_localization" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe LocalizedText
editLocalizedName,
        Key
"default_member_permissions" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Text
editDefaultMemberPermissions,
        Key
"dm_permission" forall a. ToJSON a => Key -> Maybe a -> Maybe Pair
.=? Maybe Bool
editDMPermission,
        Key
"type" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Scientific -> Value
Number Scientific
3
      ]

data Choice a = Choice
  { -- | The name of the choice
    forall a. Choice a -> Text
choiceName :: T.Text,
    -- | The localized name of the choice
    forall a. Choice a -> Maybe LocalizedText
choiceLocalizedName :: Maybe LocalizedText,
    -- | The value of the choice
    forall a. Choice a -> a
choiceValue :: a
  }
  deriving (Int -> Choice a -> ShowS
forall a. Show a => Int -> Choice a -> ShowS
forall a. Show a => [Choice a] -> ShowS
forall a. Show a => Choice a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Choice a] -> ShowS
$cshowList :: forall a. Show a => [Choice a] -> ShowS
show :: Choice a -> String
$cshow :: forall a. Show a => Choice a -> String
showsPrec :: Int -> Choice a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Choice a -> ShowS
Show, ReadPrec [Choice a]
ReadPrec (Choice a)
ReadS [Choice a]
forall a. Read a => ReadPrec [Choice a]
forall a. Read a => ReadPrec (Choice a)
forall a. Read a => Int -> ReadS (Choice a)
forall a. Read a => ReadS [Choice a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Choice a]
$creadListPrec :: forall a. Read a => ReadPrec [Choice a]
readPrec :: ReadPrec (Choice a)
$creadPrec :: forall a. Read a => ReadPrec (Choice a)
readList :: ReadS [Choice a]
$creadList :: forall a. Read a => ReadS [Choice a]
readsPrec :: Int -> ReadS (Choice a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Choice a)
Read, Choice a -> Choice a -> Bool
forall a. Eq a => Choice a -> Choice a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Choice a -> Choice a -> Bool
$c/= :: forall a. Eq a => Choice a -> Choice a -> Bool
== :: Choice a -> Choice a -> Bool
$c== :: forall a. Eq a => Choice a -> Choice a -> Bool
Eq, Choice a -> Choice a -> Bool
Choice a -> Choice a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Choice a)
forall a. Ord a => Choice a -> Choice a -> Bool
forall a. Ord a => Choice a -> Choice a -> Ordering
forall a. Ord a => Choice a -> Choice a -> Choice a
min :: Choice a -> Choice a -> Choice a
$cmin :: forall a. Ord a => Choice a -> Choice a -> Choice a
max :: Choice a -> Choice a -> Choice a
$cmax :: forall a. Ord a => Choice a -> Choice a -> Choice a
>= :: Choice a -> Choice a -> Bool
$c>= :: forall a. Ord a => Choice a -> Choice a -> Bool
> :: Choice a -> Choice a -> Bool
$c> :: forall a. Ord a => Choice a -> Choice a -> Bool
<= :: Choice a -> Choice a -> Bool
$c<= :: forall a. Ord a => Choice a -> Choice a -> Bool
< :: Choice a -> Choice a -> Bool
$c< :: forall a. Ord a => Choice a -> Choice a -> Bool
compare :: Choice a -> Choice a -> Ordering
$ccompare :: forall a. Ord a => Choice a -> Choice a -> Ordering
Ord)

instance Functor Choice where
  fmap :: forall a b. (a -> b) -> Choice a -> Choice b
fmap a -> b
f (Choice Text
s Maybe LocalizedText
l a
a) = forall a. Text -> Maybe LocalizedText -> a -> Choice a
Choice Text
s Maybe LocalizedText
l (a -> b
f a
a)

instance (ToJSON a) => ToJSON (Choice a) where
  toJSON :: Choice a -> Value
toJSON Choice {a
Maybe LocalizedText
Text
choiceValue :: a
choiceLocalizedName :: Maybe LocalizedText
choiceName :: Text
choiceValue :: forall a. Choice a -> a
choiceLocalizedName :: forall a. Choice a -> Maybe LocalizedText
choiceName :: forall a. Choice a -> Text
..} =
    [Pair] -> Value
object
      [ (Key
"name", forall a. ToJSON a => a -> Value
toJSON Text
choiceName),
        (Key
"value", forall a. ToJSON a => a -> Value
toJSON a
choiceValue),
        (Key
"name_localizations", forall a. ToJSON a => a -> Value
toJSON Maybe LocalizedText
choiceLocalizedName)
      ]

instance (FromJSON a) => FromJSON (Choice a) where
  parseJSON :: Value -> Parser (Choice a)
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"Choice"
      ( \Object
v ->
          forall a. Text -> Maybe LocalizedText -> a -> Choice a
Choice
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name_localizations"
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"value"
      )

type AutocompleteOrChoice a = Either Bool [Choice a]

instance {-# OVERLAPPING #-} (FromJSON a) => FromJSON (AutocompleteOrChoice a) where
  parseJSON :: Value -> Parser (AutocompleteOrChoice a)
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"AutocompleteOrChoice"
      ( \Object
v -> do
          Maybe [Choice a]
mcs <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:! Key
"choices"
          case Maybe [Choice a]
mcs of
            Maybe [Choice a]
Nothing -> forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"autocomplete" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
            Just [Choice a]
cs -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right [Choice a]
cs
      )

choiceOrAutocompleteToJSON :: (ToJSON a) => AutocompleteOrChoice a -> Pair
choiceOrAutocompleteToJSON :: forall a. ToJSON a => AutocompleteOrChoice a -> Pair
choiceOrAutocompleteToJSON (Left Bool
b) = (Key
"autocomplete", forall a. ToJSON a => a -> Value
toJSON Bool
b)
choiceOrAutocompleteToJSON (Right [Choice a]
cs) = (Key
"choices", forall a. ToJSON a => a -> Value
toJSON [Choice a]
cs)

-- | The different channel types.
--
-- https://discord.com/developers/docs/resources/channel#channel-object-channel-types
data ApplicationCommandChannelType
  = -- | A text channel in a server.
    ApplicationCommandChannelTypeGuildText
  | -- | A direct message between users.
    ApplicationCommandChannelTypeDM
  | -- | A voice channel in a server.
    ApplicationCommandChannelTypeGuildVoice
  | -- | A direct message between multiple users.
    ApplicationCommandChannelTypeGroupDM
  | -- | An organizational category that contains up to 50 channels.
    ApplicationCommandChannelTypeGuildCategory
  | -- | A channel that users can follow and crosspost into their own server.
    ApplicationCommandChannelTypeGuildNews
  | -- | A channel in which game developers can sell their game on discord.
    ApplicationCommandChannelTypeGuildStore
  | -- | A temporary sub-channel within a guild_news channel.
    ApplicationCommandChannelTypeGuildNewsThread
  | -- | A temporary sub-channel within a guild_text channel.
    ApplicationCommandChannelTypeGuildPublicThread
  | -- | A temporary sub-channel within a GUILD_TEXT channel that is only
    -- viewable by those invited and those with the MANAGE_THREADS permission
    ApplicationCommandChannelTypeGuildPrivateThread
  | -- | A voice channel for hosting events with an audience.
    ApplicationCommandChannelTypeGuildStageVoice
  deriving (Int -> ApplicationCommandChannelType -> ShowS
[ApplicationCommandChannelType] -> ShowS
ApplicationCommandChannelType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplicationCommandChannelType] -> ShowS
$cshowList :: [ApplicationCommandChannelType] -> ShowS
show :: ApplicationCommandChannelType -> String
$cshow :: ApplicationCommandChannelType -> String
showsPrec :: Int -> ApplicationCommandChannelType -> ShowS
$cshowsPrec :: Int -> ApplicationCommandChannelType -> ShowS
Show, ReadPrec [ApplicationCommandChannelType]
ReadPrec ApplicationCommandChannelType
Int -> ReadS ApplicationCommandChannelType
ReadS [ApplicationCommandChannelType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplicationCommandChannelType]
$creadListPrec :: ReadPrec [ApplicationCommandChannelType]
readPrec :: ReadPrec ApplicationCommandChannelType
$creadPrec :: ReadPrec ApplicationCommandChannelType
readList :: ReadS [ApplicationCommandChannelType]
$creadList :: ReadS [ApplicationCommandChannelType]
readsPrec :: Int -> ReadS ApplicationCommandChannelType
$creadsPrec :: Int -> ReadS ApplicationCommandChannelType
Read, Typeable ApplicationCommandChannelType
ApplicationCommandChannelType -> DataType
ApplicationCommandChannelType -> Constr
(forall b. Data b => b -> b)
-> ApplicationCommandChannelType -> ApplicationCommandChannelType
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u)
-> ApplicationCommandChannelType
-> u
forall u.
(forall d. Data d => d -> u)
-> ApplicationCommandChannelType -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ApplicationCommandChannelType
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ApplicationCommandChannelType
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ApplicationCommandChannelType -> m ApplicationCommandChannelType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApplicationCommandChannelType -> m ApplicationCommandChannelType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c ApplicationCommandChannelType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ApplicationCommandChannelType
-> c ApplicationCommandChannelType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ApplicationCommandChannelType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApplicationCommandChannelType)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApplicationCommandChannelType -> m ApplicationCommandChannelType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApplicationCommandChannelType -> m ApplicationCommandChannelType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApplicationCommandChannelType -> m ApplicationCommandChannelType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ApplicationCommandChannelType -> m ApplicationCommandChannelType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ApplicationCommandChannelType -> m ApplicationCommandChannelType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ApplicationCommandChannelType -> m ApplicationCommandChannelType
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u)
-> ApplicationCommandChannelType
-> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u)
-> ApplicationCommandChannelType
-> u
gmapQ :: forall u.
(forall d. Data d => d -> u)
-> ApplicationCommandChannelType -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u)
-> ApplicationCommandChannelType -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ApplicationCommandChannelType
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ApplicationCommandChannelType
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ApplicationCommandChannelType
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ApplicationCommandChannelType
-> r
gmapT :: (forall b. Data b => b -> b)
-> ApplicationCommandChannelType -> ApplicationCommandChannelType
$cgmapT :: (forall b. Data b => b -> b)
-> ApplicationCommandChannelType -> ApplicationCommandChannelType
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApplicationCommandChannelType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ApplicationCommandChannelType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ApplicationCommandChannelType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c ApplicationCommandChannelType)
dataTypeOf :: ApplicationCommandChannelType -> DataType
$cdataTypeOf :: ApplicationCommandChannelType -> DataType
toConstr :: ApplicationCommandChannelType -> Constr
$ctoConstr :: ApplicationCommandChannelType -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c ApplicationCommandChannelType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r)
-> Constr
-> c ApplicationCommandChannelType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ApplicationCommandChannelType
-> c ApplicationCommandChannelType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ApplicationCommandChannelType
-> c ApplicationCommandChannelType
Data, ApplicationCommandChannelType
-> ApplicationCommandChannelType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplicationCommandChannelType
-> ApplicationCommandChannelType -> Bool
$c/= :: ApplicationCommandChannelType
-> ApplicationCommandChannelType -> Bool
== :: ApplicationCommandChannelType
-> ApplicationCommandChannelType -> Bool
$c== :: ApplicationCommandChannelType
-> ApplicationCommandChannelType -> Bool
Eq)

instance InternalDiscordEnum ApplicationCommandChannelType where
  discordTypeStartValue :: ApplicationCommandChannelType
discordTypeStartValue = ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildText
  fromDiscordType :: ApplicationCommandChannelType -> Int
fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildText = Int
0
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeDM = Int
1
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildVoice = Int
2
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGroupDM = Int
3
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildCategory = Int
4
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildNews = Int
5
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildStore = Int
6
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildNewsThread = Int
10
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildPublicThread = Int
11
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildPrivateThread = Int
12
  fromDiscordType ApplicationCommandChannelType
ApplicationCommandChannelTypeGuildStageVoice = Int
13

instance ToJSON ApplicationCommandChannelType where
  toJSON :: ApplicationCommandChannelType -> Value
toJSON = forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. InternalDiscordEnum a => a -> Int
fromDiscordType

instance FromJSON ApplicationCommandChannelType where
  parseJSON :: Value -> Parser ApplicationCommandChannelType
parseJSON = forall a. InternalDiscordEnum a => String -> Value -> Parser a
discordTypeParseJSON String
"ApplicationCommandChannelType"

data GuildApplicationCommandPermissions = GuildApplicationCommandPermissions
  { -- | The id of the command.
    GuildApplicationCommandPermissions -> ApplicationCommandId
guildApplicationCommandPermissionsId :: ApplicationCommandId,
    -- | The id of the application.
    GuildApplicationCommandPermissions -> ApplicationId
guildApplicationCommandPermissionsApplicationId :: ApplicationId,
    -- | The id of the guild.
    GuildApplicationCommandPermissions -> GuildId
guildApplicationCommandPermissionsGuildId :: GuildId,
    -- | The permissions for the command in the guild.
    GuildApplicationCommandPermissions
-> [ApplicationCommandPermissions]
guildApplicationCommandPermissionsPermissions :: [ApplicationCommandPermissions]
  }
  deriving (Int -> GuildApplicationCommandPermissions -> ShowS
[GuildApplicationCommandPermissions] -> ShowS
GuildApplicationCommandPermissions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GuildApplicationCommandPermissions] -> ShowS
$cshowList :: [GuildApplicationCommandPermissions] -> ShowS
show :: GuildApplicationCommandPermissions -> String
$cshow :: GuildApplicationCommandPermissions -> String
showsPrec :: Int -> GuildApplicationCommandPermissions -> ShowS
$cshowsPrec :: Int -> GuildApplicationCommandPermissions -> ShowS
Show, ReadPrec [GuildApplicationCommandPermissions]
ReadPrec GuildApplicationCommandPermissions
Int -> ReadS GuildApplicationCommandPermissions
ReadS [GuildApplicationCommandPermissions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GuildApplicationCommandPermissions]
$creadListPrec :: ReadPrec [GuildApplicationCommandPermissions]
readPrec :: ReadPrec GuildApplicationCommandPermissions
$creadPrec :: ReadPrec GuildApplicationCommandPermissions
readList :: ReadS [GuildApplicationCommandPermissions]
$creadList :: ReadS [GuildApplicationCommandPermissions]
readsPrec :: Int -> ReadS GuildApplicationCommandPermissions
$creadsPrec :: Int -> ReadS GuildApplicationCommandPermissions
Read, GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
$c/= :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
== :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
$c== :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
Eq, Eq GuildApplicationCommandPermissions
GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Ordering
GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
$cmin :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
max :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
$cmax :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions
>= :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
$c>= :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
> :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
$c> :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
<= :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
$c<= :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
< :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
$c< :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Bool
compare :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Ordering
$ccompare :: GuildApplicationCommandPermissions
-> GuildApplicationCommandPermissions -> Ordering
Ord)

instance FromJSON GuildApplicationCommandPermissions where
  parseJSON :: Value -> Parser GuildApplicationCommandPermissions
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"GuildApplicationCommandPermissions"
      ( \Object
v ->
          ApplicationCommandId
-> ApplicationId
-> GuildId
-> [ApplicationCommandPermissions]
-> GuildApplicationCommandPermissions
GuildApplicationCommandPermissions
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"application_id"
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"guild_id"
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"permissions"
      )

instance ToJSON GuildApplicationCommandPermissions where
  toJSON :: GuildApplicationCommandPermissions -> Value
toJSON GuildApplicationCommandPermissions {[ApplicationCommandPermissions]
ApplicationCommandId
ApplicationId
GuildId
guildApplicationCommandPermissionsPermissions :: [ApplicationCommandPermissions]
guildApplicationCommandPermissionsGuildId :: GuildId
guildApplicationCommandPermissionsApplicationId :: ApplicationId
guildApplicationCommandPermissionsId :: ApplicationCommandId
guildApplicationCommandPermissionsPermissions :: GuildApplicationCommandPermissions
-> [ApplicationCommandPermissions]
guildApplicationCommandPermissionsGuildId :: GuildApplicationCommandPermissions -> GuildId
guildApplicationCommandPermissionsApplicationId :: GuildApplicationCommandPermissions -> ApplicationId
guildApplicationCommandPermissionsId :: GuildApplicationCommandPermissions -> ApplicationCommandId
..} =
    [Maybe Pair] -> Value
objectFromMaybes
      [ Key
"id" forall a. ToJSON a => Key -> a -> Maybe Pair
.== ApplicationCommandId
guildApplicationCommandPermissionsId,
        Key
"application_id" forall a. ToJSON a => Key -> a -> Maybe Pair
.== ApplicationId
guildApplicationCommandPermissionsApplicationId,
        Key
"guild_id" forall a. ToJSON a => Key -> a -> Maybe Pair
.== GuildId
guildApplicationCommandPermissionsGuildId,
        Key
"permissions" forall a. ToJSON a => Key -> a -> Maybe Pair
.== [ApplicationCommandPermissions]
guildApplicationCommandPermissionsPermissions
      ]

-- | Application command permissions allow you to enable or disable commands for
-- specific users or roles within a guild.
data ApplicationCommandPermissions = ApplicationCommandPermissions
  { -- | The id of the role or user.
    ApplicationCommandPermissions -> Snowflake
applicationCommandPermissionsId :: Snowflake,
    -- | Choose either role (1) or user (2).
    ApplicationCommandPermissions -> Integer
applicationCommandPermissionsType :: Integer,
    -- | Whether to allow or not.
    ApplicationCommandPermissions -> Bool
applicationCommandPermissionsPermission :: Bool
  }
  deriving (Int -> ApplicationCommandPermissions -> ShowS
[ApplicationCommandPermissions] -> ShowS
ApplicationCommandPermissions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApplicationCommandPermissions] -> ShowS
$cshowList :: [ApplicationCommandPermissions] -> ShowS
show :: ApplicationCommandPermissions -> String
$cshow :: ApplicationCommandPermissions -> String
showsPrec :: Int -> ApplicationCommandPermissions -> ShowS
$cshowsPrec :: Int -> ApplicationCommandPermissions -> ShowS
Show, ReadPrec [ApplicationCommandPermissions]
ReadPrec ApplicationCommandPermissions
Int -> ReadS ApplicationCommandPermissions
ReadS [ApplicationCommandPermissions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApplicationCommandPermissions]
$creadListPrec :: ReadPrec [ApplicationCommandPermissions]
readPrec :: ReadPrec ApplicationCommandPermissions
$creadPrec :: ReadPrec ApplicationCommandPermissions
readList :: ReadS [ApplicationCommandPermissions]
$creadList :: ReadS [ApplicationCommandPermissions]
readsPrec :: Int -> ReadS ApplicationCommandPermissions
$creadsPrec :: Int -> ReadS ApplicationCommandPermissions
Read, ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
$c/= :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
== :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
$c== :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
Eq, Eq ApplicationCommandPermissions
ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Ordering
ApplicationCommandPermissions
-> ApplicationCommandPermissions -> ApplicationCommandPermissions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> ApplicationCommandPermissions
$cmin :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> ApplicationCommandPermissions
max :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> ApplicationCommandPermissions
$cmax :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> ApplicationCommandPermissions
>= :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
$c>= :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
> :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
$c> :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
<= :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
$c<= :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
< :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
$c< :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Bool
compare :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Ordering
$ccompare :: ApplicationCommandPermissions
-> ApplicationCommandPermissions -> Ordering
Ord)

instance FromJSON ApplicationCommandPermissions where
  parseJSON :: Value -> Parser ApplicationCommandPermissions
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject
      String
"ApplicationCommandPermissions"
      ( \Object
v ->
          Snowflake -> Integer -> Bool -> ApplicationCommandPermissions
ApplicationCommandPermissions
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"permission"
      )

instance ToJSON ApplicationCommandPermissions where
  toJSON :: ApplicationCommandPermissions -> Value
toJSON ApplicationCommandPermissions {Bool
Integer
Snowflake
applicationCommandPermissionsPermission :: Bool
applicationCommandPermissionsType :: Integer
applicationCommandPermissionsId :: Snowflake
applicationCommandPermissionsPermission :: ApplicationCommandPermissions -> Bool
applicationCommandPermissionsType :: ApplicationCommandPermissions -> Integer
applicationCommandPermissionsId :: ApplicationCommandPermissions -> Snowflake
..} =
    [Maybe Pair] -> Value
objectFromMaybes
      [ Key
"id" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Snowflake
applicationCommandPermissionsId,
        Key
"type" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Integer
applicationCommandPermissionsType,
        Key
"permission" forall a. ToJSON a => Key -> a -> Maybe Pair
.== Bool
applicationCommandPermissionsPermission
      ]

-- | A discord locale. See
-- <https://discord.com/developers/docs/reference#locales> for available locales
type Locale = T.Text

-- | Translations for a text
type LocalizedText = Map Locale T.Text