{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module      : Issues
-- Description : Queries about issues created against projects
-- Copyright   : (c) Rob Stewart, Heriot-Watt University, 2019
-- License     : BSD3
-- Maintainer  : robstewart57@gmail.com
-- Stability   : stable
module GitLab.API.Issues
  ( -- * List issues

    -- * List group issues
    groupIssues,

    -- * List project issues
    projectIssues,

    -- * Single issue
    issue,

    -- * User issues
    userIssues,

    -- * Single project issue
    projectIssue,

    -- * New issue
    newIssue,

    -- * Edit issue
    editIssue,

    -- * Delete an issue
    deleteIssue,

    -- * Reorder an issue
    reorderIssue,

    -- * Move an issue
    moveIssue,

    -- * Clone an issue
    cloneIssue,

    -- * Subscribe to an issue
    subscribeIssue,

    -- * Unsubscribe from an issue
    unsubscribeIssue,

    -- * Create a to-do item
    createTodo,

    -- * List merge requests related to issue
    issueMergeRequests,

    -- * List merge requests that close a particular issue on merge
    issueMergeRequestsThatClose,

    -- * Participants on issues
    issueParticipants,

    -- * Comments on issues

    -- * Get issues statistics
    issueStatisticsUser,

    -- * Get group issues statistics
    issueStatisticsGroup,

    -- * Get project issues statistics
    issueStatisticsProject,

    -- * Issues attributes
    defaultIssueFilters,
    IssueAttrs (..),
    DueDate (..),
    IssueState (..),
  )
where

import qualified Data.ByteString.Lazy as BSL
import Data.Either
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Time.Clock
import Data.Time.Format.ISO8601
import GitLab.Types
import GitLab.WebRequests.GitLabWebCalls
import Network.HTTP.Client

-- | Get a list of a project’s issues
groupIssues ::
  -- | the group
  Group ->
  -- | filter the issues, see https://docs.gitlab.com/ee/api/issues.html#list-issues
  IssueAttrs ->
  -- the GitLab issues
  GitLab [Issue]
groupIssues :: Group -> IssueAttrs -> GitLab [Issue]
groupIssues Group
grp IssueAttrs
attrs = do
  Either (Response ByteString) [Issue]
result <- Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) [Issue])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
urlPath (IssueAttrs -> [GitLabParam]
issuesAttrs IssueAttrs
attrs)
  [Issue] -> GitLab [Issue]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Issue] -> Either (Response ByteString) [Issue] -> [Issue]
forall b a. b -> Either a b -> b
fromRight ([Char] -> [Issue]
forall a. HasCallStack => [Char] -> a
error [Char]
"groupsIssues error") Either (Response ByteString) [Issue]
result)
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$
        [Char]
"/groups/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show (Group -> Int
group_id Group
grp)
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/issues"

-- result <- projectIssues' (project_id p) filters
-- return (fromRight (error "projectIssues error") result)

-- | Get a list of a project’s issues
projectIssues ::
  -- | the project
  Project ->
  -- | filter the issues, see https://docs.gitlab.com/ee/api/issues.html#list-issues
  IssueAttrs ->
  -- the GitLab issues
  GitLab [Issue]
projectIssues :: Project -> IssueAttrs -> GitLab [Issue]
projectIssues Project
p IssueAttrs
filters = do
  Either (Response ByteString) [Issue]
result <- Int -> IssueAttrs -> GitLab (Either (Response ByteString) [Issue])
projectIssues' (Project -> Int
project_id Project
p) IssueAttrs
filters
  [Issue] -> GitLab [Issue]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Issue] -> Either (Response ByteString) [Issue] -> [Issue]
forall b a. b -> Either a b -> b
fromRight ([Char] -> [Issue]
forall a. HasCallStack => [Char] -> a
error [Char]
"projectIssues error") Either (Response ByteString) [Issue]
result)

-- | Get a list of a project’s issues
projectIssues' ::
  -- | the project ID
  Int ->
  -- | filter the issues, see https://docs.gitlab.com/ee/api/issues.html#list-issues
  IssueAttrs ->
  -- | the GitLab issues
  GitLab (Either (Response BSL.ByteString) [Issue])
projectIssues' :: Int -> IssueAttrs -> GitLab (Either (Response ByteString) [Issue])
projectIssues' Int
projectId IssueAttrs
attrs =
  Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) [Issue])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
urlPath (IssueAttrs -> [GitLabParam]
issuesAttrs IssueAttrs
attrs)
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$
        [Char]
"/projects/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projectId
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/issues"

