Grouping consecutive duplicates in a list? - list

Very basic but I'm finding the problem frustrating. I'm trying to group consecutive elements of a list:
myList = [1,2,3,4,4,4,5]
becomes
myList = [[1],[2],[3],[4,4,4],[5]]
This is my attempt using foldr with an accumulator:
print $ foldr (\ el acc -> if el /= head (head acc) then el ++ (head acc) else acc) [['a']] myList
I don't understand why I'm getting the following error:
Couldn't match expected type ‘[a0]’ with actual type ‘Int’
In the expression: 'a'
In the expression: ['a']
In the second argument of ‘foldr’, namely ‘[['a']]’
Any advice would be great!

Writing a fold on lists requires us to answer just two cases: [] (the empty list, or "nil") and x:xs (an element followed by a list, or "cons").
What is the answer when the list is empty? Lets say the answer is also an empty list. Therefore:
nilCase = []
What is the answer when the list is not empty? It depends on what we have already accumulated. Lets say we have already accumulated a group. We know that groups are non-empty.
consCase x ((g11:_):gs)
If x == g11 then we add it to the group. Otherwise we begin a new group. Therefore:
consCase x ggs#(g1#(g11:_):gs)
| x == g11 = (x:g1):gs
| otherwise = [x]:ggs
What if we have not accumulated any groups yet? Then we just create a new group.
consCase x [] = [[x]]
We can consolidate the three cases down to two:
consCase x ggs
| g1#(g11:_):gs <- ggs, x == g11 = (x:g1):gs
| otherwise = [x]:ggs
Then the desired fold is simply:
foldr consCase nilCase

Using foldr, it should be:
group :: (Eq a) => [a] -> [[a]]
group = foldr (\x acc -> if head acc == [] || head (head acc) == x then (x:head acc) : tail acc else [x] : acc) [[]]

