Remove elements by index in haskell - list

I'm new in haskell and I'm looking for some standard functions to work with lists by indexes.
My exact problem is that i want to remove 3 elements after every 5. If its not clear enough here is illustration:
OOOOOXXXOOOOOXXX...
I know how to write huge function with many parameters, but is there any clever way to do this?

Two completely different approaches
You can use List.splitAt together with drop:
import Data.List (splitAt)
f :: [a] -> [a]
f [] = []
f xs = let (h, t) = splitAt 5 xs in h ++ f (drop 3 t)
Now f [1..12] yields [1,2,3,4,5,9,10,11,12]. Note that this function can be expressed more elegantly using uncurry and Control.Arrow.second:
import Data.List (splitAt)
import Control.Arrow (second)
f :: [a] -> [a]
f [] = []
f xs = uncurry (++) $ second (f . drop 3) $ splitAt 5 xs
Since we're using Control.Arrow anyway, we can opt to drop splitAt and instead call in the help of Control.Arrow.(&&&), combined with take:
import Control.Arrow ((&&&))
f :: [a] -> [a]
f [] = []
f xs = uncurry (++) $ (take 5 &&& (f . drop 8)) xs
But now it's clear that an even shorter solution is the following:
f :: [a] -> [a]
f [] = []
f xs = take 5 xs ++ (f . drop 8) xs
As Chris Lutz notes, this solution can then be generalized as follows:
nofm :: Int -> Int -> [a] -> [a]
nofm _ _ [] = []
nofm n m xs = take n xs ++ (nofm n m . drop m) xs
Now nofm 5 8 yields the required function. Note that a solution with splitAt may still be more efficient!
Apply some mathematics using map, snd, filter, mod and zip:
f :: [a] -> [a]
f = map snd . filter (\(i, _) -> i `mod` 8 < (5 :: Int)) . zip [0..]
The idea here is that we pair each element in the list with its index, a natural number i. We then remove those elements for which i % 8 > 4. The general version of this solution is:
nofm :: Int -> Int -> [a] -> [a]
nofm n m = map snd . filter (\(i, _) -> i `mod` m < n) . zip [0..]

Here is my take:
deleteAt idx xs = lft ++ rgt
where (lft, (_:rgt)) = splitAt idx xs

You can count your elements easily:
strip' (x:xs) n | n == 7 = strip' xs 0
| n >= 5 = strip' xs (n+1)
| n < 5 = x : strip' xs (n+1)
strip l = strip' l 0
Though open-coding looks shorter:
strip (a:b:c:d:e:_:_:_:xs) = a:b:c:d:e:strip xs
strip (a:b:c:d:e:xs) = a:b:c:d:e:[]
strip xs = xs

Since nobody did a version with "unfoldr", here is my take:
drop3after5 lst = concat $ unfoldr chunk lst
where
chunk [] = Nothing
chunk lst = Just (take 5 lst, drop (5+3) lst)
Seems to be the shortest thus far

the take and drop functions may be able to help you here.
drop, take :: Int -> [a] -> [a]
from these we could construct a function to do one step.
takeNdropM :: Int -> Int -> [a] -> ([a], [a])
takeNdropM n m list = (take n list, drop (n+m) list)
and then we can use this to reduce our problem
takeEveryNafterEveryM :: Int -> Int -> [a] -> [a]
takeEveryNafterEveryM n m [] = []
takeEveryNafterEveryM n m list = taken ++ takeEveryNafterEveryM n m rest
where
(taken, rest) = takeNdropM n m list
*Main> takeEveryNafterEveryM 5 3 [1..20]
[1,2,3,4,5,9,10,11,12,13,17,18,19,20]
since this is not a primitive form of recursion, it is harder to express this as a simple fold.
so a new folding function could be defined to fit your needs
splitReduce :: ([a] -> ([a], [a])) -> [a] -> [a]
splitReduce f [] = []
splitReduce f list = left ++ splitReduce f right
where
(left, right) = f list
then the definition of takeEveryNafterEveryM is simply
takeEveryNafterEveryM2 n m = splitReduce (takeNdropM 5 3)

