{-# LANGUAGE CPP #-}
module GitHub.Endpoints.Repos.Comments (
commentsFor,
commentsFor',
commentsForR,
commitCommentsFor,
commitCommentsFor',
commitCommentsForR,
commitCommentFor,
commitCommentFor',
commitCommentForR,
module GitHub.Data,
) where
import GitHub.Data
import GitHub.Internal.Prelude
import GitHub.Request
import Prelude ()
commentsFor :: Name Owner -> Name Repo -> IO (Either Error (Vector Comment))
commentsFor = commentsFor' Nothing
commentsFor' :: Maybe Auth -> Name Owner -> Name Repo -> IO (Either Error (Vector Comment))
commentsFor' auth user repo =
executeRequestMaybe auth $ commentsForR user repo FetchAll
commentsForR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector Comment)
commentsForR user repo =
pagedQuery ["repos", toPathPart user, toPathPart repo, "comments"] []
commitCommentsFor :: Name Owner -> Name Repo -> Name Commit -> IO (Either Error (Vector Comment))
commitCommentsFor = commitCommentsFor' Nothing
commitCommentsFor' :: Maybe Auth -> Name Owner -> Name Repo -> Name Commit -> IO (Either Error (Vector Comment))
commitCommentsFor' auth user repo sha =
executeRequestMaybe auth $ commitCommentsForR user repo sha FetchAll
commitCommentsForR :: Name Owner -> Name Repo -> Name Commit -> FetchCount -> Request k (Vector Comment)
commitCommentsForR user repo sha =
pagedQuery ["repos", toPathPart user, toPathPart repo, "commits", toPathPart sha, "comments"] []
commitCommentFor :: Name Owner -> Name Repo -> Id Comment -> IO (Either Error Comment)
commitCommentFor = commitCommentFor' Nothing
commitCommentFor' :: Maybe Auth -> Name Owner -> Name Repo -> Id Comment -> IO (Either Error Comment)
commitCommentFor' auth user repo cid =
executeRequestMaybe auth $ commitCommentForR user repo cid
commitCommentForR :: Name Owner -> Name Repo -> Id Comment -> Request k Comment
commitCommentForR user repo cid =
query ["repos", toPathPart user, toPathPart repo, "comments", toPathPart cid] []