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 -- 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.
201 howToAccessLabel dflags _ OSMinGW32 _ lbl
202 | labelDynamic (thisPackage dflags) lbl
209 -- Mach-O (Darwin, Mac OS X)
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.
217 howToAccessLabel dflags arch OSDarwin DataReference lbl
218 -- data access to a dynamic library goes via a symbol pointer
219 | labelDynamic (thisPackage dflags) lbl
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
232 , opt_PIC && externallyVisibleCLabel lbl
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
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.
252 , labelDynamic (thisPackage dflags) lbl
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).
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.
269 howToAccessLabel _ ArchPPC_64 OSLinux kind _
271 -- ELF PPC64 (powerpc64-linux), AIX, MacOS 9, BeOS/PPC
272 | DataReference <- kind
275 -- actually, .label instead of label
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
286 howToAccessLabel dflags arch OSLinux DataReference lbl
287 -- A dynamic label needs to be accessed via a symbol pointer.
288 | labelDynamic (thisPackage dflags) lbl
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).
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.
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)
314 howToAccessLabel dflags arch OSLinux CallReference lbl
315 | labelDynamic (thisPackage dflags) lbl && not opt_PIC
319 , labelDynamic (thisPackage dflags) lbl && opt_PIC
322 howToAccessLabel dflags _ OSLinux _ lbl
323 | labelDynamic (thisPackage dflags) lbl
329 -- all other platforms
330 howToAccessLabel _ _ _ _ _
335 = panic "howToAccessLabel: PIC not defined for this platform"
339 -- -------------------------------------------------------------------
340 -- | Says what we we have to add to our 'PIC base register' in order to
341 -- get the address of a label.
343 picRelative :: Arch -> OS -> CLabel -> CmmLit
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
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
354 = CmmLabelDiffOff lbl mkPicBaseLabel 0
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
363 picRelative ArchPPC OSLinux lbl
364 = CmmLabelDiffOff lbl gotLabel 0
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)
377 | Just (SymbolPtr, lbl') <- dynamicLinkerLabelInfo lbl
378 = CmmLabel $ mkDynamicLinkerLabel GotSymbolPtr lbl'
381 = CmmLabel $ mkDynamicLinkerLabel GotSymbolOffset lbl
386 = panic "PositionIndependentCode.picRelative undefined for this platform"
390 --------------------------------------------------------------------------------
392 -- utility function for pretty-printing asm-labels,
393 -- copied from PprMach
395 asmSDoc :: Outputable.SDoc -> Doc
397 = Outputable.withPprStyleDoc
398 (Outputable.mkCodeStyle Outputable.AsmStyle) d
400 pprCLabel_asm :: CLabel -> Doc
402 = asmSDoc (pprCLabel l)
405 needImportedSymbols :: Arch -> OS -> Bool
406 needImportedSymbols arch os
411 -- PowerPC Linux: -fPIC or -dynamic
414 = opt_PIC || not opt_Static
416 -- i386 (and others?): -dynamic but not -fPIC
419 = not opt_Static && not opt_PIC
425 -- The label used to refer to our "fake GOT" from
426 -- position-independent code.
429 = mkForeignLabel -- HACK: it's not really foreign
430 (fsLit ".LCTOC1") Nothing False IsData
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
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") ]
448 pprGotDeclaration _ OSDarwin
452 -- Output whatever needs to be output once per .s file.
453 -- The .LCTOC1 label is defined to point 32768 bytes into the table,
454 -- to make the most of the PPC's 16-bit displacements.
455 -- Only needed for PIC.
456 pprGotDeclaration arch OSLinux
463 ptext (sLit ".section \".got2\",\"aw\""),
464 ptext (sLit ".LCTOC1 = .+32768") ]
466 pprGotDeclaration _ _
467 = panic "pprGotDeclaration: no match"
470 --------------------------------------------------------------------------------
471 -- On Darwin, we have to generate our own stub code for lazy binding..
472 -- For each processor architecture, there are two versions, one for PIC
473 -- and one for non-PIC.
475 -- Whenever you change something in this assembler output, make sure
476 -- the splitter in driver/split/ghc-split.lprl recognizes the new output
478 pprImportedSymbol :: Arch -> OS -> CLabel -> Doc
479 pprImportedSymbol ArchPPC OSDarwin importedLbl
480 | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
484 ptext (sLit ".symbol_stub"),
485 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
486 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
487 ptext (sLit "\tlis r11,ha16(L") <> pprCLabel_asm lbl
488 <> ptext (sLit "$lazy_ptr)"),
489 ptext (sLit "\tlwz r12,lo16(L") <> pprCLabel_asm lbl
490 <> ptext (sLit "$lazy_ptr)(r11)"),
491 ptext (sLit "\tmtctr r12"),
492 ptext (sLit "\taddi r11,r11,lo16(L") <> pprCLabel_asm lbl
493 <> ptext (sLit "$lazy_ptr)"),
494 ptext (sLit "\tbctr")
498 ptext (sLit ".section __TEXT,__picsymbolstub1,")
499 <> ptext (sLit "symbol_stubs,pure_instructions,32"),
500 ptext (sLit "\t.align 2"),
501 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
502 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
503 ptext (sLit "\tmflr r0"),
504 ptext (sLit "\tbcl 20,31,L0$") <> pprCLabel_asm lbl,
505 ptext (sLit "L0$") <> pprCLabel_asm lbl <> char ':',
506 ptext (sLit "\tmflr r11"),
507 ptext (sLit "\taddis r11,r11,ha16(L") <> pprCLabel_asm lbl
508 <> ptext (sLit "$lazy_ptr-L0$") <> pprCLabel_asm lbl <> char ')',
509 ptext (sLit "\tmtlr r0"),
510 ptext (sLit "\tlwzu r12,lo16(L") <> pprCLabel_asm lbl
511 <> ptext (sLit "$lazy_ptr-L0$") <> pprCLabel_asm lbl
512 <> ptext (sLit ")(r11)"),
513 ptext (sLit "\tmtctr r12"),
514 ptext (sLit "\tbctr")
517 ptext (sLit ".lazy_symbol_pointer"),
518 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$lazy_ptr:"),
519 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
520 ptext (sLit "\t.long dyld_stub_binding_helper")]
522 | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
524 ptext (sLit ".non_lazy_symbol_pointer"),
525 char 'L' <> pprCLabel_asm lbl <> ptext (sLit "$non_lazy_ptr:"),
526 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
527 ptext (sLit "\t.long\t0")]
533 pprImportedSymbol ArchX86 OSDarwin importedLbl
534 | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
538 ptext (sLit ".symbol_stub"),
539 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
540 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
541 ptext (sLit "\tjmp *L") <> pprCLabel_asm lbl
542 <> ptext (sLit "$lazy_ptr"),
543 ptext (sLit "L") <> pprCLabel_asm lbl
544 <> ptext (sLit "$stub_binder:"),
545 ptext (sLit "\tpushl $L") <> pprCLabel_asm lbl
546 <> ptext (sLit "$lazy_ptr"),
547 ptext (sLit "\tjmp dyld_stub_binding_helper")
551 ptext (sLit ".section __TEXT,__picsymbolstub2,")
552 <> ptext (sLit "symbol_stubs,pure_instructions,25"),
553 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$stub:"),
554 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
555 ptext (sLit "\tcall ___i686.get_pc_thunk.ax"),
557 ptext (sLit "\tmovl L") <> pprCLabel_asm lbl
558 <> ptext (sLit "$lazy_ptr-1b(%eax),%edx"),
559 ptext (sLit "\tjmp *%edx"),
560 ptext (sLit "L") <> pprCLabel_asm lbl
561 <> ptext (sLit "$stub_binder:"),
562 ptext (sLit "\tlea L") <> pprCLabel_asm lbl
563 <> ptext (sLit "$lazy_ptr-1b(%eax),%eax"),
564 ptext (sLit "\tpushl %eax"),
565 ptext (sLit "\tjmp dyld_stub_binding_helper")
567 $+$ vcat [ ptext (sLit ".section __DATA, __la_sym_ptr")
568 <> (if opt_PIC then int 2 else int 3)
569 <> ptext (sLit ",lazy_symbol_pointers"),
570 ptext (sLit "L") <> pprCLabel_asm lbl <> ptext (sLit "$lazy_ptr:"),
571 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
572 ptext (sLit "\t.long L") <> pprCLabel_asm lbl
573 <> ptext (sLit "$stub_binder")]
575 | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
577 ptext (sLit ".non_lazy_symbol_pointer"),
578 char 'L' <> pprCLabel_asm lbl <> ptext (sLit "$non_lazy_ptr:"),
579 ptext (sLit "\t.indirect_symbol") <+> pprCLabel_asm lbl,
580 ptext (sLit "\t.long\t0")]
586 pprImportedSymbol _ OSDarwin _
592 -- In theory, we don't need to generate any stubs or symbol pointers
593 -- by hand for Linux.
595 -- Reality differs from this in two areas.
597 -- 1) If we just use a dynamically imported symbol directly in a read-only
598 -- section of the main executable (as GCC does), ld generates R_*_COPY
599 -- relocations, which are fundamentally incompatible with reversed info
600 -- tables. Therefore, we need a table of imported addresses in a writable
602 -- The "official" GOT mechanism (label@got) isn't intended to be used
603 -- in position dependent code, so we have to create our own "fake GOT"
604 -- when not opt_PCI && not opt_Static.
606 -- 2) PowerPC Linux is just plain broken.
607 -- While it's theoretically possible to use GOT offsets larger
608 -- than 16 bit, the standard crt*.o files don't, which leads to
609 -- linker errors as soon as the GOT size exceeds 16 bit.
610 -- Also, the assembler doesn't support @gotoff labels.
611 -- In order to be able to use a larger GOT, we have to circumvent the
612 -- entire GOT mechanism and do it ourselves (this is also what GCC does).
615 -- When needImportedSymbols is defined,
616 -- the NCG will keep track of all DynamicLinkerLabels it uses
617 -- and output each of them using pprImportedSymbol.
619 pprImportedSymbol ArchPPC_64 OSLinux _
622 pprImportedSymbol _ OSLinux importedLbl
623 | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
624 = let symbolSize = case wordWidth of
625 W32 -> sLit "\t.long"
626 W64 -> sLit "\t.quad"
627 _ -> panic "Unknown wordRep in pprImportedSymbol"
630 ptext (sLit ".section \".got2\", \"aw\""),
631 ptext (sLit ".LC_") <> pprCLabel_asm lbl <> char ':',
632 ptext symbolSize <+> pprCLabel_asm lbl ]
634 -- PLT code stubs are generated automatically by the dynamic linker.
637 pprImportedSymbol _ _ _
638 = panic "PIC.pprImportedSymbol: no match"
640 --------------------------------------------------------------------------------
641 -- Generate code to calculate the address that should be put in the
642 -- PIC base register.
643 -- This is called by MachCodeGen for every CmmProc that accessed the
644 -- PIC base register. It adds the appropriate instructions to the
645 -- top of the CmmProc.
647 -- It is assumed that the first NatCmmTop in the input list is a Proc
648 -- and the rest are CmmDatas.
650 -- Darwin is simple: just fetch the address of a local label.
651 -- The FETCHPC pseudo-instruction is expanded to multiple instructions
652 -- during pretty-printing so that we don't have to deal with the
665 -- Get a pointer to our own fake GOT, which is defined on a per-module basis.
666 -- This is exactly how GCC does it, and it's quite horrible:
667 -- We first fetch the address of a local label (mkPicBaseLabel).
668 -- Then we add a 16-bit offset to that to get the address of a .long that we
669 -- define in .text space right next to the proc. This .long literal contains
670 -- the (32-bit) offset from our local label to our global offset table
671 -- (.LCTOC1 aka gotOffLabel).
673 initializePicBase_ppc
675 -> [NatCmmTop PPC.Instr]
676 -> NatM [NatCmmTop PPC.Instr]
678 initializePicBase_ppc ArchPPC OSLinux picReg
679 (CmmProc info lab params (ListGraph blocks) : statics)
681 gotOffLabel <- getNewLabelNat
682 tmp <- getNewRegNat $ intSize wordWidth
684 gotOffset = CmmData Text [
685 CmmDataLabel gotOffLabel,
686 CmmStaticLit (CmmLabelDiffOff gotLabel
691 = PPC.ImmConstantDiff
692 (PPC.ImmCLbl gotOffLabel)
693 (PPC.ImmCLbl mkPicBaseLabel)
698 b' = BasicBlock bID (PPC.FETCHPC picReg
699 : PPC.LD PPC.archWordSize tmp
700 (PPC.AddrRegImm picReg offsetToOffset)
701 : PPC.ADD picReg picReg (PPC.RIReg tmp)
704 return (CmmProc info lab params (ListGraph (b' : tail blocks)) : gotOffset : statics)
706 initializePicBase_ppc ArchPPC OSDarwin picReg
707 (CmmProc info lab params (ListGraph blocks) : statics)
708 = return (CmmProc info lab params (ListGraph (b':tail blocks)) : statics)
710 where BasicBlock bID insns = head blocks
711 b' = BasicBlock bID (PPC.FETCHPC picReg : insns)
714 initializePicBase_ppc _ _ _ _
715 = panic "initializePicBase_ppc: not needed"
718 -- We cheat a bit here by defining a pseudo-instruction named FETCHGOT
719 -- which pretty-prints as:
722 -- addl __GLOBAL_OFFSET_TABLE__+.-1b, %picReg
725 initializePicBase_x86
727 -> [NatCmmTop X86.Instr]
728 -> NatM [NatCmmTop X86.Instr]
730 initializePicBase_x86 ArchX86 OSLinux picReg
731 (CmmProc info lab params (ListGraph blocks) : statics)
732 = return (CmmProc info lab params (ListGraph (b':tail blocks)) : statics)
733 where BasicBlock bID insns = head blocks
734 b' = BasicBlock bID (X86.FETCHGOT picReg : insns)
736 initializePicBase_x86 ArchX86 OSDarwin picReg
737 (CmmProc info lab params (ListGraph blocks) : statics)
738 = return (CmmProc info lab params (ListGraph (b':tail blocks)) : statics)
740 where BasicBlock bID insns = head blocks
741 b' = BasicBlock bID (X86.FETCHPC picReg : insns)
743 initializePicBase_x86 _ _ _ _
744 = panic "initializePicBase_x86: not needed"