{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}

{- |
Copyright: (c) 2020 Jens Petersen
SPDX-License-Identifier: GPL-2.0-only
Maintainer: Jens Petersen <petersen@redhat.com>

Copr REST client library
-}

module Web.Fedora.Copr
  (coprChroots,
   fedoraCopr)
where

import Data.Aeson.Types (Object)
#if MIN_VERSION_aeson(2,0,0)
import Data.Aeson.Key (toText)
import qualified Data.Aeson.KeyMap as M
#else
import qualified Data.HashMap.Lazy as M
#endif
import Data.List (sort)
import Data.Text (Text)

import Web.Fedora.Copr.API

-- | Get the list of chroot of a user's copr project
coprChroots :: String -- ^ server
            -> String -- ^ owner
            -> String -- ^ project
            -> IO [Text] -- ^ list of chroots
coprChroots :: String -> String -> String -> IO [Text]
coprChroots String
server String
owner String
project = do
  Object
proj <- String -> String -> String -> IO Object
coprGetProject String
server String
owner String
project
  case Text -> Object -> Maybe Object
forall a. FromJSON a => Text -> Object -> Maybe a
lookupKey Text
"chroot_repos" Object
proj :: Maybe Object of
    Maybe Object
Nothing ->
        case Text -> Object -> Maybe String
forall a. FromJSON a => Text -> Object -> Maybe a
lookupKey Text
"error" Object
proj of
          Just String
err -> String -> IO [Text]
forall a. HasCallStack => String -> a
error String
err
          Maybe String
Nothing -> [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return []
    Just Object
obj -> [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> IO [Text]) -> [Text] -> IO [Text]
forall a b. (a -> b) -> a -> b
$ ([Text] -> [Text]
forall a. [a] -> [a]
reverse ([Text] -> [Text]) -> (Object -> [Text]) -> Object -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. Ord a => [a] -> [a]
sort ([Text] -> [Text]) -> (Object -> [Text]) -> Object -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> Text) -> [Key] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Key -> Text
toText ([Key] -> [Text]) -> (Object -> [Key]) -> Object -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Object -> [Key]
forall v. KeyMap v -> [Key]
M.keys) Object
obj
#if !MIN_VERSION_aeson(2,0,0)
      where toText = id
#endif

-- | the host name of the Fedora Copr API server
fedoraCopr :: String
fedoraCopr :: String
fedoraCopr = String
"copr.fedorainfracloud.org"