Typo in comment
[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         mkCmmInfoLabel,
77         mkCmmEntryLabel,
78         mkCmmRetInfoLabel,
79         mkCmmRetLabel,
80         mkCmmCodeLabel,
81         mkCmmDataLabel,
82         mkCmmGcPtrLabel,
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         PackageId               -- what package 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 PackageId 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 -- Constructing Cmm Labels
346 mkSplitMarkerLabel              = CmmLabel rtsPackageId (fsLit "__stg_split_marker")    CmmCode
347 mkDirty_MUT_VAR_Label           = CmmLabel rtsPackageId (fsLit "dirty_MUT_VAR")         CmmCode
348 mkUpdInfoLabel                  = CmmLabel rtsPackageId (fsLit "stg_upd_frame")         CmmInfo
349 mkIndStaticInfoLabel            = CmmLabel rtsPackageId (fsLit "stg_IND_STATIC")        CmmInfo
350 mkMainCapabilityLabel           = CmmLabel rtsPackageId (fsLit "MainCapability")        CmmData
351 mkMAP_FROZEN_infoLabel          = CmmLabel rtsPackageId (fsLit "stg_MUT_ARR_PTRS_FROZEN0") CmmInfo
352 mkMAP_DIRTY_infoLabel           = CmmLabel rtsPackageId (fsLit "stg_MUT_ARR_PTRS_DIRTY") CmmInfo
353 mkEMPTY_MVAR_infoLabel          = CmmLabel rtsPackageId (fsLit "stg_EMPTY_MVAR")        CmmInfo
354 mkTopTickyCtrLabel              = CmmLabel rtsPackageId (fsLit "top_ct")                CmmData
355 mkCAFBlackHoleInfoTableLabel    = CmmLabel rtsPackageId (fsLit "stg_CAF_BLACKHOLE")     CmmInfo
356
357 -----
358 mkCmmInfoLabel,   mkCmmEntryLabel, mkCmmRetInfoLabel, mkCmmRetLabel,
359   mkCmmCodeLabel, mkCmmDataLabel,  mkCmmGcPtrLabel
360         :: PackageId -> FastString -> CLabel
361
362 mkCmmInfoLabel      pkg str     = CmmLabel pkg str CmmInfo
363 mkCmmEntryLabel     pkg str     = CmmLabel pkg str CmmEntry
364 mkCmmRetInfoLabel   pkg str     = CmmLabel pkg str CmmRetInfo
365 mkCmmRetLabel       pkg str     = CmmLabel pkg str CmmRet
366 mkCmmCodeLabel      pkg str     = CmmLabel pkg str CmmCode
367 mkCmmDataLabel      pkg str     = CmmLabel pkg str CmmData
368 mkCmmGcPtrLabel     pkg str     = CmmLabel pkg str CmmGcPtr
369
370
371 -- Constructing RtsLabels
372 mkRtsPrimOpLabel primop         = RtsLabel (RtsPrimOp primop)
373
374 mkSelectorInfoLabel  upd off    = RtsLabel (RtsSelectorInfoTable upd off)
375 mkSelectorEntryLabel upd off    = RtsLabel (RtsSelectorEntry     upd off)
376
377 mkApInfoTableLabel   upd off    = RtsLabel (RtsApInfoTable       upd off)
378 mkApEntryLabel       upd off    = RtsLabel (RtsApEntry           upd off)
379
380
381 -- Constructing ForeignLabels
382 -- Primitive / cmm call labels
383 mkPrimCallLabel :: PrimCall -> CLabel
384 mkPrimCallLabel (PrimCall str)  = ForeignLabel str Nothing False IsFunction
385
386 -- Foreign labels
387 mkForeignLabel :: FastString -> Maybe Int -> Bool -> FunctionOrData -> CLabel
388 mkForeignLabel str mb_sz is_dynamic fod
389     = ForeignLabel str mb_sz is_dynamic fod
390
391 addLabelSize :: CLabel -> Int -> CLabel
392 addLabelSize (ForeignLabel str _ is_dynamic fod) sz
393     = ForeignLabel str (Just sz) is_dynamic fod
394 addLabelSize label _
395     = label
396
397 foreignLabelStdcallInfo :: CLabel -> Maybe Int
398 foreignLabelStdcallInfo (ForeignLabel _ info _ _) = info
399 foreignLabelStdcallInfo _lbl = Nothing
400
401
402 -- Constructing Large*Labels
403 mkLargeSRTLabel uniq            = LargeSRTLabel uniq
404 mkBitmapLabel   uniq            = LargeBitmapLabel uniq
405
406
407 -- Constructin CaseLabels
408 mkReturnPtLabel uniq            = CaseLabel uniq CaseReturnPt
409 mkReturnInfoLabel uniq          = CaseLabel uniq CaseReturnInfo
410 mkAltLabel      uniq tag        = CaseLabel uniq (CaseAlt tag)
411 mkDefaultLabel  uniq            = CaseLabel uniq CaseDefault
412
413 -- Constructing Cost Center Labels
414 mkCCLabel           cc          = CC_Label cc
415 mkCCSLabel          ccs         = CCS_Label ccs
416
417 mkRtsApFastLabel str = RtsLabel (RtsApFast str)
418
419 mkRtsSlowTickyCtrLabel :: String -> CLabel
420 mkRtsSlowTickyCtrLabel pat = RtsLabel (RtsSlowTickyCtr pat)
421
422
423 -- Constructing Code Coverage Labels
424 mkHpcTicksLabel                = HpcTicksLabel
425 mkHpcModuleNameLabel           = HpcModuleNameLabel
426
427
428 -- Constructing labels used for dynamic linking
429 mkDynamicLinkerLabel :: DynamicLinkerLabelInfo -> CLabel -> CLabel
430 mkDynamicLinkerLabel            = DynamicLinkerLabel
431
432 dynamicLinkerLabelInfo :: CLabel -> Maybe (DynamicLinkerLabelInfo, CLabel)
433 dynamicLinkerLabelInfo (DynamicLinkerLabel info lbl) = Just (info, lbl)
434 dynamicLinkerLabelInfo _        = Nothing
435     
436 mkPicBaseLabel :: CLabel
437 mkPicBaseLabel                  = PicBaseLabel
438
439
440 -- Constructing miscellaneous other labels
441 mkDeadStripPreventer :: CLabel -> CLabel
442 mkDeadStripPreventer lbl        = DeadStripPreventer lbl
443
444 mkStringLitLabel :: Unique -> CLabel
445 mkStringLitLabel                = StringLitLabel
446
447 mkAsmTempLabel :: Uniquable a => a -> CLabel
448 mkAsmTempLabel a                = AsmTempLabel (getUnique a)
449
450 mkModuleInitLabel :: Module -> String -> CLabel
451 mkModuleInitLabel mod way       = ModuleInitLabel mod way
452
453 mkPlainModuleInitLabel :: Module -> CLabel
454 mkPlainModuleInitLabel mod      = PlainModuleInitLabel mod
455
456 mkModuleInitTableLabel :: Module -> CLabel
457 mkModuleInitTableLabel mod      = ModuleInitTableLabel mod
458
459 moduleRegdLabel                 = ModuleRegdLabel
460 moduleRegTableLabel             = ModuleInitTableLabel  
461
462
463 -- -----------------------------------------------------------------------------
464 -- Converting between info labels and entry/ret labels.
465
466 infoLblToEntryLbl :: CLabel -> CLabel 
467 infoLblToEntryLbl (IdLabel n c InfoTable)       = IdLabel n c Entry
468 infoLblToEntryLbl (IdLabel n c ConInfoTable)    = IdLabel n c ConEntry
469 infoLblToEntryLbl (IdLabel n c StaticInfoTable) = IdLabel n c StaticConEntry
470 infoLblToEntryLbl (CaseLabel n CaseReturnInfo)  = CaseLabel n CaseReturnPt
471 infoLblToEntryLbl (CmmLabel m str CmmInfo)      = CmmLabel m str CmmEntry
472 infoLblToEntryLbl (CmmLabel m str CmmRetInfo)   = CmmLabel m str CmmRet
473 infoLblToEntryLbl _
474         = panic "CLabel.infoLblToEntryLbl"
475
476
477 entryLblToInfoLbl :: CLabel -> CLabel 
478 entryLblToInfoLbl (IdLabel n c Entry)           = IdLabel n c InfoTable
479 entryLblToInfoLbl (IdLabel n c ConEntry)        = IdLabel n c ConInfoTable
480 entryLblToInfoLbl (IdLabel n c StaticConEntry)  = IdLabel n c StaticInfoTable
481 entryLblToInfoLbl (CaseLabel n CaseReturnPt)    = CaseLabel n CaseReturnInfo
482 entryLblToInfoLbl (CmmLabel m str CmmEntry)     = CmmLabel m str CmmInfo
483 entryLblToInfoLbl (CmmLabel m str CmmRet)       = CmmLabel m str CmmRetInfo
484 entryLblToInfoLbl l                             
485         = pprPanic "CLabel.entryLblToInfoLbl" (pprCLabel l)
486
487
488 cvtToClosureLbl   (IdLabel n c InfoTable)       = IdLabel n c Closure
489 cvtToClosureLbl   (IdLabel n c Entry)           = IdLabel n c Closure
490 cvtToClosureLbl   (IdLabel n c ConEntry)        = IdLabel n c Closure
491 cvtToClosureLbl l@(IdLabel n c Closure)         = l
492 cvtToClosureLbl l 
493         = pprPanic "cvtToClosureLbl" (pprCLabel l)
494
495
496 cvtToSRTLbl   (IdLabel n c InfoTable)           = mkSRTLabel n c
497 cvtToSRTLbl   (IdLabel n c Entry)               = mkSRTLabel n c
498 cvtToSRTLbl   (IdLabel n c ConEntry)            = mkSRTLabel n c
499 cvtToSRTLbl l@(IdLabel n c Closure)             = mkSRTLabel n c
500 cvtToSRTLbl l 
501         = pprPanic "cvtToSRTLbl" (pprCLabel l)
502
503
504 -- -----------------------------------------------------------------------------
505 -- Does a CLabel refer to a CAF?
506 hasCAF :: CLabel -> Bool
507 hasCAF (IdLabel _ MayHaveCafRefs _) = True
508 hasCAF _                            = False
509
510
511 -- -----------------------------------------------------------------------------
512 -- Does a CLabel need declaring before use or not?
513 --
514 -- See wiki:Commentary/Compiler/Backends/PprC#Prototypes
515
516 needsCDecl :: CLabel -> Bool
517   -- False <=> it's pre-declared; don't bother
518   -- don't bother declaring SRT & Bitmap labels, we always make sure
519   -- they are defined before use.
520 needsCDecl (IdLabel _ _ SRT)            = False
521 needsCDecl (LargeSRTLabel _)            = False
522 needsCDecl (LargeBitmapLabel _)         = False
523 needsCDecl (IdLabel _ _ _)              = True
524 needsCDecl (CaseLabel _ _)              = True
525 needsCDecl (ModuleInitLabel _ _)        = True
526 needsCDecl (PlainModuleInitLabel _)     = True
527 needsCDecl (ModuleInitTableLabel _)     = True
528 needsCDecl ModuleRegdLabel              = False
529
530 needsCDecl (StringLitLabel _)           = False
531 needsCDecl (AsmTempLabel _)             = False
532 needsCDecl (RtsLabel _)                 = False
533 needsCDecl (CmmLabel _ _ _)             = False
534 needsCDecl l@(ForeignLabel _ _ _ _)     = not (isMathFun l)
535 needsCDecl (CC_Label _)                 = True
536 needsCDecl (CCS_Label _)                = True
537 needsCDecl (HpcTicksLabel _)            = True
538 needsCDecl HpcModuleNameLabel           = False
539
540
541 -- | Check whether a label is a local temporary for native code generation
542 isAsmTemp  :: CLabel -> Bool    
543 isAsmTemp (AsmTempLabel _)              = True
544 isAsmTemp _                             = False
545
546
547 -- | If a label is a local temporary used for native code generation
548 --      then return just its unique, otherwise nothing.
549 maybeAsmTemp :: CLabel -> Maybe Unique
550 maybeAsmTemp (AsmTempLabel uq)          = Just uq
551 maybeAsmTemp _                          = Nothing
552
553
554 -- Check whether a label corresponds to a C function that has 
555 --      a prototype in a system header somehere, or is built-in
556 --      to the C compiler. For these labels we abovoid generating our
557 --      own C prototypes.
558 isMathFun :: CLabel -> Bool
559 isMathFun (ForeignLabel fs _ _ _) = fs `elementOfUniqSet` math_funs
560 isMathFun _ = False
561
562 math_funs = mkUniqSet [
563         -- _ISOC99_SOURCE
564         (fsLit "acos"),         (fsLit "acosf"),        (fsLit "acosh"),
565         (fsLit "acoshf"),       (fsLit "acoshl"),       (fsLit "acosl"),
566         (fsLit "asin"),         (fsLit "asinf"),        (fsLit "asinl"),
567         (fsLit "asinh"),        (fsLit "asinhf"),       (fsLit "asinhl"),
568         (fsLit "atan"),         (fsLit "atanf"),        (fsLit "atanl"),
569         (fsLit "atan2"),        (fsLit "atan2f"),       (fsLit "atan2l"),
570         (fsLit "atanh"),        (fsLit "atanhf"),       (fsLit "atanhl"),
571         (fsLit "cbrt"),         (fsLit "cbrtf"),        (fsLit "cbrtl"),
572         (fsLit "ceil"),         (fsLit "ceilf"),        (fsLit "ceill"),
573         (fsLit "copysign"),     (fsLit "copysignf"),    (fsLit "copysignl"),
574         (fsLit "cos"),          (fsLit "cosf"),         (fsLit "cosl"),
575         (fsLit "cosh"),         (fsLit "coshf"),        (fsLit "coshl"),
576         (fsLit "erf"),          (fsLit "erff"),         (fsLit "erfl"),
577         (fsLit "erfc"),         (fsLit "erfcf"),        (fsLit "erfcl"),
578         (fsLit "exp"),          (fsLit "expf"),         (fsLit "expl"),
579         (fsLit "exp2"),         (fsLit "exp2f"),        (fsLit "exp2l"),
580         (fsLit "expm1"),        (fsLit "expm1f"),       (fsLit "expm1l"),
581         (fsLit "fabs"),         (fsLit "fabsf"),        (fsLit "fabsl"),
582         (fsLit "fdim"),         (fsLit "fdimf"),        (fsLit "fdiml"),
583         (fsLit "floor"),        (fsLit "floorf"),       (fsLit "floorl"),
584         (fsLit "fma"),          (fsLit "fmaf"),         (fsLit "fmal"),
585         (fsLit "fmax"),         (fsLit "fmaxf"),        (fsLit "fmaxl"),
586         (fsLit "fmin"),         (fsLit "fminf"),        (fsLit "fminl"),
587         (fsLit "fmod"),         (fsLit "fmodf"),        (fsLit "fmodl"),
588         (fsLit "frexp"),        (fsLit "frexpf"),       (fsLit "frexpl"),
589         (fsLit "hypot"),        (fsLit "hypotf"),       (fsLit "hypotl"),
590         (fsLit "ilogb"),        (fsLit "ilogbf"),       (fsLit "ilogbl"),
591         (fsLit "ldexp"),        (fsLit "ldexpf"),       (fsLit "ldexpl"),
592         (fsLit "lgamma"),       (fsLit "lgammaf"),      (fsLit "lgammal"),
593         (fsLit "llrint"),       (fsLit "llrintf"),      (fsLit "llrintl"),
594         (fsLit "llround"),      (fsLit "llroundf"),     (fsLit "llroundl"),
595         (fsLit "log"),          (fsLit "logf"),         (fsLit "logl"),
596         (fsLit "log10l"),       (fsLit "log10"),        (fsLit "log10f"),
597         (fsLit "log1pl"),       (fsLit "log1p"),        (fsLit "log1pf"),
598         (fsLit "log2"),         (fsLit "log2f"),        (fsLit "log2l"),
599         (fsLit "logb"),         (fsLit "logbf"),        (fsLit "logbl"),
600         (fsLit "lrint"),        (fsLit "lrintf"),       (fsLit "lrintl"),
601         (fsLit "lround"),       (fsLit "lroundf"),      (fsLit "lroundl"),
602         (fsLit "modf"),         (fsLit "modff"),        (fsLit "modfl"),
603         (fsLit "nan"),          (fsLit "nanf"),         (fsLit "nanl"),
604         (fsLit "nearbyint"),    (fsLit "nearbyintf"),   (fsLit "nearbyintl"),
605         (fsLit "nextafter"),    (fsLit "nextafterf"),   (fsLit "nextafterl"),
606         (fsLit "nexttoward"),   (fsLit "nexttowardf"),  (fsLit "nexttowardl"),
607         (fsLit "pow"),          (fsLit "powf"),         (fsLit "powl"),
608         (fsLit "remainder"),    (fsLit "remainderf"),   (fsLit "remainderl"),
609         (fsLit "remquo"),       (fsLit "remquof"),      (fsLit "remquol"),
610         (fsLit "rint"),         (fsLit "rintf"),        (fsLit "rintl"),
611         (fsLit "round"),        (fsLit "roundf"),       (fsLit "roundl"),
612         (fsLit "scalbln"),      (fsLit "scalblnf"),     (fsLit "scalblnl"),
613         (fsLit "scalbn"),       (fsLit "scalbnf"),      (fsLit "scalbnl"),
614         (fsLit "sin"),          (fsLit "sinf"),         (fsLit "sinl"),
615         (fsLit "sinh"),         (fsLit "sinhf"),        (fsLit "sinhl"),
616         (fsLit "sqrt"),         (fsLit "sqrtf"),        (fsLit "sqrtl"),
617         (fsLit "tan"),          (fsLit "tanf"),         (fsLit "tanl"),
618         (fsLit "tanh"),         (fsLit "tanhf"),        (fsLit "tanhl"),
619         (fsLit "tgamma"),       (fsLit "tgammaf"),      (fsLit "tgammal"),
620         (fsLit "trunc"),        (fsLit "truncf"),       (fsLit "truncl"),
621         -- ISO C 99 also defines these function-like macros in math.h:
622         -- fpclassify, isfinite, isinf, isnormal, signbit, isgreater,
623         -- isgreaterequal, isless, islessequal, islessgreater, isunordered
624
625         -- additional symbols from _BSD_SOURCE
626         (fsLit "drem"),         (fsLit "dremf"),        (fsLit "dreml"),
627         (fsLit "finite"),       (fsLit "finitef"),      (fsLit "finitel"),
628         (fsLit "gamma"),        (fsLit "gammaf"),       (fsLit "gammal"),
629         (fsLit "isinf"),        (fsLit "isinff"),       (fsLit "isinfl"),
630         (fsLit "isnan"),        (fsLit "isnanf"),       (fsLit "isnanl"),
631         (fsLit "j0"),           (fsLit "j0f"),          (fsLit "j0l"),
632         (fsLit "j1"),           (fsLit "j1f"),          (fsLit "j1l"),
633         (fsLit "jn"),           (fsLit "jnf"),          (fsLit "jnl"),
634         (fsLit "lgamma_r"),     (fsLit "lgammaf_r"),    (fsLit "lgammal_r"),
635         (fsLit "scalb"),        (fsLit "scalbf"),       (fsLit "scalbl"),
636         (fsLit "significand"),  (fsLit "significandf"), (fsLit "significandl"),
637         (fsLit "y0"),           (fsLit "y0f"),          (fsLit "y0l"),
638         (fsLit "y1"),           (fsLit "y1f"),          (fsLit "y1l"),
639         (fsLit "yn"),           (fsLit "ynf"),          (fsLit "ynl")
640     ]
641
642 -- -----------------------------------------------------------------------------
643 -- Is a CLabel visible outside this object file or not?
644
645 -- From the point of view of the code generator, a name is
646 -- externally visible if it has to be declared as exported
647 -- in the .o file's symbol table; that is, made non-static.
648
649 externallyVisibleCLabel :: CLabel -> Bool -- not C "static"
650 externallyVisibleCLabel (CaseLabel _ _)         = False
651 externallyVisibleCLabel (StringLitLabel _)      = False
652 externallyVisibleCLabel (AsmTempLabel _)        = False
653 externallyVisibleCLabel (ModuleInitLabel _ _)   = True
654 externallyVisibleCLabel (PlainModuleInitLabel _)= True
655 externallyVisibleCLabel (ModuleInitTableLabel _)= False
656 externallyVisibleCLabel ModuleRegdLabel         = False
657 externallyVisibleCLabel (RtsLabel _)            = True
658 externallyVisibleCLabel (CmmLabel _ _ _)        = True
659 externallyVisibleCLabel (ForeignLabel _ _ _ _)  = True
660 externallyVisibleCLabel (IdLabel name _ _)      = isExternalName name
661 externallyVisibleCLabel (CC_Label _)            = True
662 externallyVisibleCLabel (CCS_Label _)           = True
663 externallyVisibleCLabel (DynamicLinkerLabel _ _)  = False
664 externallyVisibleCLabel (HpcTicksLabel _)       = True
665 externallyVisibleCLabel HpcModuleNameLabel      = False
666 externallyVisibleCLabel (LargeBitmapLabel _)    = False
667 externallyVisibleCLabel (LargeSRTLabel _)       = False
668
669 -- -----------------------------------------------------------------------------
670 -- Finding the "type" of a CLabel 
671
672 -- For generating correct types in label declarations:
673
674 data CLabelType
675   = CodeLabel   -- Address of some executable instructions
676   | DataLabel   -- Address of data, not a GC ptr
677   | GcPtrLabel  -- Address of a (presumably static) GC object
678
679 isCFunctionLabel :: CLabel -> Bool
680 isCFunctionLabel lbl = case labelType lbl of
681                         CodeLabel -> True
682                         _other    -> False
683
684 isGcPtrLabel :: CLabel -> Bool
685 isGcPtrLabel lbl = case labelType lbl of
686                         GcPtrLabel -> True
687                         _other     -> False
688
689
690 -- | Work out the general type of data at the address of this label
691 --    whether it be code, data, or static GC object.
692 labelType :: CLabel -> CLabelType
693 labelType (CmmLabel _ _ CmmData)                = DataLabel
694 labelType (CmmLabel _ _ CmmGcPtr)               = GcPtrLabel
695 labelType (CmmLabel _ _ CmmCode)                = CodeLabel
696 labelType (CmmLabel _ _ CmmInfo)                = DataLabel
697 labelType (CmmLabel _ _ CmmEntry)               = CodeLabel
698 labelType (CmmLabel _ _ CmmRetInfo)             = DataLabel
699 labelType (CmmLabel _ _ CmmRet)                 = CodeLabel
700 labelType (RtsLabel (RtsSelectorInfoTable _ _)) = DataLabel
701 labelType (RtsLabel (RtsApInfoTable _ _))       = DataLabel
702 labelType (RtsLabel (RtsApFast _))              = CodeLabel
703 labelType (CaseLabel _ CaseReturnInfo)          = DataLabel
704 labelType (CaseLabel _ _)                       = CodeLabel
705 labelType (ModuleInitLabel _ _)                 = CodeLabel
706 labelType (PlainModuleInitLabel _)              = CodeLabel
707 labelType (ModuleInitTableLabel _)              = DataLabel
708 labelType (LargeSRTLabel _)                     = DataLabel
709 labelType (LargeBitmapLabel _)                  = DataLabel
710 labelType (ForeignLabel _ _ _ IsFunction)       = CodeLabel
711 labelType (IdLabel _ _ info)                    = idInfoLabelType info
712 labelType _                                     = DataLabel
713
714 idInfoLabelType info =
715   case info of
716     InfoTable     -> DataLabel
717     Closure       -> GcPtrLabel
718     ConInfoTable  -> DataLabel
719     StaticInfoTable -> DataLabel
720     ClosureTable  -> DataLabel
721     RednCounts    -> DataLabel
722     _             -> CodeLabel
723
724
725 -- -----------------------------------------------------------------------------
726 -- Does a CLabel need dynamic linkage?
727
728 -- When referring to data in code, we need to know whether
729 -- that data resides in a DLL or not. [Win32 only.]
730 -- @labelDynamic@ returns @True@ if the label is located
731 -- in a DLL, be it a data reference or not.
732
733 labelDynamic :: PackageId -> CLabel -> Bool
734 labelDynamic this_pkg lbl =
735   case lbl of
736    RtsLabel _           -> not opt_Static && (this_pkg /= rtsPackageId) -- i.e., is the RTS in a DLL or not?
737    CmmLabel pkg _ _     -> not opt_Static && (this_pkg /= pkg)
738    IdLabel n _ k        -> isDllName this_pkg n
739 #if mingw32_TARGET_OS
740    ForeignLabel _ _ d _ -> d
741 #else
742    -- On Mac OS X and on ELF platforms, false positives are OK,
743    -- so we claim that all foreign imports come from dynamic libraries
744    ForeignLabel _ _ _ _ -> True
745 #endif
746    ModuleInitLabel m _    -> not opt_Static && this_pkg /= (modulePackageId m)
747    PlainModuleInitLabel m -> not opt_Static && this_pkg /= (modulePackageId m)
748    ModuleInitTableLabel m -> not opt_Static && this_pkg /= (modulePackageId m)
749    
750    -- Note that DynamicLinkerLabels do NOT require dynamic linking themselves.
751    _                 -> False
752
753 {-
754 OLD?: These GRAN functions are needed for spitting out GRAN_FETCH() at the
755 right places. It is used to detect when the abstractC statement of an
756 CCodeBlock actually contains the code for a slow entry point.  -- HWL
757
758 We need at least @Eq@ for @CLabels@, because we want to avoid
759 duplicate declarations in generating C (see @labelSeenTE@ in
760 @PprAbsC@).
761 -}
762
763 -----------------------------------------------------------------------------
764 -- Printing out CLabels.
765
766 {-
767 Convention:
768
769       <name>_<type>
770
771 where <name> is <Module>_<name> for external names and <unique> for
772 internal names. <type> is one of the following:
773
774          info                   Info table
775          srt                    Static reference table
776          srtd                   Static reference table descriptor
777          entry                  Entry code (function, closure)
778          slow                   Slow entry code (if any)
779          ret                    Direct return address    
780          vtbl                   Vector table
781          <n>_alt                Case alternative (tag n)
782          dflt                   Default case alternative
783          btm                    Large bitmap vector
784          closure                Static closure
785          con_entry              Dynamic Constructor entry code
786          con_info               Dynamic Constructor info table
787          static_entry           Static Constructor entry code
788          static_info            Static Constructor info table
789          sel_info               Selector info table
790          sel_entry              Selector entry code
791          cc                     Cost centre
792          ccs                    Cost centre stack
793
794 Many of these distinctions are only for documentation reasons.  For
795 example, _ret is only distinguished from _entry to make it easy to
796 tell whether a code fragment is a return point or a closure/function
797 entry.
798 -}
799
800 instance Outputable CLabel where
801   ppr = pprCLabel
802
803 pprCLabel :: CLabel -> SDoc
804
805 #if ! OMIT_NATIVE_CODEGEN
806 pprCLabel (AsmTempLabel u)
807   =  getPprStyle $ \ sty ->
808      if asmStyle sty then 
809         ptext asmTempLabelPrefix <> pprUnique u
810      else
811         char '_' <> pprUnique u
812
813 pprCLabel (DynamicLinkerLabel info lbl)
814    = pprDynamicLinkerAsmLabel info lbl
815    
816 pprCLabel PicBaseLabel
817    = ptext (sLit "1b")
818    
819 pprCLabel (DeadStripPreventer lbl)
820    = pprCLabel lbl <> ptext (sLit "_dsp")
821 #endif
822
823 pprCLabel lbl = 
824 #if ! OMIT_NATIVE_CODEGEN
825     getPprStyle $ \ sty ->
826     if asmStyle sty then 
827         maybe_underscore (pprAsmCLbl lbl)
828     else
829 #endif
830        pprCLbl lbl
831
832 maybe_underscore doc
833   | underscorePrefix = pp_cSEP <> doc
834   | otherwise        = doc
835
836 #ifdef mingw32_TARGET_OS
837 -- In asm mode, we need to put the suffix on a stdcall ForeignLabel.
838 -- (The C compiler does this itself).
839 pprAsmCLbl (ForeignLabel fs (Just sz) _ _)
840    = ftext fs <> char '@' <> int sz
841 #endif
842 pprAsmCLbl lbl
843    = pprCLbl lbl
844
845 pprCLbl (StringLitLabel u)
846   = pprUnique u <> ptext (sLit "_str")
847
848 pprCLbl (CaseLabel u CaseReturnPt)
849   = hcat [pprUnique u, ptext (sLit "_ret")]
850 pprCLbl (CaseLabel u CaseReturnInfo)
851   = hcat [pprUnique u, ptext (sLit "_info")]
852 pprCLbl (CaseLabel u (CaseAlt tag))
853   = hcat [pprUnique u, pp_cSEP, int tag, ptext (sLit "_alt")]
854 pprCLbl (CaseLabel u CaseDefault)
855   = hcat [pprUnique u, ptext (sLit "_dflt")]
856
857 pprCLbl (LargeSRTLabel u)  = pprUnique u <> pp_cSEP <> ptext (sLit "srtd")
858 pprCLbl (LargeBitmapLabel u)  = text "b" <> pprUnique u <> pp_cSEP <> ptext (sLit "btm")
859 -- Some bitsmaps for tuple constructors have a numeric tag (e.g. '7')
860 -- until that gets resolved we'll just force them to start
861 -- with a letter so the label will be legal assmbly code.
862         
863
864 pprCLbl (CmmLabel _ str CmmCode)        = ftext str
865 pprCLbl (CmmLabel _ str CmmData)        = ftext str
866 pprCLbl (CmmLabel _ str CmmGcPtr)       = ftext str
867
868 pprCLbl (RtsLabel (RtsApFast str))   = ftext str <> ptext (sLit "_fast")
869
870 pprCLbl (RtsLabel (RtsSelectorInfoTable upd_reqd offset))
871   = hcat [ptext (sLit "stg_sel_"), text (show offset),
872                 ptext (if upd_reqd 
873                         then (sLit "_upd_info") 
874                         else (sLit "_noupd_info"))
875         ]
876
877 pprCLbl (RtsLabel (RtsSelectorEntry upd_reqd offset))
878   = hcat [ptext (sLit "stg_sel_"), text (show offset),
879                 ptext (if upd_reqd 
880                         then (sLit "_upd_entry") 
881                         else (sLit "_noupd_entry"))
882         ]
883
884 pprCLbl (RtsLabel (RtsApInfoTable upd_reqd arity))
885   = hcat [ptext (sLit "stg_ap_"), text (show arity),
886                 ptext (if upd_reqd 
887                         then (sLit "_upd_info") 
888                         else (sLit "_noupd_info"))
889         ]
890
891 pprCLbl (RtsLabel (RtsApEntry upd_reqd arity))
892   = hcat [ptext (sLit "stg_ap_"), text (show arity),
893                 ptext (if upd_reqd 
894                         then (sLit "_upd_entry") 
895                         else (sLit "_noupd_entry"))
896         ]
897
898 pprCLbl (CmmLabel _ fs CmmInfo)
899   = ftext fs <> ptext (sLit "_info")
900
901 pprCLbl (CmmLabel _ fs CmmEntry)
902   = ftext fs <> ptext (sLit "_entry")
903
904 pprCLbl (CmmLabel _ fs CmmRetInfo)
905   = ftext fs <> ptext (sLit "_info")
906
907 pprCLbl (CmmLabel _ fs CmmRet)
908   = ftext fs <> ptext (sLit "_ret")
909
910 pprCLbl (RtsLabel (RtsPrimOp primop)) 
911   = ptext (sLit "stg_") <> ppr primop
912
913 pprCLbl (RtsLabel (RtsSlowTickyCtr pat)) 
914   = ptext (sLit "SLOW_CALL_") <> text pat <> ptext (sLit "_ctr")
915
916 pprCLbl ModuleRegdLabel
917   = ptext (sLit "_module_registered")
918
919 pprCLbl (ForeignLabel str _ _ _)
920   = ftext str
921
922 pprCLbl (IdLabel name cafs flavor) = ppr name <> ppIdFlavor flavor
923
924 pprCLbl (CC_Label cc)           = ppr cc
925 pprCLbl (CCS_Label ccs)         = ppr ccs
926
927 pprCLbl (ModuleInitLabel mod way)
928    = ptext (sLit "__stginit_") <> ppr mod
929         <> char '_' <> text way
930
931 pprCLbl (PlainModuleInitLabel mod)
932    = ptext (sLit "__stginit_") <> ppr mod
933
934 pprCLbl (ModuleInitTableLabel mod)
935    = ptext (sLit "__stginittable_") <> ppr mod
936
937 pprCLbl (HpcTicksLabel mod)
938   = ptext (sLit "_hpc_tickboxes_")  <> ppr mod <> ptext (sLit "_hpc")
939
940 pprCLbl HpcModuleNameLabel
941   = ptext (sLit "_hpc_module_name_str")
942
943 ppIdFlavor :: IdLabelInfo -> SDoc
944 ppIdFlavor x = pp_cSEP <>
945                (case x of
946                        Closure          -> ptext (sLit "closure")
947                        SRT              -> ptext (sLit "srt")
948                        InfoTable        -> ptext (sLit "info")
949                        Entry            -> ptext (sLit "entry")
950                        Slow             -> ptext (sLit "slow")
951                        RednCounts       -> ptext (sLit "ct")
952                        ConEntry         -> ptext (sLit "con_entry")
953                        ConInfoTable     -> ptext (sLit "con_info")
954                        StaticConEntry   -> ptext (sLit "static_entry")
955                        StaticInfoTable  -> ptext (sLit "static_info")
956                        ClosureTable     -> ptext (sLit "closure_tbl")
957                       )
958
959
960 pp_cSEP = char '_'
961
962 -- -----------------------------------------------------------------------------
963 -- Machine-dependent knowledge about labels.
964
965 underscorePrefix :: Bool   -- leading underscore on assembler labels?
966 underscorePrefix = (cLeadingUnderscore == "YES")
967
968 asmTempLabelPrefix :: LitString  -- for formatting labels
969 asmTempLabelPrefix =
970 #if alpha_TARGET_OS
971      {- The alpha assembler likes temporary labels to look like $L123
972         instead of L123.  (Don't toss the L, because then Lf28
973         turns into $f28.)
974      -}
975      (sLit "$")
976 #elif darwin_TARGET_OS
977      (sLit "L")
978 #else
979      (sLit ".L")
980 #endif
981
982 pprDynamicLinkerAsmLabel :: DynamicLinkerLabelInfo -> CLabel -> SDoc
983
984 #if x86_64_TARGET_ARCH && darwin_TARGET_OS
985 pprDynamicLinkerAsmLabel CodeStub lbl
986   = char 'L' <> pprCLabel lbl <> text "$stub"
987 pprDynamicLinkerAsmLabel SymbolPtr lbl
988   = char 'L' <> pprCLabel lbl <> text "$non_lazy_ptr"
989 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
990   = pprCLabel lbl <> text "@GOTPCREL"
991 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
992   = pprCLabel lbl
993 pprDynamicLinkerAsmLabel _ _
994   = panic "pprDynamicLinkerAsmLabel"
995
996 #elif darwin_TARGET_OS
997 pprDynamicLinkerAsmLabel CodeStub lbl
998   = char 'L' <> pprCLabel lbl <> text "$stub"
999 pprDynamicLinkerAsmLabel SymbolPtr lbl
1000   = char 'L' <> pprCLabel lbl <> text "$non_lazy_ptr"
1001 pprDynamicLinkerAsmLabel _ _
1002   = panic "pprDynamicLinkerAsmLabel"
1003
1004 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
1005 pprDynamicLinkerAsmLabel CodeStub lbl
1006   = pprCLabel lbl <> text "@plt"
1007 pprDynamicLinkerAsmLabel SymbolPtr lbl
1008   = text ".LC_" <> pprCLabel lbl
1009 pprDynamicLinkerAsmLabel _ _
1010   = panic "pprDynamicLinkerAsmLabel"
1011
1012 #elif x86_64_TARGET_ARCH && linux_TARGET_OS
1013 pprDynamicLinkerAsmLabel CodeStub lbl
1014   = pprCLabel lbl <> text "@plt"
1015 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
1016   = pprCLabel lbl <> text "@gotpcrel"
1017 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
1018   = pprCLabel lbl
1019 pprDynamicLinkerAsmLabel SymbolPtr lbl
1020   = text ".LC_" <> pprCLabel lbl
1021
1022 #elif linux_TARGET_OS
1023 pprDynamicLinkerAsmLabel CodeStub lbl
1024   = pprCLabel lbl <> text "@plt"
1025 pprDynamicLinkerAsmLabel SymbolPtr lbl
1026   = text ".LC_" <> pprCLabel lbl
1027 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
1028   = pprCLabel lbl <> text "@got"
1029 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
1030   = pprCLabel lbl <> text "@gotoff"
1031
1032 #elif mingw32_TARGET_OS
1033 pprDynamicLinkerAsmLabel SymbolPtr lbl
1034   = text "__imp_" <> pprCLabel lbl
1035 pprDynamicLinkerAsmLabel _ _
1036   = panic "pprDynamicLinkerAsmLabel"
1037
1038 #else
1039 pprDynamicLinkerAsmLabel _ _
1040   = panic "pprDynamicLinkerAsmLabel"
1041 #endif