Reputation: 642
How can I zip
two lists like
["Line1","Line2","Line3"]
["Line4","Line5"]
without discarding rest elements in first list?
I'd like to zip extra elements with empty list, if it can be done.
Upvotes: 14
Views: 8945
Reputation: 2996
I know this is an old question, but for the sake of documentation, a simpler solution would be:
{- | Zip two lists together, padding the shorter list with `Nothing` values so all values
in either list are conserved.
-}
zipPadded :: forall a b. [a] -> [b] -> [(Maybe a, Maybe b)]
zipPadded as bs =
zip ((Just <$> as) <> repeat Nothing) ((Just <$> bs) <> repeat Nothing)
& takeWhile (not . bothNothing)
where
bothNothing (Nothing, Nothing) = True
bothNothing _ = False
This can be composed with functions that fill in the default values, etc.
Upvotes: 0
Reputation: 11
Sometimes I don't want to pad my list. For instance, when I want to zip equal length lists only. Here is a general purpose solution, which maybe returns any extra values if one list is longer.
zipWithSave :: (a -> b -> c) -> [a] -> [b] -> ([c],Maybe (Either [a] [b]))
zipWithSave f [] [] = ([],Nothing)
zipWithSave f [] bs = ([],Just (Right bs))
zipWithSave f as [] = ([],Just (Left as))
zipWithSave f (a:as) (b:bs) = (f a b : cs , sv)
where (cs, sv) = zipWithSave f as bs
Using (zps,svs) = zipWithSave f as bs
, svs
can be one of three cases: Just (Left x)
wherein leftovers from as
are returned as x
, Just (Right x)
wherein leftovers from bs
are returned, or Nothing
in the case of equal length lists.
Another general purpose one is to just supply extra functions for each case.
zipWithOr :: (a -> b -> c) -> (a -> c) -> (b -> c) -> [a] -> [b] -> [c]
zipWithOr _ _ _ [] [] = []
zipWithOr _ _ fb [] bs = map fb bs
zipWithOr _ fa _ as [] = map fa as
zipWithOr f fa fb (a:as) (b:bs) = (f a b) : zipWithOr f fa fb as bs
This is just an elaboration of Zeta's approach. That function is then implemented as (using {-# LANGUAGE TupleSections #-}):
zipWithPadding a b as bs = zipWithOr (,) (,b) (a,) as bs
Upvotes: 1
Reputation: 1080
I think it will be much simple for you if you are new one in programming in Haskell
zip' :: [String] -> [String] ->[(String,String)]
zip' [][] = []
zip' (x:xs)[] = bmi x : zip' xs []
where bmi x = (x,"")
zip' [](x:xs) = bmi x : zip' [] xs
where bmi x = ("",x)
zip' (x:xs) (y:ys) = bmi x y : zip' xs ys
where bmi x y = (x,y)
Upvotes: 1
Reputation: 1091
An alternative implementation of Reite's solution, using higher order functions, just for fun. :) Possibly slower, though, since I guess the length functions will require additional traversals of the lists.
import Data.Monoid (mempty)
zipPad :: (Monoid a, Monoid b) => [a] -> [b] -> [(a,b)]
zipPad xs ys = take maxLength $ zip (pad xs) (pad ys)
where
maxLength = max (length xs) (length ys)
pad v = v ++ repeat mempty
Upvotes: 1
Reputation: 1667
Another solution is to make a zip function that works on monoids and fills in the missing values with mempty:
import Data.Monoid
mzip :: (Monoid a, Monoid b) => [a] -> [b] -> [(a, b)]
mzip (a:as) (b:bs) = (a, b) : mzip as bs
mzip [] (b:bs) = (mempty, b) : mzip [] bs
mzip (a:as) [] = (a, mempty) : mzip as []
mzip _ _ = []
> mzip ["Line1","Line2","Line3"] ["Line4","Line5"]
[("Line1","Line4"),("Line2","Line5"),("Line3","")]
Upvotes: 10
Reputation: 105876
zipWithPadding :: a -> b -> [a] -> [b] -> [(a,b)]
zipWithPadding a b (x:xs) (y:ys) = (x,y) : zipWithPadding a b xs ys
zipWithPadding a _ [] ys = zip (repeat a) ys
zipWithPadding _ b xs [] = zip xs (repeat b)
As long as there are elements, we can simply zip them. As soon as we run out of elements, we simply zip the remaining list with an infinite list of the padding element.
In your case, you would use this as
zipWithPadding "" "" ["Line1","Line2","Line3"] ["Line4","Line5"]
-- result: [("Line1","Line4"),("Line2","Line5"),("Line3","")]
Upvotes: 16