module Github.Issues (
issue,
issue',
issueR,
issuesForRepo,
issuesForRepo',
issuesForRepoR,
IssueLimitation(..),
createIssue,
createIssueR,
newIssue,
editIssue,
editIssueR,
editOfIssue,
module Github.Data,
) where
import Github.Auth
import Github.Data
import Github.Request
import Data.Aeson.Compat (encode)
import Data.List (intercalate)
import Data.Text (Text)
import Data.Time.ISO8601 (formatISO8601)
import Data.Vector (Vector)
import qualified Data.ByteString.Char8 as BS8
issue' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Id Issue -> IO (Either Error Issue)
issue' auth user reqRepoName reqIssueNumber =
executeRequestMaybe auth $ issueR user reqRepoName reqIssueNumber
issue :: Name GithubOwner -> Name Repo -> Id Issue -> IO (Either Error Issue)
issue = issue' Nothing
issueR :: Name GithubOwner -> Name Repo -> Id Issue -> GithubRequest k Issue
issueR user reqRepoName reqIssueNumber =
GithubGet ["repos", toPathPart user, toPathPart reqRepoName, "issues", toPathPart reqIssueNumber] []
issuesForRepo' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> [IssueLimitation] -> IO (Either Error (Vector Issue))
issuesForRepo' auth user reqRepoName issueLimitations =
executeRequestMaybe auth $ issuesForRepoR user reqRepoName issueLimitations Nothing
issuesForRepo :: Name GithubOwner -> Name Repo -> [IssueLimitation] -> IO (Either Error (Vector Issue))
issuesForRepo = issuesForRepo' Nothing
issuesForRepoR :: Name GithubOwner -> Name Repo -> [IssueLimitation] -> Maybe Count -> GithubRequest k (Vector Issue)
issuesForRepoR user reqRepoName issueLimitations =
GithubPagedGet ["repos", toPathPart user, toPathPart reqRepoName, "issues"] qs
where
qs = map convert issueLimitations
convert AnyMilestone = ("milestone", Just "*")
convert NoMilestone = ("milestone", Just "none")
convert (MilestoneId n) = ("milestone", Just . BS8.pack $ show n)
convert Open = ("state", Just "open")
convert OnlyClosed = ("state", Just "closed")
convert Unassigned = ("assignee", Just "none")
convert AnyAssignment = ("assignee", Just "")
convert (AssignedTo u) = ("assignee", Just $ BS8.pack u)
convert (Mentions u) = ("mentioned", Just $ BS8.pack u)
convert (Labels l) = ("labels", Just . BS8.pack $ intercalate "," l)
convert Ascending = ("direction", Just "asc")
convert Descending = ("direction", Just "desc")
convert (PerPage n) = ("per_page", Just . BS8.pack $ show n)
convert (Since t) = ("since", Just . BS8.pack $ formatISO8601 t)
newIssue :: Text -> NewIssue
newIssue title = NewIssue title Nothing Nothing Nothing Nothing
createIssue :: GithubAuth -> Name GithubOwner -> Name Repo -> NewIssue
-> IO (Either Error Issue)
createIssue auth user repo ni =
executeRequest auth $ createIssueR user repo ni
createIssueR :: Name GithubOwner -> Name Repo -> NewIssue -> GithubRequest 'True Issue
createIssueR user repo =
GithubPost Post ["repos", toPathPart user, toPathPart repo, "issues"] . encode
editOfIssue :: EditIssue
editOfIssue = EditIssue Nothing Nothing Nothing Nothing Nothing Nothing
editIssue :: GithubAuth -> Name GithubOwner -> Name Repo -> Id Issue -> EditIssue
-> IO (Either Error Issue)
editIssue auth user repo iss edit =
executeRequest auth $ editIssueR user repo iss edit
editIssueR :: Name GithubOwner -> Name Repo -> Id Issue -> EditIssue -> GithubRequest 'True Issue
editIssueR user repo iss =
GithubPost Patch ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iss] . encode