-- | Webhook endpoints
module Calamity.HTTP.Webhook (
  WebhookRequest (..),
  CreateWebhookData (..),
  ModifyWebhookData (..),
  ExecuteWebhookOptions (..),
) where

import Calamity.HTTP.Channel (AllowedMentions, CreateMessageAttachment (..))
import Calamity.HTTP.Internal.Request
import Calamity.HTTP.Internal.Route
import Calamity.Internal.AesonThings
import Calamity.Types.Model.Channel
import Calamity.Types.Model.Guild
import Calamity.Types.Snowflake
import Control.Lens hiding ((.=))
import Data.Aeson
import Data.Default.Class
import Data.Text (Text)
import qualified Data.Text as T
import GHC.Generics
import Network.HTTP.Client.MultipartFormData
import Network.HTTP.Req
import Network.Mime
import PyF

data CreateWebhookData = CreateWebhookData
  { CreateWebhookData -> Maybe Text
username :: Maybe Text
  , -- | The avatar field should be in discord's image data format: https://discord.com/developers/docs/reference#image-data
    CreateWebhookData -> Maybe Text
avatar :: Maybe Text
  }
  deriving (Int -> CreateWebhookData -> ShowS
[CreateWebhookData] -> ShowS
CreateWebhookData -> String
(Int -> CreateWebhookData -> ShowS)
-> (CreateWebhookData -> String)
-> ([CreateWebhookData] -> ShowS)
-> Show CreateWebhookData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWebhookData] -> ShowS
$cshowList :: [CreateWebhookData] -> ShowS
show :: CreateWebhookData -> String
$cshow :: CreateWebhookData -> String
showsPrec :: Int -> CreateWebhookData -> ShowS
$cshowsPrec :: Int -> CreateWebhookData -> ShowS
Show, (forall x. CreateWebhookData -> Rep CreateWebhookData x)
-> (forall x. Rep CreateWebhookData x -> CreateWebhookData)
-> Generic CreateWebhookData
forall x. Rep CreateWebhookData x -> CreateWebhookData
forall x. CreateWebhookData -> Rep CreateWebhookData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateWebhookData x -> CreateWebhookData
$cfrom :: forall x. CreateWebhookData -> Rep CreateWebhookData x
Generic, CreateWebhookData
CreateWebhookData -> Default CreateWebhookData
forall a. a -> Default a
def :: CreateWebhookData
$cdef :: CreateWebhookData
Default)
  deriving ([CreateWebhookData] -> Encoding
[CreateWebhookData] -> Value
CreateWebhookData -> Encoding
CreateWebhookData -> Value
(CreateWebhookData -> Value)
-> (CreateWebhookData -> Encoding)
-> ([CreateWebhookData] -> Value)
-> ([CreateWebhookData] -> Encoding)
-> ToJSON CreateWebhookData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CreateWebhookData] -> Encoding
$ctoEncodingList :: [CreateWebhookData] -> Encoding
toJSONList :: [CreateWebhookData] -> Value
$ctoJSONList :: [CreateWebhookData] -> Value
toEncoding :: CreateWebhookData -> Encoding
$ctoEncoding :: CreateWebhookData -> Encoding
toJSON :: CreateWebhookData -> Value
$ctoJSON :: CreateWebhookData -> Value
ToJSON) via CalamityJSON CreateWebhookData

data ModifyWebhookData = ModifyWebhookData
  { ModifyWebhookData -> Maybe Text
username :: Maybe Text
  , -- | The avatar field should be in discord's image data format: https://discord.com/developers/docs/reference#image-data
    ModifyWebhookData -> Maybe Text
avatar :: Maybe Text
  , ModifyWebhookData -> Maybe (Snowflake Channel)
channelID :: Maybe (Snowflake Channel)
  }
  deriving (Int -> ModifyWebhookData -> ShowS
[ModifyWebhookData] -> ShowS
ModifyWebhookData -> String
(Int -> ModifyWebhookData -> ShowS)
-> (ModifyWebhookData -> String)
-> ([ModifyWebhookData] -> ShowS)
-> Show ModifyWebhookData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyWebhookData] -> ShowS
$cshowList :: [ModifyWebhookData] -> ShowS
show :: ModifyWebhookData -> String
$cshow :: ModifyWebhookData -> String
showsPrec :: Int -> ModifyWebhookData -> ShowS
$cshowsPrec :: Int -> ModifyWebhookData -> ShowS
Show, (forall x. ModifyWebhookData -> Rep ModifyWebhookData x)
-> (forall x. Rep ModifyWebhookData x -> ModifyWebhookData)
-> Generic ModifyWebhookData
forall x. Rep ModifyWebhookData x -> ModifyWebhookData
forall x. ModifyWebhookData -> Rep ModifyWebhookData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModifyWebhookData x -> ModifyWebhookData
$cfrom :: forall x. ModifyWebhookData -> Rep ModifyWebhookData x
Generic, ModifyWebhookData
ModifyWebhookData -> Default ModifyWebhookData
forall a. a -> Default a
def :: ModifyWebhookData
$cdef :: ModifyWebhookData
Default)
  deriving ([ModifyWebhookData] -> Encoding
[ModifyWebhookData] -> Value
ModifyWebhookData -> Encoding
ModifyWebhookData -> Value
(ModifyWebhookData -> Value)
-> (ModifyWebhookData -> Encoding)
-> ([ModifyWebhookData] -> Value)
-> ([ModifyWebhookData] -> Encoding)
-> ToJSON ModifyWebhookData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ModifyWebhookData] -> Encoding
$ctoEncodingList :: [ModifyWebhookData] -> Encoding
toJSONList :: [ModifyWebhookData] -> Value
$ctoJSONList :: [ModifyWebhookData] -> Value
toEncoding :: ModifyWebhookData -> Encoding
$ctoEncoding :: ModifyWebhookData -> Encoding
toJSON :: ModifyWebhookData -> Value
$ctoJSON :: ModifyWebhookData -> Value
ToJSON) via CalamityJSON ModifyWebhookData

data ExecuteWebhookOptions = ExecuteWebhookOptions
  { ExecuteWebhookOptions -> Maybe Bool
wait :: Maybe Bool
  , ExecuteWebhookOptions -> Maybe Text
content :: Maybe Text
  , ExecuteWebhookOptions -> [CreateMessageAttachment]
attachments :: [CreateMessageAttachment]
  , ExecuteWebhookOptions -> Maybe [Embed]
embeds :: Maybe [Embed]
  , ExecuteWebhookOptions -> Maybe Text
username :: Maybe Text
  , ExecuteWebhookOptions -> Maybe Text
avatarUrl :: Maybe Text
  , ExecuteWebhookOptions -> Maybe AllowedMentions
allowedMentions :: Maybe AllowedMentions
  , ExecuteWebhookOptions -> Maybe Bool
tts :: Maybe Bool
  , ExecuteWebhookOptions -> [Component]
components :: [Component]
  }
  deriving (Int -> ExecuteWebhookOptions -> ShowS
[ExecuteWebhookOptions] -> ShowS
ExecuteWebhookOptions -> String
(Int -> ExecuteWebhookOptions -> ShowS)
-> (ExecuteWebhookOptions -> String)
-> ([ExecuteWebhookOptions] -> ShowS)
-> Show ExecuteWebhookOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecuteWebhookOptions] -> ShowS
$cshowList :: [ExecuteWebhookOptions] -> ShowS
show :: ExecuteWebhookOptions -> String
$cshow :: ExecuteWebhookOptions -> String
showsPrec :: Int -> ExecuteWebhookOptions -> ShowS
$cshowsPrec :: Int -> ExecuteWebhookOptions -> ShowS
Show, (forall x. ExecuteWebhookOptions -> Rep ExecuteWebhookOptions x)
-> (forall x. Rep ExecuteWebhookOptions x -> ExecuteWebhookOptions)
-> Generic ExecuteWebhookOptions
forall x. Rep ExecuteWebhookOptions x -> ExecuteWebhookOptions
forall x. ExecuteWebhookOptions -> Rep ExecuteWebhookOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExecuteWebhookOptions x -> ExecuteWebhookOptions
$cfrom :: forall x. ExecuteWebhookOptions -> Rep ExecuteWebhookOptions x
Generic, ExecuteWebhookOptions
ExecuteWebhookOptions -> Default ExecuteWebhookOptions
forall a. a -> Default a
def :: ExecuteWebhookOptions
$cdef :: ExecuteWebhookOptions
Default)

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
showList :: [CreateMessageAttachmentJson] -> ShowS
$cshowList :: [CreateMessageAttachmentJson] -> ShowS
show :: CreateMessageAttachmentJson -> String
$cshow :: CreateMessageAttachmentJson -> String
showsPrec :: Int -> CreateMessageAttachmentJson -> ShowS
$cshowsPrec :: Int -> CreateMessageAttachmentJson -> ShowS
Show, (forall x.
 CreateMessageAttachmentJson -> Rep CreateMessageAttachmentJson x)
