module GitHub.Endpoints.PullRequests (
pullRequestsFor,
pullRequestsFor',
pullRequestsForR,
pullRequest',
pullRequest,
pullRequestR,
pullRequestDiff',
pullRequestDiff,
pullRequestDiffR,
pullRequestPatch',
pullRequestPatch,
pullRequestPatchR,
createPullRequest,
createPullRequestR,
updatePullRequest,
updatePullRequestR,
pullRequestCommits',
pullRequestCommitsIO,
pullRequestCommitsR,
pullRequestFiles',
pullRequestFiles,
pullRequestFilesR,
isPullRequestMerged,
isPullRequestMergedR,
mergePullRequest,
mergePullRequestR,
module GitHub.Data
) where
import GitHub.Data
import GitHub.Internal.Prelude
import GitHub.Request
import Prelude ()
import Data.ByteString.Lazy (ByteString)
pullRequestsFor :: Name Owner -> Name Repo -> IO (Either Error (Vector SimplePullRequest))
pullRequestsFor user repo =
executeRequest' $ pullRequestsForR user repo mempty FetchAll
pullRequestsFor' :: Maybe Auth -> Name Owner -> Name Repo -> IO (Either Error (Vector SimplePullRequest))
pullRequestsFor' auth user repo =
executeRequestMaybe auth $ pullRequestsForR user repo mempty FetchAll
pullRequestsForR
:: Name Owner
-> Name Repo
-> PullRequestMod
-> FetchCount
-> Request k (Vector SimplePullRequest)
pullRequestsForR user repo opts = pagedQuery
["repos", toPathPart user, toPathPart repo, "pulls"]
(prModToQueryString opts)
pullRequestDiff' :: Maybe Auth -> Name Owner -> Name Repo -> IssueNumber -> IO (Either Error ByteString)
pullRequestDiff' auth user repo prid =
executeRequestMaybe auth $ pullRequestDiffR user repo prid
pullRequestDiff :: Name Owner -> Name Repo -> IssueNumber -> IO (Either Error ByteString)
pullRequestDiff = pullRequestDiff' Nothing
pullRequestDiffR :: Name Owner -> Name Repo -> IssueNumber -> GenRequest 'MtDiff rw ByteString
pullRequestDiffR user repo prid =
Query ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid] []
pullRequestPatch' :: Maybe Auth -> Name Owner -> Name Repo -> IssueNumber -> IO (Either Error ByteString)
pullRequestPatch' auth user repo prid =
executeRequestMaybe auth $ pullRequestPatchR user repo prid
pullRequestPatch :: Name Owner -> Name Repo -> IssueNumber -> IO (Either Error ByteString)
pullRequestPatch = pullRequestPatch' Nothing
pullRequestPatchR :: Name Owner -> Name Repo -> IssueNumber -> GenRequest 'MtPatch rw ByteString
pullRequestPatchR user repo prid =
Query ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid] []
pullRequest' :: Maybe Auth -> Name Owner -> Name Repo -> IssueNumber -> IO (Either Error PullRequest)
pullRequest' auth user repo prid =
executeRequestMaybe auth $ pullRequestR user repo prid
pullRequest :: Name Owner -> Name Repo -> IssueNumber -> IO (Either Error PullRequest)
pullRequest = pullRequest' Nothing
pullRequestR :: Name Owner -> Name Repo -> IssueNumber -> Request k PullRequest
pullRequestR user repo prid =
query ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid] []
createPullRequest :: Auth
-> Name Owner
-> Name Repo
-> CreatePullRequest
-> IO (Either Error PullRequest)
createPullRequest auth user repo cpr =
executeRequest auth $ createPullRequestR user repo cpr
createPullRequestR :: Name Owner
-> Name Repo
-> CreatePullRequest
-> Request 'RW PullRequest
createPullRequestR user repo cpr =
command Post ["repos", toPathPart user, toPathPart repo, "pulls"] (encode cpr)
updatePullRequest :: Auth -> Name Owner -> Name Repo -> IssueNumber -> EditPullRequest -> IO (Either Error PullRequest)
updatePullRequest auth user repo prid epr =
executeRequest auth $ updatePullRequestR user repo prid epr
updatePullRequestR :: Name Owner
-> Name Repo
-> IssueNumber
-> EditPullRequest
-> Request 'RW PullRequest
updatePullRequestR user repo prid epr =
command Patch ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid] (encode epr)
pullRequestCommits' :: Maybe Auth -> Name Owner -> Name Repo -> IssueNumber -> IO (Either Error (Vector Commit))
pullRequestCommits' auth user repo prid =
executeRequestMaybe auth $ pullRequestCommitsR user repo prid FetchAll
pullRequestCommitsIO :: Name Owner -> Name Repo -> IssueNumber -> IO (Either Error (Vector Commit))
pullRequestCommitsIO = pullRequestCommits' Nothing
pullRequestCommitsR :: Name Owner -> Name Repo -> IssueNumber -> FetchCount -> Request k (Vector Commit)
pullRequestCommitsR user repo prid =
pagedQuery ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid, "commits"] []
pullRequestFiles' :: Maybe Auth -> Name Owner -> Name Repo -> IssueNumber -> IO (Either Error (Vector File))
pullRequestFiles' auth user repo prid =
executeRequestMaybe auth $ pullRequestFilesR user repo prid FetchAll
pullRequestFiles :: Name Owner -> Name Repo -> IssueNumber -> IO (Either Error (Vector File))
pullRequestFiles = pullRequestFiles' Nothing
pullRequestFilesR :: Name Owner -> Name Repo -> IssueNumber -> FetchCount -> Request k (Vector File)
pullRequestFilesR user repo prid =
pagedQuery ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid, "files"] []
isPullRequestMerged :: Auth -> Name Owner -> Name Repo -> IssueNumber -> IO (Either Error Bool)
isPullRequestMerged auth user repo prid =
executeRequest auth $ isPullRequestMergedR user repo prid
isPullRequestMergedR :: Name Owner -> Name Repo -> IssueNumber -> GenRequest 'MtStatus rw Bool
isPullRequestMergedR user repo prid =
Query ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid, "merge"] []
mergePullRequest :: Auth -> Name Owner -> Name Repo -> IssueNumber -> Maybe Text -> IO (Either Error MergeResult)
mergePullRequest auth user repo prid commitMessage =
executeRequest auth $ mergePullRequestR user repo prid commitMessage
mergePullRequestR :: Name Owner -> Name Repo -> IssueNumber -> Maybe Text -> GenRequest 'MtStatus 'RW MergeResult
mergePullRequestR user repo prid commitMessage =
Command Put paths (encode $ buildCommitMessageMap commitMessage)
where
paths = ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid, "merge"]
buildCommitMessageMap :: Maybe Text -> Value
buildCommitMessageMap (Just msg) = object ["commit_message" .= msg ]
buildCommitMessageMap Nothing = object []