[Haskell-beginners] Padding List with Zeros

Daniel Fischer daniel.is.fischer at web.de
Wed Sep 15 15:12:09 EDT 2010


On Wednesday 15 September 2010 20:24:09, Hein Hundal wrote:
> On Wed, 15 Sep 2010 16:23:49, Daniel Fischer wrote:
> > On Wednesday 15 September 2010 15:15:49, Henry Olders wrote:
> > > On 2010-09-14, at 19:35 , Lorenzo Isella wrote:
> > > > Dear All,
> > > > I still have to find my way with immutable lists and list
> > > > comprehension. Consider the following lists
> > > >
> > > > A=[0,10,20,30,40,50]
> > > > B=[0,10,50] (i.e. B is a subset of list A; list A is
> > > > already ordered in increasing order and so is B).
> > > > C=[2,1,-5] i.e. there is a corresponding element in C for every
> > > > element in B.
> > > >
> > > > Now, I would like to define a new list D having length equal
> > > > to the length of A. The elements of D in the position of the
> > > > elements of A in common with B are equal to the corresponding
> > > > entries in C, whereas the other ones are zero i.e.
> > > > D=[2,1,0,0,0,-5]. How can I achieve that? The first thought
> > > > that comes to my mind is to define a list of zeros which I
> > > > would modify according to my needs, but that is not allowed...
>
> Yes, that is not allowed.  First thing I thought of also.
>
> > > > Many thanks
> > > >
> > > > Lorenzo
> > >
> > > Being a real Haskell newby, I can figure out a one-line solution in
> > > Python, but I don't know how to do something similar in Haskell, or
> > > even if it's possible. Please correct me if I'm wrong, but there
> > > does not seem to be a dictionary type in Haskell, and I am not aware
> > > of how to specify an inline if...else inside a list comprehension. I
> > > would really appreciate it if someone could show me how to do
> > > something similar to this Python statement in Haskell.
> >
> >import Data.Maybe
> >
> > > >>> A=[0,10,20,30,40,50]
> > > >>> B=[0,10,50]
> > > >>> C=[2,1,-5]
> >
> > These have to be lowercase in Haskell, of course :)
> >
> > > >>> [dict(zip(B,C))[a] if a in B else 0 for a in A]
> >
> > map (fromMaybe 0 . (`lookup` zip b c)) a
> >
> > or, as a list comprehension,
> >
> > [fromMaybe 0 (lookup v dic) | let dic = zip b c, v <- a]
> >
> > Slightly more verbose than the Python.
> >
> > But this doesn't deal with multiple entries (istr that was
> > mentioned previously in this thread), for
> >
> > a = [0, 10, 10, 20, 30 , 40, 50]
> > b = [0, 10, 10, 50]
> > c = [2, 1, 3, -5]
> >
> > neither would produce
> >
> > [2, 1, 3, 0, 0, 0, -5]
> >
> > which I believe would be the desired behavior.
> >
> > > [2, 1, 0, 0, 0, -5]
> > >
> > > Henry
>
> I love the map solution and the lookup solutions--very concise.  Someday
> perhaps those will occur to me when I look at these problems.
>
> Here is my (extremely) verbose beginner solution.  I think this solution
> is linear time and it returns the "desired behavior" in Daniel's post.
>
> -- indices v1 v2
> --    find the elemIndex of v2's elements in v1
> --    almost equivalent to (map (flip elemIndex v1) v2)
> --
> indices v1 v2 = indices' 0 v1 v2
> indices' iOff (x:xs) (y:ys)
>
>    | x < y = indices' (iOff+1) xs (y:ys)
>    | x ==y = iOff:(indices' (iOff+1) xs ys)
>    | x > y = error "indicies:: elem not found"
>
> indices' _  _ [] = []
> indices' _ [] (y:ys) = error "indices:: elem not found"
>
>
> -- makevec 0 indices values
> --   returns a vector with values filled in at the indices given
> --
> makevec _ [] _ = []
> makevec _ _ [] = error "makevec:: "
> makevec iOffSet (i:is) (x:xs)
>
>    | iOffSet < i = replicate (i-iOffSet) 0 ++ makevec i (i:is) (x:xs)
>    | iOffSet ==i = x:(makevec (iOffSet+1) is xs)
>    | iOffSet > i = error "makevec error"
>
> hisfunc :: [Integer] -> [Integer] -> [Integer] -> [Integer]
> hisfunc a b c = let front = makevec 0 (indices a b) c
>    in front ++ replicate (length a - length front) 0
>
>
> test1 = hisfunc a b c
> test2 = hisfunc (a++[70, 90]) b c
> test3 = hisfunc (a++[70, 90]) (b++[70]) (c++[-14])
> test4 = hisfunc [0,10,10,20,30,40,50] [0,10,10,50] [2,1,3,-5]

Somewhat simpler in one go:

-- Preconditions:
-- length bs == length cs
-- as and bs are sorted
-- bs is a sublist of as
expand :: (Ord a, Num a) => [a] -> [a] -> [a] -> [a]
expand as [] _ = map (const 0) as
expand (a:as) bbs@(b:bs) ccs@(c:cs)
    | a < b     = 0 : expand as bbs ccs
    | otherwise = c : expand as bs cs
expand _ _ _ = []


More information about the Beginners mailing list