-----------------------------------------------------------------------------
-- |
-- License     :  BSD-3-Clause
-- Maintainer  :  Oleg Grenrus <oleg.grenrus@iki.fi>
--
-- The API for dealing with labels on Github issues as described on
-- <http://developer.github.com/v3/issues/labels/>.
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 ()

-- | List all labels for this repository.
-- See <https://developer.github.com/v3/issues/labels/#list-all-labels-for-this-repository>
labelsOnRepoR :: Name Owner -> Name Repo -> FetchCount -> Request k (Vector IssueLabel)
labelsOnRepoR :: 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"] []

-- | Query a single label.
-- See <https://developer.github.com/v3/issues/labels/#get-a-single-label>
labelR :: Name Owner -> Name Repo -> Name IssueLabel -> Request k IssueLabel
labelR :: 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] []

-- | Create a label.
-- See <https://developer.github.com/v3/issues/labels/#create-a-label>
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

-- | Update a label.
-- See <https://developer.github.com/v3/issues/labels/#update-a-label>
updateLabelR :: Name Owner
             -> Name Repo
             -> Name IssueLabel   -- ^ old label name
             -> UpdateIssueLabel   -- ^ new label
             -> 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

-- | Delete a label.
-- See <https://developer.github.com/v3/issues/labels/#delete-a-label>
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

-- | List labels on an issue.
-- See <https://developer.github.com/v3/issues/labels/#list-labels-on-an-issue>
labelsOnIssueR :: Name Owner -> Name Repo -> Id Issue -> FetchCount -> Request k (Vector IssueLabel)
labelsOnIssueR :: 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"] []

-- | Add lables to an issue.
-- See <https://developer.github.com/v3/issues/labels/#add-labels-to-an-issue>
addLabelsToIssueR :: Foldable f
                  => Name Owner
                  -> Name Repo
                  -> Id Issue
                  -> f (Name IssueLabel)
                  -> Request 'RW (Vector IssueLabel)
addLabelsToIssueR :: 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 (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"]

-- | Remove a label from an issue.
-- See <https://developer.github.com/v3/issues/labels/#remove-a-label-from-an-issue>
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

-- | Replace all labels on an issue.
-- See <https://developer.github.com/v3/issues/labels/#replace-all-labels-for-an-issue>
--
-- Sending an empty list will remove all labels from the issue.
replaceAllLabelsForIssueR :: Foldable f
                          => Name Owner
                          -> Name Repo
                          -> Id Issue
                          -> f (Name IssueLabel)
                          -> Request 'RW (Vector IssueLabel)
replaceAllLabelsForIssueR :: 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 (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"]

-- | Remove all labels from an issue.
-- See <https://developer.github.com/v3/issues/labels/#remove-all-labels-from-an-issue>
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

-- | Query labels for every issue in a milestone.
-- See <https://developer.github.com/v3/issues/labels/#get-labels-for-every-issue-in-a-milestone>
labelsOnMilestoneR :: Name Owner -> Name Repo -> Id Milestone -> FetchCount -> Request k (Vector IssueLabel)
labelsOnMilestoneR :: 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"] []