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