{-# LANGUAGE CPP #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE OverloadedStrings #-} ----------------------------------------------------------------------------- -- | -- License : BSD-3-Clause -- Maintainer : Oleg Grenrus -- -- The issues API as described on . module GitHub.Endpoints.Issues ( issue, issue', issueR, issuesForRepo, issuesForRepo', issuesForRepoR, IssueLimitation(..), createIssue, createIssueR, newIssue, editIssue, editIssueR, editOfIssue, module GitHub.Data, ) where 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 -- | Details on a specific issue, given the repo owner and name, and the issue -- number.' -- -- > issue' (Just ("github-username", "github-password")) "thoughtbot" "paperclip" "462" issue' :: Maybe Auth -> Name Owner -> Name Repo -> Id Issue -> IO (Either Error Issue) issue' auth user reqRepoName reqIssueNumber = executeRequestMaybe auth $ issueR user reqRepoName reqIssueNumber -- | Details on a specific issue, given the repo owner and name, and the issue -- number. -- -- > issue "thoughtbot" "paperclip" (Id "462") issue :: Name Owner -> Name Repo -> Id Issue -> IO (Either Error Issue) issue = issue' Nothing -- | Query a single issue. -- See issueR :: Name Owner -> Name Repo -> Id Issue -> Request k Issue issueR user reqRepoName reqIssueNumber = Query ["repos", toPathPart user, toPathPart reqRepoName, "issues", toPathPart reqIssueNumber] [] -- | All issues for a repo (given the repo owner and name), with optional -- restrictions as described in the @IssueLimitation@ data type. -- -- > issuesForRepo' (Just ("github-username", "github-password")) "thoughtbot" "paperclip" [NoMilestone, OnlyClosed, Mentions "jyurek", Ascending] issuesForRepo' :: Maybe Auth -> Name Owner -> Name Repo -> [IssueLimitation] -> IO (Either Error (Vector Issue)) issuesForRepo' auth user reqRepoName issueLimitations = executeRequestMaybe auth $ issuesForRepoR user reqRepoName issueLimitations Nothing -- | All issues for a repo (given the repo owner and name), with optional -- restrictions as described in the @IssueLimitation@ data type. -- -- > issuesForRepo "thoughtbot" "paperclip" [NoMilestone, OnlyClosed, Mentions "jyurek", Ascending] issuesForRepo :: Name Owner -> Name Repo -> [IssueLimitation] -> IO (Either Error (Vector Issue)) issuesForRepo = issuesForRepo' Nothing -- | List issues for a repository. -- See issuesForRepoR :: Name Owner -> Name Repo -> [IssueLimitation] -> Maybe Count -> Request k (Vector Issue) issuesForRepoR user reqRepoName issueLimitations = PagedQuery ["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) -- Creating new issues. newIssue :: Text -> NewIssue newIssue title = NewIssue title Nothing Nothing Nothing Nothing -- | Create a new issue. -- -- > createIssue (User (user, password)) user repo -- > (newIssue "some_repo") {...} createIssue :: Auth -> Name Owner -> Name Repo -> NewIssue -> IO (Either Error Issue) createIssue auth user repo ni = executeRequest auth $ createIssueR user repo ni -- | Create an issue. -- See createIssueR :: Name Owner -> Name Repo -> NewIssue -> Request 'True Issue createIssueR user repo = Command Post ["repos", toPathPart user, toPathPart repo, "issues"] . encode -- Editing issues. editOfIssue :: EditIssue editOfIssue = EditIssue Nothing Nothing Nothing Nothing Nothing Nothing -- | Edit an issue. -- -- > editIssue (User (user, password)) user repo issue -- > editOfIssue {...} editIssue :: Auth -> Name Owner -> Name Repo -> Id Issue -> EditIssue -> IO (Either Error Issue) editIssue auth user repo iss edit = executeRequest auth $ editIssueR user repo iss edit -- | Edit an issue. -- See editIssueR :: Name Owner -> Name Repo -> Id Issue -> EditIssue -> Request 'True Issue editIssueR user repo iss = Command Patch ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iss] . encode