Adding zeros between elements in list? - list

I'm trying to change a list in haskell to include 0 between every element. If we have initial list [1..20] then i would like to change it to [1,0,2,0,3..20]
What i thought about doing is actually using map on every function, extracting element then adding it to list and use ++[0] to it but not sure if this is the right approach or not. Still learning haskell so might have errors.
My code:
x = map classify[1..20]
classify :: Int -> Int
addingFunction 0 [Int]
addingFunction :: Int -> [a] -> [a]
addingFunction x xs = [a] ++ x ++ xs

intersperse is made for this. Just import Data.List (intersperse), then intersperse 0 yourList.

You cannot do this with map. One of the fundamental properties of map is that its output will always have exactly as many items as its input, because each output element corresponds to one input, and vice versa.
There is a related tool with the necessary power, though:
concatMap :: (a -> [b]) -> [a] -> [b]
This way, each input item can produce zero or more output items. You can use this to build the function you wanted:
between :: a -> [a] -> [a]
sep `between` xs = drop 1 . concatMap insert $ xs
where insert x = [sep, x]
0 `between` [1..10]
[1,0,2,0,3,0,4,0,5,0,6,0,7,0,8,0,9,0,10]
Or a more concise definition of between:
between sep = drop 1 . concatMap ((sep :) . pure)

With simple pattern matching it should be:
addingFunction n [] = []
addingFunction n [x] = [x]
addingFunction n (x:xs) = x: n : (addingFunction n xs)
addingFunction 0 [1..20]
=> [1,0,2,0,3,0,4,0,5,0,6,0,7,0,8,0,9,0,10,0,11,0,12,0,13,0,14,0,15,0,16,0,17,0,18,0,19,0,20]

If you want to use map to solve this, you can do something like this:
Have a function that get a int and return 2 element list with int and zero:
addZero :: List
addZero a = [0, a]
Then you can call map with this function:
x = map addZero [1..20] -- this will return [[0,1], [0, 2] ...]
You will notice that it is a nested list. That is just how map work. We need a way to combine the inner list together into just one list. This case we use foldl
combineList :: [[Int]] -> [Int]
combineList list = foldl' (++) [] list
-- [] ++ [0, 1] ++ [0, 2] ...
So the way foldl work in this case is that it accepts a combine function, initial value, and the list to combine.
Since we don't need the first 0 we can drop it:
dropFirst :: [Int] -> [Int]
dropFirst list = case list of
x:xs -> xs
[] -> []
Final code:
x = dropFirst $ combineList $ map addZero [1..20]
addZero :: Int -> [Int]
addZero a = [0, a]
combineList :: [[Int]] -> [Int]
combineList list = foldl (++) [] list
dropFirst :: [Int] -> [Int]
dropFirst list = case list of
x:xs -> xs
[] -> []

We here can make use of a foldr pattern where for each element in the original list, we prepend it with an 0:
addZeros :: Num a => [a] -> [a]
addZeros [] = []
addZeros (x:xs) = x : foldr (((0 :) .) . (:)) [] xs

If you don't want to use intersperse, you can write your own.
intersperse :: a -> [a] -> [a]
intersperse p as = drop 1 [x | a <- as, x <- [p, a]]
If you like, you can use Applicative operations:
import Control.Applicative
intersperse :: a -> [a] -> [a]
intersperse p as = drop 1 $ as <**> [const p, id]
This is basically the definition used in Data.Sequence.

Related

Sum corresponding elements of two lists, with the extra elements of the longer list added at the end