-- | Only for administrators. Get a single issue.
issue ::
  -- | issue ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Issue))
issue :: Int -> GitLab (Either (Response ByteString) (Maybe Issue))
issue Int
issId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Issue))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
urlPath []
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack
        [Char]
"/issues/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issId)

-- | gets all issues create by a user.
userIssues ::
  -- | the user
  User ->
  GitLab [Issue]
userIssues :: User -> GitLab [Issue]
userIssues User
usr =
  [Issue] -> Either (Response ByteString) [Issue] -> [Issue]
forall b a. b -> Either a b -> b
fromRight ([Char] -> [Issue]
forall a. HasCallStack => [Char] -> a
error [Char]
"userIssues error") (Either (Response ByteString) [Issue] -> [Issue])
-> GitLab (Either (Response ByteString) [Issue]) -> GitLab [Issue]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) [Issue])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
addr [GitLabParam]
params
  where
    addr :: Text
addr = Text
"/issues"
    params :: [GitLabParam]
    params :: [GitLabParam]
params =
      [ (ByteString
"author_id", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (User -> Int
user_id User
usr))))),
        (ByteString
"scope", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"all")
      ]

-- | Get a single project issue. If the project is private or the
-- issue is confidential, you need to provide credentials to
-- authorize.
projectIssue ::
  -- | Project
  Project ->
  -- | issue ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Issue))
projectIssue :: Project
-> Int -> GitLab (Either (Response ByteString) (Maybe Issue))
projectIssue Project
p Int
issId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Issue))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
urlPath []
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack
        [Char]
"/project/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
p))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issId)

-- | create a new issue.
newIssue ::
  -- | project
  Project ->
  -- | issue title
  Text ->
  -- | issue description
  Text ->
  GitLab (Either (Response BSL.ByteString) (Maybe Issue))
newIssue :: Project
-> Text
-> Text
-> GitLab (Either (Response ByteString) (Maybe Issue))
newIssue Project
project =
  Int
-> Text
-> Text
-> GitLab (Either (Response ByteString) (Maybe Issue))
newIssue' (Project -> Int
project_id Project
project)

-- | create a new issue.
newIssue' ::
  -- | project ID
  Int ->
  -- | issue title
  Text ->
  -- | issue description
  Text ->
  GitLab (Either (Response BSL.ByteString) (Maybe Issue))
newIssue' :: Int
-> Text
-> Text
-> GitLab (Either (Response ByteString) (Maybe Issue))
newIssue' Int
projectId Text
issueTitle Text
issueDescription =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Issue))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr [GitLabParam]
dataBody
  where
    dataBody :: [GitLabParam]
    dataBody :: [GitLabParam]
dataBody =
      [ (ByteString
"title", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
issueTitle)),
        (ByteString
"description", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
issueDescription))
      ]
    addr :: Text
addr =
      Text
"/projects/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projectId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues"

-- | edits an issue. see <https://docs.gitlab.com/ee/api/issues.html#edit-issue>
editIssue ::
  Project ->
  -- | issue ID
  IssueId ->
  EditIssueReq ->
  GitLab (Either (Response BSL.ByteString) Issue)
editIssue :: Project
-> Int
-> EditIssueReq
-> GitLab (Either (Response ByteString) Issue)
editIssue Project
prj Int
issueId EditIssueReq
editIssueReq = do
  let urlPath :: Text
urlPath =
        Text
"/projects/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues/"
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId)
  Either (Response ByteString) (Maybe Issue)
result <-
    Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Issue))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPut
      Text
urlPath
      (EditIssueReq -> [GitLabParam]
editIssuesAttrs EditIssueReq
editIssueReq)
  case Either (Response ByteString) (Maybe Issue)
result of
    Left Response ByteString
resp -> Either (Response ByteString) Issue
-> GitLab (Either (Response ByteString) Issue)
forall (m :: * -> *) a. Monad m => a -> m a
return (Response ByteString -> Either (Response ByteString) Issue
forall a b. a -> Either a b
Left Response ByteString
resp)
    Right Maybe Issue
Nothing -> [Char] -> GitLab (Either (Response ByteString) Issue)
forall a. HasCallStack => [Char] -> a
error [Char]
"editIssue error"
    Right (Just Issue
iss) -> Either (Response ByteString) Issue
-> GitLab (Either (Response ByteString) Issue)
forall (m :: * -> *) a. Monad m => a -> m a
return (Issue -> Either (Response ByteString) Issue
forall a b. b -> Either a b
Right Issue
iss)

