[Haskell-cafe] Poor Parsec error message

2008-07-10 Thread Lyle Kopnicky

Hi folks,

I'm using Parsec to parse a stream of tokens. The token primitive takes, 
among other arguments, a function to print tokens. However, this 
function is not always applied. Try the code below:


-
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Pos(newPos)

mytoken :: (Eq t, Show t) = t - GenParser (SourcePos,t) () t
mytoken x = token showTok posFromTok testTok where
  showTok (pos,t) =  ++ show t ++ 
  posFromTok (pos,t) = pos
  testTok (pos,t) = if (x == t) then Just t else Nothing

main = do
  putStrLn 
  case parse the123Parser  [(newPos  1 n, n) | n - [1,2,3,4]] of
  (Left err) - putStrLn (show err)
  (Right _) - putStrLn parsed correctly
  putStrLn 
  case parse the123Parser  [(newPos  1 n, n) | n - [1,3,4]] of
  (Left err) - putStrLn (show err)
  (Right _) - putStrLn parsed correctly

the123Parser = do
  mytoken 1
  mytoken 2
  mytoken 3
  eof
  return 123
---

The output I get looks like this:

(line 1, column 4):
unexpected [((line 1, column 4),4)]
expecting end of input

(line 1, column 3):
unexpected 3

In the second parse case, it correctly uses my showTok function to show 
the token. But in the first case, it just uses the regular show method. 
I guess that's because the eof parser doesn't know anything about how to 
show the token it sees. Any ideas on how I can get the error message in 
the first case to look more like the second case?


Thanks,
Lyle
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Poor Parsec error message

2008-07-10 Thread Lyle Kopnicky
I figured it out, but it's not pretty. The problem is that the eof 
parser had no awareness of the showTok function. To fix the problem, I 
had to replace eof with its definition in terms of notFollowedBy, then 
replace notFollowedBy with its definition in terms of try and 
unexpected. Then, I changed the show [c] into showToken c.


Passing a token shower to the token function isn't a very robust way of 
guaranteeing your tokens display properly in error messages, because the 
other combinators don't take the same option. Of course, you can 
implement a Show instance for your tokens as you like. But, if you make 
the Show instance show the pretty version for the user, you lose the 
ability to see the real structure you get from a derived Show instance. 
In my real code, I want debugging to show tokens using a derived Show 
instance, so I can see all the structure. But when I show them to the 
user, I don't want them to see the embedded SourcePos, or the 
constructor names - I just want them to see a representation of what was 
lexed in order to produce that token.


I think there should be a class called Token, with a method called 
showToken, or unlex, or display, or displayInError, something like that. 
This class should be a precondition of all the GenParser combinators. It 
should use the provided method to show the token in error messages.


Here's the working version:

import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Pos(newPos)

showToken (pos,t) =  ++ show t ++ 

myToken :: (Eq t, Show t) = (t - Bool) - GenParser (SourcePos,t) () 
(SourcePos,t)

myToken q = token showToken posFromTok testTok where
   posFromTok (pos,t) = pos
   testTok (pos,t) = if (q t) then Just (pos,t) else Nothing

main = do
   putStrLn 
   case parse the123Parser  [(newPos  1 n, n) | n - [1,2,3,4]] of
   (Left err) - putStrLn (show err)
   (Right _) - putStrLn parsed correctly
   putStrLn 
   case parse the123Parser  [(newPos  1 n, n) | n - [1,3,4]] of
   (Left err) - putStrLn (show err)
   (Right _) - putStrLn parsed correctly

the123Parser = do
   myToken (==1)
   myToken (==2)
   myToken (==3)
   try (do{ c - myToken (const True); unexpected (showToken c) } | 
return ())

   notFollowedBy (myToken (==4))
   return 123

- Lyle
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe