{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module GHC.Runtime.Heap.Layout (
        
        WordOff, ByteOff,
        wordsToBytes, bytesToWordsRoundUp,
        roundUpToWords, roundUpTo,
        StgWord, fromStgWord, toStgWord,
        StgHalfWord, fromStgHalfWord, toStgHalfWord,
        halfWordSize, halfWordSizeInBits,
        
        SMRep(..), 
        IsStatic,
        ClosureTypeInfo(..), ArgDescr(..), Liveness,
        ConstrDescription,
        
        mkHeapRep, blackHoleRep, indStaticRep, mkStackRep, mkRTSRep, arrPtrsRep,
        smallArrPtrsRep, arrWordsRep,
        
        isStaticRep, isConRep, isThunkRep, isFunRep, isStaticNoCafCon,
        isStackRep,
        
        heapClosureSizeW,
        fixedHdrSizeW, arrWordsHdrSize, arrWordsHdrSizeW, arrPtrsHdrSize,
        arrPtrsHdrSizeW, profHdrSize, thunkHdrSize, nonHdrSize, nonHdrSizeW,
        smallArrPtrsHdrSize, smallArrPtrsHdrSizeW, hdrSize, hdrSizeW,
        fixedHdrSize,
        
        rtsClosureType, rET_SMALL, rET_BIG,
        aRG_GEN, aRG_GEN_BIG,
        
        card, cardRoundUp, cardTableSizeB, cardTableSizeW
    ) where
import GHC.Prelude
import GHC.Types.Basic( ConTagZ )
import GHC.Platform
import GHC.Platform.Profile
import GHC.Utils.Outputable
import GHC.Utils.Panic
import Data.Word
import Data.ByteString (ByteString)
type ByteOff = Int
type WordOff = Int
roundUpToWords :: Platform -> ByteOff -> ByteOff
roundUpToWords :: Platform -> ConTagZ -> ConTagZ
roundUpToWords Platform
platform ConTagZ
n = ConTagZ -> ConTagZ -> ConTagZ
roundUpTo ConTagZ
n (Platform -> ConTagZ
platformWordSizeInBytes Platform
platform)
roundUpTo :: ByteOff -> ByteOff -> ByteOff
roundUpTo :: ConTagZ -> ConTagZ -> ConTagZ
roundUpTo ConTagZ
base ConTagZ
size = (ConTagZ
base ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ (ConTagZ
size ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
- ConTagZ
1)) ConTagZ -> ConTagZ -> ConTagZ
forall a. Bits a => a -> a -> a
.&. (ConTagZ -> ConTagZ
forall a. Bits a => a -> a
complement (ConTagZ
size ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
- ConTagZ
1))
wordsToBytes :: Num a => Platform -> a -> a
wordsToBytes :: forall a. Num a => Platform -> a -> a
wordsToBytes Platform
platform a
n = ConTagZ -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Platform -> ConTagZ
platformWordSizeInBytes Platform
platform) a -> a -> a
forall a. Num a => a -> a -> a
* a
n
{-# SPECIALIZE wordsToBytes :: Platform -> Int -> Int #-}
{-# SPECIALIZE wordsToBytes :: Platform -> Word -> Word #-}
{-# SPECIALIZE wordsToBytes :: Platform -> Integer -> Integer #-}
bytesToWordsRoundUp :: Platform -> ByteOff -> WordOff
bytesToWordsRoundUp :: Platform -> ConTagZ -> ConTagZ
bytesToWordsRoundUp Platform
platform ConTagZ
n = (ConTagZ
n ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
word_size ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
- ConTagZ
1) ConTagZ -> ConTagZ -> ConTagZ
forall a. Integral a => a -> a -> a
`quot` ConTagZ
word_size
 where word_size :: ConTagZ
word_size = Platform -> ConTagZ
platformWordSizeInBytes Platform
platform
newtype StgWord = StgWord Word64
    deriving (StgWord -> StgWord -> Bool
(StgWord -> StgWord -> Bool)
-> (StgWord -> StgWord -> Bool) -> Eq StgWord
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StgWord -> StgWord -> Bool
== :: StgWord -> StgWord -> Bool
$c/= :: StgWord -> StgWord -> Bool
/= :: StgWord -> StgWord -> Bool
Eq, Eq StgWord
StgWord
Eq StgWord =>
(StgWord -> StgWord -> StgWord)
-> (StgWord -> StgWord -> StgWord)
-> (StgWord -> StgWord -> StgWord)
-> (StgWord -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> StgWord
-> (ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> Bool)
-> (StgWord -> Maybe ConTagZ)
-> (StgWord -> ConTagZ)
-> (StgWord -> Bool)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ -> StgWord)
-> (StgWord -> ConTagZ)
-> Bits StgWord
ConTagZ -> StgWord
StgWord -> Bool
StgWord -> ConTagZ
StgWord -> Maybe ConTagZ
StgWord -> StgWord
StgWord -> ConTagZ -> Bool
StgWord -> ConTagZ -> StgWord
StgWord -> StgWord -> StgWord
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ -> a)
-> a
-> (ConTagZ -> a)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ -> Bool)
-> (a -> Maybe ConTagZ)
-> (a -> ConTagZ)
-> (a -> Bool)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ -> a)
-> (a -> ConTagZ)
-> Bits a
$c.&. :: StgWord -> StgWord -> StgWord
.&. :: StgWord -> StgWord -> StgWord
$c.|. :: StgWord -> StgWord -> StgWord
.|. :: StgWord -> StgWord -> StgWord
$cxor :: StgWord -> StgWord -> StgWord
xor :: StgWord -> StgWord -> StgWord
$ccomplement :: StgWord -> StgWord
complement :: StgWord -> StgWord
$cshift :: StgWord -> ConTagZ -> StgWord
shift :: StgWord -> ConTagZ -> StgWord
$crotate :: StgWord -> ConTagZ -> StgWord
rotate :: StgWord -> ConTagZ -> StgWord
$czeroBits :: StgWord
zeroBits :: StgWord
$cbit :: ConTagZ -> StgWord
bit :: ConTagZ -> StgWord
$csetBit :: StgWord -> ConTagZ -> StgWord
setBit :: StgWord -> ConTagZ -> StgWord
$cclearBit :: StgWord -> ConTagZ -> StgWord
clearBit :: StgWord -> ConTagZ -> StgWord
$ccomplementBit :: StgWord -> ConTagZ -> StgWord
complementBit :: StgWord -> ConTagZ -> StgWord
$ctestBit :: StgWord -> ConTagZ -> Bool
testBit :: StgWord -> ConTagZ -> Bool
$cbitSizeMaybe :: StgWord -> Maybe ConTagZ
bitSizeMaybe :: StgWord -> Maybe ConTagZ
$cbitSize :: StgWord -> ConTagZ
bitSize :: StgWord -> ConTagZ
$cisSigned :: StgWord -> Bool
isSigned :: StgWord -> Bool
$cshiftL :: StgWord -> ConTagZ -> StgWord
shiftL :: StgWord -> ConTagZ -> StgWord
$cunsafeShiftL :: StgWord -> ConTagZ -> StgWord
unsafeShiftL :: StgWord -> ConTagZ -> StgWord
$cshiftR :: StgWord -> ConTagZ -> StgWord
shiftR :: StgWord -> ConTagZ -> StgWord
$cunsafeShiftR :: StgWord -> ConTagZ -> StgWord
unsafeShiftR :: StgWord -> ConTagZ -> StgWord
$crotateL :: StgWord -> ConTagZ -> StgWord
rotateL :: StgWord -> ConTagZ -> StgWord
$crotateR :: StgWord -> ConTagZ -> StgWord
rotateR :: StgWord -> ConTagZ -> StgWord
$cpopCount :: StgWord -> ConTagZ
popCount :: StgWord -> ConTagZ
Bits)
fromStgWord :: StgWord -> Integer
fromStgWord :: StgWord -> Integer
fromStgWord (StgWord Word64
i) = Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger Word64
i
toStgWord :: Platform -> Integer -> StgWord
toStgWord :: Platform -> Integer -> StgWord
toStgWord Platform
platform Integer
i
    = case Platform -> PlatformWordSize
