Replacing Nth character in String array in Haskell - list

I am new to Haskell and functional programming in general. I am trying to implement a function to take a list like this
["abc", "def", "ghi"]
and want to be able to replace the xth character in the yth element for example
replaceChar 1 2 'd' arr
would produce
["abc", "ded", "ghi"]
So essentially the first parameter is the element and the second is the position of the string, the third is the character and last is the [String].
The signature of this function looks like this:
replaceChar :: Int -> Int -> Char -> [String] -> [String]
Any help would be appreciated. Thanks!

First a note: while your signature is perfectly fine, you really don't use the fact that you're dealing with character strings, it could just as well be lists of any other type. It's usually a good idea1 to manifest that in your signature by using a completely generic type variable (lowercase letter) instead of Char:
replaceAtXY :: Int -> Int -> a -> [[a]] -> [[a]]
Next, note that basically the problem can be reduced to modifying the n-th element of an ordinary (non-nested) lists. On the outer list, you modify the y-th sublist, namely, in that sublist you modify the x-th element.
So what does "modifying" mean in Haskell? We can't mutate elements of course2. We need a function that takes a list and returns another one, and does this based on a function which operates on single elements of the list.
modifyNth :: Int -> (a->a) -> [a]->[a]
Observe that this is somewhat similar to the standard function map :: (a->b) -> [a]->[b].
Once you have that function, you can easily implement
modifyXY :: Int -> Int -> (a->a) -> [[a]]->[[a]]
modifyXY x y f nList = modifyNth y (modifyNth x f) nList
(BTW the nList parameter doesn't need to be written, you can η-reduce it).
1As to why this is a good idea: obviously, it allows you to use the function in more general settings. But more importantly, it gives the type checker extra information that you won't do anything with the contained elements themselves. This actually helps to catch a lot of bugs in more complicated applications!
2Actually you can, even with rather nice semantics, in the ST monad.

Let's break this problem into two functions, one that replaces an element in a string with a new char, and one that does this for a list of strings.
I would recommend something like:
replaceCharInStr :: Int -> Char -> String -> String
replaceCharInStr 0 c (s:ss) = c:ss
replaceCharInStr n c (s:ss) = s : ???
replaceCharInStr n c [] = error "replaceCharInStr: Empty string"
here we say that if n is 0, ignore the first element of the string with c, then if n is not 0 and the list has at least one element, prepend that element in front of something (exercise left to reader. Hint: recursion), then if our string is empty, raise an error. I will say that I don't particularly like that error is used here, it would be much better to return a Maybe String, or we could say that replaceCharInStr n c [] = [c]. We could also change the type signature to replaceCharInStr :: Int -> a -> [a] -> [a], since this isn't specific to strings.
For the next function, what we'd like to do is take an index, and apply a function at that index. In general, this function would have type
applyAt :: Int -> (a -> a) -> [a] -> [a]
And could be implemented similarly to replaceCharInStr with
applyAt :: Int -> (a -> a) -> [a] -> [a]
applyAt 0 f (x:xs) = f x : xs
applyAt n c (x:xs) = x : ???
applyAt n c [] = error "applyAt: Empty list"
In fact, this is the exact same shape as replaceCharInStr, so if you get this one implemented, then you should be able to implement replaceCharInStr in terms of applyAt as
replaceCharInStr n c xs = applyAt n (\x -> c) xs
-- Or = applyAt n (const c) xs
Then your replaceChar function could be implemented as
replaceChar :: Int -> Int -> Char -> [String] -> [String]
replaceChar n m c strings = applyAt n (replaceCharInStr m c) strings
-- Or = applyAt n (applyAt m (const c)) strings
All that's left is to implement applyAt.

If you have Edward Kmett's Lens package, then your example is a one-liner:
import Control.Lens
["abc", "def", "ghi"] & ix 1 . ix 2 .~ 'd'
returns
["abc","ded","ghi"]
Lens can emulate the indexing and property access you'd expect from an imperative language, but in Haskell. If you're just beginning to learn Haskell, you should probably wait a bit before using Lens. It's clever and powerful but it's also large and complex.

Try this:
replace n 0 c (x:xs) = (replace' n c x) : xs
replace n m c (x:xs) = x : (replace n (m-1) c xs)
where
replace' 0 c (x:xs) = c : xs
replace' n c (x:xs) = x : (replace' (n-1) c xs)
Here you just traverse the list until the corresponding index is 0 and we replace the character in the matches list. We use the same principle for replacing the charachter in the list. We traverse it and when we reach the specified index, we replace the character at that index by our new one.
In the end, everything gets consed bak on each other to replace the old structure, this time with the character replaced.

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

Breaking a list into sublists of a specified size using foldr

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.

Edit every Nth item in a list

I want to perform an arithmetic operation (e.g. doubling the value) on a list of integers, every n places.
For example, given the list [1,2,3,4,5,6,7], I want to double values every three places. In that case, we would have [1,2,6,4,5,12,7].
How can I do it?
applyEvery :: Int -> (a -> a) -> [a] -> [a]
applyEvery n f = zipWith ($) (cycle (replicate (n-1) id ++ [f]))
The cycle subexpression builds a list of functions [id,id,...,id,f] with the correct number of elements and repeats it ad nauseam, while the zipWith ($) applies that list of functions to the argument list.
Since you asked for it, more detail! Feel free to ask for more explanation.
The main idea is maybe best explained with an ASCII picture (which won't stop me from writing a thousand a lot of ASCII words!):
functions : [ id, id, f , id, id, f , id, id, f, ...
input list: [ 1, 2, 3, 4, 5, 6, 7 ]
-----------------------------------------------------
result : [ 1, 2, f 3, 4, 5, f 6, 7 ]
Just like there's no reason to hardcode the fact that you want to double every third element in the list, there's nothing special about f (which in your example is doubling), except that it should have the same result type as doing nothing. So I made these the parameters of my function. It's even not important that you operate on a list of numbers, so the function works on lists of a, as long as it's given an 'interval' and an operation. That gives us the type signature applyEvery :: Int -> (a -> a) -> [a] -> [a]. I put the input list last, because then a partial application like doubleEveryThird = applyEvery 3 (*2) is something that returns a new list, a so-called combinator. I picked the order of the other two arguments basically at random :-)
To build the list of functions, we first assemble the basic building block, consisting of n-1 ids, followed by an f as follows: replicate (n-1) id ++ [f]. replicate m x makes a list containing m repetitions of the xargument, e.g. replicate 5 'a' = "aaaaa", but it also works for functions. We have to append the f wrapped in a list of its own, instead of using : because you can only prepend single elements at the front - Haskell's lists are singly-linked.
Next, we keep on repeating the basic building block with cycle (not repeat as I first had mistakenly). cycle has type [a] -> [a] so the result is a list of "the same level of nested-ness". Example cycle [1,2,3] evaluates to [1,2,3,1,2,3,1,2,3,...]
[ Side note: the only repeat-y function we haven't used is repeat itself: that forms an infinite list consisting of its argument ]
With that out of the way, the slightly tricky zipWith ($) part. You might already know the plain zip function, which takes two lists and puts elements in the same place in a tuple in the result, terminating when either list runs out of elements. Pictorially:
xs : [ a , b , c , d, e]
ys: [ x, y , z ]
------------------------------
zip xs ys: [(a,x),(b,y),(c,z)]
This already looks an awful lot like the first picture, right? The only thing is that we don't want to put the individual elements together in a tuple, but apply the first element (which is a function) to the second instead. Zipping with a custom combining function is done with zipWith. Another picture (the last one, I promise!):
xs : [ a , b , c , d, e]
ys: [ x, y, z ]
----------------------------------------
zipWith f xs ys: [ f a x, f b y, f c z ]
Now, what should we choose to zipWith with? Well, we want to apply the first argument to the second, so (\f x -> f x) should do the trick. If lambdas make you uncomfortable, you can also define a top-level function apply f x = f x and use that instead. However, this already a standard operator in the Prelude, namely $! Since you can't use a infix operator as a standalone function, we have to use the syntactic sugar ($) (which really just means (\f x -> f $ x))
Putting all of the above together, we get:
applyEvery :: Int -> (a -> a) -> [a] -> [a]
applyEvery n f xs = zipWith ($) (cycle (replicate (n-1) id ++ [f])) xs
But we can get rid of the xs at the end, leading to the definition I gave.
A common way to get indexes for values in a list is to zip the list into tuples of (value, index).
ghci > let zipped = zip [1,2,3,4,5,6,7] [1..]
ghci > zipped
[(1,1),(2,2),(3,3),(4,4),(5,5),(6,6),(7,7)]
Then you just need to map over that list and return a new one. If index is divisible by 3 (index `rem` 3 == 0), we'll double the value, otherwise we'll return the same value:
ghci > map (\(value, index) -> if index `rem` 3 == 0 then value*2 else value) zipped
[1,2,6,4,5,12,7]
Tell me if that all makes sense—I can add more detail if you aren't familiar with zip and map and such.
Zip
You can find documentation on zip by looking at its Haddocks, which say: "zip takes two lists and returns a list of corresponding pairs." (Docs are hosted in several places, but I went to https://www.stackage.org and searched for zip).
Map
The map function applies a function to each item in a list, generating a new value for each element.
Lambdas
Lambdas are just functions without a specific name. We used one in the first argument to map to say what we should do to each element in the list. You may have seen these in other languages like Python, Ruby, or Swift.
This is the syntax for lambdas:
(\arg1, arg2 -> functionBodyHere)
We could have also written it without a lambda:
ghci > let myCalculation (value, index) = if index `rem` 3 == 0 then value*2 else value
ghci > map myCalculation zipped
[1,2,6,4,5,12,7]
Note: this code is not yet tested.
In lens land, this is called a Traversal. Control.Lens gives you these:
{-# LANGUAGE RankNTypes, ScopedTypeVariables #-}
type Traversal s t a b =
forall f . Applicative f => (a -> f b) -> s -> f t
type Traversal' s a = Traversal s s a a
We can use lens's itraverse from Control.Lens.Indexed:
-- everyNth :: (TraversableWithIndex i t, Integral i)
=> i -> Traversal' (t a) a
everyNth :: (TraversableWithIndex i t, Integral i, Applicative f)
=> i -> (a -> f a) -> t a -> f (t a)
everyNth n f = itraverse f where
g i x | i `rem` n == n - 1 = f x
| otherwise = pure x
This can be specialized to your specific purpose:
import Data.Profunctor.Unsafe
import Data.Functor.Identity
everyNthPureList :: Int -> (a -> a) -> [a] -> [a]
everyNthPureList n f = runIdentity #. everyNth n (Identity #. f)
mapIf :: (Int -> Bool) -> (a -> a) -> [a] -> [a]
mapIf pred f l = map (\(value,index) -> if (pred index) then f value else value) $ zip l [1..]
mapEveryN :: Int -> (a -> a) -> [a] -> [a]
mapEveryN n = mapIf (\x -> x `mod` n == 0)
Live on Ideone.
A simple recursive approach:
everyNth n f xs = igo n xs where
igo 1 (y:ys) = f y : igo n ys
igo m (y:ys) = y : igo (m-1) ys
igo _ [] = []
doubleEveryThird = everyNth 3 (*2)
Basically, igo starts at n, counts down until it reaches 1, where it will apply the function, and go back up to n. doubleEveryThird is partially applied: everyNth expects three arguments, but we only gave it two, so dougleEveryThird will expect that final argument.

Haskell and manipulating a list of tuples

Ok so have been faced with a problem where basically I have a been told to make a multiset, or a list of tuples. (Char,Int) and then I have to write a function that takes a item and inserts it into this list, but if there is already a matching tuple in the list it increases the Int.
i.e. i had a list [(p,2),(w,3)] and i get another w it should give [(p,2),(w,4)]
How would you go about it, i've tried
listAdd :: Char->Int->ListOfT -> ListOfT
listAdd c i l
|length l == 0 =(c,i):l
|fst l == c = (c,i+1):l
but this gives loads of errors, i need to remove the list element at that point and replace it with with (c,i+1), so how do i remove from the list and how to i get i+1? also how do you make a loop which will go through all the elements in a list?
And i can't use any of the import Data stuff
I know this is asking a ton but any help would be great thanks.
Neo
Okay can this code be fiddled with so it can be used tto make tuples of any items not just chars. so i could load it up and make a list of tuples with stirngs instead, close it then load it up again and make a list of tuples of ints?
ok I think your idea is not bad you just have to get the details straight.
The loop you asked about is usually either done with recursion (as a list is a recursive structure that's a great idea) or with some higher order functions like map, filter, foldr, ... that will hide the recursion from you (you could say they abstract away the repeating stuff) - anway in this case I think the easiest way is just to go with what you started and use the direct recursion.
Here is a simple version (you maybe want to extent) that does the basic stuff:
listAdd :: Char -> [(Char,Int)] -> [(Char,Int)]
listAdd c [] = [(c,1)]
listAdd c ((c',i):xs)
| c' == c = (c,i+1):xs
| otherwise = (c',i) : listAdd c xs
as you can see the first case is very similar to what you had: if the dictionary (the second argument) is the empty list than you just add a new tuple with the char to insert and the number 1
if not then you check if the first element in the dictionary has the same character (c' here), if yes then you increase the count and if not you let this element stand as it is and recursively search through the rest of the dictionary.
Also note that you can use pattern matching here to not only deconstruct the dictionary into head::tail form but also deconstruct the head into (..,..) tuple parts as well.
If you want you can use a # in there to and get the second case a bit more concise:
listAdd :: Char -> [(Char,Int)] -> [(Char,Int)]
listAdd c [] = [(c,1)]
listAdd c (x#(c',i):xs)
| c' == c = (c,i+1):xs
| otherwise = x : listAdd c xs
PS: in case you wondered why I did not use your Int argument? Because I don't know what you want to do with it if there is already a value - here is a version where I just add it to it (seems resonable):
listAdd :: Char -> Int -> [(Char,Int)] -> [(Char,Int)]
listAdd c i [] = [(c,i)]
listAdd c i (x#(c',i'):xs)
| c' == c = (c,i+i'):xs
| otherwise = x : listAdd c i xs
List manipulations with just recursive functions can be indeed hard for beginners to grok, but in this case they should fit the problem nicely.
Let's start with a bit better signature and a helper.
type MyList = [(Char, Int)]
listAdd :: Char -> MyList -> MyList
listAdd p l = listAdd' p [] l
Notice that I've changed the signature to accept just Char; we don't need to supply the initial count, since if there are no such elements currently on the list, we'll just set it to 1 when adding a new element.
Okay, that's the basic skeleton. The helper is there just to make it easier to store the "already processed" part of the list. Let's look at it:
listAdd' :: Char -> MyList -> MyList -> MyList
First, we add the recursion end condition:
listAdd' p left [] = left ++ [(p, 1)]
This means that if we haven't found the element to replace earlier, we can just add it at the end.
listAdd' p left (x:right) = if p == fst x
then left ++ [(fst x, snd x + 1)] ++ right
else listAdd' p (left ++ [x]) right
Okay, so now we split up the "right" part to the first element of it and the rest. Let's look at the if:
if we managed to find the element, we can end the computation by appending the rest of the list to the modified element and what we had previously
if it's still not it, we proceed with recursion.
As an additional remark at the end, you could easily change Char to Eq a => a to allow your function to work on any type that can be directly compared, Char included.

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.