-- | deletes an issue. see <https://docs.gitlab.com/ee/api/issues.html#delete-an-issue>
deleteIssue ::
  Project ->
  -- | issue ID
  IssueId ->
  GitLab (Either (Response BSL.ByteString) (Maybe ()))
deleteIssue :: Project -> Int -> GitLab (Either (Response ByteString) (Maybe ()))
deleteIssue Project
prj Int
issueId = do
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe ()))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabDelete Text
issueAddr []
  where
    issueAddr :: Text
    issueAddr :: Text
issueAddr =
      Text
"/projects/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId)

-- | edits an issue. see <https://docs.gitlab.com/ee/api/issues.html#edit-issue>
reorderIssue ::
  Project ->
  -- | issue ID
  IssueId ->
  -- | The ID of a project’s issue that should be placed after this
  -- issue
  Int ->
  -- | The ID of a project’s issue that should be placed before this
  -- issue
  Int ->
  GitLab (Either (Response BSL.ByteString) Issue)
reorderIssue :: Project
-> Int -> Int -> Int -> GitLab (Either (Response ByteString) Issue)
reorderIssue Project
prj Int
issueId Int
moveAfterId Int
moveBeforeId = do
  let urlPath :: Text
urlPath =
        Text
"/projects/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues/"
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId)
          Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/reorder"
  Either (Response ByteString) (Maybe Issue)
result <-
    Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Issue))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPut
      Text
urlPath
      [ (ByteString
"move_after_id", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
moveAfterId)))),
        (ByteString
"move_before_id", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
moveBeforeId))))
      ]
  case Either (Response ByteString) (Maybe Issue)
result of
    Left Response ByteString
resp -> Either (Response ByteString) Issue
-> GitLab (Either (Response ByteString) Issue)
forall (m :: * -> *) a. Monad m => a -> m a
return (Response ByteString -> Either (Response ByteString) Issue
forall a b. a -> Either a b
Left Response ByteString
resp)
    Right Maybe Issue
Nothing -> [Char] -> GitLab (Either (Response ByteString) Issue)
forall a. HasCallStack => [Char] -> a
error [Char]
"reorderIssue error"
    Right (Just Issue
iss) -> Either (Response ByteString) Issue
-> GitLab (Either (Response ByteString) Issue)
forall (m :: * -> *) a. Monad m => a -> m a
return (Issue -> Either (Response ByteString) Issue
forall a b. b -> Either a b
Right Issue
iss)

-- | Moves an issue to a different project. If a given label or
-- milestone with the same name also exists in the target project,
-- it’s then assigned to the issue being moved.
moveIssue ::
  -- | project
  Project ->
  -- | The internal ID of a project’s issue
  IssueId ->
  -- | The ID of the new project
  ProjectId ->
  GitLab (Either (Response BSL.ByteString) (Maybe Issue))
moveIssue :: Project
-> Int
-> Int
-> GitLab (Either (Response ByteString) (Maybe Issue))
moveIssue Project
prj Int
issueId Int
toPrjId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Issue))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr [GitLabParam]
dataBody
  where
    dataBody :: [GitLabParam]
    dataBody :: [GitLabParam]
dataBody =
      [ (ByteString
"to_project_id", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
toPrjId))))
      ]
    addr :: Text
addr =
      Text
"/projects/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/move"

-- | Clone the issue to given project. Copies as much data as possible
-- as long as the target project contains equivalent labels,
-- milestones, and so on.
cloneIssue ::
  -- | project
  Project ->
  -- | The internal ID of a project’s issue
  IssueId ->
  -- | The ID of the new project
  ProjectId ->
  GitLab (Either (Response BSL.ByteString) (Maybe Issue))
cloneIssue :: Project
-> Int
-> Int
-> GitLab (Either (Response ByteString) (Maybe Issue))
cloneIssue Project
prj Int
issueId Int
toPrjId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Issue))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr [GitLabParam]
dataBody
  where
    dataBody :: [GitLabParam]
    dataBody :: [GitLabParam]
dataBody =
      [ (ByteString
"to_project_id", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
toPrjId))))
      ]
    addr :: Text
addr =
      Text
"/projects/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/clone"

-- | Subscribes the authenticated user to an issue to receive
-- notifications.
subscribeIssue ::
  -- | project
  Project ->
  -- | The internal ID of a project’s issue
  IssueId ->
  GitLab (Either (Response BSL.ByteString) (Maybe Issue))
