{-# LANGUAGE DataKinds #-} ----------------------------------------------------------------------------- -- | -- License : BSD-3-Clause -- Maintainer : Oleg Grenrus -- -- The Github issue comments API from -- . module GitHub.Endpoints.Issues.Comments ( comment, commentR, comments, commentsR, comments', createComment, createCommentR, editComment, editCommentR, module GitHub.Data, ) where import Data.Aeson.Compat (encode) import Data.Text (Text) import Data.Vector (Vector) import GitHub.Data import GitHub.Request -- | A specific comment, by ID. -- -- > comment "thoughtbot" "paperclip" 1468184 comment :: Name Owner -> Name Repo -> Id Comment -> IO (Either Error IssueComment) comment user repo cid = executeRequest' $ commentR user repo cid -- | Query a single comment. -- See commentR :: Name Owner -> Name Repo -> Id Comment -> Request k IssueComment commentR user repo cid = Query ["repos", toPathPart user, toPathPart repo, "issues", "comments", toPathPart cid] [] -- | All comments on an issue, by the issue's number. -- -- > comments "thoughtbot" "paperclip" 635 comments :: Name Owner -> Name Repo -> Id Issue -> IO (Either Error (Vector IssueComment)) comments = comments' Nothing -- | All comments on an issue, by the issue's number, using authentication. -- -- > comments' (User (user, password)) "thoughtbot" "paperclip" 635 comments' :: Maybe Auth -> Name Owner -> Name Repo -> Id Issue -> IO (Either Error (Vector IssueComment)) comments' auth user repo iid = executeRequestMaybe auth $ commentsR user repo iid Nothing -- | List comments on an issue. -- See commentsR :: Name Owner -> Name Repo -> Id Issue -> Maybe Count -> Request k (Vector IssueComment) commentsR user repo iid = PagedQuery ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "comments"] [] -- | Create a new comment. -- -- > createComment (User (user, password)) user repo issue -- > "some words" createComment :: Auth -> Name Owner -> Name Repo -> Id Issue -> Text -> IO (Either Error Comment) createComment auth user repo iss body = executeRequest auth $ createCommentR user repo iss body -- | Create a comment. -- See createCommentR :: Name Owner -> Name Repo -> Id Issue -> Text -> Request 'True Comment createCommentR user repo iss body = Command Post parts (encode $ NewComment body) where parts = ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iss, "comments"] -- | Edit a comment. -- -- > editComment (User (user, password)) user repo commentid -- > "new words" editComment :: Auth -> Name Owner -> Name Repo -> Id Comment -> Text -> IO (Either Error Comment) editComment auth user repo commid body = executeRequest auth $ editCommentR user repo commid body -- | Edit a comment. -- See editCommentR :: Name Owner -> Name Repo -> Id Comment -> Text -> Request 'True Comment editCommentR user repo commid body = Command Patch parts (encode $ EditComment body) where parts = ["repos", toPathPart user, toPathPart repo, "issues", "comments", toPathPart commid]