[Haskell-cafe] How to use notFollowedBy function in Parsec

Sara Kenedy sarakenedy at gmail.com
Sat Nov 19 18:43:48 EST 2005


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.


More information about the Haskell-Cafe mailing list