2 This module handles generation of position independent code and
3 dynamic-linking related issues for the native code generator.
5 This depends both the architecture and OS, so we define it here
6 instead of in one of the architecture specific modules.
8 Things outside this module which are related to this:
11 - PIC base label (pretty printed as local label 1)
12 - DynamicLinkerLabels - several kinds:
13 CodeStub, SymbolPtr, GotSymbolPtr, GotSymbolOffset
14 - labelDynamic predicate
16 - The GlobalReg datatype has a PicBaseReg constructor
17 - The CmmLit datatype has a CmmLabelDiffOff constructor
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
25 - The cmmToCmm pass in AsmCodeGen calls cmmMakeDynamicReference for all
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).
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
42 cmmMakeDynamicReference,
48 initializePicBase_ppc,
54 import qualified PPC.Instr as PPC
55 import qualified PPC.Regs as PPC
57 import qualified X86.Instr as X86
67 import CLabel ( CLabel, pprCLabel,
68 mkDynamicLinkerLabel, DynamicLinkerLabelInfo(..),
69 dynamicLinkerLabelInfo, mkPicBaseLabel,
70 labelDynamic, externallyVisibleCLabel )
72 import CLabel ( mkForeignLabel )
75 import StaticFlags ( opt_PIC, opt_Static )
79 import qualified Outputable
81 import Panic ( panic )
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
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.
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
114 cmmMakeDynamicReference dflags addImport referenceKind lbl
115 | Just _ <- dynamicLinkerLabelInfo lbl
116 = return $ CmmLit $ CmmLabel lbl -- already processed it, pass through
119 = case howToAccessLabel
121 (platformArch $ targetPlatform dflags)
122 (platformOS $ targetPlatform dflags)
126 let stub = mkDynamicLinkerLabel CodeStub lbl
128 return $ CmmLit $ CmmLabel stub
130 AccessViaSymbolPtr -> do
131 let symbolPtr = mkDynamicLinkerLabel SymbolPtr lbl
133 return $ CmmLoad (cmmMakePicReference dflags symbolPtr) bWord
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
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.
151 cmmMakePicReference :: DynFlags -> CLabel -> CmmExpr
152 cmmMakePicReference dflags lbl
154 -- Windows doesn't need PIC,
155 -- everything gets relocated at runtime
156 | OSMinGW32 <- platformOS $ targetPlatform dflags
157 = CmmLit $ CmmLabel lbl
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)
169 = CmmLit $ CmmLabel lbl
172 absoluteLabel :: CLabel -> Bool
174 = case dynamicLinkerLabelInfo lbl of
175 Just (GotSymbolPtr, _) -> False
176 Just (GotSymbolOffset, _) -> False
180 --------------------------------------------------------------------------------
181 -- Knowledge about how special dynamic linker labels like symbol
182 -- pointers, code stubs and GOT offsets look like is located in the
185 -- We have to decide which labels need to be accessed
186 -- indirectly or via a piece of stub code.
187 data LabelAccessStyle
193 :: DynFlags -> Arch -> OS -> ReferenceKind -> CLabel -> LabelAccessStyle
197 -- In Windows speak, a "module" is a set of objects linked into the
198 -- same Portable Exectuable (PE) file. (both .exe and .dll files are PEs).
200 -- If we're compiling a multi-module program then symbols from other modules
201 -- are accessed by a symbol pointer named __imp_SYMBOL. At runtime we have the
204 -- (in the local module)
205 -- __imp_SYMBOL: addr of SYMBOL
207 -- (in the other module)
208 -- SYMBOL: the real function / data.
210 -- To access the function at SYMBOL from our local module, we just need to
211 -- dereference the local __imp_SYMBOL.
213 -- If opt_Static is set then we assume that all our code will be linked
214 -- into the same .exe file. In this case we always access symbols directly,
215 -- and never use __imp_SYMBOL.
217 howToAccessLabel dflags _ OSMinGW32 _ lbl
219 -- Assume all symbols will be in the same PE, so just access them directly.
223 -- If the target symbol is in another PE we need to access it via the
224 -- appropriate __imp_SYMBOL pointer.
225 | labelDynamic (thisPackage dflags) lbl
228 -- Target symbol is in the same PE as the caller, so just access it directly.
233 -- Mach-O (Darwin, Mac OS X)
235 -- Indirect access is required in the following cases:
236 -- * things imported from a dynamic library
237 -- * (not on x86_64) data from a different module, if we're generating PIC code
238 -- It is always possible to access something indirectly,
239 -- even when it's not necessary.
241 howToAccessLabel dflags arch OSDarwin DataReference lbl
242 -- data access to a dynamic library goes via a symbol pointer
243 | labelDynamic (thisPackage dflags) lbl
246 -- when generating PIC code, all cross-module data references must
247 -- must go via a symbol pointer, too, because the assembler
248 -- cannot generate code for a label difference where one
249 -- label is undefined. Doesn't apply t x86_64.
250 -- Unfortunately, we don't know whether it's cross-module,
251 -- so we do it for all externally visible labels.
252 -- This is a slight waste of time and space, but otherwise
253 -- we'd need to pass the current Module all the way in to
256 , opt_PIC && externallyVisibleCLabel lbl
262 howToAccessLabel dflags arch OSDarwin JumpReference lbl
263 -- dyld code stubs don't work for tailcalls because the
264 -- stack alignment is only right for regular calls.
265 -- Therefore, we have to go via a symbol pointer:
266 | arch == ArchX86 || arch == ArchX86_64
267 , labelDynamic (thisPackage dflags) lbl
271 howToAccessLabel dflags arch OSDarwin _ lbl
272 -- Code stubs are the usual method of choice for imported code;
273 -- not needed on x86_64 because Apple's new linker, ld64, generates
274 -- them automatically.
276 , labelDynamic (thisPackage dflags) lbl
284 -- ELF tries to pretend to the main application code that dynamic linking does
285 -- not exist. While this may sound convenient, it tends to mess things up in
286 -- very bad ways, so we have to be careful when we generate code for the main
287 -- program (-dynamic but no -fPIC).
289 -- Indirect access is required for references to imported symbols
290 -- from position independent code. It is also required from the main program
291 -- when dynamic libraries containing Haskell code are used.
293 howToAccessLabel _ ArchPPC_64 OSLinux kind _
295 -- ELF PPC64 (powerpc64-linux), AIX, MacOS 9, BeOS/PPC
296 | DataReference <- kind
299 -- actually, .label instead of label
303 howToAccessLabel _ _ OSLinux _ _
304 -- no PIC -> the dynamic linker does everything for us;
305 -- if we don't dynamically link to Haskell code,
306 -- it actually manages to do so without messing thins up.
307 | not opt_PIC && opt_Static
310 howToAccessLabel dflags arch OSLinux DataReference lbl
311 -- A dynamic label needs to be accessed via a symbol pointer.
312 | labelDynamic (thisPackage dflags) lbl
315 -- For PowerPC32 -fPIC, we have to access even static data
316 -- via a symbol pointer (see below for an explanation why
317 -- PowerPC32 Linux is especially broken).
326 -- In most cases, we have to avoid symbol stubs on ELF, for the following reasons:
327 -- on i386, the position-independent symbol stubs in the Procedure Linkage Table
328 -- require the address of the GOT to be loaded into register %ebx on entry.
329 -- The linker will take any reference to the symbol stub as a hint that
330 -- the label in question is a code label. When linking executables, this
331 -- will cause the linker to replace even data references to the label with
332 -- references to the symbol stub.
334 -- This leaves calling a (foreign) function from non-PIC code
335 -- (AccessDirectly, because we get an implicit symbol stub)
336 -- and calling functions from PIC code on non-i386 platforms (via a symbol stub)
338 howToAccessLabel dflags arch OSLinux CallReference lbl
339 | labelDynamic (thisPackage dflags) lbl && not opt_PIC
343 , labelDynamic (thisPackage dflags) lbl && opt_PIC
346 howToAccessLabel dflags _ OSLinux _ lbl
347 | labelDynamic (thisPackage dflags) lbl
353 -- all other platforms
354 howToAccessLabel _ _ _ _ _
359 = panic "howToAccessLabel: PIC not defined for this platform"
363 -- -------------------------------------------------------------------
364 -- | Says what we we have to add to our 'PIC base register' in order to
365 -- get the address of a label.
367 picRelative :: Arch -> OS -> CLabel -> CmmLit
369 -- Darwin, but not x86_64:
370 -- The PIC base register points to the PIC base label at the beginning
371 -- of the current CmmTop. We just have to use a label difference to
373 -- We have already made sure that all labels that are not from the current
374 -- module are accessed indirectly ('as' can't calculate differences between
375 -- undefined labels).
376 picRelative arch OSDarwin lbl
378 = CmmLabelDiffOff lbl mkPicBaseLabel 0
382 -- The PIC base register points to our fake GOT. Use a label difference
383 -- to get the offset.
384 -- We have made sure that *everything* is accessed indirectly, so this
385 -- is only used for offsets from the GOT to symbol pointers inside the
387 picRelative ArchPPC OSLinux lbl
388 = CmmLabelDiffOff lbl gotLabel 0
391 -- Most Linux versions:
392 -- The PIC base register points to the GOT. Use foo@got for symbol
393 -- pointers, and foo@gotoff for everything else.
394 -- Linux and Darwin on x86_64:
395 -- The PIC base register is %rip, we use foo@gotpcrel for symbol pointers,
396 -- and a GotSymbolOffset label for other things.
397 -- For reasons of tradition, the symbol offset label is written as a plain label.
398 picRelative arch os lbl
399 | os == OSLinux || (os == OSDarwin && arch == ArchX86_64)
401 | Just (SymbolPtr, lbl') <- dynamicLinkerLabelInfo lbl
402 = CmmLabel $ mkDynamicLinkerLabel GotSymbolPtr lbl'
405 = CmmLabel $ mkDynamicLinkerLabel GotSymbolOffset lbl
410 = panic "PositionIndependentCode.picRelative undefined for this platform"
414 --------------------------------------------------------------------------------
416 -- utility function for pretty-printing asm-labels,
417 -- copied from PprMach
419 asmSDoc :: Outputable.SDoc -> Doc
421 = Outputable.withPprStyleDoc
422 (Outputable.mkCodeStyle Outputable.AsmStyle) d
424 pprCLabel_asm :: CLabel -> Doc
426 = asmSDoc (pprCLabel l)
429 needImportedSymbols :: Arch -> OS -> Bool
430 needImportedSymbols arch os
435 -- PowerPC Linux: -fPIC or -dynamic
438 = opt_PIC || not opt_Static
440 -- i386 (and others?): -dynamic but not -fPIC
443 = not opt_Static && not opt_PIC
449 -- The label used to refer to our "fake GOT" from
450 -- position-independent code.
453 = mkForeignLabel -- HACK: it's not really foreign
454 (fsLit ".LCTOC1") Nothing False IsData
458 --------------------------------------------------------------------------------
459 -- We don't need to declare any offset tables.
460 -- However, for PIC on x86, we need a small helper function.
461 pprGotDeclaration :: Arch -> OS -> Doc
462 pprGotDeclaration ArchX86 OSDarwin
465 ptext (sLit ".section __TEXT,__textcoal_nt,coalesced,no_toc"),
466 ptext (sLit ".weak_definition ___i686.get_pc_thunk.ax"),
467 ptext (sLit ".private_extern ___i686.get_pc_thunk.ax"),
468 ptext (sLit "___i686.get_pc_thunk.ax:"),
469 ptext (sLit "\tmovl (%esp), %eax"),
470 ptext (sLit "\tret") ]
472 pprGotDeclaration _ OSDarwin
476 -- Output whatever needs to be output once per .s file.
477 -- The .LCTOC1 label is defined to point 32768 bytes into the table,
478 -- to make the most of the PPC's 16-bit displacements.
479 -- Only needed for PIC.
480 pprGotDeclaration arch OSLinux
487 ptext (sLit ".section \".got2\",\"aw\""),
488 ptext (sLit ".LCTOC1 = .+32768") ]
490 pprGotDeclaration _ _
491 = panic "pprGotDeclaration: no match"
494 --------------------------------------------------------------------------------
495 -- On Darwin, we have to generate our own stub code for lazy binding..
496 -- For each processor architecture, there are two versions, one for PIC
497 -- and one for non-PIC.
499 -- Whenever you change something in this assembler output, make sure
500 -- the splitter in driver/split/ghc-split.lprl recognizes the new output
502 pprImportedSymbol :: Arch -> OS -> CLabel -> Doc
503 pprImportedSymbol ArchPPC OSDarwin importedLbl
504 | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
508 ptext (sLit ".symbol_stub"),
509 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
510 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
511 ptext (sLit "\tlis r11,ha16(L") <> pprCLabel_asm lbl
512 <> ptext (sLit "$lazy_ptr)"),
513 ptext (sLit "\tlwz r12,lo16(L") <> pprCLabel_asm lbl
514 <> ptext (sLit "$lazy_ptr)(r11)"),
515 ptext (sLit "\tmtctr r12"),
516 ptext (sLit "\taddi r11,r11,lo16(L") <> pprCLabel_asm lbl
517 <> ptext (sLit "$lazy_ptr)"),
518 ptext (sLit "\tbctr")
522 ptext (sLit ".section __TEXT,__picsymbolstub1,")
523 <> ptext (sLit "symbol_stubs,pure_instructions,32"),
524 ptext (sLit "\t.align 2"),
525 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
526 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
527 ptext (sLit "\tmflr r0"),
528 ptext (sLit "\tbcl 20,31,L0$") <> pprCLabel_asm lbl,
529 ptext (sLit "L0$") <> pprCLabel_asm lbl <> char ':',
530 ptext (sLit "\tmflr r11"),
531 ptext (sLit "\taddis r11,r11,ha16(L") <> pprCLabel_asm lbl
532 <> ptext (sLit "$lazy_ptr-L0$") <> pprCLabel_asm lbl <> char ')',
533 ptext (sLit "\tmtlr r0"),
534 ptext (sLit "\tlwzu r12,lo16(L") <> pprCLabel_asm lbl
535 <> ptext (sLit "$lazy_ptr-L0$") <> pprCLabel_asm lbl
536 <> ptext (sLit ")(r11)"),
537 ptext (sLit "\tmtctr r12"),
538 ptext (sLit "\tbctr")
541 ptext (sLit ".lazy_symbol_pointer"),
542 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$lazy_ptr:"),
543 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
544 ptext (sLit "\t.long dyld_stub_binding_helper")]
546 | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
548 ptext (sLit ".non_lazy_symbol_pointer"),
549 char 'L' <> pprCLabel_asm lbl <> ptext (sLit "$non_lazy_ptr:"),
550 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
551 ptext (sLit "\t.long\t0")]
557 pprImportedSymbol ArchX86 OSDarwin importedLbl
558 | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
562 ptext (sLit ".symbol_stub"),
563 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
564 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
565 ptext (sLit "\tjmp *L") <> pprCLabel_asm lbl
566 <> ptext (sLit "$lazy_ptr"),
567 ptext (sLit "L") <> pprCLabel_asm lbl
568 <> ptext (sLit "$stub_binder:"),
569 ptext (sLit "\tpushl $L") <> pprCLabel_asm lbl
570 <> ptext (sLit "$lazy_ptr"),
571 ptext (sLit "\tjmp dyld_stub_binding_helper")
575 ptext (sLit ".section __TEXT,__picsymbolstub2,")
576 <> ptext (sLit "symbol_stubs,pure_instructions,25"),
577 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
578 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
579 ptext (sLit "\tcall ___i686.get_pc_thunk.ax"),
581 ptext (sLit "\tmovl L") <> pprCLabel_asm lbl
582 <> ptext (sLit "$lazy_ptr-1b(%eax),%edx"),
583 ptext (sLit "\tjmp *%edx"),
584 ptext (sLit "L") <> pprCLabel_asm lbl
585 <> ptext (sLit "$stub_binder:"),
586 ptext (sLit "\tlea L") <> pprCLabel_asm lbl
587 <> ptext (sLit "$lazy_ptr-1b(%eax),%eax"),
588 ptext (sLit "\tpushl %eax"),
589 ptext (sLit "\tjmp dyld_stub_binding_helper")
591 $+$ vcat [ ptext (sLit ".section __DATA, __la_sym_ptr")
592 <> (if opt_PIC then int 2 else int 3)
593 <> ptext (sLit ",lazy_symbol_pointers"),
594 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$lazy_ptr:"),
595 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
596 ptext (sLit "\t.long L") <> pprCLabel_asm lbl
597 <> ptext (sLit "$stub_binder")]
599 | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
601 ptext (sLit ".non_lazy_symbol_pointer"),
602 char 'L' <> pprCLabel_asm lbl <> ptext (sLit "$non_lazy_ptr:"),
603 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
604 ptext (sLit "\t.long\t0")]
610 pprImportedSymbol _ OSDarwin _
616 -- In theory, we don't need to generate any stubs or symbol pointers
617 -- by hand for Linux.
619 -- Reality differs from this in two areas.
621 -- 1) If we just use a dynamically imported symbol directly in a read-only
622 -- section of the main executable (as GCC does), ld generates R_*_COPY
623 -- relocations, which are fundamentally incompatible with reversed info
624 -- tables. Therefore, we need a table of imported addresses in a writable
626 -- The "official" GOT mechanism (label@got) isn't intended to be used
627 -- in position dependent code, so we have to create our own "fake GOT"
628 -- when not opt_PCI && not opt_Static.
630 -- 2) PowerPC Linux is just plain broken.
631 -- While it's theoretically possible to use GOT offsets larger
632 -- than 16 bit, the standard crt*.o files don't, which leads to
633 -- linker errors as soon as the GOT size exceeds 16 bit.
634 -- Also, the assembler doesn't support @gotoff labels.
635 -- In order to be able to use a larger GOT, we have to circumvent the
636 -- entire GOT mechanism and do it ourselves (this is also what GCC does).
639 -- When needImportedSymbols is defined,
640 -- the NCG will keep track of all DynamicLinkerLabels it uses
641 -- and output each of them using pprImportedSymbol.
643 pprImportedSymbol ArchPPC_64 OSLinux _
646 pprImportedSymbol _ OSLinux importedLbl
647 | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
648 = let symbolSize = case wordWidth of
649 W32 -> sLit "\t.long"
650 W64 -> sLit "\t.quad"
651 _ -> panic "Unknown wordRep in pprImportedSymbol"
654 ptext (sLit ".section \".got2\", \"aw\""),
655 ptext (sLit ".LC_") <> pprCLabel_asm lbl <> char ':',
656 ptext symbolSize <+> pprCLabel_asm lbl ]
658 -- PLT code stubs are generated automatically by the dynamic linker.
661 pprImportedSymbol _ _ _
662 = panic "PIC.pprImportedSymbol: no match"
664 --------------------------------------------------------------------------------
665 -- Generate code to calculate the address that should be put in the
666 -- PIC base register.
667 -- This is called by MachCodeGen for every CmmProc that accessed the
668 -- PIC base register. It adds the appropriate instructions to the
669 -- top of the CmmProc.
671 -- It is assumed that the first NatCmmTop in the input list is a Proc
672 -- and the rest are CmmDatas.
674 -- Darwin is simple: just fetch the address of a local label.
675 -- The FETCHPC pseudo-instruction is expanded to multiple instructions
676 -- during pretty-printing so that we don't have to deal with the
689 -- Get a pointer to our own fake GOT, which is defined on a per-module basis.
690 -- This is exactly how GCC does it, and it's quite horrible:
691 -- We first fetch the address of a local label (mkPicBaseLabel).
692 -- Then we add a 16-bit offset to that to get the address of a .long that we
693 -- define in .text space right next to the proc. This .long literal contains
694 -- the (32-bit) offset from our local label to our global offset table
695 -- (.LCTOC1 aka gotOffLabel).
697 initializePicBase_ppc
699 -> [NatCmmTop PPC.Instr]
700 -> NatM [NatCmmTop PPC.Instr]
702 initializePicBase_ppc ArchPPC OSLinux picReg
703 (CmmProc info lab params (ListGraph blocks) : statics)
705 gotOffLabel <- getNewLabelNat
706 tmp <- getNewRegNat $ intSize wordWidth
708 gotOffset = CmmData Text [
709 CmmDataLabel gotOffLabel,
710 CmmStaticLit (CmmLabelDiffOff gotLabel
715 = PPC.ImmConstantDiff
716 (PPC.ImmCLbl gotOffLabel)
717 (PPC.ImmCLbl mkPicBaseLabel)
722 b' = BasicBlock bID (PPC.FETCHPC picReg
723 : PPC.LD PPC.archWordSize tmp
724 (PPC.AddrRegImm picReg offsetToOffset)
725 : PPC.ADD picReg picReg (PPC.RIReg tmp)
728 return (CmmProc info lab params (ListGraph (b' : tail blocks)) : gotOffset : statics)
730 initializePicBase_ppc ArchPPC OSDarwin picReg
731 (CmmProc info lab params (ListGraph blocks) : statics)
732 = return (CmmProc info lab params (ListGraph (b':tail blocks)) : statics)
734 where BasicBlock bID insns = head blocks
735 b' = BasicBlock bID (PPC.FETCHPC picReg : insns)
738 initializePicBase_ppc _ _ _ _
739 = panic "initializePicBase_ppc: not needed"
742 -- We cheat a bit here by defining a pseudo-instruction named FETCHGOT
743 -- which pretty-prints as:
746 -- addl __GLOBAL_OFFSET_TABLE__+.-1b, %picReg
749 initializePicBase_x86
751 -> [NatCmmTop X86.Instr]
752 -> NatM [NatCmmTop X86.Instr]
754 initializePicBase_x86 ArchX86 OSLinux picReg
755 (CmmProc info lab params (ListGraph blocks) : statics)
756 = return (CmmProc info lab params (ListGraph (b':tail blocks)) : statics)
757 where BasicBlock bID insns = head blocks
758 b' = BasicBlock bID (X86.FETCHGOT picReg : insns)
760 initializePicBase_x86 ArchX86 OSDarwin picReg
761 (CmmProc info lab params (ListGraph blocks) : statics)
762 = return (CmmProc info lab params (ListGraph (b':tail blocks)) : statics)
764 where BasicBlock bID insns = head blocks
765 b' = BasicBlock bID (X86.FETCHPC picReg : insns)
767 initializePicBase_x86 _ _ _ _
768 = panic "initializePicBase_x86: not needed"