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 =
    forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, 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 =
    forall (mt :: RW) a. Paths -> QueryString -> Request mt a
query [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"labels", 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 =
    forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Post [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"labels"] forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 =
    forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Patch [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"labels", forall a. IsPathPart a => a -> Text
toPathPart Name IssueLabel
oldLbl] forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 =
    forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"labels", forall a. IsPathPart a => a -> Text
toPathPart Name IssueLabel
lbl] 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 =
    forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", 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 =
    forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Post Paths
paths (forall a. ToJSON a => a -> ByteString
encode forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f (Name IssueLabel)
lbls)
  where
    paths :: Paths
paths = [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", 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 =
    forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"labels", forall a. IsPathPart a => a -> Text
toPathPart Name IssueLabel
lbl] 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 =
    forall a. CommandMethod -> Paths -> ByteString -> Request 'RW a
command CommandMethod
Put Paths
paths (forall a. ToJSON a => a -> ByteString
encode forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f (Name IssueLabel)
lbls)
  where
    paths :: Paths
paths = [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", 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 =
    forall (mt :: MediaType (*)) a.
CommandMethod -> Paths -> ByteString -> GenRequest mt 'RW a
Command CommandMethod
Delete [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"issues", forall a. IsPathPart a => a -> Text
toPathPart Id Issue
iid, Text
"labels"] 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 =
    forall a (mt :: RW).
FromJSON a =>
Paths -> QueryString -> FetchCount -> Request mt (Vector a)
pagedQuery [Text
"repos", forall a. IsPathPart a => a -> Text
toPathPart Name Owner
user, forall a. IsPathPart a => a -> Text
toPathPart Name Repo
repo, Text
"milestones", forall a. IsPathPart a => a -> Text
toPathPart Id Milestone
mid, Text
"labels"] []