397a074ad3f377f03412fc258f6ccea41fca4a14
[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, maybeAsmTemp, 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 maybeAsmTemp :: CLabel -> Maybe Unique
501 maybeAsmTemp (AsmTempLabel uq) = Just uq
502 maybeAsmTemp _                 = Nothing
503
504 -- -----------------------------------------------------------------------------
505 -- Is a CLabel visible outside this object file or not?
506
507 -- From the point of view of the code generator, a name is
508 -- externally visible if it has to be declared as exported
509 -- in the .o file's symbol table; that is, made non-static.
510
511 externallyVisibleCLabel :: CLabel -> Bool -- not C "static"
512 externallyVisibleCLabel (CaseLabel _ _)    = False
513 externallyVisibleCLabel (StringLitLabel _) = False
514 externallyVisibleCLabel (AsmTempLabel _)   = False
515 externallyVisibleCLabel (ModuleInitLabel _ _ _)= True
516 externallyVisibleCLabel (PlainModuleInitLabel _ _)= True
517 externallyVisibleCLabel ModuleRegdLabel    = False
518 externallyVisibleCLabel (RtsLabel _)       = True
519 externallyVisibleCLabel (ForeignLabel _ _ _) = True
520 externallyVisibleCLabel (IdLabel name _)     = isExternalName name
521 externallyVisibleCLabel (DynIdLabel name _)  = isExternalName name
522 externallyVisibleCLabel (CC_Label _)       = True
523 externallyVisibleCLabel (CCS_Label _)      = True
524 externallyVisibleCLabel (DynamicLinkerLabel _ _)  = False
525 externallyVisibleCLabel (HpcTicksLabel _)   = True
526 externallyVisibleCLabel (HpcModuleOffsetLabel _)  = True
527 externallyVisibleCLabel HpcModuleNameLabel      = False
528
529 -- -----------------------------------------------------------------------------
530 -- Finding the "type" of a CLabel 
531
532 -- For generating correct types in label declarations:
533
534 data CLabelType
535   = CodeLabel
536   | DataLabel
537
538 labelType :: CLabel -> CLabelType
539 labelType (RtsLabel (RtsSelectorInfoTable _ _)) = DataLabel
540 labelType (RtsLabel (RtsApInfoTable _ _))       = DataLabel
541 labelType (RtsLabel (RtsData _))              = DataLabel
542 labelType (RtsLabel (RtsCode _))              = CodeLabel
543 labelType (RtsLabel (RtsInfo _))              = DataLabel
544 labelType (RtsLabel (RtsEntry _))             = CodeLabel
545 labelType (RtsLabel (RtsRetInfo _))           = DataLabel
546 labelType (RtsLabel (RtsRet _))               = CodeLabel
547 labelType (RtsLabel (RtsDataFS _))            = DataLabel
548 labelType (RtsLabel (RtsCodeFS _))            = CodeLabel
549 labelType (RtsLabel (RtsInfoFS _))            = DataLabel
550 labelType (RtsLabel (RtsEntryFS _))           = CodeLabel
551 labelType (RtsLabel (RtsRetInfoFS _))         = DataLabel
552 labelType (RtsLabel (RtsRetFS _))             = CodeLabel
553 labelType (RtsLabel (RtsApFast _))            = CodeLabel
554 labelType (CaseLabel _ CaseReturnInfo)        = DataLabel
555 labelType (CaseLabel _ _)                     = CodeLabel
556 labelType (ModuleInitLabel _ _ _)             = CodeLabel
557 labelType (PlainModuleInitLabel _ _)          = CodeLabel
558
559 labelType (IdLabel _ info) = idInfoLabelType info
560 labelType (DynIdLabel _ info) = idInfoLabelType info
561 labelType _        = DataLabel
562
563 idInfoLabelType info =
564   case info of
565     InfoTable     -> DataLabel
566     Closure       -> DataLabel
567     Bitmap        -> DataLabel
568     ConInfoTable  -> DataLabel
569     StaticInfoTable -> DataLabel
570     ClosureTable  -> DataLabel
571     _             -> CodeLabel
572
573
574 -- -----------------------------------------------------------------------------
575 -- Does a CLabel need dynamic linkage?
576
577 -- When referring to data in code, we need to know whether
578 -- that data resides in a DLL or not. [Win32 only.]
579 -- @labelDynamic@ returns @True@ if the label is located
580 -- in a DLL, be it a data reference or not.
581
582 labelDynamic :: CLabel -> Bool
583 labelDynamic lbl = 
584   case lbl of
585    RtsLabel _        -> not opt_Static  -- i.e., is the RTS in a DLL or not?
586    IdLabel n k       -> False
587    DynIdLabel n k    -> True
588 #if mingw32_TARGET_OS
589    ForeignLabel _ _ d  -> d
590 #else
591    -- On Mac OS X and on ELF platforms, false positives are OK,
592    -- so we claim that all foreign imports come from dynamic libraries
593    ForeignLabel _ _ _ -> True
594 #endif
595    ModuleInitLabel m _ dyn    -> not opt_Static && dyn
596    PlainModuleInitLabel m dyn -> not opt_Static && dyn
597    
598    -- Note that DynamicLinkerLabels do NOT require dynamic linking themselves.
599    _                 -> False
600
601 {-
602 OLD?: These GRAN functions are needed for spitting out GRAN_FETCH() at the
603 right places. It is used to detect when the abstractC statement of an
604 CCodeBlock actually contains the code for a slow entry point.  -- HWL
605
606 We need at least @Eq@ for @CLabels@, because we want to avoid
607 duplicate declarations in generating C (see @labelSeenTE@ in
608 @PprAbsC@).
609 -}
610
611 -----------------------------------------------------------------------------
612 -- Printing out CLabels.
613
614 {-
615 Convention:
616
617       <name>_<type>
618
619 where <name> is <Module>_<name> for external names and <unique> for
620 internal names. <type> is one of the following:
621
622          info                   Info table
623          srt                    Static reference table
624          srtd                   Static reference table descriptor
625          entry                  Entry code (function, closure)
626          slow                   Slow entry code (if any)
627          ret                    Direct return address    
628          vtbl                   Vector table
629          <n>_alt                Case alternative (tag n)
630          dflt                   Default case alternative
631          btm                    Large bitmap vector
632          closure                Static closure
633          con_entry              Dynamic Constructor entry code
634          con_info               Dynamic Constructor info table
635          static_entry           Static Constructor entry code
636          static_info            Static Constructor info table
637          sel_info               Selector info table
638          sel_entry              Selector entry code
639          cc                     Cost centre
640          ccs                    Cost centre stack
641
642 Many of these distinctions are only for documentation reasons.  For
643 example, _ret is only distinguished from _entry to make it easy to
644 tell whether a code fragment is a return point or a closure/function
645 entry.
646 -}
647
648 instance Outputable CLabel where
649   ppr = pprCLabel
650
651 pprCLabel :: CLabel -> SDoc
652
653 #if ! OMIT_NATIVE_CODEGEN
654 pprCLabel (AsmTempLabel u)
655   =  getPprStyle $ \ sty ->
656      if asmStyle sty then 
657         ptext asmTempLabelPrefix <> pprUnique u
658      else
659         char '_' <> pprUnique u
660
661 pprCLabel (DynamicLinkerLabel info lbl)
662    = pprDynamicLinkerAsmLabel info lbl
663    
664 pprCLabel PicBaseLabel
665    = ptext SLIT("1b")
666    
667 pprCLabel (DeadStripPreventer lbl)
668    = pprCLabel lbl <> ptext SLIT("_dsp")
669 #endif
670
671 pprCLabel lbl = 
672 #if ! OMIT_NATIVE_CODEGEN
673     getPprStyle $ \ sty ->
674     if asmStyle sty then 
675         maybe_underscore (pprAsmCLbl lbl)
676     else
677 #endif
678        pprCLbl lbl
679
680 maybe_underscore doc
681   | underscorePrefix = pp_cSEP <> doc
682   | otherwise        = doc
683
684 #ifdef mingw32_TARGET_OS
685 -- In asm mode, we need to put the suffix on a stdcall ForeignLabel.
686 -- (The C compiler does this itself).
687 pprAsmCLbl (ForeignLabel fs (Just sz) _)
688    = ftext fs <> char '@' <> int sz
689 #endif
690 pprAsmCLbl lbl
691    = pprCLbl lbl
692
693 pprCLbl (StringLitLabel u)
694   = pprUnique u <> ptext SLIT("_str")
695
696 pprCLbl (CaseLabel u CaseReturnPt)
697   = hcat [pprUnique u, ptext SLIT("_ret")]
698 pprCLbl (CaseLabel u CaseReturnInfo)
699   = hcat [pprUnique u, ptext SLIT("_info")]
700 pprCLbl (CaseLabel u (CaseAlt tag))
701   = hcat [pprUnique u, pp_cSEP, int tag, ptext SLIT("_alt")]
702 pprCLbl (CaseLabel u CaseDefault)
703   = hcat [pprUnique u, ptext SLIT("_dflt")]
704
705 pprCLbl (RtsLabel (RtsCode str))   = ptext str
706 pprCLbl (RtsLabel (RtsData str))   = ptext str
707 pprCLbl (RtsLabel (RtsCodeFS str)) = ftext str
708 pprCLbl (RtsLabel (RtsDataFS str)) = ftext str
709
710 pprCLbl (RtsLabel (RtsApFast str)) = ptext str <> ptext SLIT("_fast")
711
712 pprCLbl (RtsLabel (RtsSelectorInfoTable upd_reqd offset))
713   = hcat [ptext SLIT("stg_sel_"), text (show offset),
714                 ptext (if upd_reqd 
715                         then SLIT("_upd_info") 
716                         else SLIT("_noupd_info"))
717         ]
718
719 pprCLbl (RtsLabel (RtsSelectorEntry upd_reqd offset))
720   = hcat [ptext SLIT("stg_sel_"), text (show offset),
721                 ptext (if upd_reqd 
722                         then SLIT("_upd_entry") 
723                         else SLIT("_noupd_entry"))
724         ]
725
726 pprCLbl (RtsLabel (RtsApInfoTable upd_reqd arity))
727   = hcat [ptext SLIT("stg_ap_"), text (show arity),
728                 ptext (if upd_reqd 
729                         then SLIT("_upd_info") 
730                         else SLIT("_noupd_info"))
731         ]
732
733 pprCLbl (RtsLabel (RtsApEntry upd_reqd arity))
734   = hcat [ptext SLIT("stg_ap_"), text (show arity),
735                 ptext (if upd_reqd 
736                         then SLIT("_upd_entry") 
737                         else SLIT("_noupd_entry"))
738         ]
739
740 pprCLbl (RtsLabel (RtsInfo fs))
741   = ptext fs <> ptext SLIT("_info")
742
743 pprCLbl (RtsLabel (RtsEntry fs))
744   = ptext fs <> ptext SLIT("_entry")
745
746 pprCLbl (RtsLabel (RtsRetInfo fs))
747   = ptext fs <> ptext SLIT("_info")
748
749 pprCLbl (RtsLabel (RtsRet fs))
750   = ptext fs <> ptext SLIT("_ret")
751
752 pprCLbl (RtsLabel (RtsInfoFS fs))
753   = ftext fs <> ptext SLIT("_info")
754
755 pprCLbl (RtsLabel (RtsEntryFS fs))
756   = ftext fs <> ptext SLIT("_entry")
757
758 pprCLbl (RtsLabel (RtsRetInfoFS fs))
759   = ftext fs <> ptext SLIT("_info")
760
761 pprCLbl (RtsLabel (RtsRetFS fs))
762   = ftext fs <> ptext SLIT("_ret")
763
764 pprCLbl (RtsLabel (RtsPrimOp primop)) 
765   = ppr primop <> ptext SLIT("_fast")
766
767 pprCLbl (RtsLabel (RtsSlowTickyCtr pat)) 
768   = ptext SLIT("SLOW_CALL_") <> text pat <> ptext SLIT("_ctr")
769
770 pprCLbl ModuleRegdLabel
771   = ptext SLIT("_module_registered")
772
773 pprCLbl (ForeignLabel str _ _)
774   = ftext str
775
776 pprCLbl (IdLabel name  flavor) = ppr name <> ppIdFlavor flavor
777 pprCLbl (DynIdLabel name  flavor) = ppr name <> ppIdFlavor flavor
778
779 pprCLbl (CC_Label cc)           = ppr cc
780 pprCLbl (CCS_Label ccs)         = ppr ccs
781
782 pprCLbl (ModuleInitLabel mod way _)     
783    = ptext SLIT("__stginit_") <> ppr mod
784         <> char '_' <> text way
785 pprCLbl (PlainModuleInitLabel mod _)    
786    = ptext SLIT("__stginit_") <> ppr mod
787
788 pprCLbl (HpcTicksLabel mod)
789   = ptext SLIT("_hpc_tickboxes_")  <> ppr mod <> ptext SLIT("_hpc")
790
791 pprCLbl (HpcModuleOffsetLabel mod)
792   = ptext SLIT("_hpc_module_offset_")  <> ppr mod <> ptext SLIT("_hpc")
793
794 pprCLbl HpcModuleNameLabel
795   = ptext SLIT("_hpc_module_name_str")
796
797 ppIdFlavor :: IdLabelInfo -> SDoc
798 ppIdFlavor x = pp_cSEP <>
799                (case x of
800                        Closure          -> ptext SLIT("closure")
801                        SRT              -> ptext SLIT("srt")
802                        SRTDesc          -> ptext SLIT("srtd")
803                        InfoTable        -> ptext SLIT("info")
804                        Entry            -> ptext SLIT("entry")
805                        Slow             -> ptext SLIT("slow")
806                        RednCounts       -> ptext SLIT("ct")
807                        Bitmap           -> ptext SLIT("btm")
808                        ConEntry         -> ptext SLIT("con_entry")
809                        ConInfoTable     -> ptext SLIT("con_info")
810                        StaticConEntry   -> ptext SLIT("static_entry")
811                        StaticInfoTable  -> ptext SLIT("static_info")
812                        ClosureTable     -> ptext SLIT("closure_tbl")
813                       )
814
815
816 pp_cSEP = char '_'
817
818 -- -----------------------------------------------------------------------------
819 -- Machine-dependent knowledge about labels.
820
821 underscorePrefix :: Bool   -- leading underscore on assembler labels?
822 underscorePrefix = (cLeadingUnderscore == "YES")
823
824 asmTempLabelPrefix :: LitString  -- for formatting labels
825 asmTempLabelPrefix =
826 #if alpha_TARGET_OS
827      {- The alpha assembler likes temporary labels to look like $L123
828         instead of L123.  (Don't toss the L, because then Lf28
829         turns into $f28.)
830      -}
831      SLIT("$")
832 #elif darwin_TARGET_OS
833      SLIT("L")
834 #else
835      SLIT(".L")
836 #endif
837
838 pprDynamicLinkerAsmLabel :: DynamicLinkerLabelInfo -> CLabel -> SDoc
839
840 #if x86_64_TARGET_ARCH && darwin_TARGET_OS
841 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
842   = pprCLabel lbl <> text "@GOTPCREL"
843 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
844   = pprCLabel lbl
845 pprDynamicLinkerAsmLabel _ _
846   = panic "pprDynamicLinkerAsmLabel"
847 #elif darwin_TARGET_OS
848 pprDynamicLinkerAsmLabel CodeStub lbl
849   = char 'L' <> pprCLabel lbl <> text "$stub"
850 pprDynamicLinkerAsmLabel SymbolPtr lbl
851   = char 'L' <> pprCLabel lbl <> text "$non_lazy_ptr"
852 pprDynamicLinkerAsmLabel _ _
853   = panic "pprDynamicLinkerAsmLabel"
854 #elif powerpc_TARGET_ARCH && linux_TARGET_OS
855 pprDynamicLinkerAsmLabel CodeStub lbl
856   = pprCLabel lbl <> text "@plt"
857 pprDynamicLinkerAsmLabel SymbolPtr lbl
858   = text ".LC_" <> pprCLabel lbl
859 pprDynamicLinkerAsmLabel _ _
860   = panic "pprDynamicLinkerAsmLabel"
861 #elif x86_64_TARGET_ARCH && linux_TARGET_OS
862 pprDynamicLinkerAsmLabel CodeStub lbl
863   = pprCLabel lbl <> text "@plt"
864 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
865   = pprCLabel lbl <> text "@gotpcrel"
866 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
867   = pprCLabel lbl
868 pprDynamicLinkerAsmLabel _ _
869   = panic "pprDynamicLinkerAsmLabel"
870 #elif linux_TARGET_OS
871 pprDynamicLinkerAsmLabel CodeStub lbl
872   = pprCLabel lbl <> text "@plt"
873 pprDynamicLinkerAsmLabel SymbolPtr lbl
874   = text ".LC_" <> pprCLabel lbl
875 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
876   = pprCLabel lbl <> text "@got"
877 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
878   = pprCLabel lbl <> text "@gotoff"
879 #elif mingw32_TARGET_OS
880 pprDynamicLinkerAsmLabel SymbolPtr lbl
881   = text "__imp_" <> pprCLabel lbl
882 pprDynamicLinkerAsmLabel _ _
883   = panic "pprDynamicLinkerAsmLabel"
884 #else
885 pprDynamicLinkerAsmLabel _ _
886   = panic "pprDynamicLinkerAsmLabel"
887 #endif