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