-> (forall x.
    Rep CreateMessageAttachmentJson x -> CreateMessageAttachmentJson)
-> Generic CreateMessageAttachmentJson
forall x.
Rep CreateMessageAttachmentJson x -> CreateMessageAttachmentJson
forall x.
CreateMessageAttachmentJson -> Rep CreateMessageAttachmentJson x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateMessageAttachmentJson x -> CreateMessageAttachmentJson
$cfrom :: forall x.
CreateMessageAttachmentJson -> Rep CreateMessageAttachmentJson x
Generic)
  deriving ([CreateMessageAttachmentJson] -> Encoding
[CreateMessageAttachmentJson] -> Value
CreateMessageAttachmentJson -> Encoding
CreateMessageAttachmentJson -> Value
(CreateMessageAttachmentJson -> Value)
-> (CreateMessageAttachmentJson -> Encoding)
-> ([CreateMessageAttachmentJson] -> Value)
-> ([CreateMessageAttachmentJson] -> Encoding)
-> ToJSON CreateMessageAttachmentJson
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CreateMessageAttachmentJson] -> Encoding
$ctoEncodingList :: [CreateMessageAttachmentJson] -> Encoding
toJSONList :: [CreateMessageAttachmentJson] -> Value
$ctoJSONList :: [CreateMessageAttachmentJson] -> Value
toEncoding :: CreateMessageAttachmentJson -> Encoding
$ctoEncoding :: CreateMessageAttachmentJson -> Encoding
toJSON :: CreateMessageAttachmentJson -> Value
$ctoJSON :: CreateMessageAttachmentJson -> Value
ToJSON) via CalamityJSON CreateMessageAttachmentJson

data ExecuteWebhookJson = ExecuteWebhookJson
  { ExecuteWebhookJson -> Maybe Text
content :: Maybe Text
  , ExecuteWebhookJson -> Maybe [Embed]
embeds :: Maybe [Embed]
  , ExecuteWebhookJson -> Maybe Text
username :: Maybe Text
  , ExecuteWebhookJson -> Maybe Text
avatarUrl :: Maybe Text
  , ExecuteWebhookJson -> Maybe Bool
tts :: Maybe Bool
  , ExecuteWebhookJson -> [CreateMessageAttachmentJson]
attachments :: [CreateMessageAttachmentJson]
  , ExecuteWebhookJson -> Maybe AllowedMentions
allowedMentions :: Maybe AllowedMentions
  , ExecuteWebhookJson -> [Component]
components :: [Component]
  }
  deriving (Int -> ExecuteWebhookJson -> ShowS
[ExecuteWebhookJson] -> ShowS
ExecuteWebhookJson -> String
(Int -> ExecuteWebhookJson -> ShowS)
-> (ExecuteWebhookJson -> String)
-> ([ExecuteWebhookJson] -> ShowS)
-> Show ExecuteWebhookJson
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecuteWebhookJson] -> ShowS
$cshowList :: [ExecuteWebhookJson] -> ShowS
show :: ExecuteWebhookJson -> String
$cshow :: ExecuteWebhookJson -> String
showsPrec :: Int -> ExecuteWebhookJson -> ShowS
$cshowsPrec :: Int -> ExecuteWebhookJson -> ShowS
Show, (forall x. ExecuteWebhookJson -> Rep ExecuteWebhookJson x)
-> (forall x. Rep ExecuteWebhookJson x -> ExecuteWebhookJson)
-> Generic ExecuteWebhookJson
forall x. Rep ExecuteWebhookJson x -> ExecuteWebhookJson
forall x. ExecuteWebhookJson -> Rep ExecuteWebhookJson x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExecuteWebhookJson x -> ExecuteWebhookJson
$cfrom :: forall x. ExecuteWebhookJson -> Rep ExecuteWebhookJson x
Generic)
  deriving ([ExecuteWebhookJson] -> Encoding
[ExecuteWebhookJson] -> Value
ExecuteWebhookJson -> Encoding
ExecuteWebhookJson -> Value
(ExecuteWebhookJson -> Value)
-> (ExecuteWebhookJson -> Encoding)
-> ([ExecuteWebhookJson] -> Value)
-> ([ExecuteWebhookJson] -> Encoding)
-> ToJSON ExecuteWebhookJson
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ExecuteWebhookJson] -> Encoding
$ctoEncodingList :: [ExecuteWebhookJson] -> Encoding
toJSONList :: [ExecuteWebhookJson] -> Value
$ctoJSONList :: [ExecuteWebhookJson] -> Value
toEncoding :: ExecuteWebhookJson -> Encoding
$ctoEncoding :: ExecuteWebhookJson -> Encoding
toJSON :: ExecuteWebhookJson -> Value
$ctoJSON :: ExecuteWebhookJson -> Value
ToJSON) via CalamityJSON ExecuteWebhookJson

