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