Commit c72b9184 authored by Mael NICOLAS's avatar Mael NICOLAS

[WIP] Done sort & fl

parent 2b64e9d8
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Network.HTTP.Client (newManager)
......@@ -10,7 +12,7 @@ main :: IO ()
main = do
manager' <- newManager tlsManagerSettings
res <- runClientM
(fl Nothing)
(search ["docid"] . Just $ Desc "docid")
(mkClientEnv manager' $ BaseUrl Https "api.archives-ouvertes.fr" 443 "")
case res of
(Left err) -> print err
......
......@@ -13,6 +13,23 @@ import Data.Text
import Data.Map
import Data.Aeson
type HALAPI = Search
type Search = "search"
-- fl determine which fields will be returned it can be a list of fields or *
:> QueryParams "fl" Text
-- preatty much clear, (Asc || Desc) + field you want to sort by
:> QueryParam "sort" SortField
:> Get '[JSON] Response
-- Get's argument type
data SortField = Asc Text | Desc Text
deriving (Show)
instance ToHttpApiData SortField where
toUrlPiece (Asc t) = t <> " asc"
toUrlPiece (Desc t) = t <> " desc"
-- Response type
data Response = Response
{
numFound :: Integer,
......@@ -30,14 +47,8 @@ newtype Doc = Doc (Map Text Value)
deriving (Show, Generic)
instance FromJSON Doc
type HALAPI = Search
type Search = "search"
-- fl determine which fields will be returned it can be a list of fields or *
:> QueryParam "fl" Text :> Get '[JSON] Response
halAPI :: Proxy HALAPI
halAPI = Proxy
fl :: Maybe Text -> ClientM Response
fl = client halAPI
search :: [Text] -> Maybe SortField -> ClientM Response
search = client halAPI
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment