module Github.PullRequests (
pullRequestsFor'',
pullRequestsFor',
pullRequestsFor,
pullRequestsForR,
pullRequest',
pullRequest,
pullRequestR,
createPullRequest,
createPullRequestR,
updatePullRequest,
updatePullRequestR,
pullRequestCommits',
pullRequestCommitsIO,
pullRequestCommitsR,
pullRequestFiles',
pullRequestFiles,
pullRequestFilesR,
isPullRequestMerged,
isPullRequestMergedR,
mergePullRequest,
mergePullRequestR,
module Github.Data
) where
import Github.Auth
import Github.Data
import Github.Request
import Data.Aeson.Compat (Value, encode, object, (.=))
import Data.Vector (Vector)
import Network.HTTP.Types
import qualified Data.ByteString.Char8 as BS8
pullRequestsFor'' :: Maybe GithubAuth -> Maybe String -> Name GithubOwner -> Name Repo -> IO (Either Error (Vector SimplePullRequest))
pullRequestsFor'' auth state user repo =
executeRequestMaybe auth $ pullRequestsForR user repo state Nothing
pullRequestsFor' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> IO (Either Error (Vector SimplePullRequest))
pullRequestsFor' auth = pullRequestsFor'' auth Nothing
pullRequestsFor :: Name GithubOwner -> Name Repo -> IO (Either Error (Vector SimplePullRequest))
pullRequestsFor = pullRequestsFor'' Nothing Nothing
pullRequestsForR :: Name GithubOwner -> Name Repo
-> Maybe String
-> Maybe Count
-> GithubRequest k (Vector SimplePullRequest)
pullRequestsForR user repo state =
GithubPagedGet ["repos", toPathPart user, toPathPart repo, "pulls"] qs
where
qs = maybe [] (\s -> [("state", Just . BS8.pack $ s)]) state
pullRequest' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Id PullRequest -> IO (Either Error PullRequest)
pullRequest' auth user repo prid =
executeRequestMaybe auth $ pullRequestR user repo prid
pullRequest :: Name GithubOwner -> Name Repo -> Id PullRequest -> IO (Either Error PullRequest)
pullRequest = pullRequest' Nothing
pullRequestR :: Name GithubOwner -> Name Repo -> Id PullRequest -> GithubRequest k PullRequest
pullRequestR user repo prid =
GithubGet ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid] []
createPullRequest :: GithubAuth
-> Name GithubOwner
-> Name Repo
-> CreatePullRequest
-> IO (Either Error PullRequest)
createPullRequest auth user repo cpr =
executeRequest auth $ createPullRequestR user repo cpr
createPullRequestR :: Name GithubOwner
-> Name Repo
-> CreatePullRequest
-> GithubRequest 'True PullRequest
createPullRequestR user repo cpr =
GithubPost Post ["repos", toPathPart user, toPathPart repo, "pulls"] (encode cpr)
updatePullRequest :: GithubAuth -> Name GithubOwner -> Name Repo -> Id PullRequest -> EditPullRequest -> IO (Either Error PullRequest)
updatePullRequest auth user repo prid epr =
executeRequest auth $ updatePullRequestR user repo prid epr
updatePullRequestR :: Name GithubOwner
-> Name Repo
-> Id PullRequest
-> EditPullRequest
-> GithubRequest 'True PullRequest
updatePullRequestR user repo prid epr =
GithubPost Patch ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid] (encode epr)
pullRequestCommits' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Id PullRequest -> IO (Either Error (Vector Commit))
pullRequestCommits' auth user repo prid =
executeRequestMaybe auth $ pullRequestCommitsR user repo prid Nothing
pullRequestCommitsIO :: Name GithubOwner -> Name Repo -> Id PullRequest -> IO (Either Error (Vector Commit))
pullRequestCommitsIO = pullRequestCommits' Nothing
pullRequestCommitsR :: Name GithubOwner -> Name Repo -> Id PullRequest -> Maybe Count -> GithubRequest k (Vector Commit)
pullRequestCommitsR user repo prid =
GithubPagedGet ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid, "commits"] []
pullRequestFiles' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Id PullRequest -> IO (Either Error (Vector File))
pullRequestFiles' auth user repo prid =
executeRequestMaybe auth $ pullRequestFilesR user repo prid Nothing
pullRequestFiles :: Name GithubOwner -> Name Repo -> Id PullRequest -> IO (Either Error (Vector File))
pullRequestFiles = pullRequestFiles' Nothing
pullRequestFilesR :: Name GithubOwner -> Name Repo -> Id PullRequest -> Maybe Count -> GithubRequest k (Vector File)
pullRequestFilesR user repo prid =
GithubPagedGet ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid, "files"] []
isPullRequestMerged :: GithubAuth -> Name GithubOwner -> Name Repo -> Id PullRequest -> IO (Either Error Status)
isPullRequestMerged auth user repo prid =
executeRequest auth $ isPullRequestMergedR user repo prid
isPullRequestMergedR :: Name GithubOwner -> Name Repo -> Id PullRequest -> GithubRequest k Status
isPullRequestMergedR user repo prid = GithubStatus $
GithubGet ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid, "merge"] []
mergePullRequest :: GithubAuth -> Name GithubOwner -> Name Repo -> Id PullRequest -> Maybe String -> IO (Either Error Status)
mergePullRequest auth user repo prid commitMessage =
executeRequest auth $ mergePullRequestR user repo prid commitMessage
mergePullRequestR :: Name GithubOwner -> Name Repo -> Id PullRequest -> Maybe String -> GithubRequest 'True Status
mergePullRequestR user repo prid commitMessage = GithubStatus $
GithubPost Put paths (encode $ buildCommitMessageMap commitMessage)
where
paths = ["repos", toPathPart user, toPathPart repo, "pulls", toPathPart prid, "merge"]
buildCommitMessageMap :: Maybe String -> Value
buildCommitMessageMap (Just msg) = object ["commit_message" .= msg ]
buildCommitMessageMap Nothing = object []