Safe Haskell | None |
---|---|
Language | Haskell2010 |
Discord.Types
Synopsis
- data UTCTime = UTCTime {
- utctDay :: Day
- utctDayTime :: DiffTime
- type Object = KeyMap Value
- type ColorInteger = Integer
- type ParentId = Snowflake
- type WebhookId = Snowflake
- type IntegrationId = Snowflake
- type RoleId = Snowflake
- type OverwriteId = Snowflake
- type UserId = Snowflake
- type EmojiId = Snowflake
- type MessageId = Snowflake
- type GuildId = Snowflake
- type StageId = Snowflake
- type ChannelId = Snowflake
- newtype Snowflake = Snowflake Word64
- data Auth = Auth Text
- authToken :: Auth -> Text
- snowflakeCreationDate :: Snowflake -> UTCTime
- epochTime :: UTCTime
- data EmbedField = EmbedField {}
- data EmbedFooter = EmbedFooter {}
- data EmbedAuthor = EmbedAuthor {}
- data EmbedProvider = EmbedProvider {}
- data EmbedImage = EmbedImage {}
- data EmbedVideo = EmbedVideo {}
- data EmbedThumbnail = EmbedThumbnail {}
- data Embed = Embed {
- embedAuthor :: Maybe EmbedAuthor
- embedTitle :: Maybe Text
- embedUrl :: Maybe Text
- embedThumbnail :: Maybe EmbedThumbnail
- embedDescription :: Maybe Text
- embedFields :: [EmbedField]
- embedImage :: Maybe EmbedImage
- embedFooter :: Maybe EmbedFooter
- embedColor :: Maybe ColorInteger
- embedTimestamp :: Maybe UTCTime
- embedType :: Maybe Text
- embedVideo :: Maybe EmbedVideo
- embedProvider :: Maybe EmbedProvider
- data CreateEmbedImage
- data CreateEmbed = CreateEmbed {
- createEmbedAuthorName :: Text
- createEmbedAuthorUrl :: Text
- createEmbedAuthorIcon :: Maybe CreateEmbedImage
- createEmbedTitle :: Text
- createEmbedUrl :: Text
- createEmbedThumbnail :: Maybe CreateEmbedImage
- createEmbedDescription :: Text
- createEmbedFields :: [EmbedField]
- createEmbedImage :: Maybe CreateEmbedImage
- createEmbedFooterText :: Text
- createEmbedFooterIcon :: Maybe CreateEmbedImage
- createEmbedColor :: Maybe ColorInteger
- createEmbed :: CreateEmbed -> Embed
- data 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 {}
- data MessageReference = MessageReference {}
- newtype Nonce = Nonce Text
- data Attachment = Attachment {}
- data Emoji = Emoji {}
- data MessageReaction = MessageReaction {}
- data Message = Message {
- messageId :: MessageId
- messageChannel :: ChannelId
- messageAuthor :: User
- messageText :: 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
- messageGuild :: Maybe GuildId
- messageReference :: Maybe MessageReference
- referencedMessage :: Maybe Message
- data Overwrite = Overwrite {}
- data Channel
- = ChannelText { }
- | ChannelNews { }
- | ChannelStorePage { }
- | ChannelVoice { }
- | ChannelDirectMessage { }
- | ChannelGroupDM { }
- | ChannelGuildCategory { }
- | ChannelStage { }
- | ChannelUnknownType { }
- channelIsInGuild :: Channel -> Bool
- data GuildEmbed = GuildEmbed {}
- data IntegrationAccount = IntegrationAccount {
- accountId :: Text
- accountName :: Text
- data Integration = Integration {}
- data InviteMeta = InviteMeta {}
- data InviteWithMeta = InviteWithMeta Invite InviteMeta
- data Invite = Invite {}
- data GuildBan = GuildBan {}
- data VoiceRegion = VoiceRegion {}
- data Role = Role {}
- data PartialGuild = PartialGuild {}
- data GuildInfo = GuildInfo {}
- data GuildUnavailable = GuildUnavailable {}
- data Guild = Guild {
- guildId :: GuildId
- guildName :: Text
- guildIcon :: Maybe Text
- guildSplash :: Maybe Text
- guildOwnerId :: UserId
- guildPermissions :: Maybe Integer
- guildRegion :: Maybe Text
- guildAfkId :: Maybe ChannelId
- guildAfkTimeout :: Integer
- guildEmbedEnabled :: Maybe Bool
- guildEmbedChannel :: Maybe ChannelId
- guildVerificationLevel :: Integer
- guildNotification :: Integer
- guildExplicitFilterLevel :: Integer
- guildRoles :: [Role]
- guildEmojis :: [Emoji]
- guildFeatures :: [Text]
- guildMultiFactAuth :: !Integer
- guildApplicationId :: Maybe Snowflake
- data GuildMember = GuildMember {
- memberUser :: User
- memberNick :: Maybe Text
- memberRoles :: [Snowflake]
- memberJoinedAt :: UTCTime
- memberDeaf :: Bool
- memberMute :: Bool
- data TypingInfo = TypingInfo {}
- data PresenceInfo = PresenceInfo {}
- data ReactionRemoveInfo = ReactionRemoveInfo {}
- data ReactionInfo = ReactionInfo {}
- data Event
- = Ready Int User [Channel] [GuildUnavailable] Text
- | Resumed [Text]
- | ChannelCreate Channel
- | ChannelUpdate Channel
- | ChannelDelete Channel
- | ChannelPinsUpdate ChannelId (Maybe UTCTime)
- | GuildCreate Guild GuildInfo
- | GuildUpdate Guild
- | GuildDelete GuildUnavailable
- | GuildBanAdd GuildId User
- | GuildBanRemove GuildId User
- | GuildEmojiUpdate GuildId [Emoji]
- | GuildIntegrationsUpdate GuildId
- | GuildMemberAdd GuildId GuildMember
- | GuildMemberRemove GuildId User
- | GuildMemberUpdate GuildId [RoleId] User (Maybe Text)
- | GuildMemberChunk GuildId [GuildMember]
- | GuildRoleCreate GuildId Role
- | GuildRoleUpdate GuildId Role
- | GuildRoleDelete GuildId RoleId
- | MessageCreate Message
- | MessageUpdate ChannelId MessageId
- | MessageDelete ChannelId MessageId
- | MessageDeleteBulk ChannelId [MessageId]
- | MessageReactionAdd ReactionInfo
- | MessageReactionRemove ReactionInfo
- | MessageReactionRemoveAll ChannelId MessageId
- | MessageReactionRemoveEmoji ReactionRemoveInfo
- | PresenceUpdate PresenceInfo
- | TypingStart TypingInfo
- | UserUpdate User
- | UnknownEvent Text Object
- reparse :: (ToJSON a, FromJSON b) => a -> Parser b
- eventParse :: Text -> Object -> Parser Event
- data UpdateStatusType
- data ActivityType
- data Activity = Activity {}
- data UpdateStatusOpts = UpdateStatusOpts {}
- data UpdateStatusVoiceOpts = UpdateStatusVoiceOpts {}
- data RequestGuildMembersOpts = RequestGuildMembersOpts {}
- data GatewaySendable
- data GatewayIntent = GatewayIntent {
- gatewayIntentGuilds :: Bool
- gatewayIntentMembers :: Bool
- gatewayIntentBans :: Bool
- gatewayIntentEmojis :: Bool
- gatewayIntentIntegrations :: Bool
- gatewayIntentWebhooks :: Bool
- gatewayIntentInvites :: Bool
- gatewayIntentVoiceStates :: Bool
- gatewayIntentPrecenses :: Bool
- gatewayIntentMessageChanges :: Bool
- gatewayIntentMessageReactions :: Bool
- gatewayIntentMessageTyping :: Bool
- gatewayIntentDirectMessageChanges :: Bool
- gatewayIntentDirectMessageReactions :: Bool
- gatewayIntentDirectMessageTyping :: Bool
- pattern Resume :: Auth -> Text -> Integer -> GatewaySendableInternal
- pattern Heartbeat :: Integer -> GatewaySendableInternal
- pattern Identify :: Auth -> GatewayIntent -> (Int, Int) -> GatewaySendableInternal
- pattern HeartbeatAck :: GatewayReceivable
- pattern Hello :: Integer -> GatewayReceivable
- pattern InvalidSession :: Bool -> GatewayReceivable
- pattern Reconnect :: GatewayReceivable
- pattern HeartbeatRequest :: Integer -> GatewayReceivable
- pattern ParseError :: Text -> GatewayReceivable
- pattern Dispatch :: Event -> Integer -> GatewayReceivable
- compileGatewayIntent :: GatewayIntent -> Int
- activityTypeId :: ActivityType -> Int
- statusString :: UpdateStatusType -> Text
Documentation
This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.
Constructors
UTCTime | |
Fields
|
Instances
Eq UTCTime | |
Data UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime # toConstr :: UTCTime -> Constr # dataTypeOf :: UTCTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) # gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # | |
Ord UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
ToJSON UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON UTCTime | |
FromJSONKey UTCTime | |
Defined in Data.Aeson.Types.FromJSON Methods | |
NFData UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
ToHttpApiData UTCTime |
|
Defined in Web.Internal.HttpApiData Methods toUrlPiece :: UTCTime -> Text # toEncodedUrlPiece :: UTCTime -> Builder # toHeader :: UTCTime -> ByteString # toQueryParam :: UTCTime -> Text # | |
FromHttpApiData UTCTime |
|
Defined in Web.Internal.HttpApiData Methods parseUrlPiece :: Text -> Either Text UTCTime # parseHeader :: ByteString -> Either Text UTCTime # |
type ColorInteger = Integer Source #
type IntegrationId = Snowflake Source #
type OverwriteId = Snowflake Source #
A unique integer identifier. Can be used to calculate the creation date of an entity.
Instances
Authorization token for the Discord API
snowflakeCreationDate :: Snowflake -> UTCTime Source #
Gets a creation date from a snowflake.
data EmbedField Source #
Constructors
EmbedField | |
Fields |
Instances
Eq EmbedField Source # | |
Defined in Discord.Internal.Types.Embed | |
Ord EmbedField Source # | |
Defined in Discord.Internal.Types.Embed Methods compare :: EmbedField -> EmbedField -> Ordering # (<) :: EmbedField -> EmbedField -> Bool # (<=) :: EmbedField -> EmbedField -> Bool # (>) :: EmbedField -> EmbedField -> Bool # (>=) :: EmbedField -> EmbedField -> Bool # max :: EmbedField -> EmbedField -> EmbedField # min :: EmbedField -> EmbedField -> EmbedField # | |
Show EmbedField Source # | |
Defined in Discord.Internal.Types.Embed Methods showsPrec :: Int -> EmbedField -> ShowS # show :: EmbedField -> String # showList :: [EmbedField] -> ShowS # | |
ToJSON EmbedField Source # | |
Defined in Discord.Internal.Types.Embed Methods toJSON :: EmbedField -> Value # toEncoding :: EmbedField -> Encoding # toJSONList :: [EmbedField] -> Value # toEncodingList :: [EmbedField] -> Encoding # | |
FromJSON EmbedField Source # | |
Defined in Discord.Internal.Types.Embed |
data EmbedAuthor Source #
Constructors
EmbedAuthor | |
Fields |
Instances
Eq EmbedAuthor Source # | |
Defined in Discord.Internal.Types.Embed | |
Ord EmbedAuthor Source # | |
Defined in Discord.Internal.Types.Embed Methods compare :: EmbedAuthor -> EmbedAuthor -> Ordering # (<) :: EmbedAuthor -> EmbedAuthor -> Bool # (<=) :: EmbedAuthor -> EmbedAuthor -> Bool # (>) :: EmbedAuthor -> EmbedAuthor -> Bool # (>=) :: EmbedAuthor -> EmbedAuthor -> Bool # max :: EmbedAuthor -> EmbedAuthor -> EmbedAuthor # min :: EmbedAuthor -> EmbedAuthor -> EmbedAuthor # | |
Show EmbedAuthor Source # | |
Defined in Discord.Internal.Types.Embed Methods showsPrec :: Int -> EmbedAuthor -> ShowS # show :: EmbedAuthor -> String # showList :: [EmbedAuthor] -> ShowS # | |
ToJSON EmbedAuthor Source # | |
Defined in Discord.Internal.Types.Embed Methods toJSON :: EmbedAuthor -> Value # toEncoding :: EmbedAuthor -> Encoding # toJSONList :: [EmbedAuthor] -> Value # toEncodingList :: [EmbedAuthor] -> Encoding # | |
FromJSON EmbedAuthor Source # | |
Defined in Discord.Internal.Types.Embed |
data EmbedProvider Source #
Constructors
EmbedProvider | |
Fields |
Instances
data EmbedImage Source #
Constructors
EmbedImage | |
Fields |
Instances
Eq EmbedImage Source # | |
Defined in Discord.Internal.Types.Embed | |
Ord EmbedImage Source # | |
Defined in Discord.Internal.Types.Embed Methods compare :: EmbedImage -> EmbedImage -> Ordering # (<) :: EmbedImage -> EmbedImage -> Bool # (<=) :: EmbedImage -> EmbedImage -> Bool # (>) :: EmbedImage -> EmbedImage -> Bool # (>=) :: EmbedImage -> EmbedImage -> Bool # max :: EmbedImage -> EmbedImage -> EmbedImage # min :: EmbedImage -> EmbedImage -> EmbedImage # | |
Show EmbedImage Source # | |
Defined in Discord.Internal.Types.Embed Methods showsPrec :: Int -> EmbedImage -> ShowS # show :: EmbedImage -> String # showList :: [EmbedImage] -> ShowS # | |
ToJSON EmbedImage Source # | |
Defined in Discord.Internal.Types.Embed Methods toJSON :: EmbedImage -> Value # toEncoding :: EmbedImage -> Encoding # toJSONList :: [EmbedImage] -> Value # toEncodingList :: [EmbedImage] -> Encoding # | |
FromJSON EmbedImage Source # | |
Defined in Discord.Internal.Types.Embed |
data EmbedVideo Source #
Constructors
EmbedVideo | |
Fields |
Instances
Eq EmbedVideo Source # | |
Defined in Discord.Internal.Types.Embed | |
Ord EmbedVideo Source # | |
Defined in Discord.Internal.Types.Embed Methods compare :: EmbedVideo -> EmbedVideo -> Ordering # (<) :: EmbedVideo -> EmbedVideo -> Bool # (<=) :: EmbedVideo -> EmbedVideo -> Bool # (>) :: EmbedVideo -> EmbedVideo -> Bool # (>=) :: EmbedVideo -> EmbedVideo -> Bool # max :: EmbedVideo -> EmbedVideo -> EmbedVideo # min :: EmbedVideo -> EmbedVideo -> EmbedVideo # | |
Show EmbedVideo Source # | |
Defined in Discord.Internal.Types.Embed Methods showsPrec :: Int -> EmbedVideo -> ShowS # show :: EmbedVideo -> String # showList :: [EmbedVideo] -> ShowS # | |
ToJSON EmbedVideo Source # | |
Defined in Discord.Internal.Types.Embed Methods toJSON :: EmbedVideo -> Value # toEncoding :: EmbedVideo -> Encoding # toJSONList :: [EmbedVideo] -> Value # toEncodingList :: [EmbedVideo] -> Encoding # | |
FromJSON EmbedVideo Source # | |
Defined in Discord.Internal.Types.Embed |
data EmbedThumbnail Source #
Constructors
EmbedThumbnail | |
Instances
An embed attached to a message.
Constructors
Embed | |
Fields
|
data CreateEmbedImage Source #
Constructors
CreateEmbedImageUrl Text | |
CreateEmbedImageUpload ByteString |
Instances
Eq CreateEmbedImage Source # | |
Defined in Discord.Internal.Types.Embed Methods (==) :: CreateEmbedImage -> CreateEmbedImage -> Bool # (/=) :: CreateEmbedImage -> CreateEmbedImage -> Bool # | |
Ord CreateEmbedImage Source # | |
Defined in Discord.Internal.Types.Embed Methods compare :: CreateEmbedImage -> CreateEmbedImage -> Ordering # (<) :: CreateEmbedImage -> CreateEmbedImage -> Bool # (<=) :: CreateEmbedImage -> CreateEmbedImage -> Bool # (>) :: CreateEmbedImage -> CreateEmbedImage -> Bool # (>=) :: CreateEmbedImage -> CreateEmbedImage -> Bool # max :: CreateEmbedImage -> CreateEmbedImage -> CreateEmbedImage # min :: CreateEmbedImage -> CreateEmbedImage -> CreateEmbedImage # | |
Show CreateEmbedImage Source # | |
Defined in Discord.Internal.Types.Embed Methods showsPrec :: Int -> CreateEmbedImage -> ShowS # show :: CreateEmbedImage -> String # showList :: [CreateEmbedImage] -> ShowS # |
data CreateEmbed Source #
Constructors
Instances
Eq CreateEmbed Source # | |
Defined in Discord.Internal.Types.Embed | |
Ord CreateEmbed Source # | |
Defined in Discord.Internal.Types.Embed Methods compare :: CreateEmbed -> CreateEmbed -> Ordering # (<) :: CreateEmbed -> CreateEmbed -> Bool # (<=) :: CreateEmbed -> CreateEmbed -> Bool # (>) :: CreateEmbed -> CreateEmbed -> Bool # (>=) :: CreateEmbed -> CreateEmbed -> Bool # max :: CreateEmbed -> CreateEmbed -> CreateEmbed # min :: CreateEmbed -> CreateEmbed -> CreateEmbed # | |
Show CreateEmbed Source # | |
Defined in Discord.Internal.Types.Embed Methods showsPrec :: Int -> CreateEmbed -> ShowS # show :: CreateEmbed -> String # showList :: [CreateEmbed] -> ShowS # | |
Default CreateEmbed Source # | |
Defined in Discord.Internal.Types.Embed Methods def :: CreateEmbed # |
createEmbed :: CreateEmbed -> Embed Source #
data ConnectionObject Source #
Constructors
Instances
Constructors
Webhook | |
Fields |
Represents information about a user.
Constructors
User | |
Fields
|
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
Eq Attachment Source # | |
Defined in Discord.Internal.Types.Channel | |
Ord Attachment Source # | |
Defined in Discord.Internal.Types.Channel Methods compare :: Attachment -> Attachment -> Ordering # (<) :: Attachment -> Attachment -> Bool # (<=) :: Attachment -> Attachment -> Bool # (>) :: Attachment -> Attachment -> Bool # (>=) :: Attachment -> Attachment -> Bool # max :: Attachment -> Attachment -> Attachment # min :: Attachment -> Attachment -> Attachment # | |
Show Attachment Source # | |
Defined in Discord.Internal.Types.Channel Methods showsPrec :: Int -> Attachment -> ShowS # show :: Attachment -> String # showList :: [Attachment] -> ShowS # | |
FromJSON Attachment Source # | |
Defined in Discord.Internal.Types.Channel |
Represents an emoticon (emoji)
Constructors
Emoji | |
data MessageReaction Source #
Constructors
MessageReaction | |
Fields |
Instances
Represents information about a message in a Discord channel.
Constructors
Message | |
Fields
|
Permission overwrites for a channel.
Constructors
Overwrite | |
Fields
|
Instances
Eq Overwrite Source # | |
Ord Overwrite Source # | |
Show Overwrite Source # | |
ToJSON Overwrite Source # | |
Defined in Discord.Internal.Types.Channel | |
FromJSON Overwrite Source # | |
Guild channels represent an isolated set of users and messages in a Guild (Server)
Constructors
ChannelText | A text channel in a guild. |
Fields
| |
ChannelNews | |
Fields
| |
ChannelStorePage | |
Fields
| |
ChannelVoice | A voice channel in a guild. |
Fields
| |
ChannelDirectMessage | DM Channels represent a one-to-one conversation between two users, outside the scope of guilds |
Fields
| |
ChannelGroupDM | |
Fields
| |
ChannelGuildCategory | |
Fields
| |
ChannelStage | |
Fields
| |
ChannelUnknownType | |
Fields
|
channelIsInGuild :: Channel -> Bool Source #
If the channel is part of a guild (has a guild id field)
data GuildEmbed Source #
Represents an image to be used in third party sites to link to a discord channel
Constructors
GuildEmbed | |
Fields
|
Instances
Eq GuildEmbed Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord GuildEmbed Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: GuildEmbed -> GuildEmbed -> Ordering # (<) :: GuildEmbed -> GuildEmbed -> Bool # (<=) :: GuildEmbed -> GuildEmbed -> Bool # (>) :: GuildEmbed -> GuildEmbed -> Bool # (>=) :: GuildEmbed -> GuildEmbed -> Bool # max :: GuildEmbed -> GuildEmbed -> GuildEmbed # min :: GuildEmbed -> GuildEmbed -> GuildEmbed # | |
Show GuildEmbed Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> GuildEmbed -> ShowS # show :: GuildEmbed -> String # showList :: [GuildEmbed] -> ShowS # | |
ToJSON GuildEmbed Source # | |
Defined in Discord.Internal.Types.Guild Methods toJSON :: GuildEmbed -> Value # toEncoding :: GuildEmbed -> Encoding # toJSONList :: [GuildEmbed] -> Value # toEncodingList :: [GuildEmbed] -> Encoding # | |
FromJSON GuildEmbed Source # | |
Defined in Discord.Internal.Types.Guild |
data IntegrationAccount Source #
Represents a third party account link.
Constructors
IntegrationAccount | |
Fields
|
Instances
data Integration Source #
Represents the behavior of a third party account link.
Constructors
Integration | |
Fields
|
Instances
Eq Integration Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord Integration Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: Integration -> Integration -> Ordering # (<) :: Integration -> Integration -> Bool # (<=) :: Integration -> Integration -> Bool # (>) :: Integration -> Integration -> Bool # (>=) :: Integration -> Integration -> Bool # max :: Integration -> Integration -> Integration # min :: Integration -> Integration -> Integration # | |
Show Integration Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> Integration -> ShowS # show :: Integration -> String # showList :: [Integration] -> ShowS # | |
FromJSON Integration Source # | |
Defined in Discord.Internal.Types.Guild |
data InviteMeta Source #
Additional metadata about an invite.
Constructors
InviteMeta | |
Fields
|
Instances
Eq InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: InviteMeta -> InviteMeta -> Ordering # (<) :: InviteMeta -> InviteMeta -> Bool # (<=) :: InviteMeta -> InviteMeta -> Bool # (>) :: InviteMeta -> InviteMeta -> Bool # (>=) :: InviteMeta -> InviteMeta -> Bool # max :: InviteMeta -> InviteMeta -> InviteMeta # min :: InviteMeta -> InviteMeta -> InviteMeta # | |
Show InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> InviteMeta -> ShowS # show :: InviteMeta -> String # showList :: [InviteMeta] -> ShowS # | |
FromJSON InviteMeta Source # | |
Defined in Discord.Internal.Types.Guild |
data InviteWithMeta Source #
Invite code with additional metadata
Constructors
InviteWithMeta Invite InviteMeta |
Instances
FromJSON InviteWithMeta Source # | |
Defined in Discord.Internal.Types.Guild Methods parseJSON :: Value -> Parser InviteWithMeta # parseJSONList :: Value -> Parser [InviteWithMeta] # |
Represents a code to add a user to a guild
Constructors
Invite | |
Fields
|
Info about a Ban
Constructors
GuildBan | |
Fields
|
data VoiceRegion Source #
VoiceRegion is only refrenced in Guild endpoints, will be moved when voice support is added
Constructors
VoiceRegion | |
Fields
|
Instances
Eq VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: VoiceRegion -> VoiceRegion -> Ordering # (<) :: VoiceRegion -> VoiceRegion -> Bool # (<=) :: VoiceRegion -> VoiceRegion -> Bool # (>) :: VoiceRegion -> VoiceRegion -> Bool # (>=) :: VoiceRegion -> VoiceRegion -> Bool # max :: VoiceRegion -> VoiceRegion -> VoiceRegion # min :: VoiceRegion -> VoiceRegion -> VoiceRegion # | |
Show VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> VoiceRegion -> ShowS # show :: VoiceRegion -> String # showList :: [VoiceRegion] -> ShowS # | |
FromJSON VoiceRegion Source # | |
Defined in Discord.Internal.Types.Guild |
Roles represent a set of permissions attached to a group of users. Roles have unique names, colors, and can be "pinned" to the side bar, causing their members to be listed separately. Roles are unique per guild, and can have separate permission profiles for the global context (guild) and channel context.
Constructors
Role | |
Fields
|
data PartialGuild Source #
Constructors
PartialGuild | |
Fields |
Instances
Eq PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: PartialGuild -> PartialGuild -> Ordering # (<) :: PartialGuild -> PartialGuild -> Bool # (<=) :: PartialGuild -> PartialGuild -> Bool # (>) :: PartialGuild -> PartialGuild -> Bool # (>=) :: PartialGuild -> PartialGuild -> Bool # max :: PartialGuild -> PartialGuild -> PartialGuild # min :: PartialGuild -> PartialGuild -> PartialGuild # | |
Show PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> PartialGuild -> ShowS # show :: PartialGuild -> String # showList :: [PartialGuild] -> ShowS # | |
FromJSON PartialGuild Source # | |
Defined in Discord.Internal.Types.Guild |
Constructors
GuildInfo | |
Fields
|
Instances
Eq GuildInfo Source # | |
Ord GuildInfo Source # | |
Show GuildInfo Source # | |
FromJSON GuildInfo Source # | |
Guilds in Discord represent a collection of users and channels into an isolated Server
Constructors
Guild | |
Fields
|
data GuildMember Source #
Representation of a guild member.
Constructors
GuildMember | |
Fields
|
Instances
Eq GuildMember Source # | |
Defined in Discord.Internal.Types.Guild | |
Ord GuildMember Source # | |
Defined in Discord.Internal.Types.Guild Methods compare :: GuildMember -> GuildMember -> Ordering # (<) :: GuildMember -> GuildMember -> Bool # (<=) :: GuildMember -> GuildMember -> Bool # (>) :: GuildMember -> GuildMember -> Bool # (>=) :: GuildMember -> GuildMember -> Bool # max :: GuildMember -> GuildMember -> GuildMember # min :: GuildMember -> GuildMember -> GuildMember # | |
Show GuildMember Source # | |
Defined in Discord.Internal.Types.Guild Methods showsPrec :: Int -> GuildMember -> ShowS # show :: GuildMember -> String # showList :: [GuildMember] -> ShowS # | |
FromJSON GuildMember Source # | |
Defined in Discord.Internal.Types.Guild |
data TypingInfo Source #
Constructors
TypingInfo | |
Fields |
Instances
Eq TypingInfo Source # | |
Defined in Discord.Internal.Types.Events | |
Ord TypingInfo Source # | |
Defined in Discord.Internal.Types.Events Methods compare :: TypingInfo -> TypingInfo -> Ordering # (<) :: TypingInfo -> TypingInfo -> Bool # (<=) :: TypingInfo -> TypingInfo -> Bool # (>) :: TypingInfo -> TypingInfo -> Bool # (>=) :: TypingInfo -> TypingInfo -> Bool # max :: TypingInfo -> TypingInfo -> TypingInfo # min :: TypingInfo -> TypingInfo -> TypingInfo # | |
Show TypingInfo Source # | |
Defined in Discord.Internal.Types.Events Methods showsPrec :: Int -> TypingInfo -> ShowS # show :: TypingInfo -> String # showList :: [TypingInfo] -> ShowS # | |
FromJSON TypingInfo Source # | |
Defined in Discord.Internal.Types.Events |
data PresenceInfo Source #
Constructors
PresenceInfo | |
Fields
|
Instances
Eq PresenceInfo Source # | |
Defined in Discord.Internal.Types.Events | |
Ord PresenceInfo Source # | |
Defined in Discord.Internal.Types.Events Methods compare :: PresenceInfo -> PresenceInfo -> Ordering # (<) :: PresenceInfo -> PresenceInfo -> Bool # (<=) :: PresenceInfo -> PresenceInfo -> Bool # (>) :: PresenceInfo -> PresenceInfo -> Bool # (>=) :: PresenceInfo -> PresenceInfo -> Bool # max :: PresenceInfo -> PresenceInfo -> PresenceInfo # min :: PresenceInfo -> PresenceInfo -> PresenceInfo # | |
Show PresenceInfo Source # | |
Defined in Discord.Internal.Types.Events Methods showsPrec :: Int -> PresenceInfo -> ShowS # show :: PresenceInfo -> String # showList :: [PresenceInfo] -> ShowS # | |
FromJSON PresenceInfo Source # | |
Defined in Discord.Internal.Types.Events |
data ReactionRemoveInfo Source #
Constructors
ReactionRemoveInfo | |
Instances
data ReactionInfo Source #
Constructors
ReactionInfo | |
Fields |
Instances
Eq ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events | |
Ord ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events Methods compare :: ReactionInfo -> ReactionInfo -> Ordering # (<) :: ReactionInfo -> ReactionInfo -> Bool # (<=) :: ReactionInfo -> ReactionInfo -> Bool # (>) :: ReactionInfo -> ReactionInfo -> Bool # (>=) :: ReactionInfo -> ReactionInfo -> Bool # max :: ReactionInfo -> ReactionInfo -> ReactionInfo # min :: ReactionInfo -> ReactionInfo -> ReactionInfo # | |
Show ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events Methods showsPrec :: Int -> ReactionInfo -> ShowS # show :: ReactionInfo -> String # showList :: [ReactionInfo] -> ShowS # | |
FromJSON ReactionInfo Source # | |
Defined in Discord.Internal.Types.Events |
Represents possible events sent by discord. Detailed information can be found at https://discord.com/developers/docs/topics/gateway.
Constructors
Instances
data UpdateStatusType Source #
Constructors
UpdateStatusOnline | |
UpdateStatusDoNotDisturb | |
UpdateStatusAwayFromKeyboard | |
UpdateStatusInvisibleOffline | |
UpdateStatusOffline |
Instances
data ActivityType Source #
Instances
Eq ActivityType Source # | |
Defined in Discord.Internal.Types.Gateway | |
Ord ActivityType Source # | |
Defined in Discord.Internal.Types.Gateway Methods compare :: ActivityType -> ActivityType -> Ordering # (<) :: ActivityType -> ActivityType -> Bool # (<=) :: ActivityType -> ActivityType -> Bool # (>) :: ActivityType -> ActivityType -> Bool # (>=) :: ActivityType -> ActivityType -> Bool # max :: ActivityType -> ActivityType -> ActivityType # min :: ActivityType -> ActivityType -> ActivityType # | |
Show ActivityType Source # | |
Defined in Discord.Internal.Types.Gateway Methods showsPrec :: Int -> ActivityType -> ShowS # show :: ActivityType -> String # showList :: [ActivityType] -> ShowS # |
Constructors
Activity | |
Fields
|
data UpdateStatusOpts Source #
Constructors
UpdateStatusOpts | |
Instances
Eq UpdateStatusOpts Source # | |
Defined in Discord.Internal.Types.Gateway Methods (==) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # (/=) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # | |
Ord UpdateStatusOpts Source # | |
Defined in Discord.Internal.Types.Gateway Methods compare :: UpdateStatusOpts -> UpdateStatusOpts -> Ordering # (<) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # (<=) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # (>) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # (>=) :: UpdateStatusOpts -> UpdateStatusOpts -> Bool # max :: UpdateStatusOpts -> UpdateStatusOpts -> UpdateStatusOpts # min :: UpdateStatusOpts -> UpdateStatusOpts -> UpdateStatusOpts # | |
Show UpdateStatusOpts Source # | |
Defined in Discord.Internal.Types.Gateway Methods showsPrec :: Int -> UpdateStatusOpts -> ShowS # show :: UpdateStatusOpts -> String # showList :: [UpdateStatusOpts] -> ShowS # |
data UpdateStatusVoiceOpts Source #
Constructors
UpdateStatusVoiceOpts | |
Instances
data RequestGuildMembersOpts Source #
Constructors
RequestGuildMembersOpts | |
Instances
data GatewaySendable Source #
Sent to gateway by a user
Constructors
RequestGuildMembers RequestGuildMembersOpts | |
UpdateStatus UpdateStatusOpts | |
UpdateStatusVoice UpdateStatusVoiceOpts |
Instances
data GatewayIntent Source #
Constructors
Instances
Eq GatewayIntent Source # | |
Defined in Discord.Internal.Types.Gateway Methods (==) :: GatewayIntent -> GatewayIntent -> Bool # (/=) :: GatewayIntent -> GatewayIntent -> Bool # | |
Ord GatewayIntent Source # | |
Defined in Discord.Internal.Types.Gateway Methods compare :: GatewayIntent -> GatewayIntent -> Ordering # (<) :: GatewayIntent -> GatewayIntent -> Bool # (<=) :: GatewayIntent -> GatewayIntent -> Bool # (>) :: GatewayIntent -> GatewayIntent -> Bool # (>=) :: GatewayIntent -> GatewayIntent -> Bool # max :: GatewayIntent -> GatewayIntent -> GatewayIntent # min :: GatewayIntent -> GatewayIntent -> GatewayIntent # | |
Show GatewayIntent Source # | |
Defined in Discord.Internal.Types.Gateway Methods showsPrec :: Int -> GatewayIntent -> ShowS # show :: GatewayIntent -> String # showList :: [GatewayIntent] -> ShowS # | |
Default GatewayIntent Source # | |
Defined in Discord.Internal.Types.Gateway Methods def :: GatewayIntent # |
pattern Heartbeat :: Integer -> GatewaySendableInternal Source #
pattern Identify :: Auth -> GatewayIntent -> (Int, Int) -> GatewaySendableInternal Source #
pattern HeartbeatAck :: GatewayReceivable Source #
pattern Hello :: Integer -> GatewayReceivable Source #
pattern InvalidSession :: Bool -> GatewayReceivable Source #
pattern Reconnect :: GatewayReceivable Source #
pattern HeartbeatRequest :: Integer -> GatewayReceivable Source #
pattern ParseError :: Text -> GatewayReceivable Source #
activityTypeId :: ActivityType -> Int Source #
statusString :: UpdateStatusType -> Text Source #