Fix haddock parse error
[gargantext.git] / src / Gargantext / API / Node / Corpus / New.hs
index 13e6fd5de28e130dbc826bbd9fe441c654cb153e..3268aace491d12a284c6e9f5e39e9a0b6c2a88a4 100644 (file)
@@ -18,9 +18,12 @@ New corpus means either:
 module Gargantext.API.Node.Corpus.New
       where
 
+import Conduit
 import Control.Lens hiding (elements, Empty)
 import Data.Aeson
 import Data.Aeson.TH (deriveJSON)
+import qualified Data.ByteString.Base64 as BSB64
+import Data.Conduit.Internal (zipSources)
 import Data.Either
 import Data.Maybe (fromMaybe)
 import Data.Swagger
@@ -30,32 +33,37 @@ import GHC.Generics (Generic)
 import Servant
 import Servant.Job.Utils (jsonOptions)
 -- import Servant.Multipart
+import qualified Data.Text.Encoding as TE
 -- import Test.QuickCheck (elements)
 import Test.QuickCheck.Arbitrary
 
-import Gargantext.Prelude
-
-import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
-import qualified Gargantext.API.Admin.Orchestrator.Types as T
+import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs, ScraperEvent(..), scst_events)
 import Gargantext.API.Admin.Types (HasSettings)
-import Gargantext.API.Node.Corpus.New.File
+import Gargantext.API.Job (addEvent, jobLogSuccess, jobLogFailTotal)
+import Gargantext.API.Node.Corpus.New.Types
+import Gargantext.API.Node.Corpus.Searx
+import Gargantext.API.Node.Corpus.Types
 import Gargantext.API.Node.Types
 import Gargantext.Core (Lang(..){-, allLangs-})
-import Gargantext.Database.Action.Mail (sendMail)
+import Gargantext.Core.Text.List.Social (FlowSocialListWith(..))
 import Gargantext.Core.Types.Individu (User(..))
 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
-import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpus, getDataText, flowDataText, TermType(..), DataOrigin(..){-, allDataOrigins-})
-import Gargantext.Database.Action.User (getUserId)
+import Gargantext.Database.Action.Flow (flowCorpus, getDataText, flowDataText, TermType(..){-, allDataOrigins-})
+import Gargantext.Database.Action.Flow.Types (FlowCmdM)
+import Gargantext.Database.Action.Mail (sendMail)
 import Gargantext.Database.Action.Node (mkNodeWithParent)
+import Gargantext.Database.Action.User (getUserId)
 import Gargantext.Database.Admin.Types.Hyperdata
 import Gargantext.Database.Admin.Types.Node (CorpusId, NodeType(..), UserId)
+import Gargantext.Database.Prelude (hasConfig)
 import Gargantext.Database.Query.Table.Node (getNodeWith)
 import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
 import Gargantext.Database.Schema.Node (node_hyperdata)
-import qualified Gargantext.Prelude.Utils as GPU
+import Gargantext.Prelude
+import Gargantext.Prelude.Config (gc_max_docs_parsers)
 import qualified Gargantext.Core.Text.Corpus.API as API
