
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