Safe Haskell | Safe-Inferred |
---|---|
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
- data ChannelTypeOption
- = ChannelTypeOptionGuildText
- | ChannelTypeOptionDM
- | ChannelTypeOptionGuildVoice
- | ChannelTypeOptionGroupDM
- | ChannelTypeOptionGuildCategory
- | ChannelTypeOptionGuildNews
- | ChannelTypeOptionGuildStore
- | ChannelTypeOptionGuildNewsThread
- | ChannelTypeOptionGuildPublicThread
- | ChannelTypeOptionGuildPrivateThread
- | ChannelTypeOptionGuildStageVoice
- type AesonKey = Key
- type Shard = (Int, Int)
- type WebhookToken = DiscordToken WebhookIdType
- type InteractionToken = DiscordToken InteractionIdType
- newtype DiscordToken a = DiscordToken {}
- type ScheduledEventEntityId = DiscordId ScheduledEventEntityIdType
- type ScheduledEventId = DiscordId ScheduledEventIdType
- type InteractionId = DiscordId InteractionIdType
- type ApplicationCommandId = DiscordId ApplicationCommandIdType
- type ApplicationId = DiscordId ApplicationIdType
- type ParentId = DiscordId ParentIdType
- type WebhookId = DiscordId WebhookIdType
- type IntegrationId = DiscordId IntegrationIdType
- type RoleId = DiscordId RoleIdType
- type UserId = DiscordId UserIdType
- type StickerId = DiscordId StickerIdType
- type EmojiId = DiscordId EmojiIdType
- type AttachmentId = DiscordId AttachmentIdType
- type MessageId = DiscordId MessageIdType
- type GuildId = DiscordId GuildIdType
- type StageId = DiscordId StageIdType
- type ChannelId = DiscordId ChannelIdType
- newtype DiscordId a = DiscordId {}
- newtype RolePermissions = RolePermissions {}
- newtype Snowflake = Snowflake {}
- newtype Auth = Auth Text
- authToken :: Auth -> Text
- snowflakeCreationDate :: Snowflake -> UTCTime
- epochTime :: UTCTime
- (.==) :: ToJSON a => AesonKey -> a -> Maybe Pair
- (.=?) :: ToJSON a => AesonKey -> Maybe a -> Maybe Pair
- objectFromMaybes :: [Maybe Pair] -> Value
- getMimeType :: ByteString -> Maybe Text
- 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
- userGlobalName :: 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 StickerFormatType
- data StickerItem = StickerItem {}
- data Sticker = Sticker {
- stickerId :: StickerId
- stickerStickerPackId :: Maybe Snowflake
- stickerName :: Text
- stickerDescription :: Maybe Text
- stickerTags :: [Text]
- stickerIsStandardType :: Bool
- stickerFormatType :: StickerFormatType
- stickerAvailable :: Maybe Bool
- stickerGuildId :: Maybe GuildId
- stickerUser :: Maybe User
- stickerSortValue :: Maybe Integer
- data StickerPack = StickerPack {}
- data Emoji = Emoji {}
- mkEmoji :: Text -> Emoji
- 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 {
- roleId :: RoleId
- roleName :: Text
- roleColor :: DiscordColor
- roleHoist :: Bool
- rolePos :: Integer
- rolePerms :: RolePermissions
- roleManaged :: Bool
- roleMention :: Bool
- 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
- 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
- roleIdToRole :: Guild -> RoleId -> Maybe Role
- data PermissionFlag
- = CREATE_INSTANT_INVITE
- | KICK_MEMBERS
- | BAN_MEMBERS
- | ADMINISTRATOR
- | MANAGE_CHANNELS
- | MANAGE_GUILD
- | ADD_REACTIONS
- | VIEW_AUDIT_LOG
- | PRIORITY_SPEAKER
- | STREAM
- | VIEW_CHANNEL
- | SEND_MESSAGES
- | SEND_TTS_MESSAGES
- | MANAGE_MESSAGES
- | EMBED_LINKS
- | ATTACH_FILES
- | READ_MESSAGE_HISTORY
- | MENTION_EVERYONE
- | USE_EXTERNAL_EMOJIS
- | VIEW_GUILD_INSIGHT
- | CONNECT
- | SPEAK
- | MUTE_MEMBERS
- | DEAFEN_MEMBERS
- | MOVE_MEMBERS
- | USE_VAD
- | CHANGE_NICKNAME
- | MANAGE_NICKNAMES
- | MANAGE_ROLES
- | MANAGE_WEBHOOKS
- | MANAGE_EMOJIS_AND_STICKERS
- | USE_APPLICATION_COMMANDS
- | REQUEST_TO_SPEAK
- | MANAGE_EVENTS
- | MANAGE_THREADS
- | CREATE_PUBLIC_THREADS
- | CREATE_PRIVATE_THREADS
- | USE_EXTERNAL_STICKERS
- | SEND_MESSAGES_IN_THREADS
- | USE_EMBEDDED_ACTIVITIES
- | MODERATE_MEMBERS
- hasRolePermissions :: [PermissionFlag] -> RolePermissions -> Bool
- hasRolePermission :: PermissionFlag -> RolePermissions -> Bool
- newRolePermissions :: [PermissionFlag] -> RolePermissions
- newRolePermission :: PermissionFlag -> RolePermissions
- setRolePermissions :: [PermissionFlag] -> RolePermissions -> RolePermissions
- clearRolePermissions :: [PermissionFlag] -> RolePermissions -> RolePermissions
- setRolePermission :: PermissionFlag -> RolePermissions -> RolePermissions
- clearRolePermission :: PermissionFlag -> RolePermissions -> RolePermissions
- hasGuildMemberPermission :: Guild -> GuildMember -> PermissionFlag -> Bool
- data TextInput = TextInput {}
- data SelectOption = SelectOption {}
- data SelectMenuData
- data SelectMenu = SelectMenu {}
- data ButtonStyle
- data Button
- = Button { }
- | ButtonUrl {
- buttonUrl :: Text
- buttonDisabled :: Bool
- buttonLabel :: Maybe Text
- buttonEmoji :: Maybe Emoji
- data ActionRow
- mkButton :: Text -> Text -> Button
- mkSelectMenu :: Text -> [SelectOption] -> SelectMenu
- mkSelectOption :: Text -> Text -> SelectOption
- mkTextInput :: Text -> Text -> TextInput
- 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 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 [ActionRow]
- 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 TypingInfo = TypingInfo {}
- data ReactionRemoveInfo = ReactionRemoveInfo {}
- data ReactionInfo = ReactionInfo {}
- data GuildCreateData = GuildCreateData {
- guildCreateJoinedAt :: !UTCTime
- guildCreateLarge :: !Bool
- guildCreateUnavailable :: !(Maybe Bool)
- guildCreateMemberCount :: !Int
- guildCreateMembers :: ![GuildMember]
- guildCreateChannels :: ![Channel]
- guildCreateThreads :: ![Channel]
- guildCreatePresences :: ![PresenceInfo]
- guildCreateScheduledEvents :: ![ScheduledEvent]
- data PartialApplication = PartialApplication {}
- data Event
- = Ready Int User [GuildUnavailable] Text HostName (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 GuildCreateData
- | 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
- extractHostname :: String -> HostName
- 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
- gatewayIntentPresences :: 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
FromJSON UTCTime | |
FromJSONKey UTCTime | |
Defined in Data.Aeson.Types.FromJSON Methods | |
ToJSON UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
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 # | |
NFData UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
Eq UTCTime | |
Ord UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
FromFormKey UTCTime | |
Defined in Web.Internal.FormUrlEncoded | |
ToFormKey UTCTime | |
Defined in Web.Internal.FormUrlEncoded | |
FromHttpApiData UTCTime |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text UTCTime # parseHeader :: ByteString -> Either Text UTCTime # | |
ToHttpApiData UTCTime |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: UTCTime -> Text # toEncodedUrlPiece :: UTCTime -> Builder # toHeader :: UTCTime -> ByteString # toQueryParam :: UTCTime -> Text # toEncodedQueryParam :: UTCTime -> Builder # |
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
or more conveniently using the DerivingVia extension
deriving viaGenerically
Coord instanceToJSON
Coord
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 oftoJSON
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
data ChannelTypeOption Source #
The different channel types. Used for application commands and components.
https://discord.com/developers/docs/resources/channel#channel-object-channel-types
Constructors
ChannelTypeOptionGuildText | A text channel in a server. |
ChannelTypeOptionDM | A direct message between users. |
ChannelTypeOptionGuildVoice | A voice channel in a server. |
ChannelTypeOptionGroupDM | A direct message between multiple users. |
ChannelTypeOptionGuildCategory | An organizational category that contains up to 50 channels. |
ChannelTypeOptionGuildNews | A channel that users can follow and crosspost into their own server. |
ChannelTypeOptionGuildStore | A channel in which game developers can sell their game on discord. |
ChannelTypeOptionGuildNewsThread | A temporary sub-channel within a guild_news channel. |
ChannelTypeOptionGuildPublicThread | A temporary sub-channel within a guild_text channel. |
ChannelTypeOptionGuildPrivateThread | A temporary sub-channel within a GUILD_TEXT channel that is only viewable by those invited and those with the MANAGE_THREADS permission |
ChannelTypeOptionGuildStageVoice | A voice channel for hosting events with an audience. |
Instances
type WebhookToken = DiscordToken WebhookIdType Source #
type InteractionToken = DiscordToken InteractionIdType Source #
newtype DiscordToken a Source #
Constructors
DiscordToken | |
Instances
type ScheduledEventEntityId = DiscordId ScheduledEventEntityIdType Source #
type ScheduledEventId = DiscordId ScheduledEventIdType Source #
type InteractionId = DiscordId InteractionIdType Source #
type ApplicationCommandId = DiscordId ApplicationCommandIdType Source #
type ApplicationId = DiscordId ApplicationIdType Source #
type IntegrationId = DiscordId IntegrationIdType Source #
type AttachmentId = DiscordId AttachmentIdType Source #
Instances
newtype RolePermissions Source #
Constructors
RolePermissions | |
Fields |
Instances
A unique integer identifier. Can be used to calculate the creation date of an entity.
Constructors
Snowflake | |
Fields |
Instances
Authorization token for the Discord API
snowflakeCreationDate :: Snowflake -> UTCTime Source #
Gets a creation date from a snowflake.
getMimeType :: ByteString -> Maybe Text Source #
getMimeType bs
returns a possible mimetype for the given bytestring,
based on the first few magic bytes. It may return any of PNGJPEGGIF or WEBP
mimetypes, or Nothing if none are matched.
Reference: https://en.wikipedia.org/wiki/List_of_file_signatures
Although Discord's official documentation does not state WEBP as a supported format, it has been accepted for both emojis and user avatars no problem when tested manually.
Inspired by discord.py's implementation.
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
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 # | |
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 # |
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 #
The connection object that the user has attached.
Constructors
ConnectionObject | |
Fields
|
Instances
Constructors
Webhook | |
Fields |
Represents information about a user.
Constructors
User | |
Fields
|
data StickerFormatType Source #
The format of a sticker
Instances
data StickerItem Source #
A simplified sticker object.
Constructors
StickerItem | |
Fields
|
Instances
A full sticker object
Constructors
Sticker | |
Fields
|
data StickerPack Source #
Represents a pack of standard stickers.
Constructors
StickerPack | |
Fields
|
Instances
FromJSON StickerPack Source # | |
Defined in Discord.Internal.Types.Emoji | |
Read StickerPack Source # | |
Defined in Discord.Internal.Types.Emoji Methods readsPrec :: Int -> ReadS StickerPack # readList :: ReadS [StickerPack] # readPrec :: ReadPrec StickerPack # readListPrec :: ReadPrec [StickerPack] # | |
Show StickerPack Source # | |
Defined in Discord.Internal.Types.Emoji Methods showsPrec :: Int -> StickerPack -> ShowS # show :: StickerPack -> String # showList :: [StickerPack] -> ShowS # | |
Eq StickerPack Source # | |
Defined in Discord.Internal.Types.Emoji | |
Ord StickerPack Source # | |
Defined in Discord.Internal.Types.Emoji Methods compare :: StickerPack -> StickerPack -> Ordering # (<) :: StickerPack -> StickerPack -> Bool # (<=) :: StickerPack -> StickerPack -> Bool # (>) :: StickerPack -> StickerPack -> Bool # (>=) :: StickerPack -> StickerPack -> Bool # max :: StickerPack -> StickerPack -> StickerPack # min :: StickerPack -> StickerPack -> StickerPack # |
Represents an emoticon (emoji)
Constructors
Emoji | |
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
FromJSON Integration Source # | |
Defined in Discord.Internal.Types.Guild | |
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 # | |
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 # |
data InviteMeta Source #
Additional metadata about an invite.
Constructors
InviteMeta | |
Fields
|
Instances
FromJSON InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild | |
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 # | |
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 # |
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
FromJSON VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild | |
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 # | |
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 # |
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
FromJSON PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild | |
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 # | |
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 # |
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
FromJSON PresenceInfo Source # | |
Defined in Discord.Internal.Types.Guild | |
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 # | |
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 # |
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
|
roleIdToRole :: Guild -> RoleId -> Maybe Role Source #
If there is no such role on the guild return nothing otherwise return the role. Take the head of the list. List should always be one, because the ID is unique
data PermissionFlag Source #
Constructors
Instances
hasRolePermissions :: [PermissionFlag] -> RolePermissions -> Bool Source #
Check if a given role has all the permissions
hasRolePermission :: PermissionFlag -> RolePermissions -> Bool Source #
Check if a given role has the permission
newRolePermissions :: [PermissionFlag] -> RolePermissions Source #
Replace a users rolePerms with a complete new set of permissions
newRolePermission :: PermissionFlag -> RolePermissions Source #
Get the RolePermissions of a single PermissionFlag
setRolePermissions :: [PermissionFlag] -> RolePermissions -> RolePermissions Source #
Update RolePermissions with new permissions
clearRolePermissions :: [PermissionFlag] -> RolePermissions -> RolePermissions Source #
Unset Permissions from RolePermissions
setRolePermission :: PermissionFlag -> RolePermissions -> RolePermissions Source #
Set a certain permission flag This method doesn't lose the other already present permissions
clearRolePermission :: PermissionFlag -> RolePermissions -> RolePermissions Source #
Remove a permission from a user by clearing the bit
hasGuildMemberPermission :: Guild -> GuildMember -> PermissionFlag -> Bool Source #
Check if any Role of an GuildMember has the needed permission If the result of roleIdToRole is Nothing, it prepends a False Otherwise it checks for the needed permission
Constructors
TextInput | |
Fields
|
Instances
data SelectOption Source #
A single option in a select menu.
Constructors
SelectOption | |
Fields
|
Instances
data SelectMenuData Source #
Constructors
SelectMenuDataText [SelectOption] | Text options |
SelectMenuDataUser | Users |
SelectMenuDataRole | Roles |
SelectMenuDataMentionable | Anything mentionable (users and roles) |
SelectMenuDataChannels [ChannelTypeOption] | Channels (of certain types) |
Instances
data SelectMenu Source #
Component type for a select menu.
Don't directly send select menus - they need to be within an action row.
Constructors
SelectMenu | |
Fields
|
Instances
data ButtonStyle Source #
Buttton colors.
Constructors
ButtonStylePrimary | Blurple button |
ButtonStyleSecondary | Grey button |
ButtonStyleSuccess | Green button |
ButtonStyleDanger | Red button |
Instances
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
Button | |
Fields
| |
ButtonUrl | |
Fields
|
Container for other message Components
Constructors
ActionRowButtons [Button] | |
ActionRowSelectMenu SelectMenu |
Instances
mkButton :: Text -> Text -> Button Source #
Takes the label and the custom id of the button that is to be generated.
mkSelectMenu :: Text -> [SelectOption] -> SelectMenu 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.
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 MessageReaction Source #
A reaction to a message
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 #
A user in a thread
Constructors
ThreadMember | |
Fields
|
Instances
data ThreadMetadata Source #
Metadata for threads.
Constructors
ThreadMetadata | |
Fields
|
Instances
Permission overwrites for a channel.
Constructors
Overwrite | |
Fields
|
Instances
FromJSON Overwrite Source # | |
ToJSON Overwrite Source # | |
Defined in Discord.Internal.Types.Channel | |
Read Overwrite Source # | |
Show Overwrite Source # | |
Eq Overwrite Source # | |
Ord 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 | A news Channel in a guild. |
Fields
| |
ChannelStorePage | A store page channel in a guild |
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 | Like a |
Fields
| |
ChannelGuildCategory | A channel category |
Fields
| |
ChannelStage | A stage channel |
Fields
| |
ChannelNewsThread | A news Thread |
Fields
| |
ChannelPublicThread | A thread anyone can join |
Fields
| |
ChannelPrivateThread | An on-invite thread |
Fields
| |
ChannelUnknownType | A channel of unknown type |
Fields
|
channelIsInGuild :: Channel -> Bool Source #
If the channel is part of a guild (has a guild id field)
data TypingInfo Source #
Structre containing typing status information
Constructors
TypingInfo | |
Fields |
Instances
FromJSON TypingInfo Source # | |
Defined in Discord.Internal.Types.Events | |
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 # | |
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 # |
data ReactionRemoveInfo Source #
Structure containing information about a reaction that has been removed
Constructors
ReactionRemoveInfo | |
Instances
data ReactionInfo Source #
Structure containing information about a reaction
Constructors
ReactionInfo | |
Fields
|
Instances
FromJSON ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events | |
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 # | |
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 # |
data GuildCreateData Source #
Constructors
GuildCreateData | |
Fields
|
Instances
FromJSON GuildCreateData Source # | |
Defined in Discord.Internal.Types.Events Methods parseJSON :: Value -> Parser GuildCreateData # parseJSONList :: Value -> Parser [GuildCreateData] # | |
Read GuildCreateData Source # | |
Defined in Discord.Internal.Types.Events Methods readsPrec :: Int -> ReadS GuildCreateData # readList :: ReadS [GuildCreateData] # | |
Show GuildCreateData Source # | |
Defined in Discord.Internal.Types.Events Methods showsPrec :: Int -> GuildCreateData -> ShowS # show :: GuildCreateData -> String # showList :: [GuildCreateData] -> ShowS # | |
Eq GuildCreateData Source # | |
Defined in Discord.Internal.Types.Events Methods (==) :: GuildCreateData -> GuildCreateData -> Bool # (/=) :: GuildCreateData -> GuildCreateData -> Bool # |
data PartialApplication Source #
Structure containing partial information about an Application
Constructors
PartialApplication | |
Fields |
Instances
FromJSON PartialApplication Source # | |
Defined in Discord.Internal.Types.Events Methods parseJSON :: Value -> Parser PartialApplication # parseJSONList :: Value -> Parser [PartialApplication] # | |
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 # | |
Eq PartialApplication Source # | |
Defined in Discord.Internal.Types.Events Methods (==) :: PartialApplication -> PartialApplication -> Bool # (/=) :: PartialApplication -> PartialApplication -> Bool # |
Represents possible events sent by discord. Detailed information can be found at https://discord.com/developers/docs/topics/gateway.
Constructors
Ready Int User [GuildUnavailable] Text HostName (Maybe Shard) PartialApplication | Contains the initial state information |
Resumed [Text] | Response to a |
ChannelCreate Channel | new guild channel created |
ChannelUpdate Channel | channel was updated |
ChannelDelete Channel | channel was deleted |
ThreadCreate Channel | thread created, also sent when being added to a private thread |
ThreadUpdate Channel | thread was updated |
ThreadDelete Channel | thread was deleted |
ThreadListSync ThreadListSyncFields | sent when gaining access to a channel, contains all active threads in that channel |
ThreadMembersUpdate ThreadMembersUpdateFields | thread member for the current user was updated |
ChannelPinsUpdate ChannelId (Maybe UTCTime) | message was pinned or unpinned |
GuildCreate Guild GuildCreateData | lazy-load for unavailable guild, guild became available, or user joined a new guild |
GuildUpdate Guild | guild was updated |
GuildDelete GuildUnavailable | guild became unavailable, or user left/was removed from a guild |
GuildBanAdd GuildId User | user was banned from a guild |
GuildBanRemove GuildId User | user was unbanned from a guild |
GuildEmojiUpdate GuildId [Emoji] | guild emojis were updated |
GuildIntegrationsUpdate GuildId | guild integration was updated |
GuildMemberAdd GuildId GuildMember | new user joined a guild |
GuildMemberRemove GuildId User | user was removed from a guild |
GuildMemberUpdate GuildId [RoleId] User (Maybe Text) | guild member was updated |
GuildMemberChunk GuildId [GuildMember] | response to |
GuildRoleCreate GuildId Role | guild role was created |
GuildRoleUpdate GuildId Role | guild role was updated |
GuildRoleDelete GuildId RoleId | guild role was deleted |
MessageCreate Message | message was created |
MessageUpdate ChannelId MessageId | message was updated |
MessageDelete ChannelId MessageId | message was deleted |
MessageDeleteBulk ChannelId [MessageId] | multiple messages were deleted at once |
MessageReactionAdd ReactionInfo | user reacted to a message |
MessageReactionRemove ReactionInfo | user removed a reaction from a message |
MessageReactionRemoveAll ChannelId MessageId | all reactions were explicitly removed from a message |
MessageReactionRemoveEmoji ReactionRemoveInfo | all reactions for a given emoji were explicitly removed from a message |
PresenceUpdate PresenceInfo | user was updated |
TypingStart TypingInfo | user started typing in a channel |
UserUpdate User | properties about the user changed |
InteractionCreate Interaction | someone joined, left, or moved a voice channel |
UnknownEvent Text Object | An Unknown Event, none of the others |
Instances
extractHostname :: String -> HostName Source #
Remove the "wss://" and the trailing slash in a gateway URL, thereby returning the hostname portion of the URL that we can connect to.
eventParse :: Text -> Object -> Parser EventInternalParse Source #
Parse an event from name and JSON data
data UpdateStatusType Source #
Possible values for updateStatusOptsNewStatus
Constructors
UpdateStatusOnline | |
UpdateStatusDoNotDisturb | |
UpdateStatusAwayFromKeyboard | |
UpdateStatusInvisibleOffline | |
UpdateStatusOffline |
Instances
data UpdateStatusOpts Source #
Options for UpdateStatus
Constructors
UpdateStatusOpts | |
Instances
data UpdateStatusVoiceOpts Source #
Options for UpdateStatusVoice
Constructors
UpdateStatusVoiceOpts | |
Instances
data RequestGuildMembersOpts Source #
Options for RequestGuildMembers
Constructors
RequestGuildMembersOpts | |
Instances
data GatewaySendable Source #
Sent to gateway by a user
Constructors
RequestGuildMembers RequestGuildMembersOpts | |
UpdateStatus UpdateStatusOpts | |
UpdateStatusVoice UpdateStatusVoiceOpts |
Instances
data GatewayIntent Source #
Gateway intents to subrscribe to
Details of which intent englobs what data is avalilable at the official Discord documentation
Constructors
Instances
statusString :: UpdateStatusType -> Text Source #
Converts an UpdateStatusType to a textual representation
userFacingEvent :: EventInternalParse -> Event Source #
Converts an internal event to its user facing counterpart