discord-haskell-1.11.0: Write bots for Discord in Haskell
Safe HaskellNone
LanguageHaskell2010

Discord.Internal.Types.ApplicationCommands

Synopsis

Documentation

data ApplicationCommand Source #

data ApplicationCommandOptionSubcommandOrGroup Source #

data ApplicationCommandOptionSubcommand Source #

data ApplicationCommandOptionValue Source #

Constructors

ApplicationCommandOptionValueString 
ApplicationCommandOptionValueInteger 
ApplicationCommandOptionValueBoolean 
ApplicationCommandOptionValueUser 
ApplicationCommandOptionValueChannel 
ApplicationCommandOptionValueRole 
ApplicationCommandOptionValueMentionable 
ApplicationCommandOptionValueNumber 

data InternalApplicationCommand Source #

The full information about an application command, obtainable with the various get requests. In theory, you never need to construct one of these - so if you are, reconsider what you're doing.

https://discord.com/developers/docs/interactions/application-commands#application-command-object-application-command-structure

Constructors

InternalApplicationCommand 

Fields

data CreateApplicationCommand Source #

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

Constructors

CreateApplicationCommand 

Fields

createApplicationCommandChatInput :: Text -> Text -> Maybe CreateApplicationCommand Source #

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.

createApplicationCommandUser :: Text -> Maybe CreateApplicationCommand Source #

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.

createApplicationCommandMessage :: Text -> Maybe CreateApplicationCommand Source #

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.

data ApplicationCommandType Source #

What type of application command. Represents slash commands, right clicking a user, and right clicking a message respectively.

Instances

Instances details
Enum ApplicationCommandType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Eq ApplicationCommandType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Data ApplicationCommandType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationCommandType -> c ApplicationCommandType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationCommandType #

toConstr :: ApplicationCommandType -> Constr #

dataTypeOf :: ApplicationCommandType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationCommandType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationCommandType) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationCommandType -> ApplicationCommandType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationCommandType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationCommandType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationCommandType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationCommandType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationCommandType -> m ApplicationCommandType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationCommandType -> m ApplicationCommandType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationCommandType -> m ApplicationCommandType #

Read ApplicationCommandType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Show ApplicationCommandType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON ApplicationCommandType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

FromJSON ApplicationCommandType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

data InternalApplicationCommandOption Source #

Constructors

InternalApplicationCommandOption 

Fields

Instances

Instances details
Eq InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Read InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Show InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

FromJSON InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Internals ApplicationCommandOptionValue InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Internals ApplicationCommandOptionSubcommand InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Internals ApplicationCommandOptionSubcommandOrGroup InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

data ApplicationCommandOptionType Source #

What type of command option. Can represent a wide variety of types, so please check out the documentation below.

https://discord.com/developers/docs/interactions/application-commands#application-command-object-application-command-option-type

Constructors

ApplicationCommandOptionTypeSubcommand

A subcommand. It can take further options, excluding sub commands and sub command groups.

ApplicationCommandOptionTypeSubcommandGroup

A subcommand group. It can take further options, excluding sub command groups.

ApplicationCommandOptionTypeString

Can typically be provided with default values.

ApplicationCommandOptionTypeInteger

Can typically be provided with default values, and possibly with minimum and maximum values.

ApplicationCommandOptionTypeBoolean 
ApplicationCommandOptionTypeUser 
ApplicationCommandOptionTypeChannel

Can be limited in the types of the channel allowed.

ApplicationCommandOptionTypeRole 
ApplicationCommandOptionTypeMentionable

Users and roles.

ApplicationCommandOptionTypeNumber

Can typically be provided with default values, and possibly with minimum and maximum values. Represents a double.

Instances

Instances details
Enum ApplicationCommandOptionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Eq ApplicationCommandOptionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Data ApplicationCommandOptionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationCommandOptionType -> c ApplicationCommandOptionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationCommandOptionType #

toConstr :: ApplicationCommandOptionType -> Constr #

dataTypeOf :: ApplicationCommandOptionType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationCommandOptionType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationCommandOptionType) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationCommandOptionType -> ApplicationCommandOptionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationCommandOptionType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationCommandOptionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationCommandOptionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationCommandOptionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationCommandOptionType -> m ApplicationCommandOptionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationCommandOptionType -> m ApplicationCommandOptionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationCommandOptionType -> m ApplicationCommandOptionType #

Read ApplicationCommandOptionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Show ApplicationCommandOptionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON ApplicationCommandOptionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

