module Data.Ini.Config.Raw
(
RawIni(..)
, IniSection(..)
, IniValue(..)
, BlankLine(..)
, NormalizedText(..)
, normalize
, parseRawIni
, printRawIni
, lookupInSection
, lookupSection
, lookupValue
) where
import Control.Monad (void)
import qualified Data.Foldable as F
import Data.Monoid ((<>))
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as LazyText
import qualified Data.Text.Lazy.Builder as Builder
import Data.Void (Void)
import Text.Megaparsec
import Text.Megaparsec.Char
type Parser = Parsec Void Text
data NormalizedText = NormalizedText
{ actualText :: Text
, normalizedText :: Text
} deriving (Show)
normalize :: Text -> NormalizedText
normalize t = NormalizedText t (T.toLower (T.strip t))
instance Eq NormalizedText where
NormalizedText _ x == NormalizedText _ y =
x == y
instance Ord NormalizedText where
NormalizedText _ x `compare` NormalizedText _ y =
x `compare` y
newtype RawIni = RawIni
{ fromRawIni :: Seq (NormalizedText, IniSection)
} deriving (Eq, Show)
data IniSection = IniSection
{ isName :: Text
, isVals :: Seq (NormalizedText, IniValue)
, isStartLine :: Int
, isEndLine :: Int
, isComments :: Seq BlankLine
} deriving (Eq, Show)
data IniValue = IniValue
{ vLineNo :: Int
, vName :: Text
, vValue :: Text
, vComments :: Seq BlankLine
, vCommentedOut :: Bool
, vDelimiter :: Char
} deriving (Eq, Show)
data BlankLine
= CommentLine Char Text
| BlankLine
deriving (Eq, Show)
parseRawIni :: Text -> Either String RawIni
parseRawIni t = case runParser pIni "ini file" t of
Left err -> Left (errorBundlePretty err)
Right v -> Right v
pIni :: Parser RawIni
pIni = do
leading <- sBlanks
pSections leading Seq.empty
sBlanks :: Parser (Seq BlankLine)
sBlanks = Seq.fromList <$> many ((BlankLine <$ void eol) <|> sComment)
sComment :: Parser BlankLine
sComment = do
c <- oneOf ";#"
txt <- T.pack `fmap` manyTill anySingle eol
return (CommentLine c txt)
pSections :: Seq BlankLine -> Seq (NormalizedText, IniSection) -> Parser RawIni
pSections leading prevs =
pSection leading prevs <|> (RawIni prevs <$ void eof)
pSection :: Seq BlankLine -> Seq (NormalizedText, IniSection) -> Parser RawIni
pSection leading prevs = do
start <- getCurrentLine
void (char '[')
name <- T.pack `fmap` some (noneOf "[]")
void (char ']')
void eol
comments <- sBlanks
pPairs (T.strip name) start leading prevs comments Seq.empty
pPairs :: Text
-> Int
-> Seq BlankLine
-> Seq (NormalizedText, IniSection)
-> Seq BlankLine
-> Seq (NormalizedText, IniValue)
-> Parser RawIni
pPairs name start leading prevs comments pairs = newPair <|> finishedSection
where
newPair = do
(n, pair) <- pPair comments
rs <- sBlanks
pPairs name start leading prevs rs (pairs Seq.|> (n, pair))
finishedSection = do
end <- getCurrentLine
let newSection = IniSection
{ isName = name
, isVals = pairs
, isStartLine = start
, isEndLine = end
, isComments = leading
}
pSections comments (prevs Seq.|> (normalize name, newSection))
pPair :: Seq BlankLine -> Parser (NormalizedText, IniValue)
pPair leading = do
pos <- getCurrentLine
key <- T.pack `fmap` some (noneOf "[]=:")
delim <- oneOf ":="
val <- T.pack `fmap` manyTill anySingle eol
return ( normalize key
, IniValue
{ vLineNo = pos
, vName = key
, vValue = val
, vComments = leading
, vCommentedOut = False
, vDelimiter = delim
} )
getCurrentLine :: Parser Int
getCurrentLine = (fromIntegral . unPos . sourceLine) `fmap` getSourcePos
printRawIni :: RawIni -> Text
printRawIni = LazyText.toStrict . Builder.toLazyText . F.foldMap build . fromRawIni
where
build (_, ini) =
F.foldMap buildComment (isComments ini) <>
Builder.singleton '[' <>
Builder.fromText (isName ini) <>
Builder.fromString "]\n" <>
F.foldMap buildKV (isVals ini)
buildComment BlankLine = Builder.singleton '\n'
buildComment (CommentLine c txt) =
Builder.singleton c <> Builder.fromText txt <> Builder.singleton '\n'
buildKV (_, val) =
F.foldMap buildComment (vComments val) <>
(if vCommentedOut val then Builder.fromString "# " else mempty) <>
Builder.fromText (vName val) <>
Builder.singleton (vDelimiter val) <>
Builder.fromText (vValue val) <>
Builder.singleton '\n'
lookupInSection :: Text
-> Text
-> RawIni
-> Seq.Seq Text
lookupInSection sec opt ini =
vValue <$> (F.asum (lookupValue opt <$> lookupSection sec ini))
lookupSection :: Text
-> RawIni
-> Seq.Seq IniSection
lookupSection name ini =
snd <$> (Seq.filter ((== normalize name) . fst) $ fromRawIni ini)
lookupValue :: Text
-> IniSection
-> Seq.Seq IniValue
lookupValue name section =
snd <$> Seq.filter ((== normalize name) . fst) (isVals section)