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

Discord.Internal.Types.Components

Synopsis

Documentation

data ComponentButton 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.

data Component Source #

Constructors

Component 

Fields

Instances

Instances details
Eq Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Ord Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Read Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

Internals ComponentActionRow Component Source # 
Instance details

Defined in Discord.Internal.Types.Components

data ComponentType Source #

The different types of components

Constructors

ComponentTypeActionRow

A container for other components

ComponentTypeButton

A button

ComponentTypeSelectMenu

A select menu for picking from choices

Instances

Instances details
Enum ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Eq ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Data ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Methods

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

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

toConstr :: ComponentType -> Constr #

dataTypeOf :: ComponentType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Read ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON ComponentType Source # 
Instance details

Defined in Discord.Internal.Types.Components

data InternalButtonStyle Source #

Constructors

InternalButtonStylePrimary

Blurple button

InternalButtonStyleSecondary

Grey button

InternalButtonStyleSuccess

Green button

InternalButtonStyleDanger

Red button

InternalButtonStyleLink

Grey button, navigates to URL

Instances

Instances details
Enum InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Eq InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Data InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Methods

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

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

toConstr :: InternalButtonStyle -> Constr #

dataTypeOf :: InternalButtonStyle -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Read InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

ToJSON InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

Internals ButtonStyle InternalButtonStyle Source # 
Instance details

Defined in Discord.Internal.Types.Components

data Emoji Source #

Represents an emoticon (emoji)

Constructors

Emoji 

Fields

Instances

Instances details
Eq Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

Methods

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

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

Ord Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

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 #

Read Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

Show Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

Methods

showsPrec :: Int -> Emoji -> ShowS #

show :: Emoji -> String #

showList :: [Emoji] -> ShowS #

ToJSON Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON Emoji Source # 
Instance details

Defined in Discord.Internal.Types.Components

data SelectOption Source #

Constructors

SelectOption 

Fields

Instances

Instances details
Eq SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

Ord 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

ToJSON SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components

FromJSON SelectOption Source # 
Instance details

Defined in Discord.Internal.Types.Components