FromJSON ApplicationCommandOptionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

data Choice a Source #

Constructors

Choice 

Fields

Instances

Instances details
Functor Choice Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Methods

fmap :: (a -> b) -> Choice a -> Choice b #

(<$) :: a -> Choice b -> Choice a #

Eq a => Eq (Choice a) Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Methods

(==) :: Choice a -> Choice a -> Bool #

(/=) :: Choice a -> Choice a -> Bool #

Read a => Read (Choice a) Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Show a => Show (Choice a) Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Methods

showsPrec :: Int -> Choice a -> ShowS #

show :: Choice a -> String #

showList :: [Choice a] -> ShowS #

ToJSON a => ToJSON (Choice a) Source #

The choices for a particular option. data InternalApplicationCommandOptionChoice = InternalApplicationCommandOptionChoice { internalApplicationCommandOptionChoiceName :: T.Text, internalApplicationCommandOptionChoiceValue :: StringNumberValue } deriving (Show, Read, Eq)

Instance details

Defined in Discord.Internal.Types.ApplicationCommands

FromJSON a => FromJSON (Choice a) Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

data ApplicationCommandChannelType Source #

Constructors

ApplicationCommandChannelTypeGuildText

A text channel in a server.

ApplicationCommandChannelTypeDM

A direct message between users.

ApplicationCommandChannelTypeGuildVoice

A voice channel in a server.

ApplicationCommandChannelTypeGroupDM

A direct message between multiple users.

ApplicationCommandChannelTypeGuildCategory

An organizational category that contains up to 50 channels.

ApplicationCommandChannelTypeGuildNews

A channel that users can follow and crosspost into their own server.

ApplicationCommandChannelTypeGuildStore

A channel in which game developers can sell their game on discord.

ApplicationCommandChannelTypeGuildNewsThread

A temporary sub-channel within a guild_news channel.

ApplicationCommandChannelTypeGuildPublicThread

A temporary sub-channel within a guild_text channel

ApplicationCommandChannelTypeGuildPrivateThread

A temporary sub-channel within a GUILD_TEXT channel that is only viewable by those invited and those with the MANAGE_THREADS permission

ApplicationCommandChannelTypeGuildStageVoice

A voice channel for hosting events with an audience.

Instances

Instances details
Enum ApplicationCommandChannelType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Eq ApplicationCommandChannelType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Data ApplicationCommandChannelType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationCommandChannelType -> c ApplicationCommandChannelType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationCommandChannelType #

toConstr :: ApplicationCommandChannelType -> Constr #

dataTypeOf :: ApplicationCommandChannelType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationCommandChannelType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationCommandChannelType) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationCommandChannelType -> ApplicationCommandChannelType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationCommandChannelType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationCommandChannelType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationCommandChannelType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationCommandChannelType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationCommandChannelType -> m ApplicationCommandChannelType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationCommandChannelType -> m ApplicationCommandChannelType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationCommandChannelType -> m ApplicationCommandChannelType #

Read ApplicationCommandChannelType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Show ApplicationCommandChannelType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON ApplicationCommandChannelType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

FromJSON ApplicationCommandChannelType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

data GuildApplicationCommandPermissions Source #

Instances

Instances details
Eq GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Ord GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Read GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Show GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

FromJSON GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

data ApplicationCommandPermissions Source #

Instances

Instances details
Eq ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Ord ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Read ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Show ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

FromJSON ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

data ApplicationCommandPermissionType Source #

Instances

Instances details
Enum ApplicationCommandPermissionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Eq ApplicationCommandPermissionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Data ApplicationCommandPermissionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicationCommandPermissionType -> c ApplicationCommandPermissionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ApplicationCommandPermissionType #

toConstr :: ApplicationCommandPermissionType -> Constr #

dataTypeOf :: ApplicationCommandPermissionType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ApplicationCommandPermissionType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ApplicationCommandPermissionType) #

gmapT :: (forall b. Data b => b -> b) -> ApplicationCommandPermissionType -> ApplicationCommandPermissionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationCommandPermissionType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicationCommandPermissionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicationCommandPermissionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicationCommandPermissionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicationCommandPermissionType -> m ApplicationCommandPermissionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationCommandPermissionType -> m ApplicationCommandPermissionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicationCommandPermissionType -> m ApplicationCommandPermissionType #

Ord ApplicationCommandPermissionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Read ApplicationCommandPermissionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Show ApplicationCommandPermissionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON ApplicationCommandPermissionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

FromJSON ApplicationCommandPermissionType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands