2 Module : Gargantext.Text.Corpus.API.Isidore
3 Description : To query French Humanities publication database from its API
4 Copyright : (c) CNRS, 2019-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE NoImplicitPrelude #-}
13 {-# LANGUAGE ScopedTypeVariables #-}
14 {-# LANGUAGE OverloadedStrings #-}
16 module Gargantext.Text.Corpus.API.Isidore where
18 import System.FilePath (FilePath())
19 import Data.Text (Text)
20 import Gargantext.Core (Lang(..))
21 import Gargantext.Database.Types.Node (HyperdataDocument(..))
22 import Gargantext.Prelude
25 import qualified Data.Text as Text
26 import qualified Gargantext.Text.Corpus.Parsers.Date as Date
27 import qualified Isidore as Isidore
28 import Gargantext.Text.Corpus.Parsers.CSV (writeDocs2Csv)
29 import Gargantext.Text.Corpus.Parsers (cleanText)
31 -- | TODO work with the ServantErr
32 get :: Lang -> Maybe Isidore.Limit
33 -> Maybe Isidore.TextQuery -> Maybe Isidore.AuthorQuery
34 -> IO [HyperdataDocument]
37 printErr (DecodeFailure e _) = panic e
38 printErr e = panic (cs $ show e)
40 toIsidoreDocs :: Reply -> [IsidoreDoc]
41 toIsidoreDocs (ReplyOnly r) = [r]
42 toIsidoreDocs (Replies rs) = rs
44 iDocs <- either printErr _content <$> Isidore.get l q a
46 hDocs <- mapM (\d -> isidoreToDoc la d) (toIsidoreDocs iDocs)
49 isidore2csvFile :: FilePath -> Lang -> Maybe Isidore.Limit
50 -> Maybe Isidore.TextQuery -> Maybe Isidore.AuthorQuery
52 isidore2csvFile fp la li tq aq = do
53 hdocs <- get la li tq aq
54 writeDocs2Csv fp hdocs
56 isidoreToDoc :: Lang -> IsidoreDoc -> IO HyperdataDocument
57 isidoreToDoc l (IsidoreDoc t a d u s as) = do
59 author :: Author -> Text
60 author (Author fn ln) = (_name fn) <> ", " <> (_name ln)
61 author (Authors aus) = Text.intercalate ". " $ map author aus
63 creator2text :: Creator -> Text
64 creator2text (Creator au) = author au
65 creator2text (Creators aus') = Text.intercalate ". " $ map author aus'
67 langText :: LangText -> Text
68 langText (LangText _l t1) = t1
69 langText (OnlyText t2 ) = t2
70 langText (ArrayText ts ) = Text.intercalate " " $ map langText ts
72 (utcTime, (pub_year, pub_month, pub_day)) <- Date.dateSplit l (maybe (Just "2019") (Just) d)
74 pure $ HyperdataDocument (Just "Isidore")
80 (Just $ cleanText $ langText t)
84 (cleanText <$> langText <$> a)
85 (fmap (Text.pack . show) utcTime)
92 (Just $ (Text.pack . show) l)