
Hello Cafe, I am trying to write a parser for propositional logic[1]. It's working fine for every input except equivalence ( <=> ). *Main> calculator "a=>b" Imp (Lit 'a') (Lit 'b') *Main> calculator "a<=b" Red (Lit 'a') (Lit 'b') *Main> calculator "a<=>b" *** Exception: failed to parse I think, the reason is parser taking equivalence ( <=> ) as reduction ( <= ) and next character is '>' so it is parse error . If I remove both implication and reduction then equivalence is working fine. *Main> calculator "a<=>b" Eqi (Lit 'a') (Lit 'b') Could some please tell me how to solve this problem. I also tried fixity declaration but got this error LogicPraser.hs:12:10: The fixity signature for `<=>' lacks an accompanying binding -Mukesh Tiwari [1] http://logic.stanford.edu/classes/cs157/2010/notes/chap02.html {-# LANGUAGE NoMonomorphismRestriction #-} import Text.Parsec.Token import Text.Parsec.Prim import Text.Parsec.Char import Text.Parsec.Expr import Text.Parsec.Combinator import Text.Parsec.Language import Control.Applicative hiding ( ( <|> ) , many ) import Data.Maybe ( fromJust ) --infixl 9 <=> data LExpr = Lit Char | Not LExpr | And LExpr LExpr | Or LExpr LExpr | Imp LExpr LExpr -- (=>) | Red LExpr LExpr -- ( <= ) | Eqi LExpr LExpr -- ( <=> ) deriving Show exprCal = buildExpressionParser table atom table = [ [ Prefix ( Not <$ string "~" ) ] , [ Infix ( And <$ string "&" ) AssocLeft ] , [ Infix ( Or <$ string "|" ) AssocLeft ] , [ Infix ( Imp <$ string "=>" ) AssocLeft , Infix ( Red <$ string "<=" ) AssocLeft , Infix ( Eqi <$ string "<=>" ) AssocLeft ] ] atom = char '(' *> exprCal <* char ')' <|> ( Lit <$> letter ) calculator :: String -> LExpr calculator expr = case parse exprCal "" expr of Left msg -> error "failed to parse" Right ( val ) -> val ~

On 11/01/14 19:12, mukesh tiwari wrote:
Hello Cafe, I am trying to write a parser for propositional logic[1]. It's working fine for every input except equivalence ( <=> ).
*Main> calculator "a=>b" Imp (Lit 'a') (Lit 'b') *Main> calculator "a<=b" Red (Lit 'a') (Lit 'b') *Main> calculator "a<=>b" *** Exception: failed to parse
I think, the reason is parser taking equivalence ( <=> ) as reduction ( <= ) and next character is '>' so it is parse error . If I remove both implication and reduction then equivalence is working fine.
*Main> calculator "a<=>b" Eqi (Lit 'a') (Lit 'b')
Could some please tell me how to solve this problem. I also tried fixity declaration but got this error LogicPraser.hs:12:10: The fixity signature for `<=>' lacks an accompanying binding
-Mukesh Tiwari
[1] http://logic.stanford.edu/classes/cs157/2010/notes/chap02.html [snip]
Hi, I have not studied your code but if the problem is what you describe it, you should try with back-tracking so that the parser can retry when it fails. I believe Parsec offers the ‘try’ function for this. Regarding your ‘infix <=>’, of course that would not work. It's a Haskell declaration, not something Parsec does. You're getting an error because you're saying that ‘<=>’ has left fixity of 9 but then you aren't giving a definition for ‘<=>’. The "<=>" you're parsing has nothing to do with this. Haskell sees the fixity declaration and then doesn't see you defining the ‘<=>’ operator anywhere so it complains. -- Mateusz K.

Hi Mateusz,
Thank you. Now it's working fine by using 'try' function.
-Mukesh Tiwari
On Sun, Jan 12, 2014 at 1:02 AM, Mateusz Kowalczyk
On 11/01/14 19:12, mukesh tiwari wrote:
Hello Cafe, I am trying to write a parser for propositional logic[1]. It's working fine for every input except equivalence ( <=> ).
*Main> calculator "a=>b" Imp (Lit 'a') (Lit 'b') *Main> calculator "a<=b" Red (Lit 'a') (Lit 'b') *Main> calculator "a<=>b" *** Exception: failed to parse
I think, the reason is parser taking equivalence ( <=> ) as reduction ( <= ) and next character is '>' so it is parse error . If I remove both implication and reduction then equivalence is working fine.
*Main> calculator "a<=>b" Eqi (Lit 'a') (Lit 'b')
Could some please tell me how to solve this problem. I also tried fixity declaration but got this error LogicPraser.hs:12:10: The fixity signature for `<=>' lacks an accompanying binding
-Mukesh Tiwari
[1] http://logic.stanford.edu/classes/cs157/2010/notes/chap02.html [snip]
Hi,
I have not studied your code but if the problem is what you describe it, you should try with back-tracking so that the parser can retry when it fails. I believe Parsec offers the ‘try’ function for this.
Regarding your ‘infix <=>’, of course that would not work. It's a Haskell declaration, not something Parsec does.
You're getting an error because you're saying that ‘<=>’ has left fixity of 9 but then you aren't giving a definition for ‘<=>’. The "<=>" you're parsing has nothing to do with this. Haskell sees the fixity declaration and then doesn't see you defining the ‘<=>’ operator anywhere so it complains.
-- Mateusz K. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 11 January 2014 11:12, mukesh tiwari
table = [ [ Prefix ( Not <$ string "~" ) ] , [ Infix ( And <$ string "&" ) AssocLeft ] , [ Infix ( Or <$ string "|" ) AssocLeft ] , [ Infix ( Imp <$ string "=>" ) AssocLeft , Infix ( Red <$ string "<=" ) AssocLeft , Infix ( Eqi <$ string "<=>" ) AssocLeft
Have you tried changing the order here? I would expect the "<=>" check to have to come before the "<=" check? I haven't played with this so I'm just guessing.

On 1/11/2014 2:42 PM, Hilco Wijbenga wrote:
On 11 January 2014 11:12, mukesh tiwari
wrote: table = [ [ Prefix ( Not <$ string "~" ) ] , [ Infix ( And <$ string "&" ) AssocLeft ] , [ Infix ( Or <$ string "|" ) AssocLeft ] , [ Infix ( Imp <$ string "=>" ) AssocLeft , Infix ( Red <$ string "<=" ) AssocLeft , Infix ( Eqi <$ string "<=>" ) AssocLeft Have you tried changing the order here? I would expect the "<=>" check to have to come before the "<=" check? I haven't played with this so I'm just guessing.
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe This would have the same problem, in the other direction. Parsing "a<=b" would get to "<", start matching against "<=>", then find "b" instead of ">" and fail again.
participants (4)
-
Hilco Wijbenga
-
Joe Quinn
-
Mateusz Kowalczyk
-
mukesh tiwari