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

Discord.Types

Synopsis

Documentation

data UTCTime #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Constructors

UTCTime 

Fields

Instances

Instances details
Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Data UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

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

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

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

ToHttpApiData UTCTime
>>> toUrlPiece $ UTCTime (fromGregorian 2015 10 03) 864.5
"2015-10-03T00:14:24.5Z"
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData UTCTime
>>> parseUrlPiece "2015-10-03T00:14:24Z" :: Either Text UTCTime
Right 2015-10-03 00:14:24 UTC
Instance details

Defined in Web.Internal.HttpApiData

type Object = KeyMap Value #

A JSON "object" (key/value map).

class Internals a b where Source #

Methods

toInternal :: a -> b Source #

fromInternal :: b -> Maybe a Source #

Instances

Instances details
Internals a a Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

toInternal :: a -> a Source #

fromInternal :: a -> Maybe a Source #

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

Internals ApplicationCommand InternalApplicationCommand Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Internals ComponentActionRow Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Internals ButtonStyle InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Internals InteractionDataApplicationCommandOptionValue InternalInteractionDataApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataApplicationCommandOptionSubcommand InternalInteractionDataApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataApplicationCommandOptionSubcommandOrGroup InternalInteractionDataApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataApplicationCommand InternalInteractionData Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataComponent InternalInteractionData Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals Interaction InternalInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataApplicationCommandOptions [InternalInteractionDataApplicationCommandOption] Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

data InteractionType Source #

What type of interaction has a user requested? Each requires its own type of response.

Instances

Instances details
Enum InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Eq InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Data InteractionType 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) -> InteractionType -> c InteractionType #

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

toConstr :: InteractionType -> Constr #

dataTypeOf :: InteractionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Read InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Show InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

FromJSON InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

type Shard = (Int, Int) Source #

newtype Snowflake Source #

A unique integer identifier. Can be used to calculate the creation date of an entity.

Constructors

Snowflake Word64 

Instances

Instances details
Enum Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Eq Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Integral Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Num Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Ord Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Read Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Real Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Show Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

FromJSON Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Bits Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

data Auth Source #

Authorization token for the Discord API

Constructors

Auth Text 

Instances

Instances details
Eq Auth Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

(==) :: Auth -> Auth -> Bool #

(/=) :: Auth -> Auth -> Bool #

Ord Auth Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

compare :: Auth -> Auth -> Ordering #

(<) :: Auth -> Auth -> Bool #

(<=) :: Auth -> Auth -> Bool #

(>) :: Auth -> Auth -> Bool #

(>=) :: Auth -> Auth -> Bool #

max :: Auth -> Auth -> Auth #

min :: Auth -> Auth -> Auth #

Read Auth Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Show Auth Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

showsPrec :: Int -> Auth -> ShowS #

show :: Auth -> String #

showList :: [Auth] -> ShowS #

authToken :: Auth -> Text Source #

Get the raw token formatted for use with the websocket gateway

snowflakeCreationDate :: Snowflake -> UTCTime Source #

Gets a creation date from a snowflake.

epochTime :: UTCTime Source #

Default timestamp

makeTable :: (Data t, Enum t) => t -> [(Int, t)] Source #

data EmbedField Source #

data EmbedFooter Source #

data EmbedAuthor Source #

data EmbedProvider Source #

Instances

Instances details
Eq EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Ord EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Read EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Show EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

FromJSON EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

data EmbedImage Source #

data EmbedVideo Source #

data EmbedThumbnail Source #

Instances

Instances details
Eq EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Ord EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Read EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Show EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

FromJSON EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

data Embed Source #

An embed attached to a message.

Constructors

Embed 

Fields

Instances

Instances details
Eq Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Methods

(==) :: Embed -> Embed -> Bool #

(/=) :: Embed -> Embed -> Bool #

Ord Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Methods

compare :: Embed -> Embed -> Ordering #

(<) :: Embed -> Embed -> Bool #

(<=) :: Embed -> Embed -> Bool #

(>) :: Embed -> Embed -> Bool #

(>=) :: Embed -> Embed -> Bool #

max :: Embed -> Embed -> Embed #

min :: Embed -> Embed -> Embed #

Read Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Show Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Methods

showsPrec :: Int -> Embed -> ShowS #

show :: Embed -> String #

showList :: [Embed] -> ShowS #

ToJSON Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

FromJSON Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

data CreateEmbed Source #

data GuildMember Source #

Representation of a guild member.

Constructors

GuildMember 

Fields

data ConnectionObject Source #

data User Source #

Represents information about a user.

Constructors

User 

Fields

Instances

Instances details
Eq User Source # 
Instance details

Defined in Discord.Internal.Types.User

Methods

(==) :: User -> User -> Bool #

(/=) :: User -> User -> Bool #