subscribeIssue :: Project
-> Int -> GitLab (Either (Response ByteString) (Maybe Issue))
subscribeIssue Project
prj Int
issueId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Issue))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr [GitLabParam]
dataBody
  where
    dataBody :: [GitLabParam]
    dataBody :: [GitLabParam]
dataBody =
      []
    addr :: Text
addr =
      Text
"/projects/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/subscribe"

-- | Unsubscribes the authenticated user from the issue to not receive
-- notifications from it.
unsubscribeIssue ::
  -- | project
  Project ->
  -- | The internal ID of a project’s issue
  IssueId ->
  GitLab (Either (Response BSL.ByteString) (Maybe Issue))
unsubscribeIssue :: Project
-> Int -> GitLab (Either (Response ByteString) (Maybe Issue))
unsubscribeIssue Project
prj Int
issueId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Issue))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr [GitLabParam]
dataBody
  where
    dataBody :: [GitLabParam]
    dataBody :: [GitLabParam]
dataBody =
      []
    addr :: Text
addr =
      Text
"/projects/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/unsubscribe"

-- | Get all the merge requests that are related to the issue.
createTodo ::
  -- | project
  Project ->
  -- | The internal ID of a project’s issue
  IssueId ->
  GitLab (Either (Response BSL.ByteString) (Maybe Todo))
createTodo :: Project
-> Int -> GitLab (Either (Response ByteString) (Maybe Todo))
createTodo Project
prj Int
issueId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Todo))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr [GitLabParam]
dataBody
  where
    dataBody :: [GitLabParam]
    dataBody :: [GitLabParam]
dataBody =
      []
    addr :: Text
addr =
      Text
"/projects/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/issues/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/todo"

-- | Get all the merge requests that are related to the issue.
issueMergeRequests ::
  -- | project
  Project ->
  -- | The internal ID of a project’s issue
  IssueId ->
  GitLab (Either (Response BSL.ByteString) [MergeRequest])
issueMergeRequests :: Project
-> Int -> GitLab (Either (Response ByteString) [MergeRequest])
issueMergeRequests Project
prj Int
issueId = do
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) [MergeRequest])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
urlPath []
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$
        [Char]
"/projects/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj)
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/issues/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/related_merge_requests"

-- | get all merge requests that close a particular issue when merged.
issueMergeRequestsThatClose ::
  -- | project
  Project ->
  -- | The internal ID of a project’s issue
  IssueId ->
  GitLab (Either (Response BSL.ByteString) [MergeRequest])
issueMergeRequestsThatClose :: Project
-> Int -> GitLab (Either (Response ByteString) [MergeRequest])
issueMergeRequestsThatClose Project
prj Int
issueId = do
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) [MergeRequest])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
urlPath []
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$
        [Char]
"/projects/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj)
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/issues/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/closed_by"

-- | get all merge requests that close a particular issue when merged.
issueParticipants ::
  -- | project
  Project ->
  -- | The internal ID of a project’s issue
  IssueId ->
  GitLab (Either (Response BSL.ByteString) [User])
issueParticipants :: Project -> Int -> GitLab (Either (Response ByteString) [User])
issueParticipants Project
prj Int
issueId = do
  Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) [User])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
urlPath []
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$
        [Char]
"/projects/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj)
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/issues/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show Int
issueId
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/participants"

-- | Gets issues count statistics on all issues the authenticated user has access to.
issueStatisticsUser ::
  -- | filter the issues, see https://docs.gitlab.com/ee/api/issues_statistics.html#get-issues-statistics
  IssueAttrs ->
  -- | the issue statistics
  GitLab IssueStatistics
issueStatisticsUser :: IssueAttrs -> GitLab IssueStatistics
issueStatisticsUser IssueAttrs
attrs =
  GitLab (Either (Response ByteString) (Maybe IssueStatistics))
-> GitLab IssueStatistics
forall a b. GitLab (Either a (Maybe b)) -> GitLab b
gitlabUnsafe (Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe IssueStatistics))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
urlPath (IssueAttrs -> [GitLabParam]
issuesAttrs IssueAttrs
attrs))
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack
        [Char]
"/issues_statistics"

-- | Gets issues count statistics for a given group.
issueStatisticsGroup ::
  -- | the group
  Group ->
  -- | filter the issues, see https://docs.gitlab.com/ee/api/issues_statistics.html#get-issues-statistics
  IssueAttrs ->
  -- | the issue statistics
  GitLab IssueStatistics
