{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Fedora.PDC
  ( fedoraPDC
  , pdcArches
  , pdcChangesets
  , pdcComponentBranches
  , pdcComponentBranchSLAs
  , pdcComponentRelationshipTypes
  , pdcComponentSLATypes
  , pdcComposes
  , pdcComposeImages
  , pdcComposeImageRttTests
  , pdcComposeRpms
  , pdcComposeTreeRttTests
  , pdcContentDeliveryContentFormats
  , pdcGlobalComponents
  , pdcImages
  , pdcModules
  , pdcProductVersions
  , pdcProducts
  , pdcReleases
  , pdcWhereToFileBugs
  , pdcRpms
  , queryPDC
  , lookupKey
  , lookupKey'
  , makeKey
  , makeItem
  , maybeKey
  , Query
  , QueryItem
  , getResultsList
  )
where
import Data.Aeson.Types
import Network.HTTP.Query
fedoraPDC :: String
fedoraPDC :: String
fedoraPDC = String
"pdc.fedoraproject.org"
pdcArches :: String -> IO [Object]
pdcArches :: String -> IO [Object]
pdcArches String
server =
  Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"results" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> Query -> IO Object
queryPDC String
server String
"arches" []
pdcChangesets :: String -> Query -> IO Object
pdcChangesets :: String -> Query -> IO Object
pdcChangesets String
server =
  String -> String -> Query -> IO Object
queryPDC String
server String
"changesets"
pdcComponentBranchSLAs :: String -> Query -> IO Object
pdcComponentBranchSLAs :: String -> Query -> IO Object
pdcComponentBranchSLAs String
server =
  String -> String -> Query -> IO Object
queryPDC String
server String
"component-branch-slas"
pdcComponentBranches :: String -> Query -> IO Object
pdcComponentBranches :: String -> Query -> IO Object
pdcComponentBranches String
server =
  String -> String -> Query -> IO Object
queryPDC String
server String
"component-branches"
pdcComponentRelationshipTypes :: String -> IO [Object]
pdcComponentRelationshipTypes :: String -> IO [Object]
pdcComponentRelationshipTypes String
server =
  Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"results" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> Query -> IO Object
queryPDC String
server String
"component-relationship-types" []
pdcComponentSLATypes :: String -> Query -> IO [Object]
pdcComponentSLATypes :: String -> Query -> IO [Object]
pdcComponentSLATypes String
server Query
params =
  Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"results" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> Query -> IO Object
queryPDC String
server String
"component-sla-types" Query
params
pdcComposeImageRttTests :: String -> Query -> IO Object
pdcComposeImageRttTests :: String -> Query -> IO Object
pdcComposeImageRttTests String
server =
  String -> String -> Query -> IO Object
queryPDC String
server String
"compose-image-rtt-tests"
pdcComposeImages :: String -> String -> IO Object
pdcComposeImages :: String -> String -> IO Object
pdcComposeImages String
server String
compose =
  String -> String -> Query -> IO Object
queryPDC String
server (String
"compose-images" String -> String -> String
+/+ String
compose String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/") []
pdcComposeRpms :: String -> String -> IO Object
pdcComposeRpms :: String -> String -> IO Object
pdcComposeRpms String
server String
compose =
  String -> String -> Query -> IO Object
queryPDC String
server (String
"compose-rpms" String -> String -> String
+/+ String
compose String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/") []
pdcComposeTreeRttTests :: String -> Query -> IO Object
pdcComposeTreeRttTests :: String -> Query -> IO Object
pdcComposeTreeRttTests String
server =
  String -> String -> Query -> IO Object
queryPDC String
server String
"compose-tree-rtt-tests"
pdcComposes :: String -> Maybe String -> Query -> IO Object
pdcComposes :: String -> Maybe String -> Query -> IO Object
pdcComposes String
server Maybe String
mcompose Query
params = do
  let path :: String
path = String
"composes" String -> String -> String
+/+ String -> (String -> String) -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" (String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/") Maybe String
mcompose
  String -> String -> Query -> IO Object
queryPDC String
server String
path Query
params
pdcContentDeliveryContentFormats :: String -> Query -> IO [Object]
pdcContentDeliveryContentFormats :: String -> Query -> IO [Object]
pdcContentDeliveryContentFormats String
server Query
params =
  Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"results" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> Query -> IO Object
queryPDC String
server String
"content-delivery-content-formats" Query
params
pdcGlobalComponents :: String -> Query -> IO Object
pdcGlobalComponents :: String -> Query -> IO Object
pdcGlobalComponents String
server =
   String -> String -> Query -> IO Object
queryPDC String
server String
"global-components"
pdcImages :: String -> Query -> IO Object
pdcImages :: String -> Query -> IO Object
pdcImages String
server =
   String -> String -> Query -> IO Object
queryPDC String
server String
"images"
pdcModules :: String -> Query -> IO Object
pdcModules :: String -> Query -> IO Object
pdcModules String
server =
  String -> String -> Query -> IO Object
queryPDC String
server String
"modules"
pdcProductVersions :: String -> Query -> IO [Object]
pdcProductVersions :: String -> Query -> IO [Object]
pdcProductVersions String
server Query
params =
  Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"results" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> Query -> IO Object
queryPDC String
server String
"product-versions" Query
params
pdcProducts :: String -> Query -> IO [Object]
pdcProducts :: String -> Query -> IO [Object]
pdcProducts String
server Query
params =
  Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"results" (Object -> [Object]) -> IO Object -> IO [Object]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> String -> Query -> IO Object
queryPDC String
server String
"products" Query
params
pdcReleases :: String -> Query -> IO Object
pdcReleases :: String -> Query -> IO Object
pdcReleases String
server =
  String -> String -> Query -> IO Object
queryPDC String
server String
"releases"
pdcWhereToFileBugs :: String -> Query -> IO Object
pdcWhereToFileBugs :: String -> Query -> IO Object
pdcWhereToFileBugs String
server =
  String -> String -> Query -> IO Object
queryPDC String
server String
"rpc/where-to-file-bugs"
pdcRpms :: String -> Query -> IO Object
pdcRpms :: String -> Query -> IO Object
pdcRpms String
server =
  String -> String -> Query -> IO Object
queryPDC String
server String
"rpms"
queryPDC :: String -> String -> Query -> IO Object
queryPDC :: String -> String -> Query -> IO Object
queryPDC String
server String
path Query
params =
  let url :: String
url = String
"https://" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
server String -> String -> String
+/+ String
"rest_api/v1" String -> String -> String
+/+ String
path
  in String -> Query -> IO Object
forall (m :: * -> *) a.
(MonadIO m, FromJSON a) =>
String -> Query -> m a
webAPIQuery String
url Query
params
getResultsList :: Object -> [Object]
getResultsList :: Object -> [Object]
getResultsList = Text -> Object -> [Object]
forall a. FromJSON a => Text -> Object -> a
lookupKey' Text
"results"