Adding tracing support
[ghc-hetmet.git] / compiler / cmm / CLabel.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Object-file symbols (called CLabel for histerical raisins).
4 --
5 -- (c) The University of Glasgow 2004-2006
6 --
7 -----------------------------------------------------------------------------
8
9 module CLabel (
10         CLabel, -- abstract type
11
12         mkClosureLabel,
13         mkSRTLabel,
14         mkSRTDescLabel,
15         mkInfoTableLabel,
16         mkEntryLabel,
17         mkSlowEntryLabel,
18         mkConEntryLabel,
19         mkStaticConEntryLabel,
20         mkRednCountsLabel,
21         mkConInfoTableLabel,
22         mkStaticInfoTableLabel,
23         mkApEntryLabel,
24         mkApInfoTableLabel,
25         mkClosureTableLabel,
26
27         mkLocalClosureLabel,
28         mkLocalInfoTableLabel,
29         mkLocalEntryLabel,
30         mkLocalConEntryLabel,
31         mkLocalStaticConEntryLabel,
32         mkLocalConInfoTableLabel,
33         mkLocalStaticInfoTableLabel,
34         mkLocalClosureTableLabel,
35
36         mkReturnPtLabel,
37         mkReturnInfoLabel,
38         mkAltLabel,
39         mkDefaultLabel,
40         mkBitmapLabel,
41         mkStringLitLabel,
42
43         mkAsmTempLabel,
44
45         mkModuleInitLabel,
46         mkPlainModuleInitLabel,
47
48         mkSplitMarkerLabel,
49         mkDirty_MUT_VAR_Label,
50         mkUpdInfoLabel,
51         mkSeqInfoLabel,
52         mkIndStaticInfoLabel,
53         mkMainCapabilityLabel,
54         mkMAP_FROZEN_infoLabel,
55         mkMAP_DIRTY_infoLabel,
56         mkEMPTY_MVAR_infoLabel,
57
58         mkTopTickyCtrLabel,
59         mkCAFBlackHoleInfoTableLabel,
60         mkSECAFBlackHoleInfoTableLabel,
61         mkRtsPrimOpLabel,
62         mkRtsSlowTickyCtrLabel,
63
64         moduleRegdLabel,
65
66         mkSelectorInfoLabel,
67         mkSelectorEntryLabel,
68
69         mkRtsInfoLabel,
70         mkRtsEntryLabel,
71         mkRtsRetInfoLabel,
72         mkRtsRetLabel,
73         mkRtsCodeLabel,
74         mkRtsDataLabel,
75
76         mkRtsInfoLabelFS,
77         mkRtsEntryLabelFS,
78         mkRtsRetInfoLabelFS,
79         mkRtsRetLabelFS,
80         mkRtsCodeLabelFS,
81         mkRtsDataLabelFS,
82
83         mkRtsApFastLabel,
84
85         mkForeignLabel,
86
87         mkCCLabel, mkCCSLabel,
88
89         DynamicLinkerLabelInfo(..),
90         mkDynamicLinkerLabel,
91         dynamicLinkerLabelInfo,
92         
93         mkPicBaseLabel,
94         mkDeadStripPreventer,
95
96         mkHpcTicksLabel,
97         mkHpcModuleNameLabel,
98         mkHpcModuleOffsetLabel,
99
100         infoLblToEntryLbl, entryLblToInfoLbl,
101         needsCDecl, isAsmTemp, externallyVisibleCLabel,
102         CLabelType(..), labelType, labelDynamic,
103
104         pprCLabel
105     ) where
106
107
108 #include "HsVersions.h"
109
110 import StaticFlags
111 import Packages
112 import DataCon
113 import PackageConfig
114 import Module
115 import Name
116 import Unique
117 import PrimOp
118 import Config
119 import CostCentre
120 import Outputable
121 import FastString
122
123 -- -----------------------------------------------------------------------------
124 -- The CLabel type
125
126 {-
127 CLabel is an abstract type that supports the following operations:
128
129   - Pretty printing
130
131   - In a C file, does it need to be declared before use?  (i.e. is it
132     guaranteed to be already in scope in the places we need to refer to it?)
133
134   - If it needs to be declared, what type (code or data) should it be
135     declared to have?
136
137   - Is it visible outside this object file or not?
138
139   - Is it "dynamic" (see details below)
140
141   - Eq and Ord, so that we can make sets of CLabels (currently only
142     used in outputting C as far as I can tell, to avoid generating
143     more than one declaration for any given label).
144
145   - Converting an info table label into an entry label.
146 -}
147
148 data CLabel
149   = IdLabel                     -- A family of labels related to the
150         Name                    -- definition of a particular Id or Con
151         IdLabelInfo
152
153   | DynIdLabel                  -- like IdLabel, but in a separate package,
154         Name                    -- and might therefore need a dynamic
155         IdLabelInfo             -- reference.
156
157   | CaseLabel                   -- A family of labels related to a particular
158                                 -- case expression.
159         {-# UNPACK #-} !Unique  -- Unique says which case expression
160         CaseLabelInfo
161
162   | AsmTempLabel 
163         {-# UNPACK #-} !Unique
164
165   | StringLitLabel
166         {-# UNPACK #-} !Unique
167
168   | ModuleInitLabel 
169         Module                  -- the module name
170         String                  -- its "way"
171         Bool                    -- True <=> is in a different package
172         -- at some point we might want some kind of version number in
173         -- the module init label, to guard against compiling modules in
174         -- the wrong order.  We can't use the interface file version however,
175         -- because we don't always recompile modules which depend on a module
176         -- whose version has changed.
177
178   | PlainModuleInitLabel        -- without the vesrion & way info
179         Module
180         Bool                    -- True <=> is in a different package
181
182   | ModuleRegdLabel
183
184   | RtsLabel RtsLabelInfo
185
186   | ForeignLabel FastString     -- a 'C' (or otherwise foreign) label
187         (Maybe Int)             -- possible '@n' suffix for stdcall functions
188                 -- When generating C, the '@n' suffix is omitted, but when
189                 -- generating assembler we must add it to the label.
190         Bool                    -- True <=> is dynamic
191
192   | CC_Label  CostCentre
193   | CCS_Label CostCentreStack
194
195       -- Dynamic Linking in the NCG:
196       -- generated and used inside the NCG only,
197       -- see module PositionIndependentCode for details.
198       
199   | DynamicLinkerLabel DynamicLinkerLabelInfo CLabel
200         -- special variants of a label used for dynamic linking
201
202   | PicBaseLabel                -- a label used as a base for PIC calculations
203                                 -- on some platforms.
204                                 -- It takes the form of a local numeric
205                                 -- assembler label '1'; it is pretty-printed
206                                 -- as 1b, referring to the previous definition
207                                 -- of 1: in the assembler source file.
208
209   | DeadStripPreventer CLabel
210     -- label before an info table to prevent excessive dead-stripping on darwin
211
212   | HpcTicksLabel Module       -- Per-module table of tick locations
213   | HpcModuleNameLabel         -- Per-module name of the module for Hpc
214   | HpcModuleOffsetLabel Module-- Per-module offset of the module for Hpc (dynamically generated)
215
216   deriving (Eq, Ord)
217
218 data IdLabelInfo
219   = Closure             -- Label for closure
220   | SRT                 -- Static reference table
221   | SRTDesc             -- Static reference table descriptor
222   | InfoTable           -- Info tables for closures; always read-only
223   | Entry               -- entry point
224   | Slow                -- slow entry point
225
226   | RednCounts          -- Label of place to keep Ticky-ticky  info for 
227                         -- this Id
228
229   | Bitmap              -- A bitmap (function or case return)
230
231   | ConEntry            -- constructor entry point
232   | ConInfoTable                -- corresponding info table
233   | StaticConEntry      -- static constructor entry point
234   | StaticInfoTable     -- corresponding info table
235
236   | ClosureTable        -- table of closures for Enum tycons
237
238   deriving (Eq, Ord)
239
240
241 data CaseLabelInfo
242   = CaseReturnPt
243   | CaseReturnInfo
244   | CaseAlt ConTag
245   | CaseDefault
246   deriving (Eq, Ord)
247
248
249 data RtsLabelInfo
250   = RtsSelectorInfoTable Bool{-updatable-} Int{-offset-}        -- Selector thunks
251   | RtsSelectorEntry   Bool{-updatable-} Int{-offset-}
252
253   | RtsApInfoTable Bool{-updatable-} Int{-arity-}               -- AP thunks
254   | RtsApEntry   Bool{-updatable-} Int{-arity-}
255
256   | RtsPrimOp PrimOp
257
258   | RtsInfo       LitString     -- misc rts info tables
259   | RtsEntry      LitString     -- misc rts entry points
260   | RtsRetInfo    LitString     -- misc rts ret info tables
261   | RtsRet        LitString     -- misc rts return points
262   | RtsData       LitString     -- misc rts data bits, eg CHARLIKE_closure
263   | RtsCode       LitString     -- misc rts code
264
265   | RtsInfoFS     FastString    -- misc rts info tables
266   | RtsEntryFS    FastString    -- misc rts entry points
267   | RtsRetInfoFS  FastString    -- misc rts ret info tables
268   | RtsRetFS      FastString    -- misc rts return points
269   | RtsDataFS     FastString    -- misc rts data bits, eg CHARLIKE_closure
270   | RtsCodeFS     FastString    -- misc rts code
271
272   | RtsApFast   LitString       -- _fast versions of generic apply
273
274   | RtsSlowTickyCtr String
275
276   deriving (Eq, Ord)
277         -- NOTE: Eq on LitString compares the pointer only, so this isn't
278         -- a real equality.
279
280 data DynamicLinkerLabelInfo
281   = CodeStub            -- MachO: Lfoo$stub, ELF: foo@plt
282   | SymbolPtr           -- MachO: Lfoo$non_lazy_ptr, Windows: __imp_foo
283   | GotSymbolPtr        -- ELF: foo@got
284   | GotSymbolOffset     -- ELF: foo@gotoff
285   
286   deriving (Eq, Ord)
287   
288 -- -----------------------------------------------------------------------------
289 -- Constructing CLabels
290
291 -- These are always local:
292 mkSRTLabel              name    = IdLabel name  SRT
293 mkSRTDescLabel          name    = IdLabel name  SRTDesc
294 mkSlowEntryLabel        name    = IdLabel name  Slow
295 mkBitmapLabel           name    = IdLabel name  Bitmap
296 mkRednCountsLabel       name    = IdLabel name  RednCounts
297
298 -- These have local & (possibly) external variants:
299 mkLocalClosureLabel     name    = IdLabel name  Closure
300 mkLocalInfoTableLabel   name    = IdLabel name  InfoTable
301 mkLocalEntryLabel       name    = IdLabel name  Entry
302 mkLocalClosureTableLabel name   = IdLabel name ClosureTable
303
304 mkClosureLabel this_pkg name
305   | isDllName this_pkg name = DynIdLabel    name Closure
306   | otherwise             = IdLabel name Closure
307
308 mkInfoTableLabel this_pkg name
309   | isDllName this_pkg name = DynIdLabel    name InfoTable
310   | otherwise            = IdLabel name InfoTable
311
312 mkEntryLabel this_pkg name
313   | isDllName this_pkg name = DynIdLabel    name Entry
314   | otherwise             = IdLabel name Entry
315
316 mkClosureTableLabel this_pkg name
317   | isDllName this_pkg name = DynIdLabel    name ClosureTable
318   | otherwise             = IdLabel name ClosureTable
319
320 mkLocalConInfoTableLabel     con = IdLabel con ConInfoTable
321 mkLocalConEntryLabel         con = IdLabel con ConEntry
322 mkLocalStaticInfoTableLabel  con = IdLabel con StaticInfoTable
323 mkLocalStaticConEntryLabel   con = IdLabel con StaticConEntry
324
325 mkConInfoTableLabel name False = IdLabel    name ConInfoTable
326 mkConInfoTableLabel name True  = DynIdLabel name ConInfoTable
327
328 mkStaticInfoTableLabel name False = IdLabel    name StaticInfoTable
329 mkStaticInfoTableLabel name True  = DynIdLabel name StaticInfoTable
330
331 mkConEntryLabel this_pkg name
332   | isDllName this_pkg name = DynIdLabel    name ConEntry
333   | otherwise             = IdLabel name ConEntry
334
335 mkStaticConEntryLabel this_pkg name
336   | isDllName this_pkg name = DynIdLabel    name StaticConEntry
337   | otherwise             = IdLabel name StaticConEntry
338
339
340 mkReturnPtLabel uniq            = CaseLabel uniq CaseReturnPt
341 mkReturnInfoLabel uniq          = CaseLabel uniq CaseReturnInfo
342 mkAltLabel      uniq tag        = CaseLabel uniq (CaseAlt tag)
343 mkDefaultLabel  uniq            = CaseLabel uniq CaseDefault
344
345 mkStringLitLabel                = StringLitLabel
346 mkAsmTempLabel                  = AsmTempLabel
347
348 mkModuleInitLabel :: PackageId -> Module -> String -> CLabel
349 mkModuleInitLabel this_pkg mod way
350   = ModuleInitLabel mod way $! modulePackageId mod /= this_pkg
351
352 mkPlainModuleInitLabel :: PackageId -> Module -> CLabel
353 mkPlainModuleInitLabel this_pkg mod
354   = PlainModuleInitLabel mod $! modulePackageId mod /= this_pkg
355
356         -- Some fixed runtime system labels
357
358 mkSplitMarkerLabel              = RtsLabel (RtsCode SLIT("__stg_split_marker"))
359 mkDirty_MUT_VAR_Label           = RtsLabel (RtsCode SLIT("dirty_MUT_VAR"))
360 mkUpdInfoLabel                  = RtsLabel (RtsInfo SLIT("stg_upd_frame"))
361 mkSeqInfoLabel                  = RtsLabel (RtsInfo SLIT("stg_seq_frame"))
362 mkIndStaticInfoLabel            = RtsLabel (RtsInfo SLIT("stg_IND_STATIC"))
363 mkMainCapabilityLabel           = RtsLabel (RtsData SLIT("MainCapability"))
364 mkMAP_FROZEN_infoLabel          = RtsLabel (RtsInfo SLIT("stg_MUT_ARR_PTRS_FROZEN0"))
365 mkMAP_DIRTY_infoLabel           = RtsLabel (RtsInfo SLIT("stg_MUT_ARR_PTRS_DIRTY"))
366 mkEMPTY_MVAR_infoLabel          = RtsLabel (RtsInfo SLIT("stg_EMPTY_MVAR"))
367
368 mkTopTickyCtrLabel              = RtsLabel (RtsData SLIT("top_ct"))
369 mkCAFBlackHoleInfoTableLabel    = RtsLabel (RtsInfo SLIT("stg_CAF_BLACKHOLE"))
370 mkSECAFBlackHoleInfoTableLabel  = if opt_DoTickyProfiling then
371                                     RtsLabel (RtsInfo SLIT("stg_SE_CAF_BLACKHOLE"))
372                                   else  -- RTS won't have info table unless -ticky is on
373                                     panic "mkSECAFBlackHoleInfoTableLabel requires -ticky"
374 mkRtsPrimOpLabel primop         = RtsLabel (RtsPrimOp primop)
375
376 moduleRegdLabel                 = ModuleRegdLabel
377
378 mkSelectorInfoLabel  upd off    = RtsLabel (RtsSelectorInfoTable upd off)
379 mkSelectorEntryLabel upd off    = RtsLabel (RtsSelectorEntry   upd off)
380
381 mkApInfoTableLabel  upd off     = RtsLabel (RtsApInfoTable upd off)
382 mkApEntryLabel upd off          = RtsLabel (RtsApEntry   upd off)
383
384         -- Foreign labels
385
386 mkForeignLabel :: FastString -> Maybe Int -> Bool -> CLabel
387 mkForeignLabel str mb_sz  is_dynamic = ForeignLabel str mb_sz is_dynamic
388
389         -- Cost centres etc.
390
391 mkCCLabel       cc              = CC_Label cc
392 mkCCSLabel      ccs             = CCS_Label ccs
393
394 mkRtsInfoLabel      str = RtsLabel (RtsInfo      str)
395 mkRtsEntryLabel     str = RtsLabel (RtsEntry     str)
396 mkRtsRetInfoLabel   str = RtsLabel (RtsRetInfo   str)
397 mkRtsRetLabel       str = RtsLabel (RtsRet       str)
398 mkRtsCodeLabel      str = RtsLabel (RtsCode      str)
399 mkRtsDataLabel      str = RtsLabel (RtsData      str)
400
401 mkRtsInfoLabelFS    str = RtsLabel (RtsInfoFS    str)
402 mkRtsEntryLabelFS   str = RtsLabel (RtsEntryFS   str)
403 mkRtsRetInfoLabelFS str = RtsLabel (RtsRetInfoFS str)
404 mkRtsRetLabelFS     str = RtsLabel (RtsRetFS     str)
405 mkRtsCodeLabelFS    str = RtsLabel (RtsCodeFS    str)
406 mkRtsDataLabelFS    str = RtsLabel (RtsDataFS    str)
407
408 mkRtsApFastLabel str = RtsLabel (RtsApFast str)
409
410 mkRtsSlowTickyCtrLabel :: String -> CLabel
411 mkRtsSlowTickyCtrLabel pat = RtsLabel (RtsSlowTickyCtr pat)
412
413         -- Coverage
414
415 mkHpcTicksLabel                = HpcTicksLabel
416 mkHpcModuleNameLabel           = HpcModuleNameLabel
417 mkHpcModuleOffsetLabel         = HpcModuleOffsetLabel
418
419         -- Dynamic linking
420         
421 mkDynamicLinkerLabel :: DynamicLinkerLabelInfo -> CLabel -> CLabel
422 mkDynamicLinkerLabel = DynamicLinkerLabel
423
424 dynamicLinkerLabelInfo :: CLabel -> Maybe (DynamicLinkerLabelInfo, CLabel)
425 dynamicLinkerLabelInfo (DynamicLinkerLabel info lbl) = Just (info, lbl)
426 dynamicLinkerLabelInfo _ = Nothing
427
428         -- Position independent code
429         
430 mkPicBaseLabel :: CLabel
431 mkPicBaseLabel = PicBaseLabel
432
433 mkDeadStripPreventer :: CLabel -> CLabel
434 mkDeadStripPreventer lbl = DeadStripPreventer lbl
435
436 -- -----------------------------------------------------------------------------
437 -- Converting info labels to entry labels.
438
439 infoLblToEntryLbl :: CLabel -> CLabel 
440 infoLblToEntryLbl (IdLabel n InfoTable) = IdLabel n Entry
441 infoLblToEntryLbl (IdLabel n ConInfoTable) = IdLabel n ConEntry
442 infoLblToEntryLbl (IdLabel n StaticInfoTable) = IdLabel n StaticConEntry
443 infoLblToEntryLbl (DynIdLabel n InfoTable) = DynIdLabel n Entry
444 infoLblToEntryLbl (DynIdLabel n ConInfoTable) = DynIdLabel n ConEntry
445 infoLblToEntryLbl (DynIdLabel n StaticInfoTable) = DynIdLabel n StaticConEntry
446 infoLblToEntryLbl (CaseLabel n CaseReturnInfo) = CaseLabel n CaseReturnPt
447 infoLblToEntryLbl (RtsLabel (RtsInfo s)) = RtsLabel (RtsEntry s)
448 infoLblToEntryLbl (RtsLabel (RtsRetInfo s)) = RtsLabel (RtsRet s)
449 infoLblToEntryLbl (RtsLabel (RtsInfoFS s)) = RtsLabel (RtsEntryFS s)
450 infoLblToEntryLbl (RtsLabel (RtsRetInfoFS s)) = RtsLabel (RtsRetFS s)
451 infoLblToEntryLbl _ = panic "CLabel.infoLblToEntryLbl"
452
453 entryLblToInfoLbl :: CLabel -> CLabel 
454 entryLblToInfoLbl (IdLabel n Entry) = IdLabel n InfoTable
455 entryLblToInfoLbl (IdLabel n ConEntry) = IdLabel n ConInfoTable
456 entryLblToInfoLbl (IdLabel n StaticConEntry) = IdLabel n StaticInfoTable
457 entryLblToInfoLbl (DynIdLabel n Entry) = DynIdLabel n InfoTable
458 entryLblToInfoLbl (DynIdLabel n ConEntry) = DynIdLabel n ConInfoTable
459 entryLblToInfoLbl (DynIdLabel n StaticConEntry) = DynIdLabel n StaticInfoTable
460 entryLblToInfoLbl (CaseLabel n CaseReturnPt) = CaseLabel n CaseReturnInfo
461 entryLblToInfoLbl (RtsLabel (RtsEntry s)) = RtsLabel (RtsInfo s)
462 entryLblToInfoLbl (RtsLabel (RtsRet s)) = RtsLabel (RtsRetInfo s)
463 entryLblToInfoLbl (RtsLabel (RtsEntryFS s)) = RtsLabel (RtsInfoFS s)
464 entryLblToInfoLbl (RtsLabel (RtsRetFS s)) = RtsLabel (RtsRetInfoFS s)
465 entryLblToInfoLbl l = pprPanic "CLabel.entryLblToInfoLbl" (pprCLabel l)
466
467 -- -----------------------------------------------------------------------------
468 -- Does a CLabel need declaring before use or not?
469
470 needsCDecl :: CLabel -> Bool
471   -- False <=> it's pre-declared; don't bother
472   -- don't bother declaring SRT & Bitmap labels, we always make sure
473   -- they are defined before use.
474 needsCDecl (IdLabel _ SRT)              = False
475 needsCDecl (IdLabel _ SRTDesc)          = False
476 needsCDecl (IdLabel _ Bitmap)           = False
477 needsCDecl (IdLabel _ _)                = True
478 needsCDecl (DynIdLabel _ _)             = True
479 needsCDecl (CaseLabel _ _)              = True
480 needsCDecl (ModuleInitLabel _ _ _)      = True
481 needsCDecl (PlainModuleInitLabel _ _)   = True
482 needsCDecl ModuleRegdLabel              = False
483
484 needsCDecl (StringLitLabel _)           = False
485 needsCDecl (AsmTempLabel _)             = False
486 needsCDecl (RtsLabel _)                 = False
487 needsCDecl (ForeignLabel _ _ _)         = False
488 needsCDecl (CC_Label _)                 = True
489 needsCDecl (CCS_Label _)                = True
490 needsCDecl (HpcTicksLabel _)            = True
491 needsCDecl (HpcModuleOffsetLabel _)     = True
492 needsCDecl HpcModuleNameLabel           = False
493
494 -- Whether the label is an assembler temporary:
495
496 isAsmTemp  :: CLabel -> Bool    -- is a local temporary for native code generation
497 isAsmTemp (AsmTempLabel _) = True
498 isAsmTemp _                = False
499
500 -- -----------------------------------------------------------------------------
501 -- Is a CLabel visible outside this object file or not?
502
503 -- From the point of view of the code generator, a name is
504 -- externally visible if it has to be declared as exported
505 -- in the .o file's symbol table; that is, made non-static.
506
507 externallyVisibleCLabel :: CLabel -> Bool -- not C "static"
508 externallyVisibleCLabel (CaseLabel _ _)    = False
509 externallyVisibleCLabel (StringLitLabel _) = False
510 externallyVisibleCLabel (AsmTempLabel _)   = False
511 externallyVisibleCLabel (ModuleInitLabel _ _ _)= True
512 externallyVisibleCLabel (PlainModuleInitLabel _ _)= True
513 externallyVisibleCLabel ModuleRegdLabel    = False
514 externallyVisibleCLabel (RtsLabel _)       = True
515 externallyVisibleCLabel (ForeignLabel _ _ _) = True
516 externallyVisibleCLabel (IdLabel name _)     = isExternalName name
517 externallyVisibleCLabel (DynIdLabel name _)  = isExternalName name
518 externallyVisibleCLabel (CC_Label _)       = True
519 externallyVisibleCLabel (CCS_Label _)      = True
520 externallyVisibleCLabel (DynamicLinkerLabel _ _)  = False
521 externallyVisibleCLabel (HpcTicksLabel _)   = True
522 externallyVisibleCLabel (HpcModuleOffsetLabel _)  = True
523 externallyVisibleCLabel HpcModuleNameLabel      = False
524
525 -- -----------------------------------------------------------------------------
526 -- Finding the "type" of a CLabel 
527
528 -- For generating correct types in label declarations:
529
530 data CLabelType
531   = CodeLabel
532   | DataLabel
533
534 labelType :: CLabel -> CLabelType
535 labelType (RtsLabel (RtsSelectorInfoTable _ _)) = DataLabel
536 labelType (RtsLabel (RtsApInfoTable _ _))       = DataLabel
537 labelType (RtsLabel (RtsData _))              = DataLabel
538 labelType (RtsLabel (RtsCode _))              = CodeLabel
539 labelType (RtsLabel (RtsInfo _))              = DataLabel
540 labelType (RtsLabel (RtsEntry _))             = CodeLabel
541 labelType (RtsLabel (RtsRetInfo _))           = DataLabel
542 labelType (RtsLabel (RtsRet _))               = CodeLabel
543 labelType (RtsLabel (RtsDataFS _))            = DataLabel
544 labelType (RtsLabel (RtsCodeFS _))            = CodeLabel
545 labelType (RtsLabel (RtsInfoFS _))            = DataLabel
546 labelType (RtsLabel (RtsEntryFS _))           = CodeLabel
547 labelType (RtsLabel (RtsRetInfoFS _))         = DataLabel
548 labelType (RtsLabel (RtsRetFS _))             = CodeLabel
549 labelType (RtsLabel (RtsApFast _))            = CodeLabel
550 labelType (CaseLabel _ CaseReturnInfo)        = DataLabel
551 labelType (CaseLabel _ _)                     = CodeLabel
552 labelType (ModuleInitLabel _ _ _)             = CodeLabel
553 labelType (PlainModuleInitLabel _ _)          = CodeLabel
554
555 labelType (IdLabel _ info) = idInfoLabelType info
556 labelType (DynIdLabel _ info) = idInfoLabelType info
557 labelType _        = DataLabel
558
559 idInfoLabelType info =
560   case info of
561     InfoTable     -> DataLabel
562     Closure       -> DataLabel
563     Bitmap        -> DataLabel
564     ConInfoTable  -> DataLabel
565     StaticInfoTable -> DataLabel
566     ClosureTable  -> DataLabel
567     _             -> CodeLabel
568
569
570 -- -----------------------------------------------------------------------------
571 -- Does a CLabel need dynamic linkage?
572
573 -- When referring to data in code, we need to know whether
574 -- that data resides in a DLL or not. [Win32 only.]
575 -- @labelDynamic@ returns @True@ if the label is located
576 -- in a DLL, be it a data reference or not.
577
578 labelDynamic :: CLabel -> Bool
579 labelDynamic lbl = 
580   case lbl of
581    RtsLabel _        -> not opt_Static  -- i.e., is the RTS in a DLL or not?
582    IdLabel n k       -> False
583    DynIdLabel n k    -> True
584 #if mingw32_TARGET_OS
585    ForeignLabel _ _ d  -> d
586 #else
587    -- On Mac OS X and on ELF platforms, false positives are OK,
588    -- so we claim that all foreign imports come from dynamic libraries
589    ForeignLabel _ _ _ -> True
590 #endif
591    ModuleInitLabel m _ dyn    -> not opt_Static && dyn
592    PlainModuleInitLabel m dyn -> not opt_Static && dyn
593    
594    -- Note that DynamicLinkerLabels do NOT require dynamic linking themselves.
595    _                 -> False
596
597 {-
598 OLD?: These GRAN functions are needed for spitting out GRAN_FETCH() at the
599 right places. It is used to detect when the abstractC statement of an
600 CCodeBlock actually contains the code for a slow entry point.  -- HWL
601
602 We need at least @Eq@ for @CLabels@, because we want to avoid
603 duplicate declarations in generating C (see @labelSeenTE@ in
604 @PprAbsC@).
605 -}
606
607 -----------------------------------------------------------------------------
608 -- Printing out CLabels.
609
610 {-
611 Convention:
612
613       <name>_<type>
614
615 where <name> is <Module>_<name> for external names and <unique> for
616 internal names. <type> is one of the following:
617
618          info                   Info table
619          srt                    Static reference table
620          srtd                   Static reference table descriptor
621          entry                  Entry code (function, closure)
622          slow                   Slow entry code (if any)
623          ret                    Direct return address    
624          vtbl                   Vector table
625          <n>_alt                Case alternative (tag n)
626          dflt                   Default case alternative
627          btm                    Large bitmap vector
628          closure                Static closure
629          con_entry              Dynamic Constructor entry code
630          con_info               Dynamic Constructor info table
631          static_entry           Static Constructor entry code
632          static_info            Static Constructor info table
633          sel_info               Selector info table
634          sel_entry              Selector entry code
635          cc                     Cost centre
636          ccs                    Cost centre stack
637
638 Many of these distinctions are only for documentation reasons.  For
639 example, _ret is only distinguished from _entry to make it easy to
640 tell whether a code fragment is a return point or a closure/function
641 entry.
642 -}
643
644 instance Outputable CLabel where
645   ppr = pprCLabel
646
647 pprCLabel :: CLabel -> SDoc
648
649 #if ! OMIT_NATIVE_CODEGEN
650 pprCLabel (AsmTempLabel u)
651   =  getPprStyle $ \ sty ->
652      if asmStyle sty then 
653         ptext asmTempLabelPrefix <> pprUnique u
654      else
655         char '_' <> pprUnique u
656
657 pprCLabel (DynamicLinkerLabel info lbl)
658    = pprDynamicLinkerAsmLabel info lbl
659    
660 pprCLabel PicBaseLabel
661    = ptext SLIT("1b")
662    
663 pprCLabel (DeadStripPreventer lbl)
664    = pprCLabel lbl <> ptext SLIT("_dsp")
665 #endif
666
667 pprCLabel lbl = 
668 #if ! OMIT_NATIVE_CODEGEN
669     getPprStyle $ \ sty ->
670     if asmStyle sty then 
671         maybe_underscore (pprAsmCLbl lbl)
672     else
673 #endif
674        pprCLbl lbl
675
676 maybe_underscore doc
677   | underscorePrefix = pp_cSEP <> doc
678   | otherwise        = doc
679
680 #ifdef mingw32_TARGET_OS
681 -- In asm mode, we need to put the suffix on a stdcall ForeignLabel.
682 -- (The C compiler does this itself).
683 pprAsmCLbl (ForeignLabel fs (Just sz) _)
684    = ftext fs <> char '@' <> int sz
685 #endif
686 pprAsmCLbl lbl
687    = pprCLbl lbl
688
689 pprCLbl (StringLitLabel u)
690   = pprUnique u <> ptext SLIT("_str")
691
692 pprCLbl (CaseLabel u CaseReturnPt)
693   = hcat [pprUnique u, ptext SLIT("_ret")]
694 pprCLbl (CaseLabel u CaseReturnInfo)
695   = hcat [pprUnique u, ptext SLIT("_info")]
696 pprCLbl (CaseLabel u (CaseAlt tag))
697   = hcat [pprUnique u, pp_cSEP, int tag, ptext SLIT("_alt")]
698 pprCLbl (CaseLabel u CaseDefault)
699   = hcat [pprUnique u, ptext SLIT("_dflt")]
700
701 pprCLbl (RtsLabel (RtsCode str))   = ptext str
702 pprCLbl (RtsLabel (RtsData str))   = ptext str
703 pprCLbl (RtsLabel (RtsCodeFS str)) = ftext str
704 pprCLbl (RtsLabel (RtsDataFS str)) = ftext str
705
706 pprCLbl (RtsLabel (RtsApFast str)) = ptext str <> ptext SLIT("_fast")
707
708 pprCLbl (RtsLabel (RtsSelectorInfoTable upd_reqd offset))
709   = hcat [ptext SLIT("stg_sel_"), text (show offset),
710                 ptext (if upd_reqd 
711                         then SLIT("_upd_info") 
712                         else SLIT("_noupd_info"))
713         ]
714
715 pprCLbl (RtsLabel (RtsSelectorEntry upd_reqd offset))
716   = hcat [ptext SLIT("stg_sel_"), text (show offset),
717                 ptext (if upd_reqd 
718                         then SLIT("_upd_entry") 
719                         else SLIT("_noupd_entry"))
720         ]
721
722 pprCLbl (RtsLabel (RtsApInfoTable upd_reqd arity))
723   = hcat [ptext SLIT("stg_ap_"), text (show arity),
724                 ptext (if upd_reqd 
725                         then SLIT("_upd_info") 
726                         else SLIT("_noupd_info"))
727         ]
728
729 pprCLbl (RtsLabel (RtsApEntry upd_reqd arity))
730   = hcat [ptext SLIT("stg_ap_"), text (show arity),
731                 ptext (if upd_reqd 
732                         then SLIT("_upd_entry") 
733                         else SLIT("_noupd_entry"))
734         ]
735
736 pprCLbl (RtsLabel (RtsInfo fs))
737   = ptext fs <> ptext SLIT("_info")
738
739 pprCLbl (RtsLabel (RtsEntry fs))
740   = ptext fs <> ptext SLIT("_entry")
741
742 pprCLbl (RtsLabel (RtsRetInfo fs))
743   = ptext fs <> ptext SLIT("_info")
744
745 pprCLbl (RtsLabel (RtsRet fs))
746   = ptext fs <> ptext SLIT("_ret")
747
748 pprCLbl (RtsLabel (RtsInfoFS fs))
749   = ftext fs <> ptext SLIT("_info")
750
751 pprCLbl (RtsLabel (RtsEntryFS fs))
752   = ftext fs <> ptext SLIT("_entry")
753
754 pprCLbl (RtsLabel (RtsRetInfoFS fs))
755   = ftext fs <> ptext SLIT("_info")
756
757 pprCLbl (RtsLabel (RtsRetFS fs))
758   = ftext fs <> ptext SLIT("_ret")
759
760 pprCLbl (RtsLabel (RtsPrimOp primop)) 
761   = ppr primop <> ptext SLIT("_fast")
762
763 pprCLbl (RtsLabel (RtsSlowTickyCtr pat)) 
764   = ptext SLIT("SLOW_CALL_") <> text pat <> ptext SLIT("_ctr")
765
766 pprCLbl ModuleRegdLabel
767   = ptext SLIT("_module_registered")
768
769 pprCLbl (ForeignLabel str _ _)
770   = ftext str
771
772 pprCLbl (IdLabel name  flavor) = ppr name <> ppIdFlavor flavor
773 pprCLbl (DynIdLabel name  flavor) = ppr name <> ppIdFlavor flavor
774
775 pprCLbl (CC_Label cc)           = ppr cc
776 pprCLbl (CCS_Label ccs)         = ppr ccs
777
778 pprCLbl (ModuleInitLabel mod way _)     
779    = ptext SLIT("__stginit_") <> ppr mod
780         <> char '_' <> text way
781 pprCLbl (PlainModuleInitLabel mod _)    
782    = ptext SLIT("__stginit_") <> ppr mod
783
784 pprCLbl (HpcTicksLabel mod)
785   = ptext SLIT("_hpc_tickboxes_")  <> ppr mod <> ptext SLIT("_hpc")
786
787 pprCLbl (HpcModuleOffsetLabel mod)
788   = ptext SLIT("_hpc_module_offset_")  <> ppr mod <> ptext SLIT("_hpc")
789
790 pprCLbl HpcModuleNameLabel
791   = ptext SLIT("_hpc_module_name_str")
792
793 ppIdFlavor :: IdLabelInfo -> SDoc
794 ppIdFlavor x = pp_cSEP <>
795                (case x of
796                        Closure          -> ptext SLIT("closure")
797                        SRT              -> ptext SLIT("srt")
798                        SRTDesc          -> ptext SLIT("srtd")
799                        InfoTable        -> ptext SLIT("info")
800                        Entry            -> ptext SLIT("entry")
801                        Slow             -> ptext SLIT("slow")
802                        RednCounts       -> ptext SLIT("ct")
803                        Bitmap           -> ptext SLIT("btm")
804                        ConEntry         -> ptext SLIT("con_entry")
805                        ConInfoTable     -> ptext SLIT("con_info")
806                        StaticConEntry   -> ptext SLIT("static_entry")
807                        StaticInfoTable  -> ptext SLIT("static_info")
808                        ClosureTable     -> ptext SLIT("closure_tbl")
809                       )
810
811
812 pp_cSEP = char '_'
813
814 -- -----------------------------------------------------------------------------
815 -- Machine-dependent knowledge about labels.
816
817 underscorePrefix :: Bool   -- leading underscore on assembler labels?
818 underscorePrefix = (cLeadingUnderscore == "YES")
819
820 asmTempLabelPrefix :: LitString  -- for formatting labels
821 asmTempLabelPrefix =
822 #if alpha_TARGET_OS
823      {- The alpha assembler likes temporary labels to look like $L123
824         instead of L123.  (Don't toss the L, because then Lf28
825         turns into $f28.)
826      -}
827      SLIT("$")
828 #elif darwin_TARGET_OS
829      SLIT("L")
830 #else
831      SLIT(".L")
832 #endif
833
834 pprDynamicLinkerAsmLabel :: DynamicLinkerLabelInfo -> CLabel -> SDoc
835
836 #if x86_64_TARGET_ARCH && darwin_TARGET_OS
837 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
838   = pprCLabel lbl <> text "@GOTPCREL"
839 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
840   = pprCLabel lbl
841 pprDynamicLinkerAsmLabel _ _
842   = panic "pprDynamicLinkerAsmLabel"
843 #elif darwin_TARGET_OS
844 pprDynamicLinkerAsmLabel CodeStub lbl
845   = char 'L' <> pprCLabel lbl <> text "$stub"
846 pprDynamicLinkerAsmLabel SymbolPtr lbl
847   = char 'L' <> pprCLabel lbl <> text "$non_lazy_ptr"
848 pprDynamicLinkerAsmLabel _ _
849   = panic "pprDynamicLinkerAsmLabel"
850 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
851 pprDynamicLinkerAsmLabel CodeStub lbl
852   = pprCLabel lbl <> text "@plt"
853 pprDynamicLinkerAsmLabel SymbolPtr lbl
854   = text ".LC_" <> pprCLabel lbl
855 pprDynamicLinkerAsmLabel _ _
856   = panic "pprDynamicLinkerAsmLabel"
857 #elif x86_64_TARGET_ARCH && linux_TARGET_OS
858 pprDynamicLinkerAsmLabel CodeStub lbl
859   = pprCLabel lbl <> text "@plt"
860 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
861   = pprCLabel lbl <> text "@gotpcrel"
862 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
863   = pprCLabel lbl
864 pprDynamicLinkerAsmLabel _ _
865   = panic "pprDynamicLinkerAsmLabel"
866 #elif linux_TARGET_OS
867 pprDynamicLinkerAsmLabel CodeStub lbl
868   = pprCLabel lbl <> text "@plt"
869 pprDynamicLinkerAsmLabel SymbolPtr lbl
870   = text ".LC_" <> pprCLabel lbl
871 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
872   = pprCLabel lbl <> text "@got"
873 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
874   = pprCLabel lbl <> text "@gotoff"
875 #elif mingw32_TARGET_OS
876 pprDynamicLinkerAsmLabel SymbolPtr lbl
877   = text "__imp_" <> pprCLabel lbl
878 pprDynamicLinkerAsmLabel _ _
879   = panic "pprDynamicLinkerAsmLabel"
880 #else
881 pprDynamicLinkerAsmLabel _ _
882   = panic "pprDynamicLinkerAsmLabel"
883 #endif