Breaking a list into sublists of a specified size using foldr - list

I'm taking a functional programming class and I'm having a hard time leaving the OOP mindset behind and finding answers to a lot of my questions.
I have to create a function that takes an ordered list and converts it into specified size sublists using a variation of fold.
This isn't right, but it's what I have:
splitList :: (Ord a) => Int -> [a] -> [[a]]
splitList size xs
| [condition] = foldr (\item subList -> item:subList) [] xs
| otherwise =
I've been searching and I found out that foldr is the variation that works better for what I want, and I think I've understood how fold works, I just don't know how I'll set up the guards so that when length sublist == size haskell resets the accumulator and goes on to the next list.
If I didn't explain myself correctly, here's the result I want:
> splitList 3 [1..10]
> [[1,2,3],[4,5,6],[7,8,9],[10]]
Thanks!

While Fabián's and chi's answers are entirely correct, there is actually an option to solve this puzzle using foldr. Consider the following code:
splitList :: Int -> [a] -> [[a]]
splitList n =
foldr (\el acc -> case acc of
[] -> [[el]]
(h : t) | length h < n -> (el : h) : t
_ -> [el] : acc
) []
The strategy here is to build up a list by extending its head as long as its length is lesser than desired. This solution has, however, two drawbacks:
It does something slightly different than in your example;
splitList 3 [1..10] produces [[1],[2,3,4],[5,6,7],[8,9,10]]
It's complexity is O(n * length l), as we measure length of up to n–sized list on each of the element which yields linear number of linear operations.
Let's first take care of first issue. In order to start counting at the beginning we need to traverse the list left–to–right, while foldr does it right–to–left. There is a common trick called "continuation passing" which will allow us to reverse the direction of the walk:
splitList :: Int -> [a] -> [[a]]
splitList n l = map reverse . reverse $
foldr (\el cont acc ->
case acc of
[] -> cont [[el]]
(h : t) | length h < n -> cont ((el : h) : t)
_ -> cont ([el] : acc)
) id l []
Here, instead of building the list in the accumulator we build up a function that will transform the list in the right direction. See this question for details. The side effect is reversing the list so we need to counter that by reverse application to the whole list and all of its elements. This goes linearly and tail-recursively tho.
Now let's work on the performance issue. The problem was that the length is linear on casual lists. There are two solutions for this:
Use another structure that caches length for a constant time access
Cache the value by ourselves
Because I guess it is a list exercise, let's go for the latter option:
splitList :: Int -> [a] -> [[a]]
splitList n l = map reverse . reverse . snd $
foldr (\el cont (countAcc, listAcc) ->
case listAcc of
[] -> cont (countAcc, [[el]])
(h : t) | countAcc < n -> cont (countAcc + 1, (el : h) : t)
(h : t) -> cont (1, [el] : (h : t))
) id l (1, [])
Here we extend our computational state with a counter that at each points stores the current length of the list. This gives us a constant check on each element and results in linear time complexity in the end.

A way to simplify this problem would be to split this into multiple functions. There are two things you need to do:
take n elements from the list, and
keep taking from the list as much as possible.
Lets try taking first:
taking :: Int -> [a] -> [a]
taking n [] = undefined
taking n (x:xs) = undefined
If there are no elemensts then we cannot take any more elements so we can only return an empty list, on the other hand if we do have an element then we can think of taking n (x:xs) as x : taking (n-1) xs, we would only need to check that n > 0.
taking n (x:xs)
| n > 0 = x :taking (n-1) xs
| otherwise = []
Now, we need to do that multiple times with the remainder so we should probably also return whatever remains from taking n elements from a list, in this case it would be whatever remains when n = 0 so we could try to adapt it to
| otherwise = ([], x:xs)
and then you would need to modify the type signature to return ([a], [a]) and the other 2 definitions to ensure you do return whatever remained after taking n.
With this approach your splitList would look like:
splitList n [] = []
splitList n l = chunk : splitList n remainder
where (chunk, remainder) = taking n l
Note however that folding would not be appropriate since it "flattens" whatever you are working on, for example given a [Int] you could fold to produce a sum which would be an Int. (foldr :: (a -> b -> b) -> b -> [a] -> b or "foldr function zero list produces an element of the function return type")