-import qualified Gargantext.Core.Text.Corpus.Parsers as Parser (FileFormat(..), parseFormat)
-
+import qualified Gargantext.Core.Text.Corpus.Parsers as Parser (FileType(..), parseFormatC)
+import qualified Gargantext.Database.GargDB as GargDB
 ------------------------------------------------------------------------
 {-
 data Query = Query { query_query      :: Text
@@ -125,36 +133,22 @@ info :: FlowCmdM env err m => UserId -> m ApiInfo
 info _u = pure $ ApiInfo API.externalAPIs
 
 ------------------------------------------------------------------------
-
-data Database = Empty
-              | PubMed
-              | HAL
-              | IsTex
-              | Isidore
-  deriving (Eq, Show, Generic)
-
-deriveJSON (unPrefix "") ''Database
-instance ToSchema Database
-
-database2origin :: Database -> DataOrigin
-database2origin Empty   = InternalOrigin T.IsTex
-database2origin PubMed  = ExternalOrigin T.PubMed
-database2origin HAL     = ExternalOrigin T.HAL
-database2origin IsTex   = ExternalOrigin T.IsTex
-database2origin Isidore = ExternalOrigin T.Isidore
-
 ------------------------------------------------------------------------
 data WithQuery = WithQuery
-  { _wq_query     :: !Text
-  , _wq_databases :: !Database
-  , _wq_lang      :: !Lang
-  , _wq_node_id   :: !Int
+  { _wq_query        :: !Text
+  , _wq_databases    :: !Database
+  , _wq_datafield    :: !(Maybe Datafield)
+  , _wq_lang         :: !Lang
+  , _wq_node_id      :: !Int
+  , _wq_flowListWith :: !FlowSocialListWith
   }
   deriving Generic
 
 makeLenses ''WithQuery
 instance FromJSON WithQuery where
   parseJSON = genericParseJSON $ jsonOptions "_wq_"
+instance ToJSON WithQuery where
+  toJSON = genericToJSON $ jsonOptions "_wq_"
 instance ToSchema WithQuery where
   declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wq_")
 
@@ -181,6 +175,8 @@ type AddWithFile = Summary "Add with MultipartData to corpus endpoint"
 
 ------------------------------------------------------------------------
 -- TODO WithQuery also has a corpus id
+
+
 addToCorpusWithQuery :: FlowCmdM env err m
                        => User
                        -> CorpusId
@@ -188,36 +184,75 @@ addToCorpusWithQuery :: FlowCmdM env err m
                        -> Maybe Integer
                        -> (JobLog -> m ())
                        -> m JobLog
-addToCorpusWithQuery user cid (WithQuery q dbs l _nid) maybeLimit logStatus = do
+addToCorpusWithQuery user cid (WithQuery { _wq_query = q
+                                         , _wq_databases = dbs
+                                         , _wq_datafield = datafield
+                                         , _wq_lang = l
+                                         , _wq_flowListWith = flw }) maybeLimit logStatus = do
   -- TODO ...
   logStatus JobLog { _scst_succeeded = Just 0
                    , _scst_failed    = Just 0
-                   , _scst_remaining = Just 5
-                   , _scst_events    = Just []
-                   }
-  printDebug "addToCorpusWithQuery" (cid, dbs)
-  -- TODO add cid
-  -- TODO if cid is folder -> create Corpus
-  --      if cid is corpus -> add to corpus
-  --      if cid is root   -> create corpus in Private
-  txts <- mapM (\db  -> getDataText db (Multi l) q maybeLimit) [database2origin dbs]
-
-  logStatus JobLog { _scst_succeeded = Just 2
-                   , _scst_failed    = Just 0
-                   , _scst_remaining = Just 1
-                   , _scst_events    = Just []
-                   }
-
-  cids <- mapM (\txt -> flowDataText user txt (Multi l) cid) txts
-  printDebug "corpus id" cids
-  printDebug "sending email" ("xxxxxxxxxxxxxxxxxxxxx" :: Text)
-  sendMail user
-  -- TODO ...
-  pure      JobLog { _scst_succeeded = Just 3
-                   , _scst_failed    = Just 0
-                   , _scst_remaining = Just 0
+                   , _scst_remaining = Just 3
                    , _scst_events    = Just []
                    }
+  printDebug "[addToCorpusWithQuery] (cid, dbs)" (cid, dbs)
+  printDebug "[addToCorpusWithQuery] datafield" datafield
+  printDebug "[addToCorpusWithQuery] flowListWith" flw
+
+  case datafield of
+    Just Web -> do
+      printDebug "[addToCorpusWithQuery] processing web request" datafield
+
+      _ <- triggerSearxSearch user cid q l logStatus
+
+      pure JobLog { _scst_succeeded = Just 3
+                  , _scst_failed    = Just 0
+                  , _scst_remaining = Just 0
+                  , _scst_events    = Just []
+                  }
+
+    _ -> do
+      -- TODO add cid
+      -- TODO if cid is folder -> create Corpus
+      --      if cid is corpus -> add to corpus
+      --      if cid is root   -> create corpus in Private
+      printDebug "[G.A.N.C.New] getDataText with query" q
+      eTxts <- mapM (\db -> getDataText db (Multi l) q maybeLimit) [database2origin dbs]
+
+      let lTxts = lefts eTxts
+      printDebug "[G.A.N.C.New] lTxts" lTxts
+      case lTxts of
+        [] -> do
+          let txts = rights eTxts
+          -- TODO Sum lenghts of each txt elements
+          logStatus $ JobLog { _scst_succeeded = Just 2
+                             , _scst_failed    = Just 0
+                             , _scst_remaining = Just $ 1 + length txts
+                             , _scst_events    = Just []
+                             }
+
+          cids <- mapM (\txt -> do
+                           flowDataText user txt (Multi l) cid Nothing logStatus) txts
+          printDebug "corpus id" cids
+          printDebug "sending email" ("xxxxxxxxxxxxxxxxxxxxx" :: Text)
+          sendMail user
+          -- TODO ...
+          pure JobLog { _scst_succeeded = Just 3
+                      , _scst_failed    = Just 0
+                      , _scst_remaining = Just 0
+                      , _scst_events    = Just []
+                      }
+        
+        (err:_) -> do
+          printDebug "Error: " err
+          let jl = addEvent "ERROR" (T.pack $ show err) $
+                JobLog { _scst_succeeded = Just 2
+                       , _scst_failed    = Just 1
+                       , _scst_remaining = Just 0
+                       , _scst_events    = Just []
+                       }
+          logStatus jl
+          pure jl
 
 
 type AddWithForm = Summary "Add with FormUrlEncoded to corpus endpoint"
@@ -228,57 +263,90 @@ type AddWithForm = Summary "Add with FormUrlEncoded to corpus endpoint"
    :> "async"
      :> AsyncJobs JobLog '[FormUrlEncoded] NewWithForm JobLog
 
-addToCorpusWithForm :: FlowCmdM env err m
+addToCorpusWithForm :: (FlowCmdM env err m)
                     => User
                     -> CorpusId
                     -> NewWithForm
                     -> (JobLog -> m ())
+                    -> JobLog
                     -> m JobLog
-addToCorpusWithForm user cid (NewWithForm ft d l _n) logStatus = do
-
+addToCorpusWithForm user cid (NewWithForm ft ff d l _n) logStatus jobLog = do
   printDebug "[addToCorpusWithForm] Parsing corpus: " cid
   printDebug "[addToCorpusWithForm] fileType" ft
-  logStatus JobLog { _scst_succeeded = Just 0
-                   , _scst_failed    = Just 0
-                   , _scst_remaining = Just 2
-                   , _scst_events    = Just []
-                   }
+  printDebug "[addToCorpusWithForm] fileFormat" ff
+  logStatus jobLog
+  limit' <- view $ hasConfig . gc_max_docs_parsers
+  let limit = fromIntegral limit' :: Integer
   let
-    parse = case ft of
-      CSV_HAL   -> Parser.parseFormat Parser.CsvHal
-      CSV       -> Parser.parseFormat Parser.CsvGargV3
-      WOS       -> Parser.parseFormat Parser.WOS
-      PresseRIS -> Parser.parseFormat Parser.RisPresse
-
+    parseC = case ft of
+      CSV_HAL   -> Parser.parseFormatC Parser.CsvHal
+      CSV       -> Parser.parseFormatC Parser.CsvGargV3
+      WOS       -> Parser.parseFormatC Parser.WOS
+      PresseRIS -> Parser.parseFormatC Parser.RisPresse
+  
   -- TODO granularity of the logStatus
-  docs <- liftBase $ splitEvery 500
-      <$> take 1000000
-      <$> parse (cs d)
-
-  printDebug "Parsing corpus finished : " cid
-  logStatus JobLog { _scst_succeeded = Just 1
-                   , _scst_failed    = Just 0
-                   , _scst_remaining = Just 1
-                   , _scst_events    = Just []
-                   }
-
-
-  printDebug "Starting extraction     : " cid
-  -- TODO granularity of the logStatus
-  _cid' <- flowCorpus user
-                     (Right [cid])
-                     (Multi $ fromMaybe EN l)
-                     (map (map toHyperdataDocument) docs)
-
-  printDebug "Extraction finished   : " cid
-  printDebug "sending email" ("xxxxxxxxxxxxxxxxxxxxx" :: Text)
-  sendMail user
-
-  pure      JobLog { _scst_succeeded = Just 2
-                   , _scst_failed    = Just 0
-                   , _scst_remaining = Just 0
-                   , _scst_events    = Just []
-                   }
+  let data' = case ff of
+        Plain -> cs d
+        ZIP   -> case BSB64.decode $ TE.encodeUtf8 d of
+          Left err -> panic $ T.pack "[addToCorpusWithForm] error decoding base64: " <> T.pack err
+          Right decoded -> decoded
+  eDocsC <- liftBase $ parseC ff data'
+  case eDocsC of
+    Right (mCount, docsC) -> do
+      -- TODO Add progress (jobStatus) update for docs - this is a
+      -- long action
+
+      let docsC' = zipSources (yieldMany [1..]) docsC
+                  .| mapMC (\(idx, doc) ->
+                        if idx > limit then do
+                          --printDebug "[addToCorpusWithForm] number of docs exceeds the limit" (show limit)
+                          let panicMsg' = [ "[addToCorpusWithForm] number of docs "
+                                          , "exceeds the MAX_DOCS_PARSERS limit ("
+                                          , show limit
+                                          , ")" ]
+                          let panicMsg = T.concat $ T.pack <$> panicMsg'
+                          --logStatus $ jobLogFailTotalWithMessage panicMsg jobLog
+                          panic panicMsg
+                        else
+                          pure doc)
+                  .| mapC toHyperdataDocument
+
+      --printDebug "Parsing corpus finished : " cid
+      --logStatus jobLog2
+
+      --printDebug "Starting extraction     : " cid
+      -- TODO granularity of the logStatus
+      printDebug "flowCorpus with lang" l
+
+      _cid' <- flowCorpus user
+                          (Right [cid])
+                          (Multi $ fromMaybe EN l)
+                          Nothing
+                          --(Just $ fromIntegral $ length docs, docsC')
+                          (mCount, transPipe liftBase docsC') -- TODO fix number of docs
+                          --(map (map toHyperdataDocument) docs)
+                          logStatus
+
+      printDebug "Extraction finished   : " cid
+      printDebug "sending email" ("xxxxxxxxxxxxxxxxxxxxx" :: Text)
+      -- TODO uncomment this
+      --sendMail user
+
+      logStatus jobLog3
+      pure jobLog3
+    Left e -> do
+      printDebug "[addToCorpusWithForm] parse error" e
+
+      let evt = ScraperEvent { _scev_message = Just $ T.pack e
+                             , _scev_level = Just "ERROR"
+                             , _scev_date = Nothing }
+
+      logStatus $ over (scst_events . _Just) (\evt' -> evt' <> [evt]) jobLogE
+      pure jobLogE
+    where
+      jobLog2 = jobLogSuccess jobLog
+      jobLog3 = jobLogSuccess jobLog2
+      jobLogE = jobLogFailTotal jobLog
 
 {-
 addToCorpusWithFile :: FlowCmdM env err m
@@ -328,7 +396,7 @@ addToCorpusWithFile user cid nwf@(NewWithFile _d _l fName) logStatus = do
                    , _scst_events    = Just []
                    }
 
-  fPath <- GPU.writeFile nwf
+  fPath <- GargDB.writeFile nwf
   printDebug "[addToCorpusWithFile] File saved as: " fPath
 
   uId <- getUserId user
@@ -354,3 +422,4 @@ addToCorpusWithFile user cid nwf@(NewWithFile _d _l fName) logStatus = do
                 , _scst_remaining = Just 0
                 , _scst_events    = Just []
                 }
+