issueStatisticsGroup :: Group -> IssueAttrs -> GitLab IssueStatistics
issueStatisticsGroup Group
group IssueAttrs
filters = do
  Either (Response ByteString) (Maybe IssueStatistics)
result <- Int
-> IssueAttrs
-> GitLab (Either (Response ByteString) (Maybe IssueStatistics))
issueStatisticsGroup' (Group -> Int
group_id Group
group) IssueAttrs
filters
  case Either (Response ByteString) (Maybe IssueStatistics)
result of
    Left Response ByteString
_s -> [Char] -> GitLab IssueStatistics
forall a. HasCallStack => [Char] -> a
error [Char]
"issueStatisticsGroup error"
    Right Maybe IssueStatistics
Nothing -> [Char] -> GitLab IssueStatistics
forall a. HasCallStack => [Char] -> a
error [Char]
"issueStatisticsGroup error"
    Right (Just IssueStatistics
stats) -> IssueStatistics -> GitLab IssueStatistics
forall (m :: * -> *) a. Monad m => a -> m a
return IssueStatistics
stats

-- | Gets issues count statistics for a given group.
issueStatisticsGroup' ::
  -- | the group ID
  Int ->
  -- | filter the issues, see https://docs.gitlab.com/ee/api/issues_statistics.html#get-issues-statistics
  IssueAttrs ->
  -- | the issue statistics
  GitLab (Either (Response BSL.ByteString) (Maybe IssueStatistics))
issueStatisticsGroup' :: Int
-> IssueAttrs
-> GitLab (Either (Response ByteString) (Maybe IssueStatistics))
issueStatisticsGroup' Int
groupId IssueAttrs
attrs =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe IssueStatistics))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
urlPath (IssueAttrs -> [GitLabParam]
issuesAttrs IssueAttrs
attrs)
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$
        [Char]
"/groups/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show Int
groupId
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/issues_statistics"

-- | Gets issues count statistics for a given group.
issueStatisticsProject ::
  -- | the project
  Project ->
  -- | filter the issues, see https://docs.gitlab.com/ee/api/issues_statistics.html#get-issues-statistics
  IssueAttrs ->
  -- | the issue statistics
  GitLab IssueStatistics
issueStatisticsProject :: Project -> IssueAttrs -> GitLab IssueStatistics
issueStatisticsProject Project
proj IssueAttrs
filters = do
  Either (Response ByteString) (Maybe IssueStatistics)
result <- Int
-> IssueAttrs
-> GitLab (Either (Response ByteString) (Maybe IssueStatistics))
issueStatisticsProject' (Project -> Int
project_id Project
proj) IssueAttrs
filters
  case Either (Response ByteString) (Maybe IssueStatistics)
result of
    Left Response ByteString
_s -> [Char] -> GitLab IssueStatistics
forall a. HasCallStack => [Char] -> a
error [Char]
"issueStatisticsProject error"
    Right Maybe IssueStatistics
Nothing -> [Char] -> GitLab IssueStatistics
forall a. HasCallStack => [Char] -> a
error [Char]
"issueStatisticsProject error"
    Right (Just IssueStatistics
stats) -> IssueStatistics -> GitLab IssueStatistics
forall (m :: * -> *) a. Monad m => a -> m a
return IssueStatistics
stats

-- | Gets issues count statistics for a given project.
issueStatisticsProject' ::
  -- | the project ID
  Int ->
  -- | filter the issues, see https://docs.gitlab.com/ee/api/issues_statistics.html#get-issues-statistics
  IssueAttrs ->
  -- | the issue statistics
  GitLab (Either (Response BSL.ByteString) (Maybe IssueStatistics))
issueStatisticsProject' :: Int
-> IssueAttrs
-> GitLab (Either (Response ByteString) (Maybe IssueStatistics))
issueStatisticsProject' Int
projId IssueAttrs
attrs =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe IssueStatistics))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
urlPath (IssueAttrs -> [GitLabParam]
issuesAttrs IssueAttrs
attrs)
  where
    urlPath :: Text
