module System.Console.ConfigFile ( readFromFile ) where import System.Console.Command import System.Console.Internal (name) import Control.Applicative ((<$>)) import Control.Exception (tryJust) import Control.Monad (guard) import Data.List (isPrefixOf,concat) import Data.List.Split (Splitter,split,whenElt,keepDelimsR) import qualified Data.Map as Map import Data.Map (Map) import Data.Maybe (isJust) import qualified Data.Tree as Tree import qualified Fez.Data.Conf as Fez import System.Directory (getHomeDirectory) import System.IO.Error (isDoesNotExistError) type UserCommand = [String] readFromFile :: Commands -> UserCommand -> IO [String] readFromFile commands command = do home <- getHomeDirectory let configFile = '.' : name (Tree.rootLabel commands) fileContents <- either (const "") id <$> tryJust (guard . isDoesNotExistError) (readFile $ home ++ "/" ++ configFile) return $ Fez.parseToArgs . unlines $ filterSections command fileContents filterSections :: UserCommand -> String -> [String] filterSections c = concat . map snd . filter (flip isPrefixOf c . fst) . map parseSection . s . lines where s :: [String] -> [[String]] s = split $ keepDelimsR $ whenElt (isJust . header) header :: String -> Maybe [String] header ('[' : xs) = Just . words . takeWhile (/= ']') $ xs header _ = Nothing parseSection :: [String] -> ([String],[String]) parseSection (h : rest) = case header h of Just c -> (c,rest) Nothing -> ([],h : rest) parseSection [] = ([],[])