discord-haskell-1.11.0: Write bots for Discord in Haskell
Safe HaskellNone
LanguageHaskell2010

Discord.Internal.Types.Prelude

Description

Provides base types and utility functions needed for modules in Discord.Internal.Types

Synopsis

Documentation

data Auth Source #

Authorization token for the Discord API

Constructors

Auth Text 

Instances

Instances details
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 #

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 #

authToken :: Auth -> Text Source #

Get the raw token formatted for use with the websocket gateway

newtype Snowflake Source #

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

Constructors

Snowflake Word64 

Instances

Instances details
Enum Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Eq Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Integral Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Num Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Ord Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Read 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

ToJSON Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

FromJSON Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Bits Snowflake Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

type Shard = (Int, Int) Source #

snowflakeCreationDate :: Snowflake -> UTCTime Source #

Gets a creation date from a snowflake.

epochTime :: UTCTime Source #

Default timestamp

makeTable :: (Data t, Enum t) => t -> [(Int, t)] Source #

data InteractionType Source #

What type of interaction has a user requested? Each requires its own type of response.

Instances

Instances details
Enum InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Eq InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Data InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

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

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

toConstr :: InteractionType -> Constr #

dataTypeOf :: InteractionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Read InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Show InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

ToJSON InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

FromJSON InteractionType Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

class Internals a b where Source #

Methods

toInternal :: a -> b Source #

fromInternal :: b -> Maybe a Source #

Instances

Instances details
Internals a a Source # 
Instance details

Defined in Discord.Internal.Types.Prelude

Methods

toInternal :: a -> a Source #

fromInternal :: a -> Maybe a Source #

Internals ApplicationCommandOptionValue InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Internals ApplicationCommandOptionSubcommand InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Internals ApplicationCommandOptionSubcommandOrGroup InternalApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Internals ApplicationCommand InternalApplicationCommand Source # 
Instance details

Defined in Discord.Internal.Types.ApplicationCommands

Internals ComponentActionRow Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Internals ButtonStyle InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Internals InteractionDataApplicationCommandOptionValue InternalInteractionDataApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataApplicationCommandOptionSubcommand InternalInteractionDataApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataApplicationCommandOptionSubcommandOrGroup InternalInteractionDataApplicationCommandOption Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataApplicationCommand InternalInteractionData Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataComponent InternalInteractionData Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals Interaction InternalInteraction Source # 
Instance details

Defined in Discord.Internal.Types.Interactions

Internals InteractionDataApplicationCommandOptions [InternalInteractionDataApplicationCommandOption] Source # 
Instance details

Defined in Discord.Internal.Types.Interactions