{-# LANGUAGE TypeOperators #-} {-# LANGUAGE DataKinds #-} -- | -- Module : Linux.Arch.Aur.Rpc -- Copyright : (c) Colin Woodbury, 2014, 2015, 2016 -- License : GPL3 -- Maintainer: Colin Woodbury -- -- See https://aur.archlinux.org/rpc for details. module Linux.Arch.Aur.Rpc ( info, search ) where import Control.Monad.Trans (MonadIO, liftIO) import Control.Monad.Trans.Except import Data.Proxy import Data.Text (Text, unpack) import Linux.Arch.Aur.Types import Network.HTTP.Client (Manager, newManager) import Network.HTTP.Client.TLS import Servant.API import Servant.Client import System.IO.Unsafe --- type Info = "rpc" :> QueryParam "v" String :> QueryParam "type" String :> QueryParams "arg[]" String :> Get '[JSON] RPCResp type Search = "rpc" :> QueryParam "v" String :> QueryParam "type" String :> QueryParam "arg" String :> Get '[JSON] RPCResp type API = Info :<|> Search api :: Proxy API api = Proxy -- Bad, but necessary, apparently. __manager :: Manager __manager = unsafePerformIO $ newManager tlsManagerSettings -- | Make a call to the AUR RPC. Assumes version 5 of the API. rpcI :<|> rpcS = client api (BaseUrl Http aurUrl 80 "") __manager where aurUrl = "aur.archlinux.org" -- | Perform an @info@ call on one or more package names. info :: MonadIO m => [Text] -> m [AurInfo] info = unwrap . rpcI (Just "5") (Just "info") . map unpack -- | Perform a @search@ call on a package name or description text. search :: MonadIO m => Text -> m [AurInfo] search = unwrap . rpcS (Just "5") (Just "search") . Just . unpack unwrap :: MonadIO m => ExceptT ServantError IO RPCResp -> m [AurInfo] unwrap = liftIO . fmap (either (const []) _results) . runExceptT