Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/105754792adac0802a9a59b0df188b58fb53503f

>---------------------------------------------------------------

commit 105754792adac0802a9a59b0df188b58fb53503f
Author: Simon Marlow <[email protected]>
Date:   Mon Jul 9 13:16:53 2012 +0100

    Don't re-allocate %esi on x86.
    
    Recent changes have freed up %esi for general use on x86 when it is
    not being used for R1.  However, x86 has a non-uniform register
    architecture where there is no 8-bit equivalent of %esi.  The register
    allocators aren't sophisticated enough to cope with this, so we have
    to back off and treat %esi as non-allocatable for now.  (of course,
    LLVM doesn't suffer from this problem)
    
    One workaround would be to change the calling convention to use %rbx
    for R1, however we can't change the calling convention now without
    patching LLVM too.

>---------------------------------------------------------------

 compiler/nativeGen/X86/Regs.hs |   17 +++++++++++++++++
 1 files changed, 17 insertions(+), 0 deletions(-)

diff --git a/compiler/nativeGen/X86/Regs.hs b/compiler/nativeGen/X86/Regs.hs
index 6af9bc9..b2b6a34 100644
--- a/compiler/nativeGen/X86/Regs.hs
+++ b/compiler/nativeGen/X86/Regs.hs
@@ -471,6 +471,11 @@ callClobberedRegs       :: [Reg]
 freeReg esp = fastBool False  --        %esp is the C stack pointer
 #endif
 
+#if i386_TARGET_ARCH
+freeReg esi = fastBool False -- Note [esi/edi not allocatable]
+freeReg edi = fastBool False
+#endif
+
 #if x86_64_TARGET_ARCH
 freeReg rsp = fastBool False  --        %rsp is the C stack pointer
 #endif
@@ -662,4 +667,16 @@ allocatableRegs
    = let isFree i = isFastTrue (freeReg i)
      in  map RealRegSingle $ filter isFree allMachRegNos
 
+{-
+Note [esi/edi not allocatable]
+
+%esi is mapped to R1, so %esi would normally be allocatable while it
+is not being used for R1.  However, %esi has no 8-bit version on x86,
+and the linear register allocator is not sophisticated enough to
+handle this irregularity (we need more RegClasses).  The
+graph-colouring allocator also cannot handle this - it was designed
+with more flexibility in mind, but the current implementation is
+restricted to the same set of classes as the linear allocator.
 
+Hence, on x86 esi and edi are treated as not allocatable.
+-}



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to