urlPath =
      [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$
        [Char]
"/projects/"
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show Int
projId
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/issues_statistics"

-- | Attributes related to a project issue
data IssueAttrs = IssueAttrs
  { IssueAttrs -> Maybe Int
issueFilter_assignee_id :: Maybe Int,
    IssueAttrs -> Maybe [Char]
issueFilter_assignee_username :: Maybe String,
    IssueAttrs -> Maybe Int
issueFilter_author_id :: Maybe Int,
    IssueAttrs -> Maybe [Char]
issueFilter_author_username :: Maybe String,
    IssueAttrs -> Maybe Bool
issueFilter_confidential :: Maybe Bool,
    IssueAttrs -> Maybe UTCTime
issueFilter_created_after :: Maybe UTCTime,
    IssueAttrs -> Maybe UTCTime
issueFilter_created_before :: Maybe UTCTime,
    IssueAttrs -> Maybe DueDate
issueFilter_due_date :: Maybe DueDate,
    IssueAttrs -> Maybe Int
issueFilter_iids :: Maybe Int,
    IssueAttrs -> Maybe SearchIn
issueFilter_in :: Maybe SearchIn,
    IssueAttrs -> Maybe Int
issueFilter_iteration_id :: Maybe Int,
    IssueAttrs -> Maybe [Char]
issueFilter_iteration_title :: Maybe String,
    IssueAttrs -> Maybe [Char]
issueFilter_milestone :: Maybe String,
    IssueAttrs -> Maybe [Char]
issueFilter_labels :: Maybe String,
    IssueAttrs -> Maybe [Char]
issueFilter_my_reaction_emoji :: Maybe String,
    IssueAttrs -> Maybe Bool
issueFilter_non_archived :: Maybe Bool,
    IssueAttrs -> Maybe OrderBy
issueFilter_order_by :: Maybe OrderBy,
    IssueAttrs -> Maybe Scope
issueFilter_scope :: Maybe Scope,
    IssueAttrs -> Maybe [Char]
issueFilter_search :: Maybe String,
    IssueAttrs -> Maybe SortBy
issueFilter_sort :: Maybe SortBy,
    IssueAttrs -> Maybe IssueState
issueFilter_state :: Maybe IssueState,
    IssueAttrs -> Maybe UTCTime
issueFilter_updated_after :: Maybe UTCTime,
    IssueAttrs -> Maybe UTCTime
issueFilter_updated_before :: Maybe UTCTime,
    IssueAttrs -> Maybe Bool
issueFilter_with_labels_details :: Maybe Bool
  }

editIssuesAttrs :: EditIssueReq -> [GitLabParam]
editIssuesAttrs :: EditIssueReq -> [GitLabParam]
editIssuesAttrs EditIssueReq
filters =
  [Maybe GitLabParam] -> [GitLabParam]
forall a. [Maybe a] -> [a]
catMaybes
    [ GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"id", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (EditIssueReq -> Int
edit_issue_id EditIssueReq
filters)))),
      GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"issue_id", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show (EditIssueReq -> Int
edit_issue_issue_iid EditIssueReq
filters)))),
      -- (\i -> Just ("assignee_id", textToBS (T.pack (show i)))) =<< edit_issue_issue_id filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"title", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Text
edit_issue_title EditIssueReq
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"description", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Text
edit_issue_description EditIssueReq
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"confidential", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Bool
edit_issue_confidential EditIssueReq
filters,
      -- TODO
      -- (\is -> Just ("assignee_ids", textToBS )) =<< edit_issue_assignee_ids filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"milestone_id", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Int
edit_issue_milestone_id EditIssueReq
filters,
      -- TODO
      -- (\ts -> Just ("labels", textToBS (T.pack (show i)))) =<< edit_issue_labels filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"state_event", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Text
edit_issue_state_event EditIssueReq
filters,
      (\UTCTime
d -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"updated_at", [Char] -> Maybe ByteString
stringToBS (UTCTime -> [Char]
forall a. Show a => a -> [Char]
show UTCTime
d))) (UTCTime -> Maybe GitLabParam)
-> Maybe UTCTime -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe UTCTime
edit_issue_updated_at EditIssueReq
filters,
      (\Text
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"due_date", Text -> Maybe ByteString
textToBS Text
t)) (Text -> Maybe GitLabParam) -> Maybe Text -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Text
edit_issue_due_date EditIssueReq
filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"weight", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Int
edit_issue_weight EditIssueReq
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"discussion_locked", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Bool
edit_issue_discussion_locked EditIssueReq
filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"epic_id", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Int
edit_issue_epic_id EditIssueReq
filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"epic_iid", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EditIssueReq -> Maybe Int
edit_issue_epic_iid EditIssueReq
filters
    ]
  where
    textToBS :: Text -> Maybe ByteString
textToBS = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Text -> ByteString) -> Text -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
    stringToBS :: [Char] -> Maybe ByteString
stringToBS = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> ([Char] -> ByteString) -> [Char] -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8 (Text -> ByteString) -> ([Char] -> Text) -> [Char] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack
    showBool :: Bool -> Text
    showBool :: Bool -> Text
