Proposal #1464: add dropPrefix to Data.List

Hi all, I seem to have a copy of this function in everything I write sooner or later, so I'd like to propose its addition to Data.List. It strips a prefix from a list and, if successful, returns the tail. I often use it with pattern guards: foo :: String -> IO () foo x | Just y <- dropPrefix "foo=" = putStrLn ("foo is " ++ show y) foo _ = putStrLn "Unknown" but you can of course achieve the same by using case etc. The definition is: dropPrefix :: Eq a => [a] -> [a] -> Maybe [a] dropPrefix [] ys = Just ys dropPrefix (x:xs) (y:ys) | x == y = dropPrefix xs ys dropPrefix _ _ = Nothing Let's try 11 July for a discussion deadline. Thanks Ian

Ian Lynagh wrote:
The definition is:
dropPrefix :: Eq a => [a] -> [a] -> Maybe [a] dropPrefix [] ys = Just ys dropPrefix (x:xs) (y:ys) | x == y = dropPrefix xs ys dropPrefix _ _ = Nothing
Hmm. That would replace a function I write today if only it were: dropPrefix :: (Monad m, Eq a) => [a] -> [a] -> m [a] dropPrefix [] ys = return ys dropPrefix (x:xs) (y:ys) | x == y = dropPrefix xs ys dropPrefix _ _ = fail "parse error" I don't know if you'd consider this desire common enough to do the standard library that way, but I noticed this, so I figured I'd mention something. -- Chris Smith

I coded a function like this today. So, it's addition to a library
somewhere would be useful.
I also note that Ian's version is a special case of Chris's version,
so there's really no conflict here. (Yet.)
On 27/06/07, Bryan O'Sullivan
+1 on the monadic variant, of which I have a copy just like Chris's.
-- Robin Bate Boerop http://robin.bateboerop.name

Hi,
I can see how this function can be useful. However, I am strongly
opposed to adding the general monadic version---not all monads support
graceful failure, and for monads that do not support it, the only
option is to throw a run-time exception, which is at odds with the
purity of Haskell (which leads to headaches when you try to write
robust code). I think that the "Maybe" version is perfectly adequate
but if we have to have an overloaded version, then we should use
"MonadPlus".
-Iavor
On 6/26/07, Bryan O'Sullivan
Chris Smith wrote:
Hmm. That would replace a function I write today if only it were:
+1 on the monadic variant, of which I have a copy just like Chris's.
http://www.haskell.org/mailman/listinfo/libraries

iavor.diatchki:
Hi, I can see how this function can be useful. However, I am strongly opposed to adding the general monadic version---not all monads support graceful failure, and for monads that do not support it, the only option is to throw a run-time exception, which is at odds with the purity of Haskell (which leads to headaches when you try to write robust code). I think that the "Maybe" version is perfectly adequate but if we have to have an overloaded version, then we should use "MonadPlus". -Iavor
And in the dlist library we provide, maybeToMonadPlus :: MonadPlus m => Maybe a -> m a maybeToMonadPlus = maybe mzero return For those who want it. (Maybe *that* should be in Data.Maybe). -- Don

On Tue, Jun 26, 2007 at 10:00:02PM -0700, Iavor Diatchki wrote:
I can see how this function can be useful. However, I am strongly opposed to adding the general monadic version---not all monads support graceful failure, and for monads that do not support it, the only option is to throw a run-time exception, which is at odds with the purity of Haskell (which leads to headaches when you try to write robust code). I think that the "Maybe" version is perfectly adequate but if we have to have an overloaded version, then we should use "MonadPlus".
Also, no functions in Data.List work with Monads right now, so this one would be an exception. If dropPrefix is to use Monad interface, so should find, findIndex, lookup and elemIndex. $ echo ':b Data.List' | ghci | grep Monad $ echo ':b Data.List' | ghci | grep Maybe lookup :: (Eq a) => a -> [(a, b)] -> Maybe b elemIndex :: (Eq a) => a -> [a] -> Maybe Int find :: (a -> Bool) -> [a] -> Maybe a findIndex :: (a -> Bool) -> [a] -> Maybe Int unfoldr :: (b -> Maybe (a, b)) -> b -> [a] Best regards Tomek

Iavor Diatchki wrote:
I can see how this function can be useful. However, I am strongly opposed to adding the general monadic version---not all monads support graceful failure [...]
Absolutely. Consider me in favor of the MonadPlus version, then. I had just copied style from Data.Map before. Monad would be more convenient than Maybe, but MonadPlus is better yet. -- Chris Smith

