How to use notFollowedBy function in Parsec

Dear all, Using Parsec, I want to represent a string (of anyToken) not ended with symbol semi (;). I use the command notFollowedby as follows: module Parser where import Parsec import qualified ParsecToken as P import ParsecLanguage langDef::LanguageDef () langDef = emptyDef {reservedOpNames = []} lexer::P.TokenParser() lexer = P.makeTokenParser langDef semi = P.semi lexer str1 :: Parser String str1 = do {str <- many anyToken; notFollowedBy semi; return str} However, when I compile, there is an error. ERROR "Test.hs":17 - Type error in application *** Expression : notFollowedBy semi *** Term : semi *** Type : GenParser Char () String *** Does not match : GenParser [Char] () [Char] I do not know how to fix it. Help me. Thanks for your time.

On Sat, Nov 19, 2005 at 06:43:48PM -0500, Sara Kenedy wrote:
str1 :: Parser String str1 = do {str <- many anyToken; notFollowedBy semi; return str}
However, when I compile, there is an error.
ERROR "Test.hs":17 - Type error in application *** Expression : notFollowedBy semi *** Term : semi *** Type : GenParser Char () String *** Does not match : GenParser [Char] () [Char]
The problem is that notFollowedBy has type notFollowedBy :: Show tok => GenParser tok st tok -> GenParser tok st () ie, the result type of the parser you pass to notFollowedBy has to be the same as the token type, in this case Char. (The reason for this type is obscure.) But semi has result type String. You could fix the type error by returning a dummy Char: str1 = do {str <- many anyToken ; notFollowedBy (semi >> return undefined) ; return str} I think this will even work; however notFollowedBy is a pretty squirrelly function. There was a discussion about it: http://www.haskell.org/pipermail/haskell/2004-February/013621.html Here is a version (which came out of that thread) with a nicer type, that probably also works more reliably (though I won't guarantee it): notFollowedBy' :: Show a => GenParser tok st a -> GenParser tok st () notFollowedBy' p = try $ join $ do a <- try p return (unexpected (show a)) <|> return (return ()) Andrew