showBool Bool
True = Text
"true"
    showBool Bool
False = Text
"false"

issuesAttrs :: IssueAttrs -> [GitLabParam]
issuesAttrs :: IssueAttrs -> [GitLabParam]
issuesAttrs IssueAttrs
filters =
  [Maybe GitLabParam] -> [GitLabParam]
forall a. [Maybe a] -> [a]
catMaybes
    [ (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"assignee_id", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe Int
issueFilter_assignee_id IssueAttrs
filters,
      (\[Char]
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"assignee_username", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack [Char]
t))) ([Char] -> Maybe GitLabParam) -> Maybe [Char] -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe [Char]
issueFilter_assignee_username IssueAttrs
filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"author_id", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe Int
issueFilter_author_id IssueAttrs
filters,
      (\[Char]
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"author_username", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack ([Char] -> [Char]
forall a. Show a => a -> [Char]
show [Char]
i)))) ([Char] -> Maybe GitLabParam) -> Maybe [Char] -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe [Char]
issueFilter_author_username IssueAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"confidential", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe Bool
issueFilter_confidential IssueAttrs
filters,
      (\UTCTime
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"created_after", Text -> Maybe ByteString
textToBS (UTCTime -> Text
showTime UTCTime
t))) (UTCTime -> Maybe GitLabParam)
-> Maybe UTCTime -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe UTCTime
issueFilter_created_after IssueAttrs
filters,
      (\UTCTime
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"created_before", Text -> Maybe ByteString
textToBS (UTCTime -> Text
showTime UTCTime
t))) (UTCTime -> Maybe GitLabParam)
-> Maybe UTCTime -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe UTCTime
issueFilter_created_before IssueAttrs
filters,
      (\DueDate
due -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"due_date", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (DueDate -> [Char]
forall a. Show a => a -> [Char]
show DueDate
due)))) (DueDate -> Maybe GitLabParam)
-> Maybe DueDate -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe DueDate
issueFilter_due_date IssueAttrs
filters,
      (\Int
iids -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"iids[]", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
iids)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe Int
issueFilter_iids IssueAttrs
filters,
      (\SearchIn
issueIn -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"assignee_id", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (SearchIn -> [Char]
forall a. Show a => a -> [Char]
show SearchIn
issueIn)))) (SearchIn -> Maybe GitLabParam)
-> Maybe SearchIn -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe SearchIn
issueFilter_in IssueAttrs
filters,
      (\Int
i -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"iteration_id", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
i)))) (Int -> Maybe GitLabParam) -> Maybe Int -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe Int
issueFilter_iteration_id IssueAttrs
filters,
      (\[Char]
s -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"iteration_title", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack [Char]
s))) ([Char] -> Maybe GitLabParam) -> Maybe [Char] -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe [Char]
issueFilter_iteration_title IssueAttrs
filters,
      (\[Char]
s -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"milestone", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack [Char]
s))) ([Char] -> Maybe GitLabParam) -> Maybe [Char] -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe [Char]
issueFilter_milestone IssueAttrs
filters,
      (\[Char]
s -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"labels", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack [Char]
s))) ([Char] -> Maybe GitLabParam) -> Maybe [Char] -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe [Char]
issueFilter_labels IssueAttrs
filters,
      (\[Char]
s -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"my_reaction_emoji", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack [Char]
s))) ([Char] -> Maybe GitLabParam) -> Maybe [Char] -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe [Char]
issueFilter_my_reaction_emoji IssueAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"non_archived", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe Bool
issueFilter_non_archived IssueAttrs
filters,
      (\OrderBy
x -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"order_by", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (OrderBy -> [Char]
forall a. Show a => a -> [Char]
show OrderBy
x)))) (OrderBy -> Maybe GitLabParam)
-> Maybe OrderBy -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe OrderBy
issueFilter_order_by IssueAttrs
filters,
      (\Scope
x -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"scope", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (Scope -> [Char]
forall a. Show a => a -> [Char]
show Scope
x)))) (Scope -> Maybe GitLabParam) -> Maybe Scope -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe Scope
issueFilter_scope IssueAttrs
filters,
      (\[Char]
s -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"search", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack [Char]
s))) ([Char] -> Maybe GitLabParam) -> Maybe [Char] -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe [Char]
issueFilter_search IssueAttrs
filters,
      (\SortBy
x -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"sort", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (SortBy -> [Char]
forall a. Show a => a -> [Char]
show SortBy
x)))) (SortBy -> Maybe GitLabParam) -> Maybe SortBy -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe SortBy
issueFilter_sort IssueAttrs
filters,
      (\IssueState
x -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"state", Text -> Maybe ByteString
textToBS ([Char] -> Text
T.pack (IssueState -> [Char]
forall a. Show a => a -> [Char]
show IssueState
x)))) (IssueState -> Maybe GitLabParam)
-> Maybe IssueState -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe IssueState
issueFilter_state IssueAttrs
filters,
      (\UTCTime
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"updated_after", Text -> Maybe ByteString
textToBS (UTCTime -> Text
showTime UTCTime
t))) (UTCTime -> Maybe GitLabParam)
-> Maybe UTCTime -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe UTCTime
issueFilter_updated_after IssueAttrs
filters,
      (\UTCTime
t -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"updated_before", Text -> Maybe ByteString
textToBS (UTCTime -> Text
showTime UTCTime
t))) (UTCTime -> Maybe GitLabParam)
-> Maybe UTCTime -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe UTCTime
issueFilter_updated_before IssueAttrs
filters,
      (\Bool
b -> GitLabParam -> Maybe GitLabParam
forall a. a -> Maybe a
Just (ByteString
"with_labels_details", Text -> Maybe ByteString
textToBS (Bool -> Text
showBool Bool
b))) (Bool -> Maybe GitLabParam) -> Maybe Bool -> Maybe GitLabParam
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IssueAttrs -> Maybe Bool
issueFilter_with_labels_details IssueAttrs
filters
    ]
  where
    textToBS :: Text -> Maybe ByteString
