[Haskell-cafe] [Parsec] A combinator to match between M and N times?

Chris Kuklewicz haskell at list.mightyreason.com
Tue Aug 29 10:11:25 EDT 2006


Stephane Bortzmeyer wrote:
> Parsec provides "count n p" to run the parser p exactly n times. I'm
> looking for a combinator "countBetween m n p" which will run the
> parser between m and n times. It does not exist in Parsec.
> 
> Much to my surprise, it seems quite difficult to write it myself and,
> until now, I failed (the best result I had was with the "option"
> combinator, which unfortunately requires a dummy value, returned when
> the parser fails).
> 
> Does anyone has a solution? Preferrably one I can understand, which
> means not yet with liftM :-

The problem with the other solutions posted so far is for (countBetween 0 100 p) 
they will always try to run p 100 times, regardless of when it starts to fail.

This can be made more efficient by stopping when p first fails.

Also, you probably have to use "try p" for the (n-m) cases, so if p consumes 
some input it does not cause the whole operation to fail.

import Text.ParserCombinators.Parsec

-- This stops when p first fails, using option to hide <|>
countBetween m n p | m<=n = do
   xs <- count m p
   let loop 0 acc = return (acc [])
       loop i acc = do
         -- mx <- option Nothing (liftM Just p)
         mx <- option Nothing (do x <- try p
                                  return (Just x))
         case mx of
           Nothing -> return (acc [])
           Just x -> loop (pred i) (acc . (x:))
   ys <- loop (n-m) id
   return (xs++ys)

-- This also works and uses <|> directly instead of via option
countBetween' m n p | m<=n = do
   xs <- count m try p
   let loop 0 acc = return (acc [])
       loop i acc =
         (do x<-p
             loop (pred i) (acc . (x:))) <|>
         (return (acc []))
   ys <- loop (n-m) id
   return (xs++ys)



More information about the Haskell-Cafe mailing list