{-# 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 where

import Data.Either
import qualified Data.Text as T
import GitLab.Types
import GitLab.WebRequests.GitLabWebCalls
import Network.HTTP.Types.Status

-- | returns the pipelines for a project.
pipelines ::
  -- | the project
  Project ->
  GitLab [Pipeline]
pipelines :: Project -> GitLab [Pipeline]
pipelines Project
p = do
  Either Status [Pipeline]
result <- Int -> GitLab (Either Status [Pipeline])
pipelines' (Project -> Int
project_id Project
p)
  [Pipeline] -> GitLab [Pipeline]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Pipeline] -> Either Status [Pipeline] -> [Pipeline]
forall b a. b -> Either a b -> b
fromRight ([Char] -> [Pipeline]
forall a. HasCallStack => [Char] -> a
error [Char]
"pipelines error") Either Status [Pipeline]
result)

-- | returns the pipelines for a project given its project ID.
pipelines' ::
  -- | the project ID
  Int ->
  GitLab (Either Status [Pipeline])
pipelines' :: Int -> GitLab (Either Status [Pipeline])
pipelines' Int
projectId =
  Text -> Text -> GitLab (Either Status [Pipeline])
forall a. FromJSON a => Text -> Text -> GitLab (Either Status [a])
gitlabWithAttrs
    Text
addr
    Text
"&sort=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"