This is my solution. It's a lot like #barkmadley's answer, using only take and drop, but with less clutter in my opinion:
takedrop :: Int -> Int -> [a] -> [a]
takedrop _ _ [] = []
takedrop n m l = take n l ++ takedrop n m (drop (n + m) l)
Not sure if it'll win any awards for speed or cleverness, but I think it's pretty clear and concise, and it certainly works:
*Main> takedrop 5 3 [1..20]
[1,2,3,4,5,9,10,11,12,13,17,18,19,20]
*Main>

Here is my solution:
remElements step num=rem' step num
where rem' _ _ []=[]
rem' s n (x:xs)
|s>0 = x:rem' (s-1) num xs
|n==0 = x:rem' (step-1) num xs
|otherwise= rem' 0 (n-1) xs
example:
*Main> remElements 5 3 [1..20]
[1,2,3,4,5,9,10,11,12,13,17,18,19,20]

myRemove = map snd . filter fst . zip (cycle $ (replicate 5 True) ++ (replicate 3 False))

Related

Replace all elements of a List

I have to replace all elements in a list by the number of occurrences of that element, like if I have "Taylor Swift" the result will be [1,1,1,1,1,1,1,1,1,1,1,1].
I already made the code to count the occurrences, I just know how to replace all elements by the number of they occurrence I already try:
ocurr :: [Char] -> Char -> Int
ocurr xs x = length(filter (x==) xs)
frequencias :: [Char] -> [Char]
frequencias "" = []
frequencias xs = [ ocurr xs y| y <- xs]
and
ocurr :: [Char] -> Char -> Int
ocurr xs x = length(filter (x==) xs)
frequencias :: [Char] -> [Char]
frequencias "" = []
frequencias xs = [x | y <- xs x = ocurr xs x]
but none of this works...
can anyone help me please?
This will not work since the return type you specify in frequencias is [Char], whereas the frequencies are, according to your occurr function, Ints. The special clause for an empty list is not necesary (although not wrong). You thus can work with:
frequencias :: [Char] -> [Int]
frequencias xs = [ ocurr xs y | y <- xs ]
you can also make use of a simple map :: (a -> b) -> [a] -> [b]:
frequencias :: [Char] -> [Int]
frequencias xs = map (ocurr xs) xs
This thus gives us:
Prelude> frequencias "Taylor Swift"
[1,1,1,1,1,1,1,1,1,1,1,1]
Prelude> frequencias "taylor swift"
[2,1,1,1,1,1,1,1,1,1,1,2]
All this filtering could get expensive. Here's an easy fix:
import qualified Data.IntMap.Strict as M
import Data.IntMap.Strict (IntMap)
import Data.Char (ord)
import Control.DeepSeq (force)
import Data.List (foldl')
frequencias :: [Char] -> [Int]
frequencias xs = force res
where
freq_map :: IntMap Int
freq_map = foldl' go M.empty xs
go fm c = M.insertWith (+) (ord c) 1 fm
res = map (\c -> case M.lookup (ord c) freq_map of
Just freq -> freq
Nothing -> error "impossible") xs
The force ensures that the frequency map will be garbage collected promptly; it's not necessary or probably desirable if the result is consumed promptly.
An alternative way to prevent a memory leak is to delete keys that are no longer needed:
import qualified Data.IntMap.Strict as M
import Data.IntMap.Strict (IntMap)
import Data.Char (ord)
import Data.List (foldl')
data Blob = Blob
{ total_count :: !Int
, remaining :: !Int
}
frequencias :: [Char] -> [Int]
frequencias xs0 = finish xs0 freq_map0
where
freq_map0 :: IntMap Blob
freq_map0 = foldl' go M.empty xs0
go fm c = M.alter f (ord c) fm
where
f Nothing = Just (Blob 1 1)
f (Just (Blob x _)) = Just (Blob (x + 1) (x + 1))
finish [] _ = []
finish (c : cs) freq_map = case M.updateLookupWithKey (\_ (Blob tot remn) ->
if remn == 1
then Nothing
else Just (Blob tot (remn - 1))) (ord c) freq_map of
(Nothing, _) -> error "Whoopsy"
(Just (Blob tot _), freq_map') -> tot : finish cs freq_map'
For comparison to #dfeuer's answer, here's a couple of lower-tech approaches.
Brute force approach. This has O(n^2) time complexity, for input list length n.
occurrences :: Eq a => [a] -> [Int]
occurrences xss = map (\ x -> count (== x) xss) xss
count :: (a -> Bool) -> [a] -> Int
count _ [] = 0
count p (x : xs) | p x = 1 + count p xs
| otherwise = count p xs
(I used English names for my functions ;-) count does the job of O.P.'s ocurr. But I've switched round the order of args to look more like Prelude.filter. ocurr is a little inefficient because filter builds an intermediate result to be the argument to length. We don't need to build that: merely count how many elements meet the predicate (== x).
(I'm quite surprised there isn't already a Prelude.count nor Data.List.count.)
This is inefficient because it traverses the list for every element, even if it already 'knows' the count for that element value -- i.e. because it's already met that element earlier in the list.
OTOH, if a large proportion of the elements occur only once, it avoids the overhead of building some sort of lookup structure.
Here's a version using an intermediate cache -- but only for elements known to occur more than once. Anybody like to guess what is its time complexity?
data Cache3 a = TheList3 [a] | Cached3 a Int (Cache3 a)
count3 :: (a -> Bool) -> Cache3 a -> (Int, Bool)
-- return both the count and whether it was cached
count3 p (TheList3 xss) = ( count p xss, False) -- reuse count from sol'n 1
count3 p (Cached3 x c xs) | p x = (c, True)
| otherwise = count3 p xs
-- don't cache if count = 1: we've just counted its only appearance so won't need it again
occurrences3 :: Eq a => [a] -> [Int]
occurrences3 xss = go (TheList3 xss) xss where
go _ [] = []
go cc (x: xs) = c: go (if cached || c < 2 then cc else ( Cached3 x c cc)) xs where
(c, cached) = count3 (== x) cc

How to enhance small Haskell Code Snippet

just recently I started to try out haskell.
It's fun trying out different exercises, but sometimes I get the feeling, that my found solutions are far from elegant: The following Code Snipplet will find the longest sub-sequence in a list, which will satisfy a given condition (for example uppercase letters etc.)
Could you help a noob to make everything shorter and more elegant - every advice is highly appreciated.
import Data.Char
longer :: [a] -> [a] -> [a]
longer x y = if length x > length y
then x
else y
longest :: [[a]]->[a]
longest = foldl longer []
nextSequence :: (a->Bool) -> [a] ->([a],[a])
nextSequence f x = span f (dropWhile (not . f) x)
longestSubsequence :: (a -> Bool) -> [a] -> [a]
longestSubsequence _ x | null x = []
longestSubsequence f x =
longest $ (\y -> [fst y , longestSubsequence f $ snd y]) (nextSequence f x)
testSequence :: String
testSequence = longestSubsequence Data.Char.isUpper
"hkerhklehrERJKJKJERKJejkrjekERHkhkerHERKLJHERJKHKJHERdjfkj"
At first, you can define your longest like this:
import Data.Function
import Data.List
longest :: [[a]] -> [a]
longest = maximumBy (compare `on` length)
And to get all subsequences that satisfy a given condition you can write a function like this:
import Data.List
getSatisfyingSubseqs :: (a -> Bool) -> [a] -> [[a]]
getSatisfyingSubseqs f = filter (f . head) . groupBy same
where same x y = f x == f y
Here we group elements where the condition yields the same result and filter only subsequences that satisfy the condition.
In the total:
longestSubsequence :: (a -> Bool) -> [a] -> [a]
longestSubsequence f = longest . getSatisfyingSubseqs f
UPDATE: And if you want to make it shorter, you can just throw out the auxiliary functions and write the whole at a time:
longestSubsequence :: (a -> Bool) -> [a] -> [a]
longestSubsequence f = maximumBy (compare `on` length) . filter (f . head) . groupBy same
where same x y = f x == f y
(Don't forget the imports)
You can run it there: https://repl.it/#Yuri12358/so-longestsequence
The span :: (a -> Bool) -> [a] -> ([a], [a]) function could be very handy here. Also note that f <$> (a,b) = (a,f b). Probably not very efficient due to the length checks but it should do the job.
lss :: (a -> Bool) -> [a] -> [a]
lss f [] = []
lss f ls#(x:xs) = if f x then longer (lss f <$> span f ls)
else lss f xs
where
longer ::([a],[a]) -> [a]
longer (xs,ys) = if length xs >= length ys then xs else ys
Your longer function uses length, which means it doesn't work if either input is infinite. However, it can be improved to work when at most one is infinite:
longer l1 l2 = go l1 l2
where
go [] _ = l2
go _ [] = l1
go (_:xs) (_:ys) = go xs ys
This is also a performance optimization. Before, if you had a 10-element list and a 10-million-element list, it would walk through all 10 million elements of the 10-million-element list before returning it. Here, it will return it as soon as it gets to the 11th element instead.

Adding zeros between elements in 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.

Delete Second Occurence of Element in List - Haskell

I'm trying to write a function that deletes the second occurrence of an element in a list.
Currently, I've written a function that removes the first element:
removeFirst _ [] = []
removeFirst a (x:xs) | a == x = xs
| otherwise = x : removeFirst a xs
as a starting point. However,I'm not sure this function can be accomplished with list comprehension. Is there a way to implement this using map?
EDIT: Now I have added a removeSecond function which calls the first
deleteSecond :: Eq a => a -> [a] -> [a]
deleteSecond _ [] = []
deleteSecond a (x:xs) | x==a = removeFirst a xs
| otherwise = x:removeSecond a xs
However now the list that is returned removes the first AND second occurrence of an element.
Well, assuming you've got removeFirst - how about searching for the first occurence, and then using removeFirst on the remaining list?
removeSecond :: Eq a => a -> [a] -> [a]
removeSecond _ [] = []
removeSecond a (x:xs) | x==a = x:removeFirst a xs
| otherwise = x:removeSecond a xs
You could also implement this as a fold.
removeNth :: Eq a => Int -> a -> [a] -> [a]
removeNth n a = concatMap snd . scanl go (0,[])
where go (m,_) b | a /= b = (m, [b])
| n /= m = (m+1, [b])
| otherwise = (m+1, [])
and in action:
λ removeNth 0 1 [1,2,3,1]
[2,3,1]
λ removeNth 1 1 [1,2,3,1]
[1,2,3]
I used scanl rather than foldl or foldr so it could both pass state left-to-right and work on infinite lists:
λ take 11 . removeNth 3 'a' $ cycle "abc"
"abcabcabcbc"
Here is an instinctive implementation using functions provided by List:
import List (elemIndices);
removeSecond x xs = case elemIndices x xs of
(_:i:_) -> (take i xs) ++ (drop (i+1) xs)
_ -> xs
removeNth n x xs = let indies = elemIndices x xs
in if length indies < n
then xs
else let idx = indies !! (n-1)
in (take idx xs) ++ (drop (idx+1) xs)
Note: This one cannot handle infinite list, and its performance may not be good for very large list.

Zip with default value instead of dropping values?

I'm looking for a function in haskell to zip two lists that may vary in length.
All zip functions I could find just drop all values of a lists that is longer than the other.
For example:
In my exercise I have two example lists.
If the first one is shorter than the second one I have to fill up using 0's. Otherwise I have to use 1's.
I'm not allowed to use any recursion. I just have to use higher order functions.
Is there any function I can use?
I really could not find any solution so far.
There is some structure to this problem, and here it comes. I'll be using this stuff:
import Control.Applicative
import Data.Traversable
import Data.List
First up, lists-with-padding are a useful concept, so let's have a type for them.
data Padme m = (:-) {padded :: [m], padder :: m} deriving (Show, Eq)
Next, I remember that the truncating-zip operation gives rise to an Applicative instance, in the library as newtype ZipList (a popular example of a non-Monad). The Applicative ZipList amounts to a decoration of the monoid given by infinity and minimum. Padme has a similar structure, except that its underlying monoid is positive numbers (with infinity), using one and maximum.
instance Applicative Padme where
pure = ([] :-)
(fs :- f) <*> (ss :- s) = zapp fs ss :- f s where
zapp [] ss = map f ss
zapp fs [] = map ($ s) fs
zapp (f : fs) (s : ss) = f s : zapp fs ss
I am obliged to utter the usual incantation to generate a default Functor instance.
instance Functor Padme where fmap = (<*>) . pure
Thus equipped, we can pad away! For example, the function which takes a ragged list of strings and pads them with spaces becomes a one liner.
deggar :: [String] -> [String]
deggar = transpose . padded . traverse (:- ' ')
See?
*Padme> deggar ["om", "mane", "padme", "hum"]
["om ","mane ","padme","hum "]
This can be expressed using These ("represents values with two non-exclusive possibilities") and Align ("functors supporting a zip operation that takes the union of non-uniform shapes") from the these library:
import Data.Align
import Data.These
zipWithDefault :: Align f => a -> b -> f a -> f b -> f (a, b)
zipWithDefault da db = alignWith (fromThese da db)
salign and the other specialised aligns in Data.Align are also worth having a look at.
Thanks to u/WarDaft, u/gallais and u/sjakobi over at r/haskell for pointing out this answer should exist here.
You can append an inifinte list of 0 or 1 to each list and then take the number you need from the result zipped list:
zipWithDefault :: a -> b -> [a] -> [b] -> [(a,b)]
zipWithDefault da db la lb = let len = max (length la) (length lb)
la' = la ++ (repeat da)
lb' = lb ++ (repeat db)
in take len $ zip la' lb'
This should do the trick:
import Data.Maybe (fromMaybe)
myZip dx dy xl yl =
map (\(x,y) -> (fromMaybe dx x, fromMaybe dy y)) $
takeWhile (/= (Nothing, Nothing)) $
zip ((map Just xl) ++ (repeat Nothing)) ((map Just yl) ++ (repeat Nothing))
main = print $ myZip 0 1 [1..10] [42,43,44]
Basically, append an infinite list of Nothing to the end of both lists, then zip them, and drop the results when both are Nothing. Then replace the Nothings with the appropriate default value, dropping the no longer needed Justs while you're at it.
No length, no counting, no hand-crafted recursions, no cooperating folds. transpose does the trick:
zipLongest :: a -> b -> [a] -> [b] -> [(a,b)]
zipLongest x y xs ys = map head . transpose $ -- longest length;
[ -- view from above:
zip xs
(ys ++ repeat y) -- with length of xs
, zip (xs ++ repeat x)
ys -- with length of ys
]
The result of transpose is as long a list as the longest one in its input list of lists. map head takes the first element in each "column", which is the pair we need, whichever the longest list was.
(update:) For an arbitrary number of lists, efficient padding to the maximal length -- aiming to avoid the potentially quadratic behaviour of other sequentially-combining approaches -- can follow the same idea:
padAll :: a -> [[a]] -> [[a]]
padAll x xss = transpose $
zipWith const
(transpose [xs ++ repeat x | xs <- xss]) -- pad all, and cut
(takeWhile id . map or . transpose $ -- to the longest list
[ (True <$ xs) ++ repeat False | xs <- xss])
> mapM_ print $ padAll '-' ["ommmmmmm", "ommmmmm", "ommmmm", "ommmm", "ommm",
"omm", "om", "o"]
"ommmmmmm"
"ommmmmm-"
"ommmmm--"
"ommmm---"
"ommm----"
"omm-----"
"om------"
"o-------"
You don't have to compare list lengths. Try to think about your zip function as a function taking only one argument xs and returning a function which will take ys and perform the required zip. Then, try to write a recursive function which recurses on xs only, as follows.
type Result = [Int] -> [(Int,Int)]
myZip :: [Int] -> Result
myZip [] = map (\y -> (0,y)) -- :: Result
myZip (x:xs) = f x (myZip xs) -- :: Result
where f x k = ??? -- :: Result
Once you have found f, notice that you can turn the recursion above into a fold!
As you said yourself, the standard zip :: [a] -> [b] -> [(a, b)] drops elements from the longer list. To amend for this fact you can modify your input before giving it to zip. First you will have to find out which list is the shorter one (most likely, using length). E.g.,
zip' x xs y ys | length xs <= length ys = ...
| otherwise = ...
where x is the default value for shorter xs and y the default value for shorter ys.
Then you extend the shorter list with the desired default elements (enough to account for the additional elements of the other list). A neat trick for doing so without having to know the length of the longer list is to use the function repeat :: a -> [a] that repeats its argument infinitely often.
zip' x xs y ys | length xs <= length ys = zip {-do something with xs-} ys
| otherwise = zip xs {-do something with ys-}
Here is another solution, that does work on infinite lists and is a straightforward upgrade of Prelude's zip functions:
zipDefault :: a -> b -> [a] -> [b] -> [(a,b)]
zipDefault _da _db [] [] = []
zipDefault da db (a:as) [] = (a,db) : zipDefault da db as []
zipDefault da db [] (b:bs) = (da,b) : zipDefault da db [] bs
zipDefault da db (a:as) (b:bs) = (a,b) : zipDefault da db as bs
and
zipDefaultWith :: a -> b -> (a->b->c) -> [a] -> [b] -> [c]
zipDefaultWith _da _db _f [] [] = []
zipDefaultWith da db f (a:as) [] = f a db : zipDefaultWith da db f as []
zipDefaultWith da db f [] (b:bs) = f da b : zipDefaultWith da db f [] bs
zipDefaultWith da db f (a:as) (b:bs) = f a b : zipDefaultWith da db f as bs
#pigworker, thank you for your enlightening solution!
Yet another implementation:
zipWithDefault :: a -> b -> (a -> b -> c) -> [a] -> [b] -> [c]
zipWithDefault dx _ f [] ys = zipWith f (repeat dx) ys
zipWithDefault _ dy f xs [] = zipWith f xs (repeat dy)
zipWithDefault dx dy f (x:xs) (y:ys) = f x y : zipWithDefault dx dy f xs ys
And also:
zipDefault :: a -> b -> [a] -> [b] -> [c]
zipDefault dx dy = zipWithDefault dx dy (,)
I would like to address the second part of Will Ness's solution, with its excellent use of known functions, by providing another to the original question.
zipPadWith :: a -> b -> (a -> b -> c) -> [a] -> [b] -> [c]
zipPadWith n _ f [] l = [f n x | x <- l]
zipPadWith _ m f l [] = [f x m | x <- l]
zipPadWith n m f (x:xs) (y:ys) = f x y : zipPadWith n m f xs ys
This function will pad a list with an element of choice. You can use a list of the same element repeated as many times as the number of lists in another like this:
rectangularWith :: a -> [[a]] -> [[a]]
rectangularWith _ [] = []
rectangularWith _ [ms] = [[m] | m <- ms]
rectangularWith n (ms:mss) = zipPadWith n [n | _ <- mss] (:) ms (rectangularWith n mss)
The end result will have been a transposed rectangular list of lists padded by the element that we provided so we only need to import transpose from Data.List and recover the order of the elements.
mapM_ print $ transpose $ rectangularWith 0 [[1,2,3,4],[5,6],[7,8],[9]]
[1,2,3,4]
[5,6,0,0]
[7,8,0,0]
[9,0,0,0]