Skip to content

Instantly share code, notes, and snippets.

@SergeyStretovich
Created September 6, 2022 05:05
Show Gist options
  • Save SergeyStretovich/2ea1bd9d1e4dbf06234f48f82af21ca9 to your computer and use it in GitHub Desktop.
Save SergeyStretovich/2ea1bd9d1e4dbf06234f48f82af21ca9 to your computer and use it in GitHub Desktop.
ini files parsing with Parsec library in Haskell
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Text.Parsec
import Text.Parsec.Expr
import qualified Text.Parsec.Token as TT
import qualified Text.Parsec.Language as Lang
import Data.Char
import System.IO
type Parser a = Parsec String () a
type Entry = (String, String)
type Section = (String, [Entry])
type IniData = [Section]
ident::Parser String
ident = many1 (letter <|> digit <|> oneOf "_.,:(){}-#@&*|") >>= return . trim
value::Parser String
value = many (noneOf "\n") >>= return . trim
nameSep::Parser ()
nameSep = try $ do
space
notFollowedBy (char '(')
stringSpaces::Parser String
stringSpaces = many (char ' ' <|> char '\t')
inidata::Parser IniData
inidata = spaces >> many section >>= return
entry::Parser Entry
entry = do
k <- sepBy1 ident nameSep
stringSpaces
char '='
stringSpaces
v <- value
spaces
return ((unwords k), v)
section::Parser Section
section = do
char '['
name <- sepBy1 ident nameSep
char ']'
stringSpaces
char '\n'
spaces
el <- many entry
return ((unwords name), el)
trim :: String -> String
trim = f . f
where f = reverse . dropWhile isSpace
split delim = foldr f [[]]
where
f x rest@(r:rs)
| x == delim = [delim] : rest
| otherwise = (x : r) : rs
removeComments::String -> String
removeComments = foldr (++) [] . filter comment . split '\n'
where comment [] = False
comment (x:_) = (x /= ';') && (x /= '\n')
run_parser :: Parser a -> String -> a
run_parser p str = case parse p "" str of
Left err -> error $ "parse error at " ++ (show err)
Right val -> val
main :: IO ()
main = do
s <- readFile "C:\\Program Files (x86)\\Opera\\operaprefs_default.ini"
--parseTest inidata s
putStrLn $ unlines $ map show ( run_parser inidata s)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment