
Udo Stenzel wrote:
Chris Kuklewicz wrote:
Again, Parsec requires you to put "try" where you need it
I'm pretty sure it does, although this
Udo Stenzel wrote:
countBetween 0 n p = p <:> countBetween 0 (n-1) p <|> return []
is a place where it's not needed in general. You should know what you're doing, though. And I like ReadP better in general, exactly because 'try' is a bit trippy.
Udo.
I just tried to mimic regular expression matching with ReadP and got what seems like a non-terminating program. Is there another way to use ReadP to do this?
import Control.Monad import Text.ParserCombinators.ReadP
type R = ReadP Int
-- Consume a specific character, return length 1 c :: Char -> R c x = char x >> return 1
-- Consume like x? x+ x* and return the length quest,plus,star :: R -> R quest x = option 0 x plus x = liftM sum (many1 x) star x = liftM sum (many x)
-- Concatenate two with sum of lengths infixr 5 +> (+>) :: R -> R -> R (+>) x y = liftM2 (+) x y
-- Concatenate list with running total of length match xs = match' xs 0 where match' [] t = return t match' (x:xs) t = do v <- x match' xs $! t+v
-- Simulate "(a?|b+|c*)*d" regular expression test = star (choice [quest (c 'a') ,plus (c 'b') ,star (c 'c')]) +> c 'd'
go foo = readP_to_S test foo
'go' works if I remove the leading 'star' operation from 'test' But 'go' seems to not terminate with the leading 'star' My regex-dfa package has a failure which seems similar, and I have been adding the ability to internally rewrite the pattern to avoid the problem. -- Chris