Safe Haskell | None |
---|---|
Language | Haskell2010 |
Discord.Types
Description
Re-export user-visible types
Synopsis
- data UTCTime = UTCTime {
- utctDay :: Day
- utctDayTime :: DiffTime
- class ToJSON a where
- type Object = KeyMap Value
- type Shard = (Int, Int)
- type InteractionToken = Text
- type InteractionId = Snowflake
- type ApplicationCommandId = Snowflake
- type ApplicationId = Snowflake
- type ParentId = Snowflake
- type WebhookId = Snowflake
- type IntegrationId = Snowflake
- type RoleId = Snowflake
- type OverwriteId = Snowflake
- type UserId = Snowflake
- type StickerId = Snowflake
- type EmojiId = Snowflake
- type AttachmentId = Snowflake
- type MessageId = Snowflake
- type GuildId = Snowflake
- type StageId = Snowflake
- type ChannelId = Snowflake
- newtype Snowflake = Snowflake Word64
- newtype Auth = Auth Text
- authToken :: Auth -> Text
- snowflakeCreationDate :: Snowflake -> UTCTime
- epochTime :: UTCTime
- toMaybeJSON :: ToJSON a => a -> Maybe Value
- data DiscordColor
- = DiscordColorRGB Integer Integer Integer
- | DiscordColorDefault
- | DiscordColorAqua
- | DiscordColorDarkAqua
- | DiscordColorGreen
- | DiscordColorDarkGreen
- | DiscordColorBlue
- | DiscordColorDarkBlue
- | DiscordColorPurple
- | DiscordColorDarkPurple
- | DiscordColorLuminousVividPink
- | DiscordColorDarkVividPink
- | DiscordColorGold
- | DiscordColorDarkGold
- | DiscordColorOrange
- | DiscordColorDarkOrange
- | DiscordColorRed
- | DiscordColorDarkRed
- | DiscordColorGray
- | DiscordColorDarkGray
- | DiscordColorDarkerGray
- | DiscordColorLightGray
- | DiscordColorNavy
- | DiscordColorDarkNavy
- | DiscordColorYellow
- | DiscordColorDiscordWhite
- | DiscordColorDiscordBlurple
- | DiscordColorDiscordGrayple
- | DiscordColorDiscordDarkButNotBlack
- | DiscordColorDiscordNotQuiteBlack
- | DiscordColorDiscordGreen
- | DiscordColorDiscordYellow
- | DiscordColorDiscordFuschia
- | DiscordColorDiscordRed
- | DiscordColorDiscordBlack
- hexToDiscordColor :: String -> DiscordColor
- data EmbedField = EmbedField {}
- data EmbedFooter = EmbedFooter {}
- data EmbedAuthor = EmbedAuthor {}
- data EmbedProvider = EmbedProvider {}
- data EmbedImage = EmbedImage {}
- data EmbedVideo = EmbedVideo {}
- data EmbedThumbnail = EmbedThumbnail {}
- data Embed = Embed {
- embedAuthor :: Maybe EmbedAuthor
- embedTitle :: Maybe Text
- embedUrl :: Maybe Text
- embedThumbnail :: Maybe EmbedThumbnail
- embedDescription :: Maybe Text
- embedFields :: [EmbedField]
- embedImage :: Maybe EmbedImage
- embedFooter :: Maybe EmbedFooter
- embedColor :: Maybe DiscordColor
- embedTimestamp :: Maybe UTCTime
- embedVideo :: Maybe EmbedVideo
- embedProvider :: Maybe EmbedProvider
- data CreateEmbedImage
- data CreateEmbed = CreateEmbed {
- createEmbedAuthorName :: Text
- createEmbedAuthorUrl :: Text
- createEmbedAuthorIcon :: Maybe CreateEmbedImage
- createEmbedTitle :: Text
- createEmbedUrl :: Text
- createEmbedThumbnail :: Maybe CreateEmbedImage
- createEmbedDescription :: Text
- createEmbedFields :: [EmbedField]
- createEmbedImage :: Maybe CreateEmbedImage
- createEmbedFooterText :: Text
- createEmbedFooterIcon :: Maybe CreateEmbedImage
- createEmbedColor :: Maybe DiscordColor
- createEmbedTimestamp :: Maybe UTCTime
- createEmbed :: CreateEmbed -> Embed
- maybeEmbed :: Maybe CreateEmbed -> [PartM IO]
- data GuildMember = GuildMember {}
- data ConnectionObject = ConnectionObject {
- connectionObjectId :: Text
- connectionObjectName :: Text
- connectionObjectType :: Text
- connectionObjectRevoked :: Bool
- connectionObjectIntegrations :: [IntegrationId]
- connectionObjectVerified :: Bool
- connectionObjectFriendSyncOn :: Bool
- connectionObjectShownInPresenceUpdates :: Bool
- connectionObjectVisibleToOthers :: Bool
- data Webhook = Webhook {}
- data User = User {
- userId :: UserId
- userName :: Text
- userDiscrim :: Maybe Text
- userAvatar :: Maybe Text
- userIsBot :: Bool
- userIsWebhook :: Bool
- userIsSystem :: Maybe Bool
- userMfa :: Maybe Bool
- userBanner :: Maybe Text
- userAccentColor :: Maybe Int
- userLocale :: Maybe Text
- userVerified :: Maybe Bool
- userEmail :: Maybe Text
- userFlags :: Maybe Integer
- userPremiumType :: Maybe Integer
- userPublicFlags :: Maybe Integer
- userMember :: Maybe GuildMember
- data Emoji = Emoji {}
- data ComponentTextInput = ComponentTextInput {}
- data SelectOption = SelectOption {}
- data ComponentSelectMenu = ComponentSelectMenu {}
- data ButtonStyle
- data ComponentButton
- = ComponentButton { }
- | ComponentButtonUrl { }
- data ComponentActionRow
- mkButton :: Text -> Text -> ComponentButton
- mkSelectMenu :: Text -> [SelectOption] -> ComponentSelectMenu
- mkSelectOption :: Text -> Text -> SelectOption
- mkComponentTextInput :: Text -> Text -> ComponentTextInput
- mkEmoji :: Text -> Emoji
- data MessageInteraction = MessageInteraction {}
- newtype MessageFlags = MessageFlags [MessageFlag]
- data MessageFlag
- data MessageActivityType
- data MessageActivity = MessageActivity {}
- data MessageType
- = MessageTypeDefault
- | MessageTypeRecipientAdd
- | MessageTypeRecipientRemove
- | MessageTypeCall
- | MessageTypeChannelNameChange
- | MessageTypeChannelIconChange
- | MessageTypeChannelPinnedMessage
- | MessageTypeGuildMemberJoin
- | MessageTypeUserPremiumGuildSubscription
- | MessageTypeUserPremiumGuildSubscriptionTier1
- | MessageTypeUserPremiumGuildSubscriptionTier2
- | MessageTypeUserPremiumGuildSubscriptionTier3
- | MessageTypeChannelFollowAdd
- | MessageTypeGuildDiscoveryDisqualified
- | MessageTypeGuildDiscoveryRequalified
- | MessageTypeGuildDiscoveryGracePeriodInitialWarning
- | MessageTypeGuildDiscoveryGracePeriodFinalWarning
- | MessageTypeThreadCreated
- | MessageTypeReply
- | MessageTypeChatInputCommand
- | MessageTypeThreadStarterMessage
- | MessageTypeGuildInviteReminder
- | MessageTypeContextMenuCommand
- data MessageReference = MessageReference {}
- newtype Nonce = Nonce Text
- data Attachment = Attachment {}
- data StickerFormatType
- data StickerItem = StickerItem {}
- data MessageReaction = MessageReaction {}
- data AllowedMentions = AllowedMentions {}
- data Message = Message {
- messageId :: MessageId
- messageChannelId :: ChannelId
- messageGuildId :: Maybe GuildId
- messageAuthor :: User
- messageMember :: Maybe GuildMember
- messageContent :: Text
- messageTimestamp :: UTCTime
- messageEdited :: Maybe UTCTime
- messageTts :: Bool
- messageEveryone :: Bool
- messageMentions :: [User]
- messageMentionRoles :: [RoleId]
- messageAttachments :: [Attachment]
- messageEmbeds :: [Embed]
- messageReactions :: [MessageReaction]
- messageNonce :: Maybe Nonce
- messagePinned :: Bool
- messageWebhookId :: Maybe WebhookId
- messageType :: MessageType
- messageActivity :: Maybe MessageActivity
- messageApplicationId :: Maybe ApplicationId
- messageReference :: Maybe MessageReference
- messageFlags :: Maybe MessageFlags
- messageReferencedMessage :: Maybe Message
- messageInteraction :: Maybe MessageInteraction
- messageThread :: Maybe Channel
- messageComponents :: Maybe [ComponentActionRow]
- messageStickerItems :: Maybe [StickerItem]
- data ThreadMembersUpdateFields = ThreadMembersUpdateFields {}
- data ThreadListSyncFields = ThreadListSyncFields {}
- data ThreadMember = ThreadMember {}
- data ThreadMetadata = ThreadMetadata {}
- data Overwrite = Overwrite {}
- data Channel
- = ChannelText { }
- | ChannelNews { }
- | ChannelStorePage { }
- | ChannelVoice { }
- | ChannelDirectMessage { }
- | ChannelGroupDM { }
- | ChannelGuildCategory { }
- | ChannelStage { }
- | ChannelNewsThread { }
- | ChannelPublicThread { }
- | ChannelPrivateThread { }
- | ChannelUnknownType { }
- channelIsInGuild :: Channel -> Bool
- data GuildWidget = GuildWidget {}
- data IntegrationAccount = IntegrationAccount {
- accountId :: Text
- accountName :: Text
- data Integration = Integration {}
- data InviteMeta = InviteMeta {}
- data InviteWithMeta = InviteWithMeta Invite InviteMeta
- data Invite = Invite {}
- data GuildBan = GuildBan {}
- data VoiceRegion = VoiceRegion {}
- data Role = Role {}
- data PartialGuild = PartialGuild {}
- data ActivityType
- data ActivityButton = ActivityButton {}
- data ActivityParty = ActivityParty {}
- data ActivityTimestamps = ActivityTimestamps {}
- data Activity = Activity {
- activityName :: Text
- activityType :: ActivityType
- activityUrl :: Maybe Text
- activityCreatedAt :: Integer
- activityTimeStamps :: Maybe ActivityTimestamps
- activityApplicationId :: Maybe ApplicationId
- activityDetails :: Maybe Text
- activityState :: Maybe Text
- activityEmoji :: Maybe Emoji
- activityParty :: Maybe ActivityParty
- activityInstance :: Maybe Bool
- activityFlags :: Maybe Integer
- activityButtons :: Maybe [ActivityButton]
- data PresenceInfo = PresenceInfo {}
- newtype GuildUnavailable = GuildUnavailable {}
- data Guild = Guild {
- guildId :: GuildId
- guildName :: Text
- guildIcon :: Maybe Text
- guildIconHash :: Maybe Text
- guildSplash :: Maybe Text
- guildDiscoverySplash :: Maybe Text
- guildOwner :: Maybe Bool
- guildOwnerId :: UserId
- guildPermissions :: Maybe Text
- guildAfkId :: Maybe ChannelId
- guildAfkTimeout :: Integer
- guildWidgetEnabled :: Maybe Bool
- guildWidgetChannelId :: Maybe ChannelId
- guildVerificationLevel :: Integer
- guildNotification :: Integer
- guildExplicitFilterLevel :: Integer
- guildRoles :: [Role]
- guildEmojis :: [Emoji]
- guildFeatures :: [Text]
- guildMultiFactAuth :: !Integer
- guildApplicationId :: Maybe ApplicationId
- guildSystemChannelId :: Maybe ChannelId
- guildSystemChannelFlags :: Integer
- guildRulesChannelId :: Maybe ChannelId
- guildJoinedAt :: Maybe UTCTime
- guildLarge :: Maybe Bool
- guildUnavailable :: Maybe Bool
- guildMemberCount :: Maybe Integer
- guildMembers :: Maybe [GuildMember]
- guildChannels :: Maybe [Channel]
- guildThreads :: Maybe [Channel]
- guildPresences :: Maybe [PresenceInfo]
- guildMaxPresences :: Maybe Integer
- guildMaxMembers :: Maybe Integer
- guildVanityURL :: Maybe Text
- guildDescription :: Maybe Text
- guildBanner :: Maybe Text
- guildPremiumTier :: Integer
- guildSubscriptionCount :: Maybe Integer
- guildPreferredLocale :: Text
- guildPublicUpdatesChannel :: Maybe ChannelId
- guildMaxVideoUsers :: Maybe Integer
- guildApproxMemberCount :: Maybe Integer
- guildApproxPresenceCount :: Maybe Integer
- guildNSFWLevel :: Integer
- guildStickers :: Maybe [StickerItem]
- guildPremiumBar :: Bool
- data TypingInfo = TypingInfo {}
- data ReactionRemoveInfo = ReactionRemoveInfo {}
- data ReactionInfo = ReactionInfo {}
- data PartialApplication = PartialApplication {}
- data Event
- = Ready Int User [Channel] [GuildUnavailable] Text (Maybe Shard) PartialApplication
- | Resumed [Text]
- | ChannelCreate Channel
- | ChannelUpdate Channel
- | ChannelDelete Channel
- | ThreadCreate Channel
- | ThreadUpdate Channel
- | ThreadDelete Channel
- | ThreadListSync ThreadListSyncFields
- | ThreadMembersUpdate ThreadMembersUpdateFields
- | ChannelPinsUpdate ChannelId (Maybe UTCTime)
- | GuildCreate Guild
- | GuildUpdate Guild
- | GuildDelete GuildUnavailable
- | GuildBanAdd GuildId User
- | GuildBanRemove GuildId User
- | GuildEmojiUpdate GuildId [Emoji]
- | GuildIntegrationsUpdate GuildId
- | GuildMemberAdd GuildId GuildMember
- | GuildMemberRemove GuildId User
- | GuildMemberUpdate GuildId [RoleId] User (Maybe Text)
- | GuildMemberChunk GuildId [GuildMember]
- | GuildRoleCreate GuildId Role
- | GuildRoleUpdate GuildId Role
- | GuildRoleDelete GuildId RoleId
- | MessageCreate Message
- | MessageUpdate ChannelId MessageId
- | MessageDelete ChannelId MessageId
- | MessageDeleteBulk ChannelId [MessageId]
- | MessageReactionAdd ReactionInfo
- | MessageReactionRemove ReactionInfo
- | MessageReactionRemoveAll ChannelId MessageId
- | MessageReactionRemoveEmoji ReactionRemoveInfo
- | PresenceUpdate PresenceInfo
- | TypingStart TypingInfo
- | UserUpdate User
- | InteractionCreate Interaction
- | UnknownEvent Text Object
- reparse :: (ToJSON a, FromJSON b) => a -> Parser b
- eventParse :: Text -> Object -> Parser EventInternalParse
- data UpdateStatusType
- data UpdateStatusOpts = UpdateStatusOpts {}
- data UpdateStatusVoiceOpts = UpdateStatusVoiceOpts {}
- data RequestGuildMembersOpts = RequestGuildMembersOpts {}
- data GatewaySendable
- data GatewayIntent = GatewayIntent {
- gatewayIntentGuilds :: Bool
- gatewayIntentMembers :: Bool
- gatewayIntentBans :: Bool
- gatewayIntentEmojis :: Bool
- gatewayIntentIntegrations :: Bool
- gatewayIntentWebhooks :: Bool
- gatewayIntentInvites :: Bool
- gatewayIntentVoiceStates :: Bool
- gatewayIntentPrecenses :: Bool
- gatewayIntentMessageChanges :: Bool
- gatewayIntentMessageReactions :: Bool
- gatewayIntentMessageTyping :: Bool
- gatewayIntentDirectMessageChanges :: Bool
- gatewayIntentDirectMessageReactions :: Bool
- gatewayIntentDirectMessageTyping :: Bool
- gatewayIntentMessageContent :: Bool
- compileGatewayIntent :: GatewayIntent -> Int
- statusString :: UpdateStatusType -> Text
- userFacingEvent :: EventInternalParse -> Event
Documentation
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
Eq UTCTime | |
Data UTCTime | |
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 | |
Defined in Data.Time.Clock.Internal.UTCTime | |
ToJSON UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON UTCTime | |
FromJSONKey UTCTime | |
Defined in Data.Aeson.Types.FromJSON Methods | |
NFData UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
ToHttpApiData UTCTime |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: UTCTime -> Text # toEncodedUrlPiece :: UTCTime -> Builder # toHeader :: UTCTime -> ByteString # toQueryParam :: UTCTime -> Text # | |
FromHttpApiData UTCTime |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text UTCTime # parseHeader :: ByteString -> Either Text UTCTime # |
A type that can be converted to JSON.
Instances in general must specify toJSON
and should (but don't need
to) specify toEncoding
.
An example type and instance:
-- Allow ourselves to writeText
literals. {-# LANGUAGE OverloadedStrings #-} data Coord = Coord { x :: Double, y :: Double } instanceToJSON
Coord wheretoJSON
(Coord x y) =object
["x".=
x, "y".=
y]toEncoding
(Coord x y) =pairs
("x".=
x<>
"y".=
y)
Instead of manually writing your ToJSON
instance, there are two options
to do it automatically:
- Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so it will probably be more efficient than the following option.
- The compiler can provide a default generic implementation for
toJSON
.
To use the second, simply add a deriving
clause to your
datatype and declare a Generic
ToJSON
instance. If you require nothing other than
defaultOptions
, it is sufficient to write (and this is the only
alternative where the default toJSON
implementation is sufficient):
{-# LANGUAGE DeriveGeneric #-} import GHC.Generics data Coord = Coord { x :: Double, y :: Double } derivingGeneric
instanceToJSON
Coord wheretoEncoding
=genericToEncoding
defaultOptions
If on the other hand you wish to customize the generic decoding, you have to implement both methods:
customOptions =defaultOptions
{fieldLabelModifier
=map
toUpper
} instanceToJSON
Coord wheretoJSON
=genericToJSON
customOptionstoEncoding
=genericToEncoding
customOptions
Previous versions of this library only had the toJSON
method. Adding
toEncoding
had two reasons:
- toEncoding is more efficient for the common case that the output of
toJSON
is directly serialized to aByteString
. Further, expressing either method in terms of the other would be non-optimal. - The choice of defaults allows a smooth transition for existing users:
Existing instances that do not define
toEncoding
still compile and have the correct semantics. This is ensured by making the default implementation oftoEncoding
usetoJSON
. This produces correct results, but since it performs an intermediate conversion to aValue
, it will be less efficient than directly emitting anEncoding
. (this also means that specifying nothing more thaninstance ToJSON Coord
would be sufficient as a generically decoding instance, but there probably exists no good reason to not specifytoEncoding
in new instances.)
Minimal complete definition
Nothing
Instances
type InteractionToken = Text Source #
type InteractionId = Snowflake Source #
type ApplicationCommandId = Snowflake Source #
type ApplicationId = Snowflake Source #
type IntegrationId = Snowflake Source #
type OverwriteId = Snowflake Source #
type AttachmentId = Snowflake Source #
A unique integer identifier. Can be used to calculate the creation date of an entity.
Instances
Authorization token for the Discord API
snowflakeCreationDate :: Snowflake -> UTCTime Source #
Gets a creation date from a snowflake.
data DiscordColor Source #
Color names Color is a bit of a mess on discord embeds. I've here stolen the pallet list from https://gist.github.com/thomasbnt/b6f455e2c7d743b796917fa3c205f812
All discord embed color stuff is credited to https://github.com/WarwickTabletop/tablebot/pull/34
Constructors
Instances
hexToDiscordColor :: String -> DiscordColor Source #
hexToDiscordColor
converts a potential hex string into a DiscordColor,
evaluating to Default if it fails.
data EmbedField Source #
Constructors
EmbedField | |
Fields |
Instances
data EmbedAuthor Source #
Constructors
EmbedAuthor | |
Fields |
Instances
data EmbedProvider Source #
Constructors
EmbedProvider | |
Fields |
Instances
data EmbedImage Source #
Constructors
EmbedImage | |
Fields |
Instances
data EmbedVideo Source #
Constructors
EmbedVideo | |
Fields |
Instances
data EmbedThumbnail Source #
Constructors
EmbedThumbnail | |
Instances
An embed attached to a message.
Constructors
Embed | |
Fields
|
data CreateEmbedImage Source #
Constructors
CreateEmbedImageUrl Text | |
CreateEmbedImageUpload ByteString |
Instances
data CreateEmbed Source #
Constructors
Instances
Eq CreateEmbed Source # | |
Defined in Discord.Internal.Types.Embed | |
Ord CreateEmbed Source # | |
Defined in Discord.Internal.Types.Embed Methods compare :: CreateEmbed -> CreateEmbed -> Ordering # (<) :: CreateEmbed -> CreateEmbed -> Bool # (<=) :: CreateEmbed -> CreateEmbed -> Bool # (>) :: CreateEmbed -> CreateEmbed -> Bool # (>=) :: CreateEmbed -> CreateEmbed -> Bool # max :: CreateEmbed -> CreateEmbed -> CreateEmbed # min :: CreateEmbed -> CreateEmbed -> CreateEmbed # | |
Read CreateEmbed Source # | |
Defined in Discord.Internal.Types.Embed Methods readsPrec :: Int -> ReadS CreateEmbed # readList :: ReadS [CreateEmbed] # readPrec :: ReadPrec CreateEmbed # readListPrec :: ReadPrec [CreateEmbed] # | |
Show CreateEmbed Source # | |
Defined in Discord.Internal.Types.Embed Methods showsPrec :: Int -> CreateEmbed -> ShowS # show :: CreateEmbed -> String # showList :: [CreateEmbed] -> ShowS # | |
Default CreateEmbed Source # | |
Defined in Discord.Internal.Types.Embed Methods def :: CreateEmbed # |
createEmbed :: CreateEmbed -> Embed Source #
maybeEmbed :: Maybe CreateEmbed -> [PartM IO] Source #
data GuildMember Source #
Representation of a guild member.
Constructors
GuildMember | |
Fields
|
Instances
data ConnectionObject Source #
Constructors
Instances
Constructors
Webhook | |
Fields |
Represents information about a user.
Constructors
User | |
Fields
|
Represents an emoticon (emoji)
Constructors
Emoji | |
data ComponentTextInput Source #
Constructors
ComponentTextInput | |
Fields
|
Instances
data SelectOption Source #
A single option in a select menu.
Constructors
SelectOption | |
Fields
|
Instances
data ComponentSelectMenu Source #
Component type for a select menus.
Don't directly send select menus - they need to be within an action row.
Constructors
ComponentSelectMenu | |
Fields
|
Instances
data ButtonStyle Source #
Buttton colors.
Constructors
ButtonStylePrimary | Blurple button |
ButtonStyleSecondary | Grey button |
ButtonStyleSuccess | Green button |
ButtonStyleDanger | Red button |
Instances
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.
Constructors
ComponentButton | |
Fields
| |
ComponentButtonUrl | |
Fields
|
Instances
data ComponentActionRow Source #
Constructors
ComponentActionRowButton [ComponentButton] | |
ComponentActionRowSelectMenu ComponentSelectMenu |
Instances
mkButton :: Text -> Text -> ComponentButton Source #
Takes the label and the custom id of the button that is to be generated.
mkSelectMenu :: Text -> [SelectOption] -> ComponentSelectMenu Source #
Takes the custom id and the options of the select menu that is to be generated.
mkSelectOption :: Text -> Text -> SelectOption Source #
Make a select option from the given label and value.
mkComponentTextInput :: Text -> Text -> ComponentTextInput Source #
data MessageInteraction Source #
This is sent on the message object when the message is a response to an Interaction without an existing message (i.e., any non-component interaction).
Constructors
MessageInteraction | |
Fields
|
Instances
newtype MessageFlags Source #
Constructors
MessageFlags [MessageFlag] |
Instances
data MessageFlag Source #
Types of flags to attach to the message.
Constructors
Instances
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
data MessageActivity Source #
Constructors
MessageActivity | |
Instances
data MessageType Source #
Constructors
Instances
data MessageReference Source #
Represents a Message Reference
Constructors
MessageReference | |
Fields
|
Instances
data Attachment Source #
Represents an attached to a message file.
Constructors
Attachment | |
Fields
|
Instances
data StickerFormatType Source #
Instances
data StickerItem Source #
Constructors
StickerItem | |
Fields |
Instances
data MessageReaction Source #
Constructors
MessageReaction | |
Fields |
Instances
data AllowedMentions Source #
Data constructor for a part of MessageDetailedOpts.
Constructors
AllowedMentions | |
Fields
|
Instances
Represents information about a message in a Discord channel.
Constructors
Message | |
Fields
|
data ThreadMembersUpdateFields Source #
Constructors
ThreadMembersUpdateFields | |
Instances
data ThreadListSyncFields Source #
Constructors
ThreadListSyncFields | |
Instances
data ThreadMember Source #
Constructors
ThreadMember | |
Fields
|
Instances
data ThreadMetadata Source #
Metadata for threads.
Constructors
ThreadMetadata | |
Fields
|
Instances
Permission overwrites for a channel.
Constructors
Overwrite | |
Fields
|
Instances
Eq Overwrite Source # | |
Ord Overwrite Source # | |
Read Overwrite Source # | |
Show Overwrite Source # | |
ToJSON Overwrite Source # | |
Defined in Discord.Internal.Types.Channel | |
FromJSON Overwrite 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
| |
ChannelNewsThread | |
Fields
| |
ChannelPublicThread | |
Fields
| |
ChannelPrivateThread | |
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
|
Instances
data IntegrationAccount Source #
Represents a third party account link.
Constructors
IntegrationAccount | |
Fields
|
Instances
data Integration Source #
Represents the behavior of a third party account link.
Constructors
Integration | |
Fields
|
Instances
Eq Integration Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord Integration Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: Integration -> Integration -> Ordering # (<) :: Integration -> Integration -> Bool # (<=) :: Integration -> Integration -> Bool # (>) :: Integration -> Integration -> Bool # (>=) :: Integration -> Integration -> Bool # max :: Integration -> Integration -> Integration # min :: Integration -> Integration -> Integration # | |
Read Integration Source # | |
Defined in Discord.Internal.Types.Guild Methods readsPrec :: Int -> ReadS Integration # readList :: ReadS [Integration] # readPrec :: ReadPrec Integration # readListPrec :: ReadPrec [Integration] # | |
Show Integration Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> Integration -> ShowS # show :: Integration -> String # showList :: [Integration] -> ShowS # | |
FromJSON Integration Source # | |
Defined in Discord.Internal.Types.Guild |
data InviteMeta Source #
Additional metadata about an invite.
Constructors
InviteMeta | |
Fields
|
Instances
Eq InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: InviteMeta -> InviteMeta -> Ordering # (<) :: InviteMeta -> InviteMeta -> Bool # (<=) :: InviteMeta -> InviteMeta -> Bool # (>) :: InviteMeta -> InviteMeta -> Bool # (>=) :: InviteMeta -> InviteMeta -> Bool # max :: InviteMeta -> InviteMeta -> InviteMeta # min :: InviteMeta -> InviteMeta -> InviteMeta # | |
Read InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild Methods readsPrec :: Int -> ReadS InviteMeta # readList :: ReadS [InviteMeta] # readPrec :: ReadPrec InviteMeta # readListPrec :: ReadPrec [InviteMeta] # | |
Show InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> InviteMeta -> ShowS # show :: InviteMeta -> String # showList :: [InviteMeta] -> ShowS # | |
FromJSON InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild |
data InviteWithMeta Source #
Invite code with additional metadata
Constructors
InviteWithMeta Invite InviteMeta |
Instances
FromJSON InviteWithMeta Source # | |
Defined in Discord.Internal.Types.Guild Methods parseJSON :: Value -> Parser InviteWithMeta # parseJSONList :: Value -> Parser [InviteWithMeta] # |
Represents a code to add a user to a guild
Constructors
Invite | |
Fields
|
Info about a Ban
Constructors
GuildBan | |
Fields
|
data VoiceRegion Source #
VoiceRegion is only refrenced in Guild endpoints, will be moved when voice support is added
Constructors
VoiceRegion | |
Fields
|
Instances
Eq VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: VoiceRegion -> VoiceRegion -> Ordering # (<) :: VoiceRegion -> VoiceRegion -> Bool # (<=) :: VoiceRegion -> VoiceRegion -> Bool # (>) :: VoiceRegion -> VoiceRegion -> Bool # (>=) :: VoiceRegion -> VoiceRegion -> Bool # max :: VoiceRegion -> VoiceRegion -> VoiceRegion # min :: VoiceRegion -> VoiceRegion -> VoiceRegion # | |
Read VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild Methods readsPrec :: Int -> ReadS VoiceRegion # readList :: ReadS [VoiceRegion] # readPrec :: ReadPrec VoiceRegion # readListPrec :: ReadPrec [VoiceRegion] # | |
Show VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> VoiceRegion -> ShowS # show :: VoiceRegion -> String # showList :: [VoiceRegion] -> ShowS # | |
FromJSON VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild |
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
|
data PartialGuild Source #
Constructors
PartialGuild | |
Fields |
Instances
Eq PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: PartialGuild -> PartialGuild -> Ordering # (<) :: PartialGuild -> PartialGuild -> Bool # (<=) :: PartialGuild -> PartialGuild -> Bool # (>) :: PartialGuild -> PartialGuild -> Bool # (>=) :: PartialGuild -> PartialGuild -> Bool # max :: PartialGuild -> PartialGuild -> PartialGuild # min :: PartialGuild -> PartialGuild -> PartialGuild # | |
Read PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild Methods readsPrec :: Int -> ReadS PartialGuild # readList :: ReadS [PartialGuild] # | |
Show PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> PartialGuild -> ShowS # show :: PartialGuild -> String # showList :: [PartialGuild] -> ShowS # | |
FromJSON PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild |
data ActivityType Source #
To see what these look like, go to here: https://discord.com/developers/docs/topics/gateway#activity-object-activity-types
Constructors
ActivityTypeGame | |
ActivityTypeStreaming | |
ActivityTypeListening | |
ActivityTypeWatching | |
ActivityTypeCustom | |
ActivityTypeCompeting |
Instances
data ActivityButton Source #
Constructors
ActivityButton | |
Fields |
Instances
data ActivityParty Source #
Constructors
ActivityParty | |
Fields
|
Instances
data ActivityTimestamps Source #
Constructors
ActivityTimestamps | |
Fields
|
Instances
Object for a single activity
https://discord.com/developers/docs/topics/gateway#activity-object
When setting a bot's activity, only the name, url, and type are sent - and it seems that not many types are permitted either.
Constructors
Activity | |
Fields
|
data PresenceInfo Source #
Constructors
PresenceInfo | |
Fields |
Instances
Eq PresenceInfo Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord PresenceInfo Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: PresenceInfo -> PresenceInfo -> Ordering # (<) :: PresenceInfo -> PresenceInfo -> Bool # (<=) :: PresenceInfo -> PresenceInfo -> Bool # (>) :: PresenceInfo -> PresenceInfo -> Bool # (>=) :: PresenceInfo -> PresenceInfo -> Bool # max :: PresenceInfo -> PresenceInfo -> PresenceInfo # min :: PresenceInfo -> PresenceInfo -> PresenceInfo # | |
Read PresenceInfo Source # | |
Defined in Discord.Internal.Types.Guild Methods readsPrec :: Int -> ReadS PresenceInfo # readList :: ReadS [PresenceInfo] # | |
Show PresenceInfo Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> PresenceInfo -> ShowS # show :: PresenceInfo -> String # showList :: [PresenceInfo] -> ShowS # | |
FromJSON PresenceInfo Source # | |
Defined in Discord.Internal.Types.Guild |
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
|
data TypingInfo Source #
Constructors
TypingInfo | |
Fields |
Instances
Eq TypingInfo Source # | |
Defined in Discord.Internal.Types.Events | |
Ord TypingInfo Source # | |
Defined in Discord.Internal.Types.Events Methods compare :: TypingInfo -> TypingInfo -> Ordering # (<) :: TypingInfo -> TypingInfo -> Bool # (<=) :: TypingInfo -> TypingInfo -> Bool # (>) :: TypingInfo -> TypingInfo -> Bool # (>=) :: TypingInfo -> TypingInfo -> Bool # max :: TypingInfo -> TypingInfo -> TypingInfo # min :: TypingInfo -> TypingInfo -> TypingInfo # | |
Read TypingInfo Source # | |
Defined in Discord.Internal.Types.Events Methods readsPrec :: Int -> ReadS TypingInfo # readList :: ReadS [TypingInfo] # readPrec :: ReadPrec TypingInfo # readListPrec :: ReadPrec [TypingInfo] # | |
Show TypingInfo Source # | |
Defined in Discord.Internal.Types.Events Methods showsPrec :: Int -> TypingInfo -> ShowS # show :: TypingInfo -> String # showList :: [TypingInfo] -> ShowS # | |
FromJSON TypingInfo Source # | |
Defined in Discord.Internal.Types.Events |
data ReactionRemoveInfo Source #
Constructors
ReactionRemoveInfo | |
Instances
data ReactionInfo Source #
Constructors
ReactionInfo | |
Fields |
Instances
Eq ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events | |
Ord ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events Methods compare :: ReactionInfo -> ReactionInfo -> Ordering # (<) :: ReactionInfo -> ReactionInfo -> Bool # (<=) :: ReactionInfo -> ReactionInfo -> Bool # (>) :: ReactionInfo -> ReactionInfo -> Bool # (>=) :: ReactionInfo -> ReactionInfo -> Bool # max :: ReactionInfo -> ReactionInfo -> ReactionInfo # min :: ReactionInfo -> ReactionInfo -> ReactionInfo # | |
Read ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events Methods readsPrec :: Int -> ReadS ReactionInfo # readList :: ReadS [ReactionInfo] # | |
Show ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events Methods showsPrec :: Int -> ReactionInfo -> ShowS # show :: ReactionInfo -> String # showList :: [ReactionInfo] -> ShowS # | |
FromJSON ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events |
data PartialApplication Source #
Constructors
PartialApplication | |
Fields |
Instances
Eq PartialApplication Source # | |
Defined in Discord.Internal.Types.Events Methods (==) :: PartialApplication -> PartialApplication -> Bool # (/=) :: PartialApplication -> PartialApplication -> Bool # | |
Read PartialApplication Source # | |
Defined in Discord.Internal.Types.Events Methods readsPrec :: Int -> ReadS PartialApplication # readList :: ReadS [PartialApplication] # | |
Show PartialApplication Source # | |
Defined in Discord.Internal.Types.Events Methods showsPrec :: Int -> PartialApplication -> ShowS # show :: PartialApplication -> String # showList :: [PartialApplication] -> ShowS # | |
FromJSON PartialApplication Source # | |
Defined in Discord.Internal.Types.Events Methods parseJSON :: Value -> Parser PartialApplication # parseJSONList :: Value -> Parser [PartialApplication] # |
Represents possible events sent by discord. Detailed information can be found at https://discord.com/developers/docs/topics/gateway.
Constructors
Instances
eventParse :: Text -> Object -> Parser EventInternalParse Source #
data UpdateStatusType Source #
Constructors
UpdateStatusOnline | |
UpdateStatusDoNotDisturb | |
UpdateStatusAwayFromKeyboard | |
UpdateStatusInvisibleOffline | |
UpdateStatusOffline |
Instances
data UpdateStatusOpts Source #
Constructors
UpdateStatusOpts | |
Instances
data UpdateStatusVoiceOpts Source #
Constructors
UpdateStatusVoiceOpts | |
Instances
data RequestGuildMembersOpts Source #
Constructors
RequestGuildMembersOpts | |
Instances
data GatewaySendable Source #
Sent to gateway by a user
Constructors
RequestGuildMembers RequestGuildMembersOpts | |
UpdateStatus UpdateStatusOpts | |
UpdateStatusVoice UpdateStatusVoiceOpts |
Instances
data GatewayIntent Source #
Constructors
Instances
statusString :: UpdateStatusType -> Text Source #