[Haskell-cafe] Is there anything manifestly stupid about this code?

Don Stewart dons at galois.com
Mon Jul 7 13:24:55 EDT 2008


lrpalmer:
> On Mon, Jul 7, 2008 at 2:21 PM, Michael Feathers
> <mfeathers at mindspring.com> wrote:
> > Thanks.  Here's a newb question: what does strictness really get me in this
> > code?
> 
> A bit of speed and memory improvements, I suspect.  The type
> (Double,Double) has three boxes, one for the tuple and one for each
> double.  The type Complex, which is defined as
> 
>     data Complex a = !a :+ !a
> 
> has one box (after -funbox-strict-fields has done its work), the one
> for the type as a whole.  So it will end up using less memory, and
> there will be fewer jumps to evaluate one (a jump is made for each
> box).

On a good day the two Double components will be unpacked into registers
entirely. As here, a loop on Complex:

    {-# OPTIONS -funbox-strict-fields #-}

    module M where

    data Complex = !Double :+ !Double

    conjugate :: Complex -> Complex
    conjugate (x:+y) =  x :+ (-y)

    realPart :: Complex -> Double
    realPart (x :+ _) =  x

    go :: Complex -> Double
    go n | realPart n > pi = realPart n
         | otherwise       = go (conjugate n)

Note that notionally Complex has 3 indirections, the Complex
constructor, and two for the Doubles. After optimisation
however, there's only unboxed doubles in registers left:

    M.$wgo :: Double# -> Double# -> Double#
    M.$wgo =
      \ (ww_sjT :: Double#) (ww1_sjU :: Double#) ->
          case >## ww_sjT 3.141592653589793 of wild_Xs {
              False -> M.$wgo ww_sjT (negateDouble# ww1_sjU);
              True -> ww_sjT


-- Don


More information about the Haskell-Cafe mailing list