{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
module GHC.Cmm.CLabel (
CLabel,
ForeignLabelSource(..),
pprDebugCLabel,
mkClosureLabel,
mkSRTLabel,
mkInfoTableLabel,
mkEntryLabel,
mkRednCountsLabel,
mkConInfoTableLabel,
mkApEntryLabel,
mkApInfoTableLabel,
mkClosureTableLabel,
mkBytesLabel,
mkLocalBlockLabel,
mkLocalClosureLabel,
mkLocalInfoTableLabel,
mkLocalClosureTableLabel,
mkBlockInfoTableLabel,
mkBitmapLabel,
mkStringLitLabel,
mkAsmTempLabel,
mkAsmTempDerivedLabel,
mkAsmTempEndLabel,
mkAsmTempDieLabel,
mkDirty_MUT_VAR_Label,
mkNonmovingWriteBarrierEnabledLabel,
mkUpdInfoLabel,
mkBHUpdInfoLabel,
mkIndStaticInfoLabel,
mkMainCapabilityLabel,
mkMAP_FROZEN_CLEAN_infoLabel,
mkMAP_FROZEN_DIRTY_infoLabel,
mkMAP_DIRTY_infoLabel,
mkSMAP_FROZEN_CLEAN_infoLabel,
mkSMAP_FROZEN_DIRTY_infoLabel,
mkSMAP_DIRTY_infoLabel,
mkBadAlignmentLabel,
mkArrWords_infoLabel,
mkSRTInfoLabel,
mkTopTickyCtrLabel,
mkCAFBlackHoleInfoTableLabel,
mkRtsPrimOpLabel,
mkRtsSlowFastTickyCtrLabel,
mkSelectorInfoLabel,
mkSelectorEntryLabel,
mkCmmInfoLabel,
mkCmmEntryLabel,
mkCmmRetInfoLabel,
mkCmmRetLabel,
mkCmmCodeLabel,
mkCmmDataLabel,
mkCmmClosureLabel,
mkRtsApFastLabel,
mkPrimCallLabel,
mkForeignLabel,
addLabelSize,
foreignLabelStdcallInfo,
isBytesLabel,
isForeignLabel,
isSomeRODataLabel,
isStaticClosureLabel,
mkCCLabel, mkCCSLabel,
DynamicLinkerLabelInfo(..),
mkDynamicLinkerLabel,
dynamicLinkerLabelInfo,
mkPicBaseLabel,
mkDeadStripPreventer,
mkHpcTicksLabel,
hasCAF,
needsCDecl, maybeLocalBlockLabel, externallyVisibleCLabel,
isMathFun,
isCFunctionLabel, isGcPtrLabel, labelDynamic,
isLocalCLabel, mayRedirectTo,
toClosureLbl, toSlowEntryLbl, toEntryLbl, toInfoLbl, hasHaskellName,
pprCLabel,
isInfoTableLabel,
isConInfoTableLabel,
isIdLabel, isTickyLabel
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Types.Id.Info
import GHC.Types.Basic
import {-# SOURCE #-} GHC.Cmm.BlockId (BlockId, mkBlockId)
import GHC.Unit
import GHC.Types.Name
import GHC.Types.Unique
import GHC.Builtin.PrimOps
import GHC.Types.CostCentre
import GHC.Utils.Outputable
import GHC.Data.FastString
import GHC.Driver.Session
import GHC.Platform
import GHC.Types.Unique.Set
import GHC.Utils.Misc
import GHC.Core.Ppr ( )
import GHC.CmmToAsm.Config
data CLabel
=
IdLabel
Name
CafInfo
IdLabelInfo
| CmmLabel
Unit
FastString
CmmLabelInfo
| RtsLabel
RtsLabelInfo
| LocalBlockLabel
{-# UNPACK #-} !Unique
| ForeignLabel
FastString
(Maybe Int)
ForeignLabelSource
FunctionOrData
| AsmTempLabel
{-# UNPACK #-} !Unique
| AsmTempDerivedLabel
CLabel
FastString
| StringLitLabel
{-# UNPACK #-} !Unique
| CC_Label CostCentre
| CCS_Label CostCentreStack
| DynamicLinkerLabel DynamicLinkerLabelInfo CLabel
| PicBaseLabel
| DeadStripPreventer CLabel
| HpcTicksLabel Module
| SRTLabel
{-# UNPACK #-} !Unique
| LargeBitmapLabel
{-# UNPACK #-} !Unique
deriving CLabel -> CLabel -> Bool
(CLabel -> CLabel -> Bool)
-> (CLabel -> CLabel -> Bool) -> Eq CLabel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CLabel -> CLabel -> Bool
$c/= :: CLabel -> CLabel -> Bool
== :: CLabel -> CLabel -> Bool
$c== :: CLabel -> CLabel -> Bool
External instance of the constraint type Eq Int
External instance of the constraint type Eq CostCentreStack
External instance of the constraint type Eq CostCentre
Instance of class: Eq of the constraint type Eq CLabel
External instance of the constraint type Eq FunctionOrData
External instance of the constraint type Eq Int
External instance of the constraint type forall a. Eq a => Eq (Maybe a)
External instance of the constraint type Eq Unique
External instance of the constraint type Eq Unique
External instance of the constraint type Eq FastString
External instance of the constraint type Eq FastString
External instance of the constraint type Eq CafInfo
External instance of the constraint type Eq Name
External instance of the constraint type forall unit. Eq unit => Eq (GenModule unit)
External instance of the constraint type Eq Unit
External instance of the constraint type Eq Unit
Instance of class: Eq of the constraint type Eq ForeignLabelSource
Instance of class: Eq of the constraint type Eq IdLabelInfo
Instance of class: Eq of the constraint type Eq RtsLabelInfo
Instance of class: Eq of the constraint type Eq CmmLabelInfo
Instance of class: Eq of the constraint type Eq DynamicLinkerLabelInfo
Instance of class: Eq of the constraint type Eq CLabel
Eq
isIdLabel :: CLabel -> Bool
isIdLabel :: CLabel -> Bool
isIdLabel IdLabel{} = Bool
True
isIdLabel CLabel
_ = Bool
False
isTickyLabel :: CLabel -> Bool
isTickyLabel :: CLabel -> Bool
isTickyLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
RednCounts) = Bool
True
isTickyLabel CLabel
_ = Bool
False
instance Ord CLabel where
compare :: CLabel -> CLabel -> Ordering
compare (IdLabel Name
a1 CafInfo
b1 IdLabelInfo
c1) (IdLabel Name
a2 CafInfo
b2 IdLabelInfo
c2) =
Name -> Name -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Name
compare Name
a1 Name
a2 Ordering -> Ordering -> Ordering
`thenCmp`
CafInfo -> CafInfo -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord CafInfo
compare CafInfo
b1 CafInfo
b2 Ordering -> Ordering -> Ordering
`thenCmp`
IdLabelInfo -> IdLabelInfo -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord IdLabelInfo
compare IdLabelInfo
c1 IdLabelInfo
c2
compare (CmmLabel Unit
a1 FastString
b1 CmmLabelInfo
c1) (CmmLabel Unit
a2 FastString
b2 CmmLabelInfo
c2) =
Unit -> Unit -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Unit
compare Unit
a1 Unit
a2 Ordering -> Ordering -> Ordering
`thenCmp`
FastString -> FastString -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord FastString
compare FastString
b1 FastString
b2 Ordering -> Ordering -> Ordering
`thenCmp`
CmmLabelInfo -> CmmLabelInfo -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord CmmLabelInfo
compare CmmLabelInfo
c1 CmmLabelInfo
c2
compare (RtsLabel RtsLabelInfo
a1) (RtsLabel RtsLabelInfo
a2) = RtsLabelInfo -> RtsLabelInfo -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord RtsLabelInfo
compare RtsLabelInfo
a1 RtsLabelInfo
a2
compare (LocalBlockLabel Unique
u1) (LocalBlockLabel Unique
u2) = Unique -> Unique -> Ordering
nonDetCmpUnique Unique
u1 Unique
u2
compare (ForeignLabel FastString
a1 Maybe Int
b1 ForeignLabelSource
c1 FunctionOrData
d1) (ForeignLabel FastString
a2 Maybe Int
b2 ForeignLabelSource
c2 FunctionOrData
d2) =
FastString -> FastString -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord FastString
compare FastString
a1 FastString
a2 Ordering -> Ordering -> Ordering
`thenCmp`
Maybe Int -> Maybe Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type forall a. Ord a => Ord (Maybe a)
External instance of the constraint type Ord Int
compare Maybe Int
b1 Maybe Int
b2 Ordering -> Ordering -> Ordering
`thenCmp`
ForeignLabelSource -> ForeignLabelSource -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord ForeignLabelSource
compare ForeignLabelSource
c1 ForeignLabelSource
c2 Ordering -> Ordering -> Ordering
`thenCmp`
FunctionOrData -> FunctionOrData -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord FunctionOrData
compare FunctionOrData
d1 FunctionOrData
d2
compare (AsmTempLabel Unique
u1) (AsmTempLabel Unique
u2) = Unique -> Unique -> Ordering
nonDetCmpUnique Unique
u1 Unique
u2
compare (AsmTempDerivedLabel CLabel
a1 FastString
b1) (AsmTempDerivedLabel CLabel
a2 FastString
b2) =
CLabel -> CLabel -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord CLabel
compare CLabel
a1 CLabel
a2 Ordering -> Ordering -> Ordering
`thenCmp`
FastString -> FastString -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord FastString
compare FastString
b1 FastString
b2
compare (StringLitLabel Unique
u1) (StringLitLabel Unique
u2) =
Unique -> Unique -> Ordering
nonDetCmpUnique Unique
u1 Unique
u2
compare (CC_Label CostCentre
a1) (CC_Label CostCentre
a2) =
CostCentre -> CostCentre -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord CostCentre
compare CostCentre
a1 CostCentre
a2
compare (CCS_Label CostCentreStack
a1) (CCS_Label CostCentreStack
a2) =
CostCentreStack -> CostCentreStack -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord CostCentreStack
compare CostCentreStack
a1 CostCentreStack
a2
compare (DynamicLinkerLabel DynamicLinkerLabelInfo
a1 CLabel
b1) (DynamicLinkerLabel DynamicLinkerLabelInfo
a2 CLabel
b2) =
DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord DynamicLinkerLabelInfo
compare DynamicLinkerLabelInfo
a1 DynamicLinkerLabelInfo
a2 Ordering -> Ordering -> Ordering
`thenCmp`
CLabel -> CLabel -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord CLabel
compare CLabel
b1 CLabel
b2
compare CLabel
PicBaseLabel CLabel
PicBaseLabel = Ordering
EQ
compare (DeadStripPreventer CLabel
a1) (DeadStripPreventer CLabel
a2) =
CLabel -> CLabel -> Ordering
forall a. Ord a => a -> a -> Ordering
Instance of class: Ord of the constraint type Ord CLabel
compare CLabel
a1 CLabel
a2
compare (HpcTicksLabel Module
a1) (HpcTicksLabel Module
a2) =
Module -> Module -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type forall unit. Ord unit => Ord (GenModule unit)
External instance of the constraint type Ord Unit
compare Module
a1 Module
a2
compare (SRTLabel Unique
u1) (SRTLabel Unique
u2) =
Unique -> Unique -> Ordering
nonDetCmpUnique Unique
u1 Unique
u2
compare (LargeBitmapLabel Unique
u1) (LargeBitmapLabel Unique
u2) =
Unique -> Unique -> Ordering
nonDetCmpUnique Unique
u1 Unique
u2
compare IdLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ IdLabel{} = Ordering
GT
compare CmmLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ CmmLabel{} = Ordering
GT
compare RtsLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ RtsLabel{} = Ordering
GT
compare LocalBlockLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ LocalBlockLabel{} = Ordering
GT
compare ForeignLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ ForeignLabel{} = Ordering
GT
compare AsmTempLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ AsmTempLabel{} = Ordering
GT
compare AsmTempDerivedLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ AsmTempDerivedLabel{} = Ordering
GT
compare StringLitLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ StringLitLabel{} = Ordering
GT
compare CC_Label{} CLabel
_ = Ordering
LT
compare CLabel
_ CC_Label{} = Ordering
GT
compare CCS_Label{} CLabel
_ = Ordering
LT
compare CLabel
_ CCS_Label{} = Ordering
GT
compare DynamicLinkerLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ DynamicLinkerLabel{} = Ordering
GT
compare PicBaseLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ PicBaseLabel{} = Ordering
GT
compare DeadStripPreventer{} CLabel
_ = Ordering
LT
compare CLabel
_ DeadStripPreventer{} = Ordering
GT
compare HpcTicksLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ HpcTicksLabel{} = Ordering
GT
compare SRTLabel{} CLabel
_ = Ordering
LT
compare CLabel
_ SRTLabel{} = Ordering
GT
data ForeignLabelSource
= ForeignLabelInPackage Unit
| ForeignLabelInExternalPackage
| ForeignLabelInThisPackage
deriving (ForeignLabelSource -> ForeignLabelSource -> Bool
(ForeignLabelSource -> ForeignLabelSource -> Bool)
-> (ForeignLabelSource -> ForeignLabelSource -> Bool)
-> Eq ForeignLabelSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForeignLabelSource -> ForeignLabelSource -> Bool
$c/= :: ForeignLabelSource -> ForeignLabelSource -> Bool
== :: ForeignLabelSource -> ForeignLabelSource -> Bool
$c== :: ForeignLabelSource -> ForeignLabelSource -> Bool
External instance of the constraint type Eq Unit
Eq, Eq ForeignLabelSource
Eq ForeignLabelSource
-> (ForeignLabelSource -> ForeignLabelSource -> Ordering)
-> (ForeignLabelSource -> ForeignLabelSource -> Bool)
-> (ForeignLabelSource -> ForeignLabelSource -> Bool)
-> (ForeignLabelSource -> ForeignLabelSource -> Bool)
-> (ForeignLabelSource -> ForeignLabelSource -> Bool)
-> (ForeignLabelSource -> ForeignLabelSource -> ForeignLabelSource)
-> (ForeignLabelSource -> ForeignLabelSource -> ForeignLabelSource)
-> Ord ForeignLabelSource
ForeignLabelSource -> ForeignLabelSource -> Bool
ForeignLabelSource -> ForeignLabelSource -> Ordering
ForeignLabelSource -> ForeignLabelSource -> ForeignLabelSource
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForeignLabelSource -> ForeignLabelSource -> ForeignLabelSource
$cmin :: ForeignLabelSource -> ForeignLabelSource -> ForeignLabelSource
max :: ForeignLabelSource -> ForeignLabelSource -> ForeignLabelSource
$cmax :: ForeignLabelSource -> ForeignLabelSource -> ForeignLabelSource
>= :: ForeignLabelSource -> ForeignLabelSource -> Bool
$c>= :: ForeignLabelSource -> ForeignLabelSource -> Bool
> :: ForeignLabelSource -> ForeignLabelSource -> Bool
$c> :: ForeignLabelSource -> ForeignLabelSource -> Bool
<= :: ForeignLabelSource -> ForeignLabelSource -> Bool
$c<= :: ForeignLabelSource -> ForeignLabelSource -> Bool
< :: ForeignLabelSource -> ForeignLabelSource -> Bool
$c< :: ForeignLabelSource -> ForeignLabelSource -> Bool
compare :: ForeignLabelSource -> ForeignLabelSource -> Ordering
$ccompare :: ForeignLabelSource -> ForeignLabelSource -> Ordering
Instance of class: Eq of the constraint type Eq ForeignLabelSource
External instance of the constraint type Ord Unit
Instance of class: Ord of the constraint type Ord ForeignLabelSource
Instance of class: Eq of the constraint type Eq ForeignLabelSource
Ord)
pprDebugCLabel :: CLabel -> SDoc
pprDebugCLabel :: CLabel -> SDoc
pprDebugCLabel CLabel
lbl
= case CLabel
lbl of
IdLabel Name
_ CafInfo
_ IdLabelInfo
info-> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> (SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"IdLabel"
SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
whenPprDebug (String -> SDoc
text String
":" SDoc -> SDoc -> SDoc
<> String -> SDoc
text (IdLabelInfo -> String
forall a. Show a => a -> String
Instance of class: Show of the constraint type Show IdLabelInfo
show IdLabelInfo
info)))
CmmLabel Unit
pkg FastString
_name CmmLabelInfo
_info
-> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> (SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"CmmLabel" SDoc -> SDoc -> SDoc
<+> Unit -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Unit
ppr Unit
pkg)
RtsLabel{} -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> (SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"RtsLabel")
ForeignLabel FastString
_name Maybe Int
mSuffix ForeignLabelSource
src FunctionOrData
funOrData
-> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> (SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"ForeignLabel"
SDoc -> SDoc -> SDoc
<+> Maybe Int -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (Maybe a)
External instance of the constraint type Outputable Int
ppr Maybe Int
mSuffix
SDoc -> SDoc -> SDoc
<+> ForeignLabelSource -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable ForeignLabelSource
ppr ForeignLabelSource
src
SDoc -> SDoc -> SDoc
<+> FunctionOrData -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable FunctionOrData
ppr FunctionOrData
funOrData)
CLabel
_ -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> (SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"other CLabel")
data IdLabelInfo
= Closure
| InfoTable
| Entry
| Slow
| LocalInfoTable
| LocalEntry
| RednCounts
| ConEntry
| ConInfoTable
| ClosureTable
| Bytes
| BlockInfoTable
deriving (IdLabelInfo -> IdLabelInfo -> Bool
(IdLabelInfo -> IdLabelInfo -> Bool)
-> (IdLabelInfo -> IdLabelInfo -> Bool) -> Eq IdLabelInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IdLabelInfo -> IdLabelInfo -> Bool
$c/= :: IdLabelInfo -> IdLabelInfo -> Bool
== :: IdLabelInfo -> IdLabelInfo -> Bool
$c== :: IdLabelInfo -> IdLabelInfo -> Bool
Eq, Eq IdLabelInfo
Eq IdLabelInfo
-> (IdLabelInfo -> IdLabelInfo -> Ordering)
-> (IdLabelInfo -> IdLabelInfo -> Bool)
-> (IdLabelInfo -> IdLabelInfo -> Bool)
-> (IdLabelInfo -> IdLabelInfo -> Bool)
-> (IdLabelInfo -> IdLabelInfo -> Bool)
-> (IdLabelInfo -> IdLabelInfo -> IdLabelInfo)
-> (IdLabelInfo -> IdLabelInfo -> IdLabelInfo)
-> Ord IdLabelInfo
IdLabelInfo -> IdLabelInfo -> Bool
IdLabelInfo -> IdLabelInfo -> Ordering
IdLabelInfo -> IdLabelInfo -> IdLabelInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IdLabelInfo -> IdLabelInfo -> IdLabelInfo
$cmin :: IdLabelInfo -> IdLabelInfo -> IdLabelInfo
max :: IdLabelInfo -> IdLabelInfo -> IdLabelInfo
$cmax :: IdLabelInfo -> IdLabelInfo -> IdLabelInfo
>= :: IdLabelInfo -> IdLabelInfo -> Bool
$c>= :: IdLabelInfo -> IdLabelInfo -> Bool
> :: IdLabelInfo -> IdLabelInfo -> Bool
$c> :: IdLabelInfo -> IdLabelInfo -> Bool
<= :: IdLabelInfo -> IdLabelInfo -> Bool
$c<= :: IdLabelInfo -> IdLabelInfo -> Bool
< :: IdLabelInfo -> IdLabelInfo -> Bool
$c< :: IdLabelInfo -> IdLabelInfo -> Bool
compare :: IdLabelInfo -> IdLabelInfo -> Ordering
$ccompare :: IdLabelInfo -> IdLabelInfo -> Ordering
Instance of class: Eq of the constraint type Eq IdLabelInfo
Instance of class: Ord of the constraint type Ord IdLabelInfo
Instance of class: Eq of the constraint type Eq IdLabelInfo
Ord, Int -> IdLabelInfo -> ShowS
[IdLabelInfo] -> ShowS
IdLabelInfo -> String
(Int -> IdLabelInfo -> ShowS)
-> (IdLabelInfo -> String)
-> ([IdLabelInfo] -> ShowS)
-> Show IdLabelInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IdLabelInfo] -> ShowS
$cshowList :: [IdLabelInfo] -> ShowS
show :: IdLabelInfo -> String
$cshow :: IdLabelInfo -> String
showsPrec :: Int -> IdLabelInfo -> ShowS
$cshowsPrec :: Int -> IdLabelInfo -> ShowS
Show)
data RtsLabelInfo
= RtsSelectorInfoTable Bool Int
| RtsSelectorEntry Bool Int
| RtsApInfoTable Bool Int
| RtsApEntry Bool Int
| RtsPrimOp PrimOp
| RtsApFast FastString
| RtsSlowFastTickyCtr String
deriving (RtsLabelInfo -> RtsLabelInfo -> Bool
(RtsLabelInfo -> RtsLabelInfo -> Bool)
-> (RtsLabelInfo -> RtsLabelInfo -> Bool) -> Eq RtsLabelInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RtsLabelInfo -> RtsLabelInfo -> Bool
$c/= :: RtsLabelInfo -> RtsLabelInfo -> Bool
== :: RtsLabelInfo -> RtsLabelInfo -> Bool
$c== :: RtsLabelInfo -> RtsLabelInfo -> Bool
External instance of the constraint type Eq Char
External instance of the constraint type Eq Char
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq PrimOp
External instance of the constraint type Eq Int
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Bool
External instance of the constraint type Eq Int
External instance of the constraint type Eq FastString
Eq, Eq RtsLabelInfo
Eq RtsLabelInfo
-> (RtsLabelInfo -> RtsLabelInfo -> Ordering)
-> (RtsLabelInfo -> RtsLabelInfo -> Bool)
-> (RtsLabelInfo -> RtsLabelInfo -> Bool)
-> (RtsLabelInfo -> RtsLabelInfo -> Bool)
-> (RtsLabelInfo -> RtsLabelInfo -> Bool)
-> (RtsLabelInfo -> RtsLabelInfo -> RtsLabelInfo)
-> (RtsLabelInfo -> RtsLabelInfo -> RtsLabelInfo)
-> Ord RtsLabelInfo
RtsLabelInfo -> RtsLabelInfo -> Bool
RtsLabelInfo -> RtsLabelInfo -> Ordering
RtsLabelInfo -> RtsLabelInfo -> RtsLabelInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RtsLabelInfo -> RtsLabelInfo -> RtsLabelInfo
$cmin :: RtsLabelInfo -> RtsLabelInfo -> RtsLabelInfo
max :: RtsLabelInfo -> RtsLabelInfo -> RtsLabelInfo
$cmax :: RtsLabelInfo -> RtsLabelInfo -> RtsLabelInfo
>= :: RtsLabelInfo -> RtsLabelInfo -> Bool
$c>= :: RtsLabelInfo -> RtsLabelInfo -> Bool
> :: RtsLabelInfo -> RtsLabelInfo -> Bool
$c> :: RtsLabelInfo -> RtsLabelInfo -> Bool
<= :: RtsLabelInfo -> RtsLabelInfo -> Bool
$c<= :: RtsLabelInfo -> RtsLabelInfo -> Bool
< :: RtsLabelInfo -> RtsLabelInfo -> Bool
$c< :: RtsLabelInfo -> RtsLabelInfo -> Bool
compare :: RtsLabelInfo -> RtsLabelInfo -> Ordering
$ccompare :: RtsLabelInfo -> RtsLabelInfo -> Ordering
External instance of the constraint type Ord Char
External instance of the constraint type Ord Char
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type Ord PrimOp
External instance of the constraint type Ord Bool
External instance of the constraint type Ord Bool
Instance of class: Eq of the constraint type Eq RtsLabelInfo
External instance of the constraint type Ord FastString
External instance of the constraint type Ord Int
Instance of class: Eq of the constraint type Eq RtsLabelInfo
Ord)
data CmmLabelInfo
= CmmInfo
| CmmEntry
| CmmRetInfo
| CmmRet
| CmmData
| CmmCode
| CmmClosure
| CmmPrimCall
deriving (CmmLabelInfo -> CmmLabelInfo -> Bool
(CmmLabelInfo -> CmmLabelInfo -> Bool)
-> (CmmLabelInfo -> CmmLabelInfo -> Bool) -> Eq CmmLabelInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CmmLabelInfo -> CmmLabelInfo -> Bool
$c/= :: CmmLabelInfo -> CmmLabelInfo -> Bool
== :: CmmLabelInfo -> CmmLabelInfo -> Bool
$c== :: CmmLabelInfo -> CmmLabelInfo -> Bool
Eq, Eq CmmLabelInfo
Eq CmmLabelInfo
-> (CmmLabelInfo -> CmmLabelInfo -> Ordering)
-> (CmmLabelInfo -> CmmLabelInfo -> Bool)
-> (CmmLabelInfo -> CmmLabelInfo -> Bool)
-> (CmmLabelInfo -> CmmLabelInfo -> Bool)
-> (CmmLabelInfo -> CmmLabelInfo -> Bool)
-> (CmmLabelInfo -> CmmLabelInfo -> CmmLabelInfo)
-> (CmmLabelInfo -> CmmLabelInfo -> CmmLabelInfo)
-> Ord CmmLabelInfo
CmmLabelInfo -> CmmLabelInfo -> Bool
CmmLabelInfo -> CmmLabelInfo -> Ordering
CmmLabelInfo -> CmmLabelInfo -> CmmLabelInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CmmLabelInfo -> CmmLabelInfo -> CmmLabelInfo
$cmin :: CmmLabelInfo -> CmmLabelInfo -> CmmLabelInfo
max :: CmmLabelInfo -> CmmLabelInfo -> CmmLabelInfo
$cmax :: CmmLabelInfo -> CmmLabelInfo -> CmmLabelInfo
>= :: CmmLabelInfo -> CmmLabelInfo -> Bool
$c>= :: CmmLabelInfo -> CmmLabelInfo -> Bool
> :: CmmLabelInfo -> CmmLabelInfo -> Bool
$c> :: CmmLabelInfo -> CmmLabelInfo -> Bool
<= :: CmmLabelInfo -> CmmLabelInfo -> Bool
$c<= :: CmmLabelInfo -> CmmLabelInfo -> Bool
< :: CmmLabelInfo -> CmmLabelInfo -> Bool
$c< :: CmmLabelInfo -> CmmLabelInfo -> Bool
compare :: CmmLabelInfo -> CmmLabelInfo -> Ordering
$ccompare :: CmmLabelInfo -> CmmLabelInfo -> Ordering
Instance of class: Eq of the constraint type Eq CmmLabelInfo
Instance of class: Ord of the constraint type Ord CmmLabelInfo
Instance of class: Eq of the constraint type Eq CmmLabelInfo
Ord)
data DynamicLinkerLabelInfo
= CodeStub
| SymbolPtr
| GotSymbolPtr
| GotSymbolOffset
deriving (DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
(DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool)
-> (DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool)
-> Eq DynamicLinkerLabelInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
$c/= :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
== :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
$c== :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
Eq, Eq DynamicLinkerLabelInfo
Eq DynamicLinkerLabelInfo
-> (DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Ordering)
-> (DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool)
-> (DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool)
-> (DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool)
-> (DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool)
-> (DynamicLinkerLabelInfo
-> DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo)
-> (DynamicLinkerLabelInfo
-> DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo)
-> Ord DynamicLinkerLabelInfo
DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Ordering
DynamicLinkerLabelInfo
-> DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DynamicLinkerLabelInfo
-> DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo
$cmin :: DynamicLinkerLabelInfo
-> DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo
max :: DynamicLinkerLabelInfo
-> DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo
$cmax :: DynamicLinkerLabelInfo
-> DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo
>= :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
$c>= :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
> :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
$c> :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
<= :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
$c<= :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
< :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
$c< :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Bool
compare :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Ordering
$ccompare :: DynamicLinkerLabelInfo -> DynamicLinkerLabelInfo -> Ordering
Instance of class: Eq of the constraint type Eq DynamicLinkerLabelInfo
Instance of class: Ord of the constraint type Ord DynamicLinkerLabelInfo
Instance of class: Eq of the constraint type Eq DynamicLinkerLabelInfo
Ord)
mkSRTLabel :: Unique -> CLabel
mkSRTLabel :: Unique -> CLabel
mkSRTLabel Unique
u = Unique -> CLabel
SRTLabel Unique
u
mkRednCountsLabel :: Name -> CLabel
mkRednCountsLabel :: Name -> CLabel
mkRednCountsLabel Name
name = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
NoCafRefs IdLabelInfo
RednCounts
mkLocalClosureLabel :: Name -> CafInfo -> CLabel
mkLocalInfoTableLabel :: Name -> CafInfo -> CLabel
mkLocalClosureTableLabel :: Name -> CafInfo -> CLabel
mkLocalClosureLabel :: Name -> CafInfo -> CLabel
mkLocalClosureLabel !Name
name !CafInfo
c = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
c IdLabelInfo
Closure
mkLocalInfoTableLabel :: Name -> CafInfo -> CLabel
mkLocalInfoTableLabel Name
name CafInfo
c = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
c IdLabelInfo
LocalInfoTable
mkLocalClosureTableLabel :: Name -> CafInfo -> CLabel
mkLocalClosureTableLabel Name
name CafInfo
c = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
c IdLabelInfo
ClosureTable
mkClosureLabel :: Name -> CafInfo -> CLabel
mkInfoTableLabel :: Name -> CafInfo -> CLabel
mkEntryLabel :: Name -> CafInfo -> CLabel
mkClosureTableLabel :: Name -> CafInfo -> CLabel
mkConInfoTableLabel :: Name -> CafInfo -> CLabel
mkBytesLabel :: Name -> CLabel
mkClosureLabel :: Name -> CafInfo -> CLabel
mkClosureLabel Name
name CafInfo
c = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
c IdLabelInfo
Closure
mkInfoTableLabel :: Name -> CafInfo -> CLabel
mkInfoTableLabel Name
name CafInfo
c = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
c IdLabelInfo
InfoTable
mkEntryLabel :: Name -> CafInfo -> CLabel
mkEntryLabel Name
name CafInfo
c = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
c IdLabelInfo
Entry
mkClosureTableLabel :: Name -> CafInfo -> CLabel
mkClosureTableLabel Name
name CafInfo
c = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
c IdLabelInfo
ClosureTable
mkConInfoTableLabel :: Name -> CafInfo -> CLabel
mkConInfoTableLabel Name
name CafInfo
c = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
c IdLabelInfo
ConInfoTable
mkBytesLabel :: Name -> CLabel
mkBytesLabel Name
name = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
NoCafRefs IdLabelInfo
Bytes
mkBlockInfoTableLabel :: Name -> CafInfo -> CLabel
mkBlockInfoTableLabel :: Name -> CafInfo -> CLabel
mkBlockInfoTableLabel Name
name CafInfo
c = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
name CafInfo
c IdLabelInfo
BlockInfoTable
mkDirty_MUT_VAR_Label,
mkNonmovingWriteBarrierEnabledLabel,
mkUpdInfoLabel,
mkBHUpdInfoLabel, mkIndStaticInfoLabel, mkMainCapabilityLabel,
mkMAP_FROZEN_CLEAN_infoLabel, mkMAP_FROZEN_DIRTY_infoLabel,
mkMAP_DIRTY_infoLabel,
mkArrWords_infoLabel,
mkTopTickyCtrLabel,
mkCAFBlackHoleInfoTableLabel,
mkSMAP_FROZEN_CLEAN_infoLabel, mkSMAP_FROZEN_DIRTY_infoLabel,
mkSMAP_DIRTY_infoLabel, mkBadAlignmentLabel :: CLabel
mkDirty_MUT_VAR_Label :: CLabel
mkDirty_MUT_VAR_Label = FastString
-> Maybe Int -> ForeignLabelSource -> FunctionOrData -> CLabel
mkForeignLabel (String -> FastString
fsLit String
"dirty_MUT_VAR") Maybe Int
forall a. Maybe a
Nothing ForeignLabelSource
ForeignLabelInExternalPackage FunctionOrData
IsFunction
mkNonmovingWriteBarrierEnabledLabel :: CLabel
mkNonmovingWriteBarrierEnabledLabel
= Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"nonmoving_write_barrier_enabled") CmmLabelInfo
CmmData
mkUpdInfoLabel :: CLabel
mkUpdInfoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_upd_frame") CmmLabelInfo
CmmInfo
mkBHUpdInfoLabel :: CLabel
mkBHUpdInfoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_bh_upd_frame" ) CmmLabelInfo
CmmInfo
mkIndStaticInfoLabel :: CLabel
mkIndStaticInfoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_IND_STATIC") CmmLabelInfo
CmmInfo
mkMainCapabilityLabel :: CLabel
mkMainCapabilityLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"MainCapability") CmmLabelInfo
CmmData
mkMAP_FROZEN_CLEAN_infoLabel :: CLabel
mkMAP_FROZEN_CLEAN_infoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_MUT_ARR_PTRS_FROZEN_CLEAN") CmmLabelInfo
CmmInfo
mkMAP_FROZEN_DIRTY_infoLabel :: CLabel
mkMAP_FROZEN_DIRTY_infoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_MUT_ARR_PTRS_FROZEN_DIRTY") CmmLabelInfo
CmmInfo
mkMAP_DIRTY_infoLabel :: CLabel
mkMAP_DIRTY_infoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_MUT_ARR_PTRS_DIRTY") CmmLabelInfo
CmmInfo
mkTopTickyCtrLabel :: CLabel
mkTopTickyCtrLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"top_ct") CmmLabelInfo
CmmData
mkCAFBlackHoleInfoTableLabel :: CLabel
mkCAFBlackHoleInfoTableLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_CAF_BLACKHOLE") CmmLabelInfo
CmmInfo
mkArrWords_infoLabel :: CLabel
mkArrWords_infoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_ARR_WORDS") CmmLabelInfo
CmmInfo
mkSMAP_FROZEN_CLEAN_infoLabel :: CLabel
mkSMAP_FROZEN_CLEAN_infoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_SMALL_MUT_ARR_PTRS_FROZEN_CLEAN") CmmLabelInfo
CmmInfo
mkSMAP_FROZEN_DIRTY_infoLabel :: CLabel
mkSMAP_FROZEN_DIRTY_infoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_SMALL_MUT_ARR_PTRS_FROZEN_DIRTY") CmmLabelInfo
CmmInfo
mkSMAP_DIRTY_infoLabel :: CLabel
mkSMAP_DIRTY_infoLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_SMALL_MUT_ARR_PTRS_DIRTY") CmmLabelInfo
CmmInfo
mkBadAlignmentLabel :: CLabel
mkBadAlignmentLabel = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId (String -> FastString
fsLit String
"stg_badAlignment") CmmLabelInfo
CmmEntry
mkSRTInfoLabel :: Int -> CLabel
mkSRTInfoLabel :: Int -> CLabel
mkSRTInfoLabel Int
n = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
rtsUnitId FastString
lbl CmmLabelInfo
CmmInfo
where
lbl :: FastString
lbl =
case Int
n of
Int
1 -> String -> FastString
fsLit String
"stg_SRT_1"
Int
2 -> String -> FastString
fsLit String
"stg_SRT_2"
Int
3 -> String -> FastString
fsLit String
"stg_SRT_3"
Int
4 -> String -> FastString
fsLit String
"stg_SRT_4"
Int
5 -> String -> FastString
fsLit String
"stg_SRT_5"
Int
6 -> String -> FastString
fsLit String
"stg_SRT_6"
Int
7 -> String -> FastString
fsLit String
"stg_SRT_7"
Int
8 -> String -> FastString
fsLit String
"stg_SRT_8"
Int
9 -> String -> FastString
fsLit String
"stg_SRT_9"
Int
10 -> String -> FastString
fsLit String
"stg_SRT_10"
Int
11 -> String -> FastString
fsLit String
"stg_SRT_11"
Int
12 -> String -> FastString
fsLit String
"stg_SRT_12"
Int
13 -> String -> FastString
fsLit String
"stg_SRT_13"
Int
14 -> String -> FastString
fsLit String
"stg_SRT_14"
Int
15 -> String -> FastString
fsLit String
"stg_SRT_15"
Int
16 -> String -> FastString
fsLit String
"stg_SRT_16"
Int
_ -> String -> FastString
forall a. String -> a
panic String
"mkSRTInfoLabel"
mkCmmInfoLabel, mkCmmEntryLabel, mkCmmRetInfoLabel, mkCmmRetLabel,
mkCmmCodeLabel, mkCmmDataLabel, mkCmmClosureLabel
:: Unit -> FastString -> CLabel
mkCmmInfoLabel :: Unit -> FastString -> CLabel
mkCmmInfoLabel Unit
pkg FastString
str = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
pkg FastString
str CmmLabelInfo
CmmInfo
mkCmmEntryLabel :: Unit -> FastString -> CLabel
mkCmmEntryLabel Unit
pkg FastString
str = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
pkg FastString
str CmmLabelInfo
CmmEntry
mkCmmRetInfoLabel :: Unit -> FastString -> CLabel
mkCmmRetInfoLabel Unit
pkg FastString
str = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
pkg FastString
str CmmLabelInfo
CmmRetInfo
mkCmmRetLabel :: Unit -> FastString -> CLabel
mkCmmRetLabel Unit
pkg FastString
str = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
pkg FastString
str CmmLabelInfo
CmmRet
mkCmmCodeLabel :: Unit -> FastString -> CLabel
mkCmmCodeLabel Unit
pkg FastString
str = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
pkg FastString
str CmmLabelInfo
CmmCode
mkCmmDataLabel :: Unit -> FastString -> CLabel
mkCmmDataLabel Unit
pkg FastString
str = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
pkg FastString
str CmmLabelInfo
CmmData
mkCmmClosureLabel :: Unit -> FastString -> CLabel
mkCmmClosureLabel Unit
pkg FastString
str = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
pkg FastString
str CmmLabelInfo
CmmClosure
mkLocalBlockLabel :: Unique -> CLabel
mkLocalBlockLabel :: Unique -> CLabel
mkLocalBlockLabel Unique
u = Unique -> CLabel
LocalBlockLabel Unique
u
mkRtsPrimOpLabel :: PrimOp -> CLabel
mkRtsPrimOpLabel :: PrimOp -> CLabel
mkRtsPrimOpLabel PrimOp
primop = RtsLabelInfo -> CLabel
RtsLabel (PrimOp -> RtsLabelInfo
RtsPrimOp PrimOp
primop)
mkSelectorInfoLabel :: Bool -> Int -> CLabel
mkSelectorEntryLabel :: Bool -> Int -> CLabel
mkSelectorInfoLabel :: Bool -> Int -> CLabel
mkSelectorInfoLabel Bool
upd Int
off = RtsLabelInfo -> CLabel
RtsLabel (Bool -> Int -> RtsLabelInfo
RtsSelectorInfoTable Bool
upd Int
off)
mkSelectorEntryLabel :: Bool -> Int -> CLabel
mkSelectorEntryLabel Bool
upd Int
off = RtsLabelInfo -> CLabel
RtsLabel (Bool -> Int -> RtsLabelInfo
RtsSelectorEntry Bool
upd Int
off)
mkApInfoTableLabel :: Bool -> Int -> CLabel
mkApEntryLabel :: Bool -> Int -> CLabel
mkApInfoTableLabel :: Bool -> Int -> CLabel
mkApInfoTableLabel Bool
upd Int
off = RtsLabelInfo -> CLabel
RtsLabel (Bool -> Int -> RtsLabelInfo
RtsApInfoTable Bool
upd Int
off)
mkApEntryLabel :: Bool -> Int -> CLabel
mkApEntryLabel Bool
upd Int
off = RtsLabelInfo -> CLabel
RtsLabel (Bool -> Int -> RtsLabelInfo
RtsApEntry Bool
upd Int
off)
mkPrimCallLabel :: PrimCall -> CLabel
mkPrimCallLabel :: PrimCall -> CLabel
mkPrimCallLabel (PrimCall FastString
str Unit
pkg)
= Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
pkg FastString
str CmmLabelInfo
CmmPrimCall
mkForeignLabel
:: FastString
-> Maybe Int
-> ForeignLabelSource
-> FunctionOrData
-> CLabel
mkForeignLabel :: FastString
-> Maybe Int -> ForeignLabelSource -> FunctionOrData -> CLabel
mkForeignLabel = FastString
-> Maybe Int -> ForeignLabelSource -> FunctionOrData -> CLabel
ForeignLabel
addLabelSize :: CLabel -> Int -> CLabel
addLabelSize :: CLabel -> Int -> CLabel
addLabelSize (ForeignLabel FastString
str Maybe Int
_ ForeignLabelSource
src FunctionOrData
fod) Int
sz
= FastString
-> Maybe Int -> ForeignLabelSource -> FunctionOrData -> CLabel
ForeignLabel FastString
str (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
sz) ForeignLabelSource
src FunctionOrData
fod
addLabelSize CLabel
label Int
_
= CLabel
label
isBytesLabel :: CLabel -> Bool
isBytesLabel :: CLabel -> Bool
isBytesLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
Bytes) = Bool
True
isBytesLabel CLabel
_lbl = Bool
False
isForeignLabel :: CLabel -> Bool
isForeignLabel :: CLabel -> Bool
isForeignLabel (ForeignLabel FastString
_ Maybe Int
_ ForeignLabelSource
_ FunctionOrData
_) = Bool
True
isForeignLabel CLabel
_lbl = Bool
False
isStaticClosureLabel :: CLabel -> Bool
isStaticClosureLabel :: CLabel -> Bool
isStaticClosureLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
Closure) = Bool
True
isStaticClosureLabel (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmClosure) = Bool
True
isStaticClosureLabel CLabel
_lbl = Bool
False
isSomeRODataLabel :: CLabel -> Bool
isSomeRODataLabel :: CLabel -> Bool
isSomeRODataLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
ClosureTable) = Bool
True
isSomeRODataLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
ConInfoTable) = Bool
True
isSomeRODataLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
InfoTable) = Bool
True
isSomeRODataLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
LocalInfoTable) = Bool
True
isSomeRODataLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
BlockInfoTable) = Bool
True
isSomeRODataLabel (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmInfo) = Bool
True
isSomeRODataLabel CLabel
_lbl = Bool
False
isInfoTableLabel :: CLabel -> Bool
isInfoTableLabel :: CLabel -> Bool
isInfoTableLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
InfoTable) = Bool
True
isInfoTableLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
LocalInfoTable) = Bool
True
isInfoTableLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
ConInfoTable) = Bool
True
isInfoTableLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
BlockInfoTable) = Bool
True
isInfoTableLabel CLabel
_ = Bool
False
isConInfoTableLabel :: CLabel -> Bool
isConInfoTableLabel :: CLabel -> Bool
isConInfoTableLabel (IdLabel Name
_ CafInfo
_ IdLabelInfo
ConInfoTable) = Bool
True
isConInfoTableLabel CLabel
_ = Bool
False
foreignLabelStdcallInfo :: CLabel -> Maybe Int
foreignLabelStdcallInfo :: CLabel -> Maybe Int
foreignLabelStdcallInfo (ForeignLabel FastString
_ Maybe Int
info ForeignLabelSource
_ FunctionOrData
_) = Maybe Int
info
foreignLabelStdcallInfo CLabel
_lbl = Maybe Int
forall a. Maybe a
Nothing
mkBitmapLabel :: Unique -> CLabel
mkBitmapLabel :: Unique -> CLabel
mkBitmapLabel Unique
uniq = Unique -> CLabel
LargeBitmapLabel Unique
uniq
mkCCLabel :: CostCentre -> CLabel
mkCCSLabel :: CostCentreStack -> CLabel
mkCCLabel :: CostCentre -> CLabel
mkCCLabel CostCentre
cc = CostCentre -> CLabel
CC_Label CostCentre
cc
mkCCSLabel :: CostCentreStack -> CLabel
mkCCSLabel CostCentreStack
ccs = CostCentreStack -> CLabel
CCS_Label CostCentreStack
ccs
mkRtsApFastLabel :: FastString -> CLabel
mkRtsApFastLabel :: FastString -> CLabel
mkRtsApFastLabel FastString
str = RtsLabelInfo -> CLabel
RtsLabel (FastString -> RtsLabelInfo
RtsApFast FastString
str)
mkRtsSlowFastTickyCtrLabel :: String -> CLabel
mkRtsSlowFastTickyCtrLabel :: String -> CLabel
mkRtsSlowFastTickyCtrLabel String
pat = RtsLabelInfo -> CLabel
RtsLabel (String -> RtsLabelInfo
RtsSlowFastTickyCtr String
pat)
mkHpcTicksLabel :: Module -> CLabel
mkHpcTicksLabel :: Module -> CLabel
mkHpcTicksLabel = Module -> CLabel
HpcTicksLabel
mkDynamicLinkerLabel :: DynamicLinkerLabelInfo -> CLabel -> CLabel
mkDynamicLinkerLabel :: DynamicLinkerLabelInfo -> CLabel -> CLabel
mkDynamicLinkerLabel = DynamicLinkerLabelInfo -> CLabel -> CLabel
DynamicLinkerLabel
dynamicLinkerLabelInfo :: CLabel -> Maybe (DynamicLinkerLabelInfo, CLabel)
dynamicLinkerLabelInfo :: CLabel -> Maybe (DynamicLinkerLabelInfo, CLabel)
dynamicLinkerLabelInfo (DynamicLinkerLabel DynamicLinkerLabelInfo
info CLabel
lbl) = (DynamicLinkerLabelInfo, CLabel)
-> Maybe (DynamicLinkerLabelInfo, CLabel)
forall a. a -> Maybe a
Just (DynamicLinkerLabelInfo
info, CLabel
lbl)
dynamicLinkerLabelInfo CLabel
_ = Maybe (DynamicLinkerLabelInfo, CLabel)
forall a. Maybe a
Nothing
mkPicBaseLabel :: CLabel
mkPicBaseLabel :: CLabel
mkPicBaseLabel = CLabel
PicBaseLabel
mkDeadStripPreventer :: CLabel -> CLabel
mkDeadStripPreventer :: CLabel -> CLabel
mkDeadStripPreventer CLabel
lbl = CLabel -> CLabel
DeadStripPreventer CLabel
lbl
mkStringLitLabel :: Unique -> CLabel
mkStringLitLabel :: Unique -> CLabel
mkStringLitLabel = Unique -> CLabel
StringLitLabel
mkAsmTempLabel :: Uniquable a => a -> CLabel
mkAsmTempLabel :: a -> CLabel
mkAsmTempLabel a
a = Unique -> CLabel
AsmTempLabel (a -> Unique
forall a. Uniquable a => a -> Unique
Evidence bound by a type signature of the constraint type Uniquable a
getUnique a
a)
mkAsmTempDerivedLabel :: CLabel -> FastString -> CLabel
mkAsmTempDerivedLabel :: CLabel -> FastString -> CLabel
mkAsmTempDerivedLabel = CLabel -> FastString -> CLabel
AsmTempDerivedLabel
mkAsmTempEndLabel :: CLabel -> CLabel
mkAsmTempEndLabel :: CLabel -> CLabel
mkAsmTempEndLabel CLabel
l = CLabel -> FastString -> CLabel
mkAsmTempDerivedLabel CLabel
l (String -> FastString
fsLit String
"_end")
mkAsmTempDieLabel :: CLabel -> CLabel
mkAsmTempDieLabel :: CLabel -> CLabel
mkAsmTempDieLabel CLabel
l = CLabel -> FastString -> CLabel
mkAsmTempDerivedLabel CLabel
l (String -> FastString
fsLit String
"_die")
toClosureLbl :: CLabel -> CLabel
toClosureLbl :: CLabel -> CLabel
toClosureLbl (IdLabel Name
n CafInfo
c IdLabelInfo
_) = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
n CafInfo
c IdLabelInfo
Closure
toClosureLbl (CmmLabel Unit
m FastString
str CmmLabelInfo
_) = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
m FastString
str CmmLabelInfo
CmmClosure
toClosureLbl CLabel
l = String -> SDoc -> CLabel
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"toClosureLbl" (CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
l)
toSlowEntryLbl :: CLabel -> CLabel
toSlowEntryLbl :: CLabel -> CLabel
toSlowEntryLbl (IdLabel Name
n CafInfo
_ IdLabelInfo
BlockInfoTable)
= String -> SDoc -> CLabel
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"toSlowEntryLbl" (Name -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Name
ppr Name
n)
toSlowEntryLbl (IdLabel Name
n CafInfo
c IdLabelInfo
_) = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
n CafInfo
c IdLabelInfo
Slow
toSlowEntryLbl CLabel
l = String -> SDoc -> CLabel
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"toSlowEntryLbl" (CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
l)
toEntryLbl :: CLabel -> CLabel
toEntryLbl :: CLabel -> CLabel
toEntryLbl (IdLabel Name
n CafInfo
c IdLabelInfo
LocalInfoTable) = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
n CafInfo
c IdLabelInfo
LocalEntry
toEntryLbl (IdLabel Name
n CafInfo
c IdLabelInfo
ConInfoTable) = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
n CafInfo
c IdLabelInfo
ConEntry
toEntryLbl (IdLabel Name
n CafInfo
_ IdLabelInfo
BlockInfoTable) = Unique -> CLabel
mkLocalBlockLabel (Name -> Unique
nameUnique Name
n)
toEntryLbl (IdLabel Name
n CafInfo
c IdLabelInfo
_) = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
n CafInfo
c IdLabelInfo
Entry
toEntryLbl (CmmLabel Unit
m FastString
str CmmLabelInfo
CmmInfo) = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
m FastString
str CmmLabelInfo
CmmEntry
toEntryLbl (CmmLabel Unit
m FastString
str CmmLabelInfo
CmmRetInfo) = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
m FastString
str CmmLabelInfo
CmmRet
toEntryLbl CLabel
l = String -> SDoc -> CLabel
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"toEntryLbl" (CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
l)
toInfoLbl :: CLabel -> CLabel
toInfoLbl :: CLabel -> CLabel
toInfoLbl (IdLabel Name
n CafInfo
c IdLabelInfo
LocalEntry) = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
n CafInfo
c IdLabelInfo
LocalInfoTable
toInfoLbl (IdLabel Name
n CafInfo
c IdLabelInfo
ConEntry) = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
n CafInfo
c IdLabelInfo
ConInfoTable
toInfoLbl (IdLabel Name
n CafInfo
c IdLabelInfo
_) = Name -> CafInfo -> IdLabelInfo -> CLabel
IdLabel Name
n CafInfo
c IdLabelInfo
InfoTable
toInfoLbl (CmmLabel Unit
m FastString
str CmmLabelInfo
CmmEntry) = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
m FastString
str CmmLabelInfo
CmmInfo
toInfoLbl (CmmLabel Unit
m FastString
str CmmLabelInfo
CmmRet) = Unit -> FastString -> CmmLabelInfo -> CLabel
CmmLabel Unit
m FastString
str CmmLabelInfo
CmmRetInfo
toInfoLbl CLabel
l = String -> SDoc -> CLabel
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"CLabel.toInfoLbl" (CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
l)
hasHaskellName :: CLabel -> Maybe Name
hasHaskellName :: CLabel -> Maybe Name
hasHaskellName (IdLabel Name
n CafInfo
_ IdLabelInfo
_) = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
n
hasHaskellName CLabel
_ = Maybe Name
forall a. Maybe a
Nothing
hasCAF :: CLabel -> Bool
hasCAF :: CLabel -> Bool
hasCAF (IdLabel Name
_ CafInfo
_ IdLabelInfo
RednCounts) = Bool
False
hasCAF (IdLabel Name
_ CafInfo
MayHaveCafRefs IdLabelInfo
_) = Bool
True
hasCAF CLabel
_ = Bool
False
needsCDecl :: CLabel -> Bool
needsCDecl :: CLabel -> Bool
needsCDecl (SRTLabel Unique
_) = Bool
True
needsCDecl (LargeBitmapLabel Unique
_) = Bool
False
needsCDecl (IdLabel Name
_ CafInfo
_ IdLabelInfo
_) = Bool
True
needsCDecl (LocalBlockLabel Unique
_) = Bool
True
needsCDecl (StringLitLabel Unique
_) = Bool
False
needsCDecl (AsmTempLabel Unique
_) = Bool
False
needsCDecl (AsmTempDerivedLabel CLabel
_ FastString
_) = Bool
False
needsCDecl (RtsLabel RtsLabelInfo
_) = Bool
False
needsCDecl (CmmLabel Unit
pkgId FastString
_ CmmLabelInfo
_)
| Unit
pkgId Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Unit
== Unit
rtsUnitId = Bool
False
| Bool
otherwise = Bool
True
needsCDecl l :: CLabel
l@(ForeignLabel{}) = Bool -> Bool
not (CLabel -> Bool
isMathFun CLabel
l)
needsCDecl (CC_Label CostCentre
_) = Bool
True
needsCDecl (CCS_Label CostCentreStack
_) = Bool
True
needsCDecl (HpcTicksLabel Module
_) = Bool
True
needsCDecl (DynamicLinkerLabel {}) = String -> Bool
forall a. String -> a
panic String
"needsCDecl DynamicLinkerLabel"
needsCDecl CLabel
PicBaseLabel = String -> Bool
forall a. String -> a
panic String
"needsCDecl PicBaseLabel"
needsCDecl (DeadStripPreventer {}) = String -> Bool
forall a. String -> a
panic String
"needsCDecl DeadStripPreventer"
maybeLocalBlockLabel :: CLabel -> Maybe BlockId
maybeLocalBlockLabel :: CLabel -> Maybe BlockId
maybeLocalBlockLabel (LocalBlockLabel Unique
uq) = BlockId -> Maybe BlockId
forall a. a -> Maybe a
Just (BlockId -> Maybe BlockId) -> BlockId -> Maybe BlockId
forall a b. (a -> b) -> a -> b
$ Unique -> BlockId
mkBlockId Unique
uq
maybeLocalBlockLabel CLabel
_ = Maybe BlockId
forall a. Maybe a
Nothing
isMathFun :: CLabel -> Bool
isMathFun :: CLabel -> Bool
isMathFun (ForeignLabel FastString
fs Maybe Int
_ ForeignLabelSource
_ FunctionOrData
_) = FastString
fs FastString -> UniqSet FastString -> Bool
forall a. Uniquable a => a -> UniqSet a -> Bool
External instance of the constraint type Uniquable FastString
`elementOfUniqSet` UniqSet FastString
math_funs
isMathFun CLabel
_ = Bool
False
math_funs :: UniqSet FastString
math_funs :: UniqSet FastString
math_funs = [FastString] -> UniqSet FastString
forall a. Uniquable a => [a] -> UniqSet a
External instance of the constraint type Uniquable FastString
mkUniqSet [
(String -> FastString
fsLit String
"acos"), (String -> FastString
fsLit String
"acosf"), (String -> FastString
fsLit String
"acosh"),
(String -> FastString
fsLit String
"acoshf"), (String -> FastString
fsLit String
"acoshl"), (String -> FastString
fsLit String
"acosl"),
(String -> FastString
fsLit String
"asin"), (String -> FastString
fsLit String
"asinf"), (String -> FastString
fsLit String
"asinl"),
(String -> FastString
fsLit String
"asinh"), (String -> FastString
fsLit String
"asinhf"), (String -> FastString
fsLit String
"asinhl"),
(String -> FastString
fsLit String
"atan"), (String -> FastString
fsLit String
"atanf"), (String -> FastString
fsLit String
"atanl"),
(String -> FastString
fsLit String
"atan2"), (String -> FastString
fsLit String
"atan2f"), (String -> FastString
fsLit String
"atan2l"),
(String -> FastString
fsLit String
"atanh"), (String -> FastString
fsLit String
"atanhf"), (String -> FastString
fsLit String
"atanhl"),
(String -> FastString
fsLit String
"cbrt"), (String -> FastString
fsLit String
"cbrtf"), (String -> FastString
fsLit String
"cbrtl"),
(String -> FastString
fsLit String
"ceil"), (String -> FastString
fsLit String
"ceilf"), (String -> FastString
fsLit String
"ceill"),
(String -> FastString
fsLit String
"copysign"), (String -> FastString
fsLit String
"copysignf"), (String -> FastString
fsLit String
"copysignl"),
(String -> FastString
fsLit String
"cos"), (String -> FastString
fsLit String
"cosf"), (String -> FastString
fsLit String
"cosl"),
(String -> FastString
fsLit String
"cosh"), (String -> FastString
fsLit String
"coshf"), (String -> FastString
fsLit String
"coshl"),
(String -> FastString
fsLit String
"erf"), (String -> FastString
fsLit String
"erff"), (String -> FastString
fsLit String
"erfl"),
(String -> FastString
fsLit String
"erfc"), (String -> FastString
fsLit String
"erfcf"), (String -> FastString
fsLit String
"erfcl"),
(String -> FastString
fsLit String
"exp"), (String -> FastString
fsLit String
"expf"), (String -> FastString
fsLit String
"expl"),
(String -> FastString
fsLit String
"exp2"), (String -> FastString
fsLit String
"exp2f"), (String -> FastString
fsLit String
"exp2l"),
(String -> FastString
fsLit String
"expm1"), (String -> FastString
fsLit String
"expm1f"), (String -> FastString
fsLit String
"expm1l"),
(String -> FastString
fsLit String
"fabs"), (String -> FastString
fsLit String
"fabsf"), (String -> FastString
fsLit String
"fabsl"),
(String -> FastString
fsLit String
"fdim"), (String -> FastString
fsLit String
"fdimf"), (String -> FastString
fsLit String
"fdiml"),
(String -> FastString
fsLit String
"floor"), (String -> FastString
fsLit String
"floorf"), (String -> FastString
fsLit String
"floorl"),
(String -> FastString
fsLit String
"fma"), (String -> FastString
fsLit String
"fmaf"), (String -> FastString
fsLit String
"fmal"),
(String -> FastString
fsLit String
"fmax"), (String -> FastString
fsLit String
"fmaxf"), (String -> FastString
fsLit String
"fmaxl"),
(String -> FastString
fsLit String
"fmin"), (String -> FastString
fsLit String
"fminf"), (String -> FastString
fsLit String
"fminl"),
(String -> FastString
fsLit String
"fmod"), (String -> FastString
fsLit String
"fmodf"), (String -> FastString
fsLit String
"fmodl"),
(String -> FastString
fsLit String
"frexp"), (String -> FastString
fsLit String
"frexpf"), (String -> FastString
fsLit String
"frexpl"),
(String -> FastString
fsLit String
"hypot"), (String -> FastString
fsLit String
"hypotf"), (String -> FastString
fsLit String
"hypotl"),
(String -> FastString
fsLit String
"ilogb"), (String -> FastString
fsLit String
"ilogbf"), (String -> FastString
fsLit String
"ilogbl"),
(String -> FastString
fsLit String
"ldexp"), (String -> FastString
fsLit String
"ldexpf"), (String -> FastString
fsLit String
"ldexpl"),
(String -> FastString
fsLit String
"lgamma"), (String -> FastString
fsLit String
"lgammaf"), (String -> FastString
fsLit String
"lgammal"),
(String -> FastString
fsLit String
"llrint"), (String -> FastString
fsLit String
"llrintf"), (String -> FastString
fsLit String
"llrintl"),
(String -> FastString
fsLit String
"llround"), (String -> FastString
fsLit String
"llroundf"), (String -> FastString
fsLit String
"llroundl"),
(String -> FastString
fsLit String
"log"), (String -> FastString
fsLit String
"logf"), (String -> FastString
fsLit String
"logl"),
(String -> FastString
fsLit String
"log10l"), (String -> FastString
fsLit String
"log10"), (String -> FastString
fsLit String
"log10f"),
(String -> FastString
fsLit String
"log1pl"), (String -> FastString
fsLit String
"log1p"), (String -> FastString
fsLit String
"log1pf"),
(String -> FastString
fsLit String
"log2"), (String -> FastString
fsLit String
"log2f"), (String -> FastString
fsLit String
"log2l"),
(String -> FastString
fsLit String
"logb"), (String -> FastString
fsLit String
"logbf"), (String -> FastString
fsLit String
"logbl"),
(String -> FastString
fsLit String
"lrint"), (String -> FastString
fsLit String
"lrintf"), (String -> FastString
fsLit String
"lrintl"),
(String -> FastString
fsLit String
"lround"), (String -> FastString
fsLit String
"lroundf"), (String -> FastString
fsLit String
"lroundl"),
(String -> FastString
fsLit String
"modf"), (String -> FastString
fsLit String
"modff"), (String -> FastString
fsLit String
"modfl"),
(String -> FastString
fsLit String
"nan"), (String -> FastString
fsLit String
"nanf"), (String -> FastString
fsLit String
"nanl"),
(String -> FastString
fsLit String
"nearbyint"), (String -> FastString
fsLit String
"nearbyintf"), (String -> FastString
fsLit String
"nearbyintl"),
(String -> FastString
fsLit String
"nextafter"), (String -> FastString
fsLit String
"nextafterf"), (String -> FastString
fsLit String
"nextafterl"),
(String -> FastString
fsLit String
"nexttoward"), (String -> FastString
fsLit String
"nexttowardf"), (String -> FastString
fsLit String
"nexttowardl"),
(String -> FastString
fsLit String
"pow"), (String -> FastString
fsLit String
"powf"), (String -> FastString
fsLit String
"powl"),
(String -> FastString
fsLit String
"remainder"), (String -> FastString
fsLit String
"remainderf"), (String -> FastString
fsLit String
"remainderl"),
(String -> FastString
fsLit String
"remquo"), (String -> FastString
fsLit String
"remquof"), (String -> FastString
fsLit String
"remquol"),
(String -> FastString
fsLit String
"rint"), (String -> FastString
fsLit String
"rintf"), (String -> FastString
fsLit String
"rintl"),
(String -> FastString
fsLit String
"round"), (String -> FastString
fsLit String
"roundf"), (String -> FastString
fsLit String
"roundl"),
(String -> FastString
fsLit String
"scalbln"), (String -> FastString
fsLit String
"scalblnf"), (String -> FastString
fsLit String
"scalblnl"),
(String -> FastString
fsLit String
"scalbn"), (String -> FastString
fsLit String
"scalbnf"), (String -> FastString
fsLit String
"scalbnl"),
(String -> FastString
fsLit String
"sin"), (String -> FastString
fsLit String
"sinf"), (String -> FastString
fsLit String
"sinl"),
(String -> FastString
fsLit String
"sinh"), (String -> FastString
fsLit String
"sinhf"), (String -> FastString
fsLit String
"sinhl"),
(String -> FastString
fsLit String
"sqrt"), (String -> FastString
fsLit String
"sqrtf"), (String -> FastString
fsLit String
"sqrtl"),
(String -> FastString
fsLit String
"tan"), (String -> FastString
fsLit String
"tanf"), (String -> FastString
fsLit String
"tanl"),
(String -> FastString
fsLit String
"tanh"), (String -> FastString
fsLit String
"tanhf"), (String -> FastString
fsLit String
"tanhl"),
(String -> FastString
fsLit String
"tgamma"), (String -> FastString
fsLit String
"tgammaf"), (String -> FastString
fsLit String
"tgammal"),
(String -> FastString
fsLit String
"trunc"), (String -> FastString
fsLit String
"truncf"), (String -> FastString
fsLit String
"truncl"),
(String -> FastString
fsLit String
"drem"), (String -> FastString
fsLit String
"dremf"), (String -> FastString
fsLit String
"dreml"),
(String -> FastString
fsLit String
"finite"), (String -> FastString
fsLit String
"finitef"), (String -> FastString
fsLit String
"finitel"),
(String -> FastString
fsLit String
"gamma"), (String -> FastString
fsLit String
"gammaf"), (String -> FastString
fsLit String
"gammal"),
(String -> FastString
fsLit String
"isinf"), (String -> FastString
fsLit String
"isinff"), (String -> FastString
fsLit String
"isinfl"),
(String -> FastString
fsLit String
"isnan"), (String -> FastString
fsLit String
"isnanf"), (String -> FastString
fsLit String
"isnanl"),
(String -> FastString
fsLit String
"j0"), (String -> FastString
fsLit String
"j0f"), (String -> FastString
fsLit String
"j0l"),
(String -> FastString
fsLit String
"j1"), (String -> FastString
fsLit String
"j1f"), (String -> FastString
fsLit String
"j1l"),
(String -> FastString
fsLit String
"jn"), (String -> FastString
fsLit String
"jnf"), (String -> FastString
fsLit String
"jnl"),
(String -> FastString
fsLit String
"lgamma_r"), (String -> FastString
fsLit String
"lgammaf_r"), (String -> FastString
fsLit String
"lgammal_r"),
(String -> FastString
fsLit String
"scalb"), (String -> FastString
fsLit String
"scalbf"), (String -> FastString
fsLit String
"scalbl"),
(String -> FastString
fsLit String
"significand"), (String -> FastString
fsLit String
"significandf"), (String -> FastString
fsLit String
"significandl"),
(String -> FastString
fsLit String
"y0"), (String -> FastString
fsLit String
"y0f"), (String -> FastString
fsLit String
"y0l"),
(String -> FastString
fsLit String
"y1"), (String -> FastString
fsLit String
"y1f"), (String -> FastString
fsLit String
"y1l"),
(String -> FastString
fsLit String
"yn"), (String -> FastString
fsLit String
"ynf"), (String -> FastString
fsLit String
"ynl"),
(String -> FastString
fsLit String
"nextup"), (String -> FastString
fsLit String
"nextupf"), (String -> FastString
fsLit String
"nextupl"),
(String -> FastString
fsLit String
"nextdown"), (String -> FastString
fsLit String
"nextdownf"), (String -> FastString
fsLit String
"nextdownl")
]
externallyVisibleCLabel :: CLabel -> Bool
externallyVisibleCLabel :: CLabel -> Bool
externallyVisibleCLabel (StringLitLabel Unique
_) = Bool
False
externallyVisibleCLabel (AsmTempLabel Unique
_) = Bool
False
externallyVisibleCLabel (AsmTempDerivedLabel CLabel
_ FastString
_)= Bool
False
externallyVisibleCLabel (RtsLabel RtsLabelInfo
_) = Bool
True
externallyVisibleCLabel (LocalBlockLabel Unique
_) = Bool
False
externallyVisibleCLabel (CmmLabel Unit
_ FastString
_ CmmLabelInfo
_) = Bool
True
externallyVisibleCLabel (ForeignLabel{}) = Bool
True
externallyVisibleCLabel (IdLabel Name
name CafInfo
_ IdLabelInfo
info) = Name -> Bool
isExternalName Name
name Bool -> Bool -> Bool
&& IdLabelInfo -> Bool
externallyVisibleIdLabel IdLabelInfo
info
externallyVisibleCLabel (CC_Label CostCentre
_) = Bool
True
externallyVisibleCLabel (CCS_Label CostCentreStack
_) = Bool
True
externallyVisibleCLabel (DynamicLinkerLabel DynamicLinkerLabelInfo
_ CLabel
_) = Bool
False
externallyVisibleCLabel (HpcTicksLabel Module
_) = Bool
True
externallyVisibleCLabel (LargeBitmapLabel Unique
_) = Bool
False
externallyVisibleCLabel (SRTLabel Unique
_) = Bool
False
externallyVisibleCLabel (PicBaseLabel {}) = String -> Bool
forall a. String -> a
panic String
"externallyVisibleCLabel PicBaseLabel"
externallyVisibleCLabel (DeadStripPreventer {}) = String -> Bool
forall a. String -> a
panic String
"externallyVisibleCLabel DeadStripPreventer"
externallyVisibleIdLabel :: IdLabelInfo -> Bool
externallyVisibleIdLabel :: IdLabelInfo -> Bool
externallyVisibleIdLabel IdLabelInfo
LocalInfoTable = Bool
False
externallyVisibleIdLabel IdLabelInfo
LocalEntry = Bool
False
externallyVisibleIdLabel IdLabelInfo
BlockInfoTable = Bool
False
externallyVisibleIdLabel IdLabelInfo
_ = Bool
True
data CLabelType
= CodeLabel
| DataLabel
| GcPtrLabel
isCFunctionLabel :: CLabel -> Bool
isCFunctionLabel :: CLabel -> Bool
isCFunctionLabel CLabel
lbl = case CLabel -> CLabelType
labelType CLabel
lbl of
CLabelType
CodeLabel -> Bool
True
CLabelType
_other -> Bool
False
isGcPtrLabel :: CLabel -> Bool
isGcPtrLabel :: CLabel -> Bool
isGcPtrLabel CLabel
lbl = case CLabel -> CLabelType
labelType CLabel
lbl of
CLabelType
GcPtrLabel -> Bool
True
CLabelType
_other -> Bool
False
labelType :: CLabel -> CLabelType
labelType :: CLabel -> CLabelType
labelType (IdLabel Name
_ CafInfo
_ IdLabelInfo
info) = IdLabelInfo -> CLabelType
idInfoLabelType IdLabelInfo
info
labelType (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmData) = CLabelType
DataLabel
labelType (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmClosure) = CLabelType
GcPtrLabel
labelType (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmCode) = CLabelType
CodeLabel
labelType (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmInfo) = CLabelType
DataLabel
labelType (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmEntry) = CLabelType
CodeLabel
labelType (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmPrimCall) = CLabelType
CodeLabel
labelType (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmRetInfo) = CLabelType
DataLabel
labelType (CmmLabel Unit
_ FastString
_ CmmLabelInfo
CmmRet) = CLabelType
CodeLabel
labelType (RtsLabel (RtsSelectorInfoTable Bool
_ Int
_)) = CLabelType
DataLabel
labelType (RtsLabel (RtsApInfoTable Bool
_ Int
_)) = CLabelType
DataLabel
labelType (RtsLabel (RtsApFast FastString
_)) = CLabelType
CodeLabel
labelType (RtsLabel RtsLabelInfo
_) = CLabelType
DataLabel
labelType (LocalBlockLabel Unique
_) = CLabelType
CodeLabel
labelType (SRTLabel Unique
_) = CLabelType
DataLabel
labelType (ForeignLabel FastString
_ Maybe Int
_ ForeignLabelSource
_ FunctionOrData
IsFunction) = CLabelType
CodeLabel
labelType (ForeignLabel FastString
_ Maybe Int
_ ForeignLabelSource
_ FunctionOrData
IsData) = CLabelType
DataLabel
labelType (AsmTempLabel Unique
_) = String -> CLabelType
forall a. String -> a
panic String
"labelType(AsmTempLabel)"
labelType (AsmTempDerivedLabel CLabel
_ FastString
_) = String -> CLabelType
forall a. String -> a
panic String
"labelType(AsmTempDerivedLabel)"
labelType (StringLitLabel Unique
_) = CLabelType
DataLabel
labelType (CC_Label CostCentre
_) = CLabelType
DataLabel
labelType (CCS_Label CostCentreStack
_) = CLabelType
DataLabel
labelType (DynamicLinkerLabel DynamicLinkerLabelInfo
_ CLabel
_) = CLabelType
DataLabel
labelType CLabel
PicBaseLabel = CLabelType
DataLabel
labelType (DeadStripPreventer CLabel
_) = CLabelType
DataLabel
labelType (HpcTicksLabel Module
_) = CLabelType
DataLabel
labelType (LargeBitmapLabel Unique
_) = CLabelType
DataLabel
idInfoLabelType :: IdLabelInfo -> CLabelType
idInfoLabelType :: IdLabelInfo -> CLabelType
idInfoLabelType IdLabelInfo
info =
case IdLabelInfo
info of
IdLabelInfo
InfoTable -> CLabelType
DataLabel
IdLabelInfo
LocalInfoTable -> CLabelType
DataLabel
IdLabelInfo
BlockInfoTable -> CLabelType
DataLabel
IdLabelInfo
Closure -> CLabelType
GcPtrLabel
IdLabelInfo
ConInfoTable -> CLabelType
DataLabel
IdLabelInfo
ClosureTable -> CLabelType
DataLabel
IdLabelInfo
RednCounts -> CLabelType
DataLabel
IdLabelInfo
Bytes -> CLabelType
DataLabel
IdLabelInfo
_ -> CLabelType
CodeLabel
isLocalCLabel :: Module -> CLabel -> Bool
isLocalCLabel :: Module -> CLabel -> Bool
isLocalCLabel Module
this_mod CLabel
lbl =
case CLabel
lbl of
IdLabel Name
name CafInfo
_ IdLabelInfo
_
| Name -> Bool
isInternalName Name
name -> Bool
True
| Bool
otherwise -> HasDebugCallStack => Name -> Module
Name -> Module
External instance of the constraint type HasDebugCallStack
nameModule Name
name Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall unit. Eq unit => Eq (GenModule unit)
External instance of the constraint type Eq Unit
== Module
this_mod
LocalBlockLabel Unique
_ -> Bool
True
CLabel
_ -> Bool
False
labelDynamic :: NCGConfig -> Module -> CLabel -> Bool
labelDynamic :: NCGConfig -> Module -> CLabel -> Bool
labelDynamic NCGConfig
config Module
this_mod CLabel
lbl =
case CLabel
lbl of
RtsLabel RtsLabelInfo
_ ->
Bool
externalDynamicRefs Bool -> Bool -> Bool
&& (Unit
this_pkg Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Unit
/= Unit
rtsUnitId)
IdLabel Name
n CafInfo
_ IdLabelInfo
_ ->
Bool
externalDynamicRefs Bool -> Bool -> Bool
&& Platform -> Module -> Name -> Bool
isDynLinkName Platform
platform Module
this_mod Name
n
CmmLabel Unit
pkg FastString
_ CmmLabelInfo
_
| OS
os OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq OS
== OS
OSMinGW32 -> Bool
externalDynamicRefs Bool -> Bool -> Bool
&& (Unit
this_pkg Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Unit
/= Unit
pkg)
| Bool
otherwise -> Bool
externalDynamicRefs
LocalBlockLabel Unique
_ -> Bool
False
ForeignLabel FastString
_ Maybe Int
_ ForeignLabelSource
source FunctionOrData
_ ->
if OS
os OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq OS
== OS
OSMinGW32
then case ForeignLabelSource
source of
ForeignLabelSource
ForeignLabelInExternalPackage -> Bool
True
ForeignLabelSource
ForeignLabelInThisPackage -> Bool
False
ForeignLabelInPackage Unit
pkgId ->
Bool
externalDynamicRefs Bool -> Bool -> Bool
&& (Unit
this_pkg Unit -> Unit -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Unit
/= Unit
pkgId)
else
Bool
True
CC_Label CostCentre
cc ->
Bool
externalDynamicRefs Bool -> Bool -> Bool
&& Bool -> Bool
not (CostCentre -> Module -> Bool
ccFromThisModule CostCentre
cc Module
this_mod)
CCS_Label CostCentreStack
_ -> Bool
False
HpcTicksLabel Module
m ->
Bool
externalDynamicRefs Bool -> Bool -> Bool
&& Module
this_mod Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall unit. Eq unit => Eq (GenModule unit)
External instance of the constraint type Eq Unit
/= Module
m
CLabel
_ -> Bool
False
where
externalDynamicRefs :: Bool
externalDynamicRefs = NCGConfig -> Bool
ncgExternalDynamicRefs NCGConfig
config
platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
os :: OS
os = Platform -> OS
platformOS Platform
platform
this_pkg :: Unit
this_pkg = Module -> Unit
forall unit. GenModule unit -> unit
moduleUnit Module
this_mod
instance Outputable CLabel where
ppr :: CLabel -> SDoc
ppr CLabel
c = (DynFlags -> SDoc) -> SDoc
sdocWithDynFlags ((DynFlags -> SDoc) -> SDoc) -> (DynFlags -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \DynFlags
dynFlags -> DynFlags -> CLabel -> SDoc
pprCLabel DynFlags
dynFlags CLabel
c
pprCLabel :: DynFlags -> CLabel -> SDoc
pprCLabel :: DynFlags -> CLabel -> SDoc
pprCLabel DynFlags
dflags = \case
(LocalBlockLabel Unique
u) -> SDoc
tempLabelPrefixOrUnderscore SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
(AsmTempLabel Unique
u)
| Bool -> Bool
not (Platform -> Bool
platformUnregisterised Platform
platform)
-> SDoc
tempLabelPrefixOrUnderscore SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
(AsmTempDerivedLabel CLabel
l FastString
suf)
| Bool
useNCG
-> PtrString -> SDoc
ptext (Platform -> PtrString
asmTempLabelPrefix Platform
platform)
SDoc -> SDoc -> SDoc
<> case CLabel
l of AsmTempLabel Unique
u -> Unique -> SDoc
pprUniqueAlways Unique
u
LocalBlockLabel Unique
u -> Unique -> SDoc
pprUniqueAlways Unique
u
CLabel
_other -> DynFlags -> CLabel -> SDoc
pprCLabel DynFlags
dflags CLabel
l
SDoc -> SDoc -> SDoc
<> FastString -> SDoc
ftext FastString
suf
(DynamicLinkerLabel DynamicLinkerLabelInfo
info CLabel
lbl)
| Bool
useNCG
-> Platform -> DynamicLinkerLabelInfo -> CLabel -> SDoc
pprDynamicLinkerAsmLabel Platform
platform DynamicLinkerLabelInfo
info CLabel
lbl
CLabel
PicBaseLabel
| Bool
useNCG
-> String -> SDoc
text String
"1b"
(DeadStripPreventer CLabel
lbl)
| Bool
useNCG
->
SDoc -> SDoc
maybe_underscore (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"dsp_" SDoc -> SDoc -> SDoc
<> DynFlags -> CLabel -> SDoc
pprCLabel DynFlags
dflags CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"_dsp"
(StringLitLabel Unique
u)
| Bool
useNCG
-> Unique -> SDoc
pprUniqueAlways Unique
u SDoc -> SDoc -> SDoc
<> PtrString -> SDoc
ptext (String -> PtrString
sLit String
"_str")
CLabel
lbl -> (PprStyle -> SDoc) -> SDoc
getPprStyle ((PprStyle -> SDoc) -> SDoc) -> (PprStyle -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \PprStyle
sty ->
if Bool
useNCG Bool -> Bool -> Bool
&& PprStyle -> Bool
asmStyle PprStyle
sty
then SDoc -> SDoc
maybe_underscore (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ CLabel -> SDoc
pprAsmCLbl CLabel
lbl
else DynFlags -> CLabel -> SDoc
pprCLbl DynFlags
dflags CLabel
lbl
where
platform :: Platform
platform = DynFlags -> Platform
targetPlatform DynFlags
dflags
useNCG :: Bool
useNCG = PlatformMisc -> Bool
platformMisc_ghcWithNativeCodeGen (DynFlags -> PlatformMisc
platformMisc DynFlags
dflags)
maybe_underscore :: SDoc -> SDoc
maybe_underscore :: SDoc -> SDoc
maybe_underscore SDoc
doc =
if Platform -> Bool
platformLeadingUnderscore Platform
platform
then SDoc
pp_cSEP SDoc -> SDoc -> SDoc
<> SDoc
doc
else SDoc
doc
pprAsmCLbl :: CLabel -> SDoc
pprAsmCLbl (ForeignLabel FastString
fs (Just Int
sz) ForeignLabelSource
_ FunctionOrData
_)
| Platform -> OS
platformOS Platform
platform OS -> OS -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq OS
== OS
OSMinGW32
= FastString -> SDoc
ftext FastString
fs SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'@' SDoc -> SDoc -> SDoc
<> Int -> SDoc
int Int
sz
pprAsmCLbl CLabel
lbl = DynFlags -> CLabel -> SDoc
pprCLbl DynFlags
dflags CLabel
lbl
pprCLbl :: DynFlags -> CLabel -> SDoc
pprCLbl :: DynFlags -> CLabel -> SDoc
pprCLbl DynFlags
dflags = \case
(StringLitLabel Unique
u) -> Unique -> SDoc
pprUniqueAlways Unique
u SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"_str"
(SRTLabel Unique
u) -> SDoc
tempLabelPrefixOrUnderscore SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u SDoc -> SDoc -> SDoc
<> SDoc
pp_cSEP SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"srt"
(LargeBitmapLabel Unique
u) -> SDoc
tempLabelPrefixOrUnderscore
SDoc -> SDoc -> SDoc
<> Char -> SDoc
char Char
'b' SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u SDoc -> SDoc -> SDoc
<> SDoc
pp_cSEP SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"btm"
(CmmLabel Unit
_ FastString
str CmmLabelInfo
CmmCode) -> FastString -> SDoc
ftext FastString
str
(CmmLabel Unit
_ FastString
str CmmLabelInfo
CmmData) -> FastString -> SDoc
ftext FastString
str
(CmmLabel Unit
_ FastString
str CmmLabelInfo
CmmPrimCall) -> FastString -> SDoc
ftext FastString
str
(LocalBlockLabel Unique
u) -> SDoc
tempLabelPrefixOrUnderscore SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"blk_" SDoc -> SDoc -> SDoc
<> Unique -> SDoc
pprUniqueAlways Unique
u
(RtsLabel (RtsApFast FastString
str)) -> FastString -> SDoc
ftext FastString
str SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"_fast"
(RtsLabel (RtsSelectorInfoTable Bool
upd_reqd Int
offset)) ->
ASSERT(offset >= 0 && offset <= mAX_SPEC_SELECTEE_SIZE dflags)
[SDoc] -> SDoc
hcat [String -> SDoc
text String
"stg_sel_", String -> SDoc
text (Int -> String
forall a. Show a => a -> String
External instance of the constraint type Show Int
show Int
offset),
PtrString -> SDoc
ptext (if Bool
upd_reqd
then (String -> PtrString
sLit String
"_upd_info")
else (String -> PtrString
sLit String
"_noupd_info"))
]
(RtsLabel (RtsSelectorEntry Bool
upd_reqd Int
offset)) ->
ASSERT(offset >= 0 && offset <= mAX_SPEC_SELECTEE_SIZE dflags)
[SDoc] -> SDoc
hcat [String -> SDoc
text String
"stg_sel_", String -> SDoc
text (Int -> String
forall a. Show a => a -> String
External instance of the constraint type Show Int
show Int
offset),
PtrString -> SDoc
ptext (if Bool
upd_reqd
then (String -> PtrString
sLit String
"_upd_entry")
else (String -> PtrString
sLit String
"_noupd_entry"))
]
(RtsLabel (RtsApInfoTable Bool
upd_reqd Int
arity)) ->
ASSERT(arity > 0 && arity <= mAX_SPEC_AP_SIZE dflags)
[SDoc] -> SDoc
hcat [String -> SDoc
text String
"stg_ap_", String -> SDoc
text (Int -> String
forall a. Show a => a -> String
External instance of the constraint type Show Int
show Int
arity),
PtrString -> SDoc
ptext (if Bool
upd_reqd
then (String -> PtrString
sLit String
"_upd_info")
else (String -> PtrString
sLit String
"_noupd_info"))
]
(RtsLabel (RtsApEntry Bool
upd_reqd Int
arity)) ->
ASSERT(arity > 0 && arity <= mAX_SPEC_AP_SIZE dflags)
[SDoc] -> SDoc
hcat [String -> SDoc
text String
"stg_ap_", String -> SDoc
text (Int -> String
forall a. Show a => a -> String
External instance of the constraint type Show Int
show Int
arity),
PtrString -> SDoc
ptext (if Bool
upd_reqd
then (String -> PtrString
sLit String
"_upd_entry")
else (String -> PtrString
sLit String
"_noupd_entry"))
]
(CmmLabel Unit
_ FastString
fs CmmLabelInfo
CmmInfo) -> FastString -> SDoc
ftext FastString
fs SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"_info"
(CmmLabel Unit
_ FastString
fs CmmLabelInfo
CmmEntry) -> FastString -> SDoc
ftext FastString
fs SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"_entry"
(CmmLabel Unit
_ FastString
fs CmmLabelInfo
CmmRetInfo) -> FastString -> SDoc
ftext FastString
fs SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"_info"
(CmmLabel Unit
_ FastString
fs CmmLabelInfo
CmmRet) -> FastString -> SDoc
ftext FastString
fs SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"_ret"
(CmmLabel Unit
_ FastString
fs CmmLabelInfo
CmmClosure) -> FastString -> SDoc
ftext FastString
fs SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"_closure"
(RtsLabel (RtsPrimOp PrimOp
primop)) -> String -> SDoc
text String
"stg_" SDoc -> SDoc -> SDoc
<> PrimOp -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable PrimOp
ppr PrimOp
primop
(RtsLabel (RtsSlowFastTickyCtr String
pat)) ->
String -> SDoc
text String
"SLOW_CALL_fast_" SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
pat SDoc -> SDoc -> SDoc
<> PtrString -> SDoc
ptext (String -> PtrString
sLit String
"_ctr")
(ForeignLabel FastString
str Maybe Int
_ ForeignLabelSource
_ FunctionOrData
_) -> FastString -> SDoc
ftext FastString
str
(IdLabel Name
name CafInfo
_cafs IdLabelInfo
flavor) -> Name -> SDoc
internalNamePrefix Name
name SDoc -> SDoc -> SDoc
<> Name -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Name
ppr Name
name SDoc -> SDoc -> SDoc
<> IdLabelInfo -> SDoc
ppIdFlavor IdLabelInfo
flavor
(CC_Label CostCentre
cc) -> CostCentre -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable CostCentre
ppr CostCentre
cc
(CCS_Label CostCentreStack
ccs) -> CostCentreStack -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable CostCentreStack
ppr CostCentreStack
ccs
(HpcTicksLabel Module
mod) -> String -> SDoc
text String
"_hpc_tickboxes_" SDoc -> SDoc -> SDoc
<> Module -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Module
ppr Module
mod SDoc -> SDoc -> SDoc
<> PtrString -> SDoc
ptext (String -> PtrString
sLit String
"_hpc")
(AsmTempLabel {}) -> String -> SDoc
forall a. String -> a
panic String
"pprCLbl AsmTempLabel"
(AsmTempDerivedLabel {}) -> String -> SDoc
forall a. String -> a
panic String
"pprCLbl AsmTempDerivedLabel"
(DynamicLinkerLabel {}) -> String -> SDoc
forall a. String -> a
panic String
"pprCLbl DynamicLinkerLabel"
(PicBaseLabel {}) -> String -> SDoc
forall a. String -> a
panic String
"pprCLbl PicBaseLabel"
(DeadStripPreventer {}) -> String -> SDoc
forall a. String -> a
panic String
"pprCLbl DeadStripPreventer"
ppIdFlavor :: IdLabelInfo -> SDoc
ppIdFlavor :: IdLabelInfo -> SDoc
ppIdFlavor IdLabelInfo
x = SDoc
pp_cSEP SDoc -> SDoc -> SDoc
<> String -> SDoc
text
(case IdLabelInfo
x of
IdLabelInfo
Closure -> String
"closure"
IdLabelInfo
InfoTable -> String
"info"
IdLabelInfo
LocalInfoTable -> String
"info"
IdLabelInfo
Entry -> String
"entry"
IdLabelInfo
LocalEntry -> String
"entry"
IdLabelInfo
Slow -> String
"slow"
IdLabelInfo
RednCounts -> String
"ct"
IdLabelInfo
ConEntry -> String
"con_entry"
IdLabelInfo
ConInfoTable -> String
"con_info"
IdLabelInfo
ClosureTable -> String
"closure_tbl"
IdLabelInfo
Bytes -> String
"bytes"
IdLabelInfo
BlockInfoTable -> String
"info"
)
pp_cSEP :: SDoc
pp_cSEP :: SDoc
pp_cSEP = Char -> SDoc
char Char
'_'
instance Outputable ForeignLabelSource where
ppr :: ForeignLabelSource -> SDoc
ppr ForeignLabelSource
fs
= case ForeignLabelSource
fs of
ForeignLabelInPackage Unit
pkgId -> SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"package: " SDoc -> SDoc -> SDoc
<> Unit -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Unit
ppr Unit
pkgId
ForeignLabelSource
ForeignLabelInThisPackage -> SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"this package"
ForeignLabelSource
ForeignLabelInExternalPackage -> SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"external package"
internalNamePrefix :: Name -> SDoc
internalNamePrefix :: Name -> SDoc
internalNamePrefix Name
name = (PprStyle -> SDoc) -> SDoc
getPprStyle ((PprStyle -> SDoc) -> SDoc) -> (PprStyle -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \ PprStyle
sty ->
if PprStyle -> Bool
asmStyle PprStyle
sty Bool -> Bool -> Bool
&& Bool
isRandomGenerated then
(DynFlags -> SDoc) -> SDoc
sdocWithDynFlags ((DynFlags -> SDoc) -> SDoc) -> (DynFlags -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \DynFlags
dflags ->
PtrString -> SDoc
ptext (Platform -> PtrString
asmTempLabelPrefix (DynFlags -> Platform
targetPlatform DynFlags
dflags))
else
SDoc
empty
where
isRandomGenerated :: Bool
isRandomGenerated = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Name -> Bool
isExternalName Name
name
tempLabelPrefixOrUnderscore :: SDoc
tempLabelPrefixOrUnderscore :: SDoc
tempLabelPrefixOrUnderscore = (DynFlags -> SDoc) -> SDoc
sdocWithDynFlags ((DynFlags -> SDoc) -> SDoc) -> (DynFlags -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \DynFlags
dflags ->
(PprStyle -> SDoc) -> SDoc
getPprStyle ((PprStyle -> SDoc) -> SDoc) -> (PprStyle -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \ PprStyle
sty ->
if PprStyle -> Bool
asmStyle PprStyle
sty then
PtrString -> SDoc
ptext (Platform -> PtrString
asmTempLabelPrefix (DynFlags -> Platform
targetPlatform DynFlags
dflags))
else
Char -> SDoc
char Char
'_'
asmTempLabelPrefix :: Platform -> PtrString
asmTempLabelPrefix :: Platform -> PtrString
asmTempLabelPrefix Platform
platform = case Platform -> OS
platformOS Platform
platform of
OS
OSDarwin -> String -> PtrString
sLit String
"L"
OS
OSAIX -> String -> PtrString
sLit String
"__L"
OS
_ -> String -> PtrString
sLit String
".L"
pprDynamicLinkerAsmLabel :: Platform -> DynamicLinkerLabelInfo -> CLabel -> SDoc
pprDynamicLinkerAsmLabel :: Platform -> DynamicLinkerLabelInfo -> CLabel -> SDoc
pprDynamicLinkerAsmLabel Platform
platform DynamicLinkerLabelInfo
dllInfo CLabel
lbl =
case Platform -> OS
platformOS Platform
platform of
OS
OSDarwin
| Platform -> Arch
platformArch Platform
platform Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Arch
== Arch
ArchX86_64 ->
case DynamicLinkerLabelInfo
dllInfo of
DynamicLinkerLabelInfo
CodeStub -> Char -> SDoc
char Char
'L' SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"$stub"
DynamicLinkerLabelInfo
SymbolPtr -> Char -> SDoc
char Char
'L' SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"$non_lazy_ptr"
DynamicLinkerLabelInfo
GotSymbolPtr -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@GOTPCREL"
DynamicLinkerLabelInfo
GotSymbolOffset -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
| Bool
otherwise ->
case DynamicLinkerLabelInfo
dllInfo of
DynamicLinkerLabelInfo
CodeStub -> Char -> SDoc
char Char
'L' SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"$stub"
DynamicLinkerLabelInfo
SymbolPtr -> Char -> SDoc
char Char
'L' SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"$non_lazy_ptr"
DynamicLinkerLabelInfo
_ -> String -> SDoc
forall a. String -> a
panic String
"pprDynamicLinkerAsmLabel"
OS
OSAIX ->
case DynamicLinkerLabelInfo
dllInfo of
DynamicLinkerLabelInfo
SymbolPtr -> String -> SDoc
text String
"LC.." SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
DynamicLinkerLabelInfo
_ -> String -> SDoc
forall a. String -> a
panic String
"pprDynamicLinkerAsmLabel"
OS
_ | OS -> Bool
osElfTarget (Platform -> OS
platformOS Platform
platform) -> SDoc
elfLabel
OS
OSMinGW32 ->
case DynamicLinkerLabelInfo
dllInfo of
DynamicLinkerLabelInfo
SymbolPtr -> String -> SDoc
text String
"__imp_" SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
DynamicLinkerLabelInfo
_ -> String -> SDoc
forall a. String -> a
panic String
"pprDynamicLinkerAsmLabel"
OS
_ -> String -> SDoc
forall a. String -> a
panic String
"pprDynamicLinkerAsmLabel"
where
elfLabel :: SDoc
elfLabel
| Platform -> Arch
platformArch Platform
platform Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Arch
== Arch
ArchPPC
= case DynamicLinkerLabelInfo
dllInfo of
DynamicLinkerLabelInfo
CodeStub ->
CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"+32768@plt"
DynamicLinkerLabelInfo
SymbolPtr -> String -> SDoc
text String
".LC_" SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
DynamicLinkerLabelInfo
_ -> String -> SDoc
forall a. String -> a
panic String
"pprDynamicLinkerAsmLabel"
| Platform -> Arch
platformArch Platform
platform Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Arch
== Arch
ArchX86_64
= case DynamicLinkerLabelInfo
dllInfo of
DynamicLinkerLabelInfo
CodeStub -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@plt"
DynamicLinkerLabelInfo
GotSymbolPtr -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@gotpcrel"
DynamicLinkerLabelInfo
GotSymbolOffset -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
DynamicLinkerLabelInfo
SymbolPtr -> String -> SDoc
text String
".LC_" SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
| Platform -> Arch
platformArch Platform
platform Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Arch
== PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V1
Bool -> Bool -> Bool
|| Platform -> Arch
platformArch Platform
platform Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Arch
== PPC_64ABI -> Arch
ArchPPC_64 PPC_64ABI
ELF_V2
= case DynamicLinkerLabelInfo
dllInfo of
DynamicLinkerLabelInfo
GotSymbolPtr -> String -> SDoc
text String
".LC_" SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@toc"
DynamicLinkerLabelInfo
GotSymbolOffset -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
DynamicLinkerLabelInfo
SymbolPtr -> String -> SDoc
text String
".LC_" SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
DynamicLinkerLabelInfo
_ -> String -> SDoc
forall a. String -> a
panic String
"pprDynamicLinkerAsmLabel"
| Bool
otherwise
= case DynamicLinkerLabelInfo
dllInfo of
DynamicLinkerLabelInfo
CodeStub -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@plt"
DynamicLinkerLabelInfo
SymbolPtr -> String -> SDoc
text String
".LC_" SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl
DynamicLinkerLabelInfo
GotSymbolPtr -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@got"
DynamicLinkerLabelInfo
GotSymbolOffset -> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable CLabel
ppr CLabel
lbl SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"@gotoff"
mayRedirectTo :: CLabel -> CLabel -> Bool
mayRedirectTo :: CLabel -> CLabel -> Bool
mayRedirectTo CLabel
symbol CLabel
target
| Just Name
nam <- Maybe Name
haskellName
, Bool
staticClosureLabel
, Name -> Bool
isExternalName Name
nam
, Just Module
mod <- Name -> Maybe Module
nameModule_maybe Name
nam
, Just Name
anam <- CLabel -> Maybe Name
hasHaskellName CLabel
symbol
, Just Module
amod <- Name -> Maybe Module
nameModule_maybe Name
anam
= Module
amod Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall unit. Eq unit => Eq (GenModule unit)
External instance of the constraint type Eq Unit
== Module
mod
| Just Name
nam <- Maybe Name
haskellName
, Bool
staticClosureLabel
, Name -> Bool
isInternalName Name
nam
= Bool
True
| Bool
otherwise = Bool
False
where staticClosureLabel :: Bool
staticClosureLabel = CLabel -> Bool
isStaticClosureLabel CLabel
target
haskellName :: Maybe Name
haskellName = CLabel -> Maybe Name
hasHaskellName CLabel
target