
Hello all Just curious: is there a library function like dropWhile, but which returns last dropped element along with the remainder of the list? If not, how can I write one - without explicit recursion - without traversing the list more than once - without traversing more of the list than necessary

On Fri, Apr 17, 2015 at 10:08:08PM +0200, martin wrote:
Hello all
Just curious: is there a library function like dropWhile, but which returns last dropped element along with the remainder of the list?
None that I know of, but span from Data.List might be worth a look

On 04/17/2015 04:08 PM, martin wrote:
Hello all
Just curious: is there a library function like dropWhile, but which returns last dropped element along with the remainder of the list?
If not, how can I write one
- without explicit recursion - without traversing the list more than once - without traversing more of the list than necessary
Here's a version that meets your last two criteria, complete with QuickCheck tests to make sure it works. Why do you want to avoid recursion? You could rewrite this to use list indices if you really wanted to, but anything you come up with is going to be essentially recursive, only less safe ---- module Main where import Test.QuickCheck -- | A version of dropWhile that returns the last element dropped as -- well as the remainder of the list. This is simply sugar over the -- 'dw' function, so you don't have to pass in a (Nothing,) tuple at -- first. -- dropWhile' :: (a -> Bool) -- ^ The predicate used to drop stuff -> [a] -- ^ The list of stuff -> (Maybe a, [a]) -- ^ (The last element dropped, list tail) dropWhile' p xs = dw p (Nothing, xs) -- | The \"real\" implementation of the dropWhile'. -- dw :: (a -> Bool) -- ^ The predicate used to drop stuff -> (Maybe a, [a]) -- ^ (Current last element dropped, current list) -> (Maybe a, [a]) -- ^ (New last element dropped, remaining list) -- This case is pretty easy. There's nothing left in the list, so just -- return what we've got. dw _ (lastdropped, []) = (lastdropped, []) dw predicate (lastdropped, xs@(x:tail_of_xs)) -- Drop the first element of the list, and "update" the return value -- before recursing. | predicate x = dw predicate (Just x, tail_of_xs) -- We're not dropping any more, just quit. | otherwise = (lastdropped, xs) -- | Make sure the tail of the list we get back is the same as it would -- be if we used dropWhile. -- prop_tailcorrect :: [Int] -> Bool prop_tailcorrect ints = actual == expected where (_, actual) = dropWhile' even ints expected = dropWhile even ints -- | Use a slower algorithm to make sure that we're getting the -- correct \"last item dropped\". -- prop_lastcorrect :: [Int] -> Bool prop_lastcorrect ints = actual == expected where (actual, _) = dropWhile' even ints expected = case (reverse $ takeWhile even ints) of [] -> Nothing (x:_) -> Just x

Am 04/17/2015 um 11:18 PM schrieb Michael Orlitzky:
Why do you want to avoid recursion? You could rewrite this to use list indices if you really wanted to, but anything you come up with is going to be essentially recursive, only less safe
Thanks for the code sample and pointing out that there may not be any last dropped element. I was wondering if there is to achive the desired behavior by plugging together higher-order functions. This was the only reason why I wanted to avoid explicit recursion.

On 04/18/2015 01:10 PM, martin wrote:
Am 04/17/2015 um 11:18 PM schrieb Michael Orlitzky:
Why do you want to avoid recursion? You could rewrite this to use list indices if you really wanted to, but anything you come up with is going to be essentially recursive, only less safe
Thanks for the code sample and pointing out that there may not be any last dropped element.
I was wondering if there is to achive the desired behavior by plugging together higher-order functions. This was the only reason why I wanted to avoid explicit recursion.
Sure. Whenever you're processing a list and building up a return value, it's probably a (left) fold. But a fold would pointlessly process the rest of the list after it had stopped dropping elements, violating one of your criteria. And foldl is of course implemented recursively =) A "short-circuiting" version of foldl might exist in some library, but there are a few ways I can think of to implement it, so it might be hard to find.

On Sat, Apr 18, 2015 at 4:21 PM, Michael Orlitzky
On 04/18/2015 01:10 PM, martin wrote:
Am 04/17/2015 um 11:18 PM schrieb Michael Orlitzky:
Why do you want to avoid recursion? You could rewrite this to use list indices if you really wanted to, but anything you come up with is going to be essentially recursive, only less safe
Thanks for the code sample and pointing out that there may not be any last dropped element.
I was wondering if there is to achive the desired behavior by plugging together higher-order functions. This was the only reason why I wanted to avoid explicit recursion.
Sure. Whenever you're processing a list and building up a return value, it's probably a (left) fold. But a fold would pointlessly process the rest of the list after it had stopped dropping elements, violating one of your criteria. And foldl is of course implemented recursively =)
A "short-circuiting" version of foldl might exist in some library, but there are a few ways I can think of to implement it, so it might be hard to find.
You don't need a left fold for this. It's a bit awkward but you can indeed just combine functions. Here's one way to write it that should not suffer from any sort of pointless list processing. import Data.List (tails) import Data.Maybe (listToMaybe) dropWhileWithLast :: (a -> Bool) -> [a] -> (Maybe a, [a]) dropWhileWithLast f xs = -- Not partial. The last element of tails is [] and -- maybe False will guarantee a non-empty list. head . dropWhile (maybe False f . listToMaybe . snd) $ zip (Nothing : map Just xs) (tails xs)
participants (4)
-
Bob Ippolito
-
Francesco Ariis
-
martin
-
Michael Orlitzky