I'm trying to add two lists together and keep the extra elements that are unused and add those into the new list e.g.
addLists [1,2,3] [1,3,5,7,9] = [2,5,8,7,9]
I have this so far:
addLists :: Num a => [a] -> [a] -> [a]
addLists xs ys = zipWith (+) xs ys
but unsure of how to get the extra elements into the new list.
and the next step is changing this to a higher order function that takes the combining function
as an argument:
longZip :: (a -> a -> a) -> [a] -> [a] -> [a]
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] is implemented as [src]:
zipWith :: (a->b->c) -> [a]->[b]->[c]
zipWith f = go
where
go [] _ = []
go _ [] = []
go (x:xs) (y:ys) = f x y : go xs ys
It thus uses explicit recursion where go will check if the two lists are non-empty and in that case yield f x y, otherwise it stops and returns an empty list [].
You can implement a variant of zipWith which will continue, even if one of the lists is empty. THis will look like:
zipLongest :: (a -> a -> a) -> [a] -> [a] -> [a]
zipLongest f = go
where go [] ys = …
go xs [] = …
go (x:xs) (y:ys) = f x y : go xs ys
where you still need to fill in ….
You can do it with higher order functions as simple as
import Data.List (transpose)
addLists :: Num a => [a] -> [a] -> [a]
addLists xs ys = map sum . transpose $ [xs, ys]
because the length of transpose[xs, ys, ...] is the length of the longest list in its argument list, and sum :: (Foldable t, Num a) => t a -> a is already defined to sum the elements of a list (since lists are Foldable).
transpose is used here as a kind of a zip (but cutting on the longest instead of the shortest list), with [] being a default element for the lists addition ++, like 0 is a default element for the numbers addition +:
cutLongest [xs, ys] $
zipWith (++) (map pure xs ++ repeat []) (map pure ys ++ repeat [])
See also:
Zip with default value instead of dropping values?
You're looking for the semialign package. It gives you an operation like zipping, but that keeps going until both lists run out. It also generalizes to types other than lists, such as rose trees. In your case, you'd use it like this:
import Data.Semialign
import Data.These
addLists :: (Semialign f, Num a) => f a -> f a -> f a
addLists = alignWith (mergeThese (+))
longZip :: Semialign f => (a -> a -> a) -> f a -> f a -> f a
longZip = alignWith . mergeThese
The new type signatures are optional. If you want, you can keep using your old ones that restrict them to lists.

Breaking up a list into sublists with recursion

I'm trying to write a function with the type declaration [(Int, Bool)] -> [[Int]]. I want the function to only add Ints to the same nested sublist if the Boolean is True. However if the Boolean is False, I want the Int associated with the next True bool to be added to a new sublist. For example: An input of
[(1,True),(2,True),(3,False),(4,True),(5,False),(6,False),(7,True)]
should return
[[1,2],[4],[7]].
My code so far:
test:: [(Int, Bool)] -> [[Int]]
test xs = case xs of
[]->[]
x:xs
| snd x == True -> [(fst x)] : test xs
| snd x == False -> test xs
I'm currently having issues on adding concurrent Ints to the same list if their bools are both True.
You can break this problem into two sub-problems.
For any given list, take the head of this list and match it against the rest of list. There are two possibilities during this matching: i) You are successful i.e. you match, and if so, you collect the matched value and continue looking for more values, or ii) You fail, i.e. you don't match, and if so, you stop immediately and return the so far matched result with rest of, not-inspected, list.
collectF :: (Eq a) => (a -> Bool) -> [a] -> ([a], [a])
collectF f [] = ([], [])
collectF f (x : xs)
| f x = let (ys, zs) = collectF f xs in (x : ys, zs)
| otherwise = ([], x : xs)
Now that you have the collectF function, you can use it recursively on input list. In each call, you would get a successful list with rest of, not-inspected, list. Apply collectF again on rest of list until it is exhausted.
groupBy :: (Eq a) => (a -> a -> Bool) -> [a] -> [[a]]
groupBy _ [] = []
groupBy f (x : xs) =
let (ys, zs) = collectF (f x) xs in
(x : ys) : groupBy f zs
*Main> groupBy (\x y -> snd x == snd y) [(1,True),(2,True),(3,False),(4,True),(5,False),(6,False),(7,True)]
[[(1,True),(2,True)],[(3,False)],[(4,True)],[(5,False),(6,False)],[(7,True)]]
I am leaving it to you to remove the True and False values from List. Also, have a look at List library of Haskell [1]. Hope, I am clear enough, but let me know if you have any other question.
[1] http://hackage.haskell.org/package/base-4.12.0.0/docs/src/Data.OldList.html#groupBy
Repeatedly, drop the Falses, grab the Trues. With view patterns:
{-# LANGUAGE ViewPatterns #-}
test :: [(a, Bool)] -> [[a]]
test (span snd . dropWhile (not . snd) -> (a,b))
| null a = []
| otherwise = map fst a : test b
Works with infinite lists as well, inasmuch as possible.
Here's how I'd write this:
import Data.List.NonEmpty (NonEmpty(..), (<|))
import qualified Data.List.NonEmpty as NE
test :: [(Int, Bool)] -> [[Int]]
test = NE.filter (not . null) . foldr go ([]:|[])
where
go :: (Int, Bool) -> NonEmpty [Int] -> NonEmpty [Int]
go (n, True) ~(h:|t) = (n:h):|t
go (n, False) l = []<|l
Or with Will Ness's suggestion:
import Data.List.NonEmpty (NonEmpty(..))
test :: [(Int, Bool)] -> [[Int]]
test = removeHeadIfEmpty . foldr prependOrStartNewList ([]:|[])
where
prependOrStartNewList :: (Int, Bool) -> NonEmpty [Int] -> NonEmpty [Int]
prependOrStartNewList (n, True) ~(h:|t) = (n:h):|t
prependOrStartNewList (n, False) l = []:|removeHeadIfEmpty l
removeHeadIfEmpty :: NonEmpty [Int] -> [[Int]]
removeHeadIfEmpty (h:|t) = if null h then t else h:t

Replicating through a list in Haskell

replicatee :: [a] -> Int -> [a]
replicatee [] _ = []
replicatee xs 0 = []
replicatee (x:xs) n = x:replicatee (x:xs) (n-1): replicatee xs n
So this is my code for replicating a an element in a list n times, the compler keeps showing an error :
Couldnt match type 'a'with [a], I'm seriously confused, please help out.
Edit : what i want my function to do is this:
replicatee [1,2,3,4] 2
[1,1,2,2,3,3,4,4]
I might have misunderstood your intention, but maybe you meant something like this:
replicatee :: a -> Int -> [a]
replicatee _ 0 = []
replicatee x n = x:replicatee x (n-1)
replicatee :: [a] -> Int -> [a]
replicatee [] _ = []
replicatee xs 0 = []
replicatee (x:xs) n = x:replicatee (x:xs) (n-1): replicatee xs n
The problem is that replicatee returns a value of type [a], but you try to add that to another list of type [a] using (:) :: a -> [a] -> [a]. From a type-checking perspective, you need to use (++), not (:):
replicatee xs'#(x:xs) n = x : (replicatee xs' (n-1) ++ replicatee xs n)
Whether it does what you intended is another matter. Based on your description, Mikkel provides the right answer.