Ord User Source # 
Instance details

Defined in Discord.Internal.Types.User

Methods

compare :: User -> User -> Ordering #

(<) :: User -> User -> Bool #

(<=) :: User -> User -> Bool #

(>) :: User -> User -> Bool #

(>=) :: User -> User -> Bool #

max :: User -> User -> User #

min :: User -> User -> User #

Read User Source # 
Instance details

Defined in Discord.Internal.Types.User

Show User Source # 
Instance details

Defined in Discord.Internal.Types.User

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

ToJSON User Source # 
Instance details

Defined in Discord.Internal.Types.User

FromJSON User Source # 
Instance details

Defined in Discord.Internal.Types.User

data SelectOption Source #

Constructors

SelectOption 

Fields

Instances

Instances details
Eq SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

Ord SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

Read SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

data Emoji Source #

Represents an emoticon (emoji)

Constructors

Emoji 

Fields

Instances

Instances details
Eq Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

Methods

(==) :: Emoji -> Emoji -> Bool #

(/=) :: Emoji -> Emoji -> Bool #

Ord Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

Methods

compare :: Emoji -> Emoji -> Ordering #

(<) :: Emoji -> Emoji -> Bool #

(<=) :: Emoji -> Emoji -> Bool #

(>) :: Emoji -> Emoji -> Bool #

(>=) :: Emoji -> Emoji -> Bool #

max :: Emoji -> Emoji -> Emoji #

min :: Emoji -> Emoji -> Emoji #

Read Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

Methods

showsPrec :: Int -> Emoji -> ShowS #

show :: Emoji -> String #

showList :: [Emoji] -> ShowS #

ToJSON Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

data InternalButtonStyle Source #

Constructors

InternalButtonStylePrimary

Blurple button

InternalButtonStyleSecondary

Grey button

InternalButtonStyleSuccess

Green button

InternalButtonStyleDanger

Red button

InternalButtonStyleLink

Grey button, navigates to URL

Instances

Instances details
Enum InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Eq InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Data InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Methods

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

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

toConstr :: InternalButtonStyle -> Constr #

dataTypeOf :: InternalButtonStyle -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Read InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Internals ButtonStyle InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

data ComponentType Source #

The different types of components

Constructors

ComponentTypeActionRow

A container for other components

ComponentTypeButton

A button

ComponentTypeSelectMenu

A select menu for picking from choices

Instances

Instances details
Enum ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Eq ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Data ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Methods

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

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

toConstr :: ComponentType -> Constr #

dataTypeOf :: ComponentType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Read ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

data Component Source #

Constructors

Component 

Fields

Instances

Instances details
Eq Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Ord Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Read Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Internals ComponentActionRow Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

data ComponentButton Source #

Component type for a button, split into URL button and not URL button.

Don't directly send button components - they need to be within an action row.

data MessageInteraction Source #

Instances

Instances details
Eq MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

FromJSON MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

newtype MessageFlags Source #

Constructors

MessageFlags [MessageFlag] 

Instances

Instances details
Eq MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

FromJSON MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data MessageFlag Source #

Types of flags to attach to the message.

Instances

Instances details
Enum MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Data MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

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

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

toConstr :: MessageFlag -> Constr #

dataTypeOf :: MessageFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data MessageActivityType Source #

Constructors

MessageActivityTypeJoin

Join a Rich Presence event

MessageActivityTypeSpectate

Spectate a Rich Presence event

MessageActivityTypeListen

Listen to a Rich Presence event

MessageActivityTypeJoinRequest

Request to join a Rich Presence event

Instances

Instances details
Enum MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Data MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

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

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

toConstr :: MessageActivityType -> Constr #

dataTypeOf :: MessageActivityType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

FromJSON MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data MessageActivity Source #

Instances

Instances details
Eq MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Data MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

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

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

toConstr :: MessageActivity -> Constr #

dataTypeOf :: MessageActivity -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

FromJSON MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data MessageType Source #

Instances

Instances details
Enum MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Data MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

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

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

toConstr :: MessageType -> Constr #

dataTypeOf :: MessageType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

FromJSON MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data MessageReference Source #

Represents a Message Reference

Constructors

MessageReference 

Fields

Instances

Instances details
Eq MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

FromJSON MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Default MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

newtype Nonce Source #

Constructors

Nonce Text 

Instances

Instances details
Eq Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

(==) :: Nonce -> Nonce -> Bool #

(/=) :: Nonce -> Nonce -> Bool #

Ord Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

compare :: Nonce -> Nonce -> Ordering #

(<) :: Nonce -> Nonce -> Bool #

(<=) :: Nonce -> Nonce -> Bool #

(>) :: Nonce -> Nonce -> Bool #

(>=) :: Nonce -> Nonce -> Bool #

max :: Nonce -> Nonce -> Nonce #

min :: Nonce -> Nonce -> Nonce #

Read Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

showsPrec :: Int -> Nonce -> ShowS #

show :: Nonce -> String #

showList :: [Nonce] -> ShowS #

ToJSON Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

FromJSON Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data Attachment Source #

Represents an attached to a message file.

Constructors

Attachment 

Fields

data StickerFormatType Source #

Instances

Instances details
Enum StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Data StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

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

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

toConstr :: StickerFormatType -> Constr #

dataTypeOf :: StickerFormatType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

FromJSON StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data StickerItem Source #

data MessageReaction Source #

Instances

Instances details
Eq MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

FromJSON MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data AllowedMentions Source #

Data constructor for a part of MessageDetailedOpts.

Instances

Instances details
Eq AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Default AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data Message Source #

Represents information about a message in a Discord channel.

Constructors

Message 

Fields

data Overwrite Source #

Permission overwrites for a channel.

Constructors

Overwrite 

Fields

data Channel Source #

Guild channels represent an isolated set of users and messages in a Guild (Server)

Constructors

ChannelText

A text channel in a guild.

Fields

ChannelNews 

Fields

ChannelStorePage 

Fields

ChannelVoice

A voice channel in a guild.

Fields

ChannelDirectMessage

DM Channels represent a one-to-one conversation between two users, outside the scope of guilds

Fields

ChannelGroupDM 

Fields

ChannelGuildCategory 

Fields

ChannelStage 

Fields

ChannelUnknownType 

Fields

channelIsInGuild :: Channel -> Bool Source #

If the channel is part of a guild (has a guild id field)

data GuildWidget Source #

Represents an image to be used in third party sites to link to a discord channel

Constructors

GuildWidget 

Fields

data IntegrationAccount Source #

Represents a third party account link.

Constructors

IntegrationAccount 

Fields

data Integration Source #

Represents the behavior of a third party account link.

Constructors

Integration 

Fields

data InviteMeta Source #

Additional metadata about an invite.

Constructors

InviteMeta 

Fields

data InviteWithMeta Source #

Invite code with additional metadata

Instances

Instances details
FromJSON InviteWithMeta Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data Invite Source #

Represents a code to add a user to a guild

Constructors

Invite 

Fields

Instances

Instances details
Eq Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

(==) :: Invite -> Invite -> Bool #

(/=) :: Invite -> Invite -> Bool #

Ord Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Read Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

FromJSON Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data VoiceRegion Source #

VoiceRegion is only refrenced in Guild endpoints, will be moved when voice support is added

Constructors

VoiceRegion 

Fields

data Role Source #

Roles represent a set of permissions attached to a group of users. Roles have unique names, colors, and can be "pinned" to the side bar, causing their members to be listed separately. Roles are unique per guild, and can have separate permission profiles for the global context (guild) and channel context.

Constructors

Role 

Fields

Instances

Instances details
Eq Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

Ord Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

(>=) :: Role -> Role -> Bool #

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

Read Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

FromJSON Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data GuildUnavailable Source #

Constructors

GuildUnavailable 

data Guild Source #

Guilds in Discord represent a collection of users and channels into an isolated Server

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

Constructors

Guild 

Fields

Instances

Instances details
Eq Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

(==) :: Guild -> Guild -> Bool #

(/=) :: Guild -> Guild -> Bool #

Ord Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

compare :: Guild -> Guild -> Ordering #

(<) :: Guild -> Guild -> Bool #

(<=) :: Guild -> Guild -> Bool #

(>) :: Guild -> Guild -> Bool #

(>=) :: Guild -> Guild -> Bool #

max :: Guild -> Guild -> Guild #

min :: Guild -> Guild -> Guild #

Read Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

showsPrec :: Int -> Guild -> ShowS #

show :: Guild -> String #

showList :: [Guild] -> ShowS #

FromJSON Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data ReactionRemoveInfo Source #

data Event Source #

Represents possible events sent by discord. Detailed information can be found at https://discord.com/developers/docs/topics/gateway.

Instances

Instances details
Eq Event Source # 
Instance details

Defined in Discord.Internal.Types.Events

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Read Event Source # 
Instance details

Defined in Discord.Internal.Types.Events

Show Event Source # 
Instance details

Defined in Discord.Internal.Types.Events

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

reparse :: (ToJSON a, FromJSON b) => a -> Parser b Source #

Convert ToJSON value to FromJSON value

data UpdateStatusType Source #

Instances

Instances details
Enum UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

Eq UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

Ord UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

Read UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

Show UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

data UpdateStatusVoiceOpts Source #

data RequestGuildMembersOpts Source #

data GatewaySendable Source #

Sent to gateway by a user

data GatewayIntent Source #