Parsec not consuming all Input? - haskell

I'am writing some code to parse commands from the Simple Imperative Language defined in
Theory of Programming Languages (Reynolds, 1998).
I have a lexer module that given a string extracts the tokens from it if it's a valid language expression and then I pass that list of tokens to the parser which should build an internal representation of the command (defined as an algebraic data type).
These are my Tokens:
--Tokens for the parser
data Token = Kw Keyword
| Num Int
| Op Operator
| Str String
| Sym Symbol
deriving Show
I'm having trouble with binary operators. I'll put as an example the sum, but it happens the same with all of them, either boolean or integers.
For example if I'd run the program parse "x:=2+3"
I should get the following list of tokens from the lexer
[Str "x", Op Colon, Op Equal, Num 2, OP, Plus, Num 3]
which is actually what I'm getting.
But then the parser should return the command
Assign "x" (Ibin Plus (Const 2) (Const 3)
which is the correct representation of the command. But instead of that I'm getting the following representation:
Assign "x" (Const 2)
I guess that I screwed it at some point in the pIntExpr function because the variable identifier and the := of the assignment are parsed OK and it's not parsing the last elements. Here are the relevant parsers for this example, to see if someone can orientate me in what I'm doing wrong.
-- Integer expressions
data IntExpr = Const Int
| Var Iden --Iden=String
| Neg IntExpr
| IBin OpInt IntExpr IntExpr
deriving Show
type TParser = Parsec [Token] ()
--Internal representation of the commands
data Comm = Skip
| Assign Iden IntExpr
| If Assert Comm Comm
| Seq Comm Comm
| While Assert Comm
| Newvar Iden IntExpr Comm
deriving Show
--Parser for non sequential commands
pComm' :: TParser Comm
pComm' = choice [pif,pskip,pAssign,pwhile,pNewVar]
--Parser for the assignment command
pAssign :: TParser Comm
pAssign = do v <- pvar
_ <- silentOp Colon
_ <- silentOp Equal
e <- pIntExp
return $ Assign v e
-- Integer expressions parser
pIntExp :: TParser IntExpr
pIntExp = choice [ var' --An intexp is either a variable
, num --Or a numeric constant
, pMul --Or <intexp>x<intexp>
, pSum --Or <intexp>+<intexp>
, pRes --Or <intexp>-<intexp>
, pDiv --Division
, pMod --Modulus
, pNeg --Unary "-"
]
-- Parser for <intexp>+<intexp>
pSum :: TParser IntExpr
pSum = do
e <- pIntExp
_ <- silentOp Lexer.Plus
e' <- pIntExp
return $ IBin Lang.Plus e e'
UPDATE TAKING INTO ACCOUNT AndrewC's ANSWER
Unfortunately moving the var' parser down in the choice list didn't work, it yields the same result. But I took AndrewC's answer into account and tried to "manually" trace the execution (I'm not familiar with ghci's debugger and ended up doing lot of single steps and got lost eventually).
This is how I reason it:
I got this token list from the lexer:
[Str "x", Op Colon, Op Equal, Num 2, OP Plus, Num 3]
So, the pComm' parser fails with pif and pskip, but succeds with pAssign, consuming Str "x", Op Colon and Op Equal and trying to parse
[Num 2, OP Plus, Num 3] with pIntExp (!!)
The pIntExp parser then tries the var' parser and fails, but succeds with the num parser consuming the Num 2 token and therefore returning the erroneous result Assign "x" (Const 2).
So with AndrewC's advice in mind about choice, I moved num parser down in the list too. For the sake of simplicity I'll consider pIntExp as
choice [pSum, num, var´] that it's what's relevant for this particular example.
The first part of the reasoning remains the same. So I'll restart from (!!) where we had
[Num 2, Op Plus, Num 3] to be parsed by pIntExp
pIntExp tries now first with pSum, which in turn "calls" pIntExp again,
which will try pSum again, and so the program hangs. I tried it and it indeed hangs and never ends.
So I was wondering if there's a form to make the pSum parser "lookahead" for the Op Plus token and then parse the corresponding expressions?
UPDATE 2: After "googling" a little bit more now that I've identified the problem I found that the combinational parsers chainl1 and/or chainl might be just what I need.
I'll be playing with these and if I work it out post the solution

The choice function tries the parser it's given in the order they are in the list.
Since yoiur parser for variables appears before your parser for the more complicated addition expression, it suceeds before the other is tried.
To solve this problem, put the variable parser after any expressions that start with a variable (and think through any other substring-matching issues when using choice.
Similar problems incude 3 - 4 + 1 evaluating to -2. People expect left association in the absence of other priorities (so sum - term instead of term - sum).
You also might not want 1 + 10 * 5 to eveluate to 55, so you'll have to be careful around + and * etc if you want to implement operator precedence. You can achieve this by parsing an expression made up of multiplication as a term and then an additive expression as a sum of terms.

Related

How to do a Read instance for a simple custom format of data

I'm trying to use a short and easy to read format to show and read my data, and I would like that it could be used from the Haskell interpreter, in order to write hand or copy-paste inputs while I try new functions.
My data is a list of Int numbers, each one with an boolean property, that I associate with + and -, being the first one the default, so it doesn't need explicit representation (as with usual sign). I would like to represent the - after the number, like in this example:
[2, 5-, 4, 0-, 1, 6-, 2-]
Note that I can not use the usual sign because I need to be able of assigning - to 0, so that 0- is different than 0 (also, may be in the future I will need to use negative numbers, like in [-4-, -2]).
I did the easy part, which is to define the data type for the terms of the list and implement the show function.
data Term = T Int Bool deriving (Eq)
instance Show Term where
show (T v True) = show v
show (T v False) = show v ++ "-"
What I don't know is how to do the corresponding read function, or whether I cannot use the - sign, because it is a sign of the Haskell language. Suggestions are welcome.
Try something like this:
instance Read Term where
readsPrec n s = do
(i,rest) <- readsPrec (n+1) s -- read `i :: Int`
return $ case rest of -- look at the rest of the string
('-':rest') -> (T i False, rest') -- if it starts with '-'...
rest' -> (T i True, rest') -- if it doesn't...
Read in Haskell follows closely the idea that a parser can be represented by the type String -> [(a, String)] (this type is given the type synonym ReadS. To familiarize yourself with this idea of parsing, I recommend the reading the following functional pearl on monadic parsing.
Then, from GHCi:
ghci> read "[2, 5-, 4, 0-, 1, 6-, 2-]" :: [Term]
[2,5-,4,0-,1,6-,2-]
I like very much the answer of Alec, which I accepted. But after reading, thinking and trying, I reached another quite simple solution, that I would like to share here.
It uses reads instead of readsPrec because the Term constructor is not infix, so we don't need to manage precedence, and it is not monadic.
instance Read Term where
readsPrec _ s =
[(T v False, rest) | (v, '-' : rest) <- reads s] ++
[(T v True , rest) | (v, rest) <- reads s]
The symmetry with the corresponding Show instance is notable:
instance Show Term where
show (T v True) = show v
show (T v False) = show v ++ "-"

Haskell Type Misunderstanding assigning variables

Complete noob to haskell here, i'm trying to make this following piece of code work:
It's intent is to take the first exp elements of a list, concatenate them, then call the same function again.
order ( i ) (l1)(l2) =
do exp <- (2 ^ i)
l <- (take exp l1) ++ (take exp l2 ) ++ (order (i+1) (drop exp l1) (drop exp l2));
return l
I'm sure this is far from idiomatic haskell, but you have to start some where though.
The error I am getting is on the
exp <- (2 ^ i )
saying that
No instance for (Num [Int])
arising from a use of `^'
Possible fix: add an instance declaration for (Num [Int])
which i am really unsure what this exactly means. Isn't both 2 and i integers, and then applying the exponentiation function will result in an integer?
Thanks!
I've rewritten your code as follows and added a main.
order _ [] [] = []
order i l1 l2 =
(take exp l1) ++ (take exp l2)
++ (order (i+1) (drop exp l1) (drop exp l2))
where
exp = 2^i
main = print $ order 1 [1,2,3,4] [3,4,5,6]
The first mistake you make is that your recursion doesn't terminate as order will always call itself again. The second mistake is in the use of do, this introduces a monad and considering you are new to Haskell, I would stay clear a bit. Use it only for I/O for now.
I hope this helps.
P.S: The error message you are getting is saying that a list of Int is used in a numeric way and there is no default implementation for that. This is probably caused by the do where the monad is over lists, but I'll leave it to cracks in Haskell to give an exact explanation.
All statements in a do block must belong to the same monad. This includes the right hand side of <- bindings. Therefore, because the right hand side of the second statement take exp l1 ++ ... is a list, the compiler infers that the type of 2^i must be a list as well.
This is because <- does more than just assign variables. In the case of the list monad, it sequentially binds the variable on the left to each element of the list on the right.
If you just want to bind a variable without any additional effects in a do block, you should use a let binding instead of <-.
do let exp = 2^i
l <- take exp l1 ++ ...
return l
That said, the use of do notation here is redundant. The monad laws guarantee that do x <- m; return x is the same as just m, so you can just write it directly as
order i l1 l2 = take exp l1 ++ ...
where exp = 2^i
In addition to Bryan's points, I think I can help explain the reason you got that specific error.
The big reason is that exp <- 2 ^ i in a do block does not mean "let exp be a name for the value of 2 ^ i" (You would express that meaning in a do block as let exp = 2 ^ i, but a do block isn't really what you want here anyway).
What exp <- 2 ^ i means is "let exp be a name for a value yielded by the monadic value 2 ^ i". Try reading the <- as "comes from" rather than "is". What exactly "comes from" means depends on the monad involved. So for this line to mean something, 2 ^ i must be a value in some kind of monad. Specifically, it's type is something like Monad m => m a, for unknown m and a.
Because the ^ operator works on numeric values, it returns something of type Num a => a. So that allows us to figure out that 2 ^ i should be something of type (Monad m, Num (m a)) => m a, for unknown m and a.
exp is extracted from this mystery m a, so it is of type a. The next line includes expressions like take exp l1. take requires its first argument to be of type Int, and so exp must be of type Int, and so we can tell that that unknown a we were working with must be Int. So 2 ^ i is now known to be of type (Monad m, Num (m Int)) => m Int; it is some sort of monadic integer.
In this line you also have l <- (take exp l1) ++ .... So l also "comes from" some sort of monadic value. The right hand side can be seen to be some sort of list (due to the use of ++, take, and drop). The monad involved in a do block must be the same throughout, and the list type constructor is indeed a monad. So if (take exp l1) ++ ... is a list of something, then 2 ^ i must also be a list of something.
So now we have 2 ^ i being of type [Int] (we originally knew it was m a; the m is the list type constructor [], and the a is Int). But we also know (from the use of the ^ operator) that it must be a member of the Num type class. There is no instance of Num for [Int], which is exactly the error you got.
That's just one of many inconsistencies that can be derived from the code you wrote; it's just the first one that GHC happened to encounter while trying to analyse it.

Why does only the first defined infix operator parse when using Parsec's buildExpressionParser?

I'm trying to write a parser for the propositional calculus using Parsec. The parser uses the buildExpressionParser function from Text.Parsec.Expr. Here's the code where I define the logical operators.
operators = [ [Prefix (string "~" >> return Negation)]
, [binary "&" Conjunction]
, [binary "|" Disjunction]
, [binary "->" Conditional]
, [binary "<->" Biconditional]
]
binary n c = Infix (spaces >> string n >> spaces >> return c) AssocRight
expr = buildExpressionParser operators term
<?> "compound expression"
I've omitted the parsers for variables, terms and parenthesised expressions, but if you think they may be relevant to the problem you can read the full source for the parser.
The parser succeeds for expressions which use only negation and conjunction, i.e. the only prefix operator and the first infix operator.
*Data.Logic.Propositional.Parser2> runPT expr () "" "p & ~q"
Right (p ∧ ¬q)
Expressions using any other operators fail on the first character of the operator, with an error like the following:
*Data.Logic.Propositional.Parser2> runPT expr () "" "p | q"
Left (line 1, column 3):
unexpected "|"
expecting space or "&"
If I comment out the line defining the parser for conjunctions, then the parser for disjunction will work (but the rest will still fail). Putting them all into a single list (i.e. of the same precedence) doesn't work either: the same problem still manifests itself.
Can anyone point out what I'm doing wrong? Many thanks.
Thanks to Daniel Fischer for such a prompt and helpful answer.
In order to finish making this parser work correctly, I also needed to handle repeated applications of the negation symbol, so that e.g. ~~p would parse correctly. This SO answer showed me how to do it, and the change I made to the parser can be found here.
Your problem is that
binary n c = Infix (spaces >> string n >> spaces >> return c) AssocRight
the first tried infix operator consumes a space before it fails, so the later possibilities are not tried. (Parsec favours consuming parsers, and <|> only tries to run the second parser if the first failed without consuming any input.)
To have the other infix operators tried if the first fails, you could either wrap the binary parsers in a try
binary n c = Infix (try $ ...) AssocRight
so that when such a parser fails, it does not consume any input, or, better, and the conventional solution to that problem, remove the initial spaces from it,
binary n c = Infix (string n >> spaces >> return c) AssocRight
and have all your parsers consume spaces after the token they parsed
variable = do c <- letter
spaces
return $ Variable (Var c)
<?> "variable"
parens p = do char '('
spaces
x <- p
char ')'
spaces
return x
<?> "parens"
Of course, if you have parsers that can parse operators with a common prefix, you would still need to wrap those in a try so that if e.g parsing >= fails, >>= can still be tried.
Mocking up a datatype for the propositions and changing the space-consuming behaviour as indicated above,
*PropositionalParser Text.Parsec> head $ runPT expr () "" "p | q -> r & s"
Right (Conditional (Disjunction (Variable (Var 'p')) (Variable (Var 'q'))) (Conjunction (Variable (Var 'r')) (Variable (Var 's'))))
even a more complicated expression is parsed.

Complex Parsec Parsers

I don't quite know how else to ask. I think I need general guidance here. I've got something like this:
expr = buildExpressionParser table term
<?> "expression"
term = choice [
(float >>= return . EDouble)
, try (natural >>= return . EInteger)
, try (stringLiteral >>= return . EString)
, try (reserved "true" >> return (EBool True))
, try (reserved "false" >> return (EBool False))
, try assign
, try ifelse
, try lambda
, try array
, try eseq
, parens expr
]
<?> "simple expression"
When I test that parser, though, I mostly get problems... like when I try to parse
(a,b) -> "b"
it is accepted by the lambda parser, but the expr parser hates it. And sometimes it even hangs up completely in eternal rules.
I've read through Write Yourself a Scheme, but it only parses the homogeneous source of Scheme.
Maybe I am generally thinking in the wrong direction.
EDIT: Here the internal parsers:
assign = do
i <- identifier
reservedOp "="
e <- expr
return $ EAssign i e
ifelse = do
reserved "if"
e <- expr
reserved "then"
a <- expr
reserved "else"
b <- expr
return $ EIfElse e a b
lambda = do
ls <- parens $ commaSep identifier
reservedOp "->"
e <- expr
return $ ELambda ls e
array = (squares $ commaSep expr) >>= return . EArray
eseq = do
a <- expr
semi <|> (newline >>= (\x -> return [x]))
b <- expr
return $ ESequence a b
table = [
[binary "*" EMult AssocLeft, binary "/" EDiv AssocLeft, binary "%" EMod AssocLeft ],
[binary "+" EPlus AssocLeft, binary "-" EMinus AssocLeft ],
[binary "~" EConcat AssocLeft],
[prefixF "not" ENot],
[binaryF "and" EAnd AssocLeft, binaryF "or" EAnd AssocLeft]
]
And by "hates it" I meant that it tells me it expects an integer or a floating point.
What Edward in the comments and I are both trying to do is mentally run your parser, and that is a little difficult without more of the parser to go on. I'm going to make some guesses here, and maybe they will help you refine your question.
Guess 1): You have tried GHCI> parse expr "(input)" "(a,b) -> \"b\" and it has returned Left …. It would be helpful to know what the error was.
Guess 2): You have also tried GHCI> parse lambda "(input)" "(a,b) -> \"b\" and it returned Right …. based on this Edward an I have both deduced that somewhere in either your term parser or perhaps in the generated expr parser there is a conflict That is some piece of the parser is succeeding in matching the beginning of the string and returning a value, but what remains is no longer valid. It would be helpful if you would try GHCI> parse term "(input)" "(a,b) -> \"b\" as this would let us know whether the problem was in term or expr.
Guess 3): The string "(a,b)" is by itself a valid expression in the grammar as you have programmed it. (Though perhaps not as you intended to program it ;-). Try sending that through the expr parser and see what happens.
Guess 4): Your grammar is left recursive. This is what causes it to get stuck and loop forever. Parsec is a LL(k) parser. If you are used to Yacc and family which are LR(1) or LR(k) parsers, the rules for recursion are exactly reversed. If you didn't understand this last sentence thats OK, but let us know.
Guess 5): The code in the expression builder looks like it came from the function's documentation. I think you may have found the term expression somewhere as well. If that is the case you you point to where it came from. if not could you explain in a few sentences how you think term ought to work.
General Advice: The large number of try statements are eventually (a.k.a. now) going to cause you grief. They are useful in some cases but also a little naughty. If the next character can determine what choice should succeed there is no need for them. If you are just trying to get something running lots of backtracking will reduce the number of intermediate forms, but it also hides pathological cases and makes errors more obscure.
There appears to be left recursion, which will cause the parser to hang if the choice in term ever gets to eseq:
expr -> term -> eseq -> expr
The term (a,b) will not parse as a lambda, or an array, so it will fall into the eseq loop.
I don't see why (a,b) -> "b" doesn't parse as an expr, since the choice in term should hit upon the lambda, which you say works, before reaching the eseq. What is the position reported in the parse error?

Haskell recursive problem, tiny parser. A few things

data Expr = Var Char | Tall Int | Sum Expr Expr | Mult Expr Expr | Neg Expr | Let Expr Expr Expr
deriving(Eq, Show)
That is the datatype for Expr, I have a few questions. I'm suppose to parse expressions like *(Expr,Expr) as shown in the datatype definition. However I do have some problems with "creating" a valid Expr. I use pattern matching for recognizing the different things Expr can be. Some more code:
parseExpr :: String -> (Expr, String)
parseExpr ('*':'(':x:',':y:')':s) = (Mult (parseExpr [x] parseExpr [y]),s)
This is not working, obviously. The return type of parseExpr is to return the rest of the expression that is to be parsed an a portion of the parsed code as an Expr. The right side of this code is the problem. I can't make a valid Expr. The function is suppose to call it self recursively until the problem is solved.
ANOTHER problem is that I don't know how to do the pattern matching against Var and Tall. How can I check that Var is an uppercase character between A-Z and that Tall is 0-9 and return it as a valid Expr?
Generally I can just look at a few parts of the string to understand what part of Expr I'm dealing with.
Input like: parseProg "let X be 9 in *(X , 2)" Would spit out: Let (Var 'X') (Tall 9) (Mult (Var 'X') (Tall 2))
Your parseExpr function returns a pair, so of course you cannot use its result directly to construct an Expr. The way I would write this would be something like
parseExpr ('*':'(':s) = (Mult x y, s'')
where (x,',':s') = parseExpr s
(y,')':s'') = parseExpr s'
The basic idea is that, since parseExpr returns the leftover string as the second argument of the pair, you need to save that string in each recursive call you make, and when you've handled all the subexpressions, you need to return whatever is left over. And obviously the error handling here sucks, so you may want to think about that a bit more if this is intended to be a robust parser.
Handling Var and Tall I would do by just extracting the first character as is and have an if to construct an Expr of the appropriate type.
And if you want to write more complex parsers in Haskell, you'll want to look at the Parsec library, which lets you write a parser as pretty much the grammar of the language you're parsing.

Resources