[Haskell-cafe] adding the elements of two lists

Doug McIlroy doug at cs.dartmouth.edu
Thu Mar 29 17:54:26 CEST 2012


> From: "Richard O'Keefe" <ok at cs.otago.ac.nz>
> Date: Thu, 29 Mar 2012 16:34:46 +1300
> 
> On 29/03/2012, at 3:08 PM, Doug McIlroy wrote:
> > --------- without newtype
> > 
> > toSeries f = f : repeat 0   -- coerce scalar to series
> > 
> > instance Num a => Num [a] where
> >   (f:fs) + (g:gs) = f+g : fs+gs
> >   (f:fs') * gs@(g:gs') = f*g : fs'*gs + (toSeries f)*gs'
> > 
> > --------- with newtype
> > 
> > newtype Num a => PS a = PS [a] deriving (Show, Eq)
> > 
> > fromPS (PS fs) = fs         -- extract list
> > toPS f = PS (f : repeat 0)  -- coerce scalar to series
> > 
> > instance Num a => Num (PS a) where
> >   (PS (f:fs)) + (PS (g:gs)) = PS (f+g : fs+gs)
> >   (PS (f:fs)) * gPS@(PS (g:gs)) =
> >      PS $ f*g : fromPS ((PS fs)*gPS + (toPS f)*(PS gs))
> 
> Try it again.
> 
> newtype PS a = PS [a] deriving (Eq, Show)
> 
> u f (PS x)        = PS $ map f x
> b f (PS x) (PS y) = PS $ zipWith f x y
> to_ps x           = PS (x : repeat 0)
> 
> ps_product (f:fs) (g:gs) = whatever
> 
> instance Num a => Num (PS a)
>   where
>     (+)     = b (+)
>     (-)     = b (-)
>     (*)     = b ps_product
>     negate  = u negate
>     abs     = u abs
>     signum  = u signum
>     fromInteger = to_ps . fromInteger
> 
> I've avoided defining ps_product because I'm not sure what
> it is supposed to do: the definition doesn't look commutative.

You have given the Hadamard product--a construction with somewhat
esoteric properties.  The product I have in mind is the ordinary
mathematical product that one meets in freshman calculus.  The
distributive law yields this symmetric formulation

	(f:fs) * (g:gs) = f*g : (toSeries f)*gs + fs*(toSeries g) + (0 : fs*gs)

The version I gave is an optimization (which I learned from Jerzy). For more
explanation see www.cs.dartmouth.edu/~doug/powser.html.

I like the lifting functions b and u, but they don't get one very far.
The product is where the PS pox begins to bite badly. I would welcome 
a perspicuous formulation of that using newtype.

Incidentally, a more efficient way to write the symmetric product is

	(f:fs) * (g:gs) = f*g : zipWith (f*) gs + zipWith fs (*g) + (0 : fs*gs)

toSeries and zipWith appear in the formulas because Haskell overloading
won't let one use the multiplication symbol for both series*series and
scalar*series. One might also invent a distinct operator for the purpose.
Coercion with toSeries strikes me as the least jarring of these approaches.
zipWith suffers from mixing levels of abstraction--it signifies not the
idea of multiplication, but the algorithm.  A new operator would suffer
both from unfamiliarity and lack of commutativity.

> 
> > The code suffers a pox of PS.
> 
> But it doesn't *need* to.
> 
> 



More information about the Haskell-Cafe mailing list