platformWordSize Platform
platform of
      
      
      PlatformWordSize
PW4 -> Word64 -> StgWord
StgWord (Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word32
forall a. Num a => Integer -> a
fromInteger Integer
i :: Word32))
      PlatformWordSize
PW8 -> Word64 -> StgWord
StgWord (Integer -> Word64
forall a. Num a => Integer -> a
fromInteger Integer
i)
instance Outputable StgWord where
    ppr :: StgWord -> SDoc
ppr (StgWord Word64
i) = Integer -> SDoc
forall doc. IsLine doc => Integer -> doc
integer (Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger Word64
i)
newtype StgHalfWord = StgHalfWord Word32
    deriving StgHalfWord -> StgHalfWord -> Bool
(StgHalfWord -> StgHalfWord -> Bool)
-> (StgHalfWord -> StgHalfWord -> Bool) -> Eq StgHalfWord
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StgHalfWord -> StgHalfWord -> Bool
== :: StgHalfWord -> StgHalfWord -> Bool
$c/= :: StgHalfWord -> StgHalfWord -> Bool
/= :: StgHalfWord -> StgHalfWord -> Bool
Eq
fromStgHalfWord :: StgHalfWord -> Integer
fromStgHalfWord :: StgHalfWord -> Integer
fromStgHalfWord (StgHalfWord Word32
w) = Word32 -> Integer
forall a. Integral a => a -> Integer
toInteger Word32
w
toStgHalfWord :: Platform -> Integer -> StgHalfWord
toStgHalfWord :: Platform -> Integer -> StgHalfWord
toStgHalfWord Platform
platform Integer
i
    = case Platform -> PlatformWordSize
platformWordSize Platform
platform of
      
      
      PlatformWordSize
PW4 -> Word32 -> StgHalfWord
StgHalfWord (Word16 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word16
forall a. Num a => Integer -> a
fromInteger Integer
i :: Word16))
      PlatformWordSize
PW8 -> Word32 -> StgHalfWord
StgHalfWord (Integer -> Word32
forall a. Num a => Integer -> a
fromInteger Integer
i :: Word32)
instance Outputable StgHalfWord where
    ppr :: StgHalfWord -> SDoc
ppr (StgHalfWord Word32
w) = Integer -> SDoc
forall doc. IsLine doc => Integer -> doc
integer (Word32 -> Integer
forall a. Integral a => a -> Integer
toInteger Word32
w)
halfWordSize :: Platform -> ByteOff
halfWordSize :: Platform -> ConTagZ
halfWordSize Platform
platform = Platform -> ConTagZ
platformWordSizeInBytes Platform
platform ConTagZ -> ConTagZ -> ConTagZ
forall a. Integral a => a -> a -> a
`div` ConTagZ
2
halfWordSizeInBits :: Platform -> Int
halfWordSizeInBits :: Platform -> ConTagZ
halfWordSizeInBits Platform
platform = Platform -> ConTagZ
platformWordSizeInBits Platform
platform ConTagZ -> ConTagZ -> ConTagZ
forall a. Integral a => a -> a -> a
`div` ConTagZ
2
data SMRep
  = HeapRep              
        IsStatic
        !WordOff         
        !WordOff         
        ClosureTypeInfo  
  | ArrayPtrsRep
        !WordOff        
        !WordOff        
  | SmallArrayPtrsRep
        !WordOff        
  | ArrayWordsRep
        !WordOff        
  | StackRep            
        Liveness
  | RTSRep              
        Int             
        SMRep           
  deriving (SMRep -> SMRep -> Bool
(SMRep -> SMRep -> Bool) -> (SMRep -> SMRep -> Bool) -> Eq SMRep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SMRep -> SMRep -> Bool
== :: SMRep -> SMRep -> Bool
$c/= :: SMRep -> SMRep -> Bool
/= :: SMRep -> SMRep -> Bool
Eq, Eq SMRep
Eq SMRep =>
(SMRep -> SMRep -> Ordering)
-> (SMRep -> SMRep -> Bool)
-> (SMRep -> SMRep -> Bool)
-> (SMRep -> SMRep -> Bool)
-> (SMRep -> SMRep -> Bool)
-> (SMRep -> SMRep -> SMRep)
-> (SMRep -> SMRep -> SMRep)
-> Ord SMRep
SMRep -> SMRep -> Bool
SMRep -> SMRep -> Ordering
SMRep -> SMRep -> SMRep
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
$ccompare :: SMRep -> SMRep -> Ordering
compare :: SMRep -> SMRep -> Ordering
$c< :: SMRep -> SMRep -> Bool
< :: SMRep -> SMRep -> Bool
$c<= :: SMRep -> SMRep -> Bool
<= :: SMRep -> SMRep -> Bool
$c> :: SMRep -> SMRep -> Bool
> :: SMRep -> SMRep -> Bool
$c>= :: SMRep -> SMRep -> Bool
>= :: SMRep -> SMRep -> Bool
$cmax :: SMRep -> SMRep -> SMRep
max :: SMRep -> SMRep -> SMRep
$cmin :: SMRep -> SMRep -> SMRep
min :: SMRep -> SMRep -> SMRep
Ord)
type IsStatic = Bool
data ClosureTypeInfo
  = Constr        ConTagZ ConstrDescription
  | Fun           FunArity ArgDescr
  | Thunk
  | ThunkSelector SelectorOffset
  | BlackHole
  | IndStatic
  deriving (ClosureTypeInfo -> ClosureTypeInfo -> Bool
(ClosureTypeInfo -> ClosureTypeInfo -> Bool)
-> (ClosureTypeInfo -> ClosureTypeInfo -> Bool)
-> Eq ClosureTypeInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
== :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
$c/= :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
/= :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
Eq, Eq ClosureTypeInfo
Eq ClosureTypeInfo =>
(ClosureTypeInfo -> ClosureTypeInfo -> Ordering)
-> (ClosureTypeInfo -> ClosureTypeInfo -> Bool)
-> (ClosureTypeInfo -> ClosureTypeInfo -> Bool)
-> (ClosureTypeInfo -> ClosureTypeInfo -> Bool)
-> (ClosureTypeInfo -> ClosureTypeInfo -> Bool)
-> (ClosureTypeInfo -> ClosureTypeInfo -> ClosureTypeInfo)
-> (ClosureTypeInfo -> ClosureTypeInfo -> ClosureTypeInfo)
-> Ord ClosureTypeInfo
ClosureTypeInfo -> ClosureTypeInfo -> Bool
ClosureTypeInfo -> ClosureTypeInfo -> Ordering
ClosureTypeInfo -> ClosureTypeInfo -> ClosureTypeInfo
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
$ccompare :: ClosureTypeInfo -> ClosureTypeInfo -> Ordering
compare :: ClosureTypeInfo -> ClosureTypeInfo -> Ordering
$c< :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
< :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
$c<= :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
<= :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
$c> :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
> :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
$c>= :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
>= :: ClosureTypeInfo -> ClosureTypeInfo -> Bool
$cmax :: ClosureTypeInfo -> ClosureTypeInfo -> ClosureTypeInfo
max :: ClosureTypeInfo -> ClosureTypeInfo -> ClosureTypeInfo
$cmin :: ClosureTypeInfo -> ClosureTypeInfo -> ClosureTypeInfo
min :: ClosureTypeInfo -> ClosureTypeInfo -> ClosureTypeInfo
Ord)
type ConstrDescription = ByteString 
type FunArity          = Int
type SelectorOffset    = Int
type Liveness = [Bool]   
                         
data ArgDescr
  = ArgSpec             
        !Int            
  | ArgGen              
        Liveness        
  | ArgUnknown          
                        
                        
  deriving (ArgDescr -> ArgDescr -> Bool
(ArgDescr -> ArgDescr -> Bool)
-> (ArgDescr -> ArgDescr -> Bool) -> Eq ArgDescr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ArgDescr -> ArgDescr -> Bool
== :: ArgDescr -> ArgDescr -> Bool
$c/= :: ArgDescr -> ArgDescr -> Bool
/= :: ArgDescr -> ArgDescr -> Bool
Eq, Eq ArgDescr
Eq ArgDescr =>
(ArgDescr -> ArgDescr -> Ordering)
-> (ArgDescr -> ArgDescr -> Bool)
-> (ArgDescr -> ArgDescr -> Bool)
-> (ArgDescr -> ArgDescr -> Bool)
-> (ArgDescr -> ArgDescr -> Bool)
-> (ArgDescr -> ArgDescr -> ArgDescr)
-> (ArgDescr -> ArgDescr -> ArgDescr)
-> Ord ArgDescr
ArgDescr -> ArgDescr -> Bool
ArgDescr -> ArgDescr -> Ordering
ArgDescr -> ArgDescr -> ArgDescr
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
$ccompare :: ArgDescr -> ArgDescr -> Ordering
compare :: ArgDescr -> ArgDescr -> Ordering
$c< :: ArgDescr -> ArgDescr -> Bool
< :: ArgDescr -> ArgDescr -> Bool
$c<= :: ArgDescr -> ArgDescr -> Bool
<= :: ArgDescr -> ArgDescr -> Bool
$c> :: ArgDescr -> ArgDescr -> Bool
> :: ArgDescr -> ArgDescr -> Bool
$c>= :: ArgDescr -> ArgDescr -> Bool
>= :: ArgDescr -> ArgDescr -> Bool
$cmax :: ArgDescr -> ArgDescr -> ArgDescr
max :: ArgDescr -> ArgDescr -> ArgDescr
$cmin :: ArgDescr -> ArgDescr -> ArgDescr
min :: ArgDescr -> ArgDescr -> ArgDescr
Ord)
instance Outputable ArgDescr where
  ppr :: ArgDescr -> SDoc
ppr (ArgSpec ConTagZ
n) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ArgSpec" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ConTagZ -> SDoc
forall a. Outputable a => a -> SDoc
ppr ConTagZ
n
  ppr (ArgGen Liveness
ls) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ArgGen" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Liveness -> SDoc
forall a. Outputable a => a -> SDoc
ppr Liveness
ls
  ppr ArgDescr
ArgUnknown = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ArgUnknown"
mkHeapRep :: Profile -> IsStatic -> WordOff -> WordOff -> ClosureTypeInfo
          -> SMRep
mkHeapRep :: Profile -> Bool -> ConTagZ -> ConTagZ -> ClosureTypeInfo -> SMRep
mkHeapRep Profile
profile Bool
is_static ConTagZ
ptr_wds ConTagZ
nonptr_wds ClosureTypeInfo
cl_type_info
  = Bool -> ConTagZ -> ConTagZ -> ClosureTypeInfo -> SMRep
HeapRep Bool
is_static
            ConTagZ
ptr_wds
            (ConTagZ
nonptr_wds ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
slop_wds)
            ClosureTypeInfo
cl_type_info
  where
     slop_wds :: ConTagZ
slop_wds
      | Bool
is_static = ConTagZ
0
      | Bool
otherwise = ConTagZ -> ConTagZ -> ConTagZ
forall a. Ord a => a -> a -> a
max ConTagZ
0 (Profile -> ConTagZ
minClosureSize Profile
profile ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
- (ConTagZ
hdr_size ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
payload_size))
     hdr_size :: ConTagZ
hdr_size     = Profile -> ClosureTypeInfo -> ConTagZ
closureTypeHdrSize Profile
profile ClosureTypeInfo
cl_type_info
     payload_size :: ConTagZ
