summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen/CgInfoTbls.hs
diff options
context:
space:
mode:
authorwolfgang <unknown>2004-10-07 15:54:42 +0000
committerwolfgang <unknown>2004-10-07 15:54:42 +0000
commitb4d045ae655e5eae25b88917cfe75d7dc7689c21 (patch)
tree73086cc32e23092a4808a7a78b3036579a867aea /ghc/compiler/codeGen/CgInfoTbls.hs
parenta558bffdbf9288a5c6620b9553ec4839c8b904e4 (diff)
downloadhaskell-b4d045ae655e5eae25b88917cfe75d7dc7689c21.tar.gz
[project @ 2004-10-07 15:54:03 by wolfgang]
Position Independent Code and Dynamic Linking Support, Part 1 This commit allows generation of position independent code (PIC) that fully supports dynamic linking on Mac OS X and PowerPC Linux. Other platforms are not yet supported, and there is no support for actually linking or using dynamic libraries - so if you use the -fPIC or -dynamic code generation flags, you have to type your (platform-specific) linker command lines yourself. nativeGen/PositionIndependentCode.hs: New file. Look here for some more comments on how this works. cmm/CLabel.hs: Add support for DynamicLinkerLabels and PIC base labels - for use inside the NCG. needsCDecl: Case alternative labels now need C decls, see the codeGen/CgInfoTbls.hs below for details cmm/Cmm.hs: Add CmmPicBaseReg (used in NCG), and CmmLabelDiffOff (used in NCG and for offsets in info tables) cmm/CmmParse.y: support offsets in info tables cmm/PprC.hs: support CmmLabelDiffOff Case alternative labels now need C decls (see the codeGen/CgInfoTbls.hs for details), so we need to pprDataExterns for info tables. cmm/PprCmm.hs: support CmmLabelDiffOff codeGen/CgInfoTbls.hs: no longer store absolute addresses in info tables, instead, we store offsets. Also, for vectored return points, emit the alternatives _after_ the vector table. This is to work around a limitation in Apple's as, which refuses to handle label differences where one label is at the end of a section. Emitting alternatives after vector info tables makes sure this never happens in GHC generated code. Case alternatives now require prototypes in hc code, though (see changes in PprC.hs, CLabel.hs). main/CmdLineOpts.lhs: Add a new option, -fPIC. main/DriverFlags.hs: Pass the correct options for PIC to gcc, depending on the platform. Only for powerpc for now. nativeGen/AsmCodeGen.hs: Many changes... Mac OS X-specific management of import stubs is no longer, it's now part of a general mechanism to handle such things for all platforms that need it (Darwin [both ppc and x86], Linux on ppc, and some platforms we don't support). Move cmmToCmm into its own monad which can accumulate a list of imported symbols. Make it call cmmMakeDynamicReference at the right places. nativeGen/MachCodeGen.hs: nativeGen/MachInstrs.hs: nativeGen/MachRegs.lhs: nativeGen/PprMach.hs: nativeGen/RegAllocInfo.hs: Too many changes to enumerate here, PowerPC specific. nativeGen/NCGMonad.hs: NatM still tracks imported symbols, as more labels can be created during code generation (float literals, jump tables; on some platforms all data access has to go through the dynamic linking mechanism). driver/mangler/ghc-asm.lprl: Mangle absolute addresses in info tables to offsets. Correctly pass through GCC-generated PIC for Mac OS X and powerpc linux. includes/Cmm.h: includes/InfoTables.h: includes/Storage.h: includes/mkDerivedConstants.c: rts/GC.c: rts/GCCompact.c: rts/HeapStackCheck.cmm: rts/Printer.c: rts/RetainerProfile.c: rts/Sanity.c: Adapt to the fact that info tables now contain offsets. rts/Linker.c: Mac-specific: change machoInitSymbolsWithoutUnderscore to support PIC.
Diffstat (limited to 'ghc/compiler/codeGen/CgInfoTbls.hs')
-rw-r--r--ghc/compiler/codeGen/CgInfoTbls.hs78
1 files changed, 59 insertions, 19 deletions
diff --git a/ghc/compiler/codeGen/CgInfoTbls.hs b/ghc/compiler/codeGen/CgInfoTbls.hs
index 5cda82352a..7692e7d71b 100644
--- a/ghc/compiler/codeGen/CgInfoTbls.hs
+++ b/ghc/compiler/codeGen/CgInfoTbls.hs
@@ -15,13 +15,14 @@ module CgInfoTbls (
emitDirectReturnInstr, emitVectoredReturnInstr,
mkRetInfoTable,
mkStdInfoTable,
+ stdInfoTableSizeB,
mkFunGenInfoExtraBits,
entryCode, closureInfoPtr,
getConstrTag,
infoTable, infoTableClosureType,
infoTablePtrs, infoTableNonPtrs,
funInfoTable,
- vectorSlot,
+ retVec
) where
@@ -120,7 +121,7 @@ emitClosureCodeAndInfoTable cl_info args body
(mkIntCLit 0, fromIntegral (dataConTagZ con))
Nothing -> -- Not a constructor
- srtLabelAndLength srt
+ srtLabelAndLength srt info_lbl
ptrs = closurePtrsSize cl_info
nptrs = size - ptrs
@@ -141,11 +142,14 @@ emitClosureCodeAndInfoTable cl_info args body
| ArgGen liveness <- arg_descr
= [ fun_amode,
srt_label,
- mkLivenessCLit liveness,
- CmmLabel (mkSlowEntryLabel (closureName cl_info)) ]
+ makeRelativeRefTo info_lbl $ mkLivenessCLit liveness,
+ slow_entry ]
| needs_srt = [fun_amode, srt_label]
| otherwise = [fun_amode]
+ slow_entry = makeRelativeRefTo info_lbl (CmmLabel slow_entry_label)
+ slow_entry_label = mkSlowEntryLabel (closureName cl_info)
+
fun_amode = packHalfWordsCLit fun_type arity
fun_type = argDescrType arg_descr
@@ -207,7 +211,15 @@ vectorSlot info_amode zero_indexed_tag
zero_indexed_tag
-- The "2" is one for the entry-code slot and one for the SRT slot
-
+retVec :: CmmExpr -> CmmExpr -> CmmExpr
+-- Get a return vector from the info pointer
+retVec info_amode zero_indexed_tag
+ = let slot = vectorSlot info_amode zero_indexed_tag
+ tableEntry = CmmLoad slot wordRep
+ in if tablesNextToCode
+ then CmmMachOp (MO_Add wordRep) [tableEntry, info_amode]
+ else tableEntry
+
emitReturnTarget
:: Name
-> CgStmts -- The direct-return code (if any)
@@ -229,7 +241,7 @@ emitReturnTarget name stmts vector srt
(False, False) -> rET_VEC_SMALL
(std_info, extra_bits) =
- mkRetInfoTable liveness srt_info cl_type vector
+ mkRetInfoTable info_lbl liveness srt_info cl_type vector
; blks <- cgStmtsToBlocks stmts
; emitInfoTableAndCode info_lbl std_info extra_bits args blks
@@ -241,15 +253,16 @@ emitReturnTarget name stmts vector srt
mkRetInfoTable
- :: Liveness -- liveness
+ :: CLabel -- info label
+ -> Liveness -- liveness
-> C_SRT -- SRT Info
-> Int -- type (eg. rET_SMALL)
-> [CmmLit] -- vector
-> ([CmmLit],[CmmLit])
-mkRetInfoTable liveness srt_info cl_type vector
+mkRetInfoTable info_lbl liveness srt_info cl_type vector
= (std_info, extra_bits)
where
- (srt_label, srt_len) = srtLabelAndLength srt_info
+ (srt_label, srt_len) = srtLabelAndLength srt_info info_lbl
srt_slot | need_srt = [srt_label]
| otherwise = []
@@ -259,9 +272,9 @@ mkRetInfoTable liveness srt_info cl_type vector
-- an SRT slot, so that the vector table is at a
-- known offset from the info pointer
- liveness_lit = mkLivenessCLit liveness
+ liveness_lit = makeRelativeRefTo info_lbl $ mkLivenessCLit liveness
std_info = mkStdInfoTable zeroCLit zeroCLit cl_type srt_len liveness_lit
- extra_bits = srt_slot ++ vector
+ extra_bits = srt_slot ++ map (makeRelativeRefTo info_lbl) vector
emitDirectReturnTarget
@@ -292,11 +305,15 @@ emitAlgReturnTarget name branches mb_deflt srt ret_conv
-- global labels, so we can't use them at the 'call site'
VectoredReturn fam_sz -> do
- { tagged_lbls <- mapFCs emit_alt branches
- ; deflt_lbl <- emit_deflt mb_deflt
+ { let tagged_lbls = zip (map fst branches) $
+ map (CmmLabel . mkAltLabel uniq . fst) branches
+ deflt_lbl | isJust mb_deflt = CmmLabel $ mkDefaultLabel uniq
+ | otherwise = mkIntCLit 0
; let vector = [ assocDefault deflt_lbl tagged_lbls i
| i <- [0..fam_sz-1]]
; lbl <- emitReturnTarget name noCgStmts vector srt
+ ; mapFCs emit_alt branches
+ ; emit_deflt mb_deflt
; return (lbl, Just (tagged_lbls, deflt_lbl)) }
where
uniq = getUnique name
@@ -331,9 +348,8 @@ emitVectoredReturnInstr :: CmmExpr -- *Zero-indexed* constructor tag
-> Code
emitVectoredReturnInstr zero_indexed_tag
= do { info_amode <- getSequelAmode
- ; let slot = vectorSlot info_amode zero_indexed_tag
- ; stmtC (CmmJump (CmmLoad slot wordRep) []) }
-
+ ; let target = retVec info_amode zero_indexed_tag
+ ; stmtC (CmmJump target []) }
-------------------------------------------------------------------------
@@ -532,7 +548,31 @@ getSRTInfo id (SRT off len bmp)
srt_escape = (-1) :: StgHalfWord
-srtLabelAndLength :: C_SRT -> (CmmLit, StgHalfWord)
-srtLabelAndLength NoC_SRT = (zeroCLit, 0)
-srtLabelAndLength (C_SRT lbl off bitmap) = (cmmLabelOffW lbl off, bitmap)
+srtLabelAndLength :: C_SRT -> CLabel -> (CmmLit, StgHalfWord)
+srtLabelAndLength NoC_SRT _
+ = (zeroCLit, 0)
+srtLabelAndLength (C_SRT lbl off bitmap) info_lbl
+ = (makeRelativeRefTo info_lbl $ cmmLabelOffW lbl off, bitmap)
+-------------------------------------------------------------------------
+--
+-- Position independent code
+--
+-------------------------------------------------------------------------
+-- In order to support position independent code, we mustn't put absolute
+-- references into read-only space. Info tables in the tablesNextToCode
+-- case must be in .text, which is read-only, so we doctor the CmmLits
+-- to use relative offsets instead.
+
+-- Note that this is done even when the -fPIC flag is not specified,
+-- as we want to keep binary compatibility between PIC and non-PIC.
+
+makeRelativeRefTo :: CLabel -> CmmLit -> CmmLit
+
+makeRelativeRefTo info_lbl (CmmLabel lbl)
+ | tablesNextToCode
+ = CmmLabelDiffOff lbl info_lbl 0
+makeRelativeRefTo info_lbl (CmmLabelOff lbl off)
+ | tablesNextToCode
+ = CmmLabelDiffOff lbl info_lbl off
+makeRelativeRefTo _ lit = lit