module GHC.StgToCmm.Types
( CmmCgInfos (..)
, LambdaFormInfo (..)
, ModuleLFInfos
, StandardFormInfo (..)
, DoSCCProfiling
, DoExtDynRefs
) where
import GHC.Prelude
import GHC.Core.DataCon
import GHC.Runtime.Heap.Layout
import GHC.Types.Basic
import GHC.Types.ForeignStubs
import GHC.Types.Name.Env
import GHC.Types.Name.Set
import GHC.Utils.Outputable
data CmmCgInfos = CmmCgInfos
{ CmmCgInfos -> NonCaffySet
cgNonCafs :: !NonCaffySet
, CmmCgInfos -> ModuleLFInfos
cgLFInfos :: !ModuleLFInfos
, CmmCgInfos -> CStub
cgIPEStub :: !CStub
}
type ModuleLFInfos = NameEnv LambdaFormInfo
data LambdaFormInfo
= LFReEntrant
!TopLevelFlag
!RepArity
!Bool
!ArgDescr
| LFThunk
!TopLevelFlag
!Bool
!Bool
!StandardFormInfo
!Bool
| LFCon
!DataCon
| LFUnknown
!Bool
| LFUnlifted
| LFLetNoEscape
instance Outputable LambdaFormInfo where
ppr :: LambdaFormInfo -> SDoc
ppr (LFReEntrant TopLevelFlag
top RepArity
rep Bool
fvs ArgDescr
argdesc) =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFReEntrant" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets
(TopLevelFlag -> SDoc
forall a. Outputable a => a -> SDoc
ppr TopLevelFlag
top SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> RepArity -> SDoc
forall a. Outputable a => a -> SDoc
ppr RepArity
rep SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
pprFvs Bool
fvs SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ArgDescr -> SDoc
forall a. Outputable a => a -> SDoc
ppr ArgDescr
argdesc)
ppr (LFThunk TopLevelFlag
top Bool
hasfv Bool
updateable StandardFormInfo
sfi Bool
m_function) =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFThunk" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets
(TopLevelFlag -> SDoc
forall a. Outputable a => a -> SDoc
ppr TopLevelFlag
top SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
pprFvs Bool
hasfv SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
pprUpdateable Bool
updateable SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
StandardFormInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr StandardFormInfo
sfi SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Bool -> SDoc
pprFuncFlag Bool
m_function)
ppr (LFCon DataCon
con) =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFCon" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets (DataCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr DataCon
con)
ppr (LFUnknown Bool
m_func) =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFUnknown" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
brackets (Bool -> SDoc
pprFuncFlag Bool
m_func)
ppr LambdaFormInfo
LFUnlifted =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFUnlifted"
ppr LambdaFormInfo
LFLetNoEscape =
String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"LFLetNoEscape"
pprFvs :: Bool -> SDoc
pprFvs :: Bool -> SDoc
pprFvs Bool
True = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"no-fvs"
pprFvs Bool
False = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"fvs"
pprFuncFlag :: Bool -> SDoc
pprFuncFlag :: Bool -> SDoc
pprFuncFlag Bool
True = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"mFunc"
pprFuncFlag Bool
False = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"value"
pprUpdateable :: Bool -> SDoc
pprUpdateable :: Bool -> SDoc
pprUpdateable Bool
True = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"updateable"
pprUpdateable Bool
False = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"oneshot"
data StandardFormInfo
= NonStandardThunk
| SelectorThunk
!WordOff
| ApThunk
!RepArity
deriving (StandardFormInfo -> StandardFormInfo -> Bool
(StandardFormInfo -> StandardFormInfo -> Bool)
-> (StandardFormInfo -> StandardFormInfo -> Bool)
-> Eq StandardFormInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StandardFormInfo -> StandardFormInfo -> Bool
== :: StandardFormInfo -> StandardFormInfo -> Bool
$c/= :: StandardFormInfo -> StandardFormInfo -> Bool
/= :: StandardFormInfo -> StandardFormInfo -> Bool
Eq)
instance Outputable StandardFormInfo where
ppr :: StandardFormInfo -> SDoc
ppr StandardFormInfo
NonStandardThunk = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"RegThunk"
ppr (SelectorThunk RepArity
w) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"SelThunk:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> RepArity -> SDoc
forall a. Outputable a => a -> SDoc
ppr RepArity
w
ppr (ApThunk RepArity
n) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ApThunk:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> RepArity -> SDoc
forall a. Outputable a => a -> SDoc
ppr RepArity
n
type DoSCCProfiling = Bool
type DoExtDynRefs = Bool