payload_size = ConTagZ
ptr_wds ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
nonptr_wds
mkRTSRep :: Int -> SMRep -> SMRep
mkRTSRep :: ConTagZ -> SMRep -> SMRep
mkRTSRep = ConTagZ -> SMRep -> SMRep
RTSRep
mkStackRep :: [Bool] -> SMRep
mkStackRep :: Liveness -> SMRep
mkStackRep Liveness
liveness = Liveness -> SMRep
StackRep Liveness
liveness
blackHoleRep :: SMRep
blackHoleRep :: SMRep
blackHoleRep = Bool -> ConTagZ -> ConTagZ -> ClosureTypeInfo -> SMRep
HeapRep Bool
False ConTagZ
0 ConTagZ
0 ClosureTypeInfo
BlackHole
indStaticRep :: SMRep
indStaticRep :: SMRep
indStaticRep = Bool -> ConTagZ -> ConTagZ -> ClosureTypeInfo -> SMRep
HeapRep Bool
True ConTagZ
1 ConTagZ
0 ClosureTypeInfo
IndStatic
arrPtrsRep :: Platform -> WordOff -> SMRep
arrPtrsRep :: Platform -> ConTagZ -> SMRep
arrPtrsRep Platform
platform ConTagZ
elems = ConTagZ -> ConTagZ -> SMRep
ArrayPtrsRep ConTagZ
elems (Platform -> ConTagZ -> ConTagZ
cardTableSizeW Platform
platform ConTagZ
elems)
smallArrPtrsRep :: WordOff -> SMRep
smallArrPtrsRep :: ConTagZ -> SMRep
smallArrPtrsRep ConTagZ
elems = ConTagZ -> SMRep
SmallArrayPtrsRep ConTagZ
elems
arrWordsRep :: Platform -> ByteOff -> SMRep
arrWordsRep :: Platform -> ConTagZ -> SMRep
arrWordsRep Platform
platform ConTagZ
bytes = ConTagZ -> SMRep
ArrayWordsRep (Platform -> ConTagZ -> ConTagZ
bytesToWordsRoundUp Platform
platform ConTagZ
bytes)
isStaticRep :: SMRep -> IsStatic
isStaticRep :: SMRep -> Bool
isStaticRep (HeapRep Bool
is_static ConTagZ
_ ConTagZ
_ ClosureTypeInfo
_) = Bool
is_static
isStaticRep (RTSRep ConTagZ
_ SMRep
rep)            = SMRep -> Bool
isStaticRep SMRep
rep
isStaticRep SMRep
_                         = Bool
False
isStackRep :: SMRep -> Bool
isStackRep :: SMRep -> Bool
isStackRep StackRep{}     = Bool
True
isStackRep (RTSRep ConTagZ
_ SMRep
rep) = SMRep -> Bool
isStackRep SMRep
rep
isStackRep SMRep
_              = Bool
False
isConRep :: SMRep -> Bool
isConRep :: SMRep -> Bool
isConRep (HeapRep Bool
_ ConTagZ
_ ConTagZ
_ Constr{}) = Bool
True
isConRep SMRep
_                        = Bool
False
isThunkRep :: SMRep -> Bool
isThunkRep :: SMRep -> Bool
isThunkRep (HeapRep Bool
_ ConTagZ
_ ConTagZ
_ ClosureTypeInfo
Thunk)           = Bool
True
isThunkRep (HeapRep Bool
_ ConTagZ
_ ConTagZ
_ ThunkSelector{}) = Bool
True
isThunkRep (HeapRep Bool
_ ConTagZ
_ ConTagZ
_ ClosureTypeInfo
BlackHole)       = Bool
True
isThunkRep (HeapRep Bool
_ ConTagZ
_ ConTagZ
_ ClosureTypeInfo
IndStatic)       = Bool
True
isThunkRep SMRep
_                               = Bool
False
isFunRep :: SMRep -> Bool
isFunRep :: SMRep -> Bool
isFunRep (HeapRep Bool
_ ConTagZ
_ ConTagZ
_ Fun{}) = Bool
True
isFunRep SMRep
_                     = Bool
False
isStaticNoCafCon :: SMRep -> Bool
isStaticNoCafCon :: SMRep -> Bool
isStaticNoCafCon (HeapRep Bool
_ ConTagZ
0 ConTagZ
_ Constr{}) = Bool
True
isStaticNoCafCon SMRep
_                        = Bool
False
fixedHdrSize :: Profile -> ByteOff
fixedHdrSize :: Profile -> ConTagZ
fixedHdrSize Profile
profile = Platform -> ConTagZ -> ConTagZ
forall a. Num a => Platform -> a -> a
wordsToBytes (Profile -> Platform
profilePlatform Profile
profile) (Profile -> ConTagZ
fixedHdrSizeW Profile
profile)
fixedHdrSizeW :: Profile -> WordOff
fixedHdrSizeW :: Profile -> ConTagZ
fixedHdrSizeW Profile
profile = PlatformConstants -> ConTagZ
pc_STD_HDR_SIZE (Profile -> PlatformConstants
profileConstants Profile
profile) ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ Profile -> ConTagZ
profHdrSize Profile
profile
profHdrSize :: Profile -> WordOff
profHdrSize :: Profile -> ConTagZ
profHdrSize Profile
profile =
   if Profile -> Bool
profileIsProfiling Profile
profile
      then PlatformConstants -> ConTagZ
pc_PROF_HDR_SIZE (Profile -> PlatformConstants
profileConstants Profile
profile)
      else ConTagZ
0
minClosureSize :: Profile -> WordOff
minClosureSize :: Profile -> ConTagZ
minClosureSize Profile
profile
 = Profile -> ConTagZ
fixedHdrSizeW Profile
profile
   ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ PlatformConstants -> ConTagZ
pc_MIN_PAYLOAD_SIZE (Profile -> PlatformConstants
profileConstants Profile
profile)
arrWordsHdrSize :: Profile -> ByteOff
arrWordsHdrSize :: Profile -> ConTagZ
arrWordsHdrSize Profile
profile
 = Profile -> ConTagZ
fixedHdrSize Profile
profile
   ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ PlatformConstants -> ConTagZ
pc_SIZEOF_StgArrBytes_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile)
arrWordsHdrSizeW :: Profile -> WordOff
arrWordsHdrSizeW :: Profile -> ConTagZ
arrWordsHdrSizeW Profile
profile
 = Profile -> ConTagZ
fixedHdrSizeW Profile
profile
   ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ (PlatformConstants -> ConTagZ
pc_SIZEOF_StgArrBytes_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile) ConTagZ -> ConTagZ -> ConTagZ
forall a. Integral a => a -> a -> a
`quot`
      Platform -> ConTagZ
platformWordSizeInBytes (Profile -> Platform
profilePlatform Profile
profile))
arrPtrsHdrSize :: Profile -> ByteOff
arrPtrsHdrSize :: Profile -> ConTagZ
arrPtrsHdrSize Profile
profile
 = Profile -> ConTagZ
fixedHdrSize Profile
profile
   ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ PlatformConstants -> ConTagZ
pc_SIZEOF_StgMutArrPtrs_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile)
arrPtrsHdrSizeW :: Profile -> WordOff
arrPtrsHdrSizeW :: Profile -> ConTagZ
arrPtrsHdrSizeW Profile
profile
 = Profile -> ConTagZ
fixedHdrSizeW Profile
profile
   ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ (PlatformConstants -> ConTagZ
pc_SIZEOF_StgMutArrPtrs_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile) ConTagZ -> ConTagZ -> ConTagZ
forall a. Integral a => a -> a -> a
`quot`
      Platform -> ConTagZ
platformWordSizeInBytes (Profile -> Platform
profilePlatform Profile
profile))
smallArrPtrsHdrSize :: Profile -> ByteOff
smallArrPtrsHdrSize :: Profile -> ConTagZ
smallArrPtrsHdrSize Profile
profile
 = Profile -> ConTagZ
