{-# LANGUAGE FlexibleContexts #-}
module Data.Ini.Reader.Internals where
import Control.Monad.Except
import Control.Monad.State
import qualified Data.ByteString as BS
import Text.Parsec as P
import Text.Parsec.String
import Data.Ini
import Data.Ini.Types
data IniReaderError
= IniParserError String
| IniSyntaxError String
| IniOtherError String
deriving (Eq, Show)
type IniParseResult = Either IniReaderError
data IniFile
= SectionL String
| OptionL String String
| OptionContL String
| CommentL
deriving (Show, Eq)
buildConfig :: [IniFile] -> IniParseResult Config
buildConfig ifs = let
isComment CommentL = True
isComment _ = False
fIfs = filter (not . isComment) ifs
mergeOptions [] = return []
mergeOptions (s@(SectionL _) : ifs) = (s :) `liftM` mergeOptions ifs
mergeOptions (CommentL : ifs ) = (CommentL :) `liftM` mergeOptions ifs
mergeOptions (OptionL on ov : OptionContL ov2 : ifs) = mergeOptions $ (OptionL on (ov ++ ov2)) : ifs
mergeOptions (o@(OptionL on ov) : ifs) = (o :) `liftM` mergeOptions ifs
mergeOptions _ = throwError $ IniSyntaxError "Syntax error in INI file."
buildit a [] = return a
buildit a (SectionL sn : is) = put sn >> buildit a is
buildit a (OptionL on ov : is) = do
sn <- get
let na = setOption sn on ov a
buildit na is
in mergeOptions fIfs >>= (\ is -> return . fst $ runState (buildit emptyConfig is) "default")
eatWhiteSpace :: Parser String
eatWhiteSpace = many $ oneOf " \t"
secParser :: Parser IniFile
secParser = let
validSecNameChrs = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ "._-/@\" "
in do
char '['
eatWhiteSpace
sn <- many1 $ oneOf validSecNameChrs
eatWhiteSpace
char ']'
manyTill anyChar newline
return $ SectionL sn
optLineParser :: Parser IniFile
optLineParser = let
validOptNameChrs = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ "_-/@"
in do
on <- many1 $ oneOf validOptNameChrs
eatWhiteSpace
char '='
eatWhiteSpace
ov <- manyTill anyChar newline
return $ OptionL on ov
optContParser :: Parser IniFile
optContParser = do
oneOf " \t"
eatWhiteSpace
oc <- noneOf " \t"
ov <- manyTill anyChar newline
return $ OptionContL $ oc:ov
noiseParser :: Parser IniFile
noiseParser = let
commentP = do
oneOf "#;"
manyTill anyChar newline
emptyL = newline >> return ""
in choice [commentP, emptyL] >> return CommentL
iniParser :: Parser [IniFile]
iniParser =
many $ choice [secParser, optLineParser, optContParser, noiseParser]