The type of your case case is [[Char]], you are attempting to build a value of type [[Int]]. Our base case should be an empty list, and we'll add list elements in each step.
Let's look at the anonymous function you're written next. Note that we'll fail due to type based on your current if within the accumulator (they must return values of the same type, and the same type as the accumulator. It'll be better, and cleaner, if we pattern match the accumulator and apply the function differently in each case:
func :: Eq a => [a] -> [[a]]
func = foldr f []
where f x [] = undefined
f x (b#(b1:_):bs)
| x == b1 = undefined
| otherwise = undefined
When we encounter the base case, we should just add the our element wrapped in a list:
f x [] = [[x]]
Next, we'll deal with the non-empty list. If x is equal to the next head of the head of the list, we should add it to that list. Otherwise, we shou
f x (b#(b1:_):bs)
| == b1 = (x:b):bs
| = [x]:b:bs
Putting this together, we have:
func :: Eq a => [a] -> [[a]]
func = foldr f []
where f x [] = [[x]]
f x (b#(b1:_):bs)
| x == b1 = (x:b):bs
| otherwise = [x]:b:bs
Having broken the problem down, it's much easier to rewrite this more compactly with a lambda function. Notice that the head [[]] is just [], so we can handle the empty list case and the equality case as one action. Thus, we can rewrite:
func :: (Eq a) => [a] -> [[a]]
func = foldr (\x (b:bs) -> if b == [] || x == head b then (x:b):bs else [x]:b:bs) [[]]
However, this solution ends up requiring the use of head since we must pattern match all versions of the accumulator.

Related

Haskell Recursion how to return an empty list and ignore recursively generated list

I'm writing a recursive function that builds a list, but has some conditions where, if met, the function should ignore the list that's been built so far and simply return an empty list on its own.
A simple example:
func (x:xs)
| x < 10 = [x] ++ func xs
| otherwise = ("return an empty list without the already built up list")
So if xs was a list [1 .. 12] then once it's built a list that's [1..9] then when it reaches 10, it'll disregard the list it's built and just return an empty array [], and not return an empty array that's passed back to the already built up list.
Is there a way to do this in Haskell? I've tried doing return [] but it gave me the error:
Couldn't match expected type ‘Int’ with actual type ‘[t0]’
return is not a statement in Haskell, but even if it was it would not work anyway. Since due to recursion, you then return that list at that specific level.
It looks however that you simply want to know if all elements are smaller than 10. If that is the case, you return the entire list, otherwise you return an empty list.
You can do that with:
func :: (Num a, Ord a) => [a] -> [a]
func xs | all (< 10) xs = xs
| otherwise = []
or we can use recursion, and make use of Maybe:
func :: (Num a, Ord a) => [a] -> Maybe [a]
func [] = Just []
func (x:xs) | x < 10 = fmap (x:) (func xs)
| otherwise = Nothing
We can then later convert the Nothing value with fromMaybe :: a -> Maybe a -> a to an empty list, although a Maybe might be better idea here, that allows us to differentatie between func [] and func [14] for example.

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).

List to tuple counting values repeated and the list inside the tuple - Haskell

im learning functional programming with Haskell and i have this exercise where i have something like [a], z, with [a] any kind of list and z the element that im gonna erase inside [a]. This problem it's kinda easy to solve (even for a newbie like me in Haskell) but I am having troubles with the way I need to print the output.
I need to create a tuple where the first element is the list without any z element and the number of times that it found z inside of a. Couple examples:
Input: [2,3,4,2,2] 2
Output: ([3,4],3)
Input: [1,1,1,1] 1
Output: ([],4)
Input: [1,2,3,4] 5
Output: ([1,2,3,4],0)
So far i've done something like this but I don't know how to keep going:
ex3 :: (Eq a, Num a) => [a] -> a -> ([a],Int)
ex3 [] _ = ([],0)
ex3 (x:xs) z | x == z = (xs,1) -- this line is wrong, but idk how to fix it
| otherwise = ([0],0) -- same here
I've done both problems individually (deleting z elements and counting how many times z is in [a]. Looks like this:
a) Deleting z elements:
ex3a :: (Eq a) => [a] -> a -> [a]
ex3a [] _ = []
ex3a (x:xs) z | x == z = ex3a xs z
| otherwise = x : ex3a xs z
b) Counting how many times z is in [a]:
ex3b :: (Eq a) => [a] -> a -> Int
ex3b [] _ = 0
ex3b (x:xs) z | x == z = 1 + ex3b xs z
| otherwise = ex3b xs z
Usually it helps to think of functions like in mathematics you think about inductive definitions. For example the first line of your function can read like:
"The ex3 of an empty list, and any element is a tuple containing the empty list and zero"
ex3 [] _ = ([], 0)
For non-empty lists of course the problem is a bit harder. Like in your code, there are basically two cases here.
"The ex3 of a non-empty list and an element z where the head of the list is not equal to z is the same as the ex3 of the tail of the list, but prepended with the head of that list", so we can write it like:
ex3 [] _ = ([], 0)
ex3 (x:xs) z | x /= z = (x:t, n)
| otherwise = ...
where (t, n) = ex3 xs z
So here we make a recursive call to ex3 with the tail of the list xs, and we obtain the result tuple (t, n), so t contains the "erased" tail, and n the number of times we removed the element, and in case x /= z, then we can return (x:t, n), since the number of removals does not change, but we have to prepend x to the list.
"The ex3 of a non-empty list and an element z where the head of the list is equal to z is the same as the ex3 of the tail of the list but with an incremented count", so:
ex3 :: (Eq a, Num n) => [a] -> a -> ([a], n)
ex3 [] _ = ([], 0)
ex3 (x:xs) z | x /= z = (x:t, n)
| otherwise = (t, n+1)
where (t, n) = ex3 xs z
We then obtain the expected results:
Prelude> ex3 [2,3,4,2,2] 2
([3,4],3)
Prelude> ex3 [1,1,1,1] 1
([],4)
Prelude> ex3 [1,2,3,4] 5
([1,2,3,4],0)
Just for fun, this is how I would implement that function:
import Data.Foldable
import Data.Monoid
ex3 :: Eq a => [a] -> a -> ([a], Int)
ex3 haystack needle = getSum <$> foldMap inject haystack where
inject hay | hay == needle = ([], 1)
| otherwise = ([hay], 0)
What I like about this is that the recursion pattern is immediately obvious -- at least to those familiar with Haskell's standard library -- without careful scrutiny (because it is just a call to foldMap).
The partition function consumes a predicate and a list; it produces a pair of lists whose first element satisfies the predicate, the second doesn't.
import Data.List (partition)
ex4 :: Eq a => [a] -> a -> ([a], Int)
ex4 xs x = length <$> partition (/= x) xs

Member Function in Haskell