fixedHdrSize Profile
profile
   ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ PlatformConstants -> ConTagZ
pc_SIZEOF_StgSmallMutArrPtrs_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile)
smallArrPtrsHdrSizeW :: Profile -> WordOff
smallArrPtrsHdrSizeW :: Profile -> ConTagZ
smallArrPtrsHdrSizeW Profile
profile
 = Profile -> ConTagZ
fixedHdrSizeW Profile
profile
   ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ (PlatformConstants -> ConTagZ
pc_SIZEOF_StgSmallMutArrPtrs_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile) ConTagZ -> ConTagZ -> ConTagZ
forall a. Integral a => a -> a -> a
`quot`
      Platform -> ConTagZ
platformWordSizeInBytes (Profile -> Platform
profilePlatform Profile
profile))
thunkHdrSize :: Profile -> WordOff
thunkHdrSize :: Profile -> ConTagZ
thunkHdrSize Profile
profile = Profile -> ConTagZ
fixedHdrSizeW Profile
profile ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
smp_hdr
        where
         platform :: Platform
platform = Profile -> Platform
profilePlatform Profile
profile
         smp_hdr :: ConTagZ
smp_hdr  = PlatformConstants -> ConTagZ
pc_SIZEOF_StgSMPThunkHeader (Platform -> PlatformConstants
platformConstants Platform
platform) ConTagZ -> ConTagZ -> ConTagZ
forall a. Integral a => a -> a -> a
`quot`
                         Platform -> ConTagZ
platformWordSizeInBytes Platform
platform
hdrSize :: Profile -> SMRep -> ByteOff
hdrSize :: Profile -> SMRep -> ConTagZ
hdrSize Profile
profile SMRep
rep = Platform -> ConTagZ -> ConTagZ
forall a. Num a => Platform -> a -> a
wordsToBytes (Profile -> Platform
profilePlatform Profile
profile) (Profile -> SMRep -> ConTagZ
hdrSizeW Profile
profile SMRep
rep)
hdrSizeW :: Profile -> SMRep -> WordOff
hdrSizeW :: Profile -> SMRep -> ConTagZ
hdrSizeW Profile
profile (HeapRep Bool
_ ConTagZ
_ ConTagZ
_ ClosureTypeInfo
ty)    = Profile -> ClosureTypeInfo -> ConTagZ
closureTypeHdrSize Profile
profile ClosureTypeInfo
ty
hdrSizeW Profile
profile (ArrayPtrsRep ConTagZ
_ ConTagZ
_)    = Profile -> ConTagZ
arrPtrsHdrSizeW Profile
profile
hdrSizeW Profile
profile (SmallArrayPtrsRep ConTagZ
_) = Profile -> ConTagZ
smallArrPtrsHdrSizeW Profile
profile
hdrSizeW Profile
profile (ArrayWordsRep ConTagZ
_)     = Profile -> ConTagZ
arrWordsHdrSizeW Profile
profile
hdrSizeW Profile
_ SMRep
_                           = String -> ConTagZ
forall a. HasCallStack => String -> a
panic String
"GHC.Runtime.Heap.Layout.hdrSizeW"
nonHdrSize :: Platform -> SMRep -> ByteOff
nonHdrSize :: Platform -> SMRep -> ConTagZ
nonHdrSize Platform
platform SMRep
rep = Platform -> ConTagZ -> ConTagZ
forall a. Num a => Platform -> a -> a
wordsToBytes Platform
platform (SMRep -> ConTagZ
nonHdrSizeW SMRep
rep)
nonHdrSizeW :: SMRep -> WordOff
nonHdrSizeW :: SMRep -> ConTagZ
nonHdrSizeW (HeapRep Bool
_ ConTagZ
p ConTagZ
np ClosureTypeInfo
_) = ConTagZ
p ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
np
nonHdrSizeW (ArrayPtrsRep ConTagZ
elems ConTagZ
ct) = ConTagZ
elems ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
ct
nonHdrSizeW (SmallArrayPtrsRep ConTagZ
elems) = ConTagZ
elems
nonHdrSizeW (ArrayWordsRep ConTagZ
words) = ConTagZ
words
nonHdrSizeW (StackRep Liveness
bs)      = Liveness -> ConTagZ
forall a. [a] -> ConTagZ
forall (t :: * -> *) a. Foldable t => t a -> ConTagZ
length Liveness
bs
nonHdrSizeW (RTSRep ConTagZ
_ SMRep
rep)     = SMRep -> ConTagZ
nonHdrSizeW SMRep
rep
heapClosureSizeW :: Profile -> SMRep -> WordOff
heapClosureSizeW :: Profile -> SMRep -> ConTagZ
heapClosureSizeW Profile
profile SMRep
rep = case SMRep
rep of
   HeapRep Bool
_ ConTagZ
p ConTagZ
np ClosureTypeInfo
ty       -> Profile -> ClosureTypeInfo -> ConTagZ
closureTypeHdrSize Profile
profile ClosureTypeInfo
ty ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
p ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
np
   ArrayPtrsRep ConTagZ
elems ConTagZ
ct   -> Profile -> ConTagZ
arrPtrsHdrSizeW Profile
profile ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
elems ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
ct
   SmallArrayPtrsRep ConTagZ
elems -> Profile -> ConTagZ
smallArrPtrsHdrSizeW Profile
profile ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
elems
   ArrayWordsRep ConTagZ
