I think the bug might be here:

inlineStmt u a (CmmCall target regs es srt ret)
   = CmmCall (infn target) regs es' srt ret
   where infn (CmmCallee fn cconv) = CmmCallee fn cconv
         infn (CmmPrim p) = CmmPrim p
         es' = [ (CmmHinted (inlineExpr u a e) hint) | (CmmHinted e hint) <- es

(from cmm/CmmOpt.hs) Note that it isn't substituting inside the 'fn' argument to CmmCallee, and it should be. This bug has been around for ages.

Cheers,
        Simon

On 13/01/2011 04:34, Edward Z. Yang wrote:
With further poking, I think the new codegen is actually tickling
an existing bug in the native code generator optimizations, since
the cmmz output looks ok:

       cSH:
           _sQR::I32 = I32[_sRi::I32 + 3];   // CmmAssign
           _sQS::I32 = I32[_sRi::I32 + 7];   // CmmAssign
           _sQT::I32 = I32[_sRi::I32 + 11];   // CmmAssign
           _sQU::I32 = I32[_sRi::I32 + 15];   // CmmAssign
           (_sR1::I32) = call "ccall" arg hints:  [`signed',
                                                   PtrHint,]  result hints:  [] 
(_sQR::I32&  (-4))(_sQS::I32, _sQT::I32, _sQU::I32);   // CmmUnsafeForeignCall

And the only change is that in the original code generator,
the assignment to _sQR is elided.

          _cSn::I32 = I32[R1 + 7];
          _cSp::I32 = I32[R1 + 11];
          _cSr::I32 = I32[R1 + 15];
          (_sR1::I32,) = foreign "ccall"
            I32[R1 + 3]((_cSn::I32, `signed'), (_cSp::I32, PtrHint),
                        (_cSr::I32,))[_unsafe_call_];

I further verified that there was no problem if I used -fvia-C.
On closer inspection, the fact that _sQR is referenced nowhere
in this dump should have raised alarms (I think the register
allocater happened to assign it to the same register as
_sRi, which is why the assembly looked vaguely plausible.)

I'm still not sure where a fix might lie, but if I take another
crack at it tomorrow I will probably figure it out.

Cheers,
Edward

Excerpts from Edward Z. Yang's message of Wed Jan 12 17:10:11 -0500 2011:
I appear to have tracked down the bug for ffi021:  the new
code generator doesn't appear to clear the tag bit for the
pointer to heap before:

         // outOfLine should follow:
         (_sR1::I32,) = foreign "ccall"
           _sQR::I32((I32[_sRi::I32 + 7], `signed'),
                     (I32[_sRi::I32 + 11], PtrHint),
                     (I32[_sRi::I32 + 15],))[_unsafe_call_];
         // emitReturn: Sequel: Assign
         ;

(gdb) disas
Dump of assembler code for function sRi_info:
=>  0x0804aa6c<+0>:     mov    %esi,%eax
    0x0804aa6e<+2>:     lea    0x0(%ebp),%ecx
    0x0804aa71<+5>:     cmp    0x54(%ebx),%ecx
    0x0804aa74<+8>:     jb     0x804aab3<sRi_info+71>
    0x0804aa76<+10>:    add    $0x4,%ebp
    0x0804aa79<+13>:    add    $0x8,%edi
    0x0804aa7c<+16>:    cmp    0x5c(%ebx),%edi
    0x0804aa7f<+19>:    ja     0x804aaa4<sRi_info+56>
    0x0804aa81<+21>:    pushl  0xf(%eax)
    0x0804aa84<+24>:    pushl  0xb(%eax)
    0x0804aa87<+27>:    pushl  0x7(%eax)
    0x0804aa8a<+30>:    call   *%eax

The pushes to the stack properly untag eax, but then we just
call the tagged pointer, which seems pretty wrong to me. Here is
the old C--:

         (_sR1::I32,) = foreign "ccall"
           I32[R1 + 3]((_cSc::I32, `signed'), (_cSe::I32, PtrHint),
                       (_cSg::I32,))[_unsafe_call_];

Unfortunately, I can't figure out where this +3 is supposed to
be happening, so I don't have a patch. Some guidance here would
be appreciated.

Cheers,
Edward

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
ti

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to