{-# LANGUAGE Safe #-}
module Config.LoadConfig (
localConfigPath,
loadConfig,
) where
import Control.Monad (when)
import Control.Monad.IO.Class
import System.Directory
import Base.CompileError
import Config.LocalConfig
import Paths_zeolite_lang (getDataFileName)
loadConfig :: (MonadIO m, CompileErrorM m) => m (Resolver,Backend)
loadConfig = do
configFile <- liftIO localConfigPath
isFile <- liftIO $ doesFileExist configFile
when (not isFile) $ compileErrorM "Zeolite has not been configured. Please run zeolite-setup."
configString <- liftIO $ readFile configFile
lc <- check $ (reads configString :: [(LocalConfig,String)])
pathsFile <- liftIO $ globalPathsPath
pathsExists <- liftIO $ doesFileExist pathsFile
paths <- if pathsExists
then liftIO $ readFile pathsFile >>= return . lines
else return []
return (addPaths (lcResolver lc) paths,lcBackend lc) where
check [(cm,"")] = return cm
check [(cm,"\n")] = return cm
check _ = compileErrorM "Zeolite configuration is corrupt. Please rerun zeolite-setup."
localConfigPath :: IO FilePath
localConfigPath = getDataFileName localConfigFilename >>= canonicalizePath
localConfigFilename :: FilePath
localConfigFilename = ".local-config"
globalPathsFilename :: FilePath
globalPathsFilename = "global-paths"
globalPathsPath :: IO FilePath
globalPathsPath = getDataFileName globalPathsFilename >>= canonicalizePath
addPaths :: Resolver -> [FilePath] -> Resolver
addPaths (SimpleResolver ls ps) ps2 = SimpleResolver ls (ps ++ ps2)