-- | Config.hs -- A module which parse config file and contain Config structure for -- further usage. module Config ( Config(..), Chan(..), Chans, readConfig ) where import Data.ConfigFile import System.Directory import qualified System.IO.UTF8 as U import Data.List import Control.Monad.Error -- | Config structure. data Config = Config { cusername :: String , cpassword :: String , cserver :: String , cthreads :: Integer , cversion :: String } deriving Show -- | Chan structure. data Chan = Chan { cname :: String , cengine :: String , curl :: String , ccookies :: String } deriving Show type Chans = [(String, Chan)] -- | Read config file in home directory and return conf structure. readConfig :: String -> IO (Config, Chans) readConfig filePath = do home <- getHomeDirectory file <- U.readFile (home++"/"++filePath) config <- runErrorT $ do conf <- readstring emptyCP file let param = get conf "main" parseChan' = parseChan conf -- returning (Config, Chans) liftM2 (,) -- Config (liftM Config (param "username") `ap` (param "password") `ap` (param "server") `ap` (liftM read $ param "threads") `ap` (param "version")) -- [(String, Chan)] (mapM parseChan' (filter (isPrefixOf "chan_") (sections conf))) case config of Left e -> error $ "Can't parse config file.\n"++show e Right conf -> return conf parseChan conf sect = liftM2 (,) (p "regexp") (liftM Chan (p "name") `ap` (p "engine") `ap` (p "url") `ap` (p "cookies")) where p = get conf sect