* Refactor CLabel.RtsLabel to CLabel.CmmLabel
[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 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 -- 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 l@(ForeignLabel _ _ _ _)     = not (isMathFun l)
534 needsCDecl (CC_Label _)                 = True
535 needsCDecl (CCS_Label _)                = True
536 needsCDecl (HpcTicksLabel _)            = True
537 needsCDecl HpcModuleNameLabel           = False
538
539
540 -- | Check whether a label is a local temporary for native code generation
541 isAsmTemp  :: CLabel -> Bool    
542 isAsmTemp (AsmTempLabel _)              = True
543 isAsmTemp _                             = False
544
545
546 -- | If a label is a local temporary used for native code generation
547 --      then return just its unique, otherwise nothing.
548 maybeAsmTemp :: CLabel -> Maybe Unique
549 maybeAsmTemp (AsmTempLabel uq)          = Just uq
550 maybeAsmTemp _                          = Nothing
551
552
553 -- Check whether a label corresponds to a C function that has 
554 --      a prototype in a system header somehere, or is built-in
555 --      to the C compiler. For these labels we abovoid generating our
556 --      own C prototypes.
557 isMathFun :: CLabel -> Bool
558 isMathFun (ForeignLabel fs _ _ _) = fs `elementOfUniqSet` math_funs
559 isMathFun _ = False
560
561 math_funs = mkUniqSet [
562         -- _ISOC99_SOURCE
563         (fsLit "acos"),         (fsLit "acosf"),        (fsLit "acosh"),
564         (fsLit "acoshf"),       (fsLit "acoshl"),       (fsLit "acosl"),
565         (fsLit "asin"),         (fsLit "asinf"),        (fsLit "asinl"),
566         (fsLit "asinh"),        (fsLit "asinhf"),       (fsLit "asinhl"),
567         (fsLit "atan"),         (fsLit "atanf"),        (fsLit "atanl"),
568         (fsLit "atan2"),        (fsLit "atan2f"),       (fsLit "atan2l"),
569         (fsLit "atanh"),        (fsLit "atanhf"),       (fsLit "atanhl"),
570         (fsLit "cbrt"),         (fsLit "cbrtf"),        (fsLit "cbrtl"),
571         (fsLit "ceil"),         (fsLit "ceilf"),        (fsLit "ceill"),
572         (fsLit "copysign"),     (fsLit "copysignf"),    (fsLit "copysignl"),
573         (fsLit "cos"),          (fsLit "cosf"),         (fsLit "cosl"),
574         (fsLit "cosh"),         (fsLit "coshf"),        (fsLit "coshl"),
575         (fsLit "erf"),          (fsLit "erff"),         (fsLit "erfl"),
576         (fsLit "erfc"),         (fsLit "erfcf"),        (fsLit "erfcl"),
577         (fsLit "exp"),          (fsLit "expf"),         (fsLit "expl"),
578         (fsLit "exp2"),         (fsLit "exp2f"),        (fsLit "exp2l"),
579         (fsLit "expm1"),        (fsLit "expm1f"),       (fsLit "expm1l"),
580         (fsLit "fabs"),         (fsLit "fabsf"),        (fsLit "fabsl"),
581         (fsLit "fdim"),         (fsLit "fdimf"),        (fsLit "fdiml"),
582         (fsLit "floor"),        (fsLit "floorf"),       (fsLit "floorl"),
583         (fsLit "fma"),          (fsLit "fmaf"),         (fsLit "fmal"),
584         (fsLit "fmax"),         (fsLit "fmaxf"),        (fsLit "fmaxl"),
585         (fsLit "fmin"),         (fsLit "fminf"),        (fsLit "fminl"),
586         (fsLit "fmod"),         (fsLit "fmodf"),        (fsLit "fmodl"),
587         (fsLit "frexp"),        (fsLit "frexpf"),       (fsLit "frexpl"),
588         (fsLit "hypot"),        (fsLit "hypotf"),       (fsLit "hypotl"),
589         (fsLit "ilogb"),        (fsLit "ilogbf"),       (fsLit "ilogbl"),
590         (fsLit "ldexp"),        (fsLit "ldexpf"),       (fsLit "ldexpl"),
591         (fsLit "lgamma"),       (fsLit "lgammaf"),      (fsLit "lgammal"),
592         (fsLit "llrint"),       (fsLit "llrintf"),      (fsLit "llrintl"),
593         (fsLit "llround"),      (fsLit "llroundf"),     (fsLit "llroundl"),
594         (fsLit "log"),          (fsLit "logf"),         (fsLit "logl"),
595         (fsLit "log10l"),       (fsLit "log10"),        (fsLit "log10f"),
596         (fsLit "log1pl"),       (fsLit "log1p"),        (fsLit "log1pf"),
597         (fsLit "log2"),         (fsLit "log2f"),        (fsLit "log2l"),
598         (fsLit "logb"),         (fsLit "logbf"),        (fsLit "logbl"),
599         (fsLit "lrint"),        (fsLit "lrintf"),       (fsLit "lrintl"),
600         (fsLit "lround"),       (fsLit "lroundf"),      (fsLit "lroundl"),
601         (fsLit "modf"),         (fsLit "modff"),        (fsLit "modfl"),
602         (fsLit "nan"),          (fsLit "nanf"),         (fsLit "nanl"),
603         (fsLit "nearbyint"),    (fsLit "nearbyintf"),   (fsLit "nearbyintl"),
604         (fsLit "nextafter"),    (fsLit "nextafterf"),   (fsLit "nextafterl"),
605         (fsLit "nexttoward"),   (fsLit "nexttowardf"),  (fsLit "nexttowardl"),
606         (fsLit "pow"),          (fsLit "powf"),         (fsLit "powl"),
607         (fsLit "remainder"),    (fsLit "remainderf"),   (fsLit "remainderl"),
608         (fsLit "remquo"),       (fsLit "remquof"),      (fsLit "remquol"),
609         (fsLit "rint"),         (fsLit "rintf"),        (fsLit "rintl"),
610         (fsLit "round"),        (fsLit "roundf"),       (fsLit "roundl"),
611         (fsLit "scalbln"),      (fsLit "scalblnf"),     (fsLit "scalblnl"),
612         (fsLit "scalbn"),       (fsLit "scalbnf"),      (fsLit "scalbnl"),
613         (fsLit "sin"),          (fsLit "sinf"),         (fsLit "sinl"),
614         (fsLit "sinh"),         (fsLit "sinhf"),        (fsLit "sinhl"),
615         (fsLit "sqrt"),         (fsLit "sqrtf"),        (fsLit "sqrtl"),
616         (fsLit "tan"),          (fsLit "tanf"),         (fsLit "tanl"),
617         (fsLit "tanh"),         (fsLit "tanhf"),        (fsLit "tanhl"),
618         (fsLit "tgamma"),       (fsLit "tgammaf"),      (fsLit "tgammal"),
619         (fsLit "trunc"),        (fsLit "truncf"),       (fsLit "truncl"),
620         -- ISO C 99 also defines these function-like macros in math.h:
621         -- fpclassify, isfinite, isinf, isnormal, signbit, isgreater,
622         -- isgreaterequal, isless, islessequal, islessgreater, isunordered
623
624         -- additional symbols from _BSD_SOURCE
625         (fsLit "drem"),         (fsLit "dremf"),        (fsLit "dreml"),
626         (fsLit "finite"),       (fsLit "finitef"),      (fsLit "finitel"),
627         (fsLit "gamma"),        (fsLit "gammaf"),       (fsLit "gammal"),
628         (fsLit "isinf"),        (fsLit "isinff"),       (fsLit "isinfl"),
629         (fsLit "isnan"),        (fsLit "isnanf"),       (fsLit "isnanl"),
630         (fsLit "j0"),           (fsLit "j0f"),          (fsLit "j0l"),
631         (fsLit "j1"),           (fsLit "j1f"),          (fsLit "j1l"),
632         (fsLit "jn"),           (fsLit "jnf"),          (fsLit "jnl"),
633         (fsLit "lgamma_r"),     (fsLit "lgammaf_r"),    (fsLit "lgammal_r"),
634         (fsLit "scalb"),        (fsLit "scalbf"),       (fsLit "scalbl"),
635         (fsLit "significand"),  (fsLit "significandf"), (fsLit "significandl"),
636         (fsLit "y0"),           (fsLit "y0f"),          (fsLit "y0l"),
637         (fsLit "y1"),           (fsLit "y1f"),          (fsLit "y1l"),
638         (fsLit "yn"),           (fsLit "ynf"),          (fsLit "ynl")
639     ]
640
641 -- -----------------------------------------------------------------------------
642 -- Is a CLabel visible outside this object file or not?
643
644 -- From the point of view of the code generator, a name is
645 -- externally visible if it has to be declared as exported
646 -- in the .o file's symbol table; that is, made non-static.
647
648 externallyVisibleCLabel :: CLabel -> Bool -- not C "static"
649 externallyVisibleCLabel (CaseLabel _ _)         = False
650 externallyVisibleCLabel (StringLitLabel _)      = False
651 externallyVisibleCLabel (AsmTempLabel _)        = False
652 externallyVisibleCLabel (ModuleInitLabel _ _)   = True
653 externallyVisibleCLabel (PlainModuleInitLabel _)= True
654 externallyVisibleCLabel (ModuleInitTableLabel _)= False
655 externallyVisibleCLabel ModuleRegdLabel         = False
656 externallyVisibleCLabel (RtsLabel _)            = True
657 externallyVisibleCLabel (CmmLabel _ _ _)        = True
658 externallyVisibleCLabel (ForeignLabel _ _ _ _)  = True
659 externallyVisibleCLabel (IdLabel name _ _)      = isExternalName name
660 externallyVisibleCLabel (CC_Label _)            = True
661 externallyVisibleCLabel (CCS_Label _)           = True
662 externallyVisibleCLabel (DynamicLinkerLabel _ _)  = False
663 externallyVisibleCLabel (HpcTicksLabel _)       = True
664 externallyVisibleCLabel HpcModuleNameLabel      = False
665 externallyVisibleCLabel (LargeBitmapLabel _)    = False
666 externallyVisibleCLabel (LargeSRTLabel _)       = False
667
668 -- -----------------------------------------------------------------------------
669 -- Finding the "type" of a CLabel 
670
671 -- For generating correct types in label declarations:
672
673 data CLabelType
674   = CodeLabel   -- Address of some executable instructions
675   | DataLabel   -- Address of data, not a GC ptr
676   | GcPtrLabel  -- Address of a (presumably static) GC object
677
678 isCFunctionLabel :: CLabel -> Bool
679 isCFunctionLabel lbl = case labelType lbl of
680                         CodeLabel -> True
681                         _other    -> False
682
683 isGcPtrLabel :: CLabel -> Bool
684 isGcPtrLabel lbl = case labelType lbl of
685                         GcPtrLabel -> True
686                         _other     -> False
687
688
689 -- | Work out the general type of data at the address of this label
690 --    whether it be code, data, or static GC object.
691 labelType :: CLabel -> CLabelType
692 labelType (CmmLabel _ _ CmmData)                = DataLabel
693 labelType (CmmLabel _ _ CmmGcPtr)               = GcPtrLabel
694 labelType (CmmLabel _ _ CmmCode)                = CodeLabel
695 labelType (CmmLabel _ _ CmmInfo)                = DataLabel
696 labelType (CmmLabel _ _ CmmEntry)               = CodeLabel
697 labelType (CmmLabel _ _ CmmRetInfo)             = DataLabel
698 labelType (CmmLabel _ _ CmmRet)                 = CodeLabel
699 labelType (RtsLabel (RtsSelectorInfoTable _ _)) = DataLabel
700 labelType (RtsLabel (RtsApInfoTable _ _))       = DataLabel
701 labelType (RtsLabel (RtsApFast _))              = CodeLabel
702 labelType (CaseLabel _ CaseReturnInfo)          = DataLabel
703 labelType (CaseLabel _ _)                       = CodeLabel
704 labelType (ModuleInitLabel _ _)                 = CodeLabel
705 labelType (PlainModuleInitLabel _)              = CodeLabel
706 labelType (ModuleInitTableLabel _)              = DataLabel
707 labelType (LargeSRTLabel _)                     = DataLabel
708 labelType (LargeBitmapLabel _)                  = DataLabel
709 labelType (ForeignLabel _ _ _ IsFunction)       = CodeLabel
710 labelType (IdLabel _ _ info)                    = idInfoLabelType info
711 labelType _                                     = DataLabel
712
713 idInfoLabelType info =
714   case info of
715     InfoTable     -> DataLabel
716     Closure       -> GcPtrLabel
717     ConInfoTable  -> DataLabel
718     StaticInfoTable -> DataLabel
719     ClosureTable  -> DataLabel
720     RednCounts    -> DataLabel
721     _             -> CodeLabel
722
723
724 -- -----------------------------------------------------------------------------
725 -- Does a CLabel need dynamic linkage?
726
727 -- When referring to data in code, we need to know whether
728 -- that data resides in a DLL or not. [Win32 only.]
729 -- @labelDynamic@ returns @True@ if the label is located
730 -- in a DLL, be it a data reference or not.
731
732 labelDynamic :: PackageId -> CLabel -> Bool
733 labelDynamic this_pkg lbl =
734   case lbl of
735    RtsLabel _           -> not opt_Static && (this_pkg /= rtsPackageId) -- i.e., is the RTS in a DLL or not?
736    CmmLabel pkg _ _     -> not opt_Static && (this_pkg /= pkg)
737    IdLabel n _ k        -> isDllName this_pkg n
738 #if mingw32_TARGET_OS
739    ForeignLabel _ _ d _ -> d
740 #else
741    -- On Mac OS X and on ELF platforms, false positives are OK,
742    -- so we claim that all foreign imports come from dynamic libraries
743    ForeignLabel _ _ _ _ -> True
744 #endif
745    ModuleInitLabel m _    -> not opt_Static && this_pkg /= (modulePackageId m)
746    PlainModuleInitLabel m -> not opt_Static && this_pkg /= (modulePackageId m)
747    ModuleInitTableLabel m -> not opt_Static && this_pkg /= (modulePackageId m)
748    
749    -- Note that DynamicLinkerLabels do NOT require dynamic linking themselves.
750    _                 -> False
751
752 {-
753 OLD?: These GRAN functions are needed for spitting out GRAN_FETCH() at the
754 right places. It is used to detect when the abstractC statement of an
755 CCodeBlock actually contains the code for a slow entry point.  -- HWL
756
757 We need at least @Eq@ for @CLabels@, because we want to avoid
758 duplicate declarations in generating C (see @labelSeenTE@ in
759 @PprAbsC@).
760 -}
761
762 -----------------------------------------------------------------------------
763 -- Printing out CLabels.
764
765 {-
766 Convention:
767
768       <name>_<type>
769
770 where <name> is <Module>_<name> for external names and <unique> for
771 internal names. <type> is one of the following:
772
773          info                   Info table
774          srt                    Static reference table
775          srtd                   Static reference table descriptor
776          entry                  Entry code (function, closure)
777          slow                   Slow entry code (if any)
778          ret                    Direct return address    
779          vtbl                   Vector table
780          <n>_alt                Case alternative (tag n)
781          dflt                   Default case alternative
782          btm                    Large bitmap vector
783          closure                Static closure
784          con_entry              Dynamic Constructor entry code
785          con_info               Dynamic Constructor info table
786          static_entry           Static Constructor entry code
787          static_info            Static Constructor info table
788          sel_info               Selector info table
789          sel_entry              Selector entry code
790          cc                     Cost centre
791          ccs                    Cost centre stack
792
793 Many of these distinctions are only for documentation reasons.  For
794 example, _ret is only distinguished from _entry to make it easy to
795 tell whether a code fragment is a return point or a closure/function
796 entry.
797 -}
798
799 instance Outputable CLabel where
800   ppr = pprCLabel
801
802 pprCLabel :: CLabel -> SDoc
803
804 #if ! OMIT_NATIVE_CODEGEN
805 pprCLabel (AsmTempLabel u)
806   =  getPprStyle $ \ sty ->
807      if asmStyle sty then 
808         ptext asmTempLabelPrefix <> pprUnique u
809      else
810         char '_' <> pprUnique u
811
812 pprCLabel (DynamicLinkerLabel info lbl)
813    = pprDynamicLinkerAsmLabel info lbl
814    
815 pprCLabel PicBaseLabel
816    = ptext (sLit "1b")
817    
818 pprCLabel (DeadStripPreventer lbl)
819    = pprCLabel lbl <> ptext (sLit "_dsp")
820 #endif
821
822 pprCLabel lbl = 
823 #if ! OMIT_NATIVE_CODEGEN
824     getPprStyle $ \ sty ->
825     if asmStyle sty then 
826         maybe_underscore (pprAsmCLbl lbl)
827     else
828 #endif
829        pprCLbl lbl
830
831 maybe_underscore doc
832   | underscorePrefix = pp_cSEP <> doc
833   | otherwise        = doc
834
835 #ifdef mingw32_TARGET_OS
836 -- In asm mode, we need to put the suffix on a stdcall ForeignLabel.
837 -- (The C compiler does this itself).
838 pprAsmCLbl (ForeignLabel fs (Just sz) _ _)
839    = ftext fs <> char '@' <> int sz
840 #endif
841 pprAsmCLbl lbl
842    = pprCLbl lbl
843
844 pprCLbl (StringLitLabel u)
845   = pprUnique u <> ptext (sLit "_str")
846
847 pprCLbl (CaseLabel u CaseReturnPt)
848   = hcat [pprUnique u, ptext (sLit "_ret")]
849 pprCLbl (CaseLabel u CaseReturnInfo)
850   = hcat [pprUnique u, ptext (sLit "_info")]
851 pprCLbl (CaseLabel u (CaseAlt tag))
852   = hcat [pprUnique u, pp_cSEP, int tag, ptext (sLit "_alt")]
853 pprCLbl (CaseLabel u CaseDefault)
854   = hcat [pprUnique u, ptext (sLit "_dflt")]
855
856 pprCLbl (LargeSRTLabel u)  = pprUnique u <> pp_cSEP <> ptext (sLit "srtd")
857 pprCLbl (LargeBitmapLabel u)  = text "b" <> pprUnique u <> pp_cSEP <> ptext (sLit "btm")
858 -- Some bitsmaps for tuple constructors have a numeric tag (e.g. '7')
859 -- until that gets resolved we'll just force them to start
860 -- with a letter so the label will be legal assmbly code.
861         
862
863 pprCLbl (CmmLabel _ str CmmCode)        = ftext str
864 pprCLbl (CmmLabel _ str CmmData)        = ftext str
865 pprCLbl (CmmLabel _ str CmmGcPtr)       = ftext str
866
867 pprCLbl (RtsLabel (RtsApFast str))   = ftext str <> ptext (sLit "_fast")
868
869 pprCLbl (RtsLabel (RtsSelectorInfoTable upd_reqd offset))
870   = hcat [ptext (sLit "stg_sel_"), text (show offset),
871                 ptext (if upd_reqd 
872                         then (sLit "_upd_info") 
873                         else (sLit "_noupd_info"))
874         ]
875
876 pprCLbl (RtsLabel (RtsSelectorEntry upd_reqd offset))
877   = hcat [ptext (sLit "stg_sel_"), text (show offset),
878                 ptext (if upd_reqd 
879                         then (sLit "_upd_entry") 
880                         else (sLit "_noupd_entry"))
881         ]
882
883 pprCLbl (RtsLabel (RtsApInfoTable upd_reqd arity))
884   = hcat [ptext (sLit "stg_ap_"), text (show arity),
885                 ptext (if upd_reqd 
886                         then (sLit "_upd_info") 
887                         else (sLit "_noupd_info"))
888         ]
889
890 pprCLbl (RtsLabel (RtsApEntry upd_reqd arity))
891   = hcat [ptext (sLit "stg_ap_"), text (show arity),
892                 ptext (if upd_reqd 
893                         then (sLit "_upd_entry") 
894                         else (sLit "_noupd_entry"))
895         ]
896
897 pprCLbl (CmmLabel _ fs CmmInfo)
898   = ftext fs <> ptext (sLit "_info")
899
900 pprCLbl (CmmLabel _ fs CmmEntry)
901   = ftext fs <> ptext (sLit "_entry")
902
903 pprCLbl (CmmLabel _ fs CmmRetInfo)
904   = ftext fs <> ptext (sLit "_info")
905
906 pprCLbl (CmmLabel _ fs CmmRet)
907   = ftext fs <> ptext (sLit "_ret")
908
909 pprCLbl (RtsLabel (RtsPrimOp primop)) 
910   = ptext (sLit "stg_") <> ppr primop
911
912 pprCLbl (RtsLabel (RtsSlowTickyCtr pat)) 
913   = ptext (sLit "SLOW_CALL_") <> text pat <> ptext (sLit "_ctr")
914
915 pprCLbl ModuleRegdLabel
916   = ptext (sLit "_module_registered")
917
918 pprCLbl (ForeignLabel str _ _ _)
919   = ftext str
920
921 pprCLbl (IdLabel name cafs flavor) = ppr name <> ppIdFlavor flavor
922
923 pprCLbl (CC_Label cc)           = ppr cc
924 pprCLbl (CCS_Label ccs)         = ppr ccs
925
926 pprCLbl (ModuleInitLabel mod way)
927    = ptext (sLit "__stginit_") <> ppr mod
928         <> char '_' <> text way
929
930 pprCLbl (PlainModuleInitLabel mod)
931    = ptext (sLit "__stginit_") <> ppr mod
932
933 pprCLbl (ModuleInitTableLabel mod)
934    = ptext (sLit "__stginittable_") <> ppr mod
935
936 pprCLbl (HpcTicksLabel mod)
937   = ptext (sLit "_hpc_tickboxes_")  <> ppr mod <> ptext (sLit "_hpc")
938
939 pprCLbl HpcModuleNameLabel
940   = ptext (sLit "_hpc_module_name_str")
941
942 ppIdFlavor :: IdLabelInfo -> SDoc
943 ppIdFlavor x = pp_cSEP <>
944                (case x of
945                        Closure          -> ptext (sLit "closure")
946                        SRT              -> ptext (sLit "srt")
947                        InfoTable        -> ptext (sLit "info")
948                        Entry            -> ptext (sLit "entry")
949                        Slow             -> ptext (sLit "slow")
950                        RednCounts       -> ptext (sLit "ct")
951                        ConEntry         -> ptext (sLit "con_entry")
952                        ConInfoTable     -> ptext (sLit "con_info")
953                        StaticConEntry   -> ptext (sLit "static_entry")
954                        StaticInfoTable  -> ptext (sLit "static_info")
955                        ClosureTable     -> ptext (sLit "closure_tbl")
956                       )
957
958
959 pp_cSEP = char '_'
960
961 -- -----------------------------------------------------------------------------
962 -- Machine-dependent knowledge about labels.
963
964 underscorePrefix :: Bool   -- leading underscore on assembler labels?
965 underscorePrefix = (cLeadingUnderscore == "YES")
966
967 asmTempLabelPrefix :: LitString  -- for formatting labels
968 asmTempLabelPrefix =
969 #if alpha_TARGET_OS
970      {- The alpha assembler likes temporary labels to look like $L123
971         instead of L123.  (Don't toss the L, because then Lf28
972         turns into $f28.)
973      -}
974      (sLit "$")
975 #elif darwin_TARGET_OS
976      (sLit "L")
977 #else
978      (sLit ".L")
979 #endif
980
981 pprDynamicLinkerAsmLabel :: DynamicLinkerLabelInfo -> CLabel -> SDoc
982
983 #if x86_64_TARGET_ARCH && darwin_TARGET_OS
984 pprDynamicLinkerAsmLabel CodeStub lbl
985   = char 'L' <> pprCLabel lbl <> text "$stub"
986 pprDynamicLinkerAsmLabel SymbolPtr lbl
987   = char 'L' <> pprCLabel lbl <> text "$non_lazy_ptr"
988 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
989   = pprCLabel lbl <> text "@GOTPCREL"
990 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
991   = pprCLabel lbl
992 pprDynamicLinkerAsmLabel _ _
993   = panic "pprDynamicLinkerAsmLabel"
994
995 #elif darwin_TARGET_OS
996 pprDynamicLinkerAsmLabel CodeStub lbl
997   = char 'L' <> pprCLabel lbl <> text "$stub"
998 pprDynamicLinkerAsmLabel SymbolPtr lbl
999   = char 'L' <> pprCLabel lbl <> text "$non_lazy_ptr"
1000 pprDynamicLinkerAsmLabel _ _
1001   = panic "pprDynamicLinkerAsmLabel"
1002
1003 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
1004 pprDynamicLinkerAsmLabel CodeStub lbl
1005   = pprCLabel lbl <> text "@plt"
1006 pprDynamicLinkerAsmLabel SymbolPtr lbl
1007   = text ".LC_" <> pprCLabel lbl
1008 pprDynamicLinkerAsmLabel _ _
1009   = panic "pprDynamicLinkerAsmLabel"
1010
1011 #elif x86_64_TARGET_ARCH && linux_TARGET_OS
1012 pprDynamicLinkerAsmLabel CodeStub lbl
1013   = pprCLabel lbl <> text "@plt"
1014 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
1015   = pprCLabel lbl <> text "@gotpcrel"
1016 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
1017   = pprCLabel lbl
1018 pprDynamicLinkerAsmLabel SymbolPtr lbl
1019   = text ".LC_" <> pprCLabel lbl
1020
1021 #elif linux_TARGET_OS
1022 pprDynamicLinkerAsmLabel CodeStub lbl
1023   = pprCLabel lbl <> text "@plt"
1024 pprDynamicLinkerAsmLabel SymbolPtr lbl
1025   = text ".LC_" <> pprCLabel lbl
1026 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
1027   = pprCLabel lbl <> text "@got"
1028 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
1029   = pprCLabel lbl <> text "@gotoff"
1030
1031 #elif mingw32_TARGET_OS
1032 pprDynamicLinkerAsmLabel SymbolPtr lbl
1033   = text "__imp_" <> pprCLabel lbl
1034 pprDynamicLinkerAsmLabel _ _
1035   = panic "pprDynamicLinkerAsmLabel"
1036
1037 #else
1038 pprDynamicLinkerAsmLabel _ _
1039   = panic "pprDynamicLinkerAsmLabel"
1040 #endif