Working on a small assignment for class, having a lot of trouble with Haskell. I am trying to make a recursive method for finding if an integer is part of a list or not. I know the gist, but am unable to get it working correctly with the haskell syntax. Check if the current list is empty, if so then False, then check if integer is equal to the head of the current list, if so, then True, then call member again with the same value you are searching for, and the tail of the list. What can I do to get this functioning properly.
Currently this is what I have:
member ::Int -> [Int] -> Bool
member x y
if y [] then False
else if x == head y then True
else member x tail y
I have also tried using
member :: (Eq x) => x -> [x] -> Bool
as the beginning line, and also a much simplier :
let member x y = if null y then False
else if x == head y then True
else member x tail y
Any help would be appreciated.
with pattern matching you can write it more clearly
member :: (Eq a) => a -> [a] -> Bool
member x [] = False
member x (y:ys) | x==y = True
| otherwise = member x ys
element _ [] = False
element e (x:xs) = e == x || e `element` xs
-- OR
element e xs = if xs == [] then False
else if e == head xs then True
else e `element` tail xs
-- OR
element e xs = xs /= [] && (e == head xs || e `element` tail xs)
-- x `op` y = op x y
-- If you're feeling cheeky
element = elem
Your syntax appears very confused, but your logic makes sense, so here's a bucket list of things to remember:
Functions can be defined by multiple equations. Equations are checked top to bottom. That means using =.
Pattern matches are not equality tests. A pattern match breaks a value into its constituents if it matches and fails otherwise. An equality test x == y returns a Bool about the equality of x and y.
Pattern matching is used for flow control via...
a case statement, like
case xs of {
[] -> ...
x:xs' -> ...
}
Multiple equations, like
element _ [] = ...
element e (x:xs) = ...
Note that you can ignore a value in a pattern with _. With multiple equations of a function with multiple arguments, you're really pattern matching on all the arguments at once.
Bools are used for flow control via if _ then _ else _:
if xs == [] then False
else True
which is really just
case x == y of {
True -> False
False -> True
}
and Bools can use the ordinary operators (&&) (infixr 3) and (||) (infixr 2)
The difference is especially nefarious on lists. instance Eq a => Eq [a], so in order to use == on lists, you need to know that the elements of the lists can be compared for equality, too. This is true even when you're just checking (== []). [] == [] actually causes an error, because the compiler cannot tell what type the elements are. Here it doesn't matter, but if you say, e.g. nonEmpty xs = xs /= [], you'll get nonEmpty :: Eq a => [a] -> Bool instead of nonEmpty :: [a] -> Bool, so nonEmpty [not] gives a type error when it should be True.
Function application has the highest precedence, and is left-associative:
element x xs reads as ((element x) xs)
element x tail xs reads as (((element x) tail) xs), which doesn't make sense here
f $ x = f x, but it's infixr 0, which means it basically reverses the rules and acts like a big set of parentheses around its right argument
element x $ tail xs reads as ((element x) (tail xs)), which works
Infix functions always have lower precedence than prefix application:
x `element` tail xs means ((element x) (tail xs)), too
let decls in expr is an expression. decls is only in scope inside expr, and the entire thing evaluates to whatever expr evaluates to. It makes no sense on the top level.
Haskell uses indentation to structure code, like Python. Reference

Haskell: return the "list" result of a function as a "list of lists" without using an empty list "[]:foo"

