{-# LANGUAGE OverloadedStrings #-}
module GitLab.API.Pipelines
(
pipelines,
pipeline,
pipelineTestReport,
newPipeline,
retryPipeline,
cancelPipelineJobs,
deletePipeline,
)
where
import qualified Data.ByteString.Lazy as BSL
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
pipelines ::
Project ->
GitLab (Maybe [Pipeline])
pipelines :: Project -> GitLab (Maybe [Pipeline])
pipelines Project
p = do
Either (Response ByteString) [Pipeline]
result <- Int -> GitLab (Either (Response ByteString) [Pipeline])
pipelines' (Project -> Int
project_id Project
p)
case Either (Response ByteString) [Pipeline]
result of
Right [Pipeline]
ps -> Maybe [Pipeline] -> GitLab (Maybe [Pipeline])
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Pipeline] -> Maybe [Pipeline]
forall a. a -> Maybe a
Just [Pipeline]
ps)
Left Response ByteString
_err -> Maybe [Pipeline] -> GitLab (Maybe [Pipeline])
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Pipeline]
forall a. Maybe a
Nothing
pipelines' ::
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")]
where
addr :: Text
addr =
Text
"/projects/"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
projectId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/pipelines"
pipeline ::
Project ->
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
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
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
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
pipelineId)
pipelineTestReport ::
Project ->
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 =
String -> Text
T.pack
( String
"/projects/"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show (Project -> Int
project_id Project
prj)
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"/pipelines/"
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
pipelineId
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"/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 []
newPipeline ::
Project ->
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
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (Project -> Int
project_id Project
prj))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/pipeline"
retryPipeline ::
Project ->
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
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
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
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
pipelineId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/retry"
cancelPipelineJobs ::
Project ->
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
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
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
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
pipelineId)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/cancel"
deletePipeline ::
Project ->
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
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
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
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
pipelineId)