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 :: Name Owner
-> Name Repo -> FetchCount -> Request k (Vector RepoWebhook)
webhooksForR Name Owner
user Name Repo
repo =
Paths
-> QueryString -> FetchCount -> Request k (Vector RepoWebhook)
forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"hooks"] []
webhookForR :: Name Owner -> Name Repo -> Id RepoWebhook -> Request k RepoWebhook
webhookForR :: Name Owner -> Name Repo -> Id RepoWebhook -> Request k RepoWebhook
webhookForR Name Owner
user Name Repo
repo Id RepoWebhook
hookId =
Paths -> QueryString -> Request k RepoWebhook
forall (mt :: RW) a. Paths -> QueryString -> Request mt a
query [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"hooks", Id RepoWebhook -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id RepoWebhook
hookId] []
createRepoWebhookR :: Name Owner -> Name Repo -> NewRepoWebhook -> Request 'RW RepoWebhook
createRepoWebhookR :: Name Owner
-> Name Repo -> NewRepoWebhook -> Request 'RW RepoWebhook
createRepoWebhookR Name Owner
user Name Repo
repo NewRepoWebhook
hook =
CommandMethod -> Paths -> ByteString -> Request 'RW RepoWebhook
forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Post [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"hooks"] (NewRepoWebhook -> ByteString
forall a. ToJSON a => a -> ByteString
encode NewRepoWebhook
hook)
editRepoWebhookR :: Name Owner -> Name Repo -> Id RepoWebhook -> EditRepoWebhook -> Request 'RW RepoWebhook
editRepoWebhookR :: Name Owner
-> Name Repo
-> Id RepoWebhook
-> EditRepoWebhook
-> Request 'RW RepoWebhook
editRepoWebhookR Name Owner
user Name Repo
repo Id RepoWebhook
hookId EditRepoWebhook
hookEdit =
CommandMethod -> Paths -> ByteString -> Request 'RW RepoWebhook
forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Patch [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"hooks", Id RepoWebhook -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id RepoWebhook
hookId] (EditRepoWebhook -> ByteString
forall a. ToJSON a => a -> ByteString
encode EditRepoWebhook
hookEdit)
testPushRepoWebhookR :: Name Owner -> Name Repo -> Id RepoWebhook -> GenRequest 'MtStatus 'RW Bool
testPushRepoWebhookR :: Name Owner
-> Name Repo -> Id RepoWebhook -> GenRequest 'MtStatus 'RW Bool
testPushRepoWebhookR Name Owner
user Name Repo
repo Id RepoWebhook
hookId =
CommandMethod
-> Paths -> ByteString -> GenRequest 'MtStatus 'RW Bool
forall (mt :: MediaType *) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post (Name Owner -> Name Repo -> Id RepoWebhook -> Maybe Text -> Paths
createWebhookOpPath Name Owner
user Name Repo
repo Id RepoWebhook
hookId (Maybe Text -> Paths) -> Maybe Text -> Paths
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"tests") (() -> ByteString
forall a. ToJSON a => a -> ByteString
encode ())
pingRepoWebhookR :: Name Owner -> Name Repo -> Id RepoWebhook -> GenRequest 'MtStatus 'RW Bool
pingRepoWebhookR :: Name Owner
-> Name Repo -> Id RepoWebhook -> GenRequest 'MtStatus 'RW Bool
pingRepoWebhookR Name Owner
user Name Repo
repo Id RepoWebhook
hookId =
CommandMethod
-> Paths -> ByteString -> GenRequest 'MtStatus 'RW Bool
forall (mt :: MediaType *) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Post (Name Owner -> Name Repo -> Id RepoWebhook -> Maybe Text -> Paths
createWebhookOpPath Name Owner
user Name Repo
repo Id RepoWebhook
hookId (Maybe Text -> Paths) -> Maybe Text -> Paths
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"pings") (() -> ByteString
forall a. ToJSON a => a -> ByteString
encode ())
deleteRepoWebhookR :: Name Owner -> Name Repo -> Id RepoWebhook -> GenRequest 'MtUnit 'RW ()
deleteRepoWebhookR :: Name Owner
-> Name Repo -> Id RepoWebhook -> GenRequest 'MtUnit 'RW ()
deleteRepoWebhookR Name Owner
user Name Repo
repo Id RepoWebhook
hookId =
CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType *) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete (Name Owner -> Name Repo -> Id RepoWebhook -> Maybe Text -> Paths
createWebhookOpPath Name Owner
user Name Repo
repo Id RepoWebhook
hookId Maybe Text
forall a. Maybe a
Nothing) ByteString
forall a. Monoid a => a
mempty
createBaseWebhookPath :: Name Owner -> Name Repo -> Id RepoWebhook -> Paths
createBaseWebhookPath :: Name Owner -> Name Repo -> Id RepoWebhook -> Paths
createBaseWebhookPath Name Owner
user Name Repo
repo Id RepoWebhook
hookId =
[Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"hooks", Id RepoWebhook -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id RepoWebhook
hookId]
createWebhookOpPath :: Name Owner -> Name Repo -> Id RepoWebhook -> Maybe Text -> Paths
createWebhookOpPath :: Name Owner -> Name Repo -> Id RepoWebhook -> Maybe Text -> Paths
createWebhookOpPath Name Owner
owner Name Repo
reqName Id RepoWebhook
webhookId Maybe Text
Nothing = Name Owner -> Name Repo -> Id RepoWebhook -> Paths
createBaseWebhookPath Name Owner
owner Name Repo
reqName Id RepoWebhook
webhookId
createWebhookOpPath Name Owner
owner Name Repo
reqName Id RepoWebhook
webhookId (Just Text
operation) = Name Owner -> Name Repo -> Id RepoWebhook -> Paths
createBaseWebhookPath Name Owner
owner Name Repo
reqName Id RepoWebhook
webhookId Paths -> Paths -> Paths
forall a. [a] -> [a] -> [a]
++ [Text
operation]