{-# LANGUAGE CPP #-}
module GitHub.Endpoints.Repos.Comments (
commentsForR,
commitCommentsForR,
commitCommentForR,
module GitHub.Data,
) where
import GitHub.Data
import GitHub.Internal.Prelude
import Prelude ()
commentsForR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector Comment)
Name Owner
user Name Repo
repo =
Paths -> QueryString -> FetchCount -> Request k (Vector Comment)
forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"comments"] []
commitCommentsForR :: Name Owner -> Name Repo -> Name Commit -> FetchCount -> Request k (Vector Comment)
Name Owner
user Name Repo
repo Name Commit
sha =
Paths -> QueryString -> FetchCount -> Request k (Vector Comment)
forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"commits", Name Commit -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Commit
sha, Text
"comments"] []
commitCommentForR :: Name Owner -> Name Repo -> Id Comment -> Request k Comment
Name Owner
user Name Repo
repo Id Comment
cid =
Paths -> QueryString -> Request k Comment
forall (mt :: RW) a. Paths -> QueryString -> Request mt a
query [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"comments", Id Comment -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Comment
cid] []