You want:
splitList 3 [1..10]
> [[1,2,3],[4,5,6],[7,8,9],[10]]
Since the "remainder" [10] in on the tail, I recommend you use foldl instead. E.g.
splitList :: (Ord a) => Int -> [a] -> [[a]]
splitList size xs
| size > 0 = foldl go [] xs
| otherwise = error "need a positive size"
where go acc x = ....
What should go do? Essentially, on your example, we must have:
splitList 3 [1..10]
= go (splitList 3 [1..9]) 10
= go [[1,2,3],[4,5,6],[7,8,9]] 10
= [[1,2,3],[4,5,6],[7,8,9],[10]]
splitList 3 [1..9]
= go (splitList 3 [1..8]) 9
= go [[1,2,3],[4,5,6],[7,8]] 9
= [[1,2,3],[4,5,6],[7,8,9]]
splitList 3 [1..8]
= go (splitList 3 [1..7]) 8
= go [[1,2,3],[4,5,6],[7]] 8
= [[1,2,3],[4,5,6],[7,8]]
and
splitList 3 [1]
= go [] 1
= [[1]]
Hence, go acc x should
check if acc is empty, if so, produce a singleton list [[x]].
otherwise, check the last list in acc:
if its length is less than size, append x
otherwise, append a new list [x] to acc
Try doing this by hand on your example to understand all the cases.
This will not be efficient, but it will work.
You don't really need the Ord a constraint.

Checking the accumulator's first sublist's length would lead to information flow from the right and the first chunk ending up the shorter one, potentially, instead of the last. Such function won't work on infinite lists either (not to mention the foldl-based variants).
A standard way to arrange for the information flow from the left with foldr is using an additional argument. The general scheme is
subLists n xs = foldr g z xs n
where
g x r i = cons x i (r (i-1))
....
The i argument to cons will guide its decision as to where to add the current element into. The i-1 decrements the counter on the way forward from the left, instead of on the way back from the right. z must have the same type as r and as the foldr itself as a whole, so,
z _ = [[]]
This means there must be a post-processing step, and some edge cases must be handled as well,
subLists n xs = post . foldr g z xs $ n
where
z _ = [[]]
g x r i | i == 1 = cons x i (r n)
g x r i = cons x i (r (i-1))
....
cons must be lazy enough not to force the results of the recursive call prematurely.
I leave it as an exercise finishing this up.
For a simpler version with a pre-processing step instead, see this recent answer of mine.

Just going to give another answer: this is quite similar to trying to write groupBy as a fold, and actually has a couple gotchas w.r.t. laziness that you have to bear in mind for an efficient and correct implementation. The following is the fastest version I found that maintains all the relevant laziness properties:
splitList :: Int -> [a] -> [[a]]
splitList m xs = snd (foldr f (const ([],[])) xs 1)
where
f x a i
| i <= 1 = let (ys,zs) = a m in ([], (x : ys) : zs)
| otherwise = let (ys,zs) = a (i-1) in (x : ys , zs)
The ys and the zs gotten from the recursive processing of the rest of list indicate the first and the rest of the groups into which the rest of the list will be broken up, by said recursive processing. So we either prepend the current element before that first subgroup if it is still shorter than needed, or we prepend before the first subgroup when it is just right and start a new, empty subgroup.

Related

Haskell - Append to a list inside a list of lists and return the lists of lists updated

