Commit 651caaee authored by Alexandre Delanoë's avatar Alexandre Delanoë

Missing merge

parents 5fd34f93 5d50f716
Pipeline #6682 canceled with stages
......@@ -20,6 +20,7 @@ module CLI.Ini where
import CLI.Types
import Data.Text qualified as T
import Data.Text.IO qualified as T (writeFile)
import Database.PostgreSQL.Simple qualified as PGS
import Gargantext.Core.Config qualified as Config
import Gargantext.Core.Config.Ini.Ini qualified as Ini
......@@ -33,24 +34,26 @@ import Toml qualified
iniCLI :: IniArgs -> IO ()
iniCLI (IniArgs iniPath) = do
-- putStrLn $ "ini path: " <> iniPath
iniCLI iniArgs = do
let iniPath = fromMaybe "gargantext.ini" $ ini_path iniArgs
let tomlPath = fromMaybe "gargantext-settings.toml" $ toml_path iniArgs
putStrLn $ "Reading configuration from file " <> iniPath <> "..."
ini <- Ini.readConfig iniPath
iniMail <- IniMail.readConfig iniPath
iniNLP <- IniNLP.readConfig iniPath
-- putStrLn (show ini :: Text)
connInfo <- Ini.readDBConfig iniPath
let c = convertConfigs ini iniMail iniNLP connInfo
-- putStrLn (show c :: Text)
putStrLn (show (Toml.encode c) :: Text)
T.writeFile tomlPath (show (Toml.encode c) :: Text)
putStrLn $ "Converted configuration into TOML and wrote it to file " <> tomlPath
iniCmd :: HasCallStack => Mod CommandFields CLI
iniCmd = command "ini" (info (helper <*> fmap CLISub ini_p) (progDesc "Parse .ini file and output a corresponding .toml file."))
iniCmd = command "ini" (info (helper <*> fmap CLISub iniParser)
(progDesc "Parse .ini file and output a corresponding .toml file."))
ini_p :: Parser CLICmd
ini_p = fmap CCMD_ini $ IniArgs
<$> strOption ( long "ini-path"
<> help "Path to ini file" )
iniParser :: Parser CLICmd
iniParser = fmap CCMD_ini $ IniArgs <$>
(optional . strOption $ long "ini-path" <> help "Path to the input ini file" ) <*>
(optional . strOption $ long "toml-path" <> help "Path to the output .toml file")
convertConfigs :: Ini.GargConfig -> IniMail.MailConfig -> IniNLP.NLPConfig -> PGS.ConnectInfo -> Config.GargConfig
convertConfigs ini@(Ini.GargConfig { .. }) iniMail nlpConfig connInfo =
......
......@@ -46,7 +46,8 @@ data ImportArgs = ImportArgs
} deriving (Show, Eq)
data IniArgs = IniArgs
{ ini_path :: !FilePath
{ ini_path :: !(Maybe FilePath)
, toml_path :: !(Maybe FilePath)
} deriving (Show, Eq)
data InitArgs = InitArgs
......
......@@ -47,7 +47,7 @@ readConfig fp = do
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_keys = 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)
......
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