Selecting string elements in a list using integer elements from another list

I'm going to use an example to explain my question because I'm not sure the best way to put it into words.
Lets say I have two lists a and b:
a = ["car", "bike", "train"] and b = [1, 3]
And I want to create a new list c by selecting the items in a whose positions correspond to the integers in b, so list c = ["car", "train"]
How would I do this in Haskell? I think I have to use list comprehension but am unsure how. Cheers.
The straightfoward way to do this is using the (!!) :: [a] -> Int -> a operator that, for a given list and zero-based index, gives the i-th element.
So you could do this with the following list comprehension:
filterIndex :: [a] -> [Int] -> [a]
filterIndex a b = [a!!(i-1) | i <- b]
However this is not efficient since (!!) runs in O(k) with k the index. Usually if you work with lists you try to prevent looking up the i-th index.
In case it is guaranteed that b is sorted, you can make it more efficient with:
-- Only if b is guaranteed to be sorted
filterIndex = filterIndex' 1
where filterIndex' _ _ [] = []
filterIndex' i a:as2 js#(j:js2) | i == j = a : tl js2
| otherwise = tl js
where tl = filterIndex' (i+1) as2
Or even more efficient:
-- Only if b is guaranteed to be sorted
filterIndex = filterIndex' 1
where filterIndex' i l (j:js) | (a:as) <- drop (j-i) l = a : filterIndex' (j+1) as (js)
filterIndex' _ _ [] = []
I am going to assume you're using b = [0, 2] instead (lists are 0 indexed in Haskell).
You can use a fold to build the new list:
selectIndices :: [a] -> [Int] -> [a]
selectIndices as is = foldr (\i bs -> as !! i : bs) [] is
This starts with an empty list and adds new elements by selecting them from the list of as using an index i from the list of indices is.
More advanced: if you prefer a point-free style, the same function can be written:
selectIndices :: [a] -> [Int] -> [a]
selectIndices as = foldr ((:) . (as !!)) []
Another approach which could be more efficient if the indices are sorted would be to go through the list one element at a time while keeping track of the current index:
selectIndices :: [a] -> [Int] -> [a]
selectIndices as is = go as 0 (sort is)
where
go :: [a] -> Int -> [Int] -> [a]
go [] _ _ = []
go _ _ [] = []
go (a:as) n (i:is)
| n == i = a : go as (n + 1) is
| otherwise = go as (n + 1) (i:is)
A simple approach is tagging the values in a with the indices and then filtering according to the indices:
filterIndex :: [Int] -> [a] -> [a]
filterIndex b = fmap snd . filter (\(i, _) -> i `elem` b) . zip [1..]
-- non-point-free version:
-- filterIndex b a = fmap snd (filter (\(i, _) -> i `elem` b) (zip [1..] a))
(If you want zero-based rather than one-based indexing, just change the infinite list to [0..]. You can even parameterise it with something like [initial..].)
If you need to make this more efficient, you might consider, among other things, a filtering algorithm that exploits ordering in b (cf. the answers by Boomerang and Willem Van Onsem), and building a dictionary from the zip [1..] a list of pairs.

