2 Module : Gargantext.Text.Parsers.IsidoreApi
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
13 {-# LANGUAGE NoImplicitPrelude #-}
14 {-# LANGUAGE ScopedTypeVariables #-}
15 {-# LANGUAGE OverloadedStrings #-}
17 module Gargantext.Text.Parsers.IsidoreApi where
19 import System.FilePath (FilePath())
20 import Data.Text (Text)
21 import Gargantext.Core (Lang(..))
22 import Gargantext.Database.Types.Node (HyperdataDocument(..))
23 import Gargantext.Prelude
26 import qualified Data.Text as Text
27 import qualified Gargantext.Text.Parsers.Date as Date
28 import qualified Isidore as Isidore
29 import Gargantext.Text.Parsers.CSV (writeDocs2Csv)
30 import Gargantext.Text.Parsers (cleanText)
32 -- | TODO work with the ServantErr
33 get :: Lang -> Maybe Isidore.Limit
34 -> Maybe Isidore.TextQuery -> Maybe Isidore.AuthorQuery
35 -> IO [HyperdataDocument]
38 printErr (DecodeFailure e _) = panic e
39 printErr e = panic (cs $ show e)
40 iDocs <- either printErr (_docs) <$> Isidore.get l q a
41 hDocs <- mapM (\d -> isidoreToDoc la d) iDocs
44 isidore2csvFile :: FilePath -> Lang -> Maybe Isidore.Limit
45 -> Maybe Isidore.TextQuery -> Maybe Isidore.AuthorQuery
47 isidore2csvFile fp la li tq aq = do
48 hdocs <- get la li tq aq
49 writeDocs2Csv fp hdocs
51 isidoreToDoc :: Lang -> IsidoreDoc -> IO HyperdataDocument
52 isidoreToDoc l (IsidoreDoc t a d u s as) = do
54 author :: Author -> Text
55 author (Author fn ln) = (_name fn) <> ", " <> (_name ln)
56 author (Authors aus) = Text.intercalate ". " $ map author aus
58 creator2text :: Creator -> Text
59 creator2text (Creator au) = author au
60 creator2text (Creators aus') = Text.intercalate ". " $ map author aus'
62 langText :: LangText -> Text
63 langText (LangText _l t1) = t1
64 langText (OnlyText t2 ) = t2
65 langText (ArrayText ts) = Text.intercalate " " $ map langText ts
67 (utcTime, (pub_year, pub_month, pub_day)) <- Date.split l (maybe (Just "2019") (Just) d)
69 pure $ HyperdataDocument (Just "IsidoreApi")
75 (Just $ cleanText $ langText t)
79 (cleanText <$> langText <$> a)
80 (fmap (Text.pack . show) utcTime)
87 (Just $ (Text.pack . show) l)