{-# LANGUAGE OverloadedStrings #-}

-- | This module contains the gerrit client library
module Gerrit
  ( -- * Client
    GerritClient,
    withClient,
    getClient,

    -- * Api
    getVersion,
    getChange,
    queryChanges,
    postReview,
    getAccountId,
    getAccount,
    getProjects,

    -- * Main data types
    GerritVersion (..),
    GerritQuery (..),
    GerritChange (..),
    GerritChangeStatus (..),
    ReviewResult (..),
    GerritAccount (..),
    GerritAccountQuery (..),
    GerritProjectQuery (..),

    -- * Convenient functions
    changeUrl,
    serverUrl,
  )
where

import Control.Exception (try)
import Data.List.NonEmpty (NonEmpty)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Gerrit.Client
import Gerrit.Data.Account
import Gerrit.Data.Change
import Gerrit.Data.Project
import Gerrit.Data.Review
import Network.HTTP.Client (HttpException)

-- | Return the base url of the 'GerritClient'
serverUrl :: GerritClient -> T.Text
serverUrl :: GerritClient -> Text
serverUrl = GerritClient -> Text
baseUrl

-- | Return the url of a 'GerritChange'
changeUrl :: GerritClient -> GerritChange -> T.Text
changeUrl :: GerritClient -> GerritChange -> Text
changeUrl GerritClient
client GerritChange
change = GerritClient -> Text
baseUrl GerritClient
client Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (GerritChange -> Int
number GerritChange
change))

-- | Get the server version
getVersion :: GerritClient -> IO GerritVersion
getVersion :: GerritClient -> IO GerritVersion
getVersion = Text -> GerritClient -> IO GerritVersion
forall a. FromJSON a => Text -> GerritClient -> IO a
gerritGet Text
"config/server/version"

-- | Get projects
getProjects ::
  -- | Count of projects to get back
  Int ->
  -- | The project query type
  GerritProjectQuery ->
  -- | Whether or not to ask result from offset
  Maybe Int ->
  -- | The client
  GerritClient ->
  IO GerritProjectsMessage
getProjects :: Int
-> GerritProjectQuery
-> Maybe Int
-> GerritClient
-> IO GerritProjectsMessage
getProjects Int
count GerritProjectQuery
query Maybe Int
startM = Text -> GerritClient -> IO GerritProjectsMessage
forall a. FromJSON a => Text -> GerritClient -> IO a
gerritGet (Text
"projects/?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> GerritProjectQuery -> Maybe Int -> Text
projectQS Int
count GerritProjectQuery
query Maybe Int
startM)

-- | Search for changes
queryChanges ::
  -- | Count of changes to get back
  Int ->
  -- | The change query
  [GerritQuery] ->
  -- | Whether or not to ask result from offset
  Maybe Int ->
  -- | The client
  GerritClient ->
  IO [GerritChange]
queryChanges :: Int
-> [GerritQuery] -> Maybe Int -> GerritClient -> IO [GerritChange]
queryChanges Int
count [GerritQuery]
queries Maybe Int
startM = Text -> GerritClient -> IO [GerritChange]
forall a. FromJSON a => Text -> GerritClient -> IO a
gerritGet (Text
"changes/?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> [GerritQuery] -> Maybe Int -> Text
changeQS Int
count [GerritQuery]
queries Maybe Int
startM)

-- | Get a change by change Id
getChange :: Int -> GerritClient -> IO (Maybe GerritChange)
getChange :: Int -> GerritClient -> IO (Maybe GerritChange)
getChange Int
changeNumber GerritClient
client = do
  Either HttpException GerritChange
res <-
    IO GerritChange -> IO (Either HttpException GerritChange)
forall e a. Exception e => IO a -> IO (Either e a)
try
      ( Text -> GerritClient -> IO GerritChange
forall a. FromJSON a => Text -> GerritClient -> IO a
gerritGet (Text
"changes/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
changeNumber) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
defaultQueryChangeOptions) GerritClient
client
      ) ::
      IO (Either HttpException GerritChange)
  Maybe GerritChange -> IO (Maybe GerritChange)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe GerritChange -> IO (Maybe GerritChange))
-> Maybe GerritChange -> IO (Maybe GerritChange)
forall a b. (a -> b) -> a -> b
$ case Either HttpException GerritChange
res of
    Right GerritChange
change -> GerritChange -> Maybe GerritChange
forall a. a -> Maybe a
Just GerritChange
change
    Left HttpException
_err -> Maybe GerritChange
forall a. Maybe a
Nothing

-- | Post a review
postReview ::
  -- | The change to review
  GerritChange ->
  -- | A message
  Text ->
  -- | A label
  Text ->
  -- | A vote
  Int ->
  -- | The client
  GerritClient ->
  -- | Returns the ReviewResult
  IO ReviewResult
postReview :: GerritChange
-> Text -> Text -> Int -> GerritClient -> IO ReviewResult
postReview GerritChange
change Text
message Text
label Int
value' = Text -> ReviewInput -> GerritClient -> IO ReviewResult
forall a b.
(ToJSON a, FromJSON b) =>
Text -> a -> GerritClient -> IO b
gerritPost Text
urlPath ReviewInput
review
  where
    urlPath :: Text
urlPath = Text
"changes/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
changeId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/revisions/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
revHash Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/review"
    changeId :: Text
changeId = GerritChange -> Text
Gerrit.Data.Change.id GerritChange
change
    revHash :: Text
revHash = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (GerritChange -> Maybe Text
Gerrit.Data.Change.current_revision GerritChange
change)
    review :: ReviewInput
review =
      ReviewInput :: Maybe Text -> Maybe (Map Text Int) -> ReviewInput
ReviewInput
        { riMessage :: Maybe Text
riMessage = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
message,
          riLabels :: Maybe (Map Text Int)
riLabels = Map Text Int -> Maybe (Map Text Int)
forall a. a -> Maybe a
Just ([(Text, Int)] -> Map Text Int
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(Text
label, Int
value')])
        }

-- | Get user account id
getAccountId :: Int -> NonEmpty GerritAccountQuery -> GerritClient -> IO [GerritAccountId]
getAccountId :: Int
-> NonEmpty GerritAccountQuery
-> GerritClient
-> IO [GerritAccountId]
getAccountId Int
count NonEmpty GerritAccountQuery
queries = Text -> GerritClient -> IO [GerritAccountId]
forall a. FromJSON a => Text -> GerritClient -> IO a
gerritGet (Text
"accounts/?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> NonEmpty GerritAccountQuery -> Text
accountQs Int
count NonEmpty GerritAccountQuery
queries)

-- | Get user account details
getAccount :: Int -> NonEmpty GerritAccountQuery -> GerritClient -> IO [GerritAccount]
getAccount :: Int
-> NonEmpty GerritAccountQuery
-> GerritClient
-> IO [GerritAccount]
getAccount Int
count NonEmpty GerritAccountQuery
queries = Text -> GerritClient -> IO [GerritAccount]
forall a. FromJSON a => Text -> GerritClient -> IO a
gerritGet (Text
"accounts/?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> NonEmpty GerritAccountQuery -> Text
accountQs Int
count NonEmpty GerritAccountQuery
queries Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"&o=DETAILS")