Repeatedly call a function: Haskell

Basically, I want to create a function that takes a list of integers and another list (this list can be of any type) and produce another list that has the elements in it from the "other list" at intervals specified by the list of integers. If I input:
ixs [2,3,1] [3,2,1]
[2,1,3]
So far I have:
ix :: Int -> [a] -> a
ix a [] = error "Empty list"
ix 1 (x:xs) = x
ix a (x:xs) = ix (a-1) xs
ixs :: [Int] -> [a] -> [a]
ixs [] _ = []
ixs _ [] = []
ixs (x:xs) (y) = ix x y: []
With this code I only get one value returned like so:
ixs [1,2] [2,1]
[2]
How can I call the ix function repeatedly on (x:xs) so that it returns all the values I want?
Edit: I want to do this without using any standard prelude functions. I just want to use recursion.
This is (almost) a map of an indexing ("getting the value at") of the first list over the second list
import Data.List ((!!))
-- (!!) :: [a] -> Int -> a
ixs :: [Int] -> [b] -> [b]
ixs ary ixes = map (ary !!) ixes
But you also have wraparound when you index a 3-element list by (3 mod 3 = 0), so we ought to just map mod over the indexes
ixs ary ixes = map (ary !!) (map (`mod` length ary) ixes)
And then we can simplify to "pointless style"
ixs ary = map (ary !!) . map (`mod` length ary)
which reads nicely as "map the indices modulo the array length then map the array indexing over the resultant indices". And it gives the right result
> ixs [2,3,1] [3,2,1]
[2,1,3]
To break down the Prelude function and Data.List function, we have
(!!) :: [b] -> Int -> b
(x:_) !! 0 = x
(_:xs) !! n
| n > 0 = xs !! (n-1)
| otherwise = error "List.(!!): negative argument."
_ !! _ = error "List.(!!): index too large."
and
map :: (a -> b) -> [a] -> [b]
map _ [] = []
map f (x:xs) = f x : map f xs
You could reverse the order of the arguments
ix' :: [a] -> Int -> a
ix' [] a = error "Empty list"
ix' (x:xs) 1 = x
ix' (x:xs) a = ix' xs (a-1)
to make it easier to map ix over a list of indeces:
ixs' :: [a] -> [Int] -> [a]
ixs' xs is = map (ix' xs) is
Like this:
> ixs' "Hello Mum" [1,5,6,1,5,6,1,5]
"Ho Ho Ho"
but it would be nicer to use flip to swap the arguments - ix' is just flip ix, so you could do
ixs :: [Int] -> [a] -> [a]
ixs is xs = map (flip ix xs) is
which you then call the way round you'd planned:
> ixs [1,5,6,1,5,6,1,5] "Hello Mum"
"Ho Ho Ho"
Perhaps something like this
ixs :: [Int] -> [a] -> [a]
ixs idx a = map (`ix` a) idx
What you want to do is map your index function across all the values in the list of
indices to index the second list. Note that your ix function is just !! function, but starts indexing from 1 instead of 0.