words     -> Profile -> ConTagZ
arrWordsHdrSizeW Profile
profile ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ConTagZ
words
   SMRep
_                       -> String -> ConTagZ
forall a. HasCallStack => String -> a
panic String
"GHC.Runtime.Heap.Layout.heapClosureSize"
closureTypeHdrSize :: Profile -> ClosureTypeInfo -> WordOff
closureTypeHdrSize :: Profile -> ClosureTypeInfo -> ConTagZ
closureTypeHdrSize Profile
profile ClosureTypeInfo
ty = case ClosureTypeInfo
ty of
                  ClosureTypeInfo
Thunk           -> Profile -> ConTagZ
thunkHdrSize Profile
profile
                  ThunkSelector{} -> Profile -> ConTagZ
thunkHdrSize Profile
profile
                  ClosureTypeInfo
BlackHole       -> Profile -> ConTagZ
thunkHdrSize Profile
profile
                  ClosureTypeInfo
IndStatic       -> Profile -> ConTagZ
thunkHdrSize Profile
profile
                  ClosureTypeInfo
_               -> Profile -> ConTagZ
fixedHdrSizeW Profile
profile
        
        
        
        
        
card :: Platform -> Int -> Int
card :: Platform -> ConTagZ -> ConTagZ
card Platform
platform ConTagZ
i = ConTagZ
i ConTagZ -> ConTagZ -> ConTagZ
forall a. Bits a => a -> ConTagZ -> a
`shiftR` PlatformConstants -> ConTagZ
pc_MUT_ARR_PTRS_CARD_BITS (Platform -> PlatformConstants
platformConstants Platform
platform)
cardRoundUp :: Platform -> Int -> Int
cardRoundUp :: Platform -> ConTagZ -> ConTagZ
cardRoundUp Platform
platform ConTagZ
i =
  Platform -> ConTagZ -> ConTagZ
card Platform
platform (ConTagZ
i ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
+ ((ConTagZ
1 ConTagZ -> ConTagZ -> ConTagZ
forall a. Bits a => a -> ConTagZ -> a
`shiftL` PlatformConstants -> ConTagZ
pc_MUT_ARR_PTRS_CARD_BITS (Platform -> PlatformConstants
platformConstants Platform
platform)) ConTagZ -> ConTagZ -> ConTagZ
forall a. Num a => a -> a -> a
- ConTagZ
1))
cardTableSizeB :: Platform -> Int -> ByteOff
cardTableSizeB :: Platform -> ConTagZ -> ConTagZ
cardTableSizeB Platform
platform ConTagZ
elems = Platform -> ConTagZ -> ConTagZ
cardRoundUp Platform
platform ConTagZ
elems
cardTableSizeW :: Platform -> Int -> WordOff
cardTableSizeW :: Platform -> ConTagZ -> ConTagZ
cardTableSizeW Platform
platform ConTagZ
elems =
  Platform -> ConTagZ -> ConTagZ
bytesToWordsRoundUp Platform
platform (Platform -> ConTagZ -> ConTagZ
cardTableSizeB Platform
platform ConTagZ
elems)
#include "ClosureTypes.h"
#include "FunTypes.h"
rtsClosureType :: SMRep -> Int
rtsClosureType :: SMRep -> ConTagZ
rtsClosureType SMRep
rep
    = case SMRep
rep of
      RTSRep ConTagZ
ty SMRep
_ -> ConTagZ
ty
      
      HeapRep Bool
_     ConTagZ
1 ConTagZ
0 Constr{} -> CONSTR_1_0
      HeapRep Bool
_     ConTagZ
0 ConTagZ
1 Constr{} -> CONSTR_0_1
      HeapRep Bool
_     ConTagZ
2 ConTagZ
0 Constr{} -> CONSTR_2_0
      HeapRep Bool
_     ConTagZ
1 ConTagZ
1 Constr{} -> CONSTR_1_1
      HeapRep Bool
_     ConTagZ
0 ConTagZ
2 Constr{} -> CONSTR_0_2
      HeapRep Bool
_     ConTagZ
0 ConTagZ
_ Constr{} -> CONSTR_NOCAF
           
      HeapRep Bool
_     ConTagZ
_ ConTagZ
_ Constr{} -> CONSTR
      HeapRep Bool
False ConTagZ
1 ConTagZ
0 Fun{} -> FUN_1_0
      HeapRep Bool
False ConTagZ
0 ConTagZ
1 Fun{} -> FUN_0_1
      HeapRep Bool
False ConTagZ
2 ConTagZ
0 Fun{} -> FUN_2_0
      HeapRep Bool
False ConTagZ
1 ConTagZ
1 Fun{} -> FUN_1_1
      HeapRep Bool
False ConTagZ
0 ConTagZ
2 Fun{} -> FUN_0_2
      HeapRep Bool
False ConTagZ
_ ConTagZ
_ Fun{} -> FUN
      HeapRep Bool
False ConTagZ
1 ConTagZ
0 ClosureTypeInfo
Thunk -> THUNK_1_0
      HeapRep Bool
False ConTagZ
0 ConTagZ
1 ClosureTypeInfo
Thunk -> THUNK_0_1
      HeapRep Bool
False ConTagZ
2 ConTagZ
0 ClosureTypeInfo
Thunk -> THUNK_2_0
      HeapRep Bool
False ConTagZ
1 ConTagZ
1 ClosureTypeInfo
Thunk -> THUNK_1_1
      HeapRep Bool
False ConTagZ
0 ConTagZ
2 ClosureTypeInfo
Thunk -> THUNK_0_2
      HeapRep Bool
