Commit 5983053e authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge remote-tracking branch 'origin/603-dev-istex-zip-file-upload' into dev

parents 04798ff5 f0312417
{-|
Module : Gargantext.Core.Text.Corpus.Parsers.JSON.Istex
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Parser for a single file in istex zip. See
https://gitlab.iscpif.fr/gargantext/purescript-gargantext/issues/603
-}
{-# LANGUAGE DuplicateRecordFields #-}
module Gargantext.Core.Text.Corpus.Parsers.JSON.Istex where
import Data.Text qualified as T
import Gargantext.Core (Lang(..))
import Gargantext.Core.Text.Corpus.Parsers.Date qualified as Date
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Gargantext.Defaults qualified as Defaults
import Gargantext.Prelude hiding (length, show)
import ISTEX.Client qualified as ISTEX
import Protolude
-- | TODO remove dateSplit here
-- TODO current year as default
toDoc :: Lang -> ISTEX.Document -> IO HyperdataDocument
toDoc la (ISTEX.Document i t a ab d s) = do
--printDebug "ISTEX date" d
(utctime, (pub_year, pub_month, pub_day)) <-
Date.dateSplit (maybe (Just $ T.pack $ show Defaults.year) (Just . T.pack . show) d)
--printDebug "toDoc Istex" (utctime, (pub_year, pub_month, pub_day))
pure $ HyperdataDocument { _hd_bdd = Just "Istex"
, _hd_doi = Just i
, _hd_url = Nothing
, _hd_uniqId = Nothing
, _hd_uniqIdBdd = Nothing
, _hd_page = Nothing
, _hd_title = t
, _hd_authors = Just $ foldl (\x y -> x <> ", " <> y) "" (map ISTEX._author_name a)
, _hd_institutes = Just $ foldl (\x y -> x <> ", " <> y) "" (concat $ (map ISTEX._author_affiliations) a)
, _hd_source = Just $ foldl (\x y -> x <> ", " <> y) "" (catMaybes $ map ISTEX._source_title s)
, _hd_abstract = ab
, _hd_publication_date = fmap (T.pack . show) utctime
, _hd_publication_year = pub_year
, _hd_publication_month = pub_month
, _hd_publication_day = pub_day
, _hd_publication_hour = Nothing
, _hd_publication_minute = Nothing
, _hd_publication_second = Nothing
, _hd_language_iso2 = Just $ (T.pack . show) la
}
{-|
Module : Gargantext.Utils.Zip
Description : Gargantext utilities
Copyright : (c) CNRS, 2017
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Utilities for handling zip files
-}
{-# LANGUAGE PackageImports #-}
module Gargantext.Utils.Zip where
import "zip" Codec.Archive.Zip (withArchive, ZipArchive)
-- import Control.Monad.Base (liftBase)
import Data.ByteString qualified as BS
import Protolude
import System.Directory (removeFile)
import System.IO.Temp (emptySystemTempFile)
withZipFileBS :: MonadIO m => BS.ByteString -> ZipArchive a -> m a
withZipFileBS bs actions =
liftIO $ bracket (emptySystemTempFile "parsed-zip")
(\path -> removeFile path) $
\path -> do
BS.writeFile path bs
withArchive path actions
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