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