{-# LANGUAGE OverloadedStrings #-}

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

    -- * Api
    getVersion,
    getChange,
    queryChanges,
    postReview,

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

    -- * Convenient functions
    changeUrl,
    hasLabel,
  )
where

import Control.Exception (try)
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
import Network.HTTP.Client (HttpException)

-- | 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"

-- | Search for changes
queryChanges :: Int -> [GerritQuery] -> GerritClient -> IO [GerritChange]
queryChanges :: Int -> [GerritQuery] -> GerritClient -> IO [GerritChange]
queryChanges Int
count [GerritQuery]
queries = 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
<> Text
queryString)
  where
    queryString :: Text
queryString = Text -> [Text] -> Text
T.intercalate Text
"&" [Text
changeString, Text
countString, Text
option]
    changeString :: Text
changeString = Text
"q=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
"+" ((GerritQuery -> Text) -> [GerritQuery] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map GerritQuery -> Text
queryText [GerritQuery]
queries)
    countString :: Text
countString = Text
"n=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
count)
    option :: Text
option = Text
"o=CURRENT_REVISION&o=DETAILED_LABELS"

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
"?o=CURRENT_REVISION&o=DETAILED_LABELS") 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.id GerritChange
change
    revHash :: Text
revHash = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (GerritChange -> Maybe Text
Gerrit.Data.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')])
        }

-- | Check if a gerrit change as a label
hasLabel :: T.Text -> Int -> GerritChange -> Bool
hasLabel :: Text -> Int -> GerritChange -> Bool
hasLabel Text
label Int
labelValue GerritChange
change = case Text -> Map Text GerritDetailedLabel -> Maybe GerritDetailedLabel
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
label (GerritChange -> Map Text GerritDetailedLabel
labels GerritChange
change) of
  Just GerritDetailedLabel
gerritLabel ->
    (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (Int -> Bool) -> Int -> Bool
forall a b. (a -> b) -> a -> b
$
      [GerritDetailedLabelVote] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([GerritDetailedLabelVote] -> Int)
-> [GerritDetailedLabelVote] -> Int
forall a b. (a -> b) -> a -> b
$ (GerritDetailedLabelVote -> Bool)
-> [GerritDetailedLabelVote] -> [GerritDetailedLabelVote]
forall a. (a -> Bool) -> [a] -> [a]
filter (\GerritDetailedLabelVote
vote -> Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 (GerritDetailedLabelVote -> Maybe Int
value GerritDetailedLabelVote
vote) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
labelValue) (GerritDetailedLabel -> [GerritDetailedLabelVote]
Gerrit.Data.all GerritDetailedLabel
gerritLabel)
  Maybe GerritDetailedLabel
_ -> Bool
False