Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Re-export user-visible types
Synopsis
- type Object = KeyMap Value
- class ToJSON a where
- data UTCTime = UTCTime {
- utctDay :: Day
- utctDayTime :: DiffTime
- data Event
- = Ready Int User [GuildUnavailable] Text HostName (Maybe Shard) PartialApplication
- | Resumed [Text]
- | AutoModerationRuleCreate AutoModerationRule
- | AutoModerationRuleUpdate AutoModerationRule
- | AutoModerationRuleDelete AutoModerationRule
- | AutoModerationActionExecution AutoModerationActionExecuteInfo
- | ChannelCreate Channel
- | ChannelUpdate Channel
- | ChannelDelete Channel
- | ThreadCreate Channel
- | ThreadUpdate Channel
- | ThreadMemberUpdate ThreadMemberUpdateFields
- | ThreadDelete Channel
- | ThreadListSync ThreadListSyncFields
- | ThreadMembersUpdate ThreadMembersUpdateFields
- | ChannelPinsUpdate ChannelId (Maybe UTCTime)
- | GuildCreate Guild GuildCreateData
- | GuildUpdate Guild
- | GuildDelete GuildUnavailable
- | GuildAuditLogEntryCreate AuditLogEntry
- | 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
- newtype Auth = Auth Text
- newtype Nonce = Nonce Text
- 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 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 Role = Role {
- roleId :: RoleId
- roleName :: Text
- roleColor :: DiscordColor
- roleHoist :: Bool
- rolePos :: Integer
- rolePerms :: RolePermissions
- roleManaged :: Bool
- roleMention :: Bool
- 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 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 Channel
- = ChannelText { }
- | ChannelNews { }
- | ChannelStorePage { }
- | ChannelVoice { }
- | ChannelDirectMessage { }
- | ChannelGroupDM { }
- | ChannelGuildCategory { }
- | ChannelStage { }
- | ChannelNewsThread { }
- | ChannelPublicThread { }
- | ChannelPrivateThread { }
- | ChannelUnknownType { }
- data Emoji = Emoji {}
- 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
- data Invite = Invite {}
- data Webhook = Webhook {}
- 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
- gatewayIntentAutoModerationConfiguration :: Bool
- gatewayIntentAutoModerationExecution :: Bool
- data AuditLog = AuditLog {}
- data AuditLogEvent
- data AllowedMentions = AllowedMentions {}
- type GuildId = DiscordId GuildIdType
- type ScheduledEventId = DiscordId ScheduledEventIdType
- newtype RolePermissions = RolePermissions {}
- newtype Snowflake = Snowflake {}
- newtype DiscordId a = DiscordId {}
- type ChannelId = DiscordId ChannelIdType
- type StageId = DiscordId StageIdType
- type MessageId = DiscordId MessageIdType
- type AttachmentId = DiscordId AttachmentIdType
- type EmojiId = DiscordId EmojiIdType
- type StickerId = DiscordId StickerIdType
- type UserId = DiscordId UserIdType
- type DiscordTeamId = DiscordId DiscordTeamIdType
- type GameSKUId = DiscordId GameSKUIdType
- type RoleId = DiscordId RoleIdType
- type IntegrationId = DiscordId IntegrationIdType
- type WebhookId = DiscordId WebhookIdType
- type ParentId = DiscordId ParentIdType
- type ApplicationId = DiscordId ApplicationIdType
- type ApplicationCommandId = DiscordId ApplicationCommandIdType
- type InteractionId = DiscordId InteractionIdType
- type ScheduledEventEntityId = DiscordId ScheduledEventEntityIdType
- type AuditLogEntryId = DiscordId AuditLogEntryIdType
- type AutoModerationRuleId = DiscordId AutoModerationRuleIdType
- newtype DiscordToken a = DiscordToken {}
- type InteractionToken = DiscordToken InteractionIdType
- type WebhookToken = DiscordToken WebhookIdType
- type Shard = (Int, Int)
- data ChannelTypeOption
- = ChannelTypeOptionGuildText
- | ChannelTypeOptionDM
- | ChannelTypeOptionGuildVoice
- | ChannelTypeOptionGroupDM
- | ChannelTypeOptionGuildCategory
- | ChannelTypeOptionGuildNews
- | ChannelTypeOptionGuildStore
- | ChannelTypeOptionGuildNewsThread
- | ChannelTypeOptionGuildPublicThread
- | ChannelTypeOptionGuildPrivateThread
- | ChannelTypeOptionGuildStageVoice
- data Overwrite = Overwrite {}
- data ThreadMetadata = ThreadMetadata {}
- data ThreadMember = ThreadMember {}
- data ThreadMemberUpdateFields = ThreadMemberUpdateFields {}
- data ThreadListSyncFields = ThreadListSyncFields {}
- data ThreadMembersUpdateFields = ThreadMembersUpdateFields {}
- data MessageReaction = MessageReaction {}
- data Attachment = Attachment {}
- data MessageReference = MessageReference {}
- data MessageActivity = MessageActivity {}
- data MessageActivityType
- data MessageFlag
- newtype MessageFlags = MessageFlags [MessageFlag]
- data MessageInteraction = MessageInteraction {}
- data GuildMember = GuildMember {}
- data ActionRow
- data AuditLogEntry = AuditLogEntry {}
- data AutoModerationRule = AutoModerationRule {
- autoModerationRuleId :: AutoModerationRuleId
- autoModerationRuleGuildId :: GuildId
- autoModerationRuleName :: String
- autoModerationRuleCreatorId :: UserId
- autoModerationRuleEventType :: AutoModerationRuleEventType
- autoModerationRuleTriggerType :: AutoModerationRuleTriggerType
- autoModerationRuleTriggerMetadata :: AutoModerationRuleTriggerMetadata
- autoModerationRuleActions :: [AutoModerationRuleAction]
- autoModerationRuleEnabled :: Bool
- autoModerationRuleExemptRoles :: [RoleId]
- autoModerationRuleExemptChannels :: [ChannelId]
- data AutoModerationRuleAction = AutoModerationRuleAction {}
- data AutoModerationRuleTriggerType
- 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 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
- data StickerItem = StickerItem {}
- data FullApplication = FullApplication {
- fullApplicationID :: ApplicationId
- fullApplicationName :: Text
- fullApplicationIcon :: Maybe Text
- fullApplicationDescription :: Text
- fullApplicationRPCOrigins :: Maybe [Text]
- fullApplicationBotPublic :: Bool
- fullApplicationRequiresCodeGrant :: Bool
- fullApplicationBotUserId :: Maybe UserId
- fullApplicationTermsOfServiceUrl :: Maybe Text
- fullApplicationPrivacyPolicyUrl :: Maybe Text
- fullApplicationOwnerId :: Maybe UserId
- fullApplicationVerifyKey :: Text
- fullApplicationTeam :: Maybe DiscordTeam
- fullApplicationGuildId :: Maybe GuildId
- fullApplicationGameSKUId :: Maybe GameSKUId
- fullapplicationSlug :: Maybe Text
- fullApplicationCoverImage :: Maybe Text
- fullApplicationFlags :: Maybe Integer
- fullApplicationApproximateGuildCount :: Maybe Integer
- fullApplicationRedirectURIs :: Maybe [Text]
- fullApplicationInteractionEndpointURL :: Maybe Text
- fullApplicationRoleConnectionVerificationURL :: Maybe Text
- fullApplicationTags :: Maybe [Text]
- fullApplicationInstallParams :: Maybe DiscordInstallParams
- fullApplicationCustomInstallUrl :: Maybe Text
- data TextInput = TextInput {}
- 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
- data Button
- = Button { }
- | ButtonUrl {
- buttonUrl :: Text
- buttonDisabled :: Bool
- buttonLabel :: Maybe Text
- buttonEmoji :: Maybe Emoji
- data ButtonStyle
- data SelectMenu = SelectMenu {}
- data SelectMenuData
- data SelectOption = SelectOption {}
- 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
- data AuditLogChange = AuditLogChange {}
- data AuditLogEntryOptions
- data AuditLogTiming
- data GetAuditLogOpts = GetAuditLogOpts {}
- data Integration = Integration {}
- data CreateEmbedImage
- data EmbedAuthor = EmbedAuthor {}
- data EmbedImage = EmbedImage {}
- data EmbedThumbnail = EmbedThumbnail {}
- data EmbedFooter = EmbedFooter {}
- data EmbedField = EmbedField {}
- data EmbedVideo = EmbedVideo {}
- data EmbedProvider = EmbedProvider {}
- data AutoModerationRuleEventType = MessageSent
- data AutoModerationRuleTriggerMetadata = AutoModerationRuleTriggerMetadata {
- autoModerationRuleTriggerMetadataKeywordFilter :: [String]
- autoModerationRuleTriggerMetadataRegexPatterns :: [String]
- autoModerationRuleTriggerMetadataPresets :: Maybe [AutoModerationRuleTriggerMetadataPreset]
- autoModerationRuleTriggerMetadataAllowList :: [String]
- autoModerationRuleTriggerMetadataMentionLimit :: Maybe Int
- autoModerationRuleTriggerMetadataRaidProtection :: Maybe Bool
- data AutoModerationRuleTriggerMetadataPreset
- data AutoModerationRuleActionType
- data AutoModerationRuleActionMetadata = AutoModerationRuleActionMetadata {}
- data DiscordTeam = DiscordTeam {}
- data DiscordInstallParams = DiscordInstallParams {}
- data DiscordTeamMember = DiscordTeamMember {}
- data DiscordTeamMemberState
- data ConnectionObject = ConnectionObject {
- connectionObjectId :: Text
- connectionObjectName :: Text
- connectionObjectType :: Text
- connectionObjectRevoked :: Bool
- connectionObjectIntegrations :: [IntegrationId]
- connectionObjectVerified :: Bool
- connectionObjectFriendSyncOn :: Bool
- connectionObjectShownInPresenceUpdates :: Bool
- connectionObjectVisibleToOthers :: Bool
- data StickerPack = StickerPack {}
- 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 StickerFormatType
- newtype GuildUnavailable = GuildUnavailable {}
- data PresenceInfo = PresenceInfo {
- presenceUserId :: UserId
- presenceActivities :: Maybe [(Activity, Maybe [Text])]
- presenceGuildId :: Maybe GuildId
- presenceStatus :: Maybe Text
- data ActivityType
- data ActivityTimestamps = ActivityTimestamps {}
- data ActivityParty = ActivityParty {}
- data ActivityButton = ActivityButton {}
- data PartialGuild = PartialGuild {}
- data VoiceRegion = VoiceRegion {}
- data GuildBan = GuildBan {}
- data InviteWithMeta = InviteWithMeta Invite InviteMeta
- data InviteMeta = InviteMeta {}
- data IntegrationAccount = IntegrationAccount {
- accountId :: Text
- accountName :: Text
- data GuildWidget = GuildWidget {}
- data PartialApplication = PartialApplication {}
- data AutoModerationActionExecuteInfo = AutoModerationActionExecuteInfo {
- autoModerationActionExecuteInfoGuildId :: GuildId
- autoModerationActionExecuteInfoAction :: AutoModerationRuleAction
- autoModerationActionExecuteInfoRuleId :: AutoModerationRuleId
- autoModerationActionExecuteInfoTriggerType :: AutoModerationRuleTriggerType
- autoModerationActionExecuteInfoUserId :: UserId
- autoModerationActionExecuteInfoChannelId :: Maybe ChannelId
- autoModerationActionExecuteInfoMessageId :: Maybe MessageId
- autoModerationActionExecuteInfoAlertMessageId :: Maybe MessageId
- autoModerationActionExecuteInfoContent :: String
- autoModerationActionExecuteInfoMatchedKeyword :: Maybe String
- autoModerationActionExecuteInfoMatchedContent :: Maybe String
- data GuildCreateData = GuildCreateData {
- guildCreateJoinedAt :: !UTCTime
- guildCreateLarge :: !Bool
- guildCreateUnavailable :: !(Maybe Bool)
- guildCreateMemberCount :: !Int
- guildCreateMembers :: ![GuildMember]
- guildCreateChannels :: ![Channel]
- guildCreateThreads :: ![Channel]
- guildCreatePresences :: ![PresenceInfo]
- guildCreateScheduledEvents :: ![ScheduledEvent]
- data ReactionInfo = ReactionInfo {}
- data ReactionRemoveInfo = ReactionRemoveInfo {}
- data TypingInfo = TypingInfo {}
- data GatewaySendable
- data RequestGuildMembersOpts = RequestGuildMembersOpts {}
- data UpdateStatusOpts = UpdateStatusOpts {}
- data UpdateStatusVoiceOpts = UpdateStatusVoiceOpts {}
- data UpdateStatusType
- epochTime :: UTCTime
- userFacingEvent :: EventInternalParse -> Event
- authToken :: Auth -> Text
- snowflakeCreationDate :: Snowflake -> UTCTime
- getMimeType :: ByteString -> Maybe Text
- (.==) :: ToJSON a => Key -> a -> Maybe Pair
- (.=?) :: ToJSON a => Key -> Maybe a -> Maybe Pair
- objectFromMaybes :: [Maybe Pair] -> Value
- channelIsInGuild :: Channel -> Bool
- createEmbed :: CreateEmbed -> Embed
- mkButton :: Text -> Text -> Button
- mkSelectMenu :: Text -> [SelectOption] -> SelectMenu
- mkSelectOption :: Text -> Text -> SelectOption
- mkTextInput :: Text -> Text -> TextInput
- hasRolePermissions :: [PermissionFlag] -> RolePermissions -> Bool
- hasRolePermission :: PermissionFlag -> RolePermissions -> Bool
- newRolePermissions :: [PermissionFlag] -> RolePermissions
- newRolePermission :: PermissionFlag -> RolePermissions
- setRolePermissions :: [PermissionFlag] -> RolePermissions -> RolePermissions
- setRolePermission :: PermissionFlag -> RolePermissions -> RolePermissions
- clearRolePermissions :: [PermissionFlag] -> RolePermissions -> RolePermissions
- clearRolePermission :: PermissionFlag -> RolePermissions -> RolePermissions
- hasGuildMemberPermission :: Guild -> GuildMember -> PermissionFlag -> Bool
- roleIdToRole :: Guild -> RoleId -> Maybe Role
- toAuditLogEvent :: Int -> Maybe AuditLogEvent
- hexToDiscordColor :: String -> DiscordColor
- maybeEmbed :: Maybe CreateEmbed -> [PartM IO]
- mkEmoji :: Text -> Emoji
- mkActivity :: Text -> ActivityType -> Activity
- parseGuildCreate :: Object -> Parser EventInternalParse
- reparse :: (ToJSON a, FromJSON b) => a -> Parser b
- extractHostname :: String -> HostName
- eventParse :: Text -> Object -> Parser EventInternalParse
- compileGatewayIntent :: GatewayIntent -> Int
- statusString :: UpdateStatusType -> Text
Documentation
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.)
Nothing
Instances
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.
UTCTime | |
|
Instances
FromJSON UTCTime | |
Defined in Data.Aeson.Types.FromJSON | |
FromJSONKey UTCTime | |
ToJSON UTCTime | |
ToJSONKey UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
Data UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime 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 parseUrlPiece :: Text -> Either Text UTCTime # parseHeader :: ByteString -> Either Text UTCTime # | |
ToHttpApiData UTCTime |
|
Defined in Web.Internal.HttpApiData toUrlPiece :: UTCTime -> Text # toEncodedUrlPiece :: UTCTime -> Builder # toHeader :: UTCTime -> ByteString # toQueryParam :: UTCTime -> Text # toEncodedQueryParam :: UTCTime -> Builder # |
Represents possible events sent by discord. Detailed information can be found at https://discord.com/developers/docs/topics/gateway.
Ready Int User [GuildUnavailable] Text HostName (Maybe Shard) PartialApplication | Contains the initial state information |
Resumed [Text] | Response to a |
AutoModerationRuleCreate AutoModerationRule | New auto moderation rule was created, requires the AutoModerationConfiguration intent |
AutoModerationRuleUpdate AutoModerationRule | Auto moderation rule was changed, requires the AutoModerationConfiguration intent |
AutoModerationRuleDelete AutoModerationRule | Auto moderation rule was deleted, requires the AutoModerationConfiguration intent |
AutoModerationActionExecution AutoModerationActionExecuteInfo | Action from an auto moderation rule was executed, requires the AutoModerationExecution intent |
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 |
ThreadMemberUpdate ThreadMemberUpdateFields | thread member for the current user 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 | member or the current user was added or removed from a thread |
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 |
GuildAuditLogEntryCreate AuditLogEntry | new entry to the audit log was added |
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 |
Authorization token for the Discord API
Represents information about a message in a Discord channel.
Message | |
|
An embed attached to a message.
Embed | |
|
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.
Role | |
|
data MessageType Source #
Instances
Represents information about a user.
User | |
|
Guild channels represent an isolated set of users and messages in a Guild (Server)
ChannelText | A text channel in a guild. |
| |
ChannelNews | A news Channel in a guild. |
| |
ChannelStorePage | A store page channel in a guild |
| |
ChannelVoice | A voice channel in a guild. |
| |
ChannelDirectMessage | DM Channels represent a one-to-one conversation between two users, outside the scope of guilds |
| |
ChannelGroupDM | Like a |
| |
ChannelGuildCategory | A channel category |
| |
ChannelStage | A stage channel |
| |
ChannelNewsThread | A news Thread |
| |
ChannelPublicThread | A thread anyone can join |
| |
ChannelPrivateThread | An on-invite thread |
| |
ChannelUnknownType | A channel of unknown type |
|
Represents an emoticon (emoji)
Guilds in Discord represent a collection of users and channels into an isolated Server
https://discord.com/developers/docs/resources/guild#guild-object
Guild | |
|
Represents a code to add a user to a guild
Invite | |
|
data GatewayIntent Source #
Gateway intents to subrscribe to
Details of which intent englobs what data is avalilable at the official Discord documentation
Instances
Audit log object, along with the entries it also contains referenced users, integrations [...] and so on
data AuditLogEvent Source #
Instances
FromJSON AuditLogEvent Source # | |
Defined in Discord.Internal.Types.AuditLog parseJSON :: Value -> Parser AuditLogEvent # parseJSONList :: Value -> Parser [AuditLogEvent] # | |
Read AuditLogEvent Source # | |
Defined in Discord.Internal.Types.AuditLog readsPrec :: Int -> ReadS AuditLogEvent # readList :: ReadS [AuditLogEvent] # | |
Show AuditLogEvent Source # | |
Defined in Discord.Internal.Types.AuditLog showsPrec :: Int -> AuditLogEvent -> ShowS # show :: AuditLogEvent -> String # showList :: [AuditLogEvent] -> ShowS # | |
Eq AuditLogEvent Source # | |
Defined in Discord.Internal.Types.AuditLog (==) :: AuditLogEvent -> AuditLogEvent -> Bool # (/=) :: AuditLogEvent -> AuditLogEvent -> Bool # |
data AllowedMentions Source #
Data constructor for a part of MessageDetailedOpts.
AllowedMentions | |
|
Instances
type ScheduledEventId = DiscordId ScheduledEventIdType Source #
newtype RolePermissions Source #
Instances
A unique integer identifier. Can be used to calculate the creation date of an entity.
Instances
FromJSON Snowflake Source # | |
Defined in Discord.Internal.Types.Prelude | |
FromJSONKey Snowflake Source # | |
ToJSON Snowflake Source # | |
ToJSONKey Snowflake Source # | |
Read Snowflake Source # | |
Show Snowflake Source # | |
Eq Snowflake Source # | |
Ord Snowflake Source # | |
Defined in Discord.Internal.Types.Prelude | |
Hashable Snowflake Source # | |
Defined in Discord.Internal.Types.Prelude | |
ToHttpApiData Snowflake Source # | |
Defined in Discord.Internal.Types.Prelude toUrlPiece :: Snowflake -> Text # toEncodedUrlPiece :: Snowflake -> Builder # toHeader :: Snowflake -> ByteString # toQueryParam :: Snowflake -> Text # toEncodedQueryParam :: Snowflake -> Builder # |
Instances
FromJSON (DiscordId a) Source # | |
Defined in Discord.Internal.Types.Prelude | |
FromJSONKey (DiscordId a) Source # | |
Defined in Discord.Internal.Types.Prelude | |
ToJSON (DiscordId a) Source # | |
ToJSONKey (DiscordId a) Source # | |
Defined in Discord.Internal.Types.Prelude toJSONKey :: ToJSONKeyFunction (DiscordId a) # toJSONKeyList :: ToJSONKeyFunction [DiscordId a] # | |
Read (DiscordId a) Source # | |
Show (DiscordId a) Source # | |
Eq (DiscordId a) Source # | |
Ord (DiscordId a) Source # | |
Defined in Discord.Internal.Types.Prelude | |
Hashable (DiscordId a) Source # | |
Defined in Discord.Internal.Types.Prelude | |
ToHttpApiData (DiscordId a) Source # | |
Defined in Discord.Internal.Types.Prelude toUrlPiece :: DiscordId a -> Text # toEncodedUrlPiece :: DiscordId a -> Builder # toHeader :: DiscordId a -> ByteString # toQueryParam :: DiscordId a -> Text # toEncodedQueryParam :: DiscordId a -> Builder # |
type AttachmentId = DiscordId AttachmentIdType Source #
type DiscordTeamId = DiscordId DiscordTeamIdType Source #
type IntegrationId = DiscordId IntegrationIdType Source #
type ApplicationId = DiscordId ApplicationIdType Source #
type ApplicationCommandId = DiscordId ApplicationCommandIdType Source #
type InteractionId = DiscordId InteractionIdType Source #
type ScheduledEventEntityId = DiscordId ScheduledEventEntityIdType Source #
type AuditLogEntryId = DiscordId AuditLogEntryIdType Source #
type AutoModerationRuleId = DiscordId AutoModerationRuleIdType Source #
newtype DiscordToken a Source #
Instances
type InteractionToken = DiscordToken InteractionIdType Source #
type WebhookToken = DiscordToken WebhookIdType Source #
data ChannelTypeOption Source #
The different channel types. Used for application commands and components.
https://discord.com/developers/docs/resources/channel#channel-object-channel-types
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
Permission overwrites for a channel.
Overwrite | |
|
data ThreadMetadata Source #
Metadata for threads.
ThreadMetadata | |
|
Instances
data ThreadMember Source #
A user in a thread
ThreadMember | |
|
Instances
data ThreadMemberUpdateFields Source #
ThreadMemberUpdateFields | |
|
Instances
data ThreadListSyncFields Source #
Instances
data ThreadMembersUpdateFields Source #
Instances
data MessageReaction Source #
A reaction to a message
Instances
data Attachment Source #
Represents an attached to a message file.
Attachment | |
|
Instances
data MessageReference Source #
Represents a Message Reference
MessageReference | |
|
Instances
data MessageActivity Source #
Instances
data MessageActivityType Source #
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 MessageFlag Source #
Types of flags to attach to the message.
Instances
newtype MessageFlags Source #
Instances
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).
MessageInteraction | |
|
Instances
data GuildMember Source #
Representation of a guild member.
GuildMember | |
|
Instances
Container for other message Components
data AuditLogEntry Source #
An audit log entry object, so to speak the actual event that took place
Instances
FromJSON AuditLogEntry Source # | |
Defined in Discord.Internal.Types.AuditLog parseJSON :: Value -> Parser AuditLogEntry # parseJSONList :: Value -> Parser [AuditLogEntry] # | |
Read AuditLogEntry Source # | |
Defined in Discord.Internal.Types.AuditLog readsPrec :: Int -> ReadS AuditLogEntry # readList :: ReadS [AuditLogEntry] # | |
Show AuditLogEntry Source # | |
Defined in Discord.Internal.Types.AuditLog showsPrec :: Int -> AuditLogEntry -> ShowS # show :: AuditLogEntry -> String # showList :: [AuditLogEntry] -> ShowS # | |
Eq AuditLogEntry Source # | |
Defined in Discord.Internal.Types.AuditLog (==) :: AuditLogEntry -> AuditLogEntry -> Bool # (/=) :: AuditLogEntry -> AuditLogEntry -> Bool # |
data AutoModerationRule Source #
Instances
FromJSON AutoModerationRule Source # | |
Defined in Discord.Internal.Types.AutoModeration | |
ToJSON AutoModerationRule Source # | |
Defined in Discord.Internal.Types.AutoModeration toJSON :: AutoModerationRule -> Value # toEncoding :: AutoModerationRule -> Encoding # toJSONList :: [AutoModerationRule] -> Value # toEncodingList :: [AutoModerationRule] -> Encoding # omitField :: AutoModerationRule -> Bool # | |
Read AutoModerationRule Source # | |
Show AutoModerationRule Source # | |
Defined in Discord.Internal.Types.AutoModeration showsPrec :: Int -> AutoModerationRule -> ShowS # show :: AutoModerationRule -> String # showList :: [AutoModerationRule] -> ShowS # | |
Eq AutoModerationRule Source # | |
Defined in Discord.Internal.Types.AutoModeration (==) :: AutoModerationRule -> AutoModerationRule -> Bool # (/=) :: AutoModerationRule -> AutoModerationRule -> Bool # |
data AutoModerationRuleAction Source #
Instances
data AutoModerationRuleTriggerType Source #
Instances
Object for a single activity
https://discord.com/developers/docs/topics/gateway-events#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.
Only youtube and twitch urls will work.
Activity | |
|
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
Instances
data StickerItem Source #
A simplified sticker object.
StickerItem | |
|
Instances
data FullApplication Source #
Structure containing partial information about an Application https://discord.com/developers/docs/resources/application#application-object
FullApplication | |
|
Instances
TextInput | |
|
data CreateEmbed Source #
The Default
instance of this type yields a def
value whose fields are all empty.
As such, the def
value is not a valid embed and needs to be adjusted before being used.
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.
Button | |
| |
ButtonUrl | |
|
data ButtonStyle Source #
Buttton colors.
ButtonStylePrimary | Blurple button |
ButtonStyleSecondary | Grey button |
ButtonStyleSuccess | Green button |
ButtonStyleDanger | Red button |
Instances
data SelectMenu Source #
Component type for a select menu.
Don't directly send select menus - they need to be within an action row.
SelectMenu | |
|
Instances
data SelectMenuData Source #
SelectMenuDataText [SelectOption] | Text options |
SelectMenuDataUser | Users |
SelectMenuDataRole | Roles |
SelectMenuDataMentionable | Anything mentionable (users and roles) |
SelectMenuDataChannels [ChannelTypeOption] | Channels (of certain types) |
Instances
data SelectOption Source #
A single option in a select menu.
SelectOption | |
|
Instances
data PermissionFlag Source #
Instances
data AuditLogChange Source #
A change object, new value and old value fields are of Aesons Value
type,
because it can be pretty much any value from discord api
Instances
FromJSON AuditLogChange Source # | |
Defined in Discord.Internal.Types.AuditLog parseJSON :: Value -> Parser AuditLogChange # parseJSONList :: Value -> Parser [AuditLogChange] # | |
Read AuditLogChange Source # | |
Defined in Discord.Internal.Types.AuditLog readsPrec :: Int -> ReadS AuditLogChange # readList :: ReadS [AuditLogChange] # | |
Show AuditLogChange Source # | |
Defined in Discord.Internal.Types.AuditLog showsPrec :: Int -> AuditLogChange -> ShowS # show :: AuditLogChange -> String # showList :: [AuditLogChange] -> ShowS # | |
Eq AuditLogChange Source # | |
Defined in Discord.Internal.Types.AuditLog (==) :: AuditLogChange -> AuditLogChange -> Bool # (/=) :: AuditLogChange -> AuditLogChange -> Bool # |
data AuditLogEntryOptions Source #
Optional data for the Audit Log Entry object
Instances
FromJSON AuditLogEntryOptions Source # | |
Defined in Discord.Internal.Types.AuditLog | |
Read AuditLogEntryOptions Source # | |
Show AuditLogEntryOptions Source # | |
Defined in Discord.Internal.Types.AuditLog showsPrec :: Int -> AuditLogEntryOptions -> ShowS # show :: AuditLogEntryOptions -> String # showList :: [AuditLogEntryOptions] -> ShowS # | |
Eq AuditLogEntryOptions Source # | |
Defined in Discord.Internal.Types.AuditLog (==) :: AuditLogEntryOptions -> AuditLogEntryOptions -> Bool # (/=) :: AuditLogEntryOptions -> AuditLogEntryOptions -> Bool # |
data AuditLogTiming Source #
Instances
Read AuditLogTiming Source # | |
Defined in Discord.Internal.Types.AuditLog readsPrec :: Int -> ReadS AuditLogTiming # readList :: ReadS [AuditLogTiming] # | |
Show AuditLogTiming Source # | |
Defined in Discord.Internal.Types.AuditLog showsPrec :: Int -> AuditLogTiming -> ShowS # show :: AuditLogTiming -> String # showList :: [AuditLogTiming] -> ShowS # | |
Eq AuditLogTiming Source # | |
Defined in Discord.Internal.Types.AuditLog (==) :: AuditLogTiming -> AuditLogTiming -> Bool # (/=) :: AuditLogTiming -> AuditLogTiming -> Bool # | |
Ord AuditLogTiming Source # | |
Defined in Discord.Internal.Types.AuditLog compare :: AuditLogTiming -> AuditLogTiming -> Ordering # (<) :: AuditLogTiming -> AuditLogTiming -> Bool # (<=) :: AuditLogTiming -> AuditLogTiming -> Bool # (>) :: AuditLogTiming -> AuditLogTiming -> Bool # (>=) :: AuditLogTiming -> AuditLogTiming -> Bool # max :: AuditLogTiming -> AuditLogTiming -> AuditLogTiming # min :: AuditLogTiming -> AuditLogTiming -> AuditLogTiming # |
data GetAuditLogOpts Source #
Options for GetAuditLog
request
Instances
Read GetAuditLogOpts Source # | |
Defined in Discord.Internal.Types.AuditLog | |
Show GetAuditLogOpts Source # | |
Defined in Discord.Internal.Types.AuditLog showsPrec :: Int -> GetAuditLogOpts -> ShowS # show :: GetAuditLogOpts -> String # showList :: [GetAuditLogOpts] -> ShowS # | |
Default GetAuditLogOpts Source # | |
Defined in Discord.Internal.Types.AuditLog def :: GetAuditLogOpts # | |
Eq GetAuditLogOpts Source # | |
Defined in Discord.Internal.Types.AuditLog (==) :: GetAuditLogOpts -> GetAuditLogOpts -> Bool # (/=) :: GetAuditLogOpts -> GetAuditLogOpts -> Bool # |
data Integration Source #
Represents the behavior of a third party account link.
Integration | |
|
Instances
data CreateEmbedImage Source #
Instances
Read CreateEmbedImage Source # | |
Defined in Discord.Internal.Types.Embed | |
Show CreateEmbedImage Source # | |
Defined in Discord.Internal.Types.Embed showsPrec :: Int -> CreateEmbedImage -> ShowS # show :: CreateEmbedImage -> String # showList :: [CreateEmbedImage] -> ShowS # | |
Eq CreateEmbedImage Source # | |
Defined in Discord.Internal.Types.Embed (==) :: CreateEmbedImage -> CreateEmbedImage -> Bool # (/=) :: CreateEmbedImage -> CreateEmbedImage -> Bool # | |
Ord CreateEmbedImage Source # | |
Defined in Discord.Internal.Types.Embed compare :: CreateEmbedImage -> CreateEmbedImage -> Ordering # (<) :: CreateEmbedImage -> CreateEmbedImage -> Bool # (<=) :: CreateEmbedImage -> CreateEmbedImage -> Bool # (>) :: CreateEmbedImage -> CreateEmbedImage -> Bool # (>=) :: CreateEmbedImage -> CreateEmbedImage -> Bool # max :: CreateEmbedImage -> CreateEmbedImage -> CreateEmbedImage # min :: CreateEmbedImage -> CreateEmbedImage -> CreateEmbedImage # |
data EmbedAuthor Source #
Instances
data EmbedImage Source #
Instances
data EmbedThumbnail Source #
Instances
data EmbedField Source #
Instances
data EmbedVideo Source #
Instances
data EmbedProvider Source #
Instances
data AutoModerationRuleEventType Source #
Instances
data AutoModerationRuleTriggerMetadata Source #
Instances
data AutoModerationRuleTriggerMetadataPreset Source #
Instances
data AutoModerationRuleActionType Source #
Instances
data AutoModerationRuleActionMetadata Source #
Instances
data DiscordTeam Source #
Instances
data DiscordInstallParams Source #
Instances
data DiscordTeamMember Source #
Instances
data DiscordTeamMemberState Source #
Instances
data ConnectionObject Source #
The connection object that the user has attached.
ConnectionObject | |
|
Instances
data StickerPack Source #
Represents a pack of standard stickers.
StickerPack | |
|
Instances
A full sticker object
Sticker | |
|
data StickerFormatType Source #
The format of a sticker
Instances
data PresenceInfo Source #
PresenceInfo | |
|
Instances
data ActivityType Source #
To see what these look like, go to here: https://discord.com/developers/docs/topics/gateway#activity-object-activity-types
ActivityTypeGame | |
ActivityTypeStreaming | |
ActivityTypeListening | |
ActivityTypeWatching | |
ActivityTypeCustom | |
ActivityTypeCompeting |
Instances
data ActivityTimestamps Source #
ActivityTimestamps | |
|
Instances
data ActivityParty Source #
Instances
data ActivityButton Source #
Instances
data PartialGuild Source #
Instances
data VoiceRegion Source #
VoiceRegion is only refrenced in Guild endpoints, will be moved when voice support is added
VoiceRegion | |
|
Instances
Info about a Ban
data InviteWithMeta Source #
Invite code with additional metadata
Instances
FromJSON InviteWithMeta Source # | |
Defined in Discord.Internal.Types.Guild parseJSON :: Value -> Parser InviteWithMeta # parseJSONList :: Value -> Parser [InviteWithMeta] # |
data InviteMeta Source #
Additional metadata about an invite.
InviteMeta | |
|
Instances
data IntegrationAccount Source #
Represents a third party account link.
IntegrationAccount | |
|
Instances
data GuildWidget Source #
Represents an image to be used in third party sites to link to a discord channel
GuildWidget | |
|
Instances
data PartialApplication Source #
Structure containing partial information about an Application
Instances
FromJSON PartialApplication Source # | |
Defined in Discord.Internal.Types.Events | |
Read PartialApplication Source # | |
Defined in Discord.Internal.Types.Events | |
Show PartialApplication Source # | |
Defined in Discord.Internal.Types.Events showsPrec :: Int -> PartialApplication -> ShowS # show :: PartialApplication -> String # showList :: [PartialApplication] -> ShowS # | |
Eq PartialApplication Source # | |
Defined in Discord.Internal.Types.Events (==) :: PartialApplication -> PartialApplication -> Bool # (/=) :: PartialApplication -> PartialApplication -> Bool # |
data AutoModerationActionExecuteInfo Source #
Structure containing auto moderation action execution information
Instances
data GuildCreateData Source #
Instances
Read GuildCreateData Source # | |
Defined in Discord.Internal.Types.Events | |
Show GuildCreateData Source # | |
Defined in Discord.Internal.Types.Events showsPrec :: Int -> GuildCreateData -> ShowS # show :: GuildCreateData -> String # showList :: [GuildCreateData] -> ShowS # | |
Eq GuildCreateData Source # | |
Defined in Discord.Internal.Types.Events (==) :: GuildCreateData -> GuildCreateData -> Bool # (/=) :: GuildCreateData -> GuildCreateData -> Bool # |
data ReactionInfo Source #
Structure containing information about a reaction
ReactionInfo | |
|
Instances
data ReactionRemoveInfo Source #
Structure containing information about a reaction that has been removed
Instances
data TypingInfo Source #
Structre containing typing status information
Instances
data GatewaySendable Source #
Sent to gateway by a user
RequestGuildMembers RequestGuildMembersOpts | |
UpdateStatus UpdateStatusOpts | |
UpdateStatusVoice UpdateStatusVoiceOpts |
Instances
data RequestGuildMembersOpts Source #
Options for RequestGuildMembers
Instances
data UpdateStatusOpts Source #
Options for UpdateStatus
Presence Update - https://discord.com/developers/docs/topics/gateway-events#update-presence
Instances
Read UpdateStatusOpts Source # | |
Defined in Discord.Internal.Types.Gateway | |
Show UpdateStatusOpts Source # | |
Defined in Discord.Internal.Types.Gateway showsPrec :: Int -> UpdateStatusOpts -> ShowS # show :: UpdateStatusOpts -> String # showList :: [UpdateStatusOpts] -> ShowS # | |
Eq UpdateStatusOpts Source # | |
Defined in Discord.Internal.Types.Gateway (==) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # (/=) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # | |
Ord UpdateStatusOpts Source # | |
Defined in Discord.Internal.Types.Gateway compare :: UpdateStatusOpts -> UpdateStatusOpts -> Ordering # (<) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # (<=) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # (>) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # (>=) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # max :: UpdateStatusOpts -> UpdateStatusOpts -> UpdateStatusOpts # min :: UpdateStatusOpts -> UpdateStatusOpts -> UpdateStatusOpts # |
data UpdateStatusVoiceOpts Source #
Options for UpdateStatusVoice
Instances
data UpdateStatusType Source #
Possible values for updateStatusOptsNewStatus
UpdateStatusOnline | |
UpdateStatusDoNotDisturb | |
UpdateStatusAwayFromKeyboard | |
UpdateStatusInvisibleOffline | |
UpdateStatusOffline |
Instances
userFacingEvent :: EventInternalParse -> Event Source #
Converts an internal event to its user facing counterpart
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.
channelIsInGuild :: Channel -> Bool Source #
If the channel is part of a guild (has a guild id field)
createEmbed :: CreateEmbed -> Embed Source #
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.
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
setRolePermission :: PermissionFlag -> RolePermissions -> RolePermissions Source #
Set a certain permission flag This method doesn't lose the other already present permissions
clearRolePermissions :: [PermissionFlag] -> RolePermissions -> RolePermissions Source #
Unset Permissions from RolePermissions
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
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
toAuditLogEvent :: Int -> Maybe AuditLogEvent Source #
See https://discord.com/developers/docs/resources/audit-log#audit-log-entry-object-audit-log-events for more information on Events
hexToDiscordColor :: String -> DiscordColor Source #
hexToDiscordColor
converts a potential hex string into a DiscordColor,
evaluating to Default if it fails.
maybeEmbed :: Maybe CreateEmbed -> [PartM IO] Source #
mkActivity :: Text -> ActivityType -> Activity Source #
The quick and easy way to make an activity for a discord bot.
To set the activityState
or activityUrl
, please use record field syntax.
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
statusString :: UpdateStatusType -> Text Source #
Converts an UpdateStatusType to a textual representation