Skip to content
  • Sergei Trofimovich's avatar
    pprC: declare extern cmm primitives as functions, not data · e18525fa
    Sergei Trofimovich authored
    
    
    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: default avatarSergei Trofimovich <slyfox@gentoo.org>
    e18525fa