module GitHub.Endpoints.Issues.Comments (
comment,
commentR,
comments,
commentsR,
comments',
createComment,
createCommentR,
deleteComment,
deleteCommentR,
editComment,
editCommentR,
module GitHub.Data,
) where
import GitHub.Data
import GitHub.Internal.Prelude
import GitHub.Request
import Prelude ()
comment :: Name Owner -> Name Repo -> Id Comment -> IO (Either Error IssueComment)
comment user repo cid =
executeRequest' $ commentR user repo cid
commentR :: Name Owner -> Name Repo -> Id Comment -> Request k IssueComment
commentR user repo cid =
query ["repos", toPathPart user, toPathPart repo, "issues", "comments", toPathPart cid] []
comments :: Name Owner -> Name Repo -> IssueNumber -> IO (Either Error (Vector IssueComment))
comments = comments' Nothing
comments' :: Maybe Auth -> Name Owner -> Name Repo -> IssueNumber -> IO (Either Error (Vector IssueComment))
comments' auth user repo iid =
executeRequestMaybe auth $ commentsR user repo iid FetchAll
commentsR :: Name Owner -> Name Repo -> IssueNumber -> FetchCount -> Request k (Vector IssueComment)
commentsR user repo iid =
pagedQuery ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "comments"] []
createComment :: Auth -> Name Owner -> Name Repo -> IssueNumber -> Text
-> IO (Either Error Comment)
createComment auth user repo iss body =
executeRequest auth $ createCommentR user repo iss body
createCommentR :: Name Owner -> Name Repo -> IssueNumber -> Text -> Request 'RW Comment
createCommentR user repo iss body =
command Post parts (encode $ NewComment body)
where
parts = ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iss, "comments"]
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
editCommentR :: Name Owner -> Name Repo -> Id Comment -> Text -> Request 'RW Comment
editCommentR user repo commid body =
command Patch parts (encode $ EditComment body)
where
parts = ["repos", toPathPart user, toPathPart repo, "issues", "comments", toPathPart commid]
deleteComment :: Auth -> Name Owner -> Name Repo -> Id Comment
-> IO (Either Error ())
deleteComment auth user repo commid =
executeRequest auth $ deleteCommentR user repo commid
deleteCommentR :: Name Owner -> Name Repo -> Id Comment -> GenRequest 'MtUnit 'RW ()
deleteCommentR user repo commid =
Command Delete parts mempty
where
parts = ["repos", toPathPart user, toPathPart repo, "issues", "comments", toPathPart commid]