I agree regarding Maybe, but in the long run, I really think we should
bring back MonadZero. This issue comes up all the time because there's
not really a proper class for monads that do handle failure gracefully
any more. I personally consider 'fail' to be a wart, and mostly try to
ignore that it even exists. Monad really isn't the class for
expressing computations which might fail.
- Cale
On 27/06/07, Iavor Diatchki
Hi, I can see how this function can be useful. However, I am strongly opposed to adding the general monadic version---not all monads support graceful failure, and for monads that do not support it, the only option is to throw a run-time exception, which is at odds with the purity of Haskell (which leads to headaches when you try to write robust code). I think that the "Maybe" version is perfectly adequate but if we have to have an overloaded version, then we should use "MonadPlus". -Iavor
On 6/26/07, Bryan O'Sullivan
wrote: Chris Smith wrote:
Hmm. That would replace a function I write today if only it were:
+1 on the monadic variant, of which I have a copy just like Chris's.

Cale Gibbard wrote:
I agree regarding Maybe, but in the long run, I really think we should bring back MonadZero.
We should also separate out the two different kinds of MonadPlus instances. There are those such as [] that satisfy mplus a b >>= k = mplus (a >>= k) (b >>= k) And there are those such as Maybe, IO and STM that satisfy mplus (return a) b = return a See http://haskell.org/haskellwiki/MonadPlus. -- Ashley Yakeley

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Cale Gibbard wrote:
I agree regarding Maybe, but in the long run, I really think we should bring back MonadZero. This issue comes up all the time because there's not really a proper class for monads that do handle failure gracefully any more. I personally consider 'fail' to be a wart, and mostly try to ignore that it even exists. Monad really isn't the class for expressing computations which might fail.
agree about Monad fail.... but does everything that can fail have to be a monad? /me thinks about non-monadic applicative and arrows (at least)... there is a class ArrowZero even! There is a Monad=>MonadPlus, an Arrow=>ArrowZero=>ArrowPlus, an Applicative=>Alternative, a Monoid. (and the Monoid kind of has the same issue as the two kinds of MonadPlus instances, considering the proposal to change Data.Map's Monoid instance, perhaps) There is a MonadFix and a ArrowLoop, but no ApplicativeFix. The arrows are somewhat special cases since they involve different-looking types. (I wonder how much things are going to change when we start using associated-types... after some years...) This feels like somewhat of an ad-hoc mess at the moment :-/ for now, I wholeheartedly support the Maybe version of dropPrefix for the purpose of going into the existing Data.List Isaac -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFGhXn3HgcxvIWYTTURAorzAJ9GlcLCk2P0/NHrNddKeQivSU3vZQCgybiq FTfTp6zdJjJfqPFPbH5O1A0= =EcsX -----END PGP SIGNATURE-----

Thomas Schilling writes:
It's most consistent with the existing functions. Also, most suggested more general implementations can be built atop of that one.
Indeed, one could always write: embed :: Monad m => Maybe a -> m a embed Nothing = fail "Nothing" embed (Just x) = return x -- -David House, dmhouse@gmail.com

Ian, Chris,
dropPrefix :: (Monad m, Eq a) => [a] -> [a] -> m [a] dropPrefix [] ys = return ys dropPrefix (x:xs) (y:ys) | x == y = dropPrefix xs ys dropPrefix _ _ = fail "parse error"
I also would like a monadic variant better (cf. Data.Map.lookup). However, I'd name it differently---not sure how, though---and reserve dropPrefix for dropPrefix :: (Eq a) => [a] -> [a] -> [a] dropPrefix prefix l = go prefix l where go (x : xs) (y : ys) | x == y = go xs ys go [] ys = ys go _ _ = l which, to me, at least, seems more in line with drop and dropWhile. Just my two cents, though. Cheers, Stefan

On Wed, 27 Jun 2007, Ian Lynagh wrote:
I seem to have a copy of this function in everything I write sooner or later, so I'd like to propose its addition to Data.List. It strips a prefix from a list and, if successful, returns the tail. I often use it with pattern guards:
foo :: String -> IO () foo x | Just y <- dropPrefix "foo=" = putStrLn ("foo is " ++ show y) foo _ = putStrLn "Unknown"
but you can of course achieve the same by using case etc.
The definition is:
dropPrefix :: Eq a => [a] -> [a] -> Maybe [a] dropPrefix [] ys = Just ys dropPrefix (x:xs) (y:ys) | x == y = dropPrefix xs ys dropPrefix _ _ = Nothing
Let's try 11 July for a discussion deadline.
Indeed, I have written this function, too, but only one time, namely for disecting CGI URLs: maybePrefixOf :: Eq a => [a] -> [a] -> Maybe [a] maybePrefixOf (x:xs) (y:ys) = if x==y then maybePrefixOf xs ys else Nothing maybePrefixOf [] ys = Just ys maybePrefixOf _ [] = Nothing

Hi Ian I think I have this thing lying around as well: On 27 Jun 2007, at 02:26, 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
But while I was grepping for it, I found I had written something slightly different. Recalling that Monoid w makes Applicative ((,) w), I have leftFactor :: Eq x => [x] -> [x] -> ([x], ([x], [x])) leftFactor (x : xs) (y : ys) | x == y = ([x], ()) *> leftFactor xs ys leftFactor xs ys = pure (xs, ys) Properties: if leftFactor xs ys = (zs, (xs', ys')) then zs is the longest list such that xs == zs ++ xs' ys == zs ++ ys' You get dropPrefix cheaply dropPrefix :: Eq a => [a] -> [a] -> Maybe [a] dropPrefix xs ys | (_, ([], zs)) <- leftFactor xs ys = Just zs | otherwise = Nothing but I also use it to do "common ancestor" calculations on hierarchical namespaces. Indeed, I have in the past used this thing on paths/contexts to determine whether two subterms of a given term were nested or not. A more frivolous usage is this variation on an ancient program: gcdList :: Eq x => [x] -> [x] -> Maybe [x] gcdList xs ys = case leftFactor xs ys of (_, ([], [])) -> Just xs (_, ([], zs)) -> gcdList xs zs (_, (zs, [])) -> gcdList zs ys _ -> Nothing gcdList xs ys calculates the largest zs such that xs == [1..m] >> zs and ys == [1..n] >> zs if any such exists. I was wondering what solutions there might be to xs ++ ys == ys ++ xs when out it popped! But I digress. It could well be that dropPrefix is much the more common, and hence that extra fuss required to get it from leftFactor isn't worth it, but I thought I'd punt out the possibility. As for whether these things should return in Maybe, or some arbitrary MonadPlus m, well, that seems like one instance of a wider question. We surely need a consistent policy here: do we target the specific *minimal* notion of computation supporting whatever it is (in this case, failure), or attempt to abstract an *arbitrary* such. If the latter, one should, of course, ask if Monad is too specific... Now I come to think about it, I quite like the minimal approach. It keeps the individual operations as simple as possible, and it pulls out the Maybe -> whatever homomorphism as a largest left factor. Or something. All the best Conor

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
Summary so far: Something should go in. The Maybe version seems more popular than generalisations, especially because Data.List already uses Maybe for the same sort of task in other functions. I don't think I tend to want the extra generality of Conor's leftFactor, and no-one else has "me-too"ed it either. Also, writing "(_, ([], zs))" rather than "Just zs" would be a bit cumbersome, so I think I'd like dropPrefix even if we also had leftFactor. Thus, based on the feedback thus far, I think dropPrefix as defined above should go in, with 'generalising Data.List functions' and 'implementing "leftFactor"' being left to possible future proposals. 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. Thanks Ian

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Ian Lynagh wrote:
I don't think I tend to want the extra generality of Conor's leftFactor, and no-one else has "me-too"ed it either. Also, writing "(_, ([], zs))" rather than "Just zs" would be a bit cumbersome, so I think I'd like dropPrefix even if we also had leftFactor.
Thus, based on the feedback thus far, I think dropPrefix as defined above should go in, with 'generalising Data.List functions' and 'implementing "leftFactor"' being left to possible future proposals.
Agreed. I very well might use leftFactor, but... it is interesting... hmm... too interesting to replace dropPrefix, I think... I really wish I could try out leftFactor in something I'm already doing, to get a better feel for it :)))
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.
The name dropPrefix is somewhat redundant, since all existing "drop" functions will only remove prefixes of a list anyway. The other connontation of "drop" is _wrong_ here: returning as much of the original list as can't be dropped (as opposed to returning a Maybe). Therefore, I see little or no merit in "drop" being part of the name, assuming "Prefix" is. I think I prefer stripPrefix. Isaac -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.6 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFGhjV0HgcxvIWYTTURAmUQAJ4xXY/QVn5pA2uEs1YjQUm0tF3DegCgqreu KlMc4lOMFULvtLGs80LCLqI= =uF9S -----END PGP SIGNATURE-----

On 30 jun 2007, at 02.35, Ian Lynagh wrote:
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.
matchAndDropPrefx dropMatchingPrefix ? / Thomas

Hello David, Saturday, June 30, 2007, 5:12:19 PM, you wrote:
matchAndDropPrefx dropMatchingPrefix
stripMatchingPrefix?
functionThatRemovesItsFirstArgumentFromSecondOneOrReturnsNothing`PleaseSendSuggestionsAboutFurtherImprovingThisFunctionNameToTheUnitedKongdomCambridgeMicrosoftResearchLabsSimonPeytonJones`ThankYouForUsingOurFunction`CopyrightIanLynagh`AllRightsReserved -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

2007/7/1, Bulat Ziganshin
functionThatRemovesItsFirstArgumentFromSecondOneOrReturnsNothing`PleaseSendSuggestionsAboutFurtherImprovingThisFunctionNameToTheUnitedKongdomCambridgeMicrosoftResearchLabsSimonPeytonJones`ThankYouForUsingOurFunction`CopyrightIanLynagh`AllRightsReserved
Hmm... fuctionThatRemovesItsFirstArgumentFromSecondOneOrReturnsNothing`theLicensesForMostSoftwareAreDesignedToTakeAwayYourFreedomToShareAndChangeItByContrastTheGnuGeneralPublicLicenseIsIntendedTo... Ah. Now I see why BSD is preferred in Haskell circles. :-) - Benja

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

Ketil Malde wrote:
On Sun, 2007-07-01 at 12:45 +0200, apfelmus wrote:
Here's an (admittedly crazy) approach
Why is it so crazy? The orthogonality issues with the different ways of breaking up lists (split/break/span/take/drop), and the multitude of possible predicates (either too complicated, or too specific) has always been an annoyance to me. I thought your solution was quite nice!
One problem is that you have to use drop (first 2) instead of drop 2 now. This can be remedied with some type-class hackery. Another problem is that performance will suffer a bit with the general approach. So, the specialized versions are likely to be kept around anyway. (Type classes can help with specialization, too.) Other than that, the general approach to drop & friends is not so crazy. But I don't like my implementation, so let's build a better one: One problem of the implementation is that I think it doesn't handle nicely the different semantics of dropPrefix compared to drop or dropWhile : whereas the latter don't fail on a premature end of the list, the dropPrefix version should fail. (The question whether it should fail with an error or with Nothing can be delegated by providing different variants of drop). The solution comes automatically when pondering what a Dropper really is: it's a *parser*. In other words, drop & friends are just functions that parse the beginning of a string and return how much has been parsed. Put differently, their feature is to ignore the "AST" resulting from a parse. type Dropper a = Parser a () -- token type a, result type () Here, I don't mean the usual (s -> (a,s)) parsers, but an implementation that fits the stream-like nature of our dropper: either a determinstic data Parser c r = Get (c -> Dropper c r) | Result r | Fail or 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). Now, which ones to choose? With deterministic parsers, we loose the normal behavior of drop and dropWhile to accept lists that are too small. Thus, we choose non-deterministic parsers and implement 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 Here, the second equation of drop tries to drop more but jumps back via Maybe's `mplus` if that fails. With the usual Monad and MonadPlus instances for Parser c a, we can now write -- take while the condition is satisfied while :: (a -> Bool) -> Dropper a while = many' . satisfy where many' p = return () `mplus` p >> many' -- accept the first n characters or less first :: Int -> Dropper a first 0 = return () first n = return () `mplus` (get >> first (n-1)) -- parse a given String prefix :: Eq a => [a] -> Dropper a prefix [] = eaten prefix (x:xs) = get >>= \c -> if c == x then prefix xs else mzero By returning successes early, while and first accept an unexpected end of input. An alternative version of first that complains when not enough characters are available to drop would be exactly :: Int -> Dropper a exactly 0 = return () exactly n = get >> exactly (n-1) or exactly n = sequence_ (replicate n get) Regards, apfelmus

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

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
Summary so far:
Something should go in.
The Maybe version seems more popular than generalisations, especially because Data.List already uses Maybe for the same sort of task in other functions.
I don't think I tend to want the extra generality of Conor's leftFactor, and no-one else has "me-too"ed it either. Also, writing "(_, ([], zs))" rather than "Just zs" would be a bit cumbersome, so I think I'd like dropPrefix even if we also had leftFactor.
Thus, based on the feedback thus far, I think dropPrefix as defined above should go in, with 'generalising Data.List functions' and 'implementing "leftFactor"' being left to possible future proposals.
On names, Stefan wrote "I'd name it differently---not sure how", as the existing drop* functions always returns a list.
FWIW, the version in GHC is called "matchPrefixMaybe". Cheers, Simon
participants (20)
-
apfelmus
-
Arie Peterson
-
Ashley Yakeley
-
Benja Fallenstein
-
Bryan O'Sullivan
-
Bulat Ziganshin
-
Cale Gibbard
-
Chris Smith
-
Conor McBride
-
David House
-
dons@cse.unsw.edu.au
-
Henning Thielemann
-
Ian Lynagh
-
Iavor Diatchki
-
Isaac Dupree
-
Robin Bate Boerop
-
Simon Marlow
-
Stefan Holdermans
-
Thomas Schilling
-
Tomasz Zielonka