[Haskell-cafe] Re: FASTER primes

Will Ness will_n48 at yahoo.com
Sun Jan 10 11:28:01 EST 2010


Daniel Fischer <daniel.is.fischer <at> web.de> writes:

> 
> Am Freitag 08 Januar 2010 19:45:47 schrieb Will Ness:
> > Daniel Fischer <daniel.is.fischer <at> web.de> writes:
> 
> > >
> > > mergeSP :: Integral a => People a -> People a -> People a
> > > mergeSP p1@(P a _) p2 = P (a ++ vips mrgd) (dorks mrgd)
> > >       where
> > >         mrgd = spMerge (dorks p1) (vips p2) (dorks p2)
> > >         spMerge l1 [] l3 = P [] (merge l1 l3)
> > >         spMerge ~l1@(x:xs) l2@(y:ys) l3 = case compare x y of
> > >                 LT -> celebrate x (spMerge xs l2 l3)
> > >                 EQ -> celebrate x (spMerge xs ys l3)
> > >                 GT -> celebrate y (spMerge l1 ys l3)
> > >
> > > ----------------------------------------------------------------------


Actually, the minimal edit that does the trick (of eliminating the space leak 
that you've identified) for my original code is just


  mergeSP (a,b) ~(c,d) = let (bc,bd) = spMerge b c d
                         in (a ++ bc, bd) 
   where 
    spMerge b [] d = ([] ,merge b d)
    spMerge b@(x:xs) c@(y:ys) d = case compare x y of
            LT ->  (x:u,v)  where (u,v) = spMerge xs c  d
            EQ ->  (x:u,v)  where (u,v) = spMerge xs ys d
            GT ->  (y:u,v)  where (u,v) = spMerge b  ys d
    spMerge [] c d = ([] ,merge c d)


which hardly looks at all different at the first glance. Just for reference, it 
was 

 {-
  mergeSP (a,b) ~(c,d) = let (bc,b') = spMerge b c
                         in (a ++ bc, merge b' d) 
   where 
    spMerge b@(x:xs) c@(y:ys) = case compare x y of
            LT ->  (x:u,v)  where (u,v) = spMerge xs c  
            EQ ->  (x:u,v)  where (u,v) = spMerge xs ys 
            GT ->  (y:u,v)  where (u,v) = spMerge b  ys 
    spMerge b [] = ([] ,b)
    spMerge [] c = ([] ,c)
 -}

spMerge of course is not tail recursive here in both versions if seen through 
the imperative eyes. But lazy evaluation makes it effectively so. The important 
thing is, when the final point is reached, there's no outstanding context - 
everything is present. There should be a name for such concept. This is very 
similar to late instantiation in Prolog (programming with "holes"), and I think 
this *would* pass as a tail-recursive function /there/.

Even in the new code the compiler could've internally held on to the original 
pair and only deconstructed the 'd' out of it at the final call to merge, 
recreating the space leak. It could just as well have recognized that 'd' isn't 
changed inside spMerge (we're pure in Haskell after all) and deconstructed the 
pair in the original code. Something is missing here.

 
> As it turns out, the important things are
> 
> 1. a feeder and separate lists of multiples for the feeder and the runner, 
> for the reasons detailed earlier (two-step feeding and larger wheel are 
> pleasing but minor optimisations).
> 
> 2. a strict pattern in tfold
> 
> 3. moving the merge inside spMerge 


> > Is this the state of our _best_ Haskell compiler????
> >
> 
> Yes. It's still a "do what I tell you to" compiler, even if a pretty slick 
> one, not a "do what I mean" compiler. Sometimes, what you tell the compiler 
> isn't what you wanted.
> It's easier to predict when you give detailed step by step instructions.
> 






More information about the Haskell-Cafe mailing list