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

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.

Related

Haskell - using foldl or foldr instead of pattern matching for updating a list with a new value at a given index

I have implemented a function (!!=) that given a list and a tuple containing an index in the list and a
new value, updates the given list with the new value at the given
index.
(!!=) :: [a] -> (Int,a) -> [a]
(!!=) xs (0, a) = a : tail xs
(!!=) [] (i, a) = error "Index not in the list"
(!!=) (x:xs) (i, a) = x : xs !!= (i-1, a)
Being a beginner with the concept of folding I was wondering if there is a way to achieve the same result using foldl or foldr instead?
Thanks a lot in advance.
I'll give you the foldl version which is easier to understand I think and the easiest / most straight-forward version I can think of.
But please note that you should not use foldl (use foldl': https://wiki.haskell.org/Foldr_Foldl_Foldl') - nor should you use ++ like this (use : and reverse after) ;)
Anway this is the idea:
(!!=) xs (i, a) = snd $ foldl
(\(j, ys) x -> (j+1, if j == i then ys ++ [a] else ys ++ [x]))
(0, [])
xs
as the state/accumulator for the fold I take a tuple of the current index and the accumulated result list (therefore the snd because I only want this in the end)
then the folding function just have to look if we are at the index and exchange the element - returning the next index and the new accumulated list
as an exercise you can try to:
use : instead of ++ and a reverse
rewrite as foldr
look at zipWith and rewrite this using this (zipWith (...) [0..] xs) instead of the fold (this is similar to using a map with index
Neither foldl nor foldr can do this particular job efficiently (unless you "cheat" by pattern matching on the list as you fold over it), though foldr can do it a bit less badly. No, what you really need is a different style of fold, sometimes called para:
para :: (a -> [a] -> b -> b) -> b -> [a] -> b
para _f n [] = n
para f n (a : as) = f a as (para f n as)
para is very similar to foldr. Each of them takes a combining function and, for each element, passes the combining function that element and the result of folding up the rest of the list. But para adds something extra: it also passes in the rest of the list! So there's no need to reconstruct the tail of the list once you've reached the replacement point.
But ... how do you count from the beginning with foldr or para? That brings in a classic trick, sometimes called a "higher-order fold". Instead of para go stop xs producing a list, it's going to produce a function that takes the insertion position as an argument.
(!!=) :: [a] -> (Int, a) -> [a]
xs0 !!= (i0, new) = para go stop xs0 i0
where
-- If the list is empty, then no matter what index
-- you seek, it's not there.
stop = \_ -> error "Index not in the list"
-- We produce a function that takes an index. If the
-- index is 0, we combine the new element with "the rest of the list".
-- Otherwise we apply the function we get from folding up the rest of
-- the list to the predecessor of the index, and tack on the current
-- element.
go x xs r = \i -> case i of
0 -> new : xs
_ -> x : r (i - 1)
Note that para is easily powerful enough to implement foldr:
foldr c = para (\a _ b -> c a b)
What's perhaps less obvious is that foldr can implement a (very inefficient version of) para:
para f n = snd . foldr go ([], n)
where
go x ~(xs, r) = (x : xs, f x xs r)
Lest you get the wrong idea and think that para is "better than" foldr, know that when its extra power isn't needed, foldr is simpler to use and will very often be compiled to more efficient code.

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.

Manipulating a list using pattern-matching

I want to write a function which takes a list as input value and manipulates it the following way:
Step 1: Put every 3 elements of the list in a sublist.
Should there remain less then 3 elements the remaining elements are put together in a specific sublist which is not going to be relevant in Step 2.
Step 2: Reverse the order of the elements in the created sublists.
The first element should be placed at the position of the third element, the second at the position of first element and the third element at the position of the second element. ([1,2,3] transformed to [2,3,1])
Example:
[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17]
-- should be transformed to
[[2,3,1],[5,6,4],[8,9,7],[11,12,10],[14,15,13],[16,17]]
So far I found the following approach to put every 3 elements together in sublists but I am not quite sure how to change the order of the elements in every sublist to match the requirements.
splitEvery :: Int -> [a] -> [[a]]
splitEvery _ [] = []
splitEvery n xs = as : splitEvery n bs
where (as,bs) = splitAt n xs
If the inner lists are always 3 elements, then you can hardcode that fact and use a simple solution like this:
f :: [a] -> [[a]]
f [] = []
f (x1:x2:x3:xs) = [x2,x3,x1]:f xs
f xs = [xs]
You can achieve your goal using take and drop as well
f [] = []
f xs = (take 3 xs) : f2 (drop 3 xs)
Idiomatic Haskell would be much better than other answers here. Basically, try to always design the API so it contains the proof that no corner case could occur. Hardcoding literals or hardcoding flip-like operations on lists (without guarantees of its length) are ALWAYS BAD.
{-# LANGUAGE LambdaCase #-}
divide : [a] -> [Either [a] (a,a,a)]
divide = \case
[] -> []
t1:t2:t3:ts -> Right (t1,t2,t3) : divide ts
ts -> [Left ts]
process :: [Either [a] (a,a,a)] -> [[a]]
process = fmap (flatten . flipEls) where
flipEls = fmap $ \(t1,t2,t3) -> [t2,t1,t3]
flatten = either id id
Now, you can just it like process . divide

Haskell function to keep the repeating elements of a list

Here is the expected input/output:
repeated "Mississippi" == "ips"
repeated [1,2,3,4,2,5,6,7,1] == [1,2]
repeated " " == " "
And here is my code so far:
repeated :: String -> String
repeated "" = ""
repeated x = group $ sort x
I know that the last part of the code doesn't work. I was thinking to sort the list then group it, then I wanted to make a filter on the list of list which are greater than 1, or something like that.
Your code already does half of the job
> group $ sort "Mississippi"
["M","iiii","pp","ssss"]
You said you want to filter out the non-duplicates. Let's define a predicate which identifies the lists having at least two elements:
atLeastTwo :: [a] -> Bool
atLeastTwo (_:_:_) = True
atLeastTwo _ = False
Using this:
> filter atLeastTwo . group $ sort "Mississippi"
["iiii","pp","ssss"]
Good. Now, we need to take only the first element from such lists. Since the lists are non-empty, we can use head safely:
> map head . filter atLeastTwo . group $ sort "Mississippi"
"ips"
Alternatively, we could replace the filter with filter (\xs -> length xs >= 2) but this would be less efficient.
Yet another option is to use a list comprehension
> [ x | (x:_y:_) <- group $ sort "Mississippi" ]
"ips"
This pattern matches on the lists starting with x and having at least another element _y, combining the filter with taking the head.
Okay, good start. One immediate problem is that the specification requires the function to work on lists of numbers, but you define it for strings. The list must be sorted, so its elements must have the typeclass Ord. Therefore, let’s fix the type signature:
repeated :: Ord a => [a] -> [a]
After calling sort and group, you will have a list of lists, [[a]]. Let’s take your idea of using filter. That works. Your predicate should, as you said, check the length of each list in the list, then compare that length to 1.
Filtering a list of lists gives you a subset, which is another list of lists, of type [[a]]. You need to flatten this list. What you want to do is map each entry in the list of lists to one of its elements. For example, the first. There’s a function in the Prelude to do that.
So, you might fill in the following skeleton:
module Repeated (repeated) where
import Data.List (group, sort)
repeated :: Ord a => [a] -> [a]
repeated = map _
. filter (\x -> _)
. group
. sort
I’ve written this in point-free style with the filtering predicate as a lambda expression, but many other ways to write this are equally good. Find one that you like! (For example, you could also write the filter predicate in point-free style, as a composition of two functions: a comparison on the result of length.)
When you try to compile this, the compiler will tell you that there are two typed holes, the _ entries to the right of the equal signs. It will also tell you the type of the holes. The first hole needs a function that takes a list and gives you back a single element. The second hole needs a Boolean expression using x. Fill these in correctly, and your program will work.
Here's some other approaches, to evaluate #chepner's comment on the solution using group $ sort. (Those solutions look simpler, because some of the complexity is hidden in the library routines.)
While it's true that sorting is O(n lg n), ...
It's not just the sorting but especially the group: that uses span, and both of them build and destroy temporary lists. I.e. they do this:
a linear traversal of an unsorted list will require some other data structure to keep track of all possible duplicates, and lookups in each will add to the space complexity at the very least. While carefully chosen data structures could be used to maintain an overall O(n) running time, the constant would probably make the algorithm slower in practice than the O(n lg n) solution, ...
group/span adds considerably to that complexity, so O(n lg n) is not a correct measure.
while greatly complicating the implementation.
The following all traverse the input list just once. Yes they build auxiliary lists. (Probably a Set would give better performance/quicker lookup.) They maybe look more complex, but to compare apples with apples look also at the code for group/span.
repeated2, repeated3, repeated4 :: Ord a => [a] -> [a]
repeated2/inserter2 builds an auxiliary list of pairs [(a, Bool)], in which the Bool is True if the a appears more than once, False if only once so far.
repeated2 xs = sort $ map fst $ filter snd $ foldr inserter2 [] xs
inserter2 :: Ord a => a -> [(a, Bool)] -> [(a, Bool)]
inserter2 x [] = [(x, False)]
inserter2 x (xb#(x', _): xs)
| x == x' = (x', True): xs
| otherwise = xb: inserter2 x xs
repeated3/inserter3 builds an auxiliary list of pairs [(a, Int)], in which the Int counts how many of the a appear. The aux list is sorted anyway, just for the heck of it.
repeated3 xs = map fst $ filter ((> 1).snd) $ foldr inserter3 [] xs
inserter3 :: Ord a => a -> [(a, Int)] -> [(a, Int)]
inserter3 x [] = [(x, 1)]
inserter3 x xss#(xc#(x', c): xs) = case x `compare` x' of
{ LT -> ((x, 1): xss)
; EQ -> ((x', c+1): xs)
; GT -> (xc: inserter3 x xs)
}
repeated4/go4 builds an output list of elements known to repeat. It maintains an intermediate list of elements met once (so far) as it traverses the input list. If it meets a repeat: it adds that element to the output list; deletes it from the intermediate list; filters that element out of the tail of the input list.
repeated4 xs = sort $ go4 [] [] xs
go4 :: Ord a => [a] -> [a] -> [a] -> [a]
go4 repeats _ [] = repeats
go4 repeats onces (x: xs) = case findUpd x onces of
{ (True, oncesU) -> go4 (x: repeats) oncesU (filter (/= x) xs)
; (False, oncesU) -> go4 repeats oncesU xs
}
findUpd :: Ord a => a -> [a] -> (Bool, [a])
findUpd x [] = (False, [x])
findUpd x (x': os) | x == x' = (True, os) -- i.e. x' removed
| otherwise =
let (b, os') = findUpd x os in (b, x': os')
(That last bit of list-fiddling in findUpd is very similar to span.)

Sort algorithm for list of integers in Haskell with recursion

I need to sort an integer list on haskell, from smaller to greater numbers, but i dont know where to start.
The recursion syntax is kinda difficult for me
A little bit of help would be great.
Ive done this but it does not solve my problem:
ordenarMemoria :: [Int] -> [Int]
ordenarMemoria [] = []
ordenarMemoria (x:y:xs)
| y > x = ordenarMemoria (y:xs)
| otherwise = ordenarMemoria (x:xs)
Thanks
You attempt is on the right track for a bubble sort, which is a good starting place for sorting. A few notes:
You handle the cases when the list is empty or has at least two elements (x and y), but you have forgotten the case when your list has exactly one element. You will always reach this case because you are calling your function recursively on smaller lists.
ordenarMemoria [x] = -- how do you sort a 1-element list?
Second note: in this pattern
ordenarMemoria (x:y:xs)
| y > x = ordenarMemoria (y:xs)
| otherwise = ordenarMemoria (x:xs)
you are sorting a list starting with two elements x and y. You compare x to y, and then sort the rest of the list after removing one of the two elements. This is all good.
The question I have is: what happened to the other element? A sorted list has to have all the same elements as the input, so you should use both x and y in the output. So in:
| y > x = ordenarMemoria (y:xs)
you have forgotten about x. Consider
| y > x = x : ordenarMemoria (y:xs)
which indicates to output x, then the sorted remainder.
The other branch forgets about one of the inputs, too.
After you fix the function, you might notice that the list gets a bit more sorted, but it is still not completely sorted. That's a property of the bubble sort—you might have to run it multiple times.
I'll highly recommend you read Learn You a Haskell, there is an online version here, it has a chapter where you can learn how to sort lists using recursion, like Quicksort for example:
quicksort :: (Ord a) => [a] -> [a]
quicksort [] = []
quicksort (x:xs) =
let smallerSorted = quicksort [a | a <- xs, a <= x]
biggerSorted = quicksort [a | a <- xs, a > x]
in smallerSorted ++ [x] ++ biggerSorted
I need to sort an integer list
How about sort from Data.List?
$ stack ghci
Prelude> :m + Data.List
Prelude Data.List> sort [2,3,1]
[1,2,3]
There are lots of choices. I generally recommend starting with bottom-up mergesort in Haskell, but heapsort isn't a bad choice either. Quicksort poses much more serious difficulties.
-- Given two lists, each of which is in increasing
-- order, produce a list in increasing order.
--
-- merge [1,4,5] [2,4,7] = [1,2,4,4,5,7]
merge :: Ord a => [a] -> [a] -> [a]
merge [] ys = ???
merge xs [] = ???
merge (x : xs) (y : ys)
| x <= y = ???
| otherwise = ???
-- Turn a list of elements into a list of lists
-- of elements, each of which has only one element.
--
-- splatter [1,2,3] = [[1], [2], [3]]
splatter :: [a] -> [[a]]
splatter = map ????
-- Given a list of sorted lists, merge the adjacent pairs of lists.
-- mergePairs [[1,3],[2,4],[0,8],[1,2],[5,7]]
-- = [[1,2,3,4],[0,1,2,8],[5,7]]
mergePairs :: Ord a => [[a]] -> [[a]]
mergePairs [] = ????
mergePairs [as] = ????
mergePairs (as : bs : more) = ????
-- Given a list of lists of sorted lists, merge them all
-- together into one list.
--
-- mergeToOne [[1,4],[2,3]] = [1,2,3,4]
mergeToOne :: Ord a => [[a]] -> [a]
mergeToOne [] = ???
mergeToOne [as] = ???
mergeToOne lots = ??? -- use mergePairs here
mergeSort :: Ord a => [a] -> [a]
mergeSort as = ???? -- Use splatter and mergeToOne
Once you've filled in the blanks above, try optimizing the sort by making splatter produce sorted lists of two or perhaps three elements instead of singletons.
Here is a modified either quicksort or insertion sort. It uses the fastest method of prefixing or suffixing values to the output list. If the next value is less than or greater than the first or last of the list, it is simply affixed to the beginning or end of the list. If the value is not less than the head value or greater than the last value then it must be inserted. The insertion is the same logic as the so-called quicksort above.
Now, the kicker. This function is made to run as a foldr function just to reduce the complexity of the the function. It can easily be converted to a recursive function but it runs fine with foldr.
f2x :: (Ord a) => a -> [a] -> [a]
f2x n ls
| null ls = [n]
| ( n <= (head ls) ) = n:ls -- ++[11]
| ( n >= (last ls) ) = ls ++ [n] -- ++ [22]
| True = [lx|lx <-ls,n > lx]++ n:[lx|lx <-ls,n < lx]
The comments after two line can be removed and the function can be run with scanr to see how many hits are with simple prefix or suffix of values and which are inserted somewhere other that the first or last value.
foldr f2x [] [5,4,3,2,1,0,9,8,7,6]
Or af = foldr a2x [] ... af [5,4,3,2,1,0,9,8,7,6] >-> [0,1,2,3,4,5,6,7,8,9]
EDIT 5/18/2018
The best thing about Stack Overflow is the people like #dfeuer that make you think. #dfeuer suggested using partition. I am like a child, not knowing how. I expressed my difficulty with partition but #dfeuer forced me to see how to use it. #dfeuer also pointed out that the use of last in the above function was wasteful. I did not know that, either.
The following function uses partition imported from Data.List.
partition outputs a tuple pair. This function is also meant to use with foldr. It is a complete insertion sort function.
ft nv ls = b++[nv]++e where (b,e) = partition (<=nv) ls
Use it like above
foldr ft [] [5,4,3,2,1,0,9,8,7,6]
Haskell and functional programming is all about using existing functions in other functions.
putEleInSortedListA :: Ord a => a -> [a] -> [a]
putEleInSortedListA a [] = [a]
putEleInSortedListA a (b:bs)
| a < b = a : b : bs
| otherwise = b: putEleInSortedListA a bs
sortListA :: Ord a => [a] -> [a]
sortListA la = foldr (\a b -> putEleInSortedListA a b) [] la