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