[Haskell] Parsec question: attempted 'notMatching' combinator

Christian Maeder maeder at tzi.de
Wed Feb 18 17:20:32 EST 2004


Hi,

In a local copy of Parsec.Prim I've added a primitive, that may be of 
help for your problem as well.

consumeNothing :: GenParser tok st ()
consumeNothing = Parser (\state -> Consumed (Ok () state (unknownError 
state)))

With this I've implemented:

checkWith :: (Show a) => GenParser tok st a -> (a -> Bool)
	  -> GenParser tok st a
p `checkWith` f = do x <- p
		     if f x then return x else
		       consumeNothing >> unexpected (show x)

I can't remember, how I've implemented the more general notFollowedBy 
with this (possibly also wrong). consumeNothing simply pretends to 
consume something, which may be dangerous when repeated.

You might also like:

bind :: (Monad m) => (a -> b -> c) -> m a -> m b -> m c
bind f p q = do { x <- p; y <- q; return (f x y) }

infixl <<

(<<) :: (Monad m) => m a -> m b -> m a
(<<) = bind const

followedWith :: GenParser tok st a -> GenParser tok st b -> GenParser 
tok st a
p `followedWith` q = try (p << lookAhead q)

Christian


Andrew Pimlott wrote:
> On Wed, Feb 18, 2004 at 02:45:15PM +0100, Daan Leijen wrote:
> 
>>On Wed, 18 Feb 2004 01:11:31 -0500, Andrew Pimlott <andrew at pimlott.net> 
>>wrote:
>>
>>>After some pondering and fiddling, a version I like:
>>>
>>>   notFollowedBy' :: Show a => GenParser tok st a -> GenParser tok st ()
>>>   notFollowedBy' p    = join $  do a <- try p; return (unexpected (show 
>>>   a))
>>>                                 <|>
>>>                                 return (return ())
> 
> 
> Argh, there is still a problem!  When notFollowedBy' fails, it will have
> consumed whatever p consumed.  Stupid example:
> 
>     ab    = do  char 'a'
>                 (notFollowedBy' $ do char 'b'; char 'c') 
>                   <|> do char 'b'; return ()
> 
>     *Main> parseTest ab "abcd"
>     parse error at (line 1, column 4):
>     unexpected 'c'
> 
> Last version:
> 
>     notFollowedBy' :: Show a => GenParser tok st a -> GenParser tok st ()
>     notFollowedBy' p  = try $ join $  do  a <- try p
>                                           return (unexpected (show a))
>                                       <|>
>                                       return (return ())
> 
> 
> Try, try again,
> Andrew
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
> 




More information about the Haskell mailing list