{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module      : Discussions
-- Description : Queries about discussions, which are a set of related notes on snippets, issues, epics, merge requests and commits.
-- Copyright   : (c) Rob Stewart, Heriot-Watt University, 2021
-- License     : BSD3
-- Maintainer  : robstewart57@gmail.com
-- Stability   : stable
module GitLab.API.Discussions where

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

-- | gets all discussion for a commit for a project.
commitDiscussions ::
  -- | the project
  Project ->
  -- | commit hash
  Text ->
  GitLab (Either (Response BSL.ByteString) [Discussion])
commitDiscussions :: Project
-> Text -> GitLab (Either (Response ByteString) [Discussion])
commitDiscussions Project
proj = Int -> Text -> GitLab (Either (Response ByteString) [Discussion])
commitDiscussions' (Project -> Int
project_id Project
proj)

-- | gets all discussion for a commit for a project given its project ID.
commitDiscussions' ::
  -- | the project ID
  Int ->
  -- | commit hash
  Text ->
  GitLab (Either (Response BSL.ByteString) [Discussion])
commitDiscussions' :: Int -> Text -> GitLab (Either (Response ByteString) [Discussion])
commitDiscussions' Int
projId Text
commitHash = do
  let urlPath :: Text
urlPath =
        String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$
          String
"/projects/"
            String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
projId
            String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"/repository"
            String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"/commits/"
            String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
commitHash
            String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"/discussions"
  Text
-> [GitLabParam]
-> GitLab (Either (Response ByteString) [Discussion])
forall a.
FromJSON a =>
Text -> [GitLabParam] -> GitLab (Either (Response ByteString) [a])
gitlabGetMany Text
urlPath []