module Github.Issues.Labels (
labelsOnRepo,
labelsOnRepo',
labelsOnRepoR,
label,
label',
labelR,
createLabel,
createLabelR,
updateLabel,
updateLabelR,
deleteLabel,
deleteLabelR,
labelsOnIssue,
labelsOnIssue',
labelsOnIssueR,
addLabelsToIssue,
addLabelsToIssueR,
removeLabelFromIssue,
removeLabelFromIssueR,
replaceAllLabelsForIssue,
replaceAllLabelsForIssueR,
removeAllLabelsFromIssue,
removeAllLabelsFromIssueR,
labelsOnMilestone,
labelsOnMilestone',
labelsOnMilestoneR,
module Github.Data,
) where
import Prelude ()
import Prelude.Compat
import Data.Aeson.Compat (encode, object, (.=))
import Data.Foldable (toList)
import Data.Vector (Vector)
import Github.Auth
import Github.Data
import Github.Request
labelsOnRepo :: Name GithubOwner -> Name Repo -> IO (Either Error (Vector IssueLabel))
labelsOnRepo = labelsOnRepo' Nothing
labelsOnRepo' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> IO (Either Error (Vector IssueLabel))
labelsOnRepo' auth user repo =
executeRequestMaybe auth $ labelsOnRepoR user repo Nothing
labelsOnRepoR :: Name GithubOwner -> Name Repo -> Maybe Count -> GithubRequest k (Vector IssueLabel)
labelsOnRepoR user repo =
GithubPagedGet ["repos", toPathPart user, toPathPart repo, "labels"] []
label :: Name GithubOwner -> Name Repo -> Name IssueLabel -> IO (Either Error IssueLabel)
label = label' Nothing
label' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Name IssueLabel -> IO (Either Error IssueLabel)
label' auth user repo lbl =
executeRequestMaybe auth $ labelR user repo lbl
labelR :: Name GithubOwner -> Name Repo -> Name IssueLabel -> GithubRequest k IssueLabel
labelR user repo lbl =
GithubGet ["repos", toPathPart user, toPathPart repo, "labels", toPathPart lbl] []
createLabel :: GithubAuth -> Name GithubOwner -> Name Repo -> Name IssueLabel -> String -> IO (Either Error IssueLabel)
createLabel auth user repo lbl color =
executeRequest auth $ createLabelR user repo lbl color
createLabelR :: Name GithubOwner -> Name Repo -> Name IssueLabel -> String -> GithubRequest 'True IssueLabel
createLabelR user repo lbl color =
GithubPost Post paths $ encode body
where
paths = ["repos", toPathPart user, toPathPart repo, "labels"]
body = object ["name" .= untagName lbl, "color" .= color]
updateLabel :: GithubAuth
-> Name GithubOwner
-> Name Repo
-> Name IssueLabel
-> Name IssueLabel
-> String
-> IO (Either Error IssueLabel)
updateLabel auth user repo oldLbl newLbl color =
executeRequest auth $ updateLabelR user repo oldLbl newLbl color
updateLabelR :: Name GithubOwner
-> Name Repo
-> Name IssueLabel
-> Name IssueLabel
-> String
-> GithubRequest 'True IssueLabel
updateLabelR user repo oldLbl newLbl color =
GithubPost Patch paths (encode body)
where
paths = ["repos", toPathPart user, toPathPart repo, "labels", toPathPart oldLbl]
body = object ["name" .= untagName newLbl, "color" .= color]
deleteLabel :: GithubAuth -> Name GithubOwner -> Name Repo -> Name IssueLabel -> IO (Either Error ())
deleteLabel auth user repo lbl =
executeRequest auth $ deleteLabelR user repo lbl
deleteLabelR :: Name GithubOwner -> Name Repo -> Name IssueLabel -> GithubRequest 'True ()
deleteLabelR user repo lbl =
GithubDelete ["repos", toPathPart user, toPathPart repo, "labels", toPathPart lbl]
labelsOnIssue :: Name GithubOwner -> Name Repo -> Id Issue -> IO (Either Error (Vector IssueLabel))
labelsOnIssue = labelsOnIssue' Nothing
labelsOnIssue' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Id Issue -> IO (Either Error (Vector IssueLabel))
labelsOnIssue' auth user repo iid =
executeRequestMaybe auth $ labelsOnIssueR user repo iid Nothing
labelsOnIssueR :: Name GithubOwner -> Name Repo -> Id Issue -> Maybe Count -> GithubRequest k (Vector IssueLabel)
labelsOnIssueR user repo iid =
GithubPagedGet ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels"] []
addLabelsToIssue :: Foldable f
=> GithubAuth
-> Name GithubOwner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> IO (Either Error (Vector IssueLabel))
addLabelsToIssue auth user repo iid lbls =
executeRequest auth $ addLabelsToIssueR user repo iid lbls
addLabelsToIssueR :: Foldable f
=> Name GithubOwner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> GithubRequest 'True (Vector IssueLabel)
addLabelsToIssueR user repo iid lbls =
GithubPost Post paths (encode $ toList lbls)
where
paths = ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels"]
removeLabelFromIssue :: GithubAuth -> Name GithubOwner -> Name Repo -> Id Issue -> Name IssueLabel -> IO (Either Error ())
removeLabelFromIssue auth user repo iid lbl =
executeRequest auth $ removeLabelFromIssueR user repo iid lbl
removeLabelFromIssueR :: Name GithubOwner -> Name Repo -> Id Issue -> Name IssueLabel -> GithubRequest 'True ()
removeLabelFromIssueR user repo iid lbl =
GithubDelete ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels", toPathPart lbl]
replaceAllLabelsForIssue :: Foldable f
=> GithubAuth
-> Name GithubOwner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> IO (Either Error (Vector IssueLabel))
replaceAllLabelsForIssue auth user repo iid lbls =
executeRequest auth $ replaceAllLabelsForIssueR user repo iid lbls
replaceAllLabelsForIssueR :: Foldable f
=> Name GithubOwner
-> Name Repo
-> Id Issue
-> f (Name IssueLabel)
-> GithubRequest 'True (Vector IssueLabel)
replaceAllLabelsForIssueR user repo iid lbls =
GithubPost Put paths (encode $ toList lbls)
where
paths = ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels"]
removeAllLabelsFromIssue :: GithubAuth -> Name GithubOwner -> Name Repo -> Id Issue -> IO (Either Error ())
removeAllLabelsFromIssue auth user repo iid =
executeRequest auth $ removeAllLabelsFromIssueR user repo iid
removeAllLabelsFromIssueR :: Name GithubOwner -> Name Repo -> Id Issue -> GithubRequest 'True ()
removeAllLabelsFromIssueR user repo iid =
GithubDelete ["repos", toPathPart user, toPathPart repo, "issues", toPathPart iid, "labels"]
labelsOnMilestone :: Name GithubOwner -> Name Repo -> Id Milestone -> IO (Either Error (Vector IssueLabel))
labelsOnMilestone = labelsOnMilestone' Nothing
labelsOnMilestone' :: Maybe GithubAuth -> Name GithubOwner -> Name Repo -> Id Milestone -> IO (Either Error (Vector IssueLabel))
labelsOnMilestone' auth user repo mid =
executeRequestMaybe auth $ labelsOnMilestoneR user repo mid Nothing
labelsOnMilestoneR :: Name GithubOwner -> Name Repo -> Id Milestone -> Maybe Count -> GithubRequest k (Vector IssueLabel)
labelsOnMilestoneR user repo mid =
GithubPagedGet ["repos", toPathPart user, toPathPart repo, "milestones", toPathPart mid, "labels"] []