Proposal #1464: add dropPrefix to Data.List
apfelmus
apfelmus at quantentunnel.de
Fri Jul 6 16:03:46 EDT 2007
apfelmus wrote:
> what a Dropper really is: it's a *parser*.
>
> type Dropper a = Parser a () -- token type a, result type ()
>
> a non-deterministic parser
>
> data Parser c a
> = Get (c -> Dropper c r)
> | Result r (Dropper c r)
> | Fail
>
> The latter are, of course, Koen Classen's parallel parsing processes
> (http://www.cs.chalmers.se/~koen/pubs/jfp04-parser.ps).
>
> drop with a "maximum munch" behavior
>
> -- drop as much as we can parse, but not more
> drop :: Dropper a -> [a] -> [a]
> drop p xs = case drop' p xs of
> Nothing -> error "drop: parse failed"
> Just xs -> xs
> where
> drop' Fail _ = Nothing
> drop' (Result _ p) xs = drop' p xs `mplus` Just xs
> drop' (Get f) (x:xs) = drop' (f x) xs
> drop' (Get _) [] = Nothing
To implement take/break/span, we can even abstract this code further.
Assuming that we have all the goodies from Text.ParserCombinators.ReadP
available, we can get the functionality of drop & friends by adapting
the parser, not the traversal. The only thing we need is a "maximum
munch" function
maximumMunch :: Parser c r -> [c] -> r
maximumMunch p = fromJust . run p Nothing
where
run Fail r _ = r
run (Result r p) _ xs = run p (Just r) xs
run (Get f) r (x:xs) = run (f x) r xs
run (Get _) r [] = r
(using an accumulating parameter is also more efficient here). Now, we
can say
drop p = maximumMunch $ p >> look
take p = maximumMunch $ fst `liftM` gather p
split p = maximumMunch $ (\(x,y) -> (y,x)) `liftM` gather (p >> look)
Regards,
apfelmus
More information about the Libraries
mailing list