Commit 9632276f authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Move GargConfig into gargantext

This commit moves `GargConfig` and the other config-related
data structures back into gargantext, so that they can be edited
and expanded without needing to worry about the prelude project.
parent 761189eb
......@@ -29,7 +29,7 @@ import Gargantext.Database.Query.Table.Node (getOrMkList)
import Gargantext.Database.Query.Table.User (insertNewUsers, )
import Gargantext.Database.Query.Tree.Root (MkCorpusUser(MkCorpusUserMaster))
import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(..), readConfig)
import Gargantext.Core.Config (GargConfig(..), readConfig)
import Gargantext.API.Admin.Types
import Gargantext.Database.Prelude (DBCmd')
import CLI.Types
......
......@@ -25,7 +25,7 @@ import Gargantext.Core.NLP (HasNLPServer)
import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Prelude (CmdRandom)
import Gargantext.Prelude
import Gargantext.Prelude.Config (readConfig)
import Gargantext.Core.Config (readConfig)
import Options.Applicative
import Prelude (String)
import Gargantext.Core.Types
......
......@@ -21,7 +21,7 @@ import Data.List qualified as List (cycle, concat, take, unlines)
import Gargantext.API.Dev (withDevEnv)
import Gargantext.API.Node () -- instances only
import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(..), readConfig)
import Gargantext.Core.Config (GargConfig(..), readConfig)
import Prelude qualified
import Options.Applicative
......
......@@ -18,7 +18,7 @@ fi
# with the `sha256sum` result calculated on the `cabal.project` and
# `cabal.project.freeze`. This ensures the files stay deterministic so that CI
# cache can kick in.
expected_cabal_project_hash="22167800d98d4f204c85c49420eaee0618e749062b9ae9709719638e54319ae9"
expected_cabal_project_hash="9e32b45568d34952aaa77884dcc5e9bb7317fe8c5bc2c45267ea7178332852e8"
expected_cabal_project_freeze_hash="7bb3ba71d0a1881a5c4fd420b9988155586e0cf51e9b6d55867bce3d311d59a5"
cabal --store-dir=$STORE_DIR v2-build --dry-run
......
......@@ -123,8 +123,7 @@ source-repository-package
source-repository-package
type: git
location: https://gitlab.iscpif.fr/gargantext/haskell-gargantext-prelude
-- tag: 618f711a530df56caefbb1577c4bf3d5ff45e214
tag: d4f9bee483d41bbdf8ab4e09efb5a5a8216edff4
tag: bb15d828d5ef36eeaa84cccb00598b585048c88e
source-repository-package
type: git
......
......@@ -164,6 +164,9 @@ library
Gargantext.API.Types
Gargantext.API.Viz.Types
Gargantext.Core
Gargantext.Core.Config
Gargantext.Core.Config.Mail
Gargantext.Core.Config.NLP
Gargantext.Core.Mail.Types
Gargantext.Core.Methods.Similarities
Gargantext.Core.Methods.Similarities.Conditional
......@@ -582,6 +585,7 @@ library
, located-base ^>= 0.1.1.1
, logging-effect ^>= 1.3.12
, matrix ^>= 0.3.6.1
, mime-mail >= 0.5.1
, monad-control ^>= 1.0.3.1
, monad-logger ^>= 0.3.36
, morpheus-graphql >= 0.17.0 && < 0.25
......@@ -595,6 +599,7 @@ library
, morpheus-graphql-tests >= 0.17.0 && < 0.25
, mtl ^>= 2.2.2
, natural-transformation ^>= 0.4
, network >= 3.1.4.0
, network-uri ^>= 2.6.4.1
, opaleye ^>= 0.9.6.1
, opaleye-textsearch >= 0.1.0.0
......@@ -651,6 +656,7 @@ library
, simple-reflect ^>= 0.3.3
, singletons ^>= 2.7
, singletons-th >= 3.1
, smtp-mail >= 0.3.0.0
, split ^>= 0.2.3.4
, stemmer ^>= 0.5.2
, stm ^>= 2.5.0.1
......
......@@ -41,8 +41,8 @@ import Gargantext.Core.NLP (NLPServerMap, HasNLPServer(..))
import Gargantext.Core.NodeStory
import Gargantext.Database.Prelude (HasConnectionPool(..), HasConfig(..))
import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(..))
import Gargantext.Prelude.Mail.Types (MailConfig)
import Gargantext.Core.Config (GargConfig(..))
import Gargantext.Core.Config.Mail (MailConfig)
import Gargantext.System.Logging
import Gargantext.Utils.Jobs.Map (LoggerM, J(..), jTask, rjGetLog)
import Gargantext.Utils.Jobs.Monad qualified as Jobs
......
......@@ -35,10 +35,9 @@ import Gargantext.Core.NLP (nlpServerMap)
import Gargantext.Core.NodeStory
import Gargantext.Database.Prelude (databaseParameters, hasConfig)
import Gargantext.Prelude
import Gargantext.Prelude.Config (gc_js_job_timeout, gc_js_id_timeout)
import Gargantext.Prelude.Config ({-GargConfig(..),-} {-gc_repofilepath,-} readConfig)
import Gargantext.Prelude.Mail qualified as Mail
import Gargantext.Prelude.NLP qualified as NLP
import Gargantext.Core.Config (gc_js_job_timeout, gc_js_id_timeout, readConfig)
import Gargantext.Core.Config.Mail qualified as Mail
import Gargantext.Core.Config.NLP qualified as NLP
import Gargantext.System.Logging
import Gargantext.Utils.Jobs qualified as Jobs
import Gargantext.Utils.Jobs.Monad qualified as Jobs
......
......@@ -6,7 +6,7 @@ import Prelude
import Control.Lens.TH
import Data.Text qualified as T
import Gargantext.Prelude.Config
import Gargantext.Core.Config
import Servant.Client.Core.BaseUrl
import Toml
......
......@@ -31,7 +31,7 @@ import Gargantext.Database.Prelude (DBCmd, HasConfig (..))
import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Query.Tree
import Gargantext.Database.Query.Tree.Root
import Gargantext.Prelude.Config (GargConfig(..))
import Gargantext.Core.Config (GargConfig(..))
import Prelude
import Servant
import Servant.Auth.Server.Internal.AddSetCookie
......
......@@ -24,9 +24,9 @@ import Gargantext.Core.NLP (nlpServerMap)
import Gargantext.Core.NodeStory (fromDBNodeStoryEnv)
import Gargantext.Database.Prelude (Cmd', Cmd'', connPool, databaseParameters, runCmd)
import Gargantext.Prelude
import Gargantext.Prelude.Config (readConfig)
import Gargantext.Prelude.Mail qualified as Mail
import Gargantext.Prelude.NLP qualified as NLP
import Gargantext.Core.Config (readConfig)
import Gargantext.Core.Config.Mail qualified as Mail
import Gargantext.Core.Config.NLP qualified as NLP
import Gargantext.System.Logging ( withLoggerHoisted )
import Servant ( ServerError )
......
......@@ -57,7 +57,7 @@ import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Query.Tree.Root (MkCorpusUser(MkCorpusUserNormalCorpusIds))
import Gargantext.Database.Schema.Node (node_hyperdata)
import Gargantext.Prelude
import Gargantext.Prelude.Config (gc_max_docs_parsers)
import Gargantext.Core.Config (gc_max_docs_parsers)
import Gargantext.System.Logging ( logLocM, LogLevel(..) )
import Gargantext.Utils.Jobs.Monad (JobHandle, MonadJobStatus(..))
import Test.QuickCheck.Arbitrary (Arbitrary(..))
......
......@@ -43,7 +43,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Tree.Error (HasTreeError)
import Gargantext.Database.Query.Tree.Root (getOrMkRootWithCorpus, MkCorpusUser (MkCorpusUserMaster))
import Gargantext.Prelude hiding (All)
import Gargantext.Prelude.Config (GargConfig(..))
import Gargantext.Core.Config (GargConfig(..))
import Gargantext.Utils.Jobs.Monad (JobHandle, MonadJobStatus(..))
import Network.HTTP.Client
import Network.HTTP.Client.TLS (tlsManagerSettings)
......
......@@ -9,7 +9,7 @@ import Gargantext.API.Prelude
import Gargantext.Core.Types (NodeType, NodeId, unNodeId)
import Gargantext.Database.Prelude (HasConfig (hasConfig), CmdCommon)
import Control.Lens.Getter (view)
import Gargantext.Prelude.Config (gc_url)
import Gargantext.Core.Config (gc_url)
import Gargantext.API.Routes.Named.Share qualified as Named
import Servant.Server.Generic (AsServerT)
......
......@@ -34,7 +34,7 @@ import Gargantext.API.Routes.Named.Corpus qualified as Named
import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Prelude (HasConfig(..))
import Gargantext.Prelude
import Gargantext.Prelude.Config (gc_max_docs_scrapers)
import Gargantext.Core.Config (gc_max_docs_scrapers)
import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..))
import Servant
import Servant.Auth.Swagger ()
......
......@@ -24,7 +24,7 @@ import Gargantext.API.Swagger (swaggerDoc)
import Gargantext.API.ThrowAll (serverPrivateGargAPI)
import Gargantext.Database.Prelude (hasConfig)
import Gargantext.Prelude hiding (Handler, catch)
import Gargantext.Prelude.Config (gc_url_backend_api)
import Gargantext.Core.Config (gc_url_backend_api)
import Gargantext.System.Logging (logLocM, LogLevel(..))
import Paths_gargantext qualified as PG -- cabal magic build module
import Servant
......
{-|
Module : Gargantext.Core.Config
Description : Textmining Collaborative Platform
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
Configuration for the gargantext server
-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Core.Config (
-- * Types
GargConfig(..)
-- * Lenses
, gc_backend_name
, gc_datafilepath
, gc_epo_api_url
, gc_frame_calc_url
, gc_frame_istex_url
, gc_frame_searx_url
, gc_frame_visio_url
, gc_frame_write_url
, gc_js_id_timeout
, gc_js_job_timeout
, gc_masteruser
, gc_max_docs_parsers
, gc_max_docs_scrapers
, gc_pubmed_api_key
, gc_repofilepath
, gc_secretkey
, gc_url
, gc_url_backend_api
-- * Utility functions
, readIniFile'
, readConfig
, val
) where
import Data.Ini (readIniFile, lookupValue, Ini)
import Data.Text as T
import Prelude (read)
import Gargantext.Prelude
-- | strip a given character from end of string
stripRight :: Char -> T.Text -> T.Text
stripRight c s = if T.last s == c then stripRight c (T.take (T.length s - 1) s) else s
data GargConfig = GargConfig { _gc_backend_name :: !T.Text
, _gc_url :: !T.Text
, _gc_url_backend_api :: !T.Text
, _gc_masteruser :: !T.Text
, _gc_secretkey :: !T.Text
, _gc_datafilepath :: !FilePath
, _gc_repofilepath :: !FilePath
, _gc_frame_write_url :: !T.Text
, _gc_frame_calc_url :: !T.Text
, _gc_frame_visio_url :: !T.Text
, _gc_frame_searx_url :: !T.Text
, _gc_frame_istex_url :: !T.Text
, _gc_max_docs_parsers :: !Integer
, _gc_max_docs_scrapers :: !Integer
, _gc_pubmed_api_key :: !T.Text
, _gc_js_job_timeout :: !Integer
, _gc_js_id_timeout :: !Integer
, _gc_epo_api_url :: !T.Text
}
deriving (Generic, Show)
makeLenses ''GargConfig
readIniFile' :: FilePath -> IO Ini
readIniFile' fp = do
ini <- readIniFile fp
case ini of
Left e -> panicTrace $ T.pack $ "ini file not found " <> show e
Right ini' -> pure ini'
val :: Ini -> Text -> Text -> Text
val ini section key = do
case (lookupValue section key ini) of
Left e -> panicTrace $ "ERROR: add " <> key <> " in section \"" <> section <> "\" to your gargantext.ini. " <> show e
Right p' -> p'
readConfig :: FilePath -> IO GargConfig
readConfig fp = do
ini <- readIniFile' fp
let val' = val ini "gargantext"
pure $ GargConfig
{ _gc_backend_name = cs $ val' "BACKEND_NAME"
, _gc_url = stripRight '/' $ val' "URL"
, _gc_url_backend_api = stripRight '/' $ val' "URL_BACKEND_API"
, _gc_masteruser = val' "MASTER_USER"
, _gc_secretkey = val' "SECRET_KEY"
, _gc_datafilepath = cs $ val' "DATA_FILEPATH"
, _gc_repofilepath = cs $ val' "REPO_FILEPATH"
, _gc_frame_write_url = stripRight '/' $ val' "FRAME_WRITE_URL"
, _gc_frame_calc_url = stripRight '/' $ val' "FRAME_CALC_URL"
, _gc_frame_visio_url = stripRight '/' $ val' "FRAME_VISIO_URL"
, _gc_frame_searx_url = stripRight '/' $ val' "FRAME_SEARX_URL"
, _gc_frame_istex_url = stripRight '/' $ val' "FRAME_ISTEX_URL"
, _gc_max_docs_parsers = read $ cs $ val' "MAX_DOCS_PARSERS"
, _gc_max_docs_scrapers = read $ cs $ val' "MAX_DOCS_SCRAPERS"
, _gc_pubmed_api_key = val' "PUBMED_API_KEY"
, _gc_js_job_timeout = read $ cs $ val' "JS_JOB_TIMEOUT"
, _gc_js_id_timeout = read $ cs $ val' "JS_ID_TIMEOUT"
, _gc_epo_api_url = cs $ val' "EPO_API_URL"
}
{-|
Module : Gargantext.Core.Config.Mail
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Core.Config.Mail (
-- * Types
GargMail(..)
, LoginType(..)
, MailConfig(..)
-- * Utility functions
, gargMail
, readConfig
-- * Lenses
, mc_mail_from
, mc_mail_host
, mc_mail_login_type
, mc_mail_password
, mc_mail_port
, mc_mail_user
)
where
import Data.Maybe
import Data.Text (unpack)
import Data.Text qualified as T
import Gargantext.Core.Config (readIniFile', val)
import Gargantext.Prelude
import Network.Mail.Mime (plainPart)
import Network.Mail.SMTP hiding (htmlPart, STARTTLS)
import Network.Socket (PortNumber)
import Prelude (read)
type Email = Text
type Name = Text
data LoginType = NoAuth | Normal | SSL | TLS | STARTTLS
deriving (Generic, Eq, Show, Read)
data MailConfig = MailConfig { _mc_mail_host :: !T.Text
, _mc_mail_port :: !PortNumber
, _mc_mail_user :: !T.Text
, _mc_mail_password :: !T.Text
, _mc_mail_login_type :: !LoginType
, _mc_mail_from :: !T.Text
}
deriving (Generic, Show)
readConfig :: FilePath -> IO MailConfig
readConfig fp = do
ini <- readIniFile' fp
let val' = val ini "mail"
pure $ MailConfig { _mc_mail_host = cs $ val' "MAIL_HOST"
, _mc_mail_port = read $ cs $ val' "MAIL_PORT"
, _mc_mail_user = cs $ val' "MAIL_USER"
, _mc_mail_from = cs $ val' "MAIL_FROM"
, _mc_mail_password = cs $ val' "MAIL_PASSWORD"
, _mc_mail_login_type = read $ cs $ val' "MAIL_LOGIN_TYPE"
}
data GargMail = GargMail { gm_to :: Email
, gm_name :: Maybe Name
, gm_subject :: Text
, gm_body :: Text
}
-- | TODO add parameters to gargantext.ini
gargMail :: MailConfig -> GargMail -> IO ()
gargMail (MailConfig {..}) (GargMail { .. }) = do
let host = unpack _mc_mail_host
user = unpack _mc_mail_user
password = unpack _mc_mail_password
case _mc_mail_login_type of
NoAuth -> sendMail host mail
Normal -> sendMailWithLogin' host _mc_mail_port user password mail
SSL -> sendMailWithLoginTLS' host _mc_mail_port user password mail
TLS -> sendMailWithLoginTLS' host _mc_mail_port user password mail
STARTTLS -> sendMailWithLoginSTARTTLS' host _mc_mail_port user password mail
where
mail = simpleMail sender receiver cc bcc gm_subject [plainPart $ cs gm_body]
sender = Address (Just "GarganText Email") _mc_mail_from
receiver = [Address gm_name gm_to]
cc = []
bcc = []
makeLenses ''MailConfig
{-|
Module : Gargantext.Core.Config.NLP
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Core.Config.NLP (
-- * Types
NLPConfig(..)
-- * Utility functions
, readConfig
-- * Lenses
, nlp_default
, nlp_languages
)
where
import Data.Ini qualified as Ini
import Data.Map.Strict qualified as Map
import Data.Maybe
import Data.Text qualified as T
import Gargantext.Core.Config (readIniFile', val)
import Gargantext.Prelude
import Gargantext.Prelude.Utils (listToMaybeAll)
import Network.URI (URI)
import Network.URI (parseURI)
data NLPConfig = NLPConfig { _nlp_default :: URI
, _nlp_languages :: (Map.Map T.Text URI) }
deriving (Generic, Show)
iniSection :: Text
iniSection = "nlp"
readConfig :: FilePath -> IO NLPConfig
readConfig fp = do
ini <- readIniFile' fp
let val' = val ini iniSection
let lang_default_text = "EN" -- Change this value by one of your choice: "All", "FR", or "EN"
let m_nlp_default = parseURI $ cs $ val' lang_default_text
let m_nlp_keys = filter (\k -> k `notElem` [lang_default_text]) $ fromRight [] $ Ini.keys iniSection ini
let m_nlp_other = listToMaybeAll $ (\k -> (,) k <$> (parseURI $ cs $ val' k)) <$> m_nlp_keys
let mRet = NLPConfig <$> m_nlp_default <*> (Map.fromList <$> m_nlp_other)
case mRet of
Nothing -> panicTrace $ T.concat [ "Cannot read config file: _nlp_default = "
, T.pack $ show m_nlp_default
, ", _nlp_other = "
, T.pack $ show m_nlp_other ]
Just ret -> pure ret
makeLenses ''NLPConfig
......@@ -19,9 +19,8 @@ import Gargantext.Core.Types.Individu
import Gargantext.Database.Prelude (HasConfig(..))
import Gargantext.Database.Schema.User (UserLight(..))
import Gargantext.Prelude
import Gargantext.Prelude.Config (gc_url, gc_backend_name)
import Gargantext.Prelude.Mail (gargMail, GargMail(..))
import Gargantext.Prelude.Mail.Types (MailConfig)
import Gargantext.Core.Config (gc_url, gc_backend_name)
import Gargantext.Core.Config.Mail (gargMail, GargMail(..), MailConfig)
import Network.URI.Encode (encodeText)
......
......@@ -12,7 +12,7 @@ Portability : POSIX
module Gargantext.Core.Mail.Types where
import Control.Lens (Getter)
import Gargantext.Prelude.Mail.Types (MailConfig)
import Gargantext.Core.Config.Mail (MailConfig)
class HasMail env where
mailSettings :: Getter env MailConfig
......@@ -11,12 +11,12 @@ Portability : POSIX
module Gargantext.Core.NLP where
import Control.Lens (Getter, at, non)
import qualified Data.Map.Strict as Map
import Data.Map.Strict qualified as Map
import Data.Maybe (fromJust)
import Network.URI (URI(..), parseURI)
import Gargantext.Core (Lang(..), NLPServerConfig(..), PosTagAlgo(..), allLangs)
import Gargantext.Prelude.NLP.Types (NLPConfig(..))
import Gargantext.Core.Config.NLP (NLPConfig(..))
import Gargantext.Utils.Tuple (uncurryMaybeSecond)
import Network.URI (URI(..), parseURI)
import Protolude hiding (All)
......
......@@ -27,7 +27,7 @@ import Gargantext.Core.Types (ListId, NodeId(..))
import Gargantext.Database.Prelude (hasConfig)
import Gargantext.Database.Query.Table.Ngrams qualified as TableNgrams
import Gargantext.Prelude
import Gargantext.Prelude.Config (gc_repofilepath)
import Gargantext.Core.Config (gc_repofilepath)
import System.Directory (renameFile, createDirectoryIfMissing, doesFileExist, removeFile)
import System.IO (hClose)
import System.IO.Temp (withTempFile)
......
......@@ -102,7 +102,7 @@ import Gargantext.Database.Query.Tree.Root (MkCorpusUser(..), getOrMkRoot, getOr
import Gargantext.Database.Schema.Ngrams ( indexNgrams, text2ngrams )
import Gargantext.Database.Schema.Node (node_hyperdata)
import Gargantext.Prelude hiding (to)
import Gargantext.Prelude.Config (GargConfig(..))
import Gargantext.Core.Config (GargConfig(..))
import Gargantext.System.Logging ( logLocM, LogLevel(DEBUG), MonadLogger )
import Gargantext.Utils.Jobs.Monad ( JobHandle, MonadJobStatus(..) )
import PUBMED.Types qualified as PUBMED
......
......@@ -34,7 +34,7 @@ import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Prelude hiding (hash)
import Gargantext.Prelude.Config (GargConfig(..))
import Gargantext.Core.Config (GargConfig(..))
import Gargantext.Prelude.Crypto.Hash (hash)
import Servant.Client.Core.BaseUrl
......
......@@ -40,7 +40,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..), nodeError,
import Gargantext.Database.Query.Table.User
import Gargantext.Prelude
import Gargantext.Prelude.Crypto.Pass.User (gargPass)
import Gargantext.Prelude.Mail.Types (MailConfig)
import Gargantext.Core.Config.Mail (MailConfig)
import qualified Data.List.NonEmpty as NE
------------------------------------------------------------------------
......
......@@ -20,7 +20,7 @@ import Data.Text qualified as Text
import Data.Tuple.Extra (both)
import Gargantext.Database.Prelude (HasConfig(..))
import Gargantext.Prelude hiding (hash)
import Gargantext.Prelude.Config ( gc_datafilepath )
import Gargantext.Core.Config ( gc_datafilepath )
import Gargantext.Prelude.Crypto.Hash ( IsHashable(hash) )
import Prelude qualified
import System.Directory (createDirectoryIfMissing)
......
......@@ -32,7 +32,7 @@ import Database.PostgreSQL.Simple.Types (Query(..))
import Gargantext.Core.Mail.Types (HasMail)
import Gargantext.Core.NLP (HasNLPServer)
import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig(), readIniFile', val)
import Gargantext.Core.Config (GargConfig, readIniFile', val)
import Opaleye (Unpackspec, showSql, FromFields, Select, runSelect, SqlJsonb, DefaultFromField, toFields, matchMaybe, MaybeFields)
import Opaleye.Aggregate (countRows)
import Opaleye.Internal.Constant qualified
......
......@@ -28,7 +28,7 @@ import Gargantext.API.Admin.Types
import Gargantext.API.Types (HTML)
import Gargantext.Database.Prelude (hasConfig)
import Gargantext.Prelude
import Gargantext.Prelude.Config (gc_frame_write_url)
import Gargantext.Core.Config (gc_frame_write_url)
import Network.HTTP.ReverseProxy
import Network.HTTP.Types (hCacheControl, RequestHeaders, hReferer, ResponseHeaders, Header)
import Network.HTTP.Types.Header (hHost)
......
......@@ -146,7 +146,7 @@
git: "https://gitlab.iscpif.fr/gargantext/gargantext-graph.git"
subdirs:
- .
- commit: d4f9bee483d41bbdf8ab4e09efb5a5a8216edff4
- commit: bb15d828d5ef36eeaa84cccb00598b585048c88e
git: "https://gitlab.iscpif.fr/gargantext/haskell-gargantext-prelude"
subdirs:
- .
......
......@@ -23,9 +23,9 @@ import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node (getOrMkList)
import Gargantext.Database.Query.Tree.Root (MkCorpusUser(..))
import Gargantext.Prelude.Config
import Gargantext.Prelude.Mail qualified as Mail
import Gargantext.Prelude.NLP qualified as NLP
import Gargantext.Core.Config
import Gargantext.Core.Config.Mail qualified as Mail
import Gargantext.Core.Config.NLP qualified as NLP
import Gargantext.System.Logging
import Gargantext.Utils.Jobs qualified as Jobs
import Gargantext.Utils.Jobs.Monad qualified as Jobs
......
......@@ -18,7 +18,7 @@ import Gargantext.API.Admin.EnvTypes (Mode(Mock))
import Gargantext.API.Admin.Settings
import Gargantext.Core.NodeStory (fromDBNodeStoryEnv)
import Gargantext.Prelude
import Gargantext.Prelude.Config
import Gargantext.Core.Config
import Gargantext.System.Logging (withLoggerHoisted)
import Paths_gargantext
import Prelude qualified
......
......@@ -36,8 +36,8 @@ import Gargantext.Core.NLP (HasNLPServer(..))
import Gargantext.Core.NodeStory
import Gargantext.Database.Prelude (HasConfig(..), HasConnectionPool(..))
import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Prelude.Config
import Gargantext.Prelude.Mail.Types (MailConfig(..), LoginType(NoAuth))
import Gargantext.Core.Config
import Gargantext.Core.Config.Mail (MailConfig(..), LoginType(NoAuth))
import Gargantext.System.Logging (HasLogger(..), Logger, MonadLogger(..))
import Gargantext.Utils.Jobs
import Network.URI (parseURI)
......
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