{-# LANGUAGE OverloadedStrings #-}
module Fedora.Bodhi
( bodhiBuild
, bodhiBuilds
, bodhiComment
, bodhiComments
, bodhiCSRF
, bodhiOverride
, bodhiOverrides
, bodhiOverrideDates
, bodhiPackages
, bodhiRelease
, bodhiReleases
, bodhiUpdate
, bodhiUpdates
, bodhiUser
, bodhiUsers
, lookupKey
, lookupKey'
, queryBodhi
, makeKey
, makeItem
, maybeKey
, Query
, QueryItem
) where
import Data.Aeson.Types
import Data.Text (Text)
import Data.Time.LocalTime
import Network.HTTP.Query
server :: String
server :: String
server = String
"bodhi.fedoraproject.org"
bodhiBuild :: String -> IO Object
bodhiBuild :: String -> IO Object
bodhiBuild String
nvr =
Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi [] (String -> IO Object) -> String -> IO Object
forall a b. (a -> b) -> a -> b
$ String
"builds" String -> String -> String
+/+ String
nvr
bodhiBuilds :: Query -> IO [Object]
bodhiBuilds :: Query -> IO [Object]
bodhiBuilds Query
params =
Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"builds" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi Query
params String
"builds/"
bodhiComment :: String -> IO Object
String
cid =
Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi [] (String -> IO Object) -> String -> IO Object
forall a b. (a -> b) -> a -> b
$ String
"comments" String -> String -> String
+/+ String
cid
bodhiComments :: Query -> IO [Object]
Query
params =
Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"comments" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi Query
params String
"comments/"
bodhiCSRF :: IO (Maybe Text)
bodhiCSRF :: IO (Maybe Text)
bodhiCSRF =
Text -> Object -> Maybe Text
forall a. FromJSON a => Text -> Object -> Maybe a
lookupKey Text
"csrf_token" (Object -> Maybe Text) -> IO Object -> IO (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi [] String
"csrf"
bodhiOverride :: String -> IO (Maybe Object)
bodhiOverride :: String -> IO (Maybe Object)
bodhiOverride String
nvr =
Text -> Object -> Maybe Object
forall a. FromJSON a => Text -> Object -> Maybe a
lookupKey Text
"override" (Object -> Maybe Object) -> IO Object -> IO (Maybe Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi [] (String
"overrides" String -> String -> String
+/+ String
nvr)
bodhiOverrideDates :: String -> IO (Maybe (LocalTime,LocalTime))
bodhiOverrideDates :: String -> IO (Maybe (LocalTime, LocalTime))
bodhiOverrideDates String
nvr = do
Maybe Object
mobj <- String -> IO (Maybe Object)
bodhiOverride String
nvr
case Maybe Object
mobj of
Maybe Object
Nothing -> do
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Override for " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
nvr String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" not found"
Maybe (LocalTime, LocalTime) -> IO (Maybe (LocalTime, LocalTime))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (LocalTime, LocalTime)
forall a. Maybe a
Nothing
Just Object
obj -> Maybe (LocalTime, LocalTime) -> IO (Maybe (LocalTime, LocalTime))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (LocalTime, LocalTime) -> IO (Maybe (LocalTime, LocalTime)))
-> Maybe (LocalTime, LocalTime)
-> IO (Maybe (LocalTime, LocalTime))
forall a b. (a -> b) -> a -> b
$ Object -> Maybe (LocalTime, LocalTime)
readDates Object
obj
where
readDates :: Object -> Maybe (LocalTime,LocalTime)
readDates :: Object -> Maybe (LocalTime, LocalTime)
readDates =
(Object -> Parser (LocalTime, LocalTime))
-> Object -> Maybe (LocalTime, LocalTime)
forall a b. (a -> Parser b) -> a -> Maybe b
parseMaybe ((Object -> Parser (LocalTime, LocalTime))
-> Object -> Maybe (LocalTime, LocalTime))
-> (Object -> Parser (LocalTime, LocalTime))
-> Object
-> Maybe (LocalTime, LocalTime)
forall a b. (a -> b) -> a -> b
$ \Object
obj -> do
LocalTime
expire <- Object
obj Object -> Text -> Parser LocalTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"expiration_date"
LocalTime
submit <- Object
obj Object -> Text -> Parser LocalTime
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"submission_date"
(LocalTime, LocalTime) -> Parser (LocalTime, LocalTime)
forall (m :: * -> *) a. Monad m => a -> m a
return (LocalTime
expire,LocalTime
submit)
bodhiOverrides :: Query -> IO [Object]
bodhiOverrides :: Query -> IO [Object]
bodhiOverrides Query
params =
Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"overrides" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi Query
params String
"overrides/"
bodhiPackages :: Query -> IO [Object]
bodhiPackages :: Query -> IO [Object]
bodhiPackages Query
params =
Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"packages" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi Query
params String
"packages/"
bodhiRelease :: String -> IO Object
bodhiRelease :: String -> IO Object
bodhiRelease String
rel =
Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi [] (String -> IO Object) -> String -> IO Object
forall a b. (a -> b) -> a -> b
$ String
"releases" String -> String -> String
+/+ String
rel
bodhiReleases :: Query -> IO [Object]
bodhiReleases :: Query -> IO [Object]
bodhiReleases Query
params =
Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"releases" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi Query
params String
"releases/"
bodhiUpdate :: String -> IO (Maybe Object)
bodhiUpdate :: String -> IO (Maybe Object)
bodhiUpdate String
update =
Text -> Object -> Maybe Object
forall a. FromJSON a => Text -> Object -> Maybe a
lookupKey Text
"update" (Object -> Maybe Object) -> IO Object -> IO (Maybe Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi [] (String
"updates" String -> String -> String
+/+ String
update)
bodhiUpdates :: Query -> IO [Object]
bodhiUpdates :: Query -> IO [Object]
bodhiUpdates Query
params =
Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"updates" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi Query
params String
"updates/"
bodhiUser :: String -> IO Object
bodhiUser :: String -> IO Object
bodhiUser String
user =
Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi [] (String -> IO Object) -> String -> IO Object
forall a b. (a -> b) -> a -> b
$ String
"users" String -> String -> String
+/+ String
user
bodhiUsers :: Query -> IO [Object]
bodhiUsers :: Query -> IO [Object]
bodhiUsers Query
params =
Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"users" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> String -> IO Object
forall a. FromJSON a => Query -> String -> IO a
queryBodhi Query
params String
"users/"
queryBodhi :: FromJSON a => Query -> String -> IO a
queryBodhi :: Query -> String -> IO a
queryBodhi Query
params String
path =
let url :: String
url = String
"https://" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
server String -> String -> String
+/+ String
path
in String -> Query -> IO a
forall (m :: * -> *) a.
(MonadIO m, FromJSON a) =>
String -> Query -> m a
webAPIQuery String
url Query
params