Add CLabel.CmmLabel and start refactoring
[ghc-hetmet.git] / compiler / cmm / CLabel.hs
1 {-# OPTIONS -w #-}
2 -- The above warning supression flag is a temporary kludge.
3 -- While working on this module you are encouraged to remove it and fix
4 -- any warnings in the module. See
5 --     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
6 -- for details
7
8 -----------------------------------------------------------------------------
9 --
10 -- Object-file symbols (called CLabel for histerical raisins).
11 --
12 -- (c) The University of Glasgow 2004-2006
13 --
14 -----------------------------------------------------------------------------
15
16 module CLabel (
17         CLabel, -- abstract type
18
19         mkClosureLabel,
20         mkSRTLabel,
21         mkInfoTableLabel,
22         mkEntryLabel,
23         mkSlowEntryLabel,
24         mkConEntryLabel,
25         mkStaticConEntryLabel,
26         mkRednCountsLabel,
27         mkConInfoTableLabel,
28         mkStaticInfoTableLabel,
29         mkLargeSRTLabel,
30         mkApEntryLabel,
31         mkApInfoTableLabel,
32         mkClosureTableLabel,
33
34         mkLocalClosureLabel,
35         mkLocalInfoTableLabel,
36         mkLocalEntryLabel,
37         mkLocalConEntryLabel,
38         mkLocalStaticConEntryLabel,
39         mkLocalConInfoTableLabel,
40         mkLocalStaticInfoTableLabel,
41         mkLocalClosureTableLabel,
42
43         mkReturnPtLabel,
44         mkReturnInfoLabel,
45         mkAltLabel,
46         mkDefaultLabel,
47         mkBitmapLabel,
48         mkStringLitLabel,
49
50         mkAsmTempLabel,
51
52         mkModuleInitLabel,
53         mkPlainModuleInitLabel,
54         mkModuleInitTableLabel,
55
56         mkSplitMarkerLabel,
57         mkDirty_MUT_VAR_Label,
58         mkUpdInfoLabel,
59         mkIndStaticInfoLabel,
60         mkMainCapabilityLabel,
61         mkMAP_FROZEN_infoLabel,
62         mkMAP_DIRTY_infoLabel,
63         mkEMPTY_MVAR_infoLabel,
64
65         mkTopTickyCtrLabel,
66         mkCAFBlackHoleInfoTableLabel,
67         mkRtsPrimOpLabel,
68         mkRtsSlowTickyCtrLabel,
69
70         moduleRegdLabel,
71         moduleRegTableLabel,
72
73         mkSelectorInfoLabel,
74         mkSelectorEntryLabel,
75
76         mkRtsInfoLabel,
77         mkRtsEntryLabel,
78         mkRtsRetInfoLabel,
79         mkRtsRetLabel,
80         mkRtsCodeLabel,
81         mkRtsDataLabel,
82         mkRtsGcPtrLabel,
83
84         mkRtsApFastLabel,
85
86         mkPrimCallLabel,
87
88         mkForeignLabel,
89         addLabelSize,
90         foreignLabelStdcallInfo,
91
92         mkCCLabel, mkCCSLabel,
93
94         DynamicLinkerLabelInfo(..),
95         mkDynamicLinkerLabel,
96         dynamicLinkerLabelInfo,
97         
98         mkPicBaseLabel,
99         mkDeadStripPreventer,
100
101         mkHpcTicksLabel,
102         mkHpcModuleNameLabel,
103
104         hasCAF,
105         infoLblToEntryLbl, entryLblToInfoLbl, cvtToClosureLbl, cvtToSRTLbl,
106         needsCDecl, isAsmTemp, maybeAsmTemp, externallyVisibleCLabel,
107         isMathFun,
108         isCFunctionLabel, isGcPtrLabel, labelDynamic,
109
110         pprCLabel
111     ) where
112
113 #include "HsVersions.h"
114
115 import IdInfo
116 import StaticFlags
117 import BasicTypes
118 import Literal
119 import Packages
120 import DataCon
121 import PackageConfig
122 import Module
123 import Name
124 import Unique
125 import PrimOp
126 import Config
127 import CostCentre
128 import Outputable
129 import FastString
130 import DynFlags
131 import UniqSet
132
133 -- -----------------------------------------------------------------------------
134 -- The CLabel type
135
136 {-
137   | CLabel is an abstract type that supports the following operations:
138
139   - Pretty printing
140
141   - In a C file, does it need to be declared before use?  (i.e. is it
142     guaranteed to be already in scope in the places we need to refer to it?)
143
144   - If it needs to be declared, what type (code or data) should it be
145     declared to have?
146
147   - Is it visible outside this object file or not?
148
149   - Is it "dynamic" (see details below)
150
151   - Eq and Ord, so that we can make sets of CLabels (currently only
152     used in outputting C as far as I can tell, to avoid generating
153     more than one declaration for any given label).
154
155   - Converting an info table label into an entry label.
156 -}
157
158 data CLabel
159   = -- | A label related to the definition of a particular Id or Con in a .hs file.
160     IdLabel                     
161         Name                    
162         CafInfo
163         IdLabelInfo             -- encodes the suffix of the label
164   
165   -- | A label from a .cmm file that is not associated with a .hs level Id.
166   | CmmLabel                    
167         Module                  -- what Cmm source module the label belongs to
168         FastString              -- identifier giving the prefix of the label
169         CmmLabelInfo            -- encodes the suffix of the label
170
171   -- | A label with a baked-in \/ algorithmically generated name that definitely
172   --    comes from the RTS. The code for it must compile into libHSrts.a \/ libHSrts.so
173   --    If it doesn't have an algorithmically generated name then use a CmmLabel 
174   --    instead and give it an appropriate Module argument.
175   | RtsLabel                    
176         RtsLabelInfo
177
178   -- | A 'C' (or otherwise foreign) label
179   | ForeignLabel FastString     
180         (Maybe Int)             -- possible '@n' suffix for stdcall functions
181                                 -- When generating C, the '@n' suffix is omitted, but when
182                                 -- generating assembler we must add it to the label.
183         Bool                    -- True <=> is dynamic
184         FunctionOrData
185
186   -- | A family of labels related to a particular case expression.
187   | CaseLabel                   
188         {-# UNPACK #-} !Unique  -- Unique says which case expression
189         CaseLabelInfo
190
191   | AsmTempLabel 
192         {-# UNPACK #-} !Unique
193
194   | StringLitLabel
195         {-# UNPACK #-} !Unique
196
197   | ModuleInitLabel 
198         Module                  -- the module name
199         String                  -- its "way"
200         -- at some point we might want some kind of version number in
201         -- the module init label, to guard against compiling modules in
202         -- the wrong order.  We can't use the interface file version however,
203         -- because we don't always recompile modules which depend on a module
204         -- whose version has changed.
205
206   | PlainModuleInitLabel        -- without the version & way info
207         Module
208
209   | ModuleInitTableLabel        -- table of imported modules to init
210         Module
211
212   | ModuleRegdLabel
213
214   | CC_Label  CostCentre
215   | CCS_Label CostCentreStack
216
217     
218   -- | These labels are generated and used inside the NCG only. 
219   --    They are special variants of a label used for dynamic linking
220   --    see module PositionIndependentCode for details.
221   | DynamicLinkerLabel DynamicLinkerLabelInfo CLabel
222  
223   -- | This label is generated and used inside the NCG only. 
224   --    It is used as a base for PIC calculations on some platforms.
225   --    It takes the form of a local numeric assembler label '1'; and 
226   --    is pretty-printed as 1b, referring to the previous definition
227   --    of 1: in the assembler source file.
228   | PicBaseLabel                
229  
230   -- | A label before an info table to prevent excessive dead-stripping on darwin
231   | DeadStripPreventer CLabel
232
233
234   -- | Per-module table of tick locations
235   | HpcTicksLabel Module
236
237   -- | Per-module name of the module for Hpc
238   | HpcModuleNameLabel
239
240   -- | Label of an StgLargeSRT
241   | LargeSRTLabel
242         {-# UNPACK #-} !Unique
243
244   -- | A bitmap (function or case return)
245   | LargeBitmapLabel
246         {-# UNPACK #-} !Unique
247
248   deriving (Eq, Ord)
249
250 data IdLabelInfo
251   = Closure             -- ^ Label for closure
252   | SRT                 -- ^ Static reference table
253   | InfoTable           -- ^ Info tables for closures; always read-only
254   | Entry               -- ^ Entry point
255   | Slow                -- ^ Slow entry point
256
257   | RednCounts          -- ^ Label of place to keep Ticky-ticky  info for this Id
258
259   | ConEntry            -- ^ Constructor entry point
260   | ConInfoTable        -- ^ Corresponding info table
261   | StaticConEntry      -- ^ Static constructor entry point
262   | StaticInfoTable     -- ^ Corresponding info table
263
264   | ClosureTable        -- ^ Table of closures for Enum tycons
265
266   deriving (Eq, Ord)
267
268
269 data CaseLabelInfo
270   = CaseReturnPt
271   | CaseReturnInfo
272   | CaseAlt ConTag
273   | CaseDefault
274   deriving (Eq, Ord)
275
276
277 data RtsLabelInfo
278   = RtsSelectorInfoTable Bool{-updatable-} Int{-offset-}  -- ^ Selector thunks
279   | RtsSelectorEntry     Bool{-updatable-} Int{-offset-}
280
281   | RtsApInfoTable       Bool{-updatable-} Int{-arity-}    -- ^ AP thunks
282   | RtsApEntry           Bool{-updatable-} Int{-arity-}
283
284   | RtsPrimOp PrimOp
285   | RtsApFast     FastString    -- ^ _fast versions of generic apply
286   | RtsSlowTickyCtr String
287
288   deriving (Eq, Ord)
289   -- NOTE: Eq on LitString compares the pointer only, so this isn't
290   -- a real equality.
291
292
293 -- | What type of Cmm label we're dealing with.
294 --      Determines the suffix appended to the name when a CLabel.CmmLabel
295 --      is pretty printed.
296 data CmmLabelInfo
297   = CmmInfo                     -- ^ misc rts info tabless,     suffix _info
298   | CmmEntry                    -- ^ misc rts entry points,     suffix _entry
299   | CmmRetInfo                  -- ^ misc rts ret info tables,  suffix _info
300   | CmmRet                      -- ^ misc rts return points,    suffix _ret
301   | CmmData                     -- ^ misc rts data bits, eg CHARLIKE_closure
302   | CmmCode                     -- ^ misc rts code
303   | CmmGcPtr                    -- ^ GcPtrs eg CHARLIKE_closure  
304   deriving (Eq, Ord)
305
306 data DynamicLinkerLabelInfo
307   = CodeStub                    -- MachO: Lfoo$stub, ELF: foo@plt
308   | SymbolPtr                   -- MachO: Lfoo$non_lazy_ptr, Windows: __imp_foo
309   | GotSymbolPtr                -- ELF: foo@got
310   | GotSymbolOffset             -- ELF: foo@gotoff
311   
312   deriving (Eq, Ord)
313  
314
315 -- -----------------------------------------------------------------------------
316 -- Constructing CLabels
317 -- -----------------------------------------------------------------------------
318
319 -- Constructing IdLabels 
320 -- These are always local:
321 mkSRTLabel              name c  = IdLabel name  c SRT
322 mkSlowEntryLabel        name c  = IdLabel name  c Slow
323 mkRednCountsLabel       name c  = IdLabel name  c RednCounts
324
325 -- These have local & (possibly) external variants:
326 mkLocalClosureLabel     name c  = IdLabel name  c Closure
327 mkLocalInfoTableLabel   name c  = IdLabel name  c InfoTable
328 mkLocalEntryLabel       name c  = IdLabel name  c Entry
329 mkLocalClosureTableLabel name c = IdLabel name  c ClosureTable
330
331 mkClosureLabel name         c     = IdLabel name c Closure
332 mkInfoTableLabel name       c     = IdLabel name c InfoTable
333 mkEntryLabel name           c     = IdLabel name c Entry
334 mkClosureTableLabel name    c     = IdLabel name c ClosureTable
335 mkLocalConInfoTableLabel    c con = IdLabel con c ConInfoTable
336 mkLocalConEntryLabel        c con = IdLabel con c ConEntry
337 mkLocalStaticInfoTableLabel c con = IdLabel con c StaticInfoTable
338 mkLocalStaticConEntryLabel  c con = IdLabel con c StaticConEntry
339 mkConInfoTableLabel name    c     = IdLabel    name c ConInfoTable
340 mkStaticInfoTableLabel name c     = IdLabel    name c StaticInfoTable
341
342 mkConEntryLabel name        c     = IdLabel name c ConEntry
343 mkStaticConEntryLabel name  c     = IdLabel name c StaticConEntry
344
345
346 -- Constructing Cmm Labels
347
348 -- | Pretend that wired-in names from the RTS are in a top-level module called RTS, 
349 --      located in the RTS package. It doesn't matter what module they're actually in
350 --      as long as that module is in the correct package.
351 topRtsModule :: Module
352 topRtsModule = mkModule rtsPackageId (mkModuleNameFS (fsLit "RTS"))
353
354 mkSplitMarkerLabel              = CmmLabel topRtsModule (fsLit "__stg_split_marker")    CmmCode
355 mkDirty_MUT_VAR_Label           = CmmLabel topRtsModule (fsLit "dirty_MUT_VAR")         CmmCode
356 mkUpdInfoLabel                  = CmmLabel topRtsModule (fsLit "stg_upd_frame")         CmmInfo
357 mkIndStaticInfoLabel            = CmmLabel topRtsModule (fsLit "stg_IND_STATIC")        CmmInfo
358 mkMainCapabilityLabel           = CmmLabel topRtsModule (fsLit "MainCapability")        CmmData
359 mkMAP_FROZEN_infoLabel          = CmmLabel topRtsModule (fsLit "stg_MUT_ARR_PTRS_FROZEN0") CmmInfo
360 mkMAP_DIRTY_infoLabel           = CmmLabel topRtsModule (fsLit "stg_MUT_ARR_PTRS_DIRTY") CmmInfo
361 mkEMPTY_MVAR_infoLabel          = CmmLabel topRtsModule (fsLit "stg_EMPTY_MVAR")        CmmInfo
362 mkTopTickyCtrLabel              = CmmLabel topRtsModule (fsLit "top_ct")                CmmData
363 mkCAFBlackHoleInfoTableLabel    = CmmLabel topRtsModule (fsLit "stg_CAF_BLACKHOLE")     CmmInfo
364
365 -----
366 mkRtsInfoLabel,   mkRtsEntryLabel, mkRtsRetInfoLabel, mkRtsRetLabel,
367   mkRtsCodeLabel, mkRtsDataLabel,  mkRtsGcPtrLabel
368         :: FastString -> CLabel
369
370 mkRtsInfoLabel      str         = CmmLabel topRtsModule str CmmInfo
371 mkRtsEntryLabel     str         = CmmLabel topRtsModule str CmmEntry
372 mkRtsRetInfoLabel   str         = CmmLabel topRtsModule str CmmRetInfo
373 mkRtsRetLabel       str         = CmmLabel topRtsModule str CmmRet
374 mkRtsCodeLabel      str         = CmmLabel topRtsModule str CmmCode
375 mkRtsDataLabel      str         = CmmLabel topRtsModule str CmmData
376 mkRtsGcPtrLabel     str         = CmmLabel topRtsModule str CmmGcPtr
377
378
379 -- Constructing RtsLabels
380 mkRtsPrimOpLabel primop         = RtsLabel (RtsPrimOp primop)
381
382 mkSelectorInfoLabel  upd off    = RtsLabel (RtsSelectorInfoTable upd off)
383 mkSelectorEntryLabel upd off    = RtsLabel (RtsSelectorEntry     upd off)
384
385 mkApInfoTableLabel   upd off    = RtsLabel (RtsApInfoTable       upd off)
386 mkApEntryLabel       upd off    = RtsLabel (RtsApEntry           upd off)
387
388
389 -- Constructing ForeignLabels
390 -- Primitive / cmm call labels
391 mkPrimCallLabel :: PrimCall -> CLabel
392 mkPrimCallLabel (PrimCall str)  = ForeignLabel str Nothing False IsFunction
393
394 -- Foreign labels
395 mkForeignLabel :: FastString -> Maybe Int -> Bool -> FunctionOrData -> CLabel
396 mkForeignLabel str mb_sz is_dynamic fod
397     = ForeignLabel str mb_sz is_dynamic fod
398
399 addLabelSize :: CLabel -> Int -> CLabel
400 addLabelSize (ForeignLabel str _ is_dynamic fod) sz
401     = ForeignLabel str (Just sz) is_dynamic fod
402 addLabelSize label _
403     = label
404
405 foreignLabelStdcallInfo :: CLabel -> Maybe Int
406 foreignLabelStdcallInfo (ForeignLabel _ info _ _) = info
407 foreignLabelStdcallInfo _lbl = Nothing
408
409
410 -- Constructing Large*Labels
411 mkLargeSRTLabel uniq            = LargeSRTLabel uniq
412 mkBitmapLabel   uniq            = LargeBitmapLabel uniq
413
414
415 -- Constructin CaseLabels
416 mkReturnPtLabel uniq            = CaseLabel uniq CaseReturnPt
417 mkReturnInfoLabel uniq          = CaseLabel uniq CaseReturnInfo
418 mkAltLabel      uniq tag        = CaseLabel uniq (CaseAlt tag)
419 mkDefaultLabel  uniq            = CaseLabel uniq CaseDefault
420
421 -- Constructing Cost Center Labels
422 mkCCLabel           cc          = CC_Label cc
423 mkCCSLabel          ccs         = CCS_Label ccs
424
425 mkRtsApFastLabel str = RtsLabel (RtsApFast str)
426
427 mkRtsSlowTickyCtrLabel :: String -> CLabel
428 mkRtsSlowTickyCtrLabel pat = RtsLabel (RtsSlowTickyCtr pat)
429
430
431 -- Constructing Code Coverage Labels
432 mkHpcTicksLabel                = HpcTicksLabel
433 mkHpcModuleNameLabel           = HpcModuleNameLabel
434
435
436 -- Constructing labels used for dynamic linking
437 mkDynamicLinkerLabel :: DynamicLinkerLabelInfo -> CLabel -> CLabel
438 mkDynamicLinkerLabel            = DynamicLinkerLabel
439
440 dynamicLinkerLabelInfo :: CLabel -> Maybe (DynamicLinkerLabelInfo, CLabel)
441 dynamicLinkerLabelInfo (DynamicLinkerLabel info lbl) = Just (info, lbl)
442 dynamicLinkerLabelInfo _        = Nothing
443     
444 mkPicBaseLabel :: CLabel
445 mkPicBaseLabel                  = PicBaseLabel
446
447
448 -- Constructing miscellaneous other labels
449 mkDeadStripPreventer :: CLabel -> CLabel
450 mkDeadStripPreventer lbl        = DeadStripPreventer lbl
451
452 mkStringLitLabel :: Unique -> CLabel
453 mkStringLitLabel                = StringLitLabel
454
455 mkAsmTempLabel :: Uniquable a => a -> CLabel
456 mkAsmTempLabel a                = AsmTempLabel (getUnique a)
457
458 mkModuleInitLabel :: Module -> String -> CLabel
459 mkModuleInitLabel mod way       = ModuleInitLabel mod way
460
461 mkPlainModuleInitLabel :: Module -> CLabel
462 mkPlainModuleInitLabel mod      = PlainModuleInitLabel mod
463
464 mkModuleInitTableLabel :: Module -> CLabel
465 mkModuleInitTableLabel mod      = ModuleInitTableLabel mod
466
467 moduleRegdLabel                 = ModuleRegdLabel
468 moduleRegTableLabel             = ModuleInitTableLabel  
469
470
471 -- -----------------------------------------------------------------------------
472 -- Converting between info labels and entry/ret labels.
473
474 infoLblToEntryLbl :: CLabel -> CLabel 
475 infoLblToEntryLbl (IdLabel n c InfoTable)       = IdLabel n c Entry
476 infoLblToEntryLbl (IdLabel n c ConInfoTable)    = IdLabel n c ConEntry
477 infoLblToEntryLbl (IdLabel n c StaticInfoTable) = IdLabel n c StaticConEntry
478 infoLblToEntryLbl (CaseLabel n CaseReturnInfo)  = CaseLabel n CaseReturnPt
479 infoLblToEntryLbl (CmmLabel m str CmmInfo)      = CmmLabel m str CmmEntry
480 infoLblToEntryLbl (CmmLabel m str CmmRetInfo)   = CmmLabel m str CmmRet
481 infoLblToEntryLbl _
482         = panic "CLabel.infoLblToEntryLbl"
483
484
485 entryLblToInfoLbl :: CLabel -> CLabel 
486 entryLblToInfoLbl (IdLabel n c Entry)           = IdLabel n c InfoTable
487 entryLblToInfoLbl (IdLabel n c ConEntry)        = IdLabel n c ConInfoTable
488 entryLblToInfoLbl (IdLabel n c StaticConEntry)  = IdLabel n c StaticInfoTable
489 entryLblToInfoLbl (CaseLabel n CaseReturnPt)    = CaseLabel n CaseReturnInfo
490 entryLblToInfoLbl (CmmLabel m str CmmEntry)     = CmmLabel m str CmmInfo
491 entryLblToInfoLbl (CmmLabel m str CmmRet)       = CmmLabel m str CmmRetInfo
492 entryLblToInfoLbl l                             
493         = pprPanic "CLabel.entryLblToInfoLbl" (pprCLabel l)
494
495
496 cvtToClosureLbl   (IdLabel n c InfoTable)       = IdLabel n c Closure
497 cvtToClosureLbl   (IdLabel n c Entry)           = IdLabel n c Closure
498 cvtToClosureLbl   (IdLabel n c ConEntry)        = IdLabel n c Closure
499 cvtToClosureLbl l@(IdLabel n c Closure)         = l
500 cvtToClosureLbl l 
501         = pprPanic "cvtToClosureLbl" (pprCLabel l)
502
503
504 cvtToSRTLbl   (IdLabel n c InfoTable)           = mkSRTLabel n c
505 cvtToSRTLbl   (IdLabel n c Entry)               = mkSRTLabel n c
506 cvtToSRTLbl   (IdLabel n c ConEntry)            = mkSRTLabel n c
507 cvtToSRTLbl l@(IdLabel n c Closure)             = mkSRTLabel n c
508 cvtToSRTLbl l 
509         = pprPanic "cvtToSRTLbl" (pprCLabel l)
510
511
512 -- -----------------------------------------------------------------------------
513 -- Does a CLabel refer to a CAF?
514 hasCAF :: CLabel -> Bool
515 hasCAF (IdLabel _ MayHaveCafRefs _) = True
516 hasCAF _                            = False
517
518
519 -- -----------------------------------------------------------------------------
520 -- Does a CLabel need declaring before use or not?
521 --
522 -- See wiki:Commentary/Compiler/Backends/PprC#Prototypes
523
524 needsCDecl :: CLabel -> Bool
525   -- False <=> it's pre-declared; don't bother
526   -- don't bother declaring SRT & Bitmap labels, we always make sure
527   -- they are defined before use.
528 needsCDecl (IdLabel _ _ SRT)            = False
529 needsCDecl (LargeSRTLabel _)            = False
530 needsCDecl (LargeBitmapLabel _)         = False
531 needsCDecl (IdLabel _ _ _)              = True
532 needsCDecl (CaseLabel _ _)              = True
533 needsCDecl (ModuleInitLabel _ _)        = True
534 needsCDecl (PlainModuleInitLabel _)     = True
535 needsCDecl (ModuleInitTableLabel _)     = True
536 needsCDecl ModuleRegdLabel              = False
537
538 needsCDecl (StringLitLabel _)           = False
539 needsCDecl (AsmTempLabel _)             = False
540 needsCDecl (RtsLabel _)                 = False
541 needsCDecl l@(ForeignLabel _ _ _ _)     = not (isMathFun l)
542 needsCDecl (CC_Label _)                 = True
543 needsCDecl (CCS_Label _)                = True
544 needsCDecl (HpcTicksLabel _)            = True
545 needsCDecl HpcModuleNameLabel           = False
546
547
548 -- | Check whether a label is a local temporary for native code generation
549 isAsmTemp  :: CLabel -> Bool    
550 isAsmTemp (AsmTempLabel _)              = True
551 isAsmTemp _                             = False
552
553
554 -- | If a label is a local temporary used for native code generation
555 --      then return just its unique, otherwise nothing.
556 maybeAsmTemp :: CLabel -> Maybe Unique
557 maybeAsmTemp (AsmTempLabel uq)          = Just uq
558 maybeAsmTemp _                          = Nothing
559
560
561 -- Check whether a label corresponds to a C function that has 
562 --      a prototype in a system header somehere, or is built-in
563 --      to the C compiler. For these labels we abovoid generating our
564 --      own C prototypes.
565 isMathFun :: CLabel -> Bool
566 isMathFun (ForeignLabel fs _ _ _) = fs `elementOfUniqSet` math_funs
567 isMathFun _ = False
568
569 math_funs = mkUniqSet [
570         -- _ISOC99_SOURCE
571         (fsLit "acos"),         (fsLit "acosf"),        (fsLit "acosh"),
572         (fsLit "acoshf"),       (fsLit "acoshl"),       (fsLit "acosl"),
573         (fsLit "asin"),         (fsLit "asinf"),        (fsLit "asinl"),
574         (fsLit "asinh"),        (fsLit "asinhf"),       (fsLit "asinhl"),
575         (fsLit "atan"),         (fsLit "atanf"),        (fsLit "atanl"),
576         (fsLit "atan2"),        (fsLit "atan2f"),       (fsLit "atan2l"),
577         (fsLit "atanh"),        (fsLit "atanhf"),       (fsLit "atanhl"),
578         (fsLit "cbrt"),         (fsLit "cbrtf"),        (fsLit "cbrtl"),
579         (fsLit "ceil"),         (fsLit "ceilf"),        (fsLit "ceill"),
580         (fsLit "copysign"),     (fsLit "copysignf"),    (fsLit "copysignl"),
581         (fsLit "cos"),          (fsLit "cosf"),         (fsLit "cosl"),
582         (fsLit "cosh"),         (fsLit "coshf"),        (fsLit "coshl"),
583         (fsLit "erf"),          (fsLit "erff"),         (fsLit "erfl"),
584         (fsLit "erfc"),         (fsLit "erfcf"),        (fsLit "erfcl"),
585         (fsLit "exp"),          (fsLit "expf"),         (fsLit "expl"),
586         (fsLit "exp2"),         (fsLit "exp2f"),        (fsLit "exp2l"),
587         (fsLit "expm1"),        (fsLit "expm1f"),       (fsLit "expm1l"),
588         (fsLit "fabs"),         (fsLit "fabsf"),        (fsLit "fabsl"),
589         (fsLit "fdim"),         (fsLit "fdimf"),        (fsLit "fdiml"),
590         (fsLit "floor"),        (fsLit "floorf"),       (fsLit "floorl"),
591         (fsLit "fma"),          (fsLit "fmaf"),         (fsLit "fmal"),
592         (fsLit "fmax"),         (fsLit "fmaxf"),        (fsLit "fmaxl"),
593         (fsLit "fmin"),         (fsLit "fminf"),        (fsLit "fminl"),
594         (fsLit "fmod"),         (fsLit "fmodf"),        (fsLit "fmodl"),
595         (fsLit "frexp"),        (fsLit "frexpf"),       (fsLit "frexpl"),
596         (fsLit "hypot"),        (fsLit "hypotf"),       (fsLit "hypotl"),
597         (fsLit "ilogb"),        (fsLit "ilogbf"),       (fsLit "ilogbl"),
598         (fsLit "ldexp"),        (fsLit "ldexpf"),       (fsLit "ldexpl"),
599         (fsLit "lgamma"),       (fsLit "lgammaf"),      (fsLit "lgammal"),
600         (fsLit "llrint"),       (fsLit "llrintf"),      (fsLit "llrintl"),
601         (fsLit "llround"),      (fsLit "llroundf"),     (fsLit "llroundl"),
602         (fsLit "log"),          (fsLit "logf"),         (fsLit "logl"),
603         (fsLit "log10l"),       (fsLit "log10"),        (fsLit "log10f"),
604         (fsLit "log1pl"),       (fsLit "log1p"),        (fsLit "log1pf"),
605         (fsLit "log2"),         (fsLit "log2f"),        (fsLit "log2l"),
606         (fsLit "logb"),         (fsLit "logbf"),        (fsLit "logbl"),
607         (fsLit "lrint"),        (fsLit "lrintf"),       (fsLit "lrintl"),
608         (fsLit "lround"),       (fsLit "lroundf"),      (fsLit "lroundl"),
609         (fsLit "modf"),         (fsLit "modff"),        (fsLit "modfl"),
610         (fsLit "nan"),          (fsLit "nanf"),         (fsLit "nanl"),
611         (fsLit "nearbyint"),    (fsLit "nearbyintf"),   (fsLit "nearbyintl"),
612         (fsLit "nextafter"),    (fsLit "nextafterf"),   (fsLit "nextafterl"),
613         (fsLit "nexttoward"),   (fsLit "nexttowardf"),  (fsLit "nexttowardl"),
614         (fsLit "pow"),          (fsLit "powf"),         (fsLit "powl"),
615         (fsLit "remainder"),    (fsLit "remainderf"),   (fsLit "remainderl"),
616         (fsLit "remquo"),       (fsLit "remquof"),      (fsLit "remquol"),
617         (fsLit "rint"),         (fsLit "rintf"),        (fsLit "rintl"),
618         (fsLit "round"),        (fsLit "roundf"),       (fsLit "roundl"),
619         (fsLit "scalbln"),      (fsLit "scalblnf"),     (fsLit "scalblnl"),
620         (fsLit "scalbn"),       (fsLit "scalbnf"),      (fsLit "scalbnl"),
621         (fsLit "sin"),          (fsLit "sinf"),         (fsLit "sinl"),
622         (fsLit "sinh"),         (fsLit "sinhf"),        (fsLit "sinhl"),
623         (fsLit "sqrt"),         (fsLit "sqrtf"),        (fsLit "sqrtl"),
624         (fsLit "tan"),          (fsLit "tanf"),         (fsLit "tanl"),
625         (fsLit "tanh"),         (fsLit "tanhf"),        (fsLit "tanhl"),
626         (fsLit "tgamma"),       (fsLit "tgammaf"),      (fsLit "tgammal"),
627         (fsLit "trunc"),        (fsLit "truncf"),       (fsLit "truncl"),
628         -- ISO C 99 also defines these function-like macros in math.h:
629         -- fpclassify, isfinite, isinf, isnormal, signbit, isgreater,
630         -- isgreaterequal, isless, islessequal, islessgreater, isunordered
631
632         -- additional symbols from _BSD_SOURCE
633         (fsLit "drem"),         (fsLit "dremf"),        (fsLit "dreml"),
634         (fsLit "finite"),       (fsLit "finitef"),      (fsLit "finitel"),
635         (fsLit "gamma"),        (fsLit "gammaf"),       (fsLit "gammal"),
636         (fsLit "isinf"),        (fsLit "isinff"),       (fsLit "isinfl"),
637         (fsLit "isnan"),        (fsLit "isnanf"),       (fsLit "isnanl"),
638         (fsLit "j0"),           (fsLit "j0f"),          (fsLit "j0l"),
639         (fsLit "j1"),           (fsLit "j1f"),          (fsLit "j1l"),
640         (fsLit "jn"),           (fsLit "jnf"),          (fsLit "jnl"),
641         (fsLit "lgamma_r"),     (fsLit "lgammaf_r"),    (fsLit "lgammal_r"),
642         (fsLit "scalb"),        (fsLit "scalbf"),       (fsLit "scalbl"),
643         (fsLit "significand"),  (fsLit "significandf"), (fsLit "significandl"),
644         (fsLit "y0"),           (fsLit "y0f"),          (fsLit "y0l"),
645         (fsLit "y1"),           (fsLit "y1f"),          (fsLit "y1l"),
646         (fsLit "yn"),           (fsLit "ynf"),          (fsLit "ynl")
647     ]
648
649 -- -----------------------------------------------------------------------------
650 -- Is a CLabel visible outside this object file or not?
651
652 -- From the point of view of the code generator, a name is
653 -- externally visible if it has to be declared as exported
654 -- in the .o file's symbol table; that is, made non-static.
655
656 externallyVisibleCLabel :: CLabel -> Bool -- not C "static"
657 externallyVisibleCLabel (CaseLabel _ _)         = False
658 externallyVisibleCLabel (StringLitLabel _)      = False
659 externallyVisibleCLabel (AsmTempLabel _)        = False
660 externallyVisibleCLabel (ModuleInitLabel _ _)   = True
661 externallyVisibleCLabel (PlainModuleInitLabel _)= True
662 externallyVisibleCLabel (ModuleInitTableLabel _)= False
663 externallyVisibleCLabel ModuleRegdLabel         = False
664 externallyVisibleCLabel (RtsLabel _)            = True
665 externallyVisibleCLabel (ForeignLabel _ _ _ _)  = True
666 externallyVisibleCLabel (IdLabel name _ _)      = isExternalName name
667 externallyVisibleCLabel (CC_Label _)            = True
668 externallyVisibleCLabel (CCS_Label _)           = True
669 externallyVisibleCLabel (DynamicLinkerLabel _ _)  = False
670 externallyVisibleCLabel (HpcTicksLabel _)       = True
671 externallyVisibleCLabel HpcModuleNameLabel      = False
672 externallyVisibleCLabel (LargeBitmapLabel _)    = False
673 externallyVisibleCLabel (LargeSRTLabel _)       = False
674
675 -- -----------------------------------------------------------------------------
676 -- Finding the "type" of a CLabel 
677
678 -- For generating correct types in label declarations:
679
680 data CLabelType
681   = CodeLabel   -- Address of some executable instructions
682   | DataLabel   -- Address of data, not a GC ptr
683   | GcPtrLabel  -- Address of a (presumably static) GC object
684
685 isCFunctionLabel :: CLabel -> Bool
686 isCFunctionLabel lbl = case labelType lbl of
687                         CodeLabel -> True
688                         _other    -> False
689
690 isGcPtrLabel :: CLabel -> Bool
691 isGcPtrLabel lbl = case labelType lbl of
692                         GcPtrLabel -> True
693                         _other     -> False
694
695
696 -- | Work out the general type of data at the address of this label
697 --    whether it be code, data, or static GC object.
698 labelType :: CLabel -> CLabelType
699 labelType (CmmLabel _ _ CmmData)                = DataLabel
700 labelType (CmmLabel _ _ CmmGcPtr)               = GcPtrLabel
701 labelType (CmmLabel _ _ CmmCode)                = CodeLabel
702 labelType (CmmLabel _ _ CmmInfo)                = DataLabel
703 labelType (CmmLabel _ _ CmmEntry)               = CodeLabel
704 labelType (CmmLabel _ _ CmmRetInfo)             = DataLabel
705 labelType (CmmLabel _ _ CmmRet)                 = CodeLabel
706 labelType (RtsLabel (RtsSelectorInfoTable _ _)) = DataLabel
707 labelType (RtsLabel (RtsApInfoTable _ _))       = DataLabel
708 labelType (RtsLabel (RtsApFast _))              = CodeLabel
709 labelType (CaseLabel _ CaseReturnInfo)          = DataLabel
710 labelType (CaseLabel _ _)                       = CodeLabel
711 labelType (ModuleInitLabel _ _)                 = CodeLabel
712 labelType (PlainModuleInitLabel _)              = CodeLabel
713 labelType (ModuleInitTableLabel _)              = DataLabel
714 labelType (LargeSRTLabel _)                     = DataLabel
715 labelType (LargeBitmapLabel _)                  = DataLabel
716 labelType (ForeignLabel _ _ _ IsFunction)       = CodeLabel
717 labelType (IdLabel _ _ info)                    = idInfoLabelType info
718 labelType _                                     = DataLabel
719
720 idInfoLabelType info =
721   case info of
722     InfoTable     -> DataLabel
723     Closure       -> GcPtrLabel
724     ConInfoTable  -> DataLabel
725     StaticInfoTable -> DataLabel
726     ClosureTable  -> DataLabel
727     RednCounts    -> DataLabel
728     _             -> CodeLabel
729
730
731 -- -----------------------------------------------------------------------------
732 -- Does a CLabel need dynamic linkage?
733
734 -- When referring to data in code, we need to know whether
735 -- that data resides in a DLL or not. [Win32 only.]
736 -- @labelDynamic@ returns @True@ if the label is located
737 -- in a DLL, be it a data reference or not.
738
739 labelDynamic :: PackageId -> CLabel -> Bool
740 labelDynamic this_pkg lbl =
741   case lbl of
742    RtsLabel _        -> not opt_Static && (this_pkg /= rtsPackageId) -- i.e., is the RTS in a DLL or not?
743    IdLabel n _ k       -> isDllName this_pkg n
744 #if mingw32_TARGET_OS
745    ForeignLabel _ _ d _ -> d
746 #else
747    -- On Mac OS X and on ELF platforms, false positives are OK,
748    -- so we claim that all foreign imports come from dynamic libraries
749    ForeignLabel _ _ _ _ -> True
750 #endif
751    ModuleInitLabel m _    -> not opt_Static && this_pkg /= (modulePackageId m)
752    PlainModuleInitLabel m -> not opt_Static && this_pkg /= (modulePackageId m)
753    ModuleInitTableLabel m -> not opt_Static && this_pkg /= (modulePackageId m)
754    
755    -- Note that DynamicLinkerLabels do NOT require dynamic linking themselves.
756    _                 -> False
757
758 {-
759 OLD?: These GRAN functions are needed for spitting out GRAN_FETCH() at the
760 right places. It is used to detect when the abstractC statement of an
761 CCodeBlock actually contains the code for a slow entry point.  -- HWL
762
763 We need at least @Eq@ for @CLabels@, because we want to avoid
764 duplicate declarations in generating C (see @labelSeenTE@ in
765 @PprAbsC@).
766 -}
767
768 -----------------------------------------------------------------------------
769 -- Printing out CLabels.
770
771 {-
772 Convention:
773
774       <name>_<type>
775
776 where <name> is <Module>_<name> for external names and <unique> for
777 internal names. <type> is one of the following:
778
779          info                   Info table
780          srt                    Static reference table
781          srtd                   Static reference table descriptor
782          entry                  Entry code (function, closure)
783          slow                   Slow entry code (if any)
784          ret                    Direct return address    
785          vtbl                   Vector table
786          <n>_alt                Case alternative (tag n)
787          dflt                   Default case alternative
788          btm                    Large bitmap vector
789          closure                Static closure
790          con_entry              Dynamic Constructor entry code
791          con_info               Dynamic Constructor info table
792          static_entry           Static Constructor entry code
793          static_info            Static Constructor info table
794          sel_info               Selector info table
795          sel_entry              Selector entry code
796          cc                     Cost centre
797          ccs                    Cost centre stack
798
799 Many of these distinctions are only for documentation reasons.  For
800 example, _ret is only distinguished from _entry to make it easy to
801 tell whether a code fragment is a return point or a closure/function
802 entry.
803 -}
804
805 instance Outputable CLabel where
806   ppr = pprCLabel
807
808 pprCLabel :: CLabel -> SDoc
809
810 #if ! OMIT_NATIVE_CODEGEN
811 pprCLabel (AsmTempLabel u)
812   =  getPprStyle $ \ sty ->
813      if asmStyle sty then 
814         ptext asmTempLabelPrefix <> pprUnique u
815      else
816         char '_' <> pprUnique u
817
818 pprCLabel (DynamicLinkerLabel info lbl)
819    = pprDynamicLinkerAsmLabel info lbl
820    
821 pprCLabel PicBaseLabel
822    = ptext (sLit "1b")
823    
824 pprCLabel (DeadStripPreventer lbl)
825    = pprCLabel lbl <> ptext (sLit "_dsp")
826 #endif
827
828 pprCLabel lbl = 
829 #if ! OMIT_NATIVE_CODEGEN
830     getPprStyle $ \ sty ->
831     if asmStyle sty then 
832         maybe_underscore (pprAsmCLbl lbl)
833     else
834 #endif
835        pprCLbl lbl
836
837 maybe_underscore doc
838   | underscorePrefix = pp_cSEP <> doc
839   | otherwise        = doc
840
841 #ifdef mingw32_TARGET_OS
842 -- In asm mode, we need to put the suffix on a stdcall ForeignLabel.
843 -- (The C compiler does this itself).
844 pprAsmCLbl (ForeignLabel fs (Just sz) _ _)
845    = ftext fs <> char '@' <> int sz
846 #endif
847 pprAsmCLbl lbl
848    = pprCLbl lbl
849
850 pprCLbl (StringLitLabel u)
851   = pprUnique u <> ptext (sLit "_str")
852
853 pprCLbl (CaseLabel u CaseReturnPt)
854   = hcat [pprUnique u, ptext (sLit "_ret")]
855 pprCLbl (CaseLabel u CaseReturnInfo)
856   = hcat [pprUnique u, ptext (sLit "_info")]
857 pprCLbl (CaseLabel u (CaseAlt tag))
858   = hcat [pprUnique u, pp_cSEP, int tag, ptext (sLit "_alt")]
859 pprCLbl (CaseLabel u CaseDefault)
860   = hcat [pprUnique u, ptext (sLit "_dflt")]
861
862 pprCLbl (LargeSRTLabel u)  = pprUnique u <> pp_cSEP <> ptext (sLit "srtd")
863 pprCLbl (LargeBitmapLabel u)  = text "b" <> pprUnique u <> pp_cSEP <> ptext (sLit "btm")
864 -- Some bitsmaps for tuple constructors have a numeric tag (e.g. '7')
865 -- until that gets resolved we'll just force them to start
866 -- with a letter so the label will be legal assmbly code.
867         
868
869 pprCLbl (CmmLabel _ str CmmCode)        = ftext str
870 pprCLbl (CmmLabel _ str CmmData)        = ftext str
871 pprCLbl (CmmLabel _ str CmmGcPtr)       = ftext str
872
873 pprCLbl (RtsLabel (RtsApFast str))   = ftext str <> ptext (sLit "_fast")
874
875 pprCLbl (RtsLabel (RtsSelectorInfoTable upd_reqd offset))
876   = hcat [ptext (sLit "stg_sel_"), text (show offset),
877                 ptext (if upd_reqd 
878                         then (sLit "_upd_info") 
879                         else (sLit "_noupd_info"))
880         ]
881
882 pprCLbl (RtsLabel (RtsSelectorEntry upd_reqd offset))
883   = hcat [ptext (sLit "stg_sel_"), text (show offset),
884                 ptext (if upd_reqd 
885                         then (sLit "_upd_entry") 
886                         else (sLit "_noupd_entry"))
887         ]
888
889 pprCLbl (RtsLabel (RtsApInfoTable upd_reqd arity))
890   = hcat [ptext (sLit "stg_ap_"), text (show arity),
891                 ptext (if upd_reqd 
892                         then (sLit "_upd_info") 
893                         else (sLit "_noupd_info"))
894         ]
895
896 pprCLbl (RtsLabel (RtsApEntry upd_reqd arity))
897   = hcat [ptext (sLit "stg_ap_"), text (show arity),
898                 ptext (if upd_reqd 
899                         then (sLit "_upd_entry") 
900                         else (sLit "_noupd_entry"))
901         ]
902
903 pprCLbl (CmmLabel _ fs CmmInfo)
904   = ftext fs <> ptext (sLit "_info")
905
906 pprCLbl (CmmLabel _ fs CmmEntry)
907   = ftext fs <> ptext (sLit "_entry")
908
909 pprCLbl (CmmLabel _ fs CmmRetInfo)
910   = ftext fs <> ptext (sLit "_info")
911
912 pprCLbl (CmmLabel _ fs CmmRet)
913   = ftext fs <> ptext (sLit "_ret")
914
915 pprCLbl (RtsLabel (RtsPrimOp primop)) 
916   = ptext (sLit "stg_") <> ppr primop
917
918 pprCLbl (RtsLabel (RtsSlowTickyCtr pat)) 
919   = ptext (sLit "SLOW_CALL_") <> text pat <> ptext (sLit "_ctr")
920
921 pprCLbl ModuleRegdLabel
922   = ptext (sLit "_module_registered")
923
924 pprCLbl (ForeignLabel str _ _ _)
925   = ftext str
926
927 pprCLbl (IdLabel name cafs flavor) = ppr name <> ppIdFlavor flavor
928
929 pprCLbl (CC_Label cc)           = ppr cc
930 pprCLbl (CCS_Label ccs)         = ppr ccs
931
932 pprCLbl (ModuleInitLabel mod way)
933    = ptext (sLit "__stginit_") <> ppr mod
934         <> char '_' <> text way
935
936 pprCLbl (PlainModuleInitLabel mod)
937    = ptext (sLit "__stginit_") <> ppr mod
938
939 pprCLbl (ModuleInitTableLabel mod)
940    = ptext (sLit "__stginittable_") <> ppr mod
941
942 pprCLbl (HpcTicksLabel mod)
943   = ptext (sLit "_hpc_tickboxes_")  <> ppr mod <> ptext (sLit "_hpc")
944
945 pprCLbl HpcModuleNameLabel
946   = ptext (sLit "_hpc_module_name_str")
947
948 ppIdFlavor :: IdLabelInfo -> SDoc
949 ppIdFlavor x = pp_cSEP <>
950                (case x of
951                        Closure          -> ptext (sLit "closure")
952                        SRT              -> ptext (sLit "srt")
953                        InfoTable        -> ptext (sLit "info")
954                        Entry            -> ptext (sLit "entry")
955                        Slow             -> ptext (sLit "slow")
956                        RednCounts       -> ptext (sLit "ct")
957                        ConEntry         -> ptext (sLit "con_entry")
958                        ConInfoTable     -> ptext (sLit "con_info")
959                        StaticConEntry   -> ptext (sLit "static_entry")
960                        StaticInfoTable  -> ptext (sLit "static_info")
961                        ClosureTable     -> ptext (sLit "closure_tbl")
962                       )
963
964
965 pp_cSEP = char '_'
966
967 -- -----------------------------------------------------------------------------
968 -- Machine-dependent knowledge about labels.
969
970 underscorePrefix :: Bool   -- leading underscore on assembler labels?
971 underscorePrefix = (cLeadingUnderscore == "YES")
972
973 asmTempLabelPrefix :: LitString  -- for formatting labels
974 asmTempLabelPrefix =
975 #if alpha_TARGET_OS
976      {- The alpha assembler likes temporary labels to look like $L123
977         instead of L123.  (Don't toss the L, because then Lf28
978         turns into $f28.)
979      -}
980      (sLit "$")
981 #elif darwin_TARGET_OS
982      (sLit "L")
983 #else
984      (sLit ".L")
985 #endif
986
987 pprDynamicLinkerAsmLabel :: DynamicLinkerLabelInfo -> CLabel -> SDoc
988
989 #if x86_64_TARGET_ARCH && darwin_TARGET_OS
990 pprDynamicLinkerAsmLabel CodeStub lbl
991   = char 'L' <> pprCLabel lbl <> text "$stub"
992 pprDynamicLinkerAsmLabel SymbolPtr lbl
993   = char 'L' <> pprCLabel lbl <> text "$non_lazy_ptr"
994 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
995   = pprCLabel lbl <> text "@GOTPCREL"
996 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
997   = pprCLabel lbl
998 pprDynamicLinkerAsmLabel _ _
999   = panic "pprDynamicLinkerAsmLabel"
1000
1001 #elif darwin_TARGET_OS
1002 pprDynamicLinkerAsmLabel CodeStub lbl
1003   = char 'L' <> pprCLabel lbl <> text "$stub"
1004 pprDynamicLinkerAsmLabel SymbolPtr lbl
1005   = char 'L' <> pprCLabel lbl <> text "$non_lazy_ptr"
1006 pprDynamicLinkerAsmLabel _ _
1007   = panic "pprDynamicLinkerAsmLabel"
1008
1009 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
1010 pprDynamicLinkerAsmLabel CodeStub lbl
1011   = pprCLabel lbl <> text "@plt"
1012 pprDynamicLinkerAsmLabel SymbolPtr lbl
1013   = text ".LC_" <> pprCLabel lbl
1014 pprDynamicLinkerAsmLabel _ _
1015   = panic "pprDynamicLinkerAsmLabel"
1016
1017 #elif x86_64_TARGET_ARCH && linux_TARGET_OS
1018 pprDynamicLinkerAsmLabel CodeStub lbl
1019   = pprCLabel lbl <> text "@plt"
1020 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
1021   = pprCLabel lbl <> text "@gotpcrel"
1022 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
1023   = pprCLabel lbl
1024 pprDynamicLinkerAsmLabel SymbolPtr lbl
1025   = text ".LC_" <> pprCLabel lbl
1026
1027 #elif linux_TARGET_OS
1028 pprDynamicLinkerAsmLabel CodeStub lbl
1029   = pprCLabel lbl <> text "@plt"
1030 pprDynamicLinkerAsmLabel SymbolPtr lbl
1031   = text ".LC_" <> pprCLabel lbl
1032 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
1033   = pprCLabel lbl <> text "@got"
1034 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
1035   = pprCLabel lbl <> text "@gotoff"
1036
1037 #elif mingw32_TARGET_OS
1038 pprDynamicLinkerAsmLabel SymbolPtr lbl
1039   = text "__imp_" <> pprCLabel lbl
1040 pprDynamicLinkerAsmLabel _ _
1041   = panic "pprDynamicLinkerAsmLabel"
1042
1043 #else
1044 pprDynamicLinkerAsmLabel _ _
1045   = panic "pprDynamicLinkerAsmLabel"
1046 #endif