Commit a3239acb authored by Alexandre Delanoë's avatar Alexandre Delanoë

[INI] max docs for scrapers config

parent e6a9f9c4
......@@ -17,6 +17,8 @@ FRAME_CALC_URL = URL_TO_CHANGE
FRAME_SEARX_URL = URL_TO_CHANGE
FRAME_ISTEX_URL = URL_TO_CHANGE
MAX_DOCS_SCRAPERS = 10000
[server]
# Server config (TODO connect in ReaderMonad)
ALLOWED_ORIGIN = http://localhost
......
......@@ -26,7 +26,7 @@ module Gargantext.API.Routes
-- import qualified Gargantext.API.Search as Search
import Control.Concurrent (threadDelay)
-- import Control.Lens (view)
import Control.Lens (view)
import Data.Text (Text)
import Data.Validity
import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
......@@ -37,10 +37,11 @@ import Gargantext.API.Node
import Gargantext.API.Prelude
import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Viz.Graph.API
-- import Gargantext.Database.Prelude (HasConfig(..))
import Gargantext.Database.Prelude (HasConfig(..))
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node
import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(..))
import Servant
import Servant.Auth as SA
import Servant.Auth.Swagger ()
......@@ -246,17 +247,16 @@ waitAPI n = do
----------------------------------------
addCorpusWithQuery :: User -> GargServer New.AddWithQuery
addCorpusWithQuery user cid = do
-- TODO gargantext.ini
-- _env <- view hasConfig
let limit = Just 100
addCorpusWithQuery user cid =
serveJobsAPI $
JobFunction (\q log ->
let
log' x = do
printDebug "addToCorpusWithQuery" x
liftBase $ log x
in New.addToCorpusWithQuery user cid q limit log'
JobFunction (\q log -> do
conf <- view hasConfig
let limit = Just $ _gc_max_docs_scrapers conf
New.addToCorpusWithQuery user cid q limit (liftBase . log)
{- let log' x = do
printDebug "addToCorpusWithQuery" x
liftBase $ log x
-}
)
{-
......
......@@ -13,6 +13,7 @@ Portability : POSIX
module Gargantext.Prelude.Config where
import Prelude (read)
import System.IO (FilePath)
import Data.Ini (readIniFile, lookupValue)
import Data.Either.Extra (Either(Left, Right))
......@@ -31,6 +32,8 @@ data GargConfig = GargConfig { _gc_masteruser :: !Text
, _gc_frame_searx_url :: !Text
, _gc_frame_istex_url :: !Text
, _gc_max_docs_scrapers :: !Integer
}
deriving (Generic, Show)
......@@ -40,11 +43,11 @@ readConfig :: FilePath -> IO GargConfig
readConfig fp = do
ini <- readIniFile fp
let ini'' = case ini of
Left e -> panic (pack $ "No ini file error" <> show e)
Left e -> panic (pack $ "gargantext.ini not found" <> show e)
Right ini' -> ini'
let val x = case (lookupValue (pack "gargantext") (pack x) ini'') of
Left _ -> panic (pack $ "no" <> x)
Left _ -> panic (pack $ "ERROR: add " <> x <> " to your gargantext.ini")
Right p' -> p'
pure $ GargConfig (val "MASTER_USER")
......@@ -54,6 +57,7 @@ readConfig fp = do
(val "FRAME_CALC_URL")
(val "FRAME_SEARX_URL")
(val "FRAME_ISTEX_URL")
(read $ cs $ val "MAX_DOCS_SCRAPERS")
defaultConfig :: GargConfig
defaultConfig = GargConfig "gargantua"
......@@ -63,3 +67,4 @@ defaultConfig = GargConfig "gargantua"
"https://frame_calc.url"
"https://frame_searx.url"
"https://frame_istex.url"
1000
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