discord-haskell-1.15.3: Write bots for Discord in Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Discord.Types

Description

Re-export user-visible types

Synopsis

Documentation

data UTCTime #

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

Instances details
FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Data UTCTime 
Instance details

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 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

FromFormKey UTCTime 
Instance details

Defined in Web.Internal.FormUrlEncoded

ToFormKey UTCTime 
Instance details

Defined in Web.Internal.FormUrlEncoded

Methods

toFormKey :: UTCTime -> Text #

FromHttpApiData UTCTime
>>> parseUrlPiece "2015-10-03T00:14:24Z" :: Either Text UTCTime
Right 2015-10-03 00:14:24 UTC
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData UTCTime
>>> toUrlPiece $ UTCTime (fromGregorian 2015 10 03) 864.5
"2015-10-03T00:14:24.5Z"
Instance details

Defined in Web.Internal.HttpApiData

class ToJSON a where #

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 write Text literals.
{-# LANGUAGE OverloadedStrings #-}

data Coord = Coord { x :: Double, y :: Double }

instance ToJSON Coord where
  toJSON (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 Generic clause to your datatype and declare a 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 } deriving Generic

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

or more conveniently using the DerivingVia extension

deriving via Generically Coord instance ToJSON Coord

If on the other hand you wish to customize the generic decoding, you have to implement both methods:

customOptions = defaultOptions
                { fieldLabelModifier = map toUpper
                }

instance ToJSON Coord where
    toJSON     = genericToJSON customOptions
    toEncoding = genericToEncoding customOptions

Previous versions of this library only had the toJSON method. Adding toEncoding had two reasons:

  1. toEncoding is more efficient for the common case that the output of toJSON is directly serialized to a ByteString. Further, expressing either method in terms of the other would be non-optimal.
  2. 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 of toEncoding use toJSON. This produces correct results, but since it performs an intermediate conversion to a Value, it will be less efficient than directly emitting an Encoding. (this also means that specifying nothing more than instance ToJSON Coord would be sufficient as a generically decoding instance, but there probably exists no good reason to not specify toEncoding in new instances.)

Minimal complete definition

Nothing

Methods

toJSON :: a -> Value #

Convert a Haskell value to a JSON-friendly intermediate type.

Instances

Instances details
ToJSON Key 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DotNetTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Value 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Number 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Version 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Void 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int16 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int8 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word16 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON IntSet 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON ChannelInviteOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Channel

ToJSON ListThreads Source # 
Instance details

Defined in Discord.Internal.Rest.Channel

ToJSON ModifyChannelOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Channel

ToJSON StartThreadNoMessageOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Channel

ToJSON StartThreadOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Channel

ToJSON CreateGuildStickerOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Emoji

ToJSON EditGuildStickerOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Emoji

ToJSON ModifyGuildEmojiOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Emoji

ToJSON AddGuildMemberOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Guild

ToJSON CreateGuildBanOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Guild

ToJSON CreateGuildIntegrationOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Guild

ToJSON ModifyGuildIntegrationOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Guild

ToJSON ModifyGuildMemberOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Guild

ToJSON ModifyGuildOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Guild

ToJSON ModifyGuildRoleOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Guild

ToJSON CreateWebhookOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Webhook

ToJSON ExecuteWebhookWithTokenOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Webhook

ToJSON ModifyWebhookOpts Source # 
Instance details

Defined in Discord.Internal.Rest.Webhook

ToJSON ApplicationCommandChannelType Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON ApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON CreateApplicationCommand Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON EditApplicationCommand Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON GuildApplicationCommandPermissions Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON OptionSubcommand Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON OptionSubcommandOrGroup Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON OptionValue Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON Options Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON Attachment Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON Channel Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON Message Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON Overwrite Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON ThreadMember Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON ThreadMetadata Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON DiscordColor Source # 
Instance details

Defined in Discord.Internal.Types.Color

ToJSON ActionRow Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON Button Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON ButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON SelectMenu Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON TextInput Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedAuthor Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedField Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedFooter Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedImage Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedVideo Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

ToJSON StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

ToJSON StickerItem Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

ToJSON GatewaySendable Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

ToJSON GatewaySendableInternal Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

ToJSON GuildWidget Source # 
Instance details

Defined in Discord.Internal.Types.Guild

ToJSON InteractionResponse Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

ToJSON InteractionResponseAutocomplete Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

ToJSON InteractionResponseMessage Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

ToJSON InteractionResponseMessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

ToJSON InteractionResponseModalData Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

ToJSON ResolvedData Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

ToJSON Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON CreateScheduledEventData Source # 
Instance details

Defined in Discord.Internal.Types.ScheduledEvents

ToJSON CreateScheduledEventImage Source # 
Instance details

Defined in Discord.Internal.Types.ScheduledEvents

ToJSON ModifyScheduledEventData Source # 
Instance details

Defined in Discord.Internal.Types.ScheduledEvents

ToJSON ScheduledEvent Source # 
Instance details

Defined in Discord.Internal.Types.ScheduledEvents

ToJSON ScheduledEventPrivacyLevel Source # 
Instance details

Defined in Discord.Internal.Types.ScheduledEvents

ToJSON ScheduledEventStatus Source # 
Instance details

Defined in Discord.Internal.Types.ScheduledEvents

ToJSON ScheduledEventType Source # 
Instance details

Defined in Discord.Internal.Types.ScheduledEvents

ToJSON GuildMember Source # 
Instance details

Defined in Discord.Internal.Types.User

ToJSON User Source # 
Instance details

Defined in Discord.Internal.Types.User

ToJSON Ordering 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Scientific 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON ShortText

Since: aeson-2.0.2.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CalendarDiffDays 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Day 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Month 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Quarter 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON QuarterOfYear 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DayOfWeek 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON SystemTime

Encoded as number

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CalendarDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON LocalTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON TimeOfDay 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON ZonedTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON UUID 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON () 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: () -> Value #

toEncoding :: () -> Encoding #

toJSONList :: [()] -> Value #

toEncodingList :: [()] -> Encoding #

ToJSON Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Char 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Double 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Float 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON v => ToJSON (KeyMap v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Identity a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Max a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Max a -> Value #

toEncoding :: Max a -> Encoding #

toJSONList :: [Max a] -> Value #

toEncodingList :: [Max a] -> Encoding #

ToJSON a => ToJSON (Min a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Min a -> Value #

toEncoding :: Min a -> Encoding #

toJSONList :: [Min a] -> Value #

toEncodingList :: [Min a] -> Encoding #

ToJSON a => ToJSON (WrappedMonoid a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Dual a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON a, Integral a) => ToJSON (Ratio a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (IntMap a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Seq a -> Value #

toEncoding :: Seq a -> Encoding #

toJSONList :: [Seq a] -> Value #

toEncodingList :: [Seq a] -> Encoding #

ToJSON a => ToJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

ToJSON v => ToJSON (Tree v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON1 f => ToJSON (Fix f)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Fix f -> Value #

toEncoding :: Fix f -> Encoding #

toJSONList :: [Fix f] -> Value #

toEncodingList :: [Fix f] -> Encoding #

(ToJSON1 f, Functor f) => ToJSON (Mu f)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Mu f -> Value #

toEncoding :: Mu f -> Encoding #

toJSONList :: [Mu f] -> Value #

toEncodingList :: [Mu f] -> Encoding #

(ToJSON1 f, Functor f) => ToJSON (Nu f)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Nu f -> Value #

toEncoding :: Nu f -> Encoding #

toJSONList :: [Nu f] -> Value #

toEncodingList :: [Nu f] -> Encoding #

ToJSON a => ToJSON (Choice a) Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

ToJSON (Base64Image a) Source #

The ToJSON instance for Base64Image creates a string representation of the image's base-64 data, suited for using as JSON values.

The format is: data:%MIME%;base64,%DATA%.

Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON (DiscordToken a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON a => ToJSON (DNonEmpty a)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Generic a, GToJSON' Value Zero (Rep a), GToJSON' Encoding Zero (Rep a)) => ToJSON (Generically a)

Since: aeson-2.1.0.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Array a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Prim a, ToJSON a) => ToJSON (PrimArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (SmallArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Maybe a)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (HashSet a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Prim a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Storable a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (a)

Since: aeson-2.0.2.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a) -> Value #

toEncoding :: (a) -> Encoding #

toJSONList :: [(a)] -> Value #

toEncodingList :: [(a)] -> Encoding #

ToJSON a => ToJSON [a] 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: [a] -> Value #

toEncoding :: [a] -> Encoding #

toJSONList :: [[a]] -> Value #

toEncodingList :: [[a]] -> Encoding #

(ToJSON a, ToJSON b) => ToJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

HasResolution a => ToJSON (Fixed a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON v, ToJSONKey k) => ToJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Map k v -> Value #

toEncoding :: Map k v -> Encoding #

toJSONList :: [Map k v] -> Value #

toEncodingList :: [Map k v] -> Encoding #

(ToJSON a, ToJSON b) => ToJSON (Either a b)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

(ToJSON a, ToJSON b) => ToJSON (These a b)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These a b -> Value #

toEncoding :: These a b -> Encoding #

toJSONList :: [These a b] -> Value #

toEncodingList :: [These a b] -> Encoding #

(ToJSON a, ToJSON b) => ToJSON (Pair a b)

Since: aeson-1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Pair a b -> Value #

toEncoding :: Pair a b -> Encoding #

toJSONList :: [Pair a b] -> Value #

toEncodingList :: [Pair a b] -> Encoding #

(ToJSON a, ToJSON b) => ToJSON (These a b)

Since: aeson-1.5.1.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These a b -> Value #

toEncoding :: These a b -> Encoding #

toJSONList :: [These a b] -> Value #

toEncodingList :: [These a b] -> Encoding #

(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON a, ToJSON b) => ToJSON (a, b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b) -> Value #

toEncoding :: (a, b) -> Encoding #

toJSONList :: [(a, b)] -> Value #

toEncodingList :: [(a, b)] -> Encoding #

ToJSON a => ToJSON (Const a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Const a b -> Value #

toEncoding :: Const a b -> Encoding #

toJSONList :: [Const a b] -> Value #

toEncodingList :: [Const a b] -> Encoding #

ToJSON b => ToJSON (Tagged a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Tagged a b -> Value #

toEncoding :: Tagged a b -> Encoding #

toJSONList :: [Tagged a b] -> Value #

toEncodingList :: [Tagged a b] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (These1 f g a)

Since: aeson-1.5.1.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These1 f g a -> Value #

toEncoding :: These1 f g a -> Encoding #

toJSONList :: [These1 f g a] -> Value #

toEncodingList :: [These1 f g a] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c) -> Value #

toEncoding :: (a, b, c) -> Encoding #

toJSONList :: [(a, b, c)] -> Value #

toEncodingList :: [(a, b, c)] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Product f g a -> Value #

toEncoding :: Product f g a -> Encoding #

toJSONList :: [Product f g a] -> Value #

toEncodingList :: [Product f g a] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Sum f g a -> Value #

toEncoding :: Sum f g a -> Encoding #

toJSONList :: [Sum f g a] -> Value #

toEncodingList :: [Sum f g a] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d) -> Value #

toEncoding :: (a, b, c, d) -> Encoding #

toJSONList :: [(a, b, c, d)] -> Value #

toEncodingList :: [(a, b, c, d)] -> Encoding #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Compose f g a -> Value #

toEncoding :: Compose f g a -> Encoding #

toJSONList :: [Compose f g a] -> Value #

toEncodingList :: [Compose f g a] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e) -> Value #

toEncoding :: (a, b, c, d, e) -> Encoding #

toJSONList :: [(a, b, c, d, e)] -> Value #

toEncodingList :: [(a, b, c, d, e)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f) -> Value #

toEncoding :: (a, b, c, d, e, f) -> Encoding #

toJSONList :: [(a, b, c, d, e, f)] -> Value #

toEncodingList :: [(a, b, c, d, e, f)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g) -> Value #

toEncoding :: (a, b, c, d, e, f, g) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Encoding #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Encoding #

type Object = KeyMap Value #

A JSON "object" (key/value map).

type Shard = (Int, Int) Source #

type WebhookToken = DiscordToken WebhookIdType Source #

type InteractionToken = DiscordToken InteractionIdType Source #

newtype DiscordToken a Source #

Constructors

DiscordToken 

Fields

Instances

Instances details
FromJSON (DiscordToken a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON (DiscordToken a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Read (DiscordToken a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Show (DiscordToken a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Eq (DiscordToken a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Ord (DiscordToken a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToHttpApiData (DiscordToken a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

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 ParentId = DiscordId ParentIdType Source #

type WebhookId = DiscordId WebhookIdType Source #

type IntegrationId = DiscordId IntegrationIdType Source #

type RoleId = DiscordId RoleIdType Source #

type UserId = DiscordId UserIdType Source #

type StickerId = DiscordId StickerIdType Source #

type EmojiId = DiscordId EmojiIdType Source #

type AttachmentId = DiscordId AttachmentIdType Source #

type MessageId = DiscordId MessageIdType Source #

type GuildId = DiscordId GuildIdType Source #

type StageId = DiscordId StageIdType Source #

type ChannelId = DiscordId ChannelIdType Source #

newtype DiscordId a Source #

Constructors

DiscordId 

Fields

Instances

Instances details
FromJSON (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Bits (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Enum (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Num (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Read (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Integral (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Real (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Show (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Eq (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

(==) :: DiscordId a -> DiscordId a -> Bool #

(/=) :: DiscordId a -> DiscordId a -> Bool #

Ord (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToHttpApiData (DiscordId a) Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

newtype Snowflake Source #

A unique integer identifier. Can be used to calculate the creation date of an entity.

Constructors

Snowflake 

Fields

Instances

Instances details
FromJSON Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Bits Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Enum Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Num Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Read Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Integral Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Real Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Show Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Eq Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Ord Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToHttpApiData Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

newtype Auth Source #

Authorization token for the Discord API

Constructors

Auth Text 

Instances

Instances details
Read Auth Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Show Auth Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

showsPrec :: Int -> Auth -> ShowS #

show :: Auth -> String #

showList :: [Auth] -> ShowS #

Eq Auth Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

(==) :: Auth -> Auth -> Bool #

(/=) :: Auth -> Auth -> Bool #

Ord Auth Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

compare :: Auth -> Auth -> Ordering #

(<) :: Auth -> Auth -> Bool #

(<=) :: Auth -> Auth -> Bool #

(>) :: Auth -> Auth -> Bool #

(>=) :: Auth -> Auth -> Bool #

max :: Auth -> Auth -> Auth #

min :: Auth -> Auth -> Auth #

authToken :: Auth -> Text Source #

Get the raw token formatted for use with the websocket gateway

snowflakeCreationDate :: Snowflake -> UTCTime Source #

Gets a creation date from a snowflake.

epochTime :: UTCTime Source #

Default timestamp

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

Instances

Instances details
FromJSON DiscordColor Source # 
Instance details

Defined in Discord.Internal.Types.Color

ToJSON DiscordColor Source # 
Instance details

Defined in Discord.Internal.Types.Color

Data DiscordColor Source # 
Instance details

Defined in Discord.Internal.Types.Color

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DiscordColor -> c DiscordColor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DiscordColor #

toConstr :: DiscordColor -> Constr #

dataTypeOf :: DiscordColor -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DiscordColor) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DiscordColor) #

gmapT :: (forall b. Data b => b -> b) -> DiscordColor -> DiscordColor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DiscordColor -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DiscordColor -> r #

gmapQ :: (forall d. Data d => d -> u) -> DiscordColor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DiscordColor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DiscordColor -> m DiscordColor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DiscordColor -> m DiscordColor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DiscordColor -> m DiscordColor #

Read DiscordColor Source # 
Instance details

Defined in Discord.Internal.Types.Color

Show DiscordColor Source # 
Instance details

Defined in Discord.Internal.Types.Color

InternalDiscordEnum DiscordColor Source # 
Instance details

Defined in Discord.Internal.Types.Color

Eq DiscordColor Source # 
Instance details

Defined in Discord.Internal.Types.Color

Ord DiscordColor Source # 
Instance details

Defined in Discord.Internal.Types.Color

hexToDiscordColor :: String -> DiscordColor Source #

hexToDiscordColor converts a potential hex string into a DiscordColor, evaluating to Default if it fails.

data EmbedField Source #

data EmbedFooter Source #

data EmbedAuthor Source #

data EmbedProvider Source #

Instances

Instances details
FromJSON EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Read EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Show EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Eq EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Ord EmbedProvider Source # 
Instance details

Defined in Discord.Internal.Types.Embed

data EmbedImage Source #

data EmbedVideo Source #

data EmbedThumbnail Source #

Instances

Instances details
FromJSON EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Read EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Show EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Eq EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Ord EmbedThumbnail Source # 
Instance details

Defined in Discord.Internal.Types.Embed

data Embed Source #

An embed attached to a message.

Constructors

Embed 

Fields

Instances

Instances details
FromJSON Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

ToJSON Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Read Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Show Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Methods

showsPrec :: Int -> Embed -> ShowS #

show :: Embed -> String #

showList :: [Embed] -> ShowS #

Eq Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Methods

(==) :: Embed -> Embed -> Bool #

(/=) :: Embed -> Embed -> Bool #

Ord Embed Source # 
Instance details

Defined in Discord.Internal.Types.Embed

Methods

compare :: Embed -> Embed -> Ordering #

(<) :: Embed -> Embed -> Bool #

(<=) :: Embed -> Embed -> Bool #

(>) :: Embed -> Embed -> Bool #

(>=) :: Embed -> Embed -> Bool #

max :: Embed -> Embed -> Embed #

min :: Embed -> Embed -> Embed #

data CreateEmbed Source #

data GuildMember Source #

Representation of a guild member.

Constructors

GuildMember 

Fields

data ConnectionObject Source #

The connection object that the user has attached.

Constructors

ConnectionObject 

Fields

data User Source #

Represents information about a user.

Constructors

User 

Fields

Instances

Instances details
FromJSON User Source # 
Instance details

Defined in Discord.Internal.Types.User

ToJSON User Source # 
Instance details

Defined in Discord.Internal.Types.User

Read User Source # 
Instance details

Defined in Discord.Internal.Types.User

Show User Source # 
Instance details

Defined in Discord.Internal.Types.User

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Eq User Source # 
Instance details

Defined in Discord.Internal.Types.User

Methods

(==) :: User -> User -> Bool #

(/=) :: User -> User -> Bool #

Ord User Source # 
Instance details

Defined in Discord.Internal.Types.User

Methods

compare :: User -> User -> Ordering #

(<) :: User -> User -> Bool #

(<=) :: User -> User -> Bool #

(>) :: User -> User -> Bool #

(>=) :: User -> User -> Bool #

max :: User -> User -> User #

min :: User -> User -> User #

data StickerFormatType Source #

The format of a sticker

Instances

Instances details
FromJSON StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

ToJSON StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Data StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StickerFormatType -> c StickerFormatType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StickerFormatType #

toConstr :: StickerFormatType -> Constr #

dataTypeOf :: StickerFormatType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StickerFormatType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StickerFormatType) #

gmapT :: (forall b. Data b => b -> b) -> StickerFormatType -> StickerFormatType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StickerFormatType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StickerFormatType -> r #

gmapQ :: (forall d. Data d => d -> u) -> StickerFormatType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StickerFormatType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StickerFormatType -> m StickerFormatType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StickerFormatType -> m StickerFormatType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StickerFormatType -> m StickerFormatType #

Read StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Show StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

InternalDiscordEnum StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Eq StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Ord StickerFormatType Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

data StickerItem Source #

A simplified sticker object.

Constructors

StickerItem 

Fields

data Sticker Source #

A full sticker object

Constructors

Sticker 

Fields

data StickerPack Source #

Represents a pack of standard stickers.

Constructors

StickerPack 

Fields

data Emoji Source #

Represents an emoticon (emoji)

Constructors

Emoji 

Fields

Instances

Instances details
FromJSON Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

ToJSON Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Read Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Show Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Methods

showsPrec :: Int -> Emoji -> ShowS #

show :: Emoji -> String #

showList :: [Emoji] -> ShowS #

Eq Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Methods

(==) :: Emoji -> Emoji -> Bool #

(/=) :: Emoji -> Emoji -> Bool #

Ord Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Emoji

Methods

compare :: Emoji -> Emoji -> Ordering #

(<) :: Emoji -> Emoji -> Bool #

(<=) :: Emoji -> Emoji -> Bool #

(>) :: Emoji -> Emoji -> Bool #

(>=) :: Emoji -> Emoji -> Bool #

max :: Emoji -> Emoji -> Emoji #

min :: Emoji -> Emoji -> Emoji #

mkEmoji :: Text -> Emoji Source #

Make an emoji with only a name

data TextInput Source #

Constructors

TextInput 

Fields

data SelectOption Source #

A single option in a select menu.

Constructors

SelectOption 

Fields

Instances

Instances details
FromJSON SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

Read SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

Eq SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

Ord SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

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

data ButtonStyle Source #

Buttton colors.

Constructors

ButtonStylePrimary

Blurple button

ButtonStyleSecondary

Grey button

ButtonStyleSuccess

Green button

ButtonStyleDanger

Red button

Instances

Instances details
FromJSON ButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON ButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Read ButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show ButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Eq ButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Ord ButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

data Button Source #

Component type for a button, split into URL button and not URL button.

Don't directly send button components - they need to be within an action row.

Constructors

Button 

Fields

ButtonUrl 

Fields

data ActionRow Source #

Container for other message Components

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.

mkTextInput :: Text -> Text -> TextInput Source #

Create a text input from an id and a label

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

Instances details
FromJSON MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

newtype MessageFlags Source #

Constructors

MessageFlags [MessageFlag] 

Instances

Instances details
FromJSON MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageFlags Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data MessageFlag Source #

Types of flags to attach to the message.

Instances

Instances details
Data MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageFlag -> c MessageFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageFlag #

toConstr :: MessageFlag -> Constr #

dataTypeOf :: MessageFlag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MessageFlag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageFlag) #

gmapT :: (forall b. Data b => b -> b) -> MessageFlag -> MessageFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageFlag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageFlag -> m MessageFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageFlag -> m MessageFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageFlag -> m MessageFlag #

Read MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

InternalDiscordEnum MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageFlag Source # 
Instance details

Defined in Discord.Internal.Types.Channel

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

Instances details
FromJSON MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Data MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageActivityType -> c MessageActivityType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageActivityType #

toConstr :: MessageActivityType -> Constr #

dataTypeOf :: MessageActivityType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MessageActivityType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageActivityType) #

gmapT :: (forall b. Data b => b -> b) -> MessageActivityType -> MessageActivityType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageActivityType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageActivityType -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageActivityType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageActivityType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageActivityType -> m MessageActivityType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageActivityType -> m MessageActivityType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageActivityType -> m MessageActivityType #

Read MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

InternalDiscordEnum MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data MessageActivity Source #

Instances

Instances details
FromJSON MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Data MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageActivity -> c MessageActivity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageActivity #

toConstr :: MessageActivity -> Constr #

dataTypeOf :: MessageActivity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MessageActivity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageActivity) #

gmapT :: (forall b. Data b => b -> b) -> MessageActivity -> MessageActivity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageActivity -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageActivity -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageActivity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageActivity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageActivity -> m MessageActivity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageActivity -> m MessageActivity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageActivity -> m MessageActivity #

Read MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageActivity Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data MessageType Source #

Instances

Instances details
FromJSON MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Data MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MessageType -> c MessageType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MessageType #

toConstr :: MessageType -> Constr #

dataTypeOf :: MessageType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MessageType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MessageType) #

gmapT :: (forall b. Data b => b -> b) -> MessageType -> MessageType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MessageType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MessageType -> r #

gmapQ :: (forall d. Data d => d -> u) -> MessageType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MessageType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MessageType -> m MessageType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageType -> m MessageType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MessageType -> m MessageType #

Read MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

InternalDiscordEnum MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageType Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data MessageReference Source #

Represents a Message Reference

Constructors

MessageReference 

Fields

Instances

Instances details
FromJSON MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Default MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageReference Source # 
Instance details

Defined in Discord.Internal.Types.Channel

newtype Nonce Source #

Constructors

Nonce Text 

Instances

Instances details
FromJSON Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

showsPrec :: Int -> Nonce -> ShowS #

show :: Nonce -> String #

showList :: [Nonce] -> ShowS #

Eq Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

(==) :: Nonce -> Nonce -> Bool #

(/=) :: Nonce -> Nonce -> Bool #

Ord Nonce Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Methods

compare :: Nonce -> Nonce -> Ordering #

(<) :: Nonce -> Nonce -> Bool #

(<=) :: Nonce -> Nonce -> Bool #

(>) :: Nonce -> Nonce -> Bool #

(>=) :: Nonce -> Nonce -> Bool #

max :: Nonce -> Nonce -> Nonce #

min :: Nonce -> Nonce -> Nonce #

data Attachment Source #

Represents an attached to a message file.

Constructors

Attachment 

Fields

data MessageReaction Source #

A reaction to a message

Instances

Instances details
FromJSON MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord MessageReaction Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data AllowedMentions Source #

Data constructor for a part of MessageDetailedOpts.

Constructors

AllowedMentions 

Fields

Instances

Instances details
ToJSON AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Default AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord AllowedMentions Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data Message Source #

Represents information about a message in a Discord channel.

Constructors

Message 

Fields

data ThreadMembersUpdateFields Source #

Instances

Instances details
FromJSON ThreadMembersUpdateFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read ThreadMembersUpdateFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show ThreadMembersUpdateFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq ThreadMembersUpdateFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord ThreadMembersUpdateFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data ThreadListSyncFields Source #

Instances

Instances details
FromJSON ThreadListSyncFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read ThreadListSyncFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show ThreadListSyncFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq ThreadListSyncFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord ThreadListSyncFields Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data ThreadMember Source #

A user in a thread

Constructors

ThreadMember 

Fields

Instances

Instances details
FromJSON ThreadMember Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON ThreadMember Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read ThreadMember Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show ThreadMember Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq ThreadMember Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord ThreadMember Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data ThreadMetadata Source #

Metadata for threads.

Constructors

ThreadMetadata 

Fields

Instances

Instances details
FromJSON ThreadMetadata Source # 
Instance details

Defined in Discord.Internal.Types.Channel

ToJSON ThreadMetadata Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Read ThreadMetadata Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Show ThreadMetadata Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Eq ThreadMetadata Source # 
Instance details

Defined in Discord.Internal.Types.Channel

Ord ThreadMetadata Source # 
Instance details

Defined in Discord.Internal.Types.Channel

data Overwrite Source #

Permission overwrites for a channel.

Constructors

Overwrite 

Fields

data Channel 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 ChannelDirectMessage but for more people

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

  • channelId :: ChannelId

    The id of the channel (Will be equal to the guild if it's the "general" channel).

  • channelJSON :: Text

    The library couldn't parse the channel type, here is the raw JSON

channelIsInGuild :: Channel -> Bool Source #

If the channel is part of a guild (has a guild id field)

data GuildWidget Source #

Represents an image to be used in third party sites to link to a discord channel

Constructors

GuildWidget 

Fields

data IntegrationAccount Source #

Represents a third party account link.

Constructors

IntegrationAccount 

Fields

data Integration Source #

Represents the behavior of a third party account link.

Constructors

Integration 

Fields

data InviteMeta Source #

Additional metadata about an invite.

Constructors

InviteMeta 

Fields

data InviteWithMeta Source #

Invite code with additional metadata

Instances

Instances details
FromJSON InviteWithMeta Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data Invite Source #

Represents a code to add a user to a guild

Constructors

Invite 

Fields

Instances

Instances details
FromJSON Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Read Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Eq Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

(==) :: Invite -> Invite -> Bool #

(/=) :: Invite -> Invite -> Bool #

Ord Invite Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data VoiceRegion Source #

VoiceRegion is only refrenced in Guild endpoints, will be moved when voice support is added

Constructors

VoiceRegion 

Fields

data Role Source #

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

Instances

Instances details
FromJSON Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Read Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Eq Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

Ord Role Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

(>=) :: Role -> Role -> Bool #

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

data ActivityType Source #

Instances

Instances details
FromJSON ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Data ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ActivityType -> c ActivityType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ActivityType #

toConstr :: ActivityType -> Constr #

dataTypeOf :: ActivityType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ActivityType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ActivityType) #

gmapT :: (forall b. Data b => b -> b) -> ActivityType -> ActivityType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ActivityType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ActivityType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ActivityType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ActivityType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ActivityType -> m ActivityType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivityType -> m ActivityType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ActivityType -> m ActivityType #

Read ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

InternalDiscordEnum ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Eq ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Ord ActivityType Source # 
Instance details

Defined in Discord.Internal.Types.Guild

data ActivityTimestamps Source #

Constructors

ActivityTimestamps 

Fields

data Activity Source #

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

newtype GuildUnavailable Source #

Constructors

GuildUnavailable 

data Guild Source #

Guilds in Discord represent a collection of users and channels into an isolated Server

https://discord.com/developers/docs/resources/guild#guild-object

Constructors

Guild 

Fields

Instances

Instances details
FromJSON Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Read Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Show Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

showsPrec :: Int -> Guild -> ShowS #

show :: Guild -> String #

showList :: [Guild] -> ShowS #

Eq Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

(==) :: Guild -> Guild -> Bool #

(/=) :: Guild -> Guild -> Bool #

Ord Guild Source # 
Instance details

Defined in Discord.Internal.Types.Guild

Methods

compare :: Guild -> Guild -> Ordering #

(<) :: Guild -> Guild -> Bool #

(<=) :: Guild -> Guild -> Bool #

(>) :: Guild -> Guild -> Bool #

(>=) :: Guild -> Guild -> Bool #

max :: Guild -> Guild -> Guild #

min :: Guild -> Guild -> Guild #

data ReactionRemoveInfo Source #

Structure containing information about a reaction that has been removed

data ReactionInfo Source #

Structure containing information about a reaction

Constructors

ReactionInfo 

Fields

data Event Source #

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 Resume gateway command

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

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 Request Guild Members gateway command

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

Instances details
Show Event Source # 
Instance details

Defined in Discord.Internal.Types.Events

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Eq Event Source # 
Instance details

Defined in Discord.Internal.Types.Events

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

reparse :: (ToJSON a, FromJSON b) => a -> Parser b Source #

Convert ToJSON value to FromJSON value

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

Instances

Instances details
Enum UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

Read UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

Show UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

Eq UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

Ord UpdateStatusType Source # 
Instance details

Defined in Discord.Internal.Types.Gateway

data UpdateStatusVoiceOpts Source #

Options for UpdateStatusVoice

data RequestGuildMembersOpts Source #

data GatewaySendable Source #

Sent to gateway by a user

data GatewayIntent Source #

Gateway intents to subrscribe to

Details of which intent englobs what data is avalilable at the official Discord documentation

statusString :: UpdateStatusType -> Text Source #

Converts an UpdateStatusType to a textual representation

userFacingEvent :: EventInternalParse -> Event Source #

Converts an internal event to its user facing counterpart