{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}
module Calamity.HTTP.Interaction (
InteractionRequest (..),
InteractionCallbackMessageOptions (..),
InteractionCallbackAutocomplete (..),
InteractionCallbackAutocompleteChoice (..),
InteractionCallbackModal (..),
) where
import Calamity.HTTP.Channel (AllowedMentions, CreateMessageAttachment (..))
import Calamity.HTTP.Internal.Request
import Calamity.HTTP.Internal.Route
import Calamity.Internal.Utils (CalamityToJSON (..), CalamityToJSON' (..), (.=), (.?=))
import Calamity.Types.Model.Channel.Component (Component, CustomID)
import Calamity.Types.Model.Channel.Embed (Embed)
import Calamity.Types.Model.Channel.Message (Message)
import Calamity.Types.Model.Interaction
import Calamity.Types.Snowflake
import Data.Aeson qualified as Aeson
import Data.Bits (shiftL, (.|.))
import Data.Default.Class
import Data.HashMap.Strict qualified as H
import Data.Maybe (fromMaybe)
import Data.Monoid (First (First, getFirst))
import Data.Text (Text)
import Data.Text qualified as T
import Network.HTTP.Client.MultipartFormData
import Network.HTTP.Req
import Network.Mime
import Optics
data InteractionCallback = InteractionCallback
{ InteractionCallback -> InteractionCallbackType
type_ :: InteractionCallbackType
, InteractionCallback -> Maybe Value
data_ :: Maybe Aeson.Value
}
deriving (Int -> InteractionCallback -> ShowS
[InteractionCallback] -> ShowS
InteractionCallback -> String
(Int -> InteractionCallback -> ShowS)
-> (InteractionCallback -> String)
-> ([InteractionCallback] -> ShowS)
-> Show InteractionCallback
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InteractionCallback -> ShowS
showsPrec :: Int -> InteractionCallback -> ShowS
$cshow :: InteractionCallback -> String
show :: InteractionCallback -> String
$cshowList :: [InteractionCallback] -> ShowS
showList :: [InteractionCallback] -> ShowS
Show)
deriving ([InteractionCallback] -> Value
[InteractionCallback] -> Encoding
InteractionCallback -> Value
InteractionCallback -> Encoding
(InteractionCallback -> Value)
-> (InteractionCallback -> Encoding)
-> ([InteractionCallback] -> Value)
-> ([InteractionCallback] -> Encoding)
-> ToJSON InteractionCallback
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: InteractionCallback -> Value
toJSON :: InteractionCallback -> Value
$ctoEncoding :: InteractionCallback -> Encoding
toEncoding :: InteractionCallback -> Encoding
$ctoJSONList :: [InteractionCallback] -> Value
toJSONList :: [InteractionCallback] -> Value
$ctoEncodingList :: [InteractionCallback] -> Encoding
toEncodingList :: [InteractionCallback] -> Encoding
Aeson.ToJSON) via CalamityToJSON InteractionCallback
instance CalamityToJSON' InteractionCallback where
toPairs :: forall kv. KeyValue kv => InteractionCallback -> [Maybe kv]
toPairs InteractionCallback {Maybe Value
InteractionCallbackType
$sel:type_:InteractionCallback :: InteractionCallback -> InteractionCallbackType
$sel:data_:InteractionCallback :: InteractionCallback -> Maybe Value
type_ :: InteractionCallbackType
data_ :: Maybe Value
..} =
[ Key
"type" Key -> InteractionCallbackType -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= InteractionCallbackType
type_
, Key
"data" Key -> Maybe Value -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe Value
data_
]
data InteractionCallbackMessageOptions = InteractionCallbackMessageOptions
{ InteractionCallbackMessageOptions -> Maybe Bool
tts :: Maybe Bool
, InteractionCallbackMessageOptions -> Maybe Text
content :: Maybe Text
, InteractionCallbackMessageOptions -> Maybe [Embed]
embeds :: Maybe [Embed]
, InteractionCallbackMessageOptions -> Maybe AllowedMentions
allowedMentions :: Maybe AllowedMentions
, InteractionCallbackMessageOptions -> Maybe Bool
ephemeral :: Maybe Bool
, InteractionCallbackMessageOptions -> Maybe Bool
suppressEmbeds :: Maybe Bool
, InteractionCallbackMessageOptions -> Maybe [Component]
components :: Maybe [Component]
, InteractionCallbackMessageOptions
-> Maybe [CreateMessageAttachment]
attachments :: Maybe [CreateMessageAttachment]
}
deriving (Int -> InteractionCallbackMessageOptions -> ShowS
[InteractionCallbackMessageOptions] -> ShowS
InteractionCallbackMessageOptions -> String
(Int -> InteractionCallbackMessageOptions -> ShowS)
-> (InteractionCallbackMessageOptions -> String)
-> ([InteractionCallbackMessageOptions] -> ShowS)
-> Show InteractionCallbackMessageOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InteractionCallbackMessageOptions -> ShowS
showsPrec :: Int -> InteractionCallbackMessageOptions -> ShowS
$cshow :: InteractionCallbackMessageOptions -> String
show :: InteractionCallbackMessageOptions -> String
$cshowList :: [InteractionCallbackMessageOptions] -> ShowS
showList :: [InteractionCallbackMessageOptions] -> ShowS
Show)
instance Default InteractionCallbackMessageOptions where
def :: InteractionCallbackMessageOptions
def = Maybe Bool
-> Maybe Text
-> Maybe [Embed]
-> Maybe AllowedMentions
-> Maybe Bool
-> Maybe Bool
-> Maybe [Component]
-> Maybe [CreateMessageAttachment]
-> InteractionCallbackMessageOptions
InteractionCallbackMessageOptions Maybe Bool
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe [Embed]
forall a. Maybe a
Nothing Maybe AllowedMentions
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe [Component]
forall a. Maybe a
Nothing Maybe [CreateMessageAttachment]
forall a. Maybe a
Nothing
data CreateMessageAttachmentJson = CreateMessageAttachmentJson
{ CreateMessageAttachmentJson -> Int
id :: Int
, CreateMessageAttachmentJson -> Text
filename :: Text
, CreateMessageAttachmentJson -> Maybe Text
description :: Maybe Text
}
deriving (Int -> CreateMessageAttachmentJson -> ShowS
[CreateMessageAttachmentJson] -> ShowS
CreateMessageAttachmentJson -> String
(Int -> CreateMessageAttachmentJson -> ShowS)
-> (CreateMessageAttachmentJson -> String)
-> ([CreateMessageAttachmentJson] -> ShowS)
-> Show CreateMessageAttachmentJson
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateMessageAttachmentJson -> ShowS
showsPrec :: Int -> CreateMessageAttachmentJson -> ShowS
$cshow :: CreateMessageAttachmentJson -> String
show :: CreateMessageAttachmentJson -> String
$cshowList :: [CreateMessageAttachmentJson] -> ShowS
showList :: [CreateMessageAttachmentJson] -> ShowS
Show)
deriving ([CreateMessageAttachmentJson] -> Value
[CreateMessageAttachmentJson] -> Encoding
CreateMessageAttachmentJson -> Value
CreateMessageAttachmentJson -> Encoding
(CreateMessageAttachmentJson -> Value)
-> (CreateMessageAttachmentJson -> Encoding)
-> ([CreateMessageAttachmentJson] -> Value)
-> ([CreateMessageAttachmentJson] -> Encoding)
-> ToJSON CreateMessageAttachmentJson
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: CreateMessageAttachmentJson -> Value
toJSON :: CreateMessageAttachmentJson -> Value
$ctoEncoding :: CreateMessageAttachmentJson -> Encoding
toEncoding :: CreateMessageAttachmentJson -> Encoding
$ctoJSONList :: [CreateMessageAttachmentJson] -> Value
toJSONList :: [CreateMessageAttachmentJson] -> Value
$ctoEncodingList :: [CreateMessageAttachmentJson] -> Encoding
toEncodingList :: [CreateMessageAttachmentJson] -> Encoding
Aeson.ToJSON) via CalamityToJSON CreateMessageAttachmentJson
instance CalamityToJSON' CreateMessageAttachmentJson where
toPairs :: forall kv. KeyValue kv => CreateMessageAttachmentJson -> [Maybe kv]
toPairs CreateMessageAttachmentJson {Int
Maybe Text
Text
$sel:id:CreateMessageAttachmentJson :: CreateMessageAttachmentJson -> Int
$sel:filename:CreateMessageAttachmentJson :: CreateMessageAttachmentJson -> Text
$sel:description:CreateMessageAttachmentJson :: CreateMessageAttachmentJson -> Maybe Text
id :: Int
filename :: Text
description :: Maybe Text
..} =
[ Key
"id" Key -> Int -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Int
id
, Key
"filename" Key -> Text -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Text
filename
, Key
"description" Key -> Maybe Text -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe Text
description
]
data CreateResponseMessageJson = CreateResponseMessageJson
{ CreateResponseMessageJson -> Maybe Bool
tts :: Maybe Bool
, CreateResponseMessageJson -> Maybe Text
content :: Maybe Text
, CreateResponseMessageJson -> Maybe [Embed]
embeds :: Maybe [Embed]
, CreateResponseMessageJson -> Maybe AllowedMentions
allowedMentions :: Maybe AllowedMentions
, CreateResponseMessageJson -> Maybe Int
flags :: Maybe Int
, CreateResponseMessageJson -> Maybe [Component]
components :: Maybe [Component]
, CreateResponseMessageJson -> Maybe [CreateMessageAttachmentJson]
attachments :: Maybe [CreateMessageAttachmentJson]
}
deriving (Int -> CreateResponseMessageJson -> ShowS
[CreateResponseMessageJson] -> ShowS
CreateResponseMessageJson -> String
(Int -> CreateResponseMessageJson -> ShowS)
-> (CreateResponseMessageJson -> String)
-> ([CreateResponseMessageJson] -> ShowS)
-> Show CreateResponseMessageJson
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateResponseMessageJson -> ShowS
showsPrec :: Int -> CreateResponseMessageJson -> ShowS
$cshow :: CreateResponseMessageJson -> String
show :: CreateResponseMessageJson -> String
$cshowList :: [CreateResponseMessageJson] -> ShowS
showList :: [CreateResponseMessageJson] -> ShowS
Show)
deriving ([CreateResponseMessageJson] -> Value
[CreateResponseMessageJson] -> Encoding
CreateResponseMessageJson -> Value
CreateResponseMessageJson -> Encoding
(CreateResponseMessageJson -> Value)
-> (CreateResponseMessageJson -> Encoding)
-> ([CreateResponseMessageJson] -> Value)
-> ([CreateResponseMessageJson] -> Encoding)
-> ToJSON CreateResponseMessageJson
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: CreateResponseMessageJson -> Value
toJSON :: CreateResponseMessageJson -> Value
$ctoEncoding :: CreateResponseMessageJson -> Encoding
toEncoding :: CreateResponseMessageJson -> Encoding
$ctoJSONList :: [CreateResponseMessageJson] -> Value
toJSONList :: [CreateResponseMessageJson] -> Value
$ctoEncodingList :: [CreateResponseMessageJson] -> Encoding
toEncodingList :: [CreateResponseMessageJson] -> Encoding
Aeson.ToJSON) via CalamityToJSON CreateResponseMessageJson
instance CalamityToJSON' CreateResponseMessageJson where
toPairs :: forall kv. KeyValue kv => CreateResponseMessageJson -> [Maybe kv]
toPairs CreateResponseMessageJson {Maybe Bool
Maybe Int
Maybe [Embed]
Maybe [Component]
Maybe [CreateMessageAttachmentJson]
Maybe Text
Maybe AllowedMentions
$sel:tts:CreateResponseMessageJson :: CreateResponseMessageJson -> Maybe Bool
$sel:content:CreateResponseMessageJson :: CreateResponseMessageJson -> Maybe Text
$sel:embeds:CreateResponseMessageJson :: CreateResponseMessageJson -> Maybe [Embed]
$sel:allowedMentions:CreateResponseMessageJson :: CreateResponseMessageJson -> Maybe AllowedMentions
$sel:flags:CreateResponseMessageJson :: CreateResponseMessageJson -> Maybe Int
$sel:components:CreateResponseMessageJson :: CreateResponseMessageJson -> Maybe [Component]
$sel:attachments:CreateResponseMessageJson :: CreateResponseMessageJson -> Maybe [CreateMessageAttachmentJson]
tts :: Maybe Bool
content :: Maybe Text
embeds :: Maybe [Embed]
allowedMentions :: Maybe AllowedMentions
flags :: Maybe Int
components :: Maybe [Component]
attachments :: Maybe [CreateMessageAttachmentJson]
..} =
[ Key
"tts" Key -> Maybe Bool -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe Bool
tts
, Key
"content" Key -> Maybe Text -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe Text
content
, Key
"embeds" Key -> Maybe [Embed] -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe [Embed]
embeds
, Key
"allowed_mentions" Key -> Maybe AllowedMentions -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe AllowedMentions
allowedMentions
, Key
"flags" Key -> Maybe Int -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe Int
flags
, Key
"components" Key -> Maybe [Component] -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe [Component]
components
, Key
"attachments" Key -> Maybe [CreateMessageAttachmentJson] -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> Maybe v -> Maybe kv
.?= Maybe [CreateMessageAttachmentJson]
attachments
]
newtype InteractionCallbackAutocomplete = InteractionCallbackAutocomplete
{ InteractionCallbackAutocomplete
-> [InteractionCallbackAutocompleteChoice]
choices :: [InteractionCallbackAutocompleteChoice]
}
deriving stock (Int -> InteractionCallbackAutocomplete -> ShowS
[InteractionCallbackAutocomplete] -> ShowS
InteractionCallbackAutocomplete -> String
(Int -> InteractionCallbackAutocomplete -> ShowS)
-> (InteractionCallbackAutocomplete -> String)
-> ([InteractionCallbackAutocomplete] -> ShowS)
-> Show InteractionCallbackAutocomplete
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InteractionCallbackAutocomplete -> ShowS
showsPrec :: Int -> InteractionCallbackAutocomplete -> ShowS
$cshow :: InteractionCallbackAutocomplete -> String
show :: InteractionCallbackAutocomplete -> String
$cshowList :: [InteractionCallbackAutocomplete] -> ShowS
showList :: [InteractionCallbackAutocomplete] -> ShowS
Show)
deriving ([InteractionCallbackAutocomplete] -> Value
[InteractionCallbackAutocomplete] -> Encoding
InteractionCallbackAutocomplete -> Value
InteractionCallbackAutocomplete -> Encoding
(InteractionCallbackAutocomplete -> Value)
-> (InteractionCallbackAutocomplete -> Encoding)
-> ([InteractionCallbackAutocomplete] -> Value)
-> ([InteractionCallbackAutocomplete] -> Encoding)
-> ToJSON InteractionCallbackAutocomplete
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: InteractionCallbackAutocomplete -> Value
toJSON :: InteractionCallbackAutocomplete -> Value
$ctoEncoding :: InteractionCallbackAutocomplete -> Encoding
toEncoding :: InteractionCallbackAutocomplete -> Encoding
$ctoJSONList :: [InteractionCallbackAutocomplete] -> Value
toJSONList :: [InteractionCallbackAutocomplete] -> Value
$ctoEncodingList :: [InteractionCallbackAutocomplete] -> Encoding
toEncodingList :: [InteractionCallbackAutocomplete] -> Encoding
Aeson.ToJSON) via CalamityToJSON InteractionCallbackAutocomplete
instance CalamityToJSON' InteractionCallbackAutocomplete where
toPairs :: forall kv.
KeyValue kv =>
InteractionCallbackAutocomplete -> [Maybe kv]
toPairs InteractionCallbackAutocomplete {[InteractionCallbackAutocompleteChoice]
$sel:choices:InteractionCallbackAutocomplete :: InteractionCallbackAutocomplete
-> [InteractionCallbackAutocompleteChoice]
choices :: [InteractionCallbackAutocompleteChoice]
..} = [Key
"choices" Key -> [InteractionCallbackAutocompleteChoice] -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= [InteractionCallbackAutocompleteChoice]
choices]
data InteractionCallbackAutocompleteChoice = InteractionCallbackAutocompleteChoice
{ InteractionCallbackAutocompleteChoice -> Text
name :: Text
, InteractionCallbackAutocompleteChoice -> HashMap Text Text
nameLocalizations :: H.HashMap Text Text
, InteractionCallbackAutocompleteChoice -> Value
value :: Aeson.Value
}
deriving stock (Int -> InteractionCallbackAutocompleteChoice -> ShowS
[InteractionCallbackAutocompleteChoice] -> ShowS
InteractionCallbackAutocompleteChoice -> String
(Int -> InteractionCallbackAutocompleteChoice -> ShowS)
-> (InteractionCallbackAutocompleteChoice -> String)
-> ([InteractionCallbackAutocompleteChoice] -> ShowS)
-> Show InteractionCallbackAutocompleteChoice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InteractionCallbackAutocompleteChoice -> ShowS
showsPrec :: Int -> InteractionCallbackAutocompleteChoice -> ShowS
$cshow :: InteractionCallbackAutocompleteChoice -> String
show :: InteractionCallbackAutocompleteChoice -> String
$cshowList :: [InteractionCallbackAutocompleteChoice] -> ShowS
showList :: [InteractionCallbackAutocompleteChoice] -> ShowS
Show)
deriving ([InteractionCallbackAutocompleteChoice] -> Value
[InteractionCallbackAutocompleteChoice] -> Encoding
InteractionCallbackAutocompleteChoice -> Value
InteractionCallbackAutocompleteChoice -> Encoding
(InteractionCallbackAutocompleteChoice -> Value)
-> (InteractionCallbackAutocompleteChoice -> Encoding)
-> ([InteractionCallbackAutocompleteChoice] -> Value)
-> ([InteractionCallbackAutocompleteChoice] -> Encoding)
-> ToJSON InteractionCallbackAutocompleteChoice
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: InteractionCallbackAutocompleteChoice -> Value
toJSON :: InteractionCallbackAutocompleteChoice -> Value
$ctoEncoding :: InteractionCallbackAutocompleteChoice -> Encoding
toEncoding :: InteractionCallbackAutocompleteChoice -> Encoding
$ctoJSONList :: [InteractionCallbackAutocompleteChoice] -> Value
toJSONList :: [InteractionCallbackAutocompleteChoice] -> Value
$ctoEncodingList :: [InteractionCallbackAutocompleteChoice] -> Encoding
toEncodingList :: [InteractionCallbackAutocompleteChoice] -> Encoding
Aeson.ToJSON) via CalamityToJSON InteractionCallbackAutocompleteChoice
instance CalamityToJSON' InteractionCallbackAutocompleteChoice where
toPairs :: forall kv.
KeyValue kv =>
InteractionCallbackAutocompleteChoice -> [Maybe kv]
toPairs InteractionCallbackAutocompleteChoice {Value
HashMap Text Text
Text
$sel:name:InteractionCallbackAutocompleteChoice :: InteractionCallbackAutocompleteChoice -> Text
$sel:nameLocalizations:InteractionCallbackAutocompleteChoice :: InteractionCallbackAutocompleteChoice -> HashMap Text Text
$sel:value:InteractionCallbackAutocompleteChoice :: InteractionCallbackAutocompleteChoice -> Value
name :: Text
nameLocalizations :: HashMap Text Text
value :: Value
..} =
[ Key
"name" Key -> Text -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Text
name
, Key
"name_localizations" Key -> HashMap Text Text -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= HashMap Text Text
nameLocalizations
, Key
"value" Key -> Value -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Value
value
]
data InteractionCallbackModal = InteractionCallbackModal
{ InteractionCallbackModal -> CustomID
customID :: CustomID
, InteractionCallbackModal -> Text
title :: Text
, InteractionCallbackModal -> [Component]
components :: [Component]
}
deriving stock (Int -> InteractionCallbackModal -> ShowS
[InteractionCallbackModal] -> ShowS
InteractionCallbackModal -> String
(Int -> InteractionCallbackModal -> ShowS)
-> (InteractionCallbackModal -> String)
-> ([InteractionCallbackModal] -> ShowS)
-> Show InteractionCallbackModal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InteractionCallbackModal -> ShowS
showsPrec :: Int -> InteractionCallbackModal -> ShowS
$cshow :: InteractionCallbackModal -> String
show :: InteractionCallbackModal -> String
$cshowList :: [InteractionCallbackModal] -> ShowS
showList :: [InteractionCallbackModal] -> ShowS
Show)
deriving ([InteractionCallbackModal] -> Value
[InteractionCallbackModal] -> Encoding
InteractionCallbackModal -> Value
InteractionCallbackModal -> Encoding
(InteractionCallbackModal -> Value)
-> (InteractionCallbackModal -> Encoding)
-> ([InteractionCallbackModal] -> Value)
-> ([InteractionCallbackModal] -> Encoding)
-> ToJSON InteractionCallbackModal
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: InteractionCallbackModal -> Value
toJSON :: InteractionCallbackModal -> Value
$ctoEncoding :: InteractionCallbackModal -> Encoding
toEncoding :: InteractionCallbackModal -> Encoding
$ctoJSONList :: [InteractionCallbackModal] -> Value
toJSONList :: [InteractionCallbackModal] -> Value
$ctoEncodingList :: [InteractionCallbackModal] -> Encoding
toEncodingList :: [InteractionCallbackModal] -> Encoding
Aeson.ToJSON) via CalamityToJSON InteractionCallbackModal
instance CalamityToJSON' InteractionCallbackModal where
toPairs :: forall kv. KeyValue kv => InteractionCallbackModal -> [Maybe kv]
toPairs InteractionCallbackModal {[Component]
Text
CustomID
$sel:customID:InteractionCallbackModal :: InteractionCallbackModal -> CustomID
$sel:title:InteractionCallbackModal :: InteractionCallbackModal -> Text
$sel:components:InteractionCallbackModal :: InteractionCallbackModal -> [Component]
customID :: CustomID
title :: Text
components :: [Component]
..} =
[ Key
"custom_id" Key -> CustomID -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= CustomID
customID
, Key
"title" Key -> Text -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= Text
title
, Key
"components" Key -> [Component] -> Maybe kv
forall v kv. (ToJSON v, KeyValue kv) => Key -> v -> Maybe kv
.= [Component]
components
]
data InteractionCallbackType
= PongType
| ChannelMessageWithSourceType
| DeferredChannelMessageWithSourceType
| DeferredUpdateMessageType
| UpdateMessageType
| ApplicationCommandAutocompleteResultType
| ModalType
deriving (Int -> InteractionCallbackType -> ShowS
[InteractionCallbackType] -> ShowS
InteractionCallbackType -> String
(Int -> InteractionCallbackType -> ShowS)
-> (InteractionCallbackType -> String)
-> ([InteractionCallbackType] -> ShowS)
-> Show InteractionCallbackType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InteractionCallbackType -> ShowS
showsPrec :: Int -> InteractionCallbackType -> ShowS
$cshow :: InteractionCallbackType -> String
show :: InteractionCallbackType -> String
$cshowList :: [InteractionCallbackType] -> ShowS
showList :: [InteractionCallbackType] -> ShowS
Show)
instance Aeson.ToJSON InteractionCallbackType where
toJSON :: InteractionCallbackType -> Value
toJSON InteractionCallbackType
ty = forall a. ToJSON a => a -> Value
Aeson.toJSON @Int (Int -> Value) -> Int -> Value
forall a b. (a -> b) -> a -> b
$ case InteractionCallbackType
ty of
InteractionCallbackType
PongType -> Int
1
InteractionCallbackType
ChannelMessageWithSourceType -> Int
4
InteractionCallbackType
DeferredChannelMessageWithSourceType -> Int
5
InteractionCallbackType
DeferredUpdateMessageType -> Int
6
InteractionCallbackType
UpdateMessageType -> Int
7
InteractionCallbackType
ApplicationCommandAutocompleteResultType -> Int
8
InteractionCallbackType
ModalType -> Int
9
toEncoding :: InteractionCallbackType -> Encoding
toEncoding InteractionCallbackType
ty = forall a. ToJSON a => a -> Encoding
Aeson.toEncoding @Int (Int -> Encoding) -> Int -> Encoding
forall a b. (a -> b) -> a -> b
$ case InteractionCallbackType
ty of
InteractionCallbackType
PongType -> Int
1
InteractionCallbackType
ChannelMessageWithSourceType -> Int
4
InteractionCallbackType
DeferredChannelMessageWithSourceType -> Int
5
InteractionCallbackType
DeferredUpdateMessageType -> Int
6
InteractionCallbackType
UpdateMessageType -> Int
7
InteractionCallbackType
ApplicationCommandAutocompleteResultType -> Int
8
InteractionCallbackType
ModalType -> Int
9
$(makeFieldLabelsNoPrefix ''InteractionCallbackMessageOptions)
$(makeFieldLabelsNoPrefix ''InteractionCallbackAutocomplete)
$(makeFieldLabelsNoPrefix ''InteractionCallbackAutocompleteChoice)
$(makeFieldLabelsNoPrefix ''InteractionCallbackModal)
data InteractionRequest a where
CreateResponseMessage ::
(HasID Interaction i) =>
i ->
InteractionToken ->
InteractionCallbackMessageOptions ->
InteractionRequest ()
CreateResponseDefer ::
(HasID Interaction i) =>
i ->
InteractionToken ->
Bool ->
InteractionRequest ()
CreateResponseDeferComponent ::
(HasID Interaction i) =>
i ->
InteractionToken ->
InteractionRequest ()
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 ()
baseRoute :: Snowflake Application -> InteractionToken -> RouteBuilder _
baseRoute :: Snowflake Application
-> InteractionToken
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application,
AddRequiredInner (Lookup ('IDRequirement Application) '[]))]
baseRoute Snowflake Application
id (InteractionToken Text
token) =
RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"webhooks" RouteBuilder '[] -> ID Application -> ConsRes (ID Application) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Application RouteBuilder
'[ '( 'IDRequirement Application,
AddRequiredInner (Lookup ('IDRequirement Application) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application,
AddRequiredInner (Lookup ('IDRequirement Application) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
token
RouteBuilder
'[ '( 'IDRequirement Application,
AddRequiredInner (Lookup ('IDRequirement Application) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Application,
AddRequiredInner (Lookup ('IDRequirement Application) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application,
AddRequiredInner (Lookup ('IDRequirement Application) '[]))])
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application,
AddRequiredInner (Lookup ('IDRequirement Application) '[]))]
forall a b. a -> (a -> b) -> b
& Snowflake Application
-> RouteBuilder
'[ '( 'IDRequirement Application,
AddRequiredInner (Lookup ('IDRequirement Application) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application,
AddRequiredInner (Lookup ('IDRequirement Application) '[]))]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Application
id
foo :: Maybe a -> Maybe a -> (a -> a -> a) -> Maybe a
foo :: forall a. Maybe a -> Maybe a -> (a -> a -> a) -> Maybe a
foo (Just a
x) (Just a
y) a -> a -> a
f = a -> Maybe a
forall a. a -> Maybe a
Just (a -> a -> a
f a
x a
y)
foo Maybe a
x Maybe a
y a -> a -> a
_ = First a -> Maybe a
forall a. First a -> Maybe a
getFirst (First a -> Maybe a) -> First a -> Maybe a
forall a b. (a -> b) -> a -> b
$ Maybe a -> First a
forall a. Maybe a -> First a
First Maybe a
x First a -> First a -> First a
forall a. Semigroup a => a -> a -> a
<> Maybe a -> First a
forall a. Maybe a -> First a
First Maybe a
y
instance Request (InteractionRequest a) where
type Result (InteractionRequest a) = a
route :: InteractionRequest a -> Route
route (CreateResponseDefer (forall b a. HasID b a => a -> Snowflake b
getID @Interaction -> Snowflake Interaction
iid) (InteractionToken Text
token) Bool
_) =
RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"interactions" RouteBuilder '[] -> ID Interaction -> ConsRes (ID Interaction) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Interaction RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
token RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"callback"
RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))])
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a b. a -> (a -> b) -> b
& Snowflake Interaction
-> RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Interaction
iid
RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (CreateResponseDeferComponent (forall b a. HasID b a => a -> Snowflake b
getID @Interaction -> Snowflake Interaction
iid) (InteractionToken Text
token)) =
RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"interactions" RouteBuilder '[] -> ID Interaction -> ConsRes (ID Interaction) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Interaction RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
token RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"callback"
RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))])
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a b. a -> (a -> b) -> b
& Snowflake Interaction
-> RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Interaction
iid
RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (CreateResponseMessage (forall b a. HasID b a => a -> Snowflake b
getID @Interaction -> Snowflake Interaction
iid) (InteractionToken Text
token) InteractionCallbackMessageOptions
_) =
RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"interactions" RouteBuilder '[] -> ID Interaction -> ConsRes (ID Interaction) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Interaction RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
token RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"callback"
RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))])
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a b. a -> (a -> b) -> b
& Snowflake Interaction
-> RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Interaction
iid
RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (CreateResponseUpdate (forall b a. HasID b a => a -> Snowflake b
getID @Interaction -> Snowflake Interaction
iid) (InteractionToken Text
token) InteractionCallbackMessageOptions
_) =
RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"interactions" RouteBuilder '[] -> ID Interaction -> ConsRes (ID Interaction) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Interaction RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
token RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"callback"
RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))])
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a b. a -> (a -> b) -> b
& Snowflake Interaction
-> RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Interaction
iid
RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (CreateResponseAutocomplete (forall b a. HasID b a => a -> Snowflake b
getID @Interaction -> Snowflake Interaction
iid) (InteractionToken Text
token) InteractionCallbackAutocomplete
_) =
RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"interactions" RouteBuilder '[] -> ID Interaction -> ConsRes (ID Interaction) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Interaction RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
token RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"callback"
RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))])
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a b. a -> (a -> b) -> b
& Snowflake Interaction
-> RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Interaction
iid
RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (CreateResponseModal (forall b a. HasID b a => a -> Snowflake b
getID @Interaction -> Snowflake Interaction
iid) (InteractionToken Text
token) InteractionCallbackModal
_) =
RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"interactions" RouteBuilder '[] -> ID Interaction -> ConsRes (ID Interaction) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Interaction RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
token RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"callback"
RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))])
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall a b. a -> (a -> b) -> b
& Snowflake Interaction
-> RouteBuilder
'[ '( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Interaction
iid
RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> (RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Interaction, 'Satisfied),
'( 'IDRequirement Interaction,
AddRequiredInner (Lookup ('IDRequirement Interaction) '[]))]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (GetOriginalInteractionResponse (forall b a. HasID b a => a -> Snowflake b
getID @Application -> Snowflake Application
aid) InteractionToken
token) =
Snowflake Application
-> InteractionToken
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
baseRoute Snowflake Application
aid InteractionToken
token RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"messages" RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"@original" RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (EditOriginalInteractionResponse (forall b a. HasID b a => a -> Snowflake b
getID @Application -> Snowflake Application
aid) InteractionToken
token InteractionCallbackMessageOptions
_) =
Snowflake Application
-> InteractionToken
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
baseRoute Snowflake Application
aid InteractionToken
token RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"messages" RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"@original" RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (DeleteOriginalInteractionResponse (forall b a. HasID b a => a -> Snowflake b
getID @Application -> Snowflake Application
aid) InteractionToken
token) =
Snowflake Application
-> InteractionToken
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
baseRoute Snowflake Application
aid InteractionToken
token RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"messages" RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"@original" RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (CreateFollowupMessage (forall b a. HasID b a => a -> Snowflake b
getID @Application -> Snowflake Application
aid) InteractionToken
token InteractionCallbackMessageOptions
_) =
Snowflake Application
-> InteractionToken
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
baseRoute Snowflake Application
aid InteractionToken
token RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (GetFollowupMessage (forall b a. HasID b a => a -> Snowflake b
getID @Application -> Snowflake Application
aid) (forall b a. HasID b a => a -> Snowflake b
getID @Message -> Snowflake Message
mid) InteractionToken
token) =
Snowflake Application
-> InteractionToken
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
baseRoute Snowflake Application
aid InteractionToken
token RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"messages" RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> ID Message
-> ConsRes
(ID Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Message RouteBuilder
'[ '( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])
-> RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a b. a -> (a -> b) -> b
& Snowflake Message
-> RouteBuilder
'[ '( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Message
mid RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (EditFollowupMessage (forall b a. HasID b a => a -> Snowflake b
getID @Application -> Snowflake Application
aid) (forall b a. HasID b a => a -> Snowflake b
getID @Message -> Snowflake Message
mid) InteractionToken
token InteractionCallbackMessageOptions
_) =
Snowflake Application
-> InteractionToken
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
baseRoute Snowflake Application
aid InteractionToken
token RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"messages" RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> ID Message
-> ConsRes
(ID Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Message RouteBuilder
'[ '( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])
-> RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a b. a -> (a -> b) -> b
& Snowflake Message
-> RouteBuilder
'[ '( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Message
mid RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
route (DeleteFollowupMessage (forall b a. HasID b a => a -> Snowflake b
getID @Application -> Snowflake Application
aid) (forall b a. HasID b a => a -> Snowflake b
getID @Message -> Snowflake Message
mid) InteractionToken
token) =
Snowflake Application
-> InteractionToken
-> RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
baseRoute Snowflake Application
aid InteractionToken
token RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> S
-> ConsRes
S
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"messages" RouteBuilder
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> ID Message
-> ConsRes
(ID Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// forall a. ID a
forall {k} (a :: k). ID a
ID @Message RouteBuilder
'[ '( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])
-> RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall a b. a -> (a -> b) -> b
& Snowflake Message
-> RouteBuilder
'[ '( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Message
mid RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> (RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
'[ '( 'IDRequirement Message, 'Satisfied),
'( 'IDRequirement Message,
AddRequiredInner
(Lookup
('IDRequirement Message)
'[ '( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)])),
'( 'IDRequirement Application, 'Satisfied),
'( 'IDRequirement Application, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
action :: InteractionRequest a
-> Url 'Https -> Option 'Https -> Req LbsResponse
action (CreateResponseDefer i
_ InteractionToken
_ Bool
ephemeral) =
let jsonBody :: InteractionCallback
jsonBody =
InteractionCallback
{ $sel:type_:InteractionCallback :: InteractionCallbackType
type_ = InteractionCallbackType
DeferredChannelMessageWithSourceType
, $sel:data_:InteractionCallback :: Maybe Value
data_ = if Bool
ephemeral then Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value)
-> ([Pair] -> Value) -> [Pair] -> Maybe Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Pair] -> Value
Aeson.object ([Pair] -> Maybe Value) -> [Pair] -> Maybe Value
forall a b. (a -> b) -> a -> b
$ [(Key
"flags", Scientific -> Value
Aeson.Number Scientific
64)] else Maybe Value
forall a. Maybe a
Nothing
}
in ReqBodyJson InteractionCallback
-> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
postWith' (InteractionCallback -> ReqBodyJson InteractionCallback
forall a. a -> ReqBodyJson a
ReqBodyJson InteractionCallback
jsonBody)
action (CreateResponseDeferComponent i
_ InteractionToken
_) =
let jsonBody :: InteractionCallback
jsonBody =
InteractionCallback
{ $sel:type_:InteractionCallback :: InteractionCallbackType
type_ = InteractionCallbackType
DeferredUpdateMessageType
, $sel:data_:InteractionCallback :: Maybe Value
data_ = Maybe Value
forall a. Maybe a
Nothing
}
in ReqBodyJson InteractionCallback
-> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
postWith' (InteractionCallback -> ReqBodyJson InteractionCallback
forall a. a -> ReqBodyJson a
ReqBodyJson InteractionCallback
jsonBody)
action (CreateResponseMessage i
_ InteractionToken
_ InteractionCallbackMessageOptions
cm) = \Url 'Https
u Option 'Https
o -> do
let filePart :: CreateMessageAttachment -> a -> PartM IO
filePart CreateMessageAttachment {Text
filename :: Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename, ByteString
content :: ByteString
$sel:content:CreateMessageAttachment :: CreateMessageAttachment -> ByteString
content} a
n =
(forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS @IO (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"files[" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"]") ByteString
content)
{ partFilename :: Maybe String
partFilename = String -> Maybe String
forall a. a -> Maybe a
Just (Text -> String
T.unpack Text
filename)
, partContentType :: Maybe MimeType
partContentType = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (Text -> MimeType
defaultMimeLookup Text
filename)
}
attachmentPart :: CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, Maybe Text
description :: Maybe Text
$sel:description:CreateMessageAttachment :: CreateMessageAttachment -> Maybe Text
description} Int
n =
Int -> Text -> Maybe Text -> CreateMessageAttachmentJson
CreateMessageAttachmentJson Int
n Text
filename Maybe Text
description
files :: [PartM IO]
files = (CreateMessageAttachment -> Int -> PartM IO)
-> [CreateMessageAttachment] -> [Int] -> [PartM IO]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> PartM IO
forall {a}. Show a => CreateMessageAttachment -> a -> PartM IO
filePart ([CreateMessageAttachment]
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [CreateMessageAttachment] -> [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a b. (a -> b) -> a -> b
$ InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments) [(Int
0 :: Int) ..]
attachments :: Maybe [CreateMessageAttachmentJson]
attachments = (\[CreateMessageAttachment]
a -> (CreateMessageAttachment -> Int -> CreateMessageAttachmentJson)
-> [CreateMessageAttachment]
-> [Int]
-> [CreateMessageAttachmentJson]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart [CreateMessageAttachment]
a [Int
0 ..]) ([CreateMessageAttachment] -> [CreateMessageAttachmentJson])
-> Maybe [CreateMessageAttachment]
-> Maybe [CreateMessageAttachmentJson]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments
ephemeral :: Maybe Int
ephemeral = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
6 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#ephemeral
suppressEmbeds :: Maybe Int
suppressEmbeds = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#suppressEmbeds
flags :: Maybe Int
flags = Maybe Int -> Maybe Int -> (Int -> Int -> Int) -> Maybe Int
forall a. Maybe a -> Maybe a -> (a -> a -> a) -> Maybe a
foo Maybe Int
ephemeral Maybe Int
suppressEmbeds Int -> Int -> Int
forall a. Bits a => a -> a -> a
(.|.)
jsonData :: CreateResponseMessageJson
jsonData =
CreateResponseMessageJson
{ $sel:content:CreateResponseMessageJson :: Maybe Text
content = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
#content
, $sel:tts:CreateResponseMessageJson :: Maybe Bool
tts = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#tts
, $sel:embeds:CreateResponseMessageJson :: Maybe [Embed]
embeds = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
-> Maybe [Embed]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
#embeds
, $sel:allowedMentions:CreateResponseMessageJson :: Maybe AllowedMentions
allowedMentions = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
-> Maybe AllowedMentions
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
#allowedMentions
, $sel:components:CreateResponseMessageJson :: Maybe [Component]
components = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
-> Maybe [Component]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
#components
, $sel:attachments:CreateResponseMessageJson :: Maybe [CreateMessageAttachmentJson]
attachments = Maybe [CreateMessageAttachmentJson]
attachments
, $sel:flags:CreateResponseMessageJson :: Maybe Int
flags = Maybe Int
flags
}
jsonBody :: InteractionCallback
jsonBody =
InteractionCallback
{ $sel:type_:InteractionCallback :: InteractionCallbackType
type_ = InteractionCallbackType
ChannelMessageWithSourceType
, $sel:data_:InteractionCallback :: Maybe Value
data_ = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value)
-> (CreateResponseMessageJson -> Value)
-> CreateResponseMessageJson
-> Maybe Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateResponseMessageJson -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON (CreateResponseMessageJson -> Maybe Value)
-> CreateResponseMessageJson -> Maybe Value
forall a b. (a -> b) -> a -> b
$ CreateResponseMessageJson
jsonData
}
ReqBodyMultipart
body <- [PartM IO] -> Req ReqBodyMultipart
forall (m :: * -> *). MonadIO m => [PartM IO] -> m ReqBodyMultipart
reqBodyMultipart (Text -> ByteString -> PartM IO
forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS Text
"payload_json" (InteractionCallback -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode InteractionCallback
jsonBody) PartM IO -> [PartM IO] -> [PartM IO]
forall a. a -> [a] -> [a]
: [PartM IO]
files)
ReqBodyMultipart -> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
postWith' ReqBodyMultipart
body Url 'Https
u Option 'Https
o
action (CreateResponseUpdate i
_ InteractionToken
_ InteractionCallbackMessageOptions
cm) = \Url 'Https
u Option 'Https
o -> do
let filePart :: CreateMessageAttachment -> a -> PartM IO
filePart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, ByteString
$sel:content:CreateMessageAttachment :: CreateMessageAttachment -> ByteString
content :: ByteString
content} a
n =
(forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS @IO (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"files[" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"]") ByteString
content)
{ partFilename :: Maybe String
partFilename = String -> Maybe String
forall a. a -> Maybe a
Just (Text -> String
T.unpack Text
filename)
, partContentType :: Maybe MimeType
partContentType = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (Text -> MimeType
defaultMimeLookup Text
filename)
}
attachmentPart :: CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, Maybe Text
$sel:description:CreateMessageAttachment :: CreateMessageAttachment -> Maybe Text
description :: Maybe Text
description} Int
n =
Int -> Text -> Maybe Text -> CreateMessageAttachmentJson
CreateMessageAttachmentJson Int
n Text
filename Maybe Text
description
files :: [PartM IO]
files = (CreateMessageAttachment -> Int -> PartM IO)
-> [CreateMessageAttachment] -> [Int] -> [PartM IO]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> PartM IO
forall {a}. Show a => CreateMessageAttachment -> a -> PartM IO
filePart ([CreateMessageAttachment]
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [CreateMessageAttachment] -> [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a b. (a -> b) -> a -> b
$ InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments) [(Int
0 :: Int) ..]
attachments :: Maybe [CreateMessageAttachmentJson]
attachments = (\[CreateMessageAttachment]
a -> (CreateMessageAttachment -> Int -> CreateMessageAttachmentJson)
-> [CreateMessageAttachment]
-> [Int]
-> [CreateMessageAttachmentJson]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart [CreateMessageAttachment]
a [Int
0 ..]) ([CreateMessageAttachment] -> [CreateMessageAttachmentJson])
-> Maybe [CreateMessageAttachment]
-> Maybe [CreateMessageAttachmentJson]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments
ephemeral :: Maybe Int
ephemeral = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
6 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#ephemeral
suppressEmbeds :: Maybe Int
suppressEmbeds = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#suppressEmbeds
flags :: Maybe Int
flags = Maybe Int -> Maybe Int -> (Int -> Int -> Int) -> Maybe Int
forall a. Maybe a -> Maybe a -> (a -> a -> a) -> Maybe a
foo Maybe Int
ephemeral Maybe Int
suppressEmbeds Int -> Int -> Int
forall a. Bits a => a -> a -> a
(.|.)
jsonData :: CreateResponseMessageJson
jsonData =
CreateResponseMessageJson
{ $sel:content:CreateResponseMessageJson :: Maybe Text
content = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
#content
, $sel:tts:CreateResponseMessageJson :: Maybe Bool
tts = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#tts
, $sel:embeds:CreateResponseMessageJson :: Maybe [Embed]
embeds = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
-> Maybe [Embed]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
#embeds
, $sel:allowedMentions:CreateResponseMessageJson :: Maybe AllowedMentions
allowedMentions = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
-> Maybe AllowedMentions
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
#allowedMentions
, $sel:components:CreateResponseMessageJson :: Maybe [Component]
components = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
-> Maybe [Component]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
#components
, $sel:attachments:CreateResponseMessageJson :: Maybe [CreateMessageAttachmentJson]
attachments = Maybe [CreateMessageAttachmentJson]
attachments
, $sel:flags:CreateResponseMessageJson :: Maybe Int
flags = Maybe Int
flags
}
jsonBody :: InteractionCallback
jsonBody =
InteractionCallback
{ $sel:type_:InteractionCallback :: InteractionCallbackType
type_ = InteractionCallbackType
UpdateMessageType
, $sel:data_:InteractionCallback :: Maybe Value
data_ = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value)
-> (CreateResponseMessageJson -> Value)
-> CreateResponseMessageJson
-> Maybe Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateResponseMessageJson -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON (CreateResponseMessageJson -> Maybe Value)
-> CreateResponseMessageJson -> Maybe Value
forall a b. (a -> b) -> a -> b
$ CreateResponseMessageJson
jsonData
}
ReqBodyMultipart
body <- [PartM IO] -> Req ReqBodyMultipart
forall (m :: * -> *). MonadIO m => [PartM IO] -> m ReqBodyMultipart
reqBodyMultipart (Text -> ByteString -> PartM IO
forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS Text
"payload_json" (InteractionCallback -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode InteractionCallback
jsonBody) PartM IO -> [PartM IO] -> [PartM IO]
forall a. a -> [a] -> [a]
: [PartM IO]
files)
ReqBodyMultipart -> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
postWith' ReqBodyMultipart
body Url 'Https
u Option 'Https
o
action (CreateResponseAutocomplete i
_ InteractionToken
_ InteractionCallbackAutocomplete
ao) =
let jsonBody :: InteractionCallback
jsonBody =
InteractionCallback
{ $sel:type_:InteractionCallback :: InteractionCallbackType
type_ = InteractionCallbackType
ApplicationCommandAutocompleteResultType
, $sel:data_:InteractionCallback :: Maybe Value
data_ = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value)
-> (InteractionCallbackAutocomplete -> Value)
-> InteractionCallbackAutocomplete
-> Maybe Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InteractionCallbackAutocomplete -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON (InteractionCallbackAutocomplete -> Maybe Value)
-> InteractionCallbackAutocomplete -> Maybe Value
forall a b. (a -> b) -> a -> b
$ InteractionCallbackAutocomplete
ao
}
in ReqBodyJson InteractionCallback
-> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
postWith' (InteractionCallback -> ReqBodyJson InteractionCallback
forall a. a -> ReqBodyJson a
ReqBodyJson InteractionCallback
jsonBody)
action (CreateResponseModal i
_ InteractionToken
_ InteractionCallbackModal
mo) =
let jsonBody :: InteractionCallback
jsonBody =
InteractionCallback
{ $sel:type_:InteractionCallback :: InteractionCallbackType
type_ = InteractionCallbackType
ModalType
, $sel:data_:InteractionCallback :: Maybe Value
data_ = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value)
-> (InteractionCallbackModal -> Value)
-> InteractionCallbackModal
-> Maybe Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InteractionCallbackModal -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON (InteractionCallbackModal -> Maybe Value)
-> InteractionCallbackModal -> Maybe Value
forall a b. (a -> b) -> a -> b
$ InteractionCallbackModal
mo
}
in ReqBodyJson InteractionCallback
-> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
postWith' (InteractionCallback -> ReqBodyJson InteractionCallback
forall a. a -> ReqBodyJson a
ReqBodyJson InteractionCallback
jsonBody)
action (GetOriginalInteractionResponse i
_ InteractionToken
_) = Url 'Https -> Option 'Https -> Req LbsResponse
getWith
action (EditOriginalInteractionResponse i
_ InteractionToken
_ InteractionCallbackMessageOptions
cm) = \Url 'Https
u Option 'Https
o -> do
let filePart :: CreateMessageAttachment -> a -> PartM IO
filePart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, ByteString
$sel:content:CreateMessageAttachment :: CreateMessageAttachment -> ByteString
content :: ByteString
content} a
n =
(forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS @IO (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"files[" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"]") ByteString
content)
{ partFilename :: Maybe String
partFilename = String -> Maybe String
forall a. a -> Maybe a
Just (Text -> String
T.unpack Text
filename)
, partContentType :: Maybe MimeType
partContentType = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (Text -> MimeType
defaultMimeLookup Text
filename)
}
attachmentPart :: CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, Maybe Text
$sel:description:CreateMessageAttachment :: CreateMessageAttachment -> Maybe Text
description :: Maybe Text
description} Int
n =
Int -> Text -> Maybe Text -> CreateMessageAttachmentJson
CreateMessageAttachmentJson Int
n Text
filename Maybe Text
description
files :: [PartM IO]
files = (CreateMessageAttachment -> Int -> PartM IO)
-> [CreateMessageAttachment] -> [Int] -> [PartM IO]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> PartM IO
forall {a}. Show a => CreateMessageAttachment -> a -> PartM IO
filePart ([CreateMessageAttachment]
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [CreateMessageAttachment] -> [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a b. (a -> b) -> a -> b
$ InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments) [(Int
0 :: Int) ..]
attachments :: Maybe [CreateMessageAttachmentJson]
attachments = (\[CreateMessageAttachment]
a -> (CreateMessageAttachment -> Int -> CreateMessageAttachmentJson)
-> [CreateMessageAttachment]
-> [Int]
-> [CreateMessageAttachmentJson]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart [CreateMessageAttachment]
a [Int
0 ..]) ([CreateMessageAttachment] -> [CreateMessageAttachmentJson])
-> Maybe [CreateMessageAttachment]
-> Maybe [CreateMessageAttachmentJson]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments
ephemeral :: Maybe Int
ephemeral = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
6 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#ephemeral
suppressEmbeds :: Maybe Int
suppressEmbeds = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#suppressEmbeds
flags :: Maybe Int
flags = Maybe Int -> Maybe Int -> (Int -> Int -> Int) -> Maybe Int
forall a. Maybe a -> Maybe a -> (a -> a -> a) -> Maybe a
foo Maybe Int
ephemeral Maybe Int
suppressEmbeds Int -> Int -> Int
forall a. Bits a => a -> a -> a
(.|.)
jsonData :: CreateResponseMessageJson
jsonData =
CreateResponseMessageJson
{ $sel:content:CreateResponseMessageJson :: Maybe Text
content = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
#content
, $sel:tts:CreateResponseMessageJson :: Maybe Bool
tts = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#tts
, $sel:embeds:CreateResponseMessageJson :: Maybe [Embed]
embeds = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
-> Maybe [Embed]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
#embeds
, $sel:allowedMentions:CreateResponseMessageJson :: Maybe AllowedMentions
allowedMentions = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
-> Maybe AllowedMentions
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
#allowedMentions
, $sel:components:CreateResponseMessageJson :: Maybe [Component]
components = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
-> Maybe [Component]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
#components
, $sel:attachments:CreateResponseMessageJson :: Maybe [CreateMessageAttachmentJson]
attachments = Maybe [CreateMessageAttachmentJson]
attachments
, $sel:flags:CreateResponseMessageJson :: Maybe Int
flags = Maybe Int
flags
}
jsonBody :: InteractionCallback
jsonBody =
InteractionCallback
{ $sel:type_:InteractionCallback :: InteractionCallbackType
type_ = InteractionCallbackType
UpdateMessageType
, $sel:data_:InteractionCallback :: Maybe Value
data_ = Value -> Maybe Value
forall a. a -> Maybe a
Just (Value -> Maybe Value)
-> (CreateResponseMessageJson -> Value)
-> CreateResponseMessageJson
-> Maybe Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateResponseMessageJson -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON (CreateResponseMessageJson -> Maybe Value)
-> CreateResponseMessageJson -> Maybe Value
forall a b. (a -> b) -> a -> b
$ CreateResponseMessageJson
jsonData
}
ReqBodyMultipart
body <- [PartM IO] -> Req ReqBodyMultipart
forall (m :: * -> *). MonadIO m => [PartM IO] -> m ReqBodyMultipart
reqBodyMultipart (Text -> ByteString -> PartM IO
forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS Text
"payload_json" (InteractionCallback -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode InteractionCallback
jsonBody) PartM IO -> [PartM IO] -> [PartM IO]
forall a. a -> [a] -> [a]
: [PartM IO]
files)
ReqBodyMultipart -> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
patchWith' ReqBodyMultipart
body Url 'Https
u Option 'Https
o
action (DeleteOriginalInteractionResponse i
_ InteractionToken
_) = Url 'Https -> Option 'Https -> Req LbsResponse
deleteWith
action (CreateFollowupMessage i
_ InteractionToken
_ InteractionCallbackMessageOptions
cm) = \Url 'Https
u Option 'Https
o -> do
let filePart :: CreateMessageAttachment -> a -> PartM IO
filePart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, ByteString
$sel:content:CreateMessageAttachment :: CreateMessageAttachment -> ByteString
content :: ByteString
content} a
n =
(forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS @IO (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"files[" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"]") ByteString
content)
{ partFilename :: Maybe String
partFilename = String -> Maybe String
forall a. a -> Maybe a
Just (Text -> String
T.unpack Text
filename)
, partContentType :: Maybe MimeType
partContentType = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (Text -> MimeType
defaultMimeLookup Text
filename)
}
attachmentPart :: CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, Maybe Text
$sel:description:CreateMessageAttachment :: CreateMessageAttachment -> Maybe Text
description :: Maybe Text
description} Int
n =
Int -> Text -> Maybe Text -> CreateMessageAttachmentJson
CreateMessageAttachmentJson Int
n Text
filename Maybe Text
description
files :: [PartM IO]
files = (CreateMessageAttachment -> Int -> PartM IO)
-> [CreateMessageAttachment] -> [Int] -> [PartM IO]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> PartM IO
forall {a}. Show a => CreateMessageAttachment -> a -> PartM IO
filePart ([CreateMessageAttachment]
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [CreateMessageAttachment] -> [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a b. (a -> b) -> a -> b
$ InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments) [(Int
0 :: Int) ..]
attachments :: Maybe [CreateMessageAttachmentJson]
attachments = (\[CreateMessageAttachment]
a -> (CreateMessageAttachment -> Int -> CreateMessageAttachmentJson)
-> [CreateMessageAttachment]
-> [Int]
-> [CreateMessageAttachmentJson]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart [CreateMessageAttachment]
a [Int
0 ..]) ([CreateMessageAttachment] -> [CreateMessageAttachmentJson])
-> Maybe [CreateMessageAttachment]
-> Maybe [CreateMessageAttachmentJson]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments
ephemeral :: Maybe Int
ephemeral = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
6 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#ephemeral
suppressEmbeds :: Maybe Int
suppressEmbeds = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#suppressEmbeds
flags :: Maybe Int
flags = Maybe Int -> Maybe Int -> (Int -> Int -> Int) -> Maybe Int
forall a. Maybe a -> Maybe a -> (a -> a -> a) -> Maybe a
foo Maybe Int
ephemeral Maybe Int
suppressEmbeds Int -> Int -> Int
forall a. Bits a => a -> a -> a
(.|.)
jsonData :: CreateResponseMessageJson
jsonData =
CreateResponseMessageJson
{ $sel:content:CreateResponseMessageJson :: Maybe Text
content = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
#content
, $sel:tts:CreateResponseMessageJson :: Maybe Bool
tts = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#tts
, $sel:embeds:CreateResponseMessageJson :: Maybe [Embed]
embeds = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
-> Maybe [Embed]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
#embeds
, $sel:allowedMentions:CreateResponseMessageJson :: Maybe AllowedMentions
allowedMentions = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
-> Maybe AllowedMentions
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
#allowedMentions
, $sel:components:CreateResponseMessageJson :: Maybe [Component]
components = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
-> Maybe [Component]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
#components
, $sel:attachments:CreateResponseMessageJson :: Maybe [CreateMessageAttachmentJson]
attachments = Maybe [CreateMessageAttachmentJson]
attachments
, $sel:flags:CreateResponseMessageJson :: Maybe Int
flags = Maybe Int
flags
}
ReqBodyMultipart
body <- [PartM IO] -> Req ReqBodyMultipart
forall (m :: * -> *). MonadIO m => [PartM IO] -> m ReqBodyMultipart
reqBodyMultipart (Text -> ByteString -> PartM IO
forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS Text
"payload_json" (CreateResponseMessageJson -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode CreateResponseMessageJson
jsonData) PartM IO -> [PartM IO] -> [PartM IO]
forall a. a -> [a] -> [a]
: [PartM IO]
files)
ReqBodyMultipart -> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
postWith' ReqBodyMultipart
body Url 'Https
u Option 'Https
o
action GetFollowupMessage {} = Url 'Https -> Option 'Https -> Req LbsResponse
getWith
action (EditFollowupMessage i
_ m
_ InteractionToken
_ InteractionCallbackMessageOptions
cm) = \Url 'Https
u Option 'Https
o -> do
let filePart :: CreateMessageAttachment -> a -> PartM IO
filePart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, ByteString
$sel:content:CreateMessageAttachment :: CreateMessageAttachment -> ByteString
content :: ByteString
content} a
n =
(forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS @IO (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"files[" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> a -> String
forall a. Show a => a -> String
show a
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"]") ByteString
content)
{ partFilename :: Maybe String
partFilename = String -> Maybe String
forall a. a -> Maybe a
Just (Text -> String
T.unpack Text
filename)
, partContentType :: Maybe MimeType
partContentType = MimeType -> Maybe MimeType
forall a. a -> Maybe a
Just (Text -> MimeType
defaultMimeLookup Text
filename)
}
attachmentPart :: CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, Maybe Text
$sel:description:CreateMessageAttachment :: CreateMessageAttachment -> Maybe Text
description :: Maybe Text
description} Int
n =
Int -> Text -> Maybe Text -> CreateMessageAttachmentJson
CreateMessageAttachmentJson Int
n Text
filename Maybe Text
description
files :: [PartM IO]
files = (CreateMessageAttachment -> Int -> PartM IO)
-> [CreateMessageAttachment] -> [Int] -> [PartM IO]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> PartM IO
forall {a}. Show a => CreateMessageAttachment -> a -> PartM IO
filePart ([CreateMessageAttachment]
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [CreateMessageAttachment] -> [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment] -> [CreateMessageAttachment]
forall a b. (a -> b) -> a -> b
$ InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments) [(Int
0 :: Int) ..]
attachments :: Maybe [CreateMessageAttachmentJson]
attachments = (\[CreateMessageAttachment]
a -> (CreateMessageAttachment -> Int -> CreateMessageAttachmentJson)
-> [CreateMessageAttachment]
-> [Int]
-> [CreateMessageAttachmentJson]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart [CreateMessageAttachment]
a [Int
0 ..]) ([CreateMessageAttachment] -> [CreateMessageAttachmentJson])
-> Maybe [CreateMessageAttachment]
-> Maybe [CreateMessageAttachmentJson]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
-> Maybe [CreateMessageAttachment]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe [CreateMessageAttachment])
#attachments
ephemeral :: Maybe Int
ephemeral = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
6 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#ephemeral
suppressEmbeds :: Maybe Int
suppressEmbeds = (\Bool
f -> if Bool
f then Int
1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
2 else Int
0) (Bool -> Int) -> Maybe Bool -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#suppressEmbeds
flags :: Maybe Int
flags = Maybe Int -> Maybe Int -> (Int -> Int -> Int) -> Maybe Int
forall a. Maybe a -> Maybe a -> (a -> a -> a) -> Maybe a
foo Maybe Int
ephemeral Maybe Int
suppressEmbeds Int -> Int -> Int
forall a. Bits a => a -> a -> a
(.|.)
jsonData :: CreateResponseMessageJson
jsonData =
CreateResponseMessageJson
{ $sel:content:CreateResponseMessageJson :: Maybe Text
content = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
-> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Text)
#content
, $sel:tts:CreateResponseMessageJson :: Maybe Bool
tts = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
-> Maybe Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx InteractionCallbackMessageOptions (Maybe Bool)
#tts
, $sel:embeds:CreateResponseMessageJson :: Maybe [Embed]
embeds = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
-> Maybe [Embed]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Embed])
#embeds
, $sel:allowedMentions:CreateResponseMessageJson :: Maybe AllowedMentions
allowedMentions = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
-> Maybe AllowedMentions
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens
NoIx
InteractionCallbackMessageOptions
(Maybe AllowedMentions)
#allowedMentions
, $sel:components:CreateResponseMessageJson :: Maybe [Component]
components = InteractionCallbackMessageOptions
cm InteractionCallbackMessageOptions
-> Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
-> Maybe [Component]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic'
A_Lens NoIx InteractionCallbackMessageOptions (Maybe [Component])
#components
, $sel:attachments:CreateResponseMessageJson :: Maybe [CreateMessageAttachmentJson]
attachments = Maybe [CreateMessageAttachmentJson]
attachments
, $sel:flags:CreateResponseMessageJson :: Maybe Int
flags = Maybe Int
flags
}
ReqBodyMultipart
body <- [PartM IO] -> Req ReqBodyMultipart
forall (m :: * -> *). MonadIO m => [PartM IO] -> m ReqBodyMultipart
reqBodyMultipart (Text -> ByteString -> PartM IO
forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS Text
"payload_json" (CreateResponseMessageJson -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode CreateResponseMessageJson
jsonData) PartM IO -> [PartM IO] -> [PartM IO]
forall a. a -> [a] -> [a]
: [PartM IO]
files)
ReqBodyMultipart -> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
patchWith' ReqBodyMultipart
body Url 'Https
u Option 'Https
o
action DeleteFollowupMessage {} = Url 'Https -> Option 'Https -> Req LbsResponse
deleteWith