Having spent hours looking for ways to manipulate [[a]] into [[a]], I thought this would be the best solution to my problem. The problem consists of appending a to [a] and returning [[a]] with the new change.
For example: xs = [[a],[b],[c]] and y = d.
I want to append y to xs!!0 . I cannot use xs!!0 ++ y because it will return just [a,d], I know this is because of Haskell's immutability.
How would I go about appending a value to a sublist and returning the list of lists? - [[a,d],[b],[c]] using the example from above to illustrate this.
let { xs = [[1]] ; y = 2 ; zs = [(xs!!0) ++ [y]] } in zs is one example to try at the GHCi prompt.
It returns [[1,2]].
And for the case of e.g. [[1],[2,3],[4]] and the like, we can do
appendToFirst :: [[a]] -> a -> [[a]]
appendToFirst (xs:r) y = (xs ++ [y]) : r
so that
> appendToFirst [[1],[2,3],[4]] 0
[[1,0],[2,3],[4]]
The (xs:r) on the left of the equal sign is a pattern.
The (:) in the ( (...) : r) on the right of the equal sign is a "cons" operation, a data constructor, (:) :: t -> [t] -> [t].
xs is bound to the input list's "head" i.e. its first element, and r is bound to the rest of the input list, in the pattern; and thus xs's value is used in creating the updated version of the list, with the first sublist changed by appending a value to its end, and r remaining as is.
xs ++ [y] creates a new entity, new list, while xs and y continue to refer to the same old values they were defined as. Since Haskell's values and variables are immutable, as you indeed have mentioned.
edit: If you want to add new element at the end of some sublist in the middle, not the first one as shown above, this can be done with e.g. splitAt function, like
appendInTheMiddle :: Int -> a -> [[a]] -> [[a]]
appendInTheMiddle i y xs =
let
(a,b) = splitAt i xs
in
init a ++ [last a ++ [y]] ++ b
Trying it out:
> appendInTheMiddle 2 0 [[1],[2],[3],[4]]
[[1],[2,0],[3],[4]]
Adding the error-handling, bounds checking, and adjusting the indexing if 0-based one is desired (that one would lead to a simpler and faster code, by the way), is left as an exercise for the reader.
Syntactically, this can be streamlined with "view patterns", as
{-# LANGUAGE ViewPatterns #-}
appendInTheMiddle :: Int -> a -> [[a]] -> [[a]]
appendInTheMiddle i y (splitAt i -> (a,b)) =
init a ++ [last a ++ [y]] ++ b

Implementing Haskell's `take` function using `foldl`

Implementing Haskell's take and drop functions using foldl.
Any suggestions on how to implement take and drop functions using foldl ??
take x ls = foldl ???
drop x ls = foldl ???
i've tried these but it's showing errors:
myFunc :: Int -> [a] -> [a]
myFunc n list = foldl func [] list
where
func x y | (length y) > n = x : y
| otherwise = y
ERROR PRODUCED :
*** Expression : foldl func [] list
*** Term : func
*** Type : a -> [a] -> [a]
*** Does not match : [a] -> [a] -> [a]
*** Because : unification would give infinite type
Can't be done.
Left fold necessarily diverges on infinite lists, but take n does not. This is so because left fold is tail recursive, so it must scan through the whole input list before it can start the processing.
With the right fold, it's
ntake :: Int -> [a] -> [a]
ntake 0 _ = []
ntake n xs = foldr g z xs 0
where
g x r i | i>=n = []
| otherwise = x : r (i+1)
z _ = []
ndrop :: Int -> [a] -> [a]
ndrop 0 xs = xs
ndrop n xs = foldr g z xs 0 xs
where
g x r i xs#(_:t) | i>=n = xs
| otherwise = r (i+1) t
z _ _ = []
ndrop implements a paramorphism nicely and faithfully, up to the order of arguments to the reducer function g, giving it access to both the current element x and the current list node xs (such that xs == (x:t)) as well as the recursive result r. A catamorphism's reducer has access only to x and r.
Folds usually encode catamorphisms, but this shows that right fold can be used to code up a paramorphism just as well. It's universal that way. I think it is beautiful.
As for the type error, to fix it just switch the arguments to your func:
func y x | ..... = .......
The accumulator in the left fold comes as the first argument to the reducer function.
If you really want it done with the left fold, and if you're really sure the lists are finite, two options:
ltake n xs = post $ foldl' g (0,id) xs
where
g (i,f) x | i < n = (i+1, f . (x:))
| otherwise = (i,f)
post (_,f) = f []
rltake n xs = foldl' g id xs r n
where
g acc x = acc . f x
f x r i | i > 0 = x : r (i-1)
| otherwise = []
r _ = []
The first counts from the left straight up, potentially stopping assembling the prefix in the middle of the full list traversal that it does carry to the end nevertheless, being a left fold.
The second also traverses the list in full turning it into a right fold which then gets to work counting down from the left again, being able to actually stop working as soon as the prefix is assembled.
Implementing drop this way is bound to be (?) even clunkier. Could be a nice exercise.
I note that you never specified the fold had to be over the supplied list. So, one approach that meets the letter of your question, though probably not the spirit, is:
sillytake :: Int -> [a] -> [a]
sillytake n xs = foldl go (const []) [1..n] xs
where go f _ (x:xs) = x : f xs
go _ _ [] = []
sillydrop :: Int -> [a] -> [a]
sillydrop n xs = foldl go id [1..n] xs
where go f _ (_:xs) = f xs
go _ _ [] = []
These each use left folds, but over the list of numbers [1..n] -- the numbers themselves are ignored, and the list is just used for its length to build a custom take n or drop n function for the given n. This function is then applied to the original supplied list xs.
These versions work fine on infinite lists:
> sillytake 5 $ sillydrop 5 $ [1..]
[6,7,8,9,10]
Will Ness showed a nice way to implement take with foldr. The least repulsive way to implement drop with foldr is this:
drop n0 xs0 = foldr go stop xs0 n0
where
stop _ = []
go x r n
| n <= 0 = x : r 0
| otherwise = r (n - 1)
Take the efficiency loss and rebuild the whole list if you have no choice! Better to drive a nail in with a screwdriver than drive a screw in with a hammer.
Both ways are horrible. But this one helps you understand how folds can be used to structure functions and what their limits are.
Folds just aren't the right tools for implementing drop; a paramorphism is the right tool.
You are not too far. Here are a pair of fixes.
First, note that func is passed the accumulator first (i.e. a list of a, in your case) and then the list element (an a). So, you need to swap the order of the arguments of func.
Then, if we want to mimic take, we need to add x when the length y is less than n, not greater!
So we get
myFunc :: Int -> [a] -> [a]
myFunc n list = foldl func [] list
where
func y x | (length y) < n = x : y
| otherwise = y
Test:
> myFunc 5 [1..10]
[5,4,3,2,1]
As you can see, this is reversing the string. This is because we add x at the front (x:y) instead of at the back (y++[x]). Or, alternatively, one could use reverse (foldl ....) to fix the order at the end.
Also, since foldl always scans the whole input list, myFunc 3 [1..1000000000] will take a lot of time, and myFunc 3 [1..] will fail to terminate. Using foldr would be much better.
drop is more tricky to do. I don't think you can easily do that without some post-processing like myFunc n xs = fst (foldl ...) or making foldl return a function which you immediately call (which is also a kind of post-processing).

Get index of next smallest element in the list in Haskell

I m a newbie to Haskell. I am pretty good with Imperative languages but not with functional. Haskell is my first as a functional language.
I am trying to figure out, how to get the index of the smallest element in the list where the minimum element is defined by me.
Let me explain by examples.
For example :
Function signature
minList :: x -> [x]
let x = 2
let list = [2,3,5,4,6,5,2,1,7,9,2]
minList x list --output 1 <- is index
This should return 1. Because the at list[1] is 3. It returns 1 because 3 is the smallest element after x (=2).
let x = 1
let list = [3,5,4,6,5,2,1,7,9,2]
minList x list -- output 9 <- is index
It should return 9 because at list[9] is 2 and 2 is the smallest element after 1. x = 1 which is defined by me.
What I have tried so far.
minListIndex :: (Ord a, Num a) => a -> [a] -> a
minListIndex x [] = 0
minListIndex x (y:ys)
| x > y = length ys
| otherwise = m
where m = minListIndex x ys
When I load the file I get this error
• Couldn't match expected type ‘a’ with actual type ‘Int’
‘a’ is a rigid type variable bound by
the type signature for:
minListIndex :: forall a. (Ord a, Num a) => a -> [a] -> a
at myFile.hs:36:17
• In the expression: 1 + length ys
In an equation for ‘minListIndex’:
minListIndex x (y : ys)
| x > y = 1 + length ys
| otherwise = 1 + m
where
m = minListIndex x ys
• Relevant bindings include
m :: a (bound at myFile.hs:41:19)
ys :: [a] (bound at myFile.hs:38:19)
y :: a (bound at myFile.hs:38:17)
x :: a (bound at myFile.hs:38:14)
minListIndex :: a -> [a] -> a (bound at myFile.hs:37:1)
When I modify the function like this
minListIndex :: (Ord a, Num a) => a -> [a] -> a
minListIndex x [] = 0
minListIndex x (y:ys)
| x > y = 2 -- <- modified...
| otherwise = 3 -- <- modifiedd
where m = minListIndex x ys
I load the file again then it compiles and runs but ofc the output is not desired.
What is the problem with
| x > y = length ys
| otherwise = m
?
In short: Basically, I want to find the index of the smallest element but higher than the x which is defined by me in parameter/function signature.
Thanks for the help in advance!
minListIndex :: (Ord a, Num a) => a -> [a] -> a
The problem is that you are trying to return result of generic type a but it is actually index in a list.
Suppose you are trying to evaluate your function for a list of doubles. In this case compiler should instantiate function's type to Double -> [Double] -> Double which is nonsense.
Actually compiler notices that you are returning something that is derived from list's length and warns you that it is not possible to match generic type a with concrete Int.
length ys returns Int, so you can try this instead:
minListIndex :: Ord a => a -> [a] -> Int
Regarding your original problem, seems that you can't solve it with plain recursion. Consider defining helper recursive function with accumulator. In your case it can be a pair (min_value_so_far, its_index).
First off, I'd separate the index type from the list element type altogether. There's no apparent reason for them to be the same. I will use the BangPatterns extension to avoid a space leak without too much notation; enable that by adding {-# language BangPatterns #-} to the very top of the file. I will also import Data.Word to get access to the Word64 type.
There are two stages: first, find the index of the given element (if it's present) and the rest of the list beyond that point. Then, find the index of the minimum of the tail.
-- Find the 0-based index of the first occurrence
-- of the given element in the list, and
-- the rest of the list after that element.
findGiven :: Eq a => a -> [a] -> Maybe (Word64, [a])
findGiven given = go 0 where
go !_k [] = Nothing --not found
go !k (x:xs)
| given == xs = Just (k, xs)
| otherwise = go (k+1) xs
-- Find the minimum (and its index) of the elements of the
-- list greater than the given one.
findMinWithIndexOver :: Ord a => a -> [a] -> Maybe (Word64, a)
findMinWithIndexOver given = go 0 Nothing where
go !_k acc [] = acc
go !k acc (x : xs)
| x <= given = go (k + 1) acc xs
| otherwise
= case acc of
Nothing -> go (k + 1) (Just (k, x)) xs
Just (ix_min, curr_min)
| x < ix_min = go (k + 1) (Just (k, x)) xs
| otherwise = go (k + 1) acc xs
You can now put these functions together to construct the one you seek. If you want a general Num result rather than a Word64 one, you can use fromIntegral at the very end. Why use Word64? Unlike Int or Word, it's (practically) guaranteed not to overflow in any reasonable amount of time. It's likely substantially faster than using something like Integer or Natural directly.
It is not clear for me what do you want exactly. Based on examples I guess it is: find the index of the smallest element higher than x which appears after x. In that case, This solution is plain Prelude. No imports
minList :: Ord a => a -> [a] -> Int
minList x l = snd . minimum . filter (\a -> x < fst a) . dropWhile (\a -> x /= fst a) $ zip l [0..]
The logic is:
create the list of pairs, [(elem, index)] using zip l [0..]
drop elements until you find the input x using dropWhile (\a -> x /= fst a)
discards elements less than x using filter (\a -> x < fst a)
find the minimum of the resulting list. Tuples are ordered using lexicographic order so it fits your problem
take the index using snd
Your function can be constructed out of ready-made parts as
import Data.Maybe (listToMaybe)
import Data.List (sortBy)
import Data.Ord (comparing)
foo :: (Ord a, Enum b) => a -> [a] -> Maybe b
foo x = fmap fst . listToMaybe . take 1
. dropWhile ((<= x) . snd)
. sortBy (comparing snd)
. dropWhile ((/= x) . snd)
. zip [toEnum 0..]
This Maybe finds the index of the next smallest element in the list above the given element, situated after the given element, in the input list. As you've requested.
You can use any Enum type of your choosing as the index.
Now you can implement this higher-level executable specs as direct recursion, using an efficient Map data structure to hold your sorted elements above x seen so far to find the next smallest, etc.
Correctness first, efficiency later!
Efficiency update: dropping after the sort drops them sorted, so there's a wasted effort there; indeed it should be replaced with the filtering (as seen in the answer by Luis Morillo) before the sort. And if our element type is in Integral (so it is a properly discrete type, unlike just an Enum, thanks to #dfeuer for pointing this out!), there's one more opportunity for an opportunistic optimization: if we hit on a succ minimal element by pure chance, there's no further chance of improvement, and so we should bail out at that point right there:
bar :: (Integral a, Enum b) => a -> [a] -> Maybe b
bar x = fmap fst . either Just (listToMaybe . take 1
. sortBy (comparing snd))
. findOrFilter ((== succ x).snd) ((> x).snd)
. dropWhile ((/= x) . snd)
. zip [toEnum 0..]
findOrFilter :: (a -> Bool) -> (a -> Bool) -> [a] -> Either a [a]
findOrFilter t p = go
where go [] = Right []
go (x:xs) | t x = Left x
| otherwise = fmap ([x | p x] ++) $ go xs
Testing:
> foo 5 [2,3,5,4,6,5,2,1,7,9,2] :: Maybe Int
Just 4
> foo 2 [2,3,5,4,6,5,2,1,7,9,2] :: Maybe Int
Just 1
> foo 1 [3,5,4,6,5,2,1,7,9,2] :: Maybe Int
Just 9

Reverse first k elements of a list

I'd like to reverse the first k elements of a list efficiently.
This is what I came up with:
reverseFirst :: Int -> [a] -> [a] -> [a]
reverseFirst 0 xs rev = rev ++ xs
reverseFirst k (x:xs) rev = reverseFirst (k-1) xs (x:rev)
reversed = reverseFirst 3 [1..5] mempty -- Result: [3,2,1,4,5]
It is fairly nice, but the (++) bothers me. Or should I maybe consider using another data structure? I want to do this many million times with short lists.
Let's think about the usual structure of reverse:
reverse = rev [] where
rev acc [] = acc
rev acc (x : xs) = rev (x : acc) xs
It starts with the empty list and tacks on elements from the front of the argument list till it's done. We want to do something similar, except we want to tack the elements onto the front of the portion of the list that we don't reverse. How can we do that when we don't have that un-reversed portion yet?
The simplest way I can think of to avoid traversing the front of the list twice is to use laziness:
reverseFirst :: Int -> [a] -> [a]
reverseFirst k xs = dis where
(dis, dat) = rf dat k xs
rf acc 0 ys = (acc, ys)
rf acc n [] = (acc, [])
rf acc n (y : ys) = rf (y : acc) (n - 1) ys
dat represents the portion of the list that is left alone. We calculate it in the same helper function rf that does the reversing, but we also pass it to rf in the initial call. It's never actually examined in rf, so everything just works. Looking at the generated core (using ghc -O2 -ddump-simpl -dsuppress-all -dno-suppress-type-signatures) suggests that the pairs are compiled away into unlifted pairs and the Ints are unboxed, so everything should probably be quite efficient.
Profiling suggests that this implementation is about 1.3 times as fast as the difference list one, and allocates about 65% as much memory.
Well, usually I'd just write splitAt 3 >>> first reverse >>> uncurry(++) to achieve the goal.
If you're anxious about performance, you can consider a difference list:
reverseFirstN :: Int -> [a] -> [a]
reverseFirstN = go id
where go rev 0 xs = rev xs
go rev k (x:xs) = go ((x:).rev) (k-1) xs
but frankly I wouldn't expect this to be a lot faster: you need to traverse the first n elements either way. Actual performance will depend a lot on what the compiler is able to fuse away.

Need to partition a list into lists based on breaks in ascending order of elements (Haskell)

Say I have any list like this:
[4,5,6,7,1,2,3,4,5,6,1,2]
I need a Haskell function that will transform this list into a list of lists which are composed of the segments of the original list which form a series in ascending order. So the result should look like this:
[[4,5,6,7],[1,2,3,4,5,6],[1,2]]
Any suggestions?
You can do this by resorting to manual recursion, but I like to believe Haskell is a more evolved language. Let's see if we can develop a solution that uses existing recursion strategies. First some preliminaries.
{-# LANGUAGE NoMonomorphismRestriction #-}
-- because who wants to write type signatures, amirite?
import Data.List.Split -- from package split on Hackage
Step one is to observe that we want to split the list based on a criteria that looks at two elements of the list at once. So we'll need a new list with elements representing a "previous" and "next" value. There's a very standard trick for this:
previousAndNext xs = zip xs (drop 1 xs)
However, for our purposes, this won't quite work: this function always outputs a list that's shorter than the input, and we will always want a list of the same length as the input (and in particular we want some output even when the input is a list of length one). So we'll modify the standard trick just a bit with a "null terminator".
pan xs = zip xs (map Just (drop 1 xs) ++ [Nothing])
Now we're going to look through this list for places where the previous element is bigger than the next element (or the next element doesn't exist). Let's write a predicate that does that check.
bigger (x, y) = maybe False (x >) y
Now let's write the function that actually does the split. Our "delimiters" will be values that satisfy bigger; and we never want to throw them away, so let's keep them.
ascendingTuples = split . keepDelimsR $ whenElt bigger
The final step is just to throw together the bit that constructs the tuples, the bit that splits the tuples, and a last bit of munging to throw away the bits of the tuples we don't care about:
ascending = map (map fst) . ascendingTuples . pan
Let's try it out in ghci:
*Main> ascending [4,5,6,7,1,2,3,4,5,6,1,2]
[[4,5,6,7],[1,2,3,4,5,6],[1,2]]
*Main> ascending [7,6..1]
[[7],[6],[5],[4],[3],[2],[1]]
*Main> ascending []
[[]]
*Main> ascending [1]
[[1]]
P.S. In the current release of split, keepDelimsR is slightly stricter than it needs to be, and as a result ascending currently doesn't work with infinite lists. I've submitted a patch that makes it lazier, though.
ascend :: Ord a => [a] -> [[a]]
ascend xs = foldr f [] xs
where
f a [] = [[a]]
f a xs'#(y:ys) | a < head y = (a:y):ys
| otherwise = [a]:xs'
In ghci
*Main> ascend [4,5,6,7,1,2,3,4,5,6,1,2]
[[4,5,6,7],[1,2,3,4,5,6],[1,2]]
This problem is a natural fit for a paramorphism-based solution. Having (as defined in that post)
para :: (a -> [a] -> b -> b) -> b -> [a] -> b
foldr :: (a -> b -> b) -> b -> [a] -> b
para c n (x : xs) = c x xs (para c n xs)
foldr c n (x : xs) = c x (foldr c n xs)
para c n [] = n
foldr c n [] = n
we can write
partition_asc xs = para c [] xs where
c x (y:_) ~(a:b) | x<y = (x:a):b
c x _ r = [x]:r
Trivial, since the abstraction fits.
BTW they have two kinds of map in Common Lisp - mapcar
(processing elements of an input list one by one)
and maplist (processing "tails" of a list). With this idea we get
import Data.List (tails)
partition_asc2 xs = foldr c [] . init . tails $ xs where
c (x:y:_) ~(a:b) | x<y = (x:a):b
c (x:_) r = [x]:r
Lazy patterns in both versions make it work with infinite input lists
in a productive manner (as first shown in Daniel Fischer's answer).
update 2020-05-08: not so trivial after all. Both head . head . partition_asc $ [4] ++ undefined and the same for partition_asc2 fail with *** Exception: Prelude.undefined. The combining function g forces the next element y prematurely. It needs to be more carefully written to be productive right away before ever looking at the next element, as e.g. for the second version,
partition_asc2' xs = foldr c [] . init . tails $ xs where
c (x:ys) r#(~(a:b)) = (x:g):gs
where
(g,gs) | not (null ys)
&& x < head ys = (a,b)
| otherwise = ([],r)
(again, as first shown in Daniel's answer).
You can use a right fold to break up the list at down-steps:
foldr foo [] xs
where
foo x yss = (x:zs) : ws
where
(zs, ws) = case yss of
(ys#(y:_)) : rest
| x < y -> (ys,rest)
| otherwise -> ([],yss)
_ -> ([],[])
(It's a bit complicated in order to have the combining function lazy in the second argument, so that it works well for infinite lists too.)
One other way of approaching this task (which, in fact lays the fundamentals of a very efficient sorting algorithm) is using the Continuation Passing Style a.k.a CPS which, in this particular case applied to folding from right; foldr.
As is, this answer would only chunk up the ascending chunks however, it would be nice to chunk up the descending ones at the same time... preferably in reverse order all in O(n) which would leave us with only binary merging of the obtained chunks for a perfectly sorted output. Yet that's another answer for another question.
chunks :: Ord a => [a] -> [[a]]
chunks xs = foldr go return xs $ []
where
go :: Ord a => a -> ([a] -> [[a]]) -> ([a] -> [[a]])
go c f = \ps -> let (r:rs) = f [c]
in case ps of
[] -> r:rs
[p] -> if c > p then (p:r):rs else [p]:(r:rs)
*Main> chunks [4,5,6,7,1,2,3,4,5,6,1,2]
[[4,5,6,7],[1,2,3,4,5,6],[1,2]]
*Main> chunks [4,5,6,7,1,2,3,4,5,4,3,2,6,1,2]
[[4,5,6,7],[1,2,3,4,5],[4],[3],[2,6],[1,2]]
In the above code c stands for current and p is for previous and again, remember we are folding from right so previous, is actually the next item to process.