{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
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
coprChroots :: String
-> String
-> String
-> IO [Text]
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
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
forall a. a -> a
toText ([Text] -> [Text]) -> (Object -> [Text]) -> Object -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Object -> [Text]
forall k v. HashMap k v -> [k]
M.keys) Object
obj
#if !MIN_VERSION_aeson(2,0,0)
where toText :: a -> a
toText = a -> a
forall a. a -> a
id
#endif
fedoraCopr :: String
fedoraCopr :: String
fedoraCopr = String
"copr.fedorainfracloud.org"