On Wed, Oct 31, 2007 at 03:37:12PM +0000, Neil Mitchell wrote:
> Hi
> 
> I've been working on optimising Haskell for a little while
> (http://www-users.cs.york.ac.uk/~ndm/supero/), so here are my thoughts
> on this.  The Clean and Haskell languages both reduce to pretty much
> the same Core language, with pretty much the same type system, once
> you get down to it - so I don't think the difference between the
> performance is a language thing, but it is a compiler thing. The
> uniqueness type stuff may give Clean a slight benefit, but I'm not
> sure how much they use that in their analyses.
> 
> Both Clean and GHC do strictness analysis - I don't know which one
> does better, but both do quite well. I think Clean has some
> generalised fusion framework, while GHC relies on rules and short-cut
> deforestation. GHC goes through C-- to C or ASM, while Clean has been
> generating native code for a lot longer. GHC is based on the STG
> machine, while Clean is based on the ABC machine - not sure which is
> better, but there are differences there.
> 
> My guess is that the native code generator in Clean beats GHC, which
> wouldn't be too surprising as GHC is currently rewriting its CPS and
> Register Allocator to produce better native code.

I don't think the register allocater is being rewritten so much as it is
being written:

[EMAIL PROTECTED]:/tmp$ cat X.hs
module X where

import Foreign
import Data.Int

memset :: Ptr Int32 -> Int32 -> Int -> IO ()
memset p v i = p `seq` v `seq` case i of
    0 -> return ()
    _ -> poke p v >> memset (p `plusPtr` sizeOf v) v (i - 1)
[EMAIL PROTECTED]:/tmp$ ghc -fbang-patterns -O2 -c -fforce-recomp -ddump-asm 
X.hs
...
X_zdwa_info:
        movl 8(%ebp),%eax
        testl %eax,%eax
        jne .LcH6
        movl $base_GHCziBase_Z0T_closure+1,%esi
        addl $12,%ebp
        jmp *(%ebp)
.LcH6:
        movl 4(%ebp),%ecx
        movl (%ebp),%edx
        movl %ecx,(%edx)
        movl (%ebp),%ecx
        addl $4,%ecx
        decl %eax
        movl %eax,8(%ebp)
        movl %ecx,(%ebp)
        jmp X_zdwa_info
...

Admittedly that's better than it used to be (I recall 13 memory
references last time I tested it), but still... the reason for your
performance woes should be quite obvious in that snippet.

Stefan

Attachment: signature.asc
Description: Digital signature

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to