Is there a function to flatten a nested list of elements? - list

How can I flatten a nested list like this:
[1, 2, 3, 4] == flatten [[[1,2],[3]],[[4]]]

Yes, it’s concat from the Standard Prelude, given by
concat :: [[a]] -> [a]
concat xss = foldr (++) [] xss
If you want to turn [[[a]]] into [a], you must use it twice:
Prelude> (concat . concat) [[[1,2],[3]],[[4]]]
[1,2,3,4]

Since nobody else has given this, it is possible to define a function which will flatten lists of an arbitrary depth by using MultiParamTypeClasses. I haven't actually found it useful, but hopefully it could be considered an interesting hack. I got the idea from Oleg's polyvariadic function implementation.
{-# LANGUAGE MultiParamTypeClasses, OverlappingInstances, FlexibleInstances #-}
module Flatten where
class Flatten i o where
flatten :: [i] -> [o]
instance Flatten a a where
flatten = id
instance Flatten i o => Flatten [i] o where
flatten = concatMap flatten
Now if you load it and run in ghci:
*Flatten> let g = [1..5]
*Flatten> flatten g :: [Integer]
[1,2,3,4,5]
*Flatten> let h = [[1,2,3],[4,5]]
*Flatten> flatten h :: [Integer]
[1,2,3,4,5]
*Flatten> let i = [[[1,2],[3]],[],[[4,5],[6]]]
*Flatten> :t i
i :: [[[Integer]]]
*Flatten> flatten i :: [Integer]
[1,2,3,4,5,6]
Note that it's usually necessary to provide the result type annotation, because otherwise ghc can't figure out where to stop recursively applying the flatten class method. If you use a function with a monomorphic type that's sufficient however.
*Flatten> :t sum
sum :: Num a => [a] -> a
*Flatten> sum $ flatten g
<interactive>:1:7:
No instance for (Flatten Integer a0)
arising from a use of `flatten'
Possible fix: add an instance declaration for (Flatten Integer a0)
In the second argument of `($)', namely `flatten g'
In the expression: sum $ flatten g
In an equation for `it': it = sum $ flatten g
*Flatten> let sumInt = sum :: [Integer] -> Integer
*Flatten> sumInt $ flatten g
15
*Flatten> sumInt $ flatten h
15

As others have pointed out, concat :: [[a]] -> [a] is the function you are looking for, and it can't flatten nested lists of arbitrary depth. You need to call it multiple times to flatten it down to the desired level.
The operation does generalize to other monads, though. It is then known as join, and has the type Monad m => m (m a) -> m a.
Prelude Control.Monad> join [[1, 2], [3, 4]]
[1,2,3,4]
Prelude Control.Monad> join (Just (Just 3))
Just 3
Prelude Control.Monad.Reader> join (+) 21
42

import Data.List
let flatten = intercalate []
flatten $ flatten [[[1,2],[3]],[[4]]]
[1,2,3,4]

As hammar pointed out, join is the "monadic" way to flatten a list. You can use the do-Notation as well to write easily flatten functions of several levels:
flatten xsss = do xss <- xsss
xs <- xss
x <- xs
return x

An arbitrarily nested list can be approximated by a Data.Tree, which can be flattened by the appropriately named function flatten.
I say approximated because Data.Tree allows a data item to be attached to every node, not just the leaves. However, you could create a Data.Tree (Maybe a), and attach Nothing to the body nodes, and flatten with catMaybes . flatten.

You can remove one level of nesting using concat, and consequently you can apply n levels of nesting by applying concat n times.
It is not possible to write a function which removes an arbitrary level of nestings, as it is not possible to express the type of a function, which takes an arbitrarily nested list and returns a flat list, using Haskell's type system (using the list datatype that is - you can write your own datatype for arbitrarily nested lists and write a flatten function for that).

Related

Creating a list of all possible lists, given each element can take one of n values

In Haskell I'm trying to create a function with the typing Int -> [a] -> [[a]], that generates a list such as: [[0, 0], [0, 1], [1, 0], [1, 1]] where each element in the smaller lists can take the value of either 1 or 0. Each of the smaller lists has the same size, which in this case is 2. If the size of the smaller lists was 3, I would expect to get the output [[0,0,0], [0,0,1], [0,1,0], [1,0,0], [1,1,0], [0,1,1], [1,0,1], [1,1,1]]
I've looked in to the permutations function, but this does not achieve exactly what I want. I believe there is also a variate function, but I cannot access this library.
Rather than the exact function (which would also be useful), what would be the process to generate such a list?
As oisdk mentions in a comment, a more general version of this exact function is already defined, with the name Control.Monad.replicateM:
Prelude> import Control.Monad (replicateM)
Prelude Control.Monad> replicateM 3 [0,1]
[[0,0,0],[0,0,1],[0,1,0],[0,1,1],[1,0,0],[1,0,1],[1,1,0],[1,1,1]]
We can use the list monad for this:
example :: [[Int]]
example = do
x <- [0,1]
y <- [0,1]
pure [x,y]
ghci> example
[[0,0],[0,1],[1,0],[1,1]]
Play with this. Then you should be able to combine it with recursion on n to create the function you need.
I'm not sure I understood the specification, but from the examples, one possible definition is
lists :: Int -> [[Int]]
lists 0 = [[]]
lists n = map (0:) xss ++ map (1:) xss
where xss = lists (n-1)
-- λ> lists 2
-- [[0,0],[0,1],[1,0],[1,1]]
-- λ> lists 3
-- [[0,0,0],[0,0,1],[0,1,0],[0,1,1],[1,0,0],[1,0,1],[1,1,0],[1,1,1]]
Another definition, using comprehension instead of map, is
lists :: Int -> [[Int]]
lists 0 = [[]]
lists n = [x:xs | x <- [0,1], xs <- lists (n-1)]
-- λ> lists 2
-- [[0,0],[0,1],[1,0],[1,1]]
-- λ> lists 3
-- [[0,0,0],[0,0,1],[0,1,0],[0,1,1],[1,0,0],[1,0,1],[1,1,0],[1,1,1]]
You can use the sequence function.
Like this:
λ>
λ> :t sequence
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
λ>
λ> let { allLists :: Int -> [a] -> [[a]] ; allLists n xs = sequence $ replicate n xs ; }
λ>
λ> allLists 3 [0,1]
[[0,0,0],[0,0,1],[0,1,0],[0,1,1],[1,0,0],[1,0,1],[1,1,0],[1,1,1]]
λ>

Get the first elements of a list of tuples

I have this list of tuples
[(4,'a'), (1,'b'), (2,'c'), (2,'a'), (1,'d'), (4,'e')]
I want to get the first elements of every tuple then replicate it to make the following: "aaaabccaadeeee"
I came up with this code, but it only gives me the replicate of the first tuple.
replicate (fst ( head [(4,'a'), (1,'b')])) ( snd ( head [(4,'a'), (1,'b')]))
--output is: "aaaa"
I was thinking to use map for to get the replicate of every tuple, but I didn't succeed.
Since you already know how to find the correct answer for a single element, all you need is a little recursion
func :: [(Int, a)] -> [a]
func [] = []
func ((n, elem):rest) = (replicate n elem) ++ (func rest)
Mapping the values should also work. You just need to concatenate the resulting strings into one.
func :: [(Int, a)] -> [a]
func xs = concat $ map func2 xs where
func2 (n, elem) = replicate n elem
Or, if you are familiar with currying:
func :: [(Int, a)] -> [a]
func xs = concat $ map (uncurry replicate) xs
Finally, if you are comfortable using function composition, the definition becomes:
func :: [(Int, a)] -> [a]
func = concat . map (uncurry replicate)
Using concat and map is so common, there is a function to do just that. It's concatMap.
func :: [(Int, a)] -> [a]
func = concatMap (uncurry replicate)
Let
ls = [(4,'a'), (1,'b'), (2,'c'), (2,'a'), (1,'d'), (4,'e')]
in
concat [replicate i x | (i, x) <- ls]
will give
"aaaabccaadeeee"
The point-free version
concat . map (uncurry replicate)
You are correct about trying to use map. But first lets see why your code did not work
replicate (fst ( head [(4,'a'), (1,'b')])) ( snd ( head [(4,'a'), (1,'b')]))
Your first parameter to replicate is the head of your list which is (4, 'a'). Then you are calling fst on this, thus the first parameter is 4. Same things happens with second parameter and you get 'a'. The result of which you see.
Before using map lets try to do this with recursion. You want to take one element of list and apply replicate to it and then combine it with the result of applying replicate on the second element.
generate [] = []
generate (x:xs) = replicate (fst x) (snd x) ++ generate xs
Do note I am using pattern matching to get the first element of list. You can us the pattern matching to get the element inside the tuple as well, and then you would not need to use the fst/snd functions. Also note I am using pattern matching to define the base case of empty list.
generate [] = []
generate ((x,y):xs) = replicate x y ++ generate xs
Now coming to map, so map will apply your function to every element of the list, here's the first try
generate (x,y) = replicate x y
map generate xs
The result of the above will be slightly different from recursion. Think about it, map is going to apply generate to every element and store the result in a list. generate creates a list. So when you apply map you are creating a list of list. You can use concat to flatten it if you want, which will give you the same result as recursion.
Last thing, if you can use recursion, then you can use fold as well. Fold will just apply a function to every element of the list and return the accumulated results (broadly speaking).
--first parameter is the function to apply, second is the accumulator, third is your list
foldr step [] xs
where step (x,y) acc =
(replicate x y) ++ acc
Again here I have used pattern matching in the function step to extract the elements of the tuple out.

Haskell - how to iterate list elements in reverse order in an elegant way?

I'm trying to write a function that given a list of numbers, returns a list where every 2nd number is doubled in value, starting from the last element. So if the list elements are 1..n, n-th is going to be left as-is, (n-1)-th is going to be doubled in value, (n-2)-th is going to be left as-is, etc.
So here's how I solved it:
MyFunc :: [Integer] -> [Integer]
MyFunc xs = reverse (MyFuncHelper (reverse xs))
MyFuncHelper :: [Integer] -> [Integer]
MyFuncHelper [] = []
MyFuncHelper (x:[]) = [x]
MyFuncHelper (x:y:zs) = [x,y*2] ++ MyFuncHelper zs
And it works:
MyFunc [1,1,1,1] = [2,1,2,1]
MyFunc [1,1,1] = [1,2,1]
However, I can't help but think there has to be a simpler solution than reversing the list, processing it and then reversing it again. Could I simply iterate the list backwards? If yes, how?
The under reversed f xs idiom from the lens library will apply f to xs in reverse order:
under reversed (take 5) [1..100] => [96,97,98,99,100]
When you need to process the list from the end, usually foldr works pretty well. Here is a solution for you without reversing the whole list twice:
doubleOdd :: Num a => [a] -> [a]
doubleOdd = fst . foldr multiplyCond ([], False)
where multiplyCond x (rest, flag) = ((if flag then (x * 2) else x) : rest, not flag)
The multiplyCond function takes a tuple with a flag and the accumulator list. The flag constantly toggles on and off to track whether we should multiply the element or not. The accumulator list simply gathers the resulting numbers. This solution may be not so concise, but avoids extra work and doesn't use anything but prelude functions.
myFunc = reverse
. map (\(b,x) -> if b then x*2 else x)
. zip (cycle [False,True])
. reverse
But this isn't much better. Your implementation is sufficiently elegant.
The simplest way to iterate the list backwards is to reverse the list. I don't think you can really do much better than that; I suspect that if you have to traverse the whole list to find the end, and remember how to get back up, you might as well just reverse it. If this is a big deal, maybe you should be using some other data structure instead of lists—Vector or Seq might be good choices.
Another way to write your helper function is to use Traversable:
import Control.Monad.State
import Data.Traversable (Traversable, traverse)
toggle :: (Bool -> a -> b) -> a -> State Bool b
toggle f a =
do active <- get
put (not active)
return (f active a)
doubleEvens :: (Num a, Traversable t) => t a -> t a
doubleEvens xs = evalState (traverse (toggle step) xs) False
where step True x = 2*x
step False x = x
yourFunc :: Num a => [a] -> [a]
yourFunc = reverse . doubleEvens
Or if we go a bit crazy with Foldable and Traversable, we can try this:
Use Foldable's foldl to extract a reverse-order list from any of its instances. For some types this will be more efficient than reversing a list.
Then we can use traverse and State to map each element of the original structure to its counterpart in the reversed order.
Here's how to do it:
import Control.Monad.State
import Data.Foldable (Foldable)
import qualified Data.Foldable as F
import Data.Traversable (Traversable, traverse)
import Data.Map (Map)
import qualified Data.Map as Map
toReversedList :: Foldable t => t a -> [a]
toReversedList = F.foldl (flip (:)) []
reverse' :: Traversable t => t a -> t a
reverse' ta = evalState (traverse step ta) (toReversedList ta)
where step _ = do (h:t) <- get
put t
return h
yourFunc' :: (Traversable t, Num a) => t a -> t a
yourFunc' = reverse' . doubleEvens
-- >>> yourFunc' $ Map.fromList [(1, 1), (2, 1), (3, 1), (4, 1)]
-- fromList [(1,2),(2,1),(3,2),(4,1)]
-- >>> yourFunc' $ Map.fromList [(1, 1), (2, 1), (3, 1)]
-- fromList [(1,1),(2,2),(3,1)]
There's probably a better way to do this, though...
func xs = zipWith (*) xs $ reverse . (take $ length xs) $ cycle [1,2]

Flatten a list of lists

I have to write a function that flattens a list of lists.
For example flatten [] = [] or flatten [1,2,3,4] = [1,2,3,4] or flatten [[1,2],[3],4,5]] = [1,2,3,4,5]
I'm having trouble with the being able to match the type depending on what is given to the flatten function.
Here's what I have:
data A a = B a | C [a] deriving (Show, Eq, Ord)
flatten::(Show a, Eq a, Ord a)=>A a -> A a
flatten (C []) = (C [])
flatten (C (x:xs) ) = (C flatten x) ++ (C flatten xs)
flatten (B a) = (C [a])
From what I can tell the issue is that the ++ operator is expecting a list for both of its arguments and I'm trying to give it something of type A. I've added the A type so the function can either get a single element or a list of elements.
Does anyone know a different way to do this differently, or explain what I can do to fix the type error?
It's a bit unclear what you are asking for, but flattening a list of list is a standard function called concat in the prelude with type signature [[a]] -> [a].
If you make a data type of nested lists as you have started above, maybe you want to adjust your data type to something like this:
data Lists a = List [a] | ListOfLists [Lists a]
Then you can flatten these to a list;
flatten :: Lists a -> [a]
flatten (List xs) = xs
flatten (ListOfLists xss) = concatMap flatten xss
As a test,
> flatten (ListOfLists [List [1,2],List [3],ListOfLists [List [4],List[5]]])
[1,2,3,4,5]
Firstly, the A type is on the right track but I don't think it's quite correct. You want it to be able to flatten arbitrarily nested lists, so a value of type "A a" should be able to contain values of type "A a":
data A a = B a | C [A a]
Secondly, the type of the function should be slightly different. Instead of returning a value of type "A a", you probably want it to return just a list of a, since by definition the function is always returning a flat list. So the type signature is thus:
flatten :: A a -> [a]
Also note that no typeclass constraints are necessary -- this function is completely generic since it does not look at the list's elements at all.
Here's my implementation:
flatten (B a) = [a]
flatten (C []) = []
flatten (C (x:xs)) = flatten x ++ flatten (C xs)
this one liner will do the job. Although as it was mentioned by Malin the type signature is different:
flatten :: [[a]] -> [a]
flatten xs = (\z n -> foldr (\x y -> foldr z y x) n xs) (:) []
simple test
frege> li = [[3,4,2],[1,9,9],[5,8]]
frege> flatten li
[3,4,2,1,9,9,5,8]
Flatten via list comprehension.
flatten arr = [y | x<- arr, y <- x]

Apply "permutations" of a function over a list

Creating the permutations of a list or set is simple enough. I need to apply a function to each element of all subsets of all elements in a list, in the order in which they occur. For instance:
apply f [x,y] = { [x,y], [f x, y], [x, f y], [f x, f y] }
The code I have is a monstrous pipeline or expensive computations, and I'm not sure how to proceed, or if it's correct. I'm sure there must be a better way to accomplish this task - perhaps in the list monad - but I'm not sure. This is my code:
apply :: Ord a => (a -> Maybe a) -> [a] -> Set [a]
apply p xs = let box = take (length xs + 1) . map (take $ length xs) in
(Set.fromList . map (catMaybes . zipWith (flip ($)) xs) . concatMap permutations
. box . map (flip (++) (repeat Just)) . flip iterate []) ((:) p)
The general idea was:
(1) make the list
[[], [f], [f,f], [f,f,f], ... ]
(2) map (++ repeat Just) over the list to obtain
[[Just, Just, Just, Just, ... ],
[f , Just, Just, Just, ... ],
[f , f , Just, Just, ... ],
... ]
(3) find all permutations of each list in (2) shaved to the length of the input list
(4) apply the permuted lists to the original list, garnering all possible applications
of the function f to each (possibly empty) subset of the original list, preserving
the original order.
I'm sure there's a better way to do it, though. I just don't know it. This way is expensive, messy, and rather prone to error. The Justs are there because of the intended application.
To do this, you can leverage the fact that lists represent non-deterministic values when using applicatives and monads. It then becomes as simple as:
apply f = mapM (\x -> [x, f x])
It basically reads as follows: "Map each item in a list to itself and the result of applying f to it. Finally, return a list of all the possible combinations of these two values across the whole list."
If I understand your problem correctly, it's best not to describe it in terms of permutations. Rather, it's closer to generating powersets.
powerset (x:xs) = let pxs = powerset xs in pxs ++ map (x :) pxs
powerset [] = [[]]
Each time you add another member to the head of the list, the powerset doubles in size. The second half of the powerset is exactly like the first, but with x included.
For your problem, the choice is not whether to include or exclude x, but whether to apply or not apply f.
powersetapp f (x:xs) = let pxs = powersetapp f xs in map (x:) pxs ++ map (f x:) pxs
powersetapp f [] = [[]]
This does what your "apply" function does, modulo making a Set out of the result.
Paul's and Heatsink's answers are good, but error out when you try to run them on infinite lists.
Here's a different method that works on both infinite and finite lists:
apply _ [] = [ [] ]
apply f (x:xs) = (x:ys):(x':ys):(double yss)
where x' = f x
(ys:yss) = apply f xs
double [] = []
double (ys:yss) = (x:ys):(x':ys):(double yss)
This works as expected - though you'll note it produces a different order to the permutations than Paul's and Heatsink's
ghci> -- on an infinite list
ghci> map (take 4) $ take 16 $ apply (+1) [0,0..]
[[0,0,0,0],[1,0,0,0],[0,1,0,0],[1,1,0,0],[0,0,1,0],...,[1,1,1,1]]
ghci> -- on a finite list
ghci> apply (+1) [0,0,0,0]
[[0,0,0,0],[1,0,0,0],[0,1,0,0],[1,1,0,0],[0,0,1,0],...,[1,1,1,1]]
Here is an alternative phrasing of rampion's infinite-input-handling solution:
-- sequence a list of nonempty lists
sequenceList :: [[a]] -> [[a]]
sequenceList [] = [[]]
sequenceList (m:ms) = do
xs <- nonempty (sequenceList ms)
x <- nonempty m
return (x:xs)
where
nonempty ~(x:xs) = x:xs
Then we can define apply in Paul's idiomatic style:
apply f = sequenceList . map (\x -> [x, f x])
Contrast sequenceList with the usual definition of sequence:
sequence :: (Monad m) => [m a] -> m [a]
sequence [] = [[]]
sequence (m:ms) = do
x <- m
xs <- sequence ms
return (x:xs)
The order of binding is reversed in sequenceList so that the variations of the first element are the "inner loop", i.e. we vary the head faster than the tail. Varying the end of an infinite list is a waste of time.
The other key change is nonempty, the promise that we won't bind an empty list. If any of the inputs were empty, or if the result of the recursive call to sequenceList were ever empty, then we would be forced to return an empty list. We can't tell in advance whether any of inputs is empty (because there are infinitely many of them to check), so the only way for this function to output anything at all is to promise that they won't be.
Anyway, this is fun subtle stuff. Don't stress about it on your first day :-)