{-# LANGUAGE OverloadedStrings #-}

-- |
-- Module      : Tags
-- Description : Queries about tags in repositories
-- Copyright   : (c) Jihyun Yu, 2021; Rob Stewart, 2022
-- License     : BSD3
-- Maintainer  : yjh0502@gmail.com, robstewart57@gmail.com
-- Stability   : stable
module GitLab.API.Tags
  ( -- * List project repository tags
    tags,

    -- * Get a single repository tag
    tag,

    -- * Create a new tag
    createTag,

    -- * Delete a tag
    deleteTag,
  )
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

-- | Get a list of repository tags from a project.
tags ::
  -- | the project
  Project ->
  GitLab (Either (Response BSL.ByteString) [Tag])
tags :: Project -> GitLab (Either (Response ByteString) [Tag])
tags Project
prj = do
  Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) [Tag])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany (Int -> Text
commitsAddr (Project -> Int
project_id Project
prj)) []
  where
    commitsAddr :: Int -> Text
    commitsAddr :: Int -> Text
commitsAddr Int
projId =
      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
projId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/tags"

-- | Get a specific repository tag determined by its name.
tag ::
  -- | the project
  Project ->
  -- | the name of the tag
  Text ->
  GitLab (Either (Response BSL.ByteString) (Maybe Tag))
tag :: Project
-> Text -> GitLab (Either (Response ByteString) (Maybe Tag))
tag Project
prj Text
tagName = do
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Tag))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabGetOne (Int -> Text
commitsAddr (Project -> Int
project_id Project
prj)) []
  where
    commitsAddr :: Int -> Text
    commitsAddr :: Int -> Text
commitsAddr Int
projId =
      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
projId)
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/repository"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/tags/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tagName

-- | Creates a new tag in the repository that points to the supplied
-- ref.
createTag ::
  -- | the project
  Project ->
  -- | the name of the tag
  Text ->
  -- | Create tag using commit SHA, another tag name, or branch name
  Text ->
  GitLab (Either (Response BSL.ByteString) (Maybe Tag))
createTag :: Project
-> Text
-> Text
-> GitLab (Either (Response ByteString) (Maybe Tag))
createTag Project
prj Text
tagName Text
ref = do
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe Tag))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabPost Text
newTagAddr [(ByteString
"tag_name", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
tagName)), (ByteString
"ref", ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Text -> ByteString
T.encodeUtf8 Text
ref))]
  where
    newTagAddr :: Text
    newTagAddr :: Text
newTagAddr =
      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
"/repository"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/tags"

-- | Deletes a tag of a repository with given name.
deleteTag ::
  -- | the project
  Project ->
  -- | the name of the tag
  Text ->
  GitLab (Either (Response BSL.ByteString) (Maybe ()))
deleteTag :: Project -> Text -> GitLab (Either (Response ByteString) (Maybe ()))
deleteTag Project
prj Text
tagName =
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) (Maybe ()))
forall a.
FromJSON a =>
Text
-> [GitLabParam] -> GitLab (Either (Response ByteString) (Maybe a))
gitlabDelete Text
tagAddr []
  where
    tagAddr :: Text
    tagAddr :: Text
tagAddr =
      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
"/repository"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/tags/"
        Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tagName