Commit 1849d1c9 authored by Mael NICOLAS's avatar Mael NICOLAS

Merge branch 'add-date/abstract/source' into 'dev'

Resolve #1

See merge request !3
parents 8878572d 76dc117d
.stack-work/
crawlerISTEX.cabal
*~
\ No newline at end of file
...@@ -7,7 +7,9 @@ import ISTEX.Client ...@@ -7,7 +7,9 @@ import ISTEX.Client
main :: IO () main :: IO ()
main = do main = do
res <- runIstexAPIClient $ search (Just 40) (Just "ia") (Just "author,title") res <- basicSearch (Just "ia")
case res of case res of
(Left err) -> print err (Left err) -> print "Error"
(Right val) -> print val (Right val) -> do
print $ take 5 $ _hits val
-- print $ _abstract <$> (_hits val)
{-# LANGUAGE OverloadedStrings #-}
module ISTEX where module ISTEX where
import ISTEX.Client import ISTEX.Client
...@@ -5,7 +7,17 @@ import Network.HTTP.Client (newManager) ...@@ -5,7 +7,17 @@ import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings) import Network.HTTP.Client.TLS (tlsManagerSettings)
import Servant.Client import Servant.Client
import qualified Data.Text as T
runIstexAPIClient :: ClientM (Documents) -> IO (Either ClientError Documents) runIstexAPIClient :: ClientM (Documents) -> IO (Either ClientError Documents)
runIstexAPIClient cmd = do runIstexAPIClient cmd = do
manager' <- newManager tlsManagerSettings manager' <- newManager tlsManagerSettings
runClientM cmd (mkClientEnv manager' $ BaseUrl Https "api.istex.fr" 443 "document") runClientM cmd (mkClientEnv manager' $ BaseUrl Https "api.istex.fr" 443 "document")
basicSearch :: Maybe T.Text -> IO (Either ClientError Documents)
basicSearch rq = do
runIstexAPIClient $
search
(Just "author,title,abstract,publicationDate,refBibs")
(Just 5000)
rq
...@@ -19,30 +19,57 @@ import qualified Control.Lens as L ...@@ -19,30 +19,57 @@ import qualified Control.Lens as L
data Author = Author data Author = Author
{ {
_name :: T.Text, _author_name :: T.Text,
_affiliations :: [T.Text] _author_affiliations :: [T.Text]
} deriving (Show, Generic) } deriving (Show, Generic)
L.makeLenses ''Author L.makeLenses ''Author
instance FromJSON Author where instance FromJSON Author where
parseJSON (Object o) = parseJSON (Object o) =
Author <$> (o .: "name") <*> (o .: "affiliations" <|> pure []) Author <$> (o .: "name") <*> (o .: "affiliations" <|> pure [])
data Source = Source
{
_source_title :: Maybe T.Text,
_source_authors :: [Author],
_source_publicationDate :: Maybe Int
} deriving (Show, Generic)
L.makeLenses ''Source
instance FromJSON Source where
parseJSON (Object o) =
Source <$>
(o .:? "title")
<*> (o .: "author")
<*> do pPubDate <- (o .:? "publicationDate")
return $ (read . T.unpack) <$> pPubDate
data Document = Document data Document = Document
{ {
_id :: T.Text, _document_id :: T.Text,
_title :: Maybe T.Text, _document_title :: Maybe T.Text,
_authors :: [Author] _document_authors :: [Author],
_document_abstract :: Maybe T.Text,
_document_publicationDate :: Maybe Int,
_document_sources :: [Source]
} deriving (Show, Generic) } deriving (Show, Generic)
L.makeLenses ''Document L.makeLenses ''Document
instance FromJSON Document where instance FromJSON Document where
parseJSON (Object o) = parseJSON (Object o) =
Document <$> (o .: "id") <*> (o .:? "title") <*> (o .: "author" <|> pure []) Document <$>
(o .: "id")
<*> (o .:? "title")
<*> (o .: "author" <|> pure [])
<*> (o .:? "abstract")
<*> do pPubDate <- (o .:? "publicationDate")
return $ (read . T.unpack) <$> pPubDate
<*> (o .: "refBibs" <|> pure [])
data Documents = Documents data Documents = Documents
{ {
_total :: Int, _documents_total :: Int,
_hits :: [Document] _documents_hits :: [Document]
} deriving (Show, Generic) } deriving (Show, Generic)
L.makeLenses ''Documents L.makeLenses ''Documents
instance FromJSON Documents where instance FromJSON Documents where
...@@ -51,13 +78,14 @@ instance FromJSON Documents where ...@@ -51,13 +78,14 @@ instance FromJSON Documents where
type ISTEXAPI = Search type ISTEXAPI = Search
type Search = QueryParam "size" Int type Search =
QueryParam "output" T.Text
:> QueryParam "size" Int
:> QueryParam "q" T.Text :> QueryParam "q" T.Text
:> QueryParam "output" T.Text
:> Get '[JSON] Documents :> Get '[JSON] Documents
istexProxy :: Proxy (ISTEXAPI) istexProxy :: Proxy (ISTEXAPI)
istexProxy = Proxy istexProxy = Proxy
search :: Maybe Int -> Maybe T.Text -> Maybe T.Text -> ClientM Documents search :: Maybe T.Text -> Maybe Int -> Maybe T.Text -> ClientM Documents
search = client istexProxy search = client istexProxy
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