Commit 2b64e9d8 authored by Mael NICOLAS's avatar Mael NICOLAS

[WIP] Type Response done

parent 94ceed1f
...@@ -11,7 +11,7 @@ main = do ...@@ -11,7 +11,7 @@ main = do
manager' <- newManager tlsManagerSettings manager' <- newManager tlsManagerSettings
res <- runClientM res <- runClientM
(fl Nothing) (fl Nothing)
(mkClientEnv manager' $ BaseUrl Https "api.archives-ouvertes.fr" 443 "search") (mkClientEnv manager' $ BaseUrl Https "api.archives-ouvertes.fr" 443 "")
case res of case res of
(Left err) -> print err (Left err) -> print err
(Right val) -> print val (Right val) -> print val
...@@ -27,6 +27,7 @@ dependencies: ...@@ -27,6 +27,7 @@ dependencies:
- http-client-tls - http-client-tls
- http-client - http-client
- text - text
- containers
library: library:
source-dirs: src source-dirs: src
......
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE OverloadedStrings #-}
module HAL.Client where module HAL.Client where
import Data.Proxy import Data.Proxy
import GHC.Generics import GHC.Generics
import Servant.API import Servant.API
import Servant.Client import Servant.Client hiding (Response)
import Data.Text import Data.Text
import Data.Map
import Data.Aeson
type HALAPI = "" :> QueryParam "fl" Text :> Get '[JSON] [Text] data Response = Response
{
numFound :: Integer,
start :: Int,
docs :: [Doc]
} deriving (Show, Generic)
instance FromJSON Response where
parseJSON (Object o) = Response <$>
((o .: "response") >>= (.: "numFound"))
<*> ((o .: "response") >>= (.: "start"))
<*> ((o .: "response") >>= (.: "docs"))
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 HALAPI
halAPI = Proxy halAPI = Proxy
fl :: Maybe Text -> ClientM [Text] fl :: Maybe Text -> ClientM Response
fl = client halAPI fl = 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