data WebhookRequest a where
  CreateWebhook :: HasID Channel c => c -> CreateWebhookData -> WebhookRequest Webhook
  GetChannelWebhooks :: HasID Channel c => c -> WebhookRequest [Webhook]
  GetGuildWebhooks :: HasID Guild c => c -> WebhookRequest [Webhook]
  GetWebhook :: HasID Webhook w => w -> WebhookRequest Webhook
  GetWebhookToken :: HasID Webhook w => w -> Text -> WebhookRequest Webhook
  ModifyWebhook :: HasID Webhook w => w -> ModifyWebhookData -> WebhookRequest Webhook
  ModifyWebhookToken :: HasID Webhook w => w -> Text -> ModifyWebhookData -> WebhookRequest Webhook
  DeleteWebhook :: HasID Webhook w => w -> WebhookRequest ()
  DeleteWebhookToken :: HasID Webhook w => w -> Text -> WebhookRequest ()
  ExecuteWebhook :: HasID Webhook w => w -> Text -> ExecuteWebhookOptions -> WebhookRequest ()

baseRoute :: Snowflake Webhook -> RouteBuilder _
baseRoute :: Snowflake Webhook
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
baseRoute Snowflake Webhook
id = 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 Webhook -> ConsRes (ID Webhook) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// ID Webhook
forall k (a :: k). ID a
ID @Webhook RouteBuilder '[ '( 'IDRequirement Webhook, 'Required)]
-> (RouteBuilder '[ '( 'IDRequirement Webhook, 'Required)]
    -> RouteBuilder
         '[ '( 'IDRequirement Webhook, 'Satisfied),
            '( 'IDRequirement Webhook, 'Required)])
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
forall a b. a -> (a -> b) -> b
& Snowflake Webhook
-> RouteBuilder '[ '( 'IDRequirement Webhook, 'Required)]
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Webhook
id

instance Request (WebhookRequest a) where
  type Result (WebhookRequest a) = a

  route :: WebhookRequest a -> Route
route (CreateWebhook (forall a. HasID Channel a => a -> Snowflake Channel
forall b a. HasID b a => a -> Snowflake b
getID @Channel -> Snowflake Channel
cid) CreateWebhookData
_) =
    RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"channels" RouteBuilder '[] -> ID Channel -> ConsRes (ID Channel) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// ID Channel
forall k (a :: k). ID a
ID @Channel RouteBuilder '[ '( 'IDRequirement Channel, 'Required)]
-> S -> ConsRes S '[ '( 'IDRequirement Channel, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"webhooks"
      RouteBuilder '[ '( 'IDRequirement Channel, 'Required)]
-> (RouteBuilder '[ '( 'IDRequirement Channel, 'Required)]
    -> RouteBuilder
         '[ '( 'IDRequirement Channel, 'Satisfied),
            '( 'IDRequirement Channel, 'Required)])
-> RouteBuilder
     '[ '( 'IDRequirement Channel, 'Satisfied),
        '( 'IDRequirement Channel, 'Required)]
forall a b. a -> (a -> b) -> b
& Snowflake Channel
-> RouteBuilder '[ '( 'IDRequirement Channel, 'Required)]
-> RouteBuilder
     '[ '( 'IDRequirement Channel, 'Satisfied),
        '( 'IDRequirement Channel, 'Required)]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Channel
