
Hi all, I'm using the Parsec library to parse the following grammar expr = atom+ atom = integer | var | (expr) The input to the parser is a list of (Token, SourcePos). I have the following code for atom: atom = try variable <|> try integerr <|> do{sat(== Reserved "("); (e,pos) <- expression; sat(==Reserved ")"); return (e,pos)} sat p = do (t,pos) <- item if p t then return(t,pos) else pzero When I run the code on the input "(_ineg_ 0)" the parser fails, but removing sat(==Reserved ")") and it succeeds. Can any one see why? E.

Am Donnerstag, 26. Juni 2008 12:40 schrieb Eric:
Hi all,
I'm using the Parsec library to parse the following grammar
expr = atom+ atom = integer | var | (expr)
The input to the parser is a list of (Token, SourcePos). I have the following code for atom:
atom = try variable <|> try integerr <|> do{sat(== Reserved "("); (e,pos) <- expression; sat(==Reserved ")"); return (e,pos)}
sat p = do (t,pos) <- item if p t then return(t,pos) else pzero
When I run the code on the input "(_ineg_ 0)" the parser fails, but removing
sat(==Reserved ")")
and it succeeds. Can any one see why?
E.
What does the tokeniser return? I would have to see more of the code to diagnose it. Cheers, Daniel

Daniel Fischer wrote:
Am Donnerstag, 26. Juni 2008 12:40 schrieb Eric:
What does the tokeniser return? I would have to see more of the code to diagnose it.
Here is the code for the tokenizer: type Scanner a = GenParser Char () a data Token = INum Integer | FNum Double | Varid String | Reserved String deriving (Show,Eq) scan :: Scanner a -> Scanner(a, SourcePos) scan p = do pos <- getPosition x <- p return(x,pos) scan_integer, scan_varid, hreserved, htoken :: Scanner (Token,SourcePos) scan_integer = do (i,pos) <- scan(integer (makeTokenParser haskellDef)) return (INum i, pos) scan_varid = do (c,pos) <- scan(hlower) cs <- identifier(makeTokenParser haskellDef) return (Varid (c:cs), pos) hlower :: Scanner Char hlower = lower <|> char '_' hreserved = do (cs, pos) <- scan(string "(" <|> string ")") return (Reserved cs,pos) htoken = scan_integer <|> scan_varid <|> hreserved scanall :: String -> [(Token,SourcePos)] scanall cs = let result = parse (many htoken) "" cs in case result of Right tkns -> tkns Left err -> error (show err) E.

Am Donnerstag, 26. Juni 2008 12:40 schrieb Eric:
Hi all,
I'm using the Parsec library to parse the following grammar
expr = atom+ atom = integer | var | (expr)
The input to the parser is a list of (Token, SourcePos). I have the following code for atom:
atom = try variable <|> try integerr <|> do{sat(== Reserved "("); (e,pos) <- expression; sat(==Reserved ")"); return (e,pos)}
sat p = do (t,pos) <- item if p t then return(t,pos) else pzero
When I run the code on the input "(_ineg_ 0)" the parser fails, but removing
sat(==Reserved ")")
and it succeeds. Can any one see why?
E.
I can't be absolutely sure without seeing your code for item and expression, possibly also variable and integerr, but I'm rather sure it's a case of a missing 'try'. I'd expect 'expression' using something like many1 atom , then when parsing the tokens of "(_ineg_ 0)", which, ignoring the SourcePos are [Reserved "(", Varid "_ineg_", INum 0, Reserved ")"], as it should be, variable and integerr fail, so the third branch is entered, sat (== Reserved "(") succeeds, the Varid and INum are parsed and finally only [Reserved ")"] is left over, on which atom is tried again. variable and integerr again fail gracefully, so sat (== Reserved "(") is tried on it, which fails, but unfortunately not gracefully, because item returns (Consumed _) and thus the overall failure consumes. Because of that, many1 atom fails and the overall parse fails. Can't be exactly that, though because then removing sat (== Reserved ")") shouldn't help. Anyway, I need at least the failure message, better the complete code, to diagnose. Cheers, Daniel

Daniel Fischer wrote:
Can't be exactly that, though because then removing sat (== Reserved ")") shouldn't help. Anyway, I need at least the failure message, better the complete code, to diagnose.
I've attached the complete code.
E. Thanks, though a plaintext file would've been better. It's pretty much what I came up with myself, the odd thing is that I can't reproduce your behaviour, whether sat (== Reserved ")") is present or not doesn't make a difference. Which version of GHC and parsec are you using? (I
Am Donnerstag, 26. Juni 2008 23:22 schrieb Eric: tried with 6.8.3 & parsec-2.1.0.1, 6.8.2 & parsec-2.1.0.0 and 6.6.1 & parsec-2.0, all give the same results, *Eric2> parseall . scanall $ "(_ineg_ 0)" *** Exception: (line 1, column 1):unknown parse error with or without the second sat). However, the problem is indeed that upon failure (sat p) returns a Consumed value (and removes the token from the input), make it sat p = try $ do (t,pos) <- item if p t then return (t,pos) else pzero and you're all set (you don't need the try's in atom, then). Cheers, Daniel
participants (2)
-
Daniel Fischer
-
Eric