[commit: ghc] master: pprC: declare extern cmm primitives as functions, not data (e18525f)

git at git.haskell.org git at git.haskell.org
Fri Sep 5 06:54:15 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/e18525fae273f4c1ad8d6cbe1dea4fc074cac721/ghc

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

commit e18525fae273f4c1ad8d6cbe1dea4fc074cac721
Author: Sergei Trofimovich <slyfox at gentoo.org>
Date:   Thu Sep 4 17:50:45 2014 +0300

    pprC: declare extern cmm primitives as functions, not data
    
    Summary:
      The commit fixes incorrect code generation of
      integer-gmp package on ia64 due to C prototypes mismatch.
      Before the patch prototypes for "foreign import prim" were:
          StgWord poizh[];
      After the patch they became:
          StgFunPtr poizh();
    
    Long story:
    
    Consider the following simple example:
    
        {-# LANGUAGE MagicHash, GHCForeignImportPrim, UnliftedFFITypes #-}
        module M where
        import GHC.Prim -- Int#
        foreign import prim "poizh" poi# :: Int# -> Int#
    
    Before the patch unregisterised build generated the
    following 'poizh' reference:
        EI_(poizh); /* StgWord poizh[]; */
        FN_(M_poizh_entry) {
        // ...
        JMP_((W_)&poizh);
        }
    
    After the patch it looks this way:
        EF_(poizh); /* StgFunPtr poizh(); */
        FN_(M_poizh_entry) {
        // ...
        JMP_((W_)&poizh);
        }
    
    On ia64 it leads to different relocation types being generated:
      incorrect one:
        addl r14 = @ltoffx(poizh#)
        ld8.mov r14 = [r14], poizh# ; r14 = address-of 'poizh#'
      correct one:
        addl r14 = @ltoff(@fptr(poizh#)), gp ; r14 = address-of-thunk 'poizh#'
        ld8 r14 = [r14]
    
    '@fptr(poizh#)' basically instructs assembler to creates
    another obect consisting of real address to 'poizh' instructions
    and module address. That '@fptr' object is used as a function "address"
    This object is different for every module referencing 'poizh' symbol.
    
    All indirect function calls expect '@fptr' object. That way
    call site reads real destination address and set destination
    module address in 'gp' register from '@fptr'.
    
    Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org>


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

e18525fae273f4c1ad8d6cbe1dea4fc074cac721
 compiler/cmm/CLabel.hs | 1 +
 1 file changed, 1 insertion(+)

diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs
index 02ad026..0f2c0ae 100644
--- a/compiler/cmm/CLabel.hs
+++ b/compiler/cmm/CLabel.hs
@@ -813,6 +813,7 @@ labelType (CmmLabel _ _ CmmClosure)             = GcPtrLabel
 labelType (CmmLabel _ _ CmmCode)                = CodeLabel
 labelType (CmmLabel _ _ CmmInfo)                = DataLabel
 labelType (CmmLabel _ _ CmmEntry)               = CodeLabel
+labelType (CmmLabel _ _ CmmPrimCall)            = CodeLabel
 labelType (CmmLabel _ _ CmmRetInfo)             = DataLabel
 labelType (CmmLabel _ _ CmmRet)                 = CodeLabel
 labelType (RtsLabel (RtsSelectorInfoTable _ _)) = DataLabel



More information about the ghc-commits mailing list