Commit 8426629a authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REFACT] Config in Prelude now

parent 2d5a3e0a
Pipeline #1013 failed with stage
......@@ -54,7 +54,7 @@ import System.Log.FastLogger
import Web.HttpApiData (parseUrlPiece)
import qualified Data.ByteString.Lazy as L
import qualified Servant.Job.Core
import Gargantext.Config (GargConfig(), readConfig, defaultConfig)
import Gargantext.Prelude.Config (GargConfig(), readConfig, defaultConfig)
type PortNumber = Int
......
......@@ -31,7 +31,7 @@ import Gargantext.Prelude
import Gargantext.Core.Crypto.Hash (hash)
import Gargantext.Database.Prelude
import Control.Lens (view)
import Gargantext.Config (GargConfig(..))
import Gargantext.Prelude.Config (GargConfig(..))
------------------------------------------------------------------------
-- | TODO mk all others nodes
......
......@@ -34,7 +34,7 @@ import Database.PostgreSQL.Simple (Connection, connect)
import Database.PostgreSQL.Simple.FromField ( Conversion, ResultError(ConversionFailed), fromField, returnError)
import Database.PostgreSQL.Simple.Internal (Field)
import Gargantext.Prelude
import Gargantext.Config (GargConfig())
import Gargantext.Prelude.Config (GargConfig())
import Opaleye (Query, Unpackspec, showSqlForPostgres, FromFields, Select, runQuery)
import Opaleye.Aggregate (countRows)
import System.IO (FilePath)
......
{-|
Module : Gargantext.Config
Module : Gargantext.Prelude.Config
Description : Textmining Collaborative Platform
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
......@@ -11,7 +11,7 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Config where
module Gargantext.Prelude.Config where
import System.IO (FilePath)
import Data.Ini (readIniFile, lookupValue)
......
......@@ -28,7 +28,7 @@ import System.Random (newStdGen)
import qualified System.Random.Shuffle as SRS
import Gargantext.API.Admin.Settings
import Gargantext.Config
import Gargantext.Prelude.Config
import Gargantext.Core.Crypto.Hash
import Gargantext.Database.Admin.Types.Node (NodeId, NodeType)
import Gargantext.Prelude
......
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