[Haskell-cafe] Re: FASTER primes

Will Ness will_n48 at yahoo.com
Sat Jan 16 12:53:33 EST 2010


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

> 
> Am Donnerstag 14 Januar 2010 08:25:48 schrieb Will Ness:
> > Daniel Fischer <daniel.is.fischer <at> web.de> writes:
> > > Am Mittwoch 13 Januar 2010 10:43:42 schrieb Heinrich Apfelmus:
> > > > I wonder whether it's really the liveness of  pair  in
> > > >
> > > >   mergeSP (a,b) pair
> > > >      = let sm = spMerge b (fst pair)
> > > >        in (a ++ fst sm, merge (snd sm) (snd pair))
> > > >
> > > > that is responsible for the space leak, ...
> > >
> > > I think that is responsible. At least that's how I understand the
> > > core:
> > >
> > > mergeSP (a,b) ~(c,d) = (a ++ bc, merge b' d)
> > >    where
> > >       (bc, b') = spMerge b c
> > >       spMerge ...
> >
> > That is equivalent to
> >
> >   first (a++) . second (`merge`d) $ spMerge b c
> >
> > and Daniel's fix is equivalent to
> >
> >   first (a++) $ spMerge b c d
> >


That should've been

  mergeSP (a,b) p = first(a++) . second(`merge`snd p) $ spMerge b (fst p)

and

  mergeSP (a,b) p = first(a++) $ spMerge b (fst p) (snd p)


The code fragments you've posted are essentially


  mergeSP (a,b) p = let res = case p of (c,_) ->
                                case spMerge b c of (# x,y #) ->
                                  (x,y)
    in
       (# (++) a (case res of (bc,_)-> bc) ,
          case res of (_,b') -> 
            case p of (_,d) -> merge b' d  #)

and

  mergeSP (a,b) p = let res = case p of (c,d) ->
                                case spMerge b c d of (# x,y #) ->
                                  (x,y)
    in
       (# (++) a (case res of (bc,_)-> bc) ,
          case res of (_,b') -> b'         #)


This looks like Haskell to me, with many detailes explicitely written out, 
probaly serving as immediate input to the compiler - not its output. So it 
can't say to us much about how this is actually implemented on the lower level. 
(?)

Your theory would certainly hold if the translation was done one-to-one without 
any further code rearrangements. But it could've been further re-arranged by 
the compiler at some later stage (is there one?) into an equivalent of, e.g. 


  mergeSP (a,b) p = let (bc,b') = case p of (c,_) ->
                                    case spMerge b c of (x,y) ->
                                      (x,y)
    in
       (# (++) a bc ,
          case p of (_,d) -> merge b' d  #)


and further,


  mergeSP (a,b) p = let (c,d)   = case p of (x,y) -> (x,y)
                        (bc,b') = case spMerge b c of (x,y) ->
                                      (x,y)
    in
       (# (++) a bc , merge b' d  #)


could it? This would take hold on /d/ and /c/ at the same time, right? 

What is that code that you've shown exactly? At which stage is it produced and 
is it subject to any further manipulation? I apologise if these are obvious 
questions, I don't know anything about GHC. I also don't know what (# x,y #) 
means?

One thing seems certain - we should not hold explicit references to same 
entities in different parts of our code, to avoid space leaks with more 
confidence. To make code look as much tail-recursive as possible, so to speak.

Does that make sense?

Anyway that was a very educational (for me) and fruitful discussion, and I 
greatly appreciate your help, and fixing and improving of the code.

Thanks!




More information about the Haskell-Cafe mailing list