On Sat, Nov 19, 2005 at 07:58:31PM -0800, Andrew Pimlott wrote:
Here is a version (which came out of that thread) with a nicer type, that probably also works more reliably (though I won't guarantee it):
notFollowedBy' :: Show a => GenParser tok st a -> GenParser tok st () notFollowedBy' p = try $ join $ do a <- try p return (unexpected (show a)) <|> return (return ())
Ok, I almost guarantee it works reliably. I know of no way to make it obvious, but by considering the four cases for p (succeeds consuming 0 tokens, succeeds consuming >0 tokens, fails having consumed 0 tokens, fails having consumerd >0 tokens) should be convincing. When this came up before, Daan suggested committing the change[1], but it seems to have gotten lost. There is also the small issue that changing the type changes the error reporting slighly[2]. Thoughts? Andrew [1] http://www.haskell.org/pipermail/haskell/2004-February/013630.html [2] http://www.haskell.org/pipermail/haskell/2004-February/013631.html

Thanks for your solution. However, when I try this,
str1 :: Parser String str1 = do str <- many anyToken notFollowedBy' semi return str
notFollowedBy' :: Show a => GenParser tok st a -> GenParser tok st () notFollowedBy' p = try $ join $ do a <- try p return (unexpected (show a)) <|> return (return ()) run:: Show a => Parser a -> String -> IO()
run p input
= case (parse p "" input) of
Left err -> do {putStr "parse error at " ;print err}
Right x -> print
When I compile, it still displays ";" at the end of the string.
Parser> run str1 "Hello ;"
"Hello ;"
The reason, as I think, because anyToken accepts any kind of token, it
considers ";" as token of its string. Thus, it does not understand
notFollowedBy' ???
Do you have any ideas about this ??? Thanks.
On 11/19/05, Andrew Pimlott
On Sat, Nov 19, 2005 at 06:43:48PM -0500, Sara Kenedy wrote:
str1 :: Parser String str1 = do {str <- many anyToken; notFollowedBy semi; return str}
However, when I compile, there is an error.
ERROR "Test.hs":17 - Type error in application *** Expression : notFollowedBy semi *** Term : semi *** Type : GenParser Char () String *** Does not match : GenParser [Char] () [Char]
The problem is that notFollowedBy has type
notFollowedBy :: Show tok => GenParser tok st tok -> GenParser tok st ()
ie, the result type of the parser you pass to notFollowedBy has to be the same as the token type, in this case Char. (The reason for this type is obscure.) But semi has result type String. You could fix the type error by returning a dummy Char:
str1 = do {str <- many anyToken ; notFollowedBy (semi >> return undefined) ; return str}
I think this will even work; however notFollowedBy is a pretty squirrelly function. There was a discussion about it:
http://www.haskell.org/pipermail/haskell/2004-February/013621.html
Here is a version (which came out of that thread) with a nicer type, that probably also works more reliably (though I won't guarantee it):
notFollowedBy' :: Show a => GenParser tok st a -> GenParser tok st () notFollowedBy' p = try $ join $ do a <- try p return (unexpected (show a)) <|> return (return ())
Andrew

On Sun, Nov 20, 2005 at 09:27:53PM -0500, Sara Kenedy wrote:
Thanks for your solution. However, when I try this,
str1 :: Parser String str1 = do str <- many anyToken notFollowedBy' semi return str
notFollowedBy' :: Show a => GenParser tok st a -> GenParser tok st () notFollowedBy' p = try $ join $ do a <- try p return (unexpected (show a)) <|> return (return ()) run:: Show a => Parser a -> String -> IO()
run p input
= case (parse p "" input) of
Left err -> do {putStr "parse error at " ;print err}
Right x -> print
When I compile, it still displays ";" at the end of the string.
Parser> run str1 "Hello ;" "Hello ;"
The reason, as I think, because anyToken accepts any kind of token, it considers ";" as token of its string. Thus, it does not understand notFollowedBy' ???
That's right--your parser consumes and returns the whole input. I can't tell you what to use instead, because it depends on what kinds of strings you want to parse. Since you are using Token parsers, maybe you want "symbol"? The functions in the Char module might also be useful. Andrew

Am Montag, 21. November 2005 03:27 schrieb Sara Kenedy: May I suggest endBy anyToken semi ? -- optionally replace semi by "char ';'", if you don't want to skip whitespace I think this is what you want --- stop at the first semicolon. If you want to ignore just a final semicolon, you might use endBy anyToken (optional semi >> eof), if you want to stop at the last semicolon, whatever comes thereafter, you have a problem, you'd need long lookahead. Cheers, Daniel
Thanks for your solution. However, when I try this,
str1 :: Parser String str1 = do str <- many anyToken notFollowedBy' semi return str
notFollowedBy' :: Show a => GenParser tok st a -> GenParser tok st () notFollowedBy' p = try $ join $ do a <- try p return (unexpected (show a)) <|> return (return ()) run:: Show a => Parser a -> String -> IO()
run p input
= case (parse p "" input) of
Left err -> do {putStr "parse error at " ;print err}
Right x -> print
When I compile, it still displays ";" at the end of the string.
Parser> run str1 "Hello ;" "Hello ;"
The reason, as I think, because anyToken accepts any kind of token, it considers ";" as token of its string. Thus, it does not understand notFollowedBy' ???
Do you have any ideas about this ??? Thanks.
On 11/19/05, Andrew Pimlott
wrote: On Sat, Nov 19, 2005 at 06:43:48PM -0500, Sara Kenedy wrote:
str1 :: Parser String str1 = do {str <- many anyToken; notFollowedBy semi; return str}
However, when I compile, there is an error.
ERROR "Test.hs":17 - Type error in application *** Expression : notFollowedBy semi *** Term : semi *** Type : GenParser Char () String *** Does not match : GenParser [Char] () [Char]
The problem is that notFollowedBy has type
notFollowedBy :: Show tok => GenParser tok st tok -> GenParser tok st ()
ie, the result type of the parser you pass to notFollowedBy has to be the same as the token type, in this case Char. (The reason for this type is obscure.) But semi has result type String. You could fix the type error by returning a dummy Char:
str1 = do {str <- many anyToken ; notFollowedBy (semi >> return undefined) ; return str}
I think this will even work; however notFollowedBy is a pretty squirrelly function. There was a discussion about it:
http://www.haskell.org/pipermail/haskell/2004-February/013621.html
Here is a version (which came out of that thread) with a nicer type, that probably also works more reliably (though I won't guarantee it):
notFollowedBy' :: Show a => GenParser tok st a -> GenParser tok st () notFollowedBy' p = try $ join $ do a <- try p return (unexpected (show a)) <|> return (return ())
Andrew
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am Dienstag, 22. November 2005 14:51 schrieben Sie:
Am Montag, 21. November 2005 03:27 schrieb Sara Kenedy:
May I suggest
endBy anyToken semi ? -- optionally replace semi by "char ';'", if you ^^^^^^^^
Oops, I confused endBy and manyTill !! Also below. And since maybe there isn't any semicolon, I'd say manyTill anyToken (semi {- try semi, perhaps -} <|> eof)
don't want to skip whitespace
I think this is what you want --- stop at the first semicolon.
If you want to ignore just a final semicolon, you might use
endBy anyToken (optional semi >> eof),
if you want to stop at the last semicolon, whatever comes thereafter, you have a problem, you'd need long lookahead.
Cheers again, Daniel

Hello,
I run as follows:
simple::Parser String
simple = do manyTill anyToken (semi <|> eof)
run:: Show a => Parser a -> String -> IO()
run p input
= case (parse p "" input) of
Left err -> do {putStr "parse error at " ;print err}
Right x -> print x
ParsecLanguage> :load Test.hs
Type checking
ERROR "Test.hs":21 - Type error in application
*** Expression : semi <|> eof
*** Term : semi
*** Type : GenParser Char () String
*** Does not match : GenParser a b ()
Do you know what happens? Thank you.
On 11/22/05, Daniel Fischer
Am Dienstag, 22. November 2005 14:51 schrieben Sie:
Am Montag, 21. November 2005 03:27 schrieb Sara Kenedy:
May I suggest
endBy anyToken semi ? -- optionally replace semi by "char ';'", if you ^^^^^^^^
Oops, I confused endBy and manyTill !! Also below. And since maybe there isn't any semicolon, I'd say
manyTill anyToken (semi {- try semi, perhaps -} <|> eof)
don't want to skip whitespace
I think this is what you want --- stop at the first semicolon.
If you want to ignore just a final semicolon, you might use
endBy anyToken (optional semi >> eof),
if you want to stop at the last semicolon, whatever comes thereafter, you have a problem, you'd need long lookahead.
Cheers again, Daniel

Am Dienstag, 22. November 2005 15:58 schrieben Sie:
Hello, I run as follows:
simple::Parser String simple = do manyTill anyToken (semi <|> eof)
run:: Show a => Parser a -> String -> IO()
run p input
= case (parse p "" input) of
Left err -> do {putStr "parse error at " ;print err}
Right x -> print x
ParsecLanguage> :load Test.hs Type checking ERROR "Test.hs":21 - Type error in application *** Expression : semi <|> eof *** Term : semi *** Type : GenParser Char () String *** Does not match : GenParser a b ()
Do you know what happens? Thank you.
Aye, <|> takes two parsers of the same type, so we'd need manyTill anyToken ((semi >> return () ) <|> eof) or manyTill anyToken (semi <|> (eof >> return "dummy String")) Cheers, Daniel

Sara Kenedy wrote:
import qualified ParsecToken as P
the proper hierarchical module name is: Text.ParserCombinators.Parsec.Token
str1 :: Parser String str1 = do {str <- many anyToken; notFollowedBy semi; return str}
simply try: str <- many anyToken; notFollowedBy (char ';'); return str "semi" only skips additional white spaces (that you are not interested in) (I find it easier not to use the Parsec.Token und Parsec.Language wrappers and remain Haskell 98 conform) Christian
participants (4)
-
Andrew Pimlott
-
Christian Maeder
-
Daniel Fischer
-
Sara Kenedy