summaryrefslogtreecommitdiffhomepage
path: root/Parsers.hs
diff options
context:
space:
mode:
authorJose A Ortega Ruiz <jao@gnu.org>2010-02-14 20:15:44 +0100
committerJose A Ortega Ruiz <jao@gnu.org>2010-02-14 20:15:44 +0100
commit70fdae2a6c1846b254d115804b2e72ddbc018204 (patch)
tree88f25f4501d4987a7154f0a8b20f25ef72bed0cb /Parsers.hs
parentbcdf6f1ac74bc54d8f6b57c294d9bc9ad80a544e (diff)
downloadxmobar-70fdae2a6c1846b254d115804b2e72ddbc018204.tar.gz
xmobar-70fdae2a6c1846b254d115804b2e72ddbc018204.tar.bz2
Merge conflict resolutions in Parsers.hs and Batt.hs
Ignore-this: 12bf0ec7afc4ac855a69375ee1b3d163 darcs-hash:20100214191544-748be-68a449772d3eb68cc059bbeec955f81258c71d70.gz
Diffstat (limited to 'Parsers.hs')
-rw-r--r--Parsers.hs78
1 files changed, 51 insertions, 27 deletions
diff --git a/Parsers.hs b/Parsers.hs
index 80ad602..88b25f1 100644
--- a/Parsers.hs
+++ b/Parsers.hs
@@ -23,12 +23,6 @@ import Config
import Runnable
import Commands
-import Control.Monad.Writer(mapM_, ap, liftM, liftM2, MonadWriter, tell)
-import Control.Applicative.Permutation(optAtom, runPermsSep)
-import Control.Applicative(Applicative, (<*>), Alternative, empty, (<$), (<$>))
-import qualified Control.Applicative
-
-import Data.List(tails, find, inits)
import qualified Data.Map as Map
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Perm
@@ -111,8 +105,11 @@ allTillSep :: Config -> Parser String
allTillSep = many . noneOf . sepChar
stripComments :: String -> String
-stripComments = unlines . map (strip False) . lines
+stripComments = unlines . map (drop 5 . strip False . (replicate 5 ' '++)) . lines
where strip m ('-':'-':xs) = if m then "--" ++ strip m xs else ""
+ strip m ('\\':xss) = case xss of
+ '\\':xs -> '\\' : strip m xs
+ _ -> strip m $ drop 1 xss
strip m ('"':xs) = '"': strip (not m) xs
strip m (x:xs) = x : strip m xs
strip _ [] = []
@@ -122,22 +119,48 @@ stripComments = unlines . map (strip False) . lines
parseConfig :: String -> Either ParseError (Config,[String])
parseConfig = runParser parseConf fields "Config" . stripComments
where
- parseConf = parse $ do
- sepEndSpaces ["Config","{"]
- x <- unWrapParser perms
- wrapSkip (string "}")
+ parseConf = do
+ many space
+ sepEndSpc ["Config","{"]
+ x <- perms
eof
- return x
- perms = runPermsSep (WrappedParser $ wrapSkip $ string ",") $ liftM9 Config
- <$> withDef font "font" strField
- <*> withDef bgColor "bgColor" strField
- <*> withDef fgColor "fgColor" strField
- <*> withDef position "position" (field readsToParsec)
- <*> withDef lowerOnStart "lowerOnStart" (field parseEnum )
- <*> withDef commands "commands" (field readsToParsec)
- <*> withDef sepChar "sepChar" strField
- <*> withDef alignSep "alignSep" strField
- <*> withDef template "template" strField
+ s <- getState
+ return (x,s)
+
+ perms = permute $ Config
+ <$?> pFont <|?> pBgColor
+ <|?> pFgColor <|?> pPosition
+ <|?> pLowerOnStart <|?> pCommands
+ <|?> pSepChar <|?> pAlignSep
+ <|?> pTemplate
+
+ fields = [ "font", "bgColor", "fgColor", "sepChar", "alignSep"
+ , "template", "position", "lowerOnStart", "commands"]
+ pFont = strField font "font"
+ pBgColor = strField bgColor "bgColor"
+ pFgColor = strField fgColor "fgColor"
+ pSepChar = strField sepChar "sepChar"
+ pAlignSep = strField alignSep "alignSep"
+ pTemplate = strField template "template"
+
+ pPosition = field position "position" $ tillFieldEnd >>= read' "position"
+ pLowerOnStart = field lowerOnStart "lowerOnStart" $ tillFieldEnd >>= read' "lowerOnStart"
+ pCommands = field commands "commands" $ readCommands
+
+ staticPos = do string "Static"
+ wrapSkip (string "{")
+ p <- many (noneOf "}")
+ wrapSkip (string "}")
+ string ","
+ return ("Static {" ++ p ++ "}")
+ tillFieldEnd = staticPos <|> many (noneOf ",}\n\r")
+
+ commandsEnd = wrapSkip (string "]") >> oneOf "},"
+ readCommands = manyTill anyChar (try commandsEnd) >>= read' commandsErr . flip (++) "]"
+
+ strField e n = field e n . between (strDel "start" n) (strDel "end" n) . many $ noneOf "\"\n\r"
+ strDel t n = char '"' <?> strErr t n
+ strErr t n = "the " ++ t ++ " of the string field " ++ n ++ " - a double quote (\")."
wrapSkip x = many space >> x >>= \r -> many space >> return r
sepEndSpc = mapM_ (wrapSkip . try . string)
@@ -146,10 +169,11 @@ parseConfig = runParser parseConf fields "Config" . stripComments
updateState (filter (/= n)) >> sepEndSpc [n,"="] >>
wrapSkip c >>= \r -> fieldEnd >> return r
- withDef ext name parser = optAtom (do tell [name]; return $ ext defaultConfig)
- (liftM return $ WrappedParser $ parser name)
+ read' d s = case reads s of
+ [(x, _)] -> return x
+ _ -> fail $ "error reading the " ++ d ++ " field: " ++ s
- parseEnum = choice $ map (\x -> x <$ string (show x)) [minBound .. maxBound]
+commandsErr :: String
+commandsErr = "commands: this usually means that a command could not be parsed.\n" ++
+ "The error could be located at the begining of the command which follows the offending one."
- strField name = flip field name $ between (char '"') (char '"') (many1 . satisfy $ (/= '"'))
- field cont name = sepEndSpaces [name,"="] >> cont