[GHC] #14346: 8.2.1 regression: heap corruption after safe foreign calls

GHC ghc-devs at haskell.org
Mon Oct 16 14:42:30 UTC 2017


#14346: 8.2.1 regression: heap corruption after safe foreign calls
-------------------------------------+-------------------------------------
        Reporter:  andrewchen        |                Owner:  (none)
            Type:  bug               |               Status:  infoneeded
        Priority:  highest           |            Milestone:
       Component:  Runtime System    |              Version:  8.2.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  Runtime crash     |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by bgamari):

 Indeed the `--chaos` tip is quite helpful. Thanks!

 So it appears that the crazy TSO is loaded in `stg_putMVar#` on line 1737:

 {{{#!c
     ...
     // There are readMVar/takeMVar(s) waiting: wake up the first one

     tso = StgMVarTSOQueue_tso(q);                                // <---
 here
     StgMVar_head(mvar) = StgMVarTSOQueue_link(q);
     if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) {
         StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure;
     }
 ...
 }}}
 Here `q` is `0x42000b7530` which is a fairly reasonable-looking
 `MVAR_TSO_QUEUE`, except with a completely wild `tso` field,
 {{{
 0x42000b7530:   0x4acd28 <stg_MVAR_TSO_QUEUE_info>      0x4f2c30
 0x42000b7540:   0x42deadbeef    0x433508 <base_GHCziInt_I32zh_con_info>
 }}}

 Indeed the last guy to write to `StgMVarTSOQueue_tso(q)` is the FFI
 target, `test`,
 {{{
 Dump of assembler code for function test:
 => 0x00000000004044f0 <+0>:     movl   $0xdeadbeef,(%rdi)
    0x00000000004044f6 <+6>:     retq
 }}}
 where `%rdi == 0x00000042000b7540`.

 Let's look at the calling sequence produced by GHC,
 {{{#!asm
 _c4Rp:
         movq $block_c4Ru_info,-8(%rbp) # I64[Sp - 8] = c4Ru;
         movq %rax,(%rbp)               # I64[Sp] = _s4Ok::I64;
         addq $-8,%rbp                  # Sp = Sp - 8;
         movq 872(%r13),%rbx            # _u4RJ::P64 = CurrentTSO;
         movq 24(%rbx),%rcx             # I64[I64[_u4RJ::P64 + 24] + 16] =
 Sp;
         movq %rbp,16(%rcx)
         movq 888(%r13),%rcx            # _u4RK::I64 = CurrentNursery;
         leaq 8(%r12),%rdx              # P64[_u4RK::I64 + 8] = Hp + 8;
             # I64[_u4RJ::P64 + 104] = I64[_u4RJ::P64 + 104]
             #                         - ((Hp + 8) - I64[_u4RK::I64]);
         movq %rdx,8(%rcx)
         leaq 8(%r12),%rdx
         subq (%rcx),%rdx
         movq 104(%rbx),%rcx
         subq %rdx,%rcx
         movq %rcx,104(%rbx)
             # (_u4RH::I64) = call "ccall" arg hints:  [PtrHint,]  result
 hints:  [PtrHint] suspendThread(BaseReg, 0);

         subq $8,%rsp                   # native-call stack adjustment
         movq %r13,%rdi                 # setup argument 1 (BaseReg)
         xorl %esi,%esi                 # setup argument 2 (0)
         movq %rax,%rbx                 # Save $rax in callee-saved
 register
         xorl %eax,%eax                 # ???
         call suspendThread
         addq $8,%rsp                   # undo stack adjustment
         subq $8,%rsp                   # redo stack adjustment; silly GHC
         movq %rbx,%rdi                 # ??? <---- This is where the bad
 argument comes from
         movq %rax,%rbx                 # Ahhh, I think I see
         xorl %eax,%eax
         call test                      # Native call
         addq $8,%rsp                   # undo stack adjustment
         subq $8,%rsp                   # you are such a joker, GHC
         movq %rbx,%rdi
         xorl %eax,%eax
         call resumeThread
         ...
 }}}

 It looks to me like what happens here is that we spill `$rax` (which
 contains a pointer to the current `MVar` closure) to `$rbx` twice, losing
 knowledge of the first spill. Consequently we end up passing the `MVar` as
 the argument to `test`. Hilarity ensues.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14346#comment:11>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list