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 :: forall (k :: RW).
Name Owner
-> Name Repo -> FetchCount -> Request k (Vector IssueLabel)
labelsOnRepoR Name Owner
user Name Repo
repo =
Paths -> QueryString -> FetchCount -> Request k (Vector IssueLabel)
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
"labels"] []
labelR :: Name Owner -> Name Repo -> Name IssueLabel -> Request k IssueLabel
labelR :: forall (k :: RW).
Name Owner -> Name Repo -> Name IssueLabel -> Request k IssueLabel
labelR Name Owner
user Name Repo
repo Name IssueLabel
lbl =
Paths -> QueryString -> Request k IssueLabel
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
"labels", Name IssueLabel -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name IssueLabel
lbl] []
createLabelR :: Name Owner -> Name Repo -> NewIssueLabel -> Request 'RW IssueLabel
createLabelR :: Name Owner -> Name Repo -> NewIssueLabel -> Request 'RW IssueLabel
createLabelR Name Owner
user Name Repo
repo =
CommandMethod -> Paths -> ByteString -> Request 'RW IssueLabel
forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Post [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
"labels"] (ByteString -> Request 'RW IssueLabel)
-> (NewIssueLabel -> ByteString)
-> NewIssueLabel
-> Request 'RW IssueLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NewIssueLabel -> ByteString
forall a. ToJSON a => a -> ByteString
encode
updateLabelR :: Name Owner
-> Name Repo
-> Name IssueLabel
-> UpdateIssueLabel
-> Request 'RW IssueLabel
updateLabelR :: Name Owner
-> Name Repo
-> Name IssueLabel
-> UpdateIssueLabel
-> Request 'RW IssueLabel
updateLabelR Name Owner
user Name Repo
repo Name IssueLabel
oldLbl =
CommandMethod -> Paths -> ByteString -> Request 'RW IssueLabel
forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Patch [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
"labels", Name IssueLabel -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name IssueLabel
oldLbl] (ByteString -> Request 'RW IssueLabel)
-> (UpdateIssueLabel -> ByteString)
-> UpdateIssueLabel
-> Request 'RW IssueLabel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UpdateIssueLabel -> ByteString
forall a. ToJSON a => a -> ByteString
encode
deleteLabelR :: Name Owner -> Name Repo -> Name IssueLabel -> GenRequest 'MtUnit 'RW ()
deleteLabelR :: Name Owner
-> Name Repo -> Name IssueLabel -> GenRequest 'MtUnit 'RW ()
deleteLabelR Name Owner
user Name Repo
repo Name IssueLabel
lbl =
CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete [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
"labels", Name IssueLabel -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name IssueLabel
lbl] ByteString
forall a. Monoid a => a
mempty
labelsOnIssueR :: Name Owner -> Name Repo -> Id Issue -> FetchCount -> Request k (Vector IssueLabel)
labelsOnIssueR :: forall (k :: RW).
Name Owner
-> Name Repo
-> Id Issue
-> FetchCount
-> Request k (Vector IssueLabel)
labelsOnIssueR Name Owner
user Name Repo
repo Id Issue
iid =
Paths -> QueryString -> FetchCount -> Request k (Vector IssueLabel)
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
"issues", Id Issue -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"labels"] []
addLabelsToIssueR :: Foldable f
=> Name Owner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> Request 'RW (Vector IssueLabel)
addLabelsToIssueR :: forall (f :: * -> *).
Foldable f =>
Name Owner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> Request 'RW (Vector IssueLabel)
addLabelsToIssueR Name Owner
user Name Repo
repo Id Issue
iid f (Name IssueLabel)
lbls =
CommandMethod
-> Paths -> ByteString -> Request 'RW (Vector IssueLabel)
forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Post Paths
paths ([Name IssueLabel] -> ByteString
forall a. ToJSON a => a -> ByteString
encode ([Name IssueLabel] -> ByteString)
-> [Name IssueLabel] -> ByteString
forall a b. (a -> b) -> a -> b
$ f (Name IssueLabel) -> [Name IssueLabel]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f (Name IssueLabel)
lbls)
where
paths :: Paths
paths = [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
"issues", Id Issue -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"labels"]
removeLabelFromIssueR :: Name Owner -> Name Repo -> Id Issue -> Name IssueLabel -> GenRequest 'MtUnit 'RW ()
removeLabelFromIssueR :: Name Owner
-> Name Repo
-> Id Issue
-> Name IssueLabel
-> GenRequest 'MtUnit 'RW ()
removeLabelFromIssueR Name Owner
user Name Repo
repo Id Issue
iid Name IssueLabel
lbl =
CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete [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
"issues", Id Issue -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"labels", Name IssueLabel -> Text
forall a. IsPathPart a => a -> Text
toPathPart Name IssueLabel
lbl] ByteString
forall a. Monoid a => a
mempty
replaceAllLabelsForIssueR :: Foldable f
=> Name Owner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> Request 'RW (Vector IssueLabel)
replaceAllLabelsForIssueR :: forall (f :: * -> *).
Foldable f =>
Name Owner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> Request 'RW (Vector IssueLabel)
replaceAllLabelsForIssueR Name Owner
user Name Repo
repo Id Issue
iid f (Name IssueLabel)
lbls =
CommandMethod
-> Paths -> ByteString -> Request 'RW (Vector IssueLabel)
forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Put Paths
paths ([Name IssueLabel] -> ByteString
forall a. ToJSON a => a -> ByteString
encode ([Name IssueLabel] -> ByteString)
-> [Name IssueLabel] -> ByteString
forall a b. (a -> b) -> a -> b
$ f (Name IssueLabel) -> [Name IssueLabel]
forall a. f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f (Name IssueLabel)
lbls)
where
paths :: Paths
paths = [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
"issues", Id Issue -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"labels"]
removeAllLabelsFromIssueR :: Name Owner -> Name Repo -> Id Issue -> GenRequest 'MtUnit 'RW ()
removeAllLabelsFromIssueR :: Name Owner -> Name Repo -> Id Issue -> GenRequest 'MtUnit 'RW ()
removeAllLabelsFromIssueR Name Owner
user Name Repo
repo Id Issue
iid =
CommandMethod -> Paths -> ByteString -> GenRequest 'MtUnit 'RW ()
forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete [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
"issues", Id Issue -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"labels"] ByteString
forall a. Monoid a => a
mempty
labelsOnMilestoneR :: Name Owner -> Name Repo -> Id Milestone -> FetchCount -> Request k (Vector IssueLabel)
labelsOnMilestoneR :: forall (k :: RW).
Name Owner
-> Name Repo
-> Id Milestone
-> FetchCount
-> Request k (Vector IssueLabel)
labelsOnMilestoneR Name Owner
user Name Repo
repo Id Milestone
mid =
Paths -> QueryString -> FetchCount -> Request k (Vector IssueLabel)
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
"milestones", Id Milestone -> Text
forall a. IsPathPart a => a -> Text
toPathPart Id Milestone
mid, Text
"labels"] []