| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Cmm.CLabel
Synopsis
- data CLabel
- newtype NeedExternDecl = NeedExternDecl Bool
- data ForeignLabelSource
- data DynamicLinkerLabelInfo
- data ConInfoTableLocation
- getConInfoTableLocation :: IdLabelInfo -> Maybe ConInfoTableLocation
- mkClosureLabel :: Name -> CafInfo -> CLabel
- mkSRTLabel :: Unique -> CLabel
- mkInfoTableLabel :: Name -> CafInfo -> CLabel
- mkEntryLabel :: Name -> CafInfo -> CLabel
- mkRednCountsLabel :: Name -> CLabel
- mkTagHitLabel :: Name -> Unique -> CLabel
- mkConInfoTableLabel :: Name -> ConInfoTableLocation -> CLabel
- mkApEntryLabel :: Platform -> Bool -> Int -> CLabel
- mkApInfoTableLabel :: Platform -> Bool -> Int -> CLabel
- mkClosureTableLabel :: Name -> CafInfo -> CLabel
- mkBytesLabel :: Name -> CLabel
- mkLocalBlockLabel :: Unique -> CLabel
- mkBlockInfoTableLabel :: Name -> CafInfo -> CLabel
- mkBitmapLabel :: Unique -> CLabel
- mkStringLitLabel :: Unique -> CLabel
- mkInitializerStubLabel :: Module -> String -> CLabel
- mkInitializerArrayLabel :: Module -> CLabel
- mkFinalizerStubLabel :: Module -> String -> CLabel
- mkFinalizerArrayLabel :: Module -> CLabel
- mkAsmTempLabel :: Uniquable a => a -> CLabel
- mkAsmTempDerivedLabel :: CLabel -> FastString -> CLabel
- mkAsmTempEndLabel :: CLabel -> CLabel
- mkAsmTempProcEndLabel :: CLabel -> CLabel
- mkAsmTempDieLabel :: CLabel -> CLabel
- mkDirty_MUT_VAR_Label :: CLabel
- mkMUT_VAR_CLEAN_infoLabel :: CLabel
- mkNonmovingWriteBarrierEnabledLabel :: CLabel
- mkUpdInfoLabel :: CLabel
- mkBHUpdInfoLabel :: CLabel
- mkIndStaticInfoLabel :: CLabel
- mkMainCapabilityLabel :: CLabel
- mkMAP_FROZEN_CLEAN_infoLabel :: CLabel
- mkMAP_FROZEN_DIRTY_infoLabel :: CLabel
- mkMAP_DIRTY_infoLabel :: CLabel
- mkSMAP_FROZEN_CLEAN_infoLabel :: CLabel
- mkSMAP_FROZEN_DIRTY_infoLabel :: CLabel
- mkSMAP_DIRTY_infoLabel :: CLabel
- mkBadAlignmentLabel :: CLabel
- mkOutOfBoundsAccessLabel :: CLabel
- mkMemcpyRangeOverlapLabel :: CLabel
- mkArrWords_infoLabel :: CLabel
- mkSRTInfoLabel :: Int -> CLabel
- mkTopTickyCtrLabel :: CLabel
- mkCAFBlackHoleInfoTableLabel :: CLabel
- mkRtsPrimOpLabel :: PrimOp -> CLabel
- mkRtsSlowFastTickyCtrLabel :: String -> CLabel
- mkSelectorInfoLabel :: Platform -> Bool -> Int -> CLabel
- mkSelectorEntryLabel :: Platform -> Bool -> Int -> CLabel
- mkCmmInfoLabel :: UnitId -> FastString -> CLabel
- mkCmmEntryLabel :: UnitId -> FastString -> CLabel
- mkCmmRetInfoLabel :: UnitId -> FastString -> CLabel
- mkCmmRetLabel :: UnitId -> FastString -> CLabel
- mkCmmCodeLabel :: UnitId -> FastString -> CLabel
- mkCmmDataLabel :: UnitId -> NeedExternDecl -> FastString -> CLabel
- mkRtsCmmDataLabel :: FastString -> CLabel
- mkCmmClosureLabel :: UnitId -> FastString -> CLabel
- mkRtsApFastLabel :: FastString -> CLabel
- mkPrimCallLabel :: PrimCall -> CLabel
- mkForeignLabel :: FastString -> Maybe Int -> ForeignLabelSource -> FunctionOrData -> CLabel
- mkCCLabel :: CostCentre -> CLabel
- mkCCSLabel :: CostCentreStack -> CLabel
- mkIPELabel :: Module -> CLabel
- data InfoProvEnt = InfoProvEnt {- infoTablePtr :: !CLabel
- infoProvEntClosureType :: !Int
- infoTableType :: !String
- infoProvModule :: !Module
- infoTableProv :: !(Maybe (RealSrcSpan, String))
 
- mkDynamicLinkerLabel :: DynamicLinkerLabelInfo -> CLabel -> CLabel
- mkPicBaseLabel :: CLabel
- mkDeadStripPreventer :: CLabel -> CLabel
- mkHpcTicksLabel :: Module -> CLabel
- hasCAF :: CLabel -> Bool
- needsCDecl :: CLabel -> Bool
- maybeLocalBlockLabel :: CLabel -> Maybe BlockId
- externallyVisibleCLabel :: CLabel -> Bool
- isMathFun :: CLabel -> Bool
- isCFunctionLabel :: CLabel -> Bool
- isGcPtrLabel :: CLabel -> Bool
- labelDynamic :: Module -> Platform -> Bool -> CLabel -> Bool
- isLocalCLabel :: Module -> CLabel -> Bool
- mayRedirectTo :: CLabel -> CLabel -> Bool
- isInfoTableLabel :: CLabel -> Bool
- isConInfoTableLabel :: CLabel -> Bool
- isIdLabel :: CLabel -> Bool
- isTickyLabel :: CLabel -> Bool
- hasHaskellName :: CLabel -> Maybe Name
- hasIdLabelInfo :: CLabel -> Maybe IdLabelInfo
- isBytesLabel :: CLabel -> Bool
- isForeignLabel :: CLabel -> Bool
- isSomeRODataLabel :: CLabel -> Bool
- isStaticClosureLabel :: CLabel -> Bool
- toClosureLbl :: Platform -> CLabel -> CLabel
- toSlowEntryLbl :: Platform -> CLabel -> CLabel
- toEntryLbl :: Platform -> CLabel -> CLabel
- toInfoLbl :: Platform -> CLabel -> CLabel
- data LabelStyle
- pprDebugCLabel :: Platform -> CLabel -> SDoc
- pprCLabel :: Platform -> LabelStyle -> CLabel -> SDoc
- ppInternalProcLabel :: Module -> CLabel -> Maybe SDoc
- dynamicLinkerLabelInfo :: CLabel -> Maybe (DynamicLinkerLabelInfo, CLabel)
- addLabelSize :: CLabel -> Int -> CLabel
- foreignLabelStdcallInfo :: CLabel -> Maybe Int
Documentation
CLabel is an abstract type that supports the following operations:
- Pretty printing
- In a C file, does it need to be declared before use? (i.e. is it guaranteed to be already in scope in the places we need to refer to it?)
- If it needs to be declared, what type (code or data) should it be declared to have?
- Is it visible outside this object file or not?
- Is it "dynamic" (see details below)
- Eq and Ord, so that we can make sets of CLabels (currently only used in outputting C as far as I can tell, to avoid generating more than one declaration for any given label).
- Converting an info table label into an entry label.
CLabel usage is a bit messy in GHC as they are used in a number of different contexts:
- By the C-- AST to identify labels
- By the unregisterised C code generator ("PprC") for naming functions (hence
    the name CLabel)
- By the native and LLVM code generators to identify labels
For extra fun, each of these uses a slightly different subset of constructors
  (e.g. AsmTempLabel and AsmTempDerivedLabel are used only in the NCG and
  LLVM backends).
In general, we use IdLabel to represent Haskell things early in the
  pipeline. However, later optimization passes will often represent blocks they
  create with LocalBlockLabel where there is no obvious Name to hang off the
  label.
newtype NeedExternDecl Source #
Indicate if GHC.CmmToC has to generate an extern declaration for the label (e.g. "extern StgWordArray(foo)"). The type is fixed to StgWordArray.
Symbols from the RTS don't need "extern" declarations because they are
 exposed via "rtsincludeStg.h" with the appropriate type. See needsCDecl.
The fixed StgWordArray type led to "conflicting types" issues with user provided Cmm files (not in the RTS) that declare data of another type (#15467 and test for #17920). Hence the Cmm parser considers that labels in data sections don't need the "extern" declaration (just add one explicitly if you need it).
See https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes for why extern declaration are needed at all.
Constructors
| NeedExternDecl Bool | 
Instances
| Eq NeedExternDecl Source # | |
| Defined in GHC.Cmm.CLabel Methods (==) :: NeedExternDecl -> NeedExternDecl -> Bool # (/=) :: NeedExternDecl -> NeedExternDecl -> Bool # | |
| Ord NeedExternDecl Source # | |
| Defined in GHC.Cmm.CLabel Methods compare :: NeedExternDecl -> NeedExternDecl -> Ordering # (<) :: NeedExternDecl -> NeedExternDecl -> Bool # (<=) :: NeedExternDecl -> NeedExternDecl -> Bool # (>) :: NeedExternDecl -> NeedExternDecl -> Bool # (>=) :: NeedExternDecl -> NeedExternDecl -> Bool # max :: NeedExternDecl -> NeedExternDecl -> NeedExternDecl # min :: NeedExternDecl -> NeedExternDecl -> NeedExternDecl # | |
data ForeignLabelSource Source #
Record where a foreign label is stored.
Constructors
| ForeignLabelInPackage UnitId | Label is in a named package | 
| ForeignLabelInExternalPackage | Label is in some external, system package that doesn't also contain compiled Haskell code, and is not associated with any .hi files. We don't have to worry about Haskell code being inlined from external packages. It is safe to treat the RTS package as "external". | 
| ForeignLabelInThisPackage | Label is in the package currently being compiled. This is only used for creating hacky tmp labels during code generation. Don't use it in any code that might be inlined across a package boundary (ie, core code) else the information will be wrong relative to the destination module. | 
Instances
| Outputable ForeignLabelSource Source # | |
| Defined in GHC.Cmm.CLabel Methods ppr :: ForeignLabelSource -> SDoc Source # | |
| Eq ForeignLabelSource Source # | |
| Defined in GHC.Cmm.CLabel Methods (==) :: ForeignLabelSource -> ForeignLabelSource -> Bool # (/=) :: ForeignLabelSource -> ForeignLabelSource -> Bool # | |
| Ord ForeignLabelSource Source # | |
| Defined in GHC.Cmm.CLabel Methods compare :: ForeignLabelSource -> ForeignLabelSource -> Ordering # (<) :: ForeignLabelSource -> ForeignLabelSource -> Bool # (<=) :: ForeignLabelSource -> ForeignLabelSource -> Bool # (>) :: ForeignLabelSource -> ForeignLabelSource -> Bool # (>=) :: ForeignLabelSource -> ForeignLabelSource -> Bool # max :: ForeignLabelSource -> ForeignLabelSource -> ForeignLabelSource # min :: ForeignLabelSource -> ForeignLabelSource -> ForeignLabelSource # | |
data DynamicLinkerLabelInfo Source #
Constructors
| CodeStub | |
| SymbolPtr | |
| GotSymbolPtr | |
| GotSymbolOffset | 
Instances
| Eq DynamicLinkerLabelInfo Source # | |
| Defined in GHC.Cmm.CLabel Methods (==) :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool # (/=) :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool # | |
| Ord DynamicLinkerLabelInfo Source # | |
| Defined in GHC.Cmm.CLabel Methods compare :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Ordering # (<) :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool # (<=) :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool # (>) :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool # (>=) :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool # max :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo # min :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo # | |
data ConInfoTableLocation Source #
Which module is the info table from, and which number was it.
Constructors
| UsageSite Module Int | |
| DefinitionSite | 
Instances
| Outputable ConInfoTableLocation Source # | |
| Defined in GHC.Cmm.CLabel Methods ppr :: ConInfoTableLocation -> SDoc Source # | |
| Eq ConInfoTableLocation Source # | |
| Defined in GHC.Cmm.CLabel Methods (==) :: ConInfoTableLocation -> ConInfoTableLocation -> Bool # (/=) :: ConInfoTableLocation -> ConInfoTableLocation -> Bool # | |
| Ord ConInfoTableLocation Source # | |
| Defined in GHC.Cmm.CLabel Methods compare :: ConInfoTableLocation -> ConInfoTableLocation -> Ordering # (<) :: ConInfoTableLocation -> ConInfoTableLocation -> Bool # (<=) :: ConInfoTableLocation -> ConInfoTableLocation -> Bool # (>) :: ConInfoTableLocation -> ConInfoTableLocation -> Bool # (>=) :: ConInfoTableLocation -> ConInfoTableLocation -> Bool # max :: ConInfoTableLocation -> ConInfoTableLocation -> ConInfoTableLocation # min :: ConInfoTableLocation -> ConInfoTableLocation -> ConInfoTableLocation # | |
getConInfoTableLocation :: IdLabelInfo -> Maybe ConInfoTableLocation Source #
Constructors
mkSRTLabel :: Unique -> CLabel Source #
mkInfoTableLabel :: Name -> CafInfo -> CLabel Source #
Decicdes between external and local labels based on the names externality.
mkRednCountsLabel :: Name -> CLabel Source #
mkConInfoTableLabel :: Name -> ConInfoTableLocation -> CLabel Source #
mkBytesLabel :: Name -> CLabel Source #
mkLocalBlockLabel :: Unique -> CLabel Source #
mkBitmapLabel :: Unique -> CLabel Source #
mkStringLitLabel :: Unique -> CLabel Source #
mkFinalizerArrayLabel :: Module -> CLabel Source #
mkAsmTempLabel :: Uniquable a => a -> CLabel Source #
mkAsmTempDerivedLabel :: CLabel -> FastString -> CLabel Source #
mkAsmTempEndLabel :: CLabel -> CLabel Source #
mkAsmTempProcEndLabel :: CLabel -> CLabel Source #
A label indicating the end of a procedure.
mkAsmTempDieLabel :: CLabel -> CLabel Source #
Construct a label for a DWARF Debug Information Entity (DIE) describing another symbol.
mkSRTInfoLabel :: Int -> CLabel Source #
mkRtsPrimOpLabel :: PrimOp -> CLabel Source #
mkCmmInfoLabel :: UnitId -> FastString -> CLabel Source #
mkCmmEntryLabel :: UnitId -> FastString -> CLabel Source #
mkCmmRetInfoLabel :: UnitId -> FastString -> CLabel Source #
mkCmmRetLabel :: UnitId -> FastString -> CLabel Source #
mkCmmCodeLabel :: UnitId -> FastString -> CLabel Source #
mkCmmDataLabel :: UnitId -> NeedExternDecl -> FastString -> CLabel Source #
mkRtsCmmDataLabel :: FastString -> CLabel Source #
mkCmmClosureLabel :: UnitId -> FastString -> CLabel Source #
mkRtsApFastLabel :: FastString -> CLabel Source #
mkPrimCallLabel :: PrimCall -> CLabel Source #
mkForeignLabel :: FastString -> Maybe Int -> ForeignLabelSource -> FunctionOrData -> CLabel Source #
Make a foreign label
mkCCLabel :: CostCentre -> CLabel Source #
mkCCSLabel :: CostCentreStack -> CLabel Source #
mkIPELabel :: Module -> CLabel Source #
data InfoProvEnt Source #
Info Table Provenance Entry See Note [Mapping Info Tables to Source Positions]
Constructors
| InfoProvEnt | |
| Fields 
 | |
Instances
| Eq InfoProvEnt Source # | |
| Defined in GHC.Cmm.CLabel | |
| Ord InfoProvEnt Source # | |
| Defined in GHC.Cmm.CLabel Methods compare :: InfoProvEnt -> InfoProvEnt -> Ordering # (<) :: InfoProvEnt -> InfoProvEnt -> Bool # (<=) :: InfoProvEnt -> InfoProvEnt -> Bool # (>) :: InfoProvEnt -> InfoProvEnt -> Bool # (>=) :: InfoProvEnt -> InfoProvEnt -> Bool # max :: InfoProvEnt -> InfoProvEnt -> InfoProvEnt # min :: InfoProvEnt -> InfoProvEnt -> InfoProvEnt # | |
| OutputableP Platform InfoProvEnt Source # | |
| Defined in GHC.Cmm.Ppr | |
mkDeadStripPreventer :: CLabel -> CLabel Source #
mkHpcTicksLabel :: Module -> CLabel Source #
Predicates
needsCDecl :: CLabel -> Bool Source #
externallyVisibleCLabel :: CLabel -> Bool Source #
Is a CLabel visible outside this object file or not? From the point of view of the code generator, a name is externally visible if it has to be declared as exported in the .o file's symbol table; that is, made non-static.
isMathFun :: CLabel -> Bool Source #
Check whether a label corresponds to a C function that has a prototype in a system header somewhere, or is built-in to the C compiler. For these labels we avoid generating our own C prototypes.
isCFunctionLabel :: CLabel -> Bool Source #
isGcPtrLabel :: CLabel -> Bool Source #
labelDynamic :: Module -> Platform -> Bool -> CLabel -> Bool Source #
Does a CLabel need dynamic linkage?
When referring to data in code, we need to know whether
 that data resides in a DLL or not. [Win32 only.]
 labelDynamic returns True if the label is located
 in a DLL, be it a data reference or not.
isInfoTableLabel :: CLabel -> Bool Source #
Whether label is points to some kind of info table
isConInfoTableLabel :: CLabel -> Bool Source #
Whether label is points to constructor info table
isTickyLabel :: CLabel -> Bool Source #
hasIdLabelInfo :: CLabel -> Maybe IdLabelInfo Source #
isBytesLabel :: CLabel -> Bool Source #
Whether label is a top-level string literal
isForeignLabel :: CLabel -> Bool Source #
Whether label is a non-haskell label (defined in C code)
isSomeRODataLabel :: CLabel -> Bool Source #
Whether label is a .rodata label
isStaticClosureLabel :: CLabel -> Bool Source #
Whether label is a static closure label (can come from haskell or cmm)
Conversions
Pretty-printing
data LabelStyle Source #
Style of label pretty-printing.
When we produce C sources or headers, we have to take into account that C compilers transform C labels when they convert them into symbols. For example, they can add prefixes (e.g., "_" on Darwin) or suffixes (size for stdcalls on Windows). So we provide two ways to pretty-print CLabels: C style or Asm style.
Constructors
| CStyle | C label style (used by C and LLVM backends) | 
| AsmStyle | Asm label style (used by NCG backend) | 
Instances
| Show LabelStyle Source # | |
| Defined in GHC.Utils.Outputable | |
| Eq LabelStyle Source # | |
| Defined in GHC.Utils.Outputable | |
| Ord LabelStyle Source # | |
| Defined in GHC.Utils.Outputable Methods compare :: LabelStyle -> LabelStyle -> Ordering # (<) :: LabelStyle -> LabelStyle -> Bool # (<=) :: LabelStyle -> LabelStyle -> Bool # (>) :: LabelStyle -> LabelStyle -> Bool # (>=) :: LabelStyle -> LabelStyle -> Bool # max :: LabelStyle -> LabelStyle -> LabelStyle # min :: LabelStyle -> LabelStyle -> LabelStyle # | |
pprDebugCLabel :: Platform -> CLabel -> SDoc Source #
For debugging problems with the CLabel representation. We can't make a Show instance for CLabel because lots of its components don't have instances. The regular Outputable instance only shows the label name, and not its other info.
Generate a label for a procedure internal to a module (if
 Opt_ExposeAllSymbols is enabled).
 See Note [Internal proc labels].