textToBS = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Text -> ByteString) -> Text -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
    showBool :: Bool -> Text
    showBool :: Bool -> Text
showBool Bool
True = Text
"true"
    showBool Bool
False = Text
"false"
    showTime :: UTCTime -> Text
    showTime :: UTCTime -> Text
showTime = [Char] -> Text
T.pack ([Char] -> Text) -> (UTCTime -> [Char]) -> UTCTime -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTCTime -> [Char]
forall t. ISO8601 t => t -> [Char]
iso8601Show

-- | When an issue is due
data DueDate
  = NoDueDate
  | Overdue
  | Week
  | Month
  | NextMonthPreviousTwoWeeks

instance Show DueDate where
  show :: DueDate -> [Char]
show DueDate
NoDueDate = [Char]
"0"
  show DueDate
Overdue = [Char]
"overdue"
  show DueDate
Week = [Char]
"week"
  show DueDate
Month = [Char]
"month"
  show DueDate
NextMonthPreviousTwoWeeks = [Char]
"next_month_and_previous_two_weeks"

-- | Is a project issues open or closed
data IssueState
  = IssueOpen
  | IssueClosed

instance Show IssueState where
  show :: IssueState -> [Char]
show IssueState
IssueOpen = [Char]
"opened"
  show IssueState
IssueClosed = [Char]
"closed"

-- | No issue filters, thereby returning all issues. Default scope is "all".
defaultIssueFilters :: IssueAttrs
defaultIssueFilters :: IssueAttrs
defaultIssueFilters =
  Maybe Int
-> Maybe [Char]
-> Maybe Int
-> Maybe [Char]
-> Maybe Bool
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe DueDate
-> Maybe Int
-> Maybe SearchIn
-> Maybe Int
-> Maybe [Char]
-> Maybe [Char]
-> Maybe [Char]
-> Maybe [Char]
-> Maybe Bool
-> Maybe OrderBy
-> Maybe Scope
-> Maybe [Char]
-> Maybe SortBy
-> Maybe IssueState
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe Bool
-> IssueAttrs
IssueAttrs Maybe Int
forall a. Maybe a
Nothing Maybe [Char]
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe [Char]
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe UTCTime
forall a. Maybe a
Nothing Maybe UTCTime
forall a. Maybe a
Nothing Maybe DueDate
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe SearchIn
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Maybe [Char]
forall a. Maybe a
Nothing Maybe [Char]
forall a. Maybe a
Nothing Maybe [Char]
forall a. Maybe a
Nothing Maybe [Char]
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe OrderBy
forall a. Maybe a
Nothing (Scope -> Maybe Scope
forall a. a -> Maybe a
Just Scope
All) Maybe [Char]
forall a. Maybe a
Nothing Maybe SortBy
forall a. Maybe a
Nothing Maybe IssueState
forall a. Maybe a
Nothing Maybe UTCTime
forall a. Maybe a
Nothing Maybe UTCTime
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing