Skip to content

Commit

Permalink
put the @n suffix on stdcall foreign calls in .cmm code
Browse files Browse the repository at this point in the history
This applies to EnterCriticalSection and LeaveCriticalSection in the RTS
  • Loading branch information
Simon Marlow committed Sep 4, 2007
1 parent 0f8ecdc commit 0981e24
Show file tree
Hide file tree
Showing 5 changed files with 32 additions and 5 deletions.
7 changes: 7 additions & 0 deletions compiler/cmm/CLabel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@ module CLabel (
mkRtsApFastLabel,

mkForeignLabel,
addLabelSize,

mkCCLabel, mkCCSLabel,

Expand Down Expand Up @@ -364,6 +365,12 @@ mkApEntryLabel upd off = RtsLabel (RtsApEntry upd off)
mkForeignLabel :: FastString -> Maybe Int -> Bool -> CLabel
mkForeignLabel str mb_sz is_dynamic = ForeignLabel str mb_sz is_dynamic

addLabelSize :: CLabel -> Int -> CLabel
addLabelSize (ForeignLabel str _ is_dynamic) sz
= ForeignLabel str (Just sz) is_dynamic
addLabelSize label _
= label

-- Cost centres etc.

mkCCLabel cc = CC_Label cc
Expand Down
24 changes: 19 additions & 5 deletions compiler/cmm/CmmParse.y
Original file line number Diff line number Diff line change
Expand Up @@ -823,8 +823,8 @@ newLocal kind ty name = do
-- classifies these labels as dynamic, hence the code generator emits the
-- PIC code for them.
newImport :: FastString -> ExtFCode ()
newImport name =
addVarDecl name (CmmLit (CmmLabel (mkForeignLabel name Nothing True)))
newImport name
= addVarDecl name (CmmLit (CmmLabel (mkForeignLabel name Nothing True)))

newLabel :: FastString -> ExtFCode BlockId
newLabel name = do
Expand Down Expand Up @@ -909,15 +909,29 @@ foreignCall conv_string results_code expr_code args_code vols safety ret
case convention of
-- Temporary hack so at least some functions are CmmSafe
CmmCallConv -> code (stmtC (CmmCall (CmmCallee expr convention) results args safety ret))
_ -> case safety of
_ ->
let expr' = adjCallTarget convention expr args in
case safety of
CmmUnsafe ->
code (emitForeignCall' PlayRisky results
(CmmCallee expr convention) args vols NoC_SRT ret)
(CmmCallee expr' convention) args vols NoC_SRT ret)
CmmSafe srt ->
code (emitForeignCall' (PlaySafe unused) results
(CmmCallee expr convention) args vols NoC_SRT ret) where
(CmmCallee expr' convention) args vols NoC_SRT ret) where
unused = panic "not used by emitForeignCall'"

adjCallTarget :: CCallConv -> CmmExpr -> [(CmmExpr,MachHint)] -> CmmExpr
#ifdef mingw32_TARGET_OS
-- On Windows, we have to add the '@N' suffix to the label when making
-- a call with the stdcall calling convention.
adjCallTarget StdCallConv (CmmLit (CmmLabel lbl)) args
= CmmLit (CmmLabel (addLabelSize lbl (sum (map size args))))
where size (e,_) = max wORD_SIZE (machRepByteWidth (cmmExprRep e))
-- c.f. CgForeignCall.emitForeignCall
#endif
adjCallTarget _ expr _
= expr

primCall
:: [ExtFCode (CmmFormal,MachHint)]
-> FastString
Expand Down
2 changes: 2 additions & 0 deletions rts/HeapStackCheck.cmm
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,8 @@
#include "Cmm.h"

#ifdef __PIC__
import EnterCriticalSection
import LeaveCriticalSection
import pthread_mutex_unlock;
#endif

Expand Down
2 changes: 2 additions & 0 deletions rts/PrimOps.cmm
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,8 @@ import __gmpz_com;
import base_GHCziIOBase_NestedAtomically_closure;
import pthread_mutex_lock;
import pthread_mutex_unlock;
import EnterCriticalSection
import LeaveCriticalSection
#endif

/*-----------------------------------------------------------------------------
Expand Down
2 changes: 2 additions & 0 deletions rts/StgMiscClosures.cmm
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@

#ifdef __PIC__
import pthread_mutex_lock;
import EnterCriticalSection
import LeaveCriticalSection
import base_GHCziBase_Czh_static_info;
import base_GHCziBase_Izh_static_info;
#endif
Expand Down

0 comments on commit 0981e24

Please sign in to comment.