-- -- Config.hs -- Copyright (C) 2014 Ivan Cukic -- -- Distributed under terms of the GPLv3 license. -- {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE LambdaCase #-} module Config ( -- top level getConfig , Config(..) , BuildProfile(..) ) where import qualified ConfigParser as Parser import Data.Maybe as Maybe data Config = Config { sourceDir :: String , logDir :: String , availableProfiles :: [String] , getProfile :: String -> IO BuildProfile , makeOptions :: [String] } data BuildProfile = BuildProfile { profileName :: String , buildDir :: String , installDir :: Maybe String , cxxCompiler :: String , cCompiler :: String , cmakeOptionsRemove :: [String] , cmakeOptionsAdd :: [String] , projects :: [String] , overrideMakeCommand :: [String] } deriving (Show, Eq) -- | Reads the configuration files getConfig :: String -> String -> IO Config getConfig configFile extraConfigFile = do -- Parsing configs. We are producing fatal errors when parsing -- fails. There is no forgiving bad configs! mainConfig <- Parser.parseFile configFile |>< "Error parsing kdesrc-buildrc. Stopping." extraConfig <- Parser.parseFile extraConfigFile |>< "Error parsing kdesrc-build-exstrarc. Stopping." -- Now, getting the essential bits from the global section of -- the kdesrc-buildrc file. Again, any error is fatal. let globalSection = Parser.getGlobalSectionBody mainConfig >< "Can not find the global section" let getGlobalValue key = Parser.getValueFor key globalSection let getGlobalValues key = Parser.getValuesFor key globalSection let sourceDir = getGlobalValue "source-dir" >< "Can not find the source-dir specification" let logDir = getGlobalValue "log-dir" >< "You need to specify log-dir in the global section of kdesrc-buildrc file" let makeOptions = getGlobalValues "make-options" let availableProfiles = Parser.getSections "build-profile" extraConfig -- Function to return a specific build profile let getProfile :: String -> IO BuildProfile getProfile config = do let configSection = Parser.getSectionBody "build-profile" config extraConfig >< "Build configuration section is not present" let getValue key = Parser.getValueFor key configSection let getValues key = Parser.getValuesFor key configSection let profileName = config let buildDir = getValue "build-dir" >< "Build directory is not specified" let cxxCompiler = getValue "cxx-compiler" >< "C++ compiler is not specified" let cCompiler = getValue "c-compiler" >< "C compiler is not specified" let cmakeOptionsRemove = getValues "cmake-options-remove" let cmakeOptionsAdd = getValues "cmake-options-add" let projects = getValues "projects" let overrideMakeCommand = getValues "make-command" let installDir = getValue "install-dir" return BuildProfile { .. } return Config { .. } -- | Report an error if maybe is nothing (><) :: Maybe a -> String -> a (><) maybeA errorString = fromMaybe (error $ "Error: " ++ errorString) maybeA -- | Report an error if maybe is nothing (|><) :: IO (Maybe a) -> String -> IO a (|><) io errorString = do result <- io return $ result >< errorString