c3b16397c1ef37a38bc2b8b3e477aaad3b859196
[ghc-hetmet.git] / ghc / compiler / nativeGen / PositionIndependentCode.hs
1 #include "../includes/ghcconfig.h"
2
3 module PositionIndependentCode (
4         cmmMakeDynamicReference,
5         needImportedSymbols,
6         pprImportedSymbol,
7         pprGotDeclaration,
8         initializePicBase
9      ) where
10
11 {-
12   This module handles generation of position independent code and
13   dynamic-linking related issues for the native code generator.
14   
15   Things outside this module which are related to this:
16   
17   + module CLabel
18     - PIC base label (pretty printed as local label 1)
19     - DynamicLinkerLabels - several kinds:
20         CodeStub, SymbolPtr, GotSymbolPtr, GotSymbolOffset
21     - labelDynamic predicate
22   + module Cmm
23     - The CmmExpr datatype has a CmmPicBaseReg constructor
24     - The CmmLit datatype has a CmmLabelDiffOff constructor
25   + codeGen & RTS
26     - When tablesNextToCode, no absolute addresses are stored in info tables
27       any more. Instead, offsets from the info label are used.
28     - For Win32 only, SRTs might contain addresses of __imp_ symbol pointers
29       because Win32 doesn't support external references in data sections.
30       TODO: make sure this still works, it might be bitrotted
31   + NCG
32     - The cmmToCmm pass in AsmCodeGen calls cmmMakeDynamicReference for all
33       labels.
34     - nativeCodeGen calls pprImportedSymbol and pprGotDeclaration to output
35       all the necessary stuff for imported symbols.
36     - The NCG monad keeps track of a list of imported symbols.
37     - MachCodeGen invokes initializePicBase to generate code to initialize
38       the PIC base register when needed.
39     - MachCodeGen calls cmmMakeDynamicReference whenever it uses a CLabel
40       that wasn't in the original Cmm code (e.g. floating point literals).
41   + The Mangler
42     - The mangler converts absolure refs to relative refs in info tables
43     - Symbol pointers, stub code and PIC calculations that are generated
44       by GCC are left intact by the mangler (so far only on ppc-darwin
45       and ppc-linux).
46 -}
47      
48 #include "HsVersions.h"
49 #include "nativeGen/NCG.h"
50
51 import Cmm
52 import MachOp           ( MachOp(MO_Add), wordRep )
53 import CLabel           ( CLabel, pprCLabel,
54                           mkDynamicLinkerLabel, DynamicLinkerLabelInfo(..),
55                           dynamicLinkerLabelInfo, mkPicBaseLabel,
56                           labelDynamic, externallyVisibleCLabel )
57
58 import MachRegs
59 import MachInstrs
60 import NCGMonad         ( NatM, getNewRegNat, getNewLabelNat )
61
62 import CmdLineOpts      ( opt_PIC )
63
64 import Pretty
65 import qualified Outputable
66
67 import Panic            ( panic )
68
69
70 -- The most important function here is cmmMakeDynamicReference.
71
72 -- It gets called by the cmmToCmm pass for every CmmLabel in the Cmm
73 -- code. It does The Right Thing(tm) to convert the CmmLabel into a
74 -- position-independent, dynamic-linking-aware reference to the thing
75 -- in question.
76 -- Note that this also has to be called from MachCodeGen in order to
77 -- access static data like floating point literals (labels that were
78 -- created after the cmmToCmm pass).
79 -- The function must run in a monad that can keep track of imported symbols
80 -- A function for recording an imported symbol must be passed in:
81 -- - addImportCmmOpt for the CmmOptM monad
82 -- - addImportNat for the NatM monad.
83
84 cmmMakeDynamicReference
85   :: Monad m => (CLabel -> m ())  -- a monad & a function
86                                   -- used for recording imported symbols
87              -> Bool              -- whether this is the target of a jump
88              -> CLabel            -- the label
89              -> m CmmExpr
90   
91 cmmMakeDynamicReference addImport isJumpTarget lbl
92   | Just _ <- dynamicLinkerLabelInfo lbl
93   = return $ CmmLit $ CmmLabel lbl   -- already processed it, pass through
94   | otherwise = case howToAccessLabel isJumpTarget lbl of
95         AccessViaStub -> do
96               let stub = mkDynamicLinkerLabel CodeStub lbl
97               addImport stub
98               return $ CmmLit $ CmmLabel stub
99         AccessViaSymbolPtr -> do
100               let symbolPtr = mkDynamicLinkerLabel SymbolPtr lbl
101               addImport symbolPtr
102               return $ CmmLoad (cmmMakePicReference symbolPtr) wordRep
103         AccessDirectly
104                 -- all currently supported processors support
105                 -- a PC-relative branch instruction, so just jump there
106           | isJumpTarget -> return $ CmmLit $ CmmLabel lbl
107                 -- for data, we might have to make some calculations:
108           | otherwise    -> return $ cmmMakePicReference lbl  
109   
110 -- -------------------------------------------------------------------
111   
112 -- Create a position independent reference to a label.
113 -- (but do not bother with dynamic linking).
114 -- We calculate the label's address by adding some (platform-dependent)
115 -- offset to our base register; this offset is calculated by
116 -- the function picRelative in the platform-dependent part below.
117
118 cmmMakePicReference :: CLabel -> CmmExpr
119   
120 #if !mingw32_TARGET_OS
121         -- Windows doesn't need PIC,
122         -- everything gets relocated at runtime
123
124 cmmMakePicReference lbl
125     | opt_PIC && absoluteLabel lbl = CmmMachOp (MO_Add wordRep) [
126             CmmPicBaseReg,
127             CmmLit $ picRelative lbl
128         ]
129     where
130         absoluteLabel lbl = case dynamicLinkerLabelInfo lbl of
131                                 Just (GotSymbolPtr, _) -> False
132                                 Just (GotSymbolOffset, _) -> False
133                                 _ -> True
134
135 #endif
136 cmmMakePicReference lbl = CmmLit $ CmmLabel lbl
137
138 -- ===================================================================
139 -- Platform dependent stuff
140 -- ===================================================================
141
142 -- Knowledge about how special dynamic linker labels like symbol
143 -- pointers, code stubs and GOT offsets look like is located in the
144 -- module CLabel.
145
146 -- -------------------------------------------------------------------
147
148 -- We have to decide which labels need to be accessed
149 -- indirectly or via a piece of stub code.
150
151 data LabelAccessStyle = AccessViaStub
152                       | AccessViaSymbolPtr
153                       | AccessDirectly
154
155 howToAccessLabel :: Bool -> CLabel -> LabelAccessStyle
156
157 #if mingw32_TARGET_OS
158 -- Windows
159 -- 
160 -- We need to use access *exactly* those things that
161 -- are imported from a DLL via an __imp_* label.
162 -- There are no stubs for imported code.
163
164 howToAccessLabel _ lbl | labelDynamic lbl = AccessViaSymbolPtr
165                        | otherwise        = AccessDirectly
166
167 #elif darwin_TARGET_OS
168 -- Mach-O (Darwin, Mac OS X)
169 --
170 -- Indirect access is required in the following cases:
171 -- * things imported from a dynamic library
172 -- * things from a different module, if we're generating PIC code
173 -- It is always possible to access something indirectly,
174 -- even when it's not necessary.
175
176 howToAccessLabel True lbl
177       -- jumps to a dynamic library go via a symbol stub
178     | labelDynamic lbl = AccessViaStub
179       -- when generating PIC code, all cross-module references must
180       -- must go via a symbol pointer, too.
181       -- Unfortunately, we don't know whether it's cross-module,
182       -- so we do it for all externally visible labels.
183       -- This is a slight waste of time and space, but otherwise
184       -- we'd need to pass the current Module all the way in to
185       -- this function.
186     | opt_PIC && externallyVisibleCLabel lbl = AccessViaStub
187 howToAccessLabel False lbl
188       -- data access to a dynamic library goes via a symbol pointer
189     | labelDynamic lbl = AccessViaSymbolPtr
190       -- cross-module PIC references: same as above
191     | opt_PIC && externallyVisibleCLabel lbl = AccessViaSymbolPtr
192 howToAccessLabel _ _ = AccessDirectly
193
194 #elif linux_TARGET_OS && powerpc_TARGET_ARCH
195 -- PowerPC Linux
196 --
197 -- PowerPC Linux is just plain broken.
198 -- While it's theoretically possible to use GOT offsets larger
199 -- than 16 bit, the standard crt*.o files don't, which leads to
200 -- linker errors as soon as the GOT size exceeds 16 bit.
201 -- Also, the assembler doesn't support @gotoff labels.
202 -- In order to be able to use a larger GOT, we circumvent the
203 -- entire GOT mechanism and do it ourselves (this is what GCC does).
204
205 -- In this scheme, we need to do _all data references_ (even refs
206 -- to static data) via a SymbolPtr when we are generating PIC.
207 -- Luckily, the PLT works as expected, so we can simply access
208 -- dynamically linked code via the PLT.
209
210 howToAccessLabel _ _ | not opt_PIC = AccessDirectly
211 howToAccessLabel True lbl
212     = if labelDynamic lbl then AccessViaStub
213                           else AccessDirectly
214 howToAccessLabel False lbl
215     = AccessViaSymbolPtr
216
217 #elif linux_TARGET_OS
218 -- ELF (Linux)
219 --
220 -- Indirect access is required for references to imported symbols
221 -- from position independent code.
222 -- It is always possible to access something indirectly,
223 -- even when it's not necessary.
224
225 -- For code, we can use a relative jump to a piece of
226 -- stub code instead (this allows lazy binding of imported symbols).
227
228 howToAccessLabel isJump lbl
229         -- no PIC -> the dynamic linker does everything for us
230    | not opt_PIC = AccessDirectly
231         -- if it's not imported, we need no indirection
232         -- ("foo" will end up being accessed as "foo@GOTOFF")
233    | not (labelDynamic lbl) = AccessDirectly
234 #if !i386_TARGET_ARCH
235 -- for Intel, we temporarily disable the use of the
236 -- Procedure Linkage Table, because PLTs on intel require the
237 -- address of the GOT to be loaded into register %ebx before
238 -- a jump through the PLT is made.
239 -- TODO: make the i386 NCG ensure this before jumping to a
240 --       CodeStub label, so we can remove this special case.
241    | isJump = AccessViaStub
242 #endif
243    | otherwise = AccessViaSymbolPtr
244
245 #else
246 --
247 -- all other platforms
248 --
249 howToAccessLabel _ _
250         | not opt_PIC = AccessDirectly
251         | otherwise   = panic "howToAccessLabel: PIC not defined for this platform"
252 #endif
253
254 -- -------------------------------------------------------------------
255
256 -- What do we have to add to our 'PIC base register' in order to
257 -- get the address of a label?
258
259 picRelative :: CLabel -> CmmLit
260 #if darwin_TARGET_OS
261 -- Darwin:
262 -- The PIC base register points to the PIC base label at the beginning
263 -- of the current CmmTop. We just have to use a label difference to
264 -- get the offset.
265 -- We have already made sure that all labels that are not from the current
266 -- module are accessed indirectly ('as' can't calculate differences between
267 -- undefined labels).
268
269 picRelative lbl
270   = CmmLabelDiffOff lbl mkPicBaseLabel 0
271
272 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
273 -- PowerPC Linux:
274 -- The PIC base register points to our fake GOT. Use a label difference
275 -- to get the offset.
276 -- We have made sure that *everything* is accessed indirectly, so this
277 -- is only used for offsets from the GOT to symbol pointers inside the
278 -- GOT.
279 picRelative lbl
280   = CmmLabelDiffOff lbl gotLabel 0
281
282 #elif linux_TARGET_OS
283 -- Other Linux versions:
284 -- The PIC base register points to the GOT. Use foo@got for symbol
285 -- pointers, and foo@gotoff for everything else.
286
287 picRelative lbl
288   | Just (SymbolPtr, lbl') <- dynamicLinkerLabelInfo lbl
289   = CmmLabel $ mkDynamicLinkerLabel GotSymbolPtr lbl'
290   | otherwise
291   = CmmLabel $ mkDynamicLinkerLabel GotSymbolOffset lbl
292
293 #else
294 picRelative lbl = panic "PositionIndependentCode.picRelative"
295 #endif
296
297 -- -------------------------------------------------------------------
298
299 -- What do we have to add to every assembly file we generate?
300
301 -- utility function for pretty-printing asm-labels,
302 -- copied from PprMach
303 asmSDoc d = Outputable.withPprStyleDoc (
304               Outputable.mkCodeStyle Outputable.AsmStyle) d
305 pprCLabel_asm l = asmSDoc (pprCLabel l)
306
307
308 #if darwin_TARGET_OS
309
310 needImportedSymbols = True
311
312 -- We don't need to declare any offset tables
313 pprGotDeclaration = Pretty.empty
314
315 -- On Darwin, we have to generate our own stub code for lazy binding..
316 -- There are two versions, one for PIC and one for non-PIC.
317 pprImportedSymbol importedLbl
318     | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
319     = case opt_PIC of
320         False ->
321             vcat [
322                 ptext SLIT(".symbol_stub"),
323                 ptext SLIT("L") <> pprCLabel_asm lbl <> ptext SLIT("$stub:"),
324                     ptext SLIT("\t.indirect_symbol") <+> pprCLabel_asm lbl,
325                     ptext SLIT("\tlis r11,ha16(L") <> pprCLabel_asm lbl
326                         <> ptext SLIT("$lazy_ptr)"),
327                     ptext SLIT("\tlwz r12,lo16(L") <> pprCLabel_asm lbl
328                         <> ptext SLIT("$lazy_ptr)(r11)"),
329                     ptext SLIT("\tmtctr r12"),
330                     ptext SLIT("\taddi r11,r11,lo16(L") <> pprCLabel_asm lbl
331                         <> ptext SLIT("$lazy_ptr)"),
332                     ptext SLIT("\tbctr")
333             ]
334         True ->
335             vcat [
336                 ptext SLIT(".section __TEXT,__picsymbolstub1,")
337                   <> ptext SLIT("symbol_stubs,pure_instructions,32"),
338                 ptext SLIT("L") <> pprCLabel_asm lbl <> ptext SLIT("$stub:"),
339                     ptext SLIT("\t.indirect_symbol") <+> pprCLabel_asm lbl,
340                     ptext SLIT("\tmflr r0"),
341                     ptext SLIT("\tbcl 20,31,L0$") <> pprCLabel_asm lbl,
342                 ptext SLIT("L0$") <> pprCLabel_asm lbl <> char ':',
343                     ptext SLIT("\tmflr r11"),
344                     ptext SLIT("\taddis r11,r11,ha16(L") <> pprCLabel_asm lbl
345                         <> ptext SLIT("$lazy_ptr-L0$") <> pprCLabel_asm lbl <> char ')',
346                     ptext SLIT("\tmtlr r0"),
347                     ptext SLIT("\tlwzu r12,lo16(L") <> pprCLabel_asm lbl
348                         <> ptext SLIT("$lazy_ptr-L0$") <> pprCLabel_asm lbl
349                         <> ptext SLIT(")(r11)"),
350                     ptext SLIT("\tmtctr r12"),
351                     ptext SLIT("\tbctr")
352             ]
353     $+$ vcat [
354         ptext SLIT(".lazy_symbol_pointer"),
355         ptext SLIT("L") <> pprCLabel_asm lbl <> ptext SLIT("$lazy_ptr:"),
356             ptext SLIT("\t.indirect_symbol") <+> pprCLabel_asm lbl,
357             ptext SLIT("\t.long dyld_stub_binding_helper")
358     ]
359
360 -- We also have to declare our symbol pointers ourselves:
361     | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
362     = vcat [
363         ptext SLIT(".non_lazy_symbol_pointer"),
364         char 'L' <> pprCLabel_asm lbl <> ptext SLIT("$non_lazy_ptr:"),
365             ptext SLIT("\t.indirect_symbol") <+> pprCLabel_asm lbl,
366             ptext SLIT("\t.long\t0")
367     ]
368
369     | otherwise = empty
370
371 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
372
373 -- For PowerPC linux, we don't do anything unless we're generating PIC.
374 needImportedSymbols = opt_PIC
375
376 -- If we're generating PIC, we need to create our own "fake GOT".
377
378 gotLabel = mkForeignLabel -- HACK: it's not really foreign
379                            FSLIT(".LCTOC1") Nothing False
380
381 -- The .LCTOC1 label is defined to point 32768 bytes into the table,
382 -- to make the most of the PPC's 16-bit displacements.
383
384 pprGotDeclaration = vcat [
385         ptext SLIT(".section \".got2\",\"aw\""),
386         ptext SLIT(".LCTOC1 = .+32768")
387     ]
388
389 -- We generate one .long literal for every symbol we import;
390 -- the dynamic linker will relocate those addresses.
391     
392 pprImportedSymbol importedLbl
393     | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
394     vcat [
395         ptext SLIT(".section \".got2\", \"aw\""),
396         ptext SLIT(".LC_") <> pprCLabel_asm lbl <> char ':',
397         ptext SLIT("\t.long") <+> pprCLabel_asm lbl
398     ]
399
400 -- PLT code stubs are generated automatically be the dynamic linker.
401     | otherwise = empty
402
403 #else
404
405 -- For all other currently supported platforms, we don't need to do
406 -- anything at all.
407
408 needImportedSymbols = False
409 pprGotDeclaration = Pretty.empty
410 pprImportedSymbol _ = empty
411 #endif
412
413 -- -------------------------------------------------------------------
414
415 -- Generate code to calculate the address that should be put in the
416 -- PIC base register.
417 -- This is called by MachCodeGen for every CmmProc that accessed the
418 -- PIC base register. It adds the appropriate instructions to the
419 -- top of the CmmProc.
420
421 -- It is assumed that the first NatCmmTop in the input list is a Proc
422 -- and the rest are CmmDatas.
423
424 initializePicBase :: Reg -> [NatCmmTop] -> NatM [NatCmmTop]
425
426 #if powerpc_TARGET_ARCH && darwin_TARGET_OS
427
428 -- Darwin is simple: just fetch the address of a local label.
429 initializePicBase picReg (CmmProc info lab params blocks : statics)
430     = return (CmmProc info lab params (b':tail blocks) : statics)
431     where BasicBlock bID insns = head blocks
432           b' = BasicBlock bID (FETCHPC picReg : insns)
433
434 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
435
436 -- Get a pointer to our own fake GOT, which is defined on a per-module basis.
437 -- This is exactly how GCC does it, and it's quite horrible:
438 -- We first fetch the address of a local label (mkPicBaseLabel).
439 -- Then we add a 16-bit offset to that to get the address of a .long that we
440 -- define in .text space right next to the proc. This .long literal contains
441 -- the (32-bit) offset from our local label to our global offset table
442 -- (.LCTOC1 aka gotOffLabel).
443 initializePicBase picReg
444     (CmmProc info lab params blocks : statics)
445     = do
446         gotOffLabel <- getNewLabelNat
447         tmp <- getNewRegNat wordRep
448         let 
449             gotOffset = CmmData Text [
450                             CmmDataLabel gotOffLabel,
451                             CmmStaticLit (CmmLabelDiffOff gotLabel
452                                                           mkPicBaseLabel
453                                                           0)
454                         ]
455             offsetToOffset = ImmConstantDiff (ImmCLbl gotOffLabel)
456                                              (ImmCLbl mkPicBaseLabel)
457             BasicBlock bID insns = head blocks
458             b' = BasicBlock bID (FETCHPC picReg
459                                : LD wordRep tmp
460                                     (AddrRegImm picReg offsetToOffset)
461                                : ADD picReg picReg (RIReg tmp)
462                                : insns)
463         return (CmmProc info lab params (b' : tail blocks) : gotOffset : statics)
464 #else
465 initializePicBase picReg proc = panic "initializePicBase"
466
467 -- TODO:
468 -- i386_TARGET_ARCH && linux_TARGET_OS:
469 -- generate something like:
470 --              call 1f
471 -- 1:           popl %picReg
472 --              addl __GLOBAL_OFFSET_TABLE__+.-1b, %picReg
473 -- It might be a good idea to use a FETCHPC pseudo-instruction (like for PowerPC)
474 -- in order to avoid having to create a new basic block.
475 -- ((FETCHPC reg) should pretty-print as call 1f; 1: popl reg)
476
477 -- mingw32_TARGET_OS: not needed, won't be called
478
479 -- i386_TARGET_ARCH && darwin_TARGET_OS:
480 -- (just for completeness ;-)
481 --              call 1f
482 -- 1:           popl %picReg
483 #endif