module GitHub.Endpoints.Repos.DeployKeys (
deployKeysForR,
deployKeyForR,
createRepoDeployKeyR,
deleteRepoDeployKeyR,
) where
import GitHub.Data
import GitHub.Internal.Prelude
import Prelude ()
deployKeysForR :: Name Owner -> Name Repo -> FetchCount -> Request 'RA (Vector RepoDeployKey)
deployKeysForR :: Name Owner
-> Name Repo -> FetchCount -> Request 'RA (Vector RepoDeployKey)
deployKeysForR Name Owner
user Name Repo
repo =
Paths
-> QueryString -> FetchCount -> Request 'RA (Vector RepoDeployKey)
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
"keys"] []
deployKeyForR :: Name Owner -> Name Repo -> Id RepoDeployKey -> Request 'RA RepoDeployKey
deployKeyForR :: Name Owner
-> Name Repo -> Id RepoDeployKey -> Request 'RA RepoDeployKey
deployKeyForR Name Owner
user Name Repo
repo Id RepoDeployKey
keyId =
Paths -> QueryString -> Request 'RA RepoDeployKey
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
"keys", Id RepoDeployKey -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id RepoDeployKey
keyId] []
createRepoDeployKeyR :: Name Owner -> Name Repo -> NewRepoDeployKey -> Request 'RW RepoDeployKey
createRepoDeployKeyR :: Name Owner
-> Name Repo -> NewRepoDeployKey -> Request 'RW RepoDeployKey
createRepoDeployKeyR Name Owner
user Name Repo
repo NewRepoDeployKey
key =
CommandMethod -> Paths -> ByteString -> Request 'RW RepoDeployKey
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
"keys"] (NewRepoDeployKey -> ByteString
forall a. ToJSON a => a -> ByteString
encode NewRepoDeployKey
key)
deleteRepoDeployKeyR :: Name Owner -> Name Repo -> Id RepoDeployKey -> GenRequest 'MtUnit 'RW ()
deleteRepoDeployKeyR :: Name Owner
-> Name Repo -> Id RepoDeployKey -> GenRequest 'MtUnit 'RW ()
deleteRepoDeployKeyR Name Owner
user Name Repo
repo Id RepoDeployKey
keyId =
CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete [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
"keys", Id RepoDeployKey -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id RepoDeployKey
keyId] ByteString
forall a. Monoid a => a
mempty