Commit 069118b2 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[DOC] fix API.

parent bfb0e7d8
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Main where module Main where
import ISIDORE.Client import Isidore.Client
import Network.HTTP.Client (newManager) import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings) import Network.HTTP.Client.TLS (tlsManagerSettings)
import Servant.Client import Servant.Client
...@@ -10,7 +10,7 @@ main :: IO () ...@@ -10,7 +10,7 @@ main :: IO ()
main = do main = do
manager' <- newManager tlsManagerSettings manager' <- newManager tlsManagerSettings
res <- runClientM res <- runClientM
(search (clientIsidore
(Just 10) (Just 10)
(Just "poison") (Just "poison")
(Nothing)) (Nothing))
......
...@@ -2,7 +2,7 @@ ...@@ -2,7 +2,7 @@
-- --
-- see: https://github.com/sol/hpack -- see: https://github.com/sol/hpack
-- --
-- hash: 7f8443023714c385aa78461bf264946e215e8e840afeaf9e117216f86773fe67 -- hash: 37b28b3c7df7f52e571a3f00f87a54ca95eb656d9c0fbfe562bacbfcccb6ab6d
name: crawlerIsidore name: crawlerIsidore
version: 0.1.0.0 version: 0.1.0.0
...@@ -26,8 +26,8 @@ source-repository head ...@@ -26,8 +26,8 @@ source-repository head
library library
exposed-modules: exposed-modules:
ISIDORE Isidore
ISIDORE.Client Isidore.Client
other-modules: other-modules:
Paths_crawlerIsidore Paths_crawlerIsidore
hs-source-dirs: hs-source-dirs:
...@@ -41,7 +41,6 @@ library ...@@ -41,7 +41,6 @@ library
, http-media , http-media
, servant , servant
, servant-client , servant-client
, servant-server
, text , text
, vector , vector
default-language: Haskell2010 default-language: Haskell2010
...@@ -63,7 +62,6 @@ executable crawlerIsidore-exe ...@@ -63,7 +62,6 @@ executable crawlerIsidore-exe
, http-media , http-media
, servant , servant
, servant-client , servant-client
, servant-server
, text , text
, vector , vector
default-language: Haskell2010 default-language: Haskell2010
...@@ -86,7 +84,6 @@ test-suite crawlerIsidore-test ...@@ -86,7 +84,6 @@ test-suite crawlerIsidore-test
, http-media , http-media
, servant , servant
, servant-client , servant-client
, servant-server
, text , text
, vector , vector
default-language: Haskell2010 default-language: Haskell2010
{-# LANGUAGE OverloadedStrings #-}
module ISIDORE where
import ISIDORE.Client
import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Servant.Client
-- crawler :: IO ()
crawler n q a = do
manager' <- newManager tlsManagerSettings
runClientM (search n q a)
(mkClientEnv manager' $ BaseUrl Https "api.isidore.science" 443 "resource")
{-|
Module : Gargantext
Description : Textmining Collaborative Platform
Copyright : (c) CNRS/IMT, 2019-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Examples:
- For a "portrait":
either (\(DecodeFailure e _) -> error $ show e) (length . _docs) <$> get (Just 100) Nothing (Just "anheim_etienne")
- For a "paysage":
either (\(DecodeFailure e _) -> error $ show e) (length . _docs) <$> get (Just 100) (Just "peste noire") Nothing
-}
{-# LANGUAGE OverloadedStrings #-}
module Isidore where
import Isidore.Client
import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Servant.Client
import Data.Maybe (Maybe)
import Data.Text (Text)
import Data.Either (Either, either)
type Limit = Int
type TextQuery = Text
type AuthorQuery = Text
get :: Maybe Limit
-> Maybe TextQuery
-> Maybe AuthorQuery
-> IO (Either ServantError Reply)
get n q a = do
manager' <- newManager tlsManagerSettings
runClientM (clientIsidore n q a)
(mkClientEnv manager' $ BaseUrl Https "api.isidore.science" 443 "resource")
{-|
Module : Gargantext
Description : Textmining Collaborative Platform
Copyright : (c) CNRS/IMT, 2019-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
module ISIDORE.Client where
module Isidore.Client where
import Control.Monad import Control.Monad
import Servant.API import Servant.API
...@@ -105,26 +116,19 @@ instance FromJSON IsidoreDoc where ...@@ -105,26 +116,19 @@ instance FromJSON IsidoreDoc where
instance FromJSON Reply where instance FromJSON Reply where
parseJSON (Object o) = Reply <$> (responseReplies >>= parseJSON) parseJSON (Object o) = Reply <$> (responseReplies >>= parseJSON)
-- <*> (responseReplies >>= (.: "abstract") >>= (.: "$"))
-- <*> (responseReplies >>= (.: "date") >>= (.: "origin"))
-- <*> (responseReplies >>= (.: "enrichedCreators") >>= (.: "creator"))
where where
responseReplies = (o .: "response") responseReplies = (o .: "response")
>>= (.: "replies") >>= (.: "replies")
>>= (.: "content") >>= (.: "content")
>>= (.: "reply") >>= (.: "reply")
-- docs = mapM (\r -> IsidoreDoc <$> (r .: "isidore") >>= (.: "title")) responseReplies
-- >>= (.: "$"))
-- >>= (.: "isidore")
data Output = JSON data Output = JSON
instance ToHttpApiData Output where instance ToHttpApiData Output where
toUrlPiece JSON = "json" toUrlPiece JSON = "json"
type ISIDOREAPI = Search type IsidoreAPI = Search
-- search?q=colza&output=json&replies=1&author=jm&
type Search = "search" type Search = "search"
:> QueryParam "replies" Int :> QueryParam "replies" Int
:> QueryParam "output" Output :> QueryParam "output" Output
...@@ -132,10 +136,10 @@ type Search = "search" ...@@ -132,10 +136,10 @@ type Search = "search"
:> QueryParam "author" T.Text :> QueryParam "author" T.Text
:> Get '[JSON] Reply :> Get '[JSON] Reply
isidoreAPI :: Proxy ISIDOREAPI isidoreAPI :: Proxy IsidoreAPI
isidoreAPI = Proxy isidoreAPI = Proxy
search :: Maybe Int -> Maybe T.Text -> Maybe T.Text -> ClientM Reply clientIsidore :: Maybe Int -> Maybe T.Text -> Maybe T.Text -> ClientM Reply
search n q a = client isidoreAPI n (Just JSON) q a clientIsidore n q a = client isidoreAPI n (Just JSON) q a
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