module GitHub.Endpoints.Issues.Labels (
labelsOnRepoR,
labelR,
createLabelR,
updateLabelR,
deleteLabelR,
labelsOnIssueR,
addLabelsToIssueR,
removeLabelFromIssueR,
replaceAllLabelsForIssueR,
removeAllLabelsFromIssueR,
labelsOnMilestoneR,
module GitHub.Data,
) where
import GitHub.Data
import GitHub.Internal.Prelude
import Prelude ()
labelsOnRepoR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector IssueLabel)
labelsOnRepoR user repo =
pagedQuery ["repos", toPathPart user, toPathPart repo, "labels"] []
labelR :: Name Owner -> Name Repo -> Name IssueLabel -> Request k IssueLabel
labelR user repo lbl =
query ["repos", toPathPart user, toPathPart repo, "labels", toPathPart lbl] []
createLabelR :: Name Owner -> Name Repo -> NewIssueLabel -> Request 'RW IssueLabel
createLabelR user repo =
command Post ["repos", toPathPart user, toPathPart repo, "labels"] . encode
updateLabelR :: Name Owner
-> Name Repo
-> Name IssueLabel
-> UpdateIssueLabel
-> Request 'RW IssueLabel
updateLabelR user repo oldLbl =
command Patch ["repos", toPathPart user, toPathPart repo, "labels", toPathPart oldLbl] . encode
deleteLabelR :: Name Owner -> Name Repo -> Name IssueLabel -> GenRequest 'MtUnit 'RW ()
deleteLabelR user repo lbl =
Command Delete ["repos", toPathPart user, toPathPart repo, "labels", toPathPart lbl] mempty
labelsOnIssueR :: Name Owner -> Name Repo -> Id Issue -> FetchCount -> Request k (Vector IssueLabel)
labelsOnIssueR user repo iid =
pagedQuery ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels"] []
addLabelsToIssueR :: Foldable f
=> Name Owner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> Request 'RW (Vector IssueLabel)
addLabelsToIssueR user repo iid lbls =
command Post paths (encode $ toList lbls)
where
paths = ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels"]
removeLabelFromIssueR :: Name Owner -> Name Repo -> Id Issue -> Name IssueLabel -> GenRequest 'MtUnit 'RW ()
removeLabelFromIssueR user repo iid lbl =
Command Delete ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels", toPathPart lbl] mempty
replaceAllLabelsForIssueR :: Foldable f
=> Name Owner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> Request 'RW (Vector IssueLabel)
replaceAllLabelsForIssueR user repo iid lbls =
command Put paths (encode $ toList lbls)
where
paths = ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels"]
removeAllLabelsFromIssueR :: Name Owner -> Name Repo -> Id Issue -> GenRequest 'MtUnit 'RW ()
removeAllLabelsFromIssueR user repo iid =
Command Delete ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels"] mempty
labelsOnMilestoneR :: Name Owner -> Name Repo -> Id Milestone -> FetchCount -> Request k (Vector IssueLabel)
labelsOnMilestoneR user repo mid =
pagedQuery ["repos", toPathPart user, toPathPart repo, "milestones", toPathPart mid, "labels"] []