Proposal #1464: add dropPrefix to Data.List

apfelmus apfelmus at quantentunnel.de
Sun Jul 1 06:45:25 EDT 2007


Ian Lynagh wrote:
> On Wed, Jun 27, 2007 at 02:26:05AM +0100, Ian Lynagh wrote:
>>     dropPrefix :: Eq a => [a] -> [a] -> Maybe [a]
>>     dropPrefix [] ys = Just ys
>>     dropPrefix (x:xs) (y:ys)
>>      | x == y = dropPrefix xs ys
>>     dropPrefix _ _ = Nothing
>
> On names, Stefan wrote "I'd name it differently---not sure how", as the
> existing drop* functions always returns a list. Other names I considered
> were stripPrefix and removePrefix, but I can't think of any commonality
> between those names and existing functions off the top of my head.

Here's an (admittedly crazy) approach to the naming problem. It comes to
mind when eating too many peppermint drops.

First a higher order drop (yummy)

    data Action  b   = Continue b | Stop | Bail
    type Dropper a b = (b -> a -> Action b, b)

    drop :: Dropper a b -> [a] -> Maybe [a]
    drop (f,y) = drop' y
        where
        drop' y (x:xs) = case f y x of
            Continue y' -> drop' y' xs
            Stop        -> Just (x:xs)
            Bail        -> Nothing

then some flavors

    while :: (a -> Bool) -> Dropper a ()
    while p = (\_ x -> if p x then Continue () else Stop, ())

    first :: Int -> Dropper a Int
    first n = (\k x -> if k < n then Continue (k+1) else Stop, 0)

    prefix :: Eq a => [a] -> Dropper a [a]
    prefix s = (f, s)
        where
        f []     _ = Stop
        f (c:cs) x = if c==x then Continue cs else Bail

and now enjoy your meal!

    drop (while (/= 5)) [1..10]
    drop (first 3) [1..10]
    drop (prefix "pre") "prefix"


Note that the Droppers can be used to write a higher order take or split
as well, but you can't eat that anymore.


Regards,
apfelmus



More information about the Libraries mailing list