| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Discord.Types
Synopsis
- data UTCTime = UTCTime {- utctDay :: Day
- utctDayTime :: DiffTime
 
- type Object = KeyMap Value
- class Internals a b where- toInternal :: a -> b
- fromInternal :: b -> Maybe a
 
- data InteractionType
- type ColorInteger = Integer
- 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
- data Auth = Auth Text
- authToken :: Auth -> Text
- snowflakeCreationDate :: Snowflake -> UTCTime
- epochTime :: UTCTime
- makeTable :: (Data t, Enum t) => t -> [(Int, t)]
- toMaybeJSON :: ToJSON a => a -> Maybe Value
- 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 ColorInteger
- embedTimestamp :: Maybe UTCTime
- embedType :: Maybe Text
- 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 ColorInteger
 
- createEmbed :: CreateEmbed -> Embed
- 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 SelectOption = SelectOption {}
- data Emoji = Emoji {}
- data InternalButtonStyle
- data ComponentType
- data Component = Component {- componentType :: ComponentType
- componentCustomId :: Maybe Text
- componentDisabled :: Maybe Bool
- componentStyle :: Maybe InternalButtonStyle
- componentLabel :: Maybe Text
- componentEmoji :: Maybe Emoji
- componentUrl :: Maybe Text
- componentOptions :: Maybe [SelectOption]
- componentPlaceholder :: Maybe Text
- componentMinValues :: Maybe Integer
- componentMaxValues :: Maybe Integer
- componentComponents :: Maybe [Component]
 
- data ComponentActionRow
- data ComponentSelectMenu = ComponentSelectMenu {}
- data ButtonStyle
- data ComponentButton- = ComponentButton { }
- | ComponentButtonUrl { }
 
- buttonStyles :: [(ButtonStyle, InternalButtonStyle)]
- validPartialEmoji :: Emoji -> Maybe Emoji
- filterOutIncorrectEmoji :: Component -> Component
- 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 [Component]
- messageStickerItems :: Maybe [StickerItem]
 
- data Overwrite = Overwrite {}
- data Channel- = ChannelText { }
- | ChannelNews { }
- | ChannelStorePage { }
- | ChannelVoice { }
- | ChannelDirectMessage { }
- | ChannelGroupDM { }
- | ChannelGuildCategory { }
- | ChannelStage { }
- | 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 GuildInfo = GuildInfo {}
- data GuildUnavailable = GuildUnavailable {}
- data Guild = Guild {- guildId :: GuildId
- guildName :: Text
- guildIcon :: Maybe Text
- guildSplash :: Maybe Text
- guildOwnerId :: UserId
- guildPermissions :: Maybe Text
- guildRegion :: 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 Snowflake
 
- data TypingInfo = TypingInfo {}
- data PresenceInfo = PresenceInfo {}
- 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
- | ChannelPinsUpdate ChannelId (Maybe UTCTime)
- | GuildCreate Guild GuildInfo
- | 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 ActivityType
- data Activity = Activity {}
- 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
 
- compileGatewayIntent :: GatewayIntent -> Int
- activityTypeId :: ActivityType -> 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 # | |
class Internals a b where Source #
Instances
data InteractionType Source #
What type of interaction has a user requested? Each requires its own type of response.
Constructors
| InteractionTypePing | |
| InteractionTypeApplicationCommand | |
| InteractionTypeMessageComponent | |
| InteractionTypeApplicationCommandAutocomplete | 
Instances
type ColorInteger = Integer Source #
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 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 #
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 
 | |
data SelectOption Source #
Constructors
| SelectOption | |
| Fields 
 | |
Instances
Represents an emoticon (emoji)
Constructors
| Emoji | |
data InternalButtonStyle Source #
Constructors
| InternalButtonStylePrimary | Blurple button | 
| InternalButtonStyleSecondary | Grey button | 
| InternalButtonStyleSuccess | Green button | 
| InternalButtonStyleDanger | Red button | 
| InternalButtonStyleLink | Grey button, navigates to URL | 
Instances
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
Constructors
| Component | |
| Fields 
 | |
Instances
| Eq Component Source # | |
| Ord Component Source # | |
| Defined in Discord.Internal.Types.Components | |
| Read Component Source # | |
| Show Component Source # | |
| ToJSON Component Source # | |
| Defined in Discord.Internal.Types.Components | |
| FromJSON Component Source # | |
| Internals ComponentActionRow Component Source # | |
| Defined in Discord.Internal.Types.Components Methods toInternal :: ComponentActionRow -> Component Source # fromInternal :: Component -> Maybe ComponentActionRow Source # | |
data ComponentActionRow Source #
Constructors
| ComponentActionRowButton [ComponentButton] | |
| ComponentActionRowSelectMenu ComponentSelectMenu | 
Instances
| Eq ComponentActionRow Source # | |
| Defined in Discord.Internal.Types.Components Methods (==) :: ComponentActionRow -> ComponentActionRow -> Bool # (/=) :: ComponentActionRow -> ComponentActionRow -> Bool # | |
| Show ComponentActionRow Source # | |
| Defined in Discord.Internal.Types.Components Methods showsPrec :: Int -> ComponentActionRow -> ShowS # show :: ComponentActionRow -> String # showList :: [ComponentActionRow] -> ShowS # | |
| Internals ComponentActionRow Component Source # | |
| Defined in Discord.Internal.Types.Components Methods toInternal :: ComponentActionRow -> Component Source # fromInternal :: Component -> Maybe ComponentActionRow Source # | |
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 | |
Instances
| Eq ComponentSelectMenu Source # | |
| Defined in Discord.Internal.Types.Components Methods (==) :: ComponentSelectMenu -> ComponentSelectMenu -> Bool # (/=) :: ComponentSelectMenu -> ComponentSelectMenu -> Bool # | |
| Read ComponentSelectMenu Source # | |
| Defined in Discord.Internal.Types.Components Methods readsPrec :: Int -> ReadS ComponentSelectMenu # readList :: ReadS [ComponentSelectMenu] # | |
| Show ComponentSelectMenu Source # | |
| Defined in Discord.Internal.Types.Components Methods showsPrec :: Int -> ComponentSelectMenu -> ShowS # show :: ComponentSelectMenu -> String # showList :: [ComponentSelectMenu] -> ShowS # | |
data ButtonStyle Source #
Instances
| Eq ButtonStyle Source # | |
| Defined in Discord.Internal.Types.Components | |
| Read ButtonStyle Source # | |
| Defined in Discord.Internal.Types.Components Methods readsPrec :: Int -> ReadS ButtonStyle # readList :: ReadS [ButtonStyle] # readPrec :: ReadPrec ButtonStyle # readListPrec :: ReadPrec [ButtonStyle] # | |
| Show ButtonStyle Source # | |
| Defined in Discord.Internal.Types.Components Methods showsPrec :: Int -> ButtonStyle -> ShowS # show :: ButtonStyle -> String # showList :: [ButtonStyle] -> ShowS # | |
| Internals ButtonStyle InternalButtonStyle Source # | |
| Defined in Discord.Internal.Types.Components Methods toInternal :: ButtonStyle -> InternalButtonStyle Source # fromInternal :: InternalButtonStyle -> Maybe ButtonStyle Source # | |
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 | |
| ComponentButtonUrl | |
| Fields | |
Instances
| Eq ComponentButton Source # | |
| Defined in Discord.Internal.Types.Components Methods (==) :: ComponentButton -> ComponentButton -> Bool # (/=) :: ComponentButton -> ComponentButton -> Bool # | |
| Show ComponentButton Source # | |
| Defined in Discord.Internal.Types.Components Methods showsPrec :: Int -> ComponentButton -> ShowS # show :: ComponentButton -> String # showList :: [ComponentButton] -> ShowS # | |
data MessageInteraction Source #
Constructors
| MessageInteraction | |
Instances
newtype MessageFlags Source #
Constructors
| MessageFlags [MessageFlag] | 
Instances
data MessageFlag Source #
Types of flags to attach to the message.
Constructors
| MessageFlagCrossposted | |
| MessageFlagIsCrosspost | |
| MessageFlagSupressEmbeds | |
| MessageFlagSourceMessageDeleted | |
| MessageFlagUrgent | |
| MessageFlagHasThread | |
| MessageFlagEphemeral | |
| MessageFlagLoading | 
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 
 | |
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 
 | |
| 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 | |
Constructors
| GuildInfo | |
| Fields 
 | |
Instances
| Eq GuildInfo Source # | |
| Ord GuildInfo Source # | |
| Read GuildInfo Source # | |
| Show GuildInfo Source # | |
| FromJSON GuildInfo 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 
 | |
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 PresenceInfo Source #
Constructors
| PresenceInfo | |
| Fields 
 | |
Instances
| Eq PresenceInfo Source # | |
| Defined in Discord.Internal.Types.Events | |
| Ord PresenceInfo Source # | |
| Defined in Discord.Internal.Types.Events 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.Events Methods readsPrec :: Int -> ReadS PresenceInfo # readList :: ReadS [PresenceInfo] # | |
| Show PresenceInfo Source # | |
| Defined in Discord.Internal.Types.Events Methods showsPrec :: Int -> PresenceInfo -> ShowS # show :: PresenceInfo -> String # showList :: [PresenceInfo] -> ShowS # | |
| FromJSON PresenceInfo 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
eventParse :: Text -> Object -> Parser EventInternalParse Source #
data UpdateStatusType Source #
Constructors
| UpdateStatusOnline | |
| UpdateStatusDoNotDisturb | |
| UpdateStatusAwayFromKeyboard | |
| UpdateStatusInvisibleOffline | |
| UpdateStatusOffline | 
Instances
data ActivityType Source #
Instances
| Eq ActivityType Source # | |
| Defined in Discord.Internal.Types.Gateway | |
| Ord ActivityType Source # | |
| Defined in Discord.Internal.Types.Gateway Methods compare :: ActivityType -> ActivityType -> Ordering # (<) :: ActivityType -> ActivityType -> Bool # (<=) :: ActivityType -> ActivityType -> Bool # (>) :: ActivityType -> ActivityType -> Bool # (>=) :: ActivityType -> ActivityType -> Bool # max :: ActivityType -> ActivityType -> ActivityType # min :: ActivityType -> ActivityType -> ActivityType # | |
| Read ActivityType Source # | |
| Defined in Discord.Internal.Types.Gateway Methods readsPrec :: Int -> ReadS ActivityType # readList :: ReadS [ActivityType] # | |
| Show ActivityType Source # | |
| Defined in Discord.Internal.Types.Gateway Methods showsPrec :: Int -> ActivityType -> ShowS # show :: ActivityType -> String # showList :: [ActivityType] -> ShowS # | |
Constructors
| Activity | |
| Fields 
 | |
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
activityTypeId :: ActivityType -> Int Source #
statusString :: UpdateStatusType -> Text Source #