{- Functions to handle the hashell configuration file. Copyright (C) 2005, 2008 Luis Francisco Araujo -} module ConfigFile where import Environment (getEnvVariable) import System.Posix.Files (fileExist) {- | Read and parse configuration file. -} ---------------------------------------------------------------------------------- -- | Take a filepath and return all the -- information in a list of tuples in the form -- of (Variable , Value). globalConfig :: [FilePath] -> IO [(String,String)] globalConfig [] = do home <- getEnvVariable "HOME" let cfg = (home ++ "/.hashell_config") fileExist cfg >>= \ s -> case s of True -> readConfig cfg >>= makeVarValTuples False -> return [] globalConfig (cfg:_) = readConfig cfg >>= makeVarValTuples -- | Read and filter comments from file. -- Return each line of the configuration file -- inside a list as strings. readConfig :: FilePath -> IO [String] readConfig = (return . filterComment . lines =<<) . readFile ---------------------------------------------------------------------------------- -- | Filter all the comments lines. filterComment :: [String] -> [String] filterComment [] = [] filterComment (('-':_):xss) = filterComment xss filterComment ([]:xss) = filterComment xss filterComment ((' ':_):xss) = filterComment xss filterComment (xs:xss) = xs : filterComment xss -- | Make a list of (Variables, Values) out of -- the list containing the configuration file information. makeVarValTuples :: [String] -> IO [(String,String)] makeVarValTuples xs = return [ (v,r) | x <- xs , let (v,(_:r)) = break (== ' ') x ]