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