d74a627d0a5d21b3dc284ba24778f8ee3da2ca1b
[ghc-hetmet.git] / compiler / nativeGen / PositionIndependentCode.hs
1 {-# OPTIONS -w #-}
2 -- The above warning supression flag is a temporary kludge.
3 -- While working on this module you are encouraged to remove it and fix
4 -- any warnings in the module. See
5 --     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
6 -- for details
7
8 module PositionIndependentCode (
9         cmmMakeDynamicReference,
10         ReferenceKind(..),
11         needImportedSymbols,
12         pprImportedSymbol,
13         pprGotDeclaration,
14         initializePicBase
15      ) where
16
17 #include "HsVersions.h"
18
19 {-
20   This module handles generation of position independent code and
21   dynamic-linking related issues for the native code generator.
22   
23   Things outside this module which are related to this:
24   
25   + module CLabel
26     - PIC base label (pretty printed as local label 1)
27     - DynamicLinkerLabels - several kinds:
28         CodeStub, SymbolPtr, GotSymbolPtr, GotSymbolOffset
29     - labelDynamic predicate
30   + module Cmm
31     - The GlobalReg datatype has a PicBaseReg constructor
32     - The CmmLit datatype has a CmmLabelDiffOff constructor
33   + codeGen & RTS
34     - When tablesNextToCode, no absolute addresses are stored in info tables
35       any more. Instead, offsets from the info label are used.
36     - For Win32 only, SRTs might contain addresses of __imp_ symbol pointers
37       because Win32 doesn't support external references in data sections.
38       TODO: make sure this still works, it might be bitrotted
39   + NCG
40     - The cmmToCmm pass in AsmCodeGen calls cmmMakeDynamicReference for all
41       labels.
42     - nativeCodeGen calls pprImportedSymbol and pprGotDeclaration to output
43       all the necessary stuff for imported symbols.
44     - The NCG monad keeps track of a list of imported symbols.
45     - MachCodeGen invokes initializePicBase to generate code to initialize
46       the PIC base register when needed.
47     - MachCodeGen calls cmmMakeDynamicReference whenever it uses a CLabel
48       that wasn't in the original Cmm code (e.g. floating point literals).
49   + The Mangler
50     - The mangler converts absolure refs to relative refs in info tables
51     - Symbol pointers, stub code and PIC calculations that are generated
52       by GCC are left intact by the mangler (so far only on ppc-darwin
53       and ppc-linux).
54 -}
55
56 #include "nativeGen/NCG.h"
57
58 import Cmm
59 import CLabel           ( CLabel, pprCLabel,
60                           mkDynamicLinkerLabel, DynamicLinkerLabelInfo(..),
61                           dynamicLinkerLabelInfo, mkPicBaseLabel,
62                           labelDynamic, externallyVisibleCLabel )
63
64 #if linux_TARGET_OS
65 import CLabel           ( mkForeignLabel )
66 #endif
67
68 import Regs
69 import Instrs
70 import NCGMonad         ( NatM, getNewRegNat, getNewLabelNat )
71
72 import StaticFlags      ( opt_PIC, opt_Static )
73
74 import Pretty
75 import qualified Outputable
76
77 import Panic            ( panic )
78 import DynFlags
79 import FastString
80
81
82 -- The most important function here is cmmMakeDynamicReference.
83
84 -- It gets called by the cmmToCmm pass for every CmmLabel in the Cmm
85 -- code. It does The Right Thing(tm) to convert the CmmLabel into a
86 -- position-independent, dynamic-linking-aware reference to the thing
87 -- in question.
88 -- Note that this also has to be called from MachCodeGen in order to
89 -- access static data like floating point literals (labels that were
90 -- created after the cmmToCmm pass).
91 -- The function must run in a monad that can keep track of imported symbols
92 -- A function for recording an imported symbol must be passed in:
93 -- - addImportCmmOpt for the CmmOptM monad
94 -- - addImportNat for the NatM monad.
95
96 data ReferenceKind = DataReference
97                    | CallReference
98                    | JumpReference
99                    deriving(Eq)
100
101 cmmMakeDynamicReference
102   :: Monad m => DynFlags
103              -> (CLabel -> m ())  -- a monad & a function
104                                   -- used for recording imported symbols
105              -> ReferenceKind     -- whether this is the target of a jump
106              -> CLabel            -- the label
107              -> m CmmExpr
108   
109 cmmMakeDynamicReference dflags addImport referenceKind lbl
110   | Just _ <- dynamicLinkerLabelInfo lbl
111   = return $ CmmLit $ CmmLabel lbl   -- already processed it, pass through
112   | otherwise = case howToAccessLabel dflags referenceKind lbl of
113         AccessViaStub -> do
114               let stub = mkDynamicLinkerLabel CodeStub lbl
115               addImport stub
116               return $ CmmLit $ CmmLabel stub
117         AccessViaSymbolPtr -> do
118               let symbolPtr = mkDynamicLinkerLabel SymbolPtr lbl
119               addImport symbolPtr
120               return $ CmmLoad (cmmMakePicReference symbolPtr) bWord
121         AccessDirectly -> case referenceKind of
122                 -- for data, we might have to make some calculations:
123               DataReference -> return $ cmmMakePicReference lbl  
124                 -- all currently supported processors support
125                 -- PC-relative branch and call instructions,
126                 -- so just jump there if it's a call or a jump
127               _ -> return $ CmmLit $ CmmLabel lbl
128   
129 -- -------------------------------------------------------------------
130   
131 -- Create a position independent reference to a label.
132 -- (but do not bother with dynamic linking).
133 -- We calculate the label's address by adding some (platform-dependent)
134 -- offset to our base register; this offset is calculated by
135 -- the function picRelative in the platform-dependent part below.
136
137 cmmMakePicReference :: CLabel -> CmmExpr
138   
139 #if !mingw32_TARGET_OS
140         -- Windows doesn't need PIC,
141         -- everything gets relocated at runtime
142
143 cmmMakePicReference lbl
144     | (opt_PIC || not opt_Static) && absoluteLabel lbl = CmmMachOp (MO_Add wordWidth) [
145             CmmReg (CmmGlobal PicBaseReg),
146             CmmLit $ picRelative lbl
147         ]
148     where
149         absoluteLabel lbl = case dynamicLinkerLabelInfo lbl of
150                                 Just (GotSymbolPtr, _) -> False
151                                 Just (GotSymbolOffset, _) -> False
152                                 _ -> True
153
154 #endif
155 cmmMakePicReference lbl = CmmLit $ CmmLabel lbl
156
157 -- ===================================================================
158 -- Platform dependent stuff
159 -- ===================================================================
160
161 -- Knowledge about how special dynamic linker labels like symbol
162 -- pointers, code stubs and GOT offsets look like is located in the
163 -- module CLabel.
164
165 -- -------------------------------------------------------------------
166
167 -- We have to decide which labels need to be accessed
168 -- indirectly or via a piece of stub code.
169
170 data LabelAccessStyle = AccessViaStub
171                       | AccessViaSymbolPtr
172                       | AccessDirectly
173
174 howToAccessLabel :: DynFlags -> ReferenceKind -> CLabel -> LabelAccessStyle
175
176 #if mingw32_TARGET_OS
177 -- Windows
178 -- 
179 -- We need to use access *exactly* those things that
180 -- are imported from a DLL via an __imp_* label.
181 -- There are no stubs for imported code.
182
183 howToAccessLabel dflags _ lbl | labelDynamic (thisPackage dflags) lbl = AccessViaSymbolPtr
184                               | otherwise        = AccessDirectly
185 #elif darwin_TARGET_OS
186 -- Mach-O (Darwin, Mac OS X)
187 --
188 -- Indirect access is required in the following cases:
189 --  * things imported from a dynamic library
190 --  * (not on x86_64) data from a different module, if we're generating PIC code
191 -- It is always possible to access something indirectly,
192 -- even when it's not necessary.
193
194 howToAccessLabel dflags DataReference lbl
195       -- data access to a dynamic library goes via a symbol pointer
196     | labelDynamic (thisPackage dflags) lbl = AccessViaSymbolPtr
197     
198 #if !x86_64_TARGET_ARCH
199       -- when generating PIC code, all cross-module data references must
200       -- must go via a symbol pointer, too, because the assembler
201       -- cannot generate code for a label difference where one
202       -- label is undefined. Doesn't apply t x86_64.
203       -- Unfortunately, we don't know whether it's cross-module,
204       -- so we do it for all externally visible labels.
205       -- This is a slight waste of time and space, but otherwise
206       -- we'd need to pass the current Module all the way in to
207       -- this function.
208     | opt_PIC && externallyVisibleCLabel lbl = AccessViaSymbolPtr
209 #endif
210     | otherwise = AccessDirectly
211
212
213 #if i386_TARGET_ARCH || x86_64_TARGET_ARCH
214     -- dyld code stubs don't work for tailcalls because the
215     -- stack alignment is only right for regular calls.
216     -- Therefore, we have to go via a symbol pointer:
217 howToAccessLabel dflags JumpReference lbl
218     | labelDynamic (thisPackage dflags) lbl
219     = AccessViaSymbolPtr
220 #endif
221
222 howToAccessLabel dflags _ lbl
223 #if !x86_64_TARGET_ARCH
224     -- Code stubs are the usual method of choice for imported code;
225     -- not needed on x86_64 because Apple's new linker, ld64, generates
226     -- them automatically.
227     | labelDynamic (thisPackage dflags) lbl
228     = AccessViaStub
229 #endif
230     | otherwise
231     = AccessDirectly
232
233
234 #elif linux_TARGET_OS && powerpc64_TARGET_ARCH
235 -- ELF PPC64 (powerpc64-linux), AIX, MacOS 9, BeOS/PPC
236
237 howToAccessLabel _ DataReference lbl = AccessViaSymbolPtr
238 howToAccessLabel _ _ lbl = AccessDirectly -- actually, .label instead of label
239
240 #elif linux_TARGET_OS
241 -- ELF (Linux)
242 --
243 -- ELF tries to pretend to the main application code that dynamic linking does 
244 -- not exist. While this may sound convenient, it tends to mess things up in
245 -- very bad ways, so we have to be careful when we generate code for the main
246 -- program (-dynamic but no -fPIC).
247 --
248 -- Indirect access is required for references to imported symbols
249 -- from position independent code. It is also required from the main program
250 -- when dynamic libraries containing Haskell code are used.
251
252 howToAccessLabel _ _ lbl
253         -- no PIC -> the dynamic linker does everything for us;
254         --           if we don't dynamically link to Haskell code,
255         --           it actually manages to do so without messing thins up.
256     | not opt_PIC && opt_Static = AccessDirectly
257    
258 howToAccessLabel dflags DataReference lbl
259         -- A dynamic label needs to be accessed via a symbol pointer.
260     | labelDynamic (thisPackage dflags) lbl = AccessViaSymbolPtr
261 #if powerpc_TARGET_ARCH
262         -- For PowerPC32 -fPIC, we have to access even static data
263         -- via a symbol pointer (see below for an explanation why
264         -- PowerPC32 Linux is especially broken).
265     | opt_PIC = AccessViaSymbolPtr
266 #endif
267     | otherwise = AccessDirectly
268
269
270 -- In most cases, we have to avoid symbol stubs on ELF, for the following reasons:
271 -- * on i386, the position-independent symbol stubs in the Procedure Linkage Table
272 --   require the address of the GOT to be loaded into register %ebx on entry.
273 -- * The linker will take any reference to the symbol stub as a hint that
274 --   the label in question is a code label. When linking executables, this
275 --   will cause the linker to replace even data references to the label with
276 --   references to the symbol stub.
277
278 -- This leaves calling a (foreign) function from non-PIC code
279 -- (AccessDirectly, because we get an implicit symbol stub)
280 -- and calling functions from PIC code on non-i386 platforms (via a symbol stub) 
281
282 howToAccessLabel dflags CallReference lbl
283     | labelDynamic (thisPackage dflags) lbl && not opt_PIC
284     = AccessDirectly
285 #if !i386_TARGET_ARCH
286     | labelDynamic (thisPackage dflags) lbl && opt_PIC
287     = AccessViaStub
288 #endif
289
290 howToAccessLabel dflags _ lbl
291     | labelDynamic (thisPackage dflags) lbl = AccessViaSymbolPtr
292     | otherwise = AccessDirectly
293 #else
294 --
295 -- all other platforms
296 --
297 howToAccessLabel _ _ _
298         | not opt_PIC = AccessDirectly
299         | otherwise   = panic "howToAccessLabel: PIC not defined for this platform"
300 #endif
301
302 -- -------------------------------------------------------------------
303
304 -- What do we have to add to our 'PIC base register' in order to
305 -- get the address of a label?
306
307 picRelative :: CLabel -> CmmLit
308 #if darwin_TARGET_OS && !x86_64_TARGET_ARCH
309 -- Darwin, but not x86_64:
310 -- The PIC base register points to the PIC base label at the beginning
311 -- of the current CmmTop. We just have to use a label difference to
312 -- get the offset.
313 -- We have already made sure that all labels that are not from the current
314 -- module are accessed indirectly ('as' can't calculate differences between
315 -- undefined labels).
316
317 picRelative lbl
318   = CmmLabelDiffOff lbl mkPicBaseLabel 0
319
320 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
321 -- PowerPC Linux:
322 -- The PIC base register points to our fake GOT. Use a label difference
323 -- to get the offset.
324 -- We have made sure that *everything* is accessed indirectly, so this
325 -- is only used for offsets from the GOT to symbol pointers inside the
326 -- GOT.
327 picRelative lbl
328   = CmmLabelDiffOff lbl gotLabel 0
329
330 #elif linux_TARGET_OS || (darwin_TARGET_OS && x86_64_TARGET_ARCH)
331 -- Most Linux versions:
332 -- The PIC base register points to the GOT. Use foo@got for symbol
333 -- pointers, and foo@gotoff for everything else.
334 -- Linux and Darwin on x86_64:
335 -- The PIC base register is %rip, we use foo@gotpcrel for symbol pointers,
336 -- and a GotSymbolOffset label for other things.
337 -- For reasons of tradition, the symbol offset label is written as a plain label.
338
339 picRelative lbl
340   | Just (SymbolPtr, lbl') <- dynamicLinkerLabelInfo lbl
341   = CmmLabel $ mkDynamicLinkerLabel GotSymbolPtr lbl'
342   | otherwise
343   = CmmLabel $ mkDynamicLinkerLabel GotSymbolOffset lbl
344
345 #else
346 picRelative lbl = panic "PositionIndependentCode.picRelative"
347 #endif
348
349 -- -------------------------------------------------------------------
350
351 -- What do we have to add to every assembly file we generate?
352
353 -- utility function for pretty-printing asm-labels,
354 -- copied from PprMach
355 asmSDoc d = Outputable.withPprStyleDoc (
356               Outputable.mkCodeStyle Outputable.AsmStyle) d
357 pprCLabel_asm l = asmSDoc (pprCLabel l)
358
359
360 #if darwin_TARGET_OS && !x86_64_TARGET_ARCH
361
362 needImportedSymbols = True
363
364 -- We don't need to declare any offset tables.
365 -- However, for PIC on x86, we need a small helper function.
366 #if i386_TARGET_ARCH
367 pprGotDeclaration
368     | opt_PIC
369     = vcat [
370         ptext (sLit ".section __TEXT,__textcoal_nt,coalesced,no_toc"),
371         ptext (sLit ".weak_definition ___i686.get_pc_thunk.ax"),
372         ptext (sLit ".private_extern ___i686.get_pc_thunk.ax"),
373         ptext (sLit "___i686.get_pc_thunk.ax:"),
374             ptext (sLit "\tmovl (%esp), %eax"),
375             ptext (sLit "\tret")
376     ]
377     | otherwise = Pretty.empty
378 #else
379 pprGotDeclaration = Pretty.empty
380 #endif
381
382 -- On Darwin, we have to generate our own stub code for lazy binding..
383 -- For each processor architecture, there are two versions, one for PIC
384 -- and one for non-PIC.
385 --
386 -- Whenever you change something in this assembler output, make sure
387 -- the splitter in driver/split/ghc-split.lprl recognizes the new output
388 pprImportedSymbol importedLbl
389 #if powerpc_TARGET_ARCH
390     | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
391     = case opt_PIC of
392         False ->
393             vcat [
394                 ptext (sLit ".symbol_stub"),
395                 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
396                     ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
397                     ptext (sLit "\tlis r11,ha16(L") <> pprCLabel_asm lbl
398                         <> ptext (sLit "$lazy_ptr)"),
399                     ptext (sLit "\tlwz r12,lo16(L") <> pprCLabel_asm lbl
400                         <> ptext (sLit "$lazy_ptr)(r11)"),
401                     ptext (sLit "\tmtctr r12"),
402                     ptext (sLit "\taddi r11,r11,lo16(L") <> pprCLabel_asm lbl
403                         <> ptext (sLit "$lazy_ptr)"),
404                     ptext (sLit "\tbctr")
405             ]
406         True ->
407             vcat [
408                 ptext (sLit ".section __TEXT,__picsymbolstub1,")
409                   <> ptext (sLit "symbol_stubs,pure_instructions,32"),
410                 ptext (sLit "\t.align 2"),
411                 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
412                     ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
413                     ptext (sLit "\tmflr r0"),
414                     ptext (sLit "\tbcl 20,31,L0$") <> pprCLabel_asm lbl,
415                 ptext (sLit "L0$") <> pprCLabel_asm lbl <> char ':',
416                     ptext (sLit "\tmflr r11"),
417                     ptext (sLit "\taddis r11,r11,ha16(L") <> pprCLabel_asm lbl
418                         <> ptext (sLit "$lazy_ptr-L0$") <> pprCLabel_asm lbl <> char ')',
419                     ptext (sLit "\tmtlr r0"),
420                     ptext (sLit "\tlwzu r12,lo16(L") <> pprCLabel_asm lbl
421                         <> ptext (sLit "$lazy_ptr-L0$") <> pprCLabel_asm lbl
422                         <> ptext (sLit ")(r11)"),
423                     ptext (sLit "\tmtctr r12"),
424                     ptext (sLit "\tbctr")
425             ]
426     $+$ vcat [
427         ptext (sLit ".lazy_symbol_pointer"),
428         ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$lazy_ptr:"),
429             ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
430             ptext (sLit "\t.long dyld_stub_binding_helper")
431     ]
432 #elif i386_TARGET_ARCH
433     | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
434     = case opt_PIC of
435         False ->
436             vcat [
437                 ptext (sLit ".symbol_stub"),
438                 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
439                     ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
440                     ptext (sLit "\tjmp *L") <> pprCLabel_asm lbl
441                         <> ptext (sLit "$lazy_ptr"),
442                 ptext (sLit "L") <> pprCLabel_asm lbl
443                     <> ptext (sLit "$stub_binder:"),
444                     ptext (sLit "\tpushl $L") <> pprCLabel_asm lbl
445                         <> ptext (sLit "$lazy_ptr"),
446                     ptext (sLit "\tjmp dyld_stub_binding_helper")
447             ]
448         True ->
449             vcat [
450                 ptext (sLit ".section __TEXT,__picsymbolstub2,")
451                     <> ptext (sLit "symbol_stubs,pure_instructions,25"),
452                 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
453                     ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
454                     ptext (sLit "\tcall ___i686.get_pc_thunk.ax"),
455                 ptext (sLit "1:"),
456                     ptext (sLit "\tmovl L") <> pprCLabel_asm lbl
457                         <> ptext (sLit "$lazy_ptr-1b(%eax),%edx"),
458                     ptext (sLit "\tjmp *%edx"),
459                 ptext (sLit "L") <> pprCLabel_asm lbl
460                     <> ptext (sLit "$stub_binder:"),
461                     ptext (sLit "\tlea L") <> pprCLabel_asm lbl
462                         <> ptext (sLit "$lazy_ptr-1b(%eax),%eax"),
463                     ptext (sLit "\tpushl %eax"),
464                     ptext (sLit "\tjmp dyld_stub_binding_helper")
465             ]
466     $+$ vcat [        ptext (sLit ".section __DATA, __la_sym_ptr")
467                     <> (if opt_PIC then int 2 else int 3)
468                     <> ptext (sLit ",lazy_symbol_pointers"),
469         ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$lazy_ptr:"),
470             ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
471             ptext (sLit "\t.long L") <> pprCLabel_asm lbl
472                     <> ptext (sLit "$stub_binder")
473     ]
474 #endif
475 -- We also have to declare our symbol pointers ourselves:
476     | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
477     = vcat [
478         ptext (sLit ".non_lazy_symbol_pointer"),
479         char 'L' <> pprCLabel_asm lbl <> ptext (sLit "$non_lazy_ptr:"),
480             ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
481             ptext (sLit "\t.long\t0")
482     ]
483
484     | otherwise = empty
485
486 #elif linux_TARGET_OS && !powerpc64_TARGET_ARCH
487
488 -- ELF / Linux
489 --
490 -- In theory, we don't need to generate any stubs or symbol pointers
491 -- by hand for Linux.
492 --
493 -- Reality differs from this in two areas.
494 --
495 -- 1) If we just use a dynamically imported symbol directly in a read-only
496 --    section of the main executable (as GCC does), ld generates R_*_COPY
497 --    relocations, which are fundamentally incompatible with reversed info
498 --    tables. Therefore, we need a table of imported addresses in a writable
499 --    section.
500 --    The "official" GOT mechanism (label@got) isn't intended to be used
501 --    in position dependent code, so we have to create our own "fake GOT"
502 --    when not opt_PCI && not opt_Static.
503 --
504 -- 2) PowerPC Linux is just plain broken.
505 --    While it's theoretically possible to use GOT offsets larger
506 --    than 16 bit, the standard crt*.o files don't, which leads to
507 --    linker errors as soon as the GOT size exceeds 16 bit.
508 --    Also, the assembler doesn't support @gotoff labels.
509 --    In order to be able to use a larger GOT, we have to circumvent the
510 --    entire GOT mechanism and do it ourselves (this is also what GCC does).
511
512
513 -- When needImportedSymbols is defined,
514 -- the NCG will keep track of all DynamicLinkerLabels it uses
515 -- and output each of them using pprImportedSymbol.
516 #if powerpc_TARGET_ARCH
517     -- PowerPC Linux: -fPIC or -dynamic
518 needImportedSymbols = opt_PIC || not opt_Static
519 #else
520     -- i386 (and others?): -dynamic but not -fPIC
521 needImportedSymbols = not opt_Static && not opt_PIC
522 #endif
523
524 -- gotLabel
525 -- The label used to refer to our "fake GOT" from
526 -- position-independent code.
527 gotLabel = mkForeignLabel -- HACK: it's not really foreign
528                            (fsLit ".LCTOC1") Nothing False IsData
529
530 -- pprGotDeclaration
531 -- Output whatever needs to be output once per .s file.
532 -- The .LCTOC1 label is defined to point 32768 bytes into the table,
533 -- to make the most of the PPC's 16-bit displacements.
534 -- Only needed for PIC.
535
536 pprGotDeclaration
537     | not opt_PIC = Pretty.empty
538     | otherwise = vcat [
539         ptext (sLit ".section \".got2\",\"aw\""),
540         ptext (sLit ".LCTOC1 = .+32768")
541     ]
542
543 -- We generate one .long/.quad literal for every symbol we import;
544 -- the dynamic linker will relocate those addresses.
545
546 pprImportedSymbol importedLbl
547     | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
548     = vcat [
549         ptext (sLit ".section \".got2\", \"aw\""),
550         ptext (sLit ".LC_") <> pprCLabel_asm lbl <> char ':',
551         ptext symbolSize <+> pprCLabel_asm lbl
552     ]
553
554 -- PLT code stubs are generated automatically by the dynamic linker.
555     | otherwise = empty
556     where
557       symbolSize = case wordWidth of
558                      W32 -> sLit "\t.long"
559                      W64 -> sLit "\t.quad"
560                      _ -> panic "Unknown wordRep in pprImportedSymbol"
561
562 #else
563
564 -- For all other currently supported platforms, we don't need to do
565 -- anything at all.
566
567 needImportedSymbols = False
568 pprGotDeclaration = Pretty.empty
569 pprImportedSymbol _ = empty
570 #endif
571
572 -- -------------------------------------------------------------------
573
574 -- Generate code to calculate the address that should be put in the
575 -- PIC base register.
576 -- This is called by MachCodeGen for every CmmProc that accessed the
577 -- PIC base register. It adds the appropriate instructions to the
578 -- top of the CmmProc.
579
580 -- It is assumed that the first NatCmmTop in the input list is a Proc
581 -- and the rest are CmmDatas.
582
583 initializePicBase :: Reg -> [NatCmmTop] -> NatM [NatCmmTop]
584
585 #if darwin_TARGET_OS
586
587 -- Darwin is simple: just fetch the address of a local label.
588 -- The FETCHPC pseudo-instruction is expanded to multiple instructions
589 -- during pretty-printing so that we don't have to deal with the
590 -- local label:
591
592 -- PowerPC version:
593 --          bcl 20,31,1f.
594 --      1:  mflr picReg
595
596 -- i386 version:
597 --          call 1f
598 --      1:  popl %picReg
599
600 initializePicBase picReg (CmmProc info lab params (ListGraph blocks) : statics)
601     = return (CmmProc info lab params (ListGraph (b':tail blocks)) : statics)
602     where BasicBlock bID insns = head blocks
603           b' = BasicBlock bID (FETCHPC picReg : insns)
604
605 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
606
607 -- Get a pointer to our own fake GOT, which is defined on a per-module basis.
608 -- This is exactly how GCC does it, and it's quite horrible:
609 -- We first fetch the address of a local label (mkPicBaseLabel).
610 -- Then we add a 16-bit offset to that to get the address of a .long that we
611 -- define in .text space right next to the proc. This .long literal contains
612 -- the (32-bit) offset from our local label to our global offset table
613 -- (.LCTOC1 aka gotOffLabel).
614 initializePicBase picReg
615     (CmmProc info lab params (ListGraph blocks) : statics)
616     = do
617         gotOffLabel <- getNewLabelNat
618         tmp <- getNewRegNat $ intSize wordWidth
619         let 
620             gotOffset = CmmData Text [
621                             CmmDataLabel gotOffLabel,
622                             CmmStaticLit (CmmLabelDiffOff gotLabel
623                                                           mkPicBaseLabel
624                                                           0)
625                         ]
626             offsetToOffset = ImmConstantDiff (ImmCLbl gotOffLabel)
627                                              (ImmCLbl mkPicBaseLabel)
628             BasicBlock bID insns = head blocks
629             b' = BasicBlock bID (FETCHPC picReg
630                                : LD wordSize tmp
631                                     (AddrRegImm picReg offsetToOffset)
632                                : ADD picReg picReg (RIReg tmp)
633                                : insns)
634         return (CmmProc info lab params (ListGraph (b' : tail blocks)) : gotOffset : statics)
635 #elif i386_TARGET_ARCH && linux_TARGET_OS
636
637 -- We cheat a bit here by defining a pseudo-instruction named FETCHGOT
638 -- which pretty-prints as:
639 --              call 1f
640 -- 1:           popl %picReg
641 --              addl __GLOBAL_OFFSET_TABLE__+.-1b, %picReg
642 -- (See PprMach.lhs)
643
644 initializePicBase picReg (CmmProc info lab params (ListGraph blocks) : statics)
645     = return (CmmProc info lab params (ListGraph (b':tail blocks)) : statics)
646     where BasicBlock bID insns = head blocks
647           b' = BasicBlock bID (FETCHGOT picReg : insns)
648
649 #else
650 initializePicBase picReg proc = panic "initializePicBase"
651
652 -- mingw32_TARGET_OS: not needed, won't be called
653 #endif