{-# LANGUAGE CPP #-}
module GitHub.Endpoints.Issues (
currentUserIssuesR,
organizationIssuesR,
issueR,
issuesForRepoR,
createIssueR,
newIssue,
editIssueR,
editOfIssue,
module GitHub.Data,
) where
import GitHub.Data
import GitHub.Internal.Prelude
import Prelude ()
currentUserIssuesR :: IssueMod -> FetchCount -> Request 'RA (Vector Issue)
currentUserIssuesR opts =
pagedQuery ["user", "issues"] (issueModToQueryString opts)
organizationIssuesR :: Name Organization -> IssueMod -> FetchCount -> Request k (Vector Issue)
organizationIssuesR org opts =
pagedQuery ["orgs", toPathPart org, "issues"] (issueModToQueryString opts)
issueR :: Name Owner -> Name Repo -> IssueNumber -> Request k Issue
issueR user reqRepoName reqIssueNumber =
query ["repos", toPathPart user, toPathPart reqRepoName, "issues", toPathPart reqIssueNumber] []
issuesForRepoR :: Name Owner -> Name Repo -> IssueRepoMod -> FetchCount -> Request k (Vector Issue)
issuesForRepoR user reqRepoName opts =
pagedQuery ["repos", toPathPart user, toPathPart reqRepoName, "issues"] qs
where
qs = issueRepoModToQueryString opts
newIssue :: Text -> NewIssue
newIssue title = NewIssue title Nothing mempty Nothing Nothing
createIssueR :: Name Owner -> Name Repo -> NewIssue -> Request 'RW Issue
createIssueR user repo =
command Post ["repos", toPathPart user, toPathPart repo, "issues"] . encode
editOfIssue :: EditIssue
editOfIssue = EditIssue Nothing Nothing Nothing Nothing Nothing Nothing
editIssueR :: Name Owner -> Name Repo -> IssueNumber -> EditIssue -> Request 'RW Issue
editIssueR user repo iss =
command Patch ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iss] . encode