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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/412af8c2eb2f2c689f77fa9e061d45eaa37110f1

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

commit 412af8c2eb2f2c689f77fa9e061d45eaa37110f1
Author: Simon Marlow <[email protected]>
Date:   Mon Oct 22 11:43:18 2012 +0100

    Foreign calls can clobber heap & stack memory too
    
    We were making an aggressive assumption that foreign calls cannot
    clobber heap or stack memory, which for the majority of foreign calls
    is true, but we violate the assumption in the implementation of
    primops in the RTS.  This was causing crashes in some STM tests.

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

 compiler/cmm/CmmSink.hs |   19 +++++++++++++++++--
 1 files changed, 17 insertions(+), 2 deletions(-)

diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs
index 6dccdab..688d6f6 100644
--- a/compiler/cmm/CmmSink.hs
+++ b/compiler/cmm/CmmSink.hs
@@ -464,8 +464,8 @@ conflicts dflags (r, rhs, addr) node
   -- foreign call.  See Note [foreign calls clobber GlobalRegs].
   | CmmUnsafeForeignCall{} <- node, anyCallerSavesRegs dflags rhs = True
 
-  -- (5) foreign calls clobber memory, but not heap/stack memory
-  | CmmUnsafeForeignCall{} <- node, AnyMem <- addr                = True
+  -- (5) foreign calls clobber heap: see Note [foreign calls clobber heap]
+  | CmmUnsafeForeignCall{} <- node, memConflicts addr AnyMem      = True
 
   -- (6) native calls clobber any memory
   | CmmCall{} <- node, memConflicts addr AnyMem                   = True
@@ -523,6 +523,21 @@ data AbsMem
 --  that was written in the same basic block.  To take advantage of
 --  non-aliasing of heap memory we will have to be more clever.
 
+-- Note [foreign calls clobber]
+--
+-- It is tempting to say that foreign calls clobber only
+-- non-heap/stack memory, but unfortunately we break this invariant in
+-- the RTS.  For example, in stg_catch_retry_frame we call
+-- stmCommitNestedTransaction() which modifies the contents of the
+-- TRec it is passed (this actually caused incorrect code to be
+-- generated).
+--
+-- Since the invariant is true for the majority of foreign calls,
+-- perhaps we ought to have a special annotation for calls that can
+-- modify heap/stack memory.  For now we just use the conservative
+-- definition here.
+
+
 bothMems :: AbsMem -> AbsMem -> AbsMem
 bothMems NoMem    x         = x
 bothMems x        NoMem     = x



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

Reply via email to