What would be the syntax (if possible at all) for returning the list of lists ([[a]]) but without the use of empty list ([]:[a])?
(similar as the second commented guard (2) below, which is incorrect)
This is a function that works correctly:
-- Split string on every (shouldSplit == true)
splitWith :: (Char -> Bool) -> [Char] -> [[Char]]
splitWith shouldSplit list = filter (not.null) -- would like to get rid of filter
(imp' shouldSplit list)
where
imp' _ [] = [[]]
imp' shouldSplit (x:xs)
| shouldSplit x = []:imp' shouldSplit xs -- (1) this line is adding empty lists
-- | shouldSplit x = [imp' shouldSplit xs] -- (2) if this would be correct, no filter needed
| otherwise = let (z:zs) = imp' shouldSplit xs in (x:z):zs
This is the correct result
Prelude> splitWith (== 'a') "miraaaakojajeja234"
["mir","koj","jej","234"]
However, it must use "filter" to clean up its result, so I would like to get rid of function "filter".
This is the result without the use of filter:
["mir","","","","koj","jej","234"]
If "| shouldSplit x = imp' shouldSplit xs" is used instead the first guard, the result is incorrect:
["mirkojjej234"]
The first guard (1) adds empty list so (I assume) compiler can treat the result as a list of lists ([[a]]).
(I'm not interested in another/different solutions of the function, just the syntax clarification.)
.
.
.
ANSWER:
Answer from Dave4420 led me to the answer, but it was a comment, not an answer so I can't accept it as answer. The solution of the problem was that I'm asking the wrong question. It is not the problem of syntax, but of my algorithm.
There are several answers with another/different solutions that solve the empty list problem, but they are not the answer to my question. However, they expanded my view of ways on how things can be done with basic Haskell syntax, and I thank them for it.
Edit:
splitWith :: (Char -> Bool) -> String -> [String]
splitWith p = go False
where
go _ [] = [[]]
go lastEmpty (x:xs)
| p x = if lastEmpty then go True xs else []:go True xs
| otherwise = let (z:zs) = go False xs in (x:z):zs
This one utilizes pattern matching to complete the task of not producing empty interleaving lists in a single traversal:
splitWith :: Eq a => (a -> Bool) -> [a] -> [[a]]
splitWith f list = case splitWith' f list of
[]:result -> result
result -> result
where
splitWith' _ [] = []
splitWith' f (a:[]) = if f a then [] else [[a]]
splitWith' f (a:b:tail) =
let next = splitWith' f (b : tail)
in if f a
then if a == b
then next
else [] : next
else case next of
[] -> [[a]]
nextHead:nextTail -> (a : nextHead) : nextTail
Running it:
main = do
print $ splitWith (== 'a') "miraaaakojajeja234"
print $ splitWith (== 'a') "mirrraaaakkkojjjajeja234"
print $ splitWith (== 'a') "aaabbbaaa"
Produces:
["mir","koj","jej","234"]
["mirrr","kkkojjj","jej","234"]
["bbb"]
The problem is quite naturally expressed as a fold over the list you're splitting. You need to keep track of two pieces of state - the result list, and the current word that is being built up to append to the result list.
I'd probably write a naive version something like this:
splitWith p xs = word:result
where
(result, word) = foldr func ([], []) xs
func x (result, word) = if p x
then (word:result,[])
else (result, x:word)
Note that this also leaves in the empty lists, because it appends the current word to the result whenever it detects a new element that satisfies the predicate p.
To fix that, just replace the list cons operator (:) with a new operator
(~:) :: [a] -> [[a]] -> [[a]]
that only conses one list to another if the original list is non-empty. The rest of the algorithm is unchanged.
splitWith p xs = word ~: result
where
(result, word) = foldr func ([], []) xs
func x (result, word) = if p x
then (word ~: result, [])
else (result, x:word)
x ~: xs = if null x then xs else x:xs
which does what you want.
I guess I had a similar idea to Chris, I think, even if not as elegant:
splitWith shouldSplit list = imp' list [] []
where
imp' [] accum result = result ++ if null accum then [] else [accum]
imp' (x:xs) accum result
| shouldSplit x =
imp' xs [] (result ++ if null accum
then []
else [accum])
| otherwise = imp' xs (accum ++ [x]) result
This is basically just an alternating application of dropWhile and break, isn't it:
splitWith p xs = g xs
where
g xs = let (a,b) = break p (dropWhile p xs)
in if null a then [] else a : g b
You say you aren't interested in other solutions than yours, but other readers might be. It sure is short and seems clear. As you learn, using basic Prelude functions becomes second nature. :)
As to your code, a little bit reworked in non-essential ways (using short suggestive function names, like p for "predicate" and g for a main worker function), it is
splitWith :: (Char -> Bool) -> [Char] -> [[Char]]
splitWith p list = filter (not.null) (g list)
where
g [] = [[]]
g (x:xs)
| p x = [] : g xs
| otherwise = let (z:zs) = g xs
in (x:z):zs
Also, there's no need to pass the predicate as an argument to the worker (as was also mentioned in the comments). Now it is arguably a bit more readable.
Next, with a minimal change it becomes
splitWith :: (Char -> Bool) -> [Char] -> [[Char]]
splitWith p list = case g list of ([]:r)-> r; x->x
where
g [] = [[]]
g (x:xs)
| p x = case z of []-> r; -- start a new word IF not already
_ -> []:r
| otherwise = (x:z):zs
where -- now z,zs are accessible
r#(z:zs) = g xs -- in both cases
which works as you wanted. The top-level case is removing at most one empty word here, which serves as a separator marker at some point during the inner function's work. Your filter (not.null) is essentially fused into the worker function g here, with the conditional opening1 of a new word (i.e. addition1 of an empty list).
Replacing your let with where allowed for the variables (z etc.) to became accessible in both branches of the second clause of the g definition.
In the end, your algorithm was close enough, and the code could be fixed after all.
1 when thinking "right-to-left". In reality the list is constructed left-to-right, in guarded recursion ⁄ tail recursion modulo cons fashion.