calamity-0.3.0.0: A library for writing discord bots in haskell
Safe HaskellNone
LanguageHaskell2010

Calamity.HTTP.Interaction

Description

Interaction endpoints

Documentation

data InteractionRequest a where Source #

Constructors

CreateResponseMessage :: HasID Interaction i => i -> InteractionToken -> InteractionCallbackMessageOptions -> InteractionRequest () 
CreateResponseDefer

Ack an interaction and defer the response

This route triggers the thinking message

Fields

CreateResponseDeferComponent :: HasID Interaction i => i -> InteractionToken -> InteractionRequest ()

Ack an interaction and defer the response

This route is only usable by component interactions, and doesn't trigger a thinking message

CreateResponseUpdate :: HasID Interaction i => i -> InteractionToken -> InteractionCallbackMessageOptions -> InteractionRequest () 
CreateResponseAutocomplete :: HasID Interaction i => i -> InteractionToken -> InteractionCallbackAutocomplete -> InteractionRequest () 
CreateResponseModal :: HasID Interaction i => i -> InteractionToken -> InteractionCallbackModal -> InteractionRequest () 
GetOriginalInteractionResponse :: HasID Application i => i -> InteractionToken -> InteractionRequest Message 
EditOriginalInteractionResponse :: HasID Application i => i -> InteractionToken -> InteractionCallbackMessageOptions -> InteractionRequest Message 
DeleteOriginalInteractionResponse :: HasID Application i => i -> InteractionToken -> InteractionRequest () 
CreateFollowupMessage :: HasID Application i => i -> InteractionToken -> InteractionCallbackMessageOptions -> InteractionRequest () 
GetFollowupMessage :: (HasID Application i, HasID Message m) => i -> m -> InteractionToken -> InteractionRequest Message 
EditFollowupMessage :: (HasID Application i, HasID Message m) => i -> m -> InteractionToken -> InteractionCallbackMessageOptions -> InteractionRequest () 
DeleteFollowupMessage :: (HasID Application i, HasID Message m) => i -> m -> InteractionToken -> InteractionRequest () 

data InteractionCallbackMessageOptions Source #

Instances

Instances details
Show InteractionCallbackMessageOptions Source # 
Instance details

Defined in Calamity.HTTP.Interaction

Generic InteractionCallbackMessageOptions Source # 
Instance details

Defined in Calamity.HTTP.Interaction

Associated Types

type Rep InteractionCallbackMessageOptions :: Type -> Type #

Default InteractionCallbackMessageOptions Source # 
Instance details

Defined in Calamity.HTTP.Interaction

type Rep InteractionCallbackMessageOptions Source # 
Instance details

Defined in Calamity.HTTP.Interaction

newtype InteractionCallbackAutocomplete Source #

data InteractionCallbackAutocompleteChoice Source #

Constructors

InteractionCallbackAutocompleteChoice 

Fields

Instances

Instances details
Show InteractionCallbackAutocompleteChoice Source # 
Instance details

Defined in Calamity.HTTP.Interaction

Generic InteractionCallbackAutocompleteChoice Source # 
Instance details

Defined in Calamity.HTTP.Interaction

ToJSON InteractionCallbackAutocompleteChoice Source # 
Instance details

Defined in Calamity.HTTP.Interaction

type Rep InteractionCallbackAutocompleteChoice Source # 
Instance details

Defined in Calamity.HTTP.Interaction

type Rep InteractionCallbackAutocompleteChoice = D1 ('MetaData "InteractionCallbackAutocompleteChoice" "Calamity.HTTP.Interaction" "calamity-0.3.0.0-inplace" 'False) (C1 ('MetaCons "InteractionCallbackAutocompleteChoice" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "nameLocalizations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap Text Text)) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Value))))

data InteractionCallbackModal Source #

Instances

Instances details
Show InteractionCallbackModal Source # 
Instance details

Defined in Calamity.HTTP.Interaction

Generic InteractionCallbackModal Source # 
Instance details

Defined in Calamity.HTTP.Interaction

Associated Types

type Rep InteractionCallbackModal :: Type -> Type #

ToJSON InteractionCallbackModal Source # 
Instance details

Defined in Calamity.HTTP.Interaction

type Rep InteractionCallbackModal Source # 
Instance details

Defined in Calamity.HTTP.Interaction

type Rep InteractionCallbackModal = D1 ('MetaData "InteractionCallbackModal" "Calamity.HTTP.Interaction" "calamity-0.3.0.0-inplace" 'False) (C1 ('MetaCons "InteractionCallbackModal" 'PrefixI 'True) (S1 ('MetaSel ('Just "customID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CustomID) :*: (S1 ('MetaSel ('Just "title") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "components") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Component]))))