module GitHub.Endpoints.Reactions (
  issueReactionsR,
  createIssueReactionR,
  deleteIssueReactionR,
  commentReactionsR,
  createCommentReactionR,
  deleteCommentReactionR,
  module GitHub.Data,
) where
import GitHub.Data
import GitHub.Internal.Prelude
import Prelude ()
issueReactionsR :: Name Owner -> Name Repo -> Id Issue -> FetchCount -> Request k (Vector Reaction)
issueReactionsR :: forall (k :: RW).
Name Owner
-> Name Repo
-> Id Issue
-> FetchCount
-> Request k (Vector Reaction)
issueReactionsR Name Owner
owner Name Repo
repo Id Issue
iid =
  Paths -> QueryString -> FetchCount -> Request k (Vector Reaction)
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
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", Id Issue -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"reactions"] []
createIssueReactionR :: Name Owner -> Name Repo -> Id Issue -> ReactionContent -> Request 'RW Reaction
createIssueReactionR :: Name Owner
-> Name Repo -> Id Issue -> ReactionContent -> Request 'RW Reaction
createIssueReactionR Name Owner
owner Name Repo
repo Id Issue
iid ReactionContent
content =
    CommandMethod -> Paths -> ByteString -> Request 'RW Reaction
forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Post Paths
parts (NewReaction -> ByteString
forall a. ToJSON a => a -> ByteString
encode (NewReaction -> ByteString) -> NewReaction -> ByteString
forall a b. (a -> b) -> a -> b
$ ReactionContent -> NewReaction
NewReaction ReactionContent
content)
  where
    parts :: Paths
parts = [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", Id Issue -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"reactions"]
deleteIssueReactionR :: Name Owner -> Name Repo -> Id Issue -> Id Reaction -> GenRequest 'MtUnit 'RW ()
deleteIssueReactionR :: Name Owner
-> Name Repo
-> Id Issue
-> Id Reaction
-> GenRequest 'MtUnit 'RW ()
deleteIssueReactionR Name Owner
owner Name Repo
repo Id Issue
iid Id Reaction
rid =
    CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete Paths
parts ByteString
forall a. Monoid a => a
mempty
  where
    parts :: Paths
parts = [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", Id Issue -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"reactions", Id Reaction -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Reaction
rid]
commentReactionsR :: Name Owner -> Name Repo -> Id Comment -> FetchCount -> Request k (Vector Reaction)
 Name Owner
owner Name Repo
repo Id Comment
cid =
  Paths -> QueryString -> FetchCount -> Request k (Vector Reaction)
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
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", Text
"comments", Id Comment -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Comment
cid, Text
"reactions"] []
createCommentReactionR :: Name Owner -> Name Repo -> Id Comment -> ReactionContent -> Request 'RW Reaction
 Name Owner
owner Name Repo
repo Id Comment
cid ReactionContent
content =
    CommandMethod -> Paths -> ByteString -> Request 'RW Reaction
forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Post Paths
parts (NewReaction -> ByteString
forall a. ToJSON a => a -> ByteString
encode (NewReaction -> ByteString) -> NewReaction -> ByteString
forall a b. (a -> b) -> a -> b
$ ReactionContent -> NewReaction
NewReaction ReactionContent
content)
  where
    parts :: Paths
parts = [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", Text
"comments", Id Comment -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Comment
cid, Text
"reactions"]
deleteCommentReactionR :: Name Owner -> Name Repo -> Id Comment -> Id Reaction -> GenRequest 'MtUnit 'RW ()
 Name Owner
owner Name Repo
repo Id Comment
cid Id Reaction
rid =
    CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete Paths
parts ByteString
forall a. Monoid a => a
mempty
  where
    parts :: Paths
parts = [Text
"repos", Name Owner -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Owner
owner, Name Repo -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", Text
"comments", Id Comment -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Comment
cid, Text
"reactions", Id Reaction -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Reaction
rid]