False ConTagZ
_ ConTagZ
_ ClosureTypeInfo
Thunk -> THUNK
      HeapRep Bool
False ConTagZ
_ ConTagZ
_ ThunkSelector{} ->  THUNK_SELECTOR
      HeapRep Bool
True ConTagZ
_ ConTagZ
_ Fun{}      -> FUN_STATIC
      HeapRep Bool
True ConTagZ
_ ConTagZ
_ ClosureTypeInfo
Thunk      -> THUNK_STATIC
      HeapRep Bool
False ConTagZ
_ ConTagZ
_ ClosureTypeInfo
BlackHole -> BLACKHOLE
      HeapRep Bool
False ConTagZ
_ ConTagZ
_ ClosureTypeInfo
IndStatic -> IND_STATIC
      StackRep Liveness
_ -> STACK
      SMRep
_ -> String -> ConTagZ
forall a. HasCallStack => String -> a
panic String
"rtsClosureType"
rET_SMALL, rET_BIG, aRG_GEN, aRG_GEN_BIG :: Int
rET_SMALL :: ConTagZ
rET_SMALL   = RET_SMALL
rET_BIG :: ConTagZ
rET_BIG     = RET_BIG
aRG_GEN :: ConTagZ
aRG_GEN     = ARG_GEN
aRG_GEN_BIG :: ConTagZ
aRG_GEN_BIG = ARG_GEN_BIG
instance Outputable ClosureTypeInfo where
   ppr :: ClosureTypeInfo -> SDoc
ppr = ClosureTypeInfo -> SDoc
pprTypeInfo
instance Outputable SMRep where
   ppr :: SMRep -> SDoc
ppr (HeapRep Bool
static ConTagZ
ps ConTagZ
nps ClosureTypeInfo
tyinfo)
     = SDoc -> ConTagZ -> SDoc -> SDoc
hang (SDoc
header SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
forall doc. IsLine doc => doc
lbrace) ConTagZ
2 (ClosureTypeInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr ClosureTypeInfo
tyinfo SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
forall doc. IsLine doc => doc
rbrace)
     where
       header :: SDoc
header = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"HeapRep"
                SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> if Bool
static then String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"static" else SDoc
forall doc. IsOutput doc => doc
empty
                SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> ConTagZ -> SDoc
pp_n String
"ptrs" ConTagZ
ps SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> ConTagZ -> SDoc
pp_n String
"nonptrs" ConTagZ
nps
       pp_n :: String -> Int -> SDoc
       pp_n :: String -> ConTagZ -> SDoc
pp_n String
_ ConTagZ
0 = SDoc
forall doc. IsOutput doc => doc
empty
       pp_n String
s ConTagZ
n = ConTagZ -> SDoc
forall doc. IsLine doc => ConTagZ -> doc
int ConTagZ
n SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> String -> SDoc
forall doc. IsLine doc => String -> doc
text String
s
   ppr (ArrayPtrsRep ConTagZ
size ConTagZ
_) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ArrayPtrsRep" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ConTagZ -> SDoc
forall a. Outputable a => a -> SDoc
ppr ConTagZ
size
   ppr (SmallArrayPtrsRep ConTagZ
size) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"SmallArrayPtrsRep" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ConTagZ -> SDoc
forall a. Outputable a => a -> SDoc
ppr ConTagZ
size
   ppr (ArrayWordsRep ConTagZ
words) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ArrayWordsRep" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ConTagZ -> SDoc
forall a. Outputable a => a -> SDoc
ppr ConTagZ
words
   ppr (StackRep Liveness
bs) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"StackRep" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Liveness -> SDoc
forall a. Outputable a => a -> SDoc
ppr Liveness
bs
   ppr (RTSRep ConTagZ
ty SMRep
rep) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"tag:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> ConTagZ -> SDoc
forall a. Outputable a => a -> SDoc
ppr ConTagZ
ty SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SMRep -> SDoc
forall a. Outputable a => a -> SDoc
ppr SMRep
rep
pprTypeInfo :: ClosureTypeInfo -> SDoc
pprTypeInfo :: ClosureTypeInfo -> SDoc
pprTypeInfo (Constr ConTagZ
tag ConstrDescription
descr)
  = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Con" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
    SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"tag:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ConTagZ -> SDoc
forall a. Outputable a => a -> SDoc
ppr ConTagZ
tag
                , String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"descr:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> String -> SDoc
forall doc. IsLine doc => String -> doc
text (ConstrDescription -> String
forall a. Show a => a -> String
show ConstrDescription
descr) ])
pprTypeInfo (Fun ConTagZ
arity ArgDescr
args)
  = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Fun" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+>
    SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
braces ([SDoc] -> SDoc
forall doc. IsLine doc => [doc] -> doc
sep [ String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"arity:"    SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ConTagZ -> SDoc
forall a. Outputable a => a -> SDoc
ppr ConTagZ
arity
                , String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"fun_type:" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ArgDescr -> SDoc
forall a. Outputable a => a -> SDoc
ppr ArgDescr
args ])
pprTypeInfo (ThunkSelector ConTagZ
offset)
  = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"ThunkSel" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> ConTagZ -> SDoc
forall a. Outputable a => a -> SDoc
ppr ConTagZ
offset
pprTypeInfo ClosureTypeInfo
Thunk     = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"Thunk"
pprTypeInfo ClosureTypeInfo
BlackHole = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"BlackHole"
pprTypeInfo ClosureTypeInfo
IndStatic = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"IndStatic"