{-# LANGUAGE OverloadedStrings #-}

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

    -- * List pipeline jobs
    pipelineJobs,

    -- * List pipeline bridges
    pipelineBridges,

    -- * Get a single job
    job,

    -- * Cancel a job
    cancelJob,

    -- * Retry a job
    retryJob,

    -- * Erase a job
    eraseJob,

    -- * Run a job
    runJob,
  )
where

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

-- | returns all jobs ran on a project.
jobs ::
  -- | the project
  Project ->
  GitLab [Job]
jobs :: Project -> GitLab [Job]
jobs Project
project = do
  Either (Response ByteString) [Job]
result <- Int -> GitLab (Either (Response ByteString) [Job])
jobs' (Project -> Int
project_id Project
project)
  forall (m :: * -> *) a. Monad m => a -> m a
return (forall b a. b -> Either a b -> b
fromRight (forall a. HasCallStack => [Char] -> a
error [Char]
"jobs error") Either (Response ByteString) [Job]
result)

-- | Get a list of jobs in a project. Jobs are sorted in descending
-- order of their IDs.
jobs' ::
  -- | the project ID
  Int ->
  GitLab (Either (Response BSL.ByteString) [Job])
jobs' :: Int -> GitLab (Either (Response ByteString) [Job])
jobs' Int
projectId =
  forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
addr []
  where
    addr :: Text
addr =
      Text
"/projects/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show Int
projectId)
        forall a. Semigroup a => a -> a -> a
<> Text
"/jobs"

-- | Get a list of jobs for a pipeline.
pipelineJobs ::
  -- | the project
  Project ->
  -- | pipeline ID
  Int ->
  GitLab (Either (Response BSL.ByteString) [Job])
pipelineJobs :: Project -> Int -> GitLab (Either (Response ByteString) [Job])
pipelineJobs Project
prj Int
pipelineId =
  forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
addr []
  where
    addr :: Text
addr =
      Text
"/projects/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        forall a. Semigroup a => a -> a -> a
<> Text
"/pipelines/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show Int
pipelineId)
        forall a. Semigroup a => a -> a -> a
<> Text
"/jobs"

-- | Get a list of bridge jobs for a pipeline.
pipelineBridges ::
  -- | the project
  Project ->
  -- | pipeline ID
  Int ->
  GitLab (Either (Response BSL.ByteString) [Job])
pipelineBridges :: Project -> Int -> GitLab (Either (Response ByteString) [Job])
pipelineBridges Project
prj Int
pipelineId =
  forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
addr []
  where
    addr :: Text
addr =
      Text
"/projects/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        forall a. Semigroup a => a -> a -> a
<> Text
"/pipelines/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show Int
pipelineId)
        forall a. Semigroup a => a -> a -> a
<> Text
"/bridges"

-- | Get a single job of a project.
job ::
  -- | the project
  Project ->
  -- | job ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Job))
job :: Project -> Int -> GitLab (Either (Response ByteString) (Maybe Job))
job Project
prj Int
jobId =
  forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne Text
addr []
  where
    addr :: Text
addr =
      Text
"/projects/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        forall a. Semigroup a => a -> a -> a
<> Text
"/jobs/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show Int
jobId)

-- | Cancel a single job of a project.
cancelJob ::
  -- | the project
  Project ->
  -- | job ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Job))
cancelJob :: Project -> Int -> GitLab (Either (Response ByteString) (Maybe Job))
cancelJob Project
prj Int
jobId =
  forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr []
  where
    addr :: Text
addr =
      Text
"/projects/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        forall a. Semigroup a => a -> a -> a
<> Text
"/jobs/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show Int
jobId)
        forall a. Semigroup a => a -> a -> a
<> Text
"/cancel"

-- | Retry a single job of a project.
retryJob ::
  -- | the project
  Project ->
  -- | job ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Job))
retryJob :: Project -> Int -> GitLab (Either (Response ByteString) (Maybe Job))
retryJob Project
prj Int
jobId =
  forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr []
  where
    addr :: Text
addr =
      Text
"/projects/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        forall a. Semigroup a => a -> a -> a
<> Text
"/jobs/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show Int
jobId)
        forall a. Semigroup a => a -> a -> a
<> Text
"/cancel"

-- | Retry a single job of a project.
eraseJob ::
  -- | the project
  Project ->
  -- | job ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Job))
eraseJob :: Project -> Int -> GitLab (Either (Response ByteString) (Maybe Job))
eraseJob Project
prj Int
jobId =
  forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr []
  where
    addr :: Text
addr =
      Text
"/projects/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        forall a. Semigroup a => a -> a -> a
<> Text
"/jobs/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show Int
jobId)
        forall a. Semigroup a => a -> a -> a
<> Text
"/erase"

-- | Triggers a manual action to start a job.
runJob ::
  -- | the project
  Project ->
  -- | job ID
  Int ->
  GitLab (Either (Response BSL.ByteString) (Maybe Job))
runJob :: Project -> Int -> GitLab (Either (Response ByteString) (Maybe Job))
runJob Project
prj Int
jobId =
  forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
addr []
  where
    addr :: Text
addr =
      Text
"/projects/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show (Project -> Int
project_id Project
prj))
        forall a. Semigroup a => a -> a -> a
<> Text
"/jobs/"
        forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show Int
jobId)
        forall a. Semigroup a => a -> a -> a
<> Text
"/play"