{-# LANGUAGE OverloadedStrings #-}

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

    -- * Get a single pipeline
    pipeline,

    -- * Get a pipeline’s test report
    pipelineTestReport,

    -- * Create a new pipeline
    newPipeline,

    -- * Retry jobs in a pipeline
    retryPipeline,

    -- * Cancel a pipeline’s jobs
    cancelPipelineJobs,

    -- * Delete a pipeline
    deletePipeline,
  )
where

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

-- | List pipelines in a project. Child pipelines are not included in
-- the results, but you can get child pipeline individually.
pipelines ::
  -- | the project
  Project ->
  GitLab [Pipeline]
pipelines :: Project -> GitLab [Pipeline]
pipelines Project
p = do
  Either (Response ByteString) [Pipeline]
result <- Int -> GitLab (Either (Response ByteString) [Pipeline])
pipelines' (Project -> Int
project_id Project
p)
  [Pipeline] -> GitLab [Pipeline]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Pipeline] -> Either (Response ByteString) [Pipeline] -> [Pipeline]
forall b a. b -> Either a b -> b
fromRight ([Char] -> [Pipeline]
forall a. HasCallStack => [Char] -> a
error [Char]
"pipelines error") Either (Response ByteString) [Pipeline]
result)

-- | returns the pipelines for a project given its project ID.
pipelines' ::
  -- | the project ID
  Int ->
  GitLab (Either (Response BSL.ByteString) [Pipeline])
pipelines' :: Int -> GitLab (Either (Response ByteString) [Pipeline])
pipelines' Int
projectId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) [Pipeline])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany
    Text
addr
    [(ByteString
"sort", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
"desc")] -- most recent first
  where
    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
"/pipelines"

-- | Get one pipeline from a project.
pipeline ::
  -- | the project
  Project ->
  -- | 	The ID of a pipeline
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Pipeline))
pipeline :: Project
-> Int -> GitLab (Either (Response ByteString) (Maybe Pipeline))
pipeline Project
prj Int
pipelineId =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Pipeline))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne
    Text
addr
    []
  where
    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
"/pipelines/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
pipelineId)

-- | get a pipeline’s test report. Since GitLab 13.0.
pipelineTestReport ::
  -- | the project
  Project ->
  -- | the pipeline ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe TestReport))
pipelineTestReport :: Project
-> Int -> GitLab (Either (Response ByteString) (Maybe TestReport))
pipelineTestReport Project
prj Int
pipelineId = do
  let urlPath :: Text
urlPath =
        [Char] -> Text
T.pack
          ( [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]
"/pipelines/"
              [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show Int
pipelineId
              [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
"/test_report"
          )
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe TestReport))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
urlPath []

-- | Create a new pipeline. Since GitLab 14.6.
newPipeline ::
  -- | the project
  Project ->
  -- | The branch or tag to run the pipeline on.
  Text ->
  GitLab (Either (Response BSL.ByteString) (Maybe Pipeline))
newPipeline :: Project
-> Text -> GitLab (Either (Response ByteString) (Maybe Pipeline))
newPipeline Project
prj Text
ref = do
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Pipeline))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
    Text
pipelineAddr
    [(ByteString
"ref", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
ref))]
  where
    pipelineAddr :: Text
    pipelineAddr :: Text
pipelineAddr =
      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
"/pipeline"

-- | Retry a pipeline. Since GitLab 14.6.
retryPipeline ::
  -- | the project
  Project ->
  -- | The ID of a pipeline
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Pipeline))
retryPipeline :: Project
-> Int -> GitLab (Either (Response ByteString) (Maybe Pipeline))
retryPipeline Project
prj Int
pipelineId = do
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Pipeline))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
    Text
pipelineAddr
    []
  where
    pipelineAddr :: Text
    pipelineAddr :: Text
pipelineAddr =
      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
"/pipelines/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
pipelineId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/retry"

-- | Cancel a pipeline's jobs.
cancelPipelineJobs ::
  -- | the project
  Project ->
  -- | The ID of a pipeline
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Pipeline))
cancelPipelineJobs :: Project
-> Int -> GitLab (Either (Response ByteString) (Maybe Pipeline))
cancelPipelineJobs Project
prj Int
pipelineId = do
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Pipeline))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost
    Text
pipelineAddr
    []
  where
    pipelineAddr :: Text
    pipelineAddr :: Text
pipelineAddr =
      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
"/pipelines/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
pipelineId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/cancel"

-- | Delete a pipline. Since GitLab 14.6.
deletePipeline ::
  -- | the project
  Project ->
  -- | The ID of a pipeline
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe ()))
deletePipeline :: Project -> Int -> GitLab (Either (Response ByteString) (Maybe ()))
deletePipeline Project
prj Int
pipelineId = do
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe ()))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabDelete Text
pipelineAddr []
  where
    pipelineAddr :: Text
    pipelineAddr :: Text
pipelineAddr =
      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
"/pipelines/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (Int -> [Char]
forall a. Show a => a -> [Char]
show Int
pipelineId)