module GitHub.Endpoints.Repos.Webhooks (
webhooksForR,
webhookForR,
createRepoWebhookR,
editRepoWebhookR,
testPushRepoWebhookR,
pingRepoWebhookR,
deleteRepoWebhookR,
) where
import GitHub.Data
import GitHub.Internal.Prelude
import Prelude ()
webhooksForR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector RepoWebhook)
webhooksForR user repo =
pagedQuery ["repos", toPathPart user, toPathPart repo, "hooks"] []
webhookForR :: Name Owner -> Name Repo -> Id RepoWebhook -> Request k RepoWebhook
webhookForR user repo hookId =
query ["repos", toPathPart user, toPathPart repo, "hooks", toPathPart hookId] []
createRepoWebhookR :: Name Owner -> Name Repo -> NewRepoWebhook -> Request 'RW RepoWebhook
createRepoWebhookR user repo hook =
command Post ["repos", toPathPart user, toPathPart repo, "hooks"] (encode hook)
editRepoWebhookR :: Name Owner -> Name Repo -> Id RepoWebhook -> EditRepoWebhook -> Request 'RW RepoWebhook
editRepoWebhookR user repo hookId hookEdit =
command Patch ["repos", toPathPart user, toPathPart repo, "hooks", toPathPart hookId] (encode hookEdit)
testPushRepoWebhookR :: Name Owner -> Name Repo -> Id RepoWebhook -> GenRequest 'MtStatus 'RW Bool
testPushRepoWebhookR user repo hookId =
Command Post (createWebhookOpPath user repo hookId $ Just "tests") (encode ())
pingRepoWebhookR :: Name Owner -> Name Repo -> Id RepoWebhook -> GenRequest 'MtStatus 'RW Bool
pingRepoWebhookR user repo hookId =
Command Post (createWebhookOpPath user repo hookId $ Just "pings") (encode ())
deleteRepoWebhookR :: Name Owner -> Name Repo -> Id RepoWebhook -> GenRequest 'MtUnit 'RW ()
deleteRepoWebhookR user repo hookId =
Command Delete (createWebhookOpPath user repo hookId Nothing) mempty
createBaseWebhookPath :: Name Owner -> Name Repo -> Id RepoWebhook -> Paths
createBaseWebhookPath user repo hookId =
["repos", toPathPart user, toPathPart repo, "hooks", toPathPart hookId]
createWebhookOpPath :: Name Owner -> Name Repo -> Id RepoWebhook -> Maybe Text -> Paths
createWebhookOpPath owner reqName webhookId Nothing = createBaseWebhookPath owner reqName webhookId
createWebhookOpPath owner reqName webhookId (Just operation) = createBaseWebhookPath owner reqName webhookId ++ [operation]