discord-haskell-1.16.1: Write bots for Discord in Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Discord.Internal.Types.ApplicationCommands

Synopsis

Documentation

data ApplicationCommand Source #

The structure for an application command.

Constructors

ApplicationCommandUser 

Fields

ApplicationCommandMessage 

Fields

ApplicationCommandChatInput 

Fields

data OptionSubcommandOrGroup Source #

Either a subcommand group or a subcommand.

Constructors

OptionSubcommandGroup 

Fields

OptionSubcommandOrGroupSubcommand OptionSubcommand 

data OptionSubcommand Source #

Data for a single subcommand.

Constructors

OptionSubcommand 

Fields

data OptionValue Source #

Data for a single value.

Constructors

OptionValueString 

Fields

OptionValueInteger 

Fields

OptionValueBoolean 

Fields

OptionValueUser 

Fields

OptionValueChannel 

Fields

OptionValueRole 

Fields

OptionValueMentionable 

Fields

OptionValueNumber 

Fields

createChatInput :: 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.

createUser :: 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.

createMessage :: 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 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

CreateApplicationCommandChatInput 

Fields

CreateApplicationCommandUser 

Fields

CreateApplicationCommandMessage 

Fields

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 #

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

Defined in Discord.Internal.Types.ApplicationCommands

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

Defined in Discord.Internal.Types.ApplicationCommands

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

Defined in Discord.Internal.Types.ApplicationCommands

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 #

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 #

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

Defined in Discord.Internal.Types.ApplicationCommands

Methods

compare :: Choice a -> Choice a -> Ordering #

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

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

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

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

max :: Choice a -> Choice a -> Choice a #

min :: Choice a -> Choice a -> Choice a #

data ChannelTypeOption Source #

The different channel types. Used for application commands and components.

https://discord.com/developers/docs/resources/channel#channel-object-channel-types

Constructors

ChannelTypeOptionGuildText

A text channel in a server.

ChannelTypeOptionDM

A direct message between users.

ChannelTypeOptionGuildVoice

A voice channel in a server.

ChannelTypeOptionGroupDM

A direct message between multiple users.

ChannelTypeOptionGuildCategory

An organizational category that contains up to 50 channels.

ChannelTypeOptionGuildNews

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

ChannelTypeOptionGuildStore

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

ChannelTypeOptionGuildNewsThread

A temporary sub-channel within a guild_news channel.

ChannelTypeOptionGuildPublicThread

A temporary sub-channel within a guild_text channel.

ChannelTypeOptionGuildPrivateThread

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

ChannelTypeOptionGuildStageVoice

A voice channel for hosting events with an audience.

Instances

Instances details
FromJSON ChannelTypeOption Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON ChannelTypeOption Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Data ChannelTypeOption Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

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

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

toConstr :: ChannelTypeOption -> Constr #

dataTypeOf :: ChannelTypeOption -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ChannelTypeOption Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Show ChannelTypeOption Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

InternalDiscordEnum ChannelTypeOption Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Eq ChannelTypeOption Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Ord ChannelTypeOption Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

data GuildApplicationCommandPermissions Source #

Instances

Instances details
FromJSON GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON 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

Eq GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Ord GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

data ApplicationCommandPermissions Source #

Application command permissions allow you to enable or disable commands for specific users or roles within a guild.

Constructors

ApplicationCommandPermissions 

Fields

Instances

Instances details
FromJSON ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON 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

Eq ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Ord ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

type LocalizedText = Map Locale Text Source #

Translations for a text

type Locale = Text Source #

A discord locale. See https://discord.com/developers/docs/reference#locales for available locales