cid
      RouteBuilder
  '[ '( 'IDRequirement Channel, 'Satisfied),
     '( 'IDRequirement Channel, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Channel, 'Satisfied),
         '( 'IDRequirement Channel, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Channel, 'Satisfied),
     '( 'IDRequirement Channel, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (GetChannelWebhooks (forall a. HasID Channel a => a -> Snowflake Channel
forall b a. HasID b a => a -> Snowflake b
getID @Channel -> Snowflake Channel
cid)) =
    RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"channels" RouteBuilder '[] -> ID Channel -> ConsRes (ID Channel) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// ID Channel
forall k (a :: k). ID a
ID @Channel RouteBuilder '[ '( 'IDRequirement Channel, 'Required)]
-> S -> ConsRes S '[ '( 'IDRequirement Channel, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"webhooks"
      RouteBuilder '[ '( 'IDRequirement Channel, 'Required)]
-> (RouteBuilder '[ '( 'IDRequirement Channel, 'Required)]
    -> RouteBuilder
         '[ '( 'IDRequirement Channel, 'Satisfied),
            '( 'IDRequirement Channel, 'Required)])
-> RouteBuilder
     '[ '( 'IDRequirement Channel, 'Satisfied),
        '( 'IDRequirement Channel, 'Required)]
forall a b. a -> (a -> b) -> b
& Snowflake Channel
-> RouteBuilder '[ '( 'IDRequirement Channel, 'Required)]
-> RouteBuilder
     '[ '( 'IDRequirement Channel, 'Satisfied),
        '( 'IDRequirement Channel, 'Required)]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Channel
cid
      RouteBuilder
  '[ '( 'IDRequirement Channel, 'Satisfied),
     '( 'IDRequirement Channel, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Channel, 'Satisfied),
         '( 'IDRequirement Channel, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Channel, 'Satisfied),
     '( 'IDRequirement Channel, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (GetGuildWebhooks (forall a. HasID Guild a => a -> Snowflake Guild
forall b a. HasID b a => a -> Snowflake b
getID @Guild -> Snowflake Guild
gid)) =
    RouteBuilder '[]
mkRouteBuilder RouteBuilder '[] -> S -> ConsRes S '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"guilds" RouteBuilder '[] -> ID Guild -> ConsRes (ID Guild) '[]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// ID Guild
forall k (a :: k). ID a
ID @Guild RouteBuilder '[ '( 'IDRequirement Guild, 'Required)]
-> S -> ConsRes S '[ '( 'IDRequirement Guild, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
"webhooks"
      RouteBuilder '[ '( 'IDRequirement Guild, 'Required)]
-> (RouteBuilder '[ '( 'IDRequirement Guild, 'Required)]
    -> RouteBuilder
         '[ '( 'IDRequirement Guild, 'Satisfied),
            '( 'IDRequirement Guild, 'Required)])
-> RouteBuilder
     '[ '( 'IDRequirement Guild, 'Satisfied),
        '( 'IDRequirement Guild, 'Required)]
forall a b. a -> (a -> b) -> b
& Snowflake Guild
-> RouteBuilder '[ '( 'IDRequirement Guild, 'Required)]
-> RouteBuilder
     '[ '( 'IDRequirement Guild, 'Satisfied),
        '( 'IDRequirement Guild, 'Required)]
forall t (reqs :: [(RequirementType, RouteRequirement)]).
Typeable t =>
Snowflake t
-> RouteBuilder reqs
-> RouteBuilder ('( 'IDRequirement t, 'Satisfied) : reqs)
giveID Snowflake Guild
gid
      RouteBuilder
  '[ '( 'IDRequirement Guild, 'Satisfied),
     '( 'IDRequirement Guild, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Guild, 'Satisfied),
         '( 'IDRequirement Guild, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Guild, 'Satisfied),
     '( 'IDRequirement Guild, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (GetWebhook (forall a. HasID Webhook a => a -> Snowflake Webhook
forall b a. HasID b a => a -> Snowflake b
getID @Webhook -> Snowflake Webhook
wid)) =
    Snowflake Webhook
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
baseRoute Snowflake Webhook
wid
      RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Webhook, 'Satisfied),
         '( 'IDRequirement Webhook, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (GetWebhookToken (forall a. HasID Webhook a => a -> Snowflake Webhook
forall b a. HasID b a => a -> Snowflake b
getID @Webhook -> Snowflake Webhook
wid) Text
t) =
    Snowflake Webhook
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
baseRoute Snowflake Webhook
wid RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> S
-> ConsRes
     S
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
t
      RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Webhook, 'Satisfied),
         '( 'IDRequirement Webhook, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (ModifyWebhook (forall a. HasID Webhook a => a -> Snowflake Webhook
forall b a. HasID b a => a -> Snowflake b
getID @Webhook -> Snowflake Webhook
wid) ModifyWebhookData
_) =
    Snowflake Webhook
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
baseRoute Snowflake Webhook
wid
      RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Webhook, 'Satisfied),
         '( 'IDRequirement Webhook, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (ModifyWebhookToken (forall a. HasID Webhook a => a -> Snowflake Webhook
forall b a. HasID b a => a -> Snowflake b
getID @Webhook -> Snowflake Webhook
wid) Text
t ModifyWebhookData
_) =
    Snowflake Webhook
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
baseRoute Snowflake Webhook
wid RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> S
-> ConsRes
     S
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
t
      RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Webhook, 'Satisfied),
         '( 'IDRequirement Webhook, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (DeleteWebhook (forall a. HasID Webhook a => a -> Snowflake Webhook
forall b a. HasID b a => a -> Snowflake b
getID @Webhook -> Snowflake Webhook
wid)) =
    Snowflake Webhook
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
baseRoute Snowflake Webhook
wid
      RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Webhook, 'Satisfied),
         '( 'IDRequirement Webhook, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (DeleteWebhookToken (forall a. HasID Webhook a => a -> Snowflake Webhook
forall b a. HasID b a => a -> Snowflake b
getID @Webhook -> Snowflake Webhook
wid) Text
t) =
    Snowflake Webhook
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
baseRoute Snowflake Webhook
wid RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> S
-> ConsRes
     S
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
t
      RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Webhook, 'Satisfied),
         '( 'IDRequirement Webhook, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute
  route (ExecuteWebhook (forall a. HasID Webhook a => a -> Snowflake Webhook
forall b a. HasID b a => a -> Snowflake b
getID @Webhook -> Snowflake Webhook
wid) Text
t ExecuteWebhookOptions
_) =
    Snowflake Webhook
-> RouteBuilder
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
baseRoute Snowflake Webhook
wid RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> S
-> ConsRes
     S
     '[ '( 'IDRequirement Webhook, 'Satisfied),
        '( 'IDRequirement Webhook, 'Required)]
forall a (reqs :: [(RequirementType, RouteRequirement)]).
RouteFragmentable a reqs =>
RouteBuilder reqs -> a -> ConsRes a reqs
// Text -> S
S Text
t
      RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> (RouteBuilder
      '[ '( 'IDRequirement Webhook, 'Satisfied),
         '( 'IDRequirement Webhook, 'Required)]
    -> Route)
-> Route
forall a b. a -> (a -> b) -> b
& RouteBuilder
  '[ '( 'IDRequirement Webhook, 'Satisfied),
     '( 'IDRequirement Webhook, 'Required)]
-> Route
forall (reqs :: [(RequirementType, RouteRequirement)]).
EnsureFulfilled reqs =>
RouteBuilder reqs -> Route
buildRoute

  action :: WebhookRequest a -> Url 'Https -> Option 'Https -> Req LbsResponse
action (CreateWebhook c
_ CreateWebhookData
o) = ReqBodyJson CreateWebhookData
-> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
postWith' (ReqBodyJson CreateWebhookData
 -> Url 'Https -> Option 'Https -> Req LbsResponse)
-> ReqBodyJson CreateWebhookData
-> Url 'Https
-> Option 'Https
-> Req LbsResponse
forall a b. (a -> b) -> a -> b
$ CreateWebhookData -> ReqBodyJson CreateWebhookData
forall a. a -> ReqBodyJson a
ReqBodyJson CreateWebhookData
o
  action (GetChannelWebhooks c
_) = Url 'Https -> Option 'Https -> Req LbsResponse
getWith
  action (GetGuildWebhooks c
_) = Url 'Https -> Option 'Https -> Req LbsResponse
getWith
  action (GetWebhook w
_) = Url 'Https -> Option 'Https -> Req LbsResponse
getWith
  action (GetWebhookToken w
_ Text
_) = Url 'Https -> Option 'Https -> Req LbsResponse
getWith
  action (ModifyWebhook w
_ ModifyWebhookData
o) = ReqBodyJson ModifyWebhookData
-> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
patchWith' (ReqBodyJson ModifyWebhookData
 -> Url 'Https -> Option 'Https -> Req LbsResponse)
-> ReqBodyJson ModifyWebhookData
-> Url 'Https
-> Option 'Https
-> Req LbsResponse
forall a b. (a -> b) -> a -> b
$ ModifyWebhookData -> ReqBodyJson ModifyWebhookData
forall a. a -> ReqBodyJson a
ReqBodyJson ModifyWebhookData
o
  action (ModifyWebhookToken w
_ Text
_ ModifyWebhookData
o) = ReqBodyJson ModifyWebhookData
-> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a -> Url 'Https -> Option 'Https -> Req LbsResponse
patchWith' (ReqBodyJson ModifyWebhookData
 -> Url 'Https -> Option 'Https -> Req LbsResponse)
-> ReqBodyJson ModifyWebhookData
-> Url 'Https
-> Option 'Https
-> Req LbsResponse
forall a b. (a -> b) -> a -> b
$ ModifyWebhookData -> ReqBodyJson ModifyWebhookData
forall a. a -> ReqBodyJson a
ReqBodyJson ModifyWebhookData
o
  action (DeleteWebhook w
_) = Url 'Https -> Option 'Https -> Req LbsResponse
deleteWith
  action (DeleteWebhookToken w
_ Text
_) = Url 'Https -> Option 'Https -> Req LbsResponse
deleteWith
  action (ExecuteWebhook w
_ Text
_ ExecuteWebhookOptions
wh) = \Url 'Https
u Option 'Https
o -> do
    let filePart :: CreateMessageAttachment -> i -> PartM IO
filePart CreateMessageAttachment {Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> Text
filename :: Text
filename, ByteString
$sel:content:CreateMessageAttachment :: CreateMessageAttachment -> ByteString
content :: ByteString
content} i
n =
          (Text -> ByteString -> PartM IO
forall (m :: * -> *).
Applicative m =>
Text -> ByteString -> PartM m
partLBS @IO [fmt|files[{n}]|] 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
filename :: Text
$sel:filename:CreateMessageAttachment :: CreateMessageAttachment -> 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 i.
FormatAny2 (PyFClassify i) i 'AlignAll =>
CreateMessageAttachment -> i -> PartM IO
filePart (ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting
     [CreateMessageAttachment]
     ExecuteWebhookOptions
     [CreateMessageAttachment]
-> [CreateMessageAttachment]
forall s a. s -> Getting a s a -> a
^. IsLabel
  "attachments"
  (Getting
     [CreateMessageAttachment]
     ExecuteWebhookOptions
     [CreateMessageAttachment])
Getting
  [CreateMessageAttachment]
  ExecuteWebhookOptions
  [CreateMessageAttachment]
#attachments) [(Int
0 :: Int) ..]
        attachments :: [CreateMessageAttachmentJson]
attachments = (CreateMessageAttachment -> Int -> CreateMessageAttachmentJson)
-> [CreateMessageAttachment]
-> [Int]
-> [CreateMessageAttachmentJson]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith CreateMessageAttachment -> Int -> CreateMessageAttachmentJson
attachmentPart (ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting
     [CreateMessageAttachment]
     ExecuteWebhookOptions
     [CreateMessageAttachment]
-> [CreateMessageAttachment]
forall s a. s -> Getting a s a -> a
^. IsLabel
  "attachments"
  (Getting
     [CreateMessageAttachment]
     ExecuteWebhookOptions
     [CreateMessageAttachment])
Getting
  [CreateMessageAttachment]
  ExecuteWebhookOptions
  [CreateMessageAttachment]
#attachments) [Int
0 ..]
        jsonBody :: ExecuteWebhookJson
jsonBody =
          ExecuteWebhookJson :: Maybe Text
-> Maybe [Embed]
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> [CreateMessageAttachmentJson]
-> Maybe AllowedMentions
-> [Component]
-> ExecuteWebhookJson
ExecuteWebhookJson
            { $sel:content:ExecuteWebhookJson :: Maybe Text
content = ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting (Maybe Text) ExecuteWebhookOptions (Maybe Text)
-> Maybe Text
forall s a. s -> Getting a s a -> a
^. IsLabel
  "content" (Getting (Maybe Text) ExecuteWebhookOptions (Maybe Text))
Getting (Maybe Text) ExecuteWebhookOptions (Maybe Text)
#content
            , $sel:username:ExecuteWebhookJson :: Maybe Text
username = ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting (Maybe Text) ExecuteWebhookOptions (Maybe Text)
-> Maybe Text
forall s a. s -> Getting a s a -> a
^. IsLabel
  "username"
  (Getting (Maybe Text) ExecuteWebhookOptions (Maybe Text))
Getting (Maybe Text) ExecuteWebhookOptions (Maybe Text)
#username
            , $sel:avatarUrl:ExecuteWebhookJson :: Maybe Text
avatarUrl = ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting (Maybe Text) ExecuteWebhookOptions (Maybe Text)
-> Maybe Text
forall s a. s -> Getting a s a -> a
^. IsLabel
  "avatarUrl"
  (Getting (Maybe Text) ExecuteWebhookOptions (Maybe Text))
Getting (Maybe Text) ExecuteWebhookOptions (Maybe Text)
#avatarUrl
            , $sel:tts:ExecuteWebhookJson :: Maybe Bool
tts = ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting (Maybe Bool) ExecuteWebhookOptions (Maybe Bool)
-> Maybe Bool
forall s a. s -> Getting a s a -> a
^. IsLabel
  "tts" (Getting (Maybe Bool) ExecuteWebhookOptions (Maybe Bool))
Getting (Maybe Bool) ExecuteWebhookOptions (Maybe Bool)
#tts
            , $sel:embeds:ExecuteWebhookJson :: Maybe [Embed]
embeds = ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting (Maybe [Embed]) ExecuteWebhookOptions (Maybe [Embed])
-> Maybe [Embed]
forall s a. s -> Getting a s a -> a
^. IsLabel
  "embeds"
  (Getting (Maybe [Embed]) ExecuteWebhookOptions (Maybe [Embed]))
Getting (Maybe [Embed]) ExecuteWebhookOptions (Maybe [Embed])
#embeds
            , $sel:allowedMentions:ExecuteWebhookJson :: Maybe AllowedMentions
allowedMentions = ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting
     (Maybe AllowedMentions)
     ExecuteWebhookOptions
     (Maybe AllowedMentions)
-> Maybe AllowedMentions
forall s a. s -> Getting a s a -> a
^. IsLabel
  "allowedMentions"
  (Getting
     (Maybe AllowedMentions)
     ExecuteWebhookOptions
     (Maybe AllowedMentions))
Getting
  (Maybe AllowedMentions)
  ExecuteWebhookOptions
  (Maybe AllowedMentions)
#allowedMentions
            , $sel:components:ExecuteWebhookJson :: [Component]
components = ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting [Component] ExecuteWebhookOptions [Component]
-> [Component]
forall s a. s -> Getting a s a -> a
^. IsLabel
  "components"
  (Getting [Component] ExecuteWebhookOptions [Component])
Getting [Component] ExecuteWebhookOptions [Component]
#components
            , $sel:attachments:ExecuteWebhookJson :: [CreateMessageAttachmentJson]
attachments = [CreateMessageAttachmentJson]
attachments
            }
    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" (ExecuteWebhookJson -> ByteString
forall a. ToJSON a => a -> ByteString
encode ExecuteWebhookJson
jsonBody) PartM IO -> [PartM IO] -> [PartM IO]
forall a. a -> [a] -> [a]
: [PartM IO]
files)
    ReqBodyMultipart
-> Option 'Https -> Url 'Https -> Option 'Https -> Req LbsResponse
forall a.
HttpBody a =>
a
-> Option 'Https -> Url 'Https -> Option 'Https -> Req LbsResponse
postWithP' ReqBodyMultipart
body (Text
"wait" Text -> Maybe Bool -> Option 'Https
forall a. ToHttpApiData a => Text -> Maybe a -> Option 'Https
=:? (ExecuteWebhookOptions
wh ExecuteWebhookOptions
-> Getting (Maybe Bool) ExecuteWebhookOptions (Maybe Bool)
-> Maybe Bool
forall s a. s -> Getting a s a -> a
^. IsLabel
  "wait" (Getting (Maybe Bool) ExecuteWebhookOptions (Maybe Bool))
Getting (Maybe Bool) ExecuteWebhookOptions (Maybe Bool)
#wait)) Url 'Https
u Option 'Https
o