
I don't know if this applies to Scheme parsing, but I find it's often
helpful to introduce a tokenizer into the parser to centralize the use
of "try" to one place::
type Token = String
tokRaw :: Parser Token
tokRaw = {- implement this yourself depending on language spec -}
tok :: Parser Token
tok = do
t <- tokRaw
many spaces
return t
-- wrap your outside parser with this; it gets the tokenizer
-- started because we only handle eating spaces after tokens,
-- not before
startParser :: Parser a -> Parser a
startParser a = many spaces >> a
sat :: (Token -> Maybe a) -> Parser a
sat f = try $ do
t <- tok
case f t of
Nothing -> mzero
Just a -> return a
lit :: Token -> Parser Token
lit s = sat (test s) > s where
test s t = if (s == t) then Just s else Nothing
Now if you replace uses of "string" and "char" in your code with
"lit", you avoid the problem of parses failing because they consumed
some input from the "wrong" token type before failing.
On 10/2/07, Alex Queiroz
Hallo,
On 10/2/07, Brandon S. Allbery KF8NH
wrote: Sorry, just woke up and still not quite tracking right, so I modified the wrong snippet of code. The trick is to wrap parseLeftList in a try, so the parser retries the next alternative when it fails.
Since "..." can only appear at the end of a list, I removed "..." from the possible symbols and added a new function:
parseThreeDottedList :: [SchDatum] -> Parser SchDatum parseThreeDottedList ls = do string "..." many parseAtmosphere char ')' return $ SchList $ ls ++ [SchSymbol "..."]
parseList :: Parser SchDatum parseList = do ls <- parseLeftList try (parseThreeDottedList ls) <|> (parseDottedList ls) <|> (parseProperList ls)
Thanks for the help.
Cheers, -- -alex http://www.ventonegro.org/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe