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.Driver.Session
import GHC.Platform
import GHC.Platform.Profile
import GHC.Data.FastString
import GHC.StgToCmm.Types
import GHC.Utils.Outputable
import GHC.Utils.Panic
import Data.Word
import Data.Bits
import Data.ByteString (ByteString)
type ByteOff = Int
roundUpToWords :: Platform -> ByteOff -> ByteOff
roundUpToWords platform n = roundUpTo n (platformWordSizeInBytes platform)
roundUpTo :: ByteOff -> ByteOff -> ByteOff
roundUpTo base size = (base + (size 1)) .&. (complement (size 1))
wordsToBytes :: Num a => Platform -> a -> a
wordsToBytes platform n = fromIntegral (platformWordSizeInBytes platform) * n
bytesToWordsRoundUp :: Platform -> ByteOff -> WordOff
bytesToWordsRoundUp platform n = (n + word_size 1) `quot` word_size
where word_size = platformWordSizeInBytes platform
newtype StgWord = StgWord Word64
deriving (Eq, Bits)
fromStgWord :: StgWord -> Integer
fromStgWord (StgWord i) = toInteger i
toStgWord :: Platform -> Integer -> StgWord
toStgWord platform i
= case platformWordSize platform of
PW4 -> StgWord (fromIntegral (fromInteger i :: Word32))
PW8 -> StgWord (fromInteger i)
instance Outputable StgWord where
ppr (StgWord i) = integer (toInteger i)
newtype StgHalfWord = StgHalfWord Word32
deriving Eq
fromStgHalfWord :: StgHalfWord -> Integer
fromStgHalfWord (StgHalfWord w) = toInteger w
toStgHalfWord :: Platform -> Integer -> StgHalfWord
toStgHalfWord platform i
= case platformWordSize platform of
PW4 -> StgHalfWord (fromIntegral (fromInteger i :: Word16))
PW8 -> StgHalfWord (fromInteger i :: Word32)
instance Outputable StgHalfWord where
ppr (StgHalfWord w) = integer (toInteger w)
halfWordSize :: Platform -> ByteOff
halfWordSize platform = platformWordSizeInBytes platform `div` 2
halfWordSizeInBits :: Platform -> Int
halfWordSizeInBits platform = platformWordSizeInBits platform `div` 2
data SMRep
= HeapRep
IsStatic
!WordOff
!WordOff
ClosureTypeInfo
| ArrayPtrsRep
!WordOff
!WordOff
| SmallArrayPtrsRep
!WordOff
| ArrayWordsRep
!WordOff
| StackRep
Liveness
| RTSRep
Int
SMRep
type IsStatic = Bool
data ClosureTypeInfo
= Constr ConTagZ ConstrDescription
| Fun FunArity ArgDescr
| Thunk
| ThunkSelector SelectorOffset
| BlackHole
| IndStatic
type ConstrDescription = ByteString
type FunArity = Int
type SelectorOffset = Int
mkHeapRep :: Profile -> IsStatic -> WordOff -> WordOff -> ClosureTypeInfo
-> SMRep
mkHeapRep profile is_static ptr_wds nonptr_wds cl_type_info
= HeapRep is_static
ptr_wds
(nonptr_wds + slop_wds)
cl_type_info
where
slop_wds
| is_static = 0
| otherwise = max 0 (minClosureSize profile (hdr_size + payload_size))
hdr_size = closureTypeHdrSize profile cl_type_info
payload_size = ptr_wds + nonptr_wds
mkRTSRep :: Int -> SMRep -> SMRep
mkRTSRep = RTSRep
mkStackRep :: [Bool] -> SMRep
mkStackRep liveness = StackRep liveness
blackHoleRep :: SMRep
blackHoleRep = HeapRep False 0 0 BlackHole
indStaticRep :: SMRep
indStaticRep = HeapRep True 1 0 IndStatic
arrPtrsRep :: Platform -> WordOff -> SMRep
arrPtrsRep platform elems = ArrayPtrsRep elems (cardTableSizeW platform elems)
smallArrPtrsRep :: WordOff -> SMRep
smallArrPtrsRep elems = SmallArrayPtrsRep elems
arrWordsRep :: Platform -> ByteOff -> SMRep
arrWordsRep platform bytes = ArrayWordsRep (bytesToWordsRoundUp platform bytes)
isStaticRep :: SMRep -> IsStatic
isStaticRep (HeapRep is_static _ _ _) = is_static
isStaticRep (RTSRep _ rep) = isStaticRep rep
isStaticRep _ = False
isStackRep :: SMRep -> Bool
isStackRep StackRep{} = True
isStackRep (RTSRep _ rep) = isStackRep rep
isStackRep _ = False
isConRep :: SMRep -> Bool
isConRep (HeapRep _ _ _ Constr{}) = True
isConRep _ = False
isThunkRep :: SMRep -> Bool
isThunkRep (HeapRep _ _ _ Thunk) = True
isThunkRep (HeapRep _ _ _ ThunkSelector{}) = True
isThunkRep (HeapRep _ _ _ BlackHole) = True
isThunkRep (HeapRep _ _ _ IndStatic) = True
isThunkRep _ = False
isFunRep :: SMRep -> Bool
isFunRep (HeapRep _ _ _ Fun{}) = True
isFunRep _ = False
isStaticNoCafCon :: SMRep -> Bool
isStaticNoCafCon (HeapRep _ 0 _ Constr{}) = True
isStaticNoCafCon _ = False
fixedHdrSize :: Profile -> ByteOff
fixedHdrSize profile = wordsToBytes (profilePlatform profile) (fixedHdrSizeW profile)
fixedHdrSizeW :: Profile -> WordOff
fixedHdrSizeW profile = pc_STD_HDR_SIZE (profileConstants profile) + profHdrSize profile
profHdrSize :: Profile -> WordOff
profHdrSize profile =
if profileIsProfiling profile
then pc_PROF_HDR_SIZE (profileConstants profile)
else 0
minClosureSize :: Profile -> WordOff
minClosureSize profile
= fixedHdrSizeW profile
+ pc_MIN_PAYLOAD_SIZE (profileConstants profile)
arrWordsHdrSize :: Profile -> ByteOff
arrWordsHdrSize profile
= fixedHdrSize profile
+ pc_SIZEOF_StgArrBytes_NoHdr (profileConstants profile)
arrWordsHdrSizeW :: Profile -> WordOff
arrWordsHdrSizeW profile
= fixedHdrSizeW profile
+ (pc_SIZEOF_StgArrBytes_NoHdr (profileConstants profile) `quot`
platformWordSizeInBytes (profilePlatform profile))
arrPtrsHdrSize :: Profile -> ByteOff
arrPtrsHdrSize profile
= fixedHdrSize profile
+ pc_SIZEOF_StgMutArrPtrs_NoHdr (profileConstants profile)
arrPtrsHdrSizeW :: Profile -> WordOff
arrPtrsHdrSizeW profile
= fixedHdrSizeW profile
+ (pc_SIZEOF_StgMutArrPtrs_NoHdr (profileConstants profile) `quot`
platformWordSizeInBytes (profilePlatform profile))
smallArrPtrsHdrSize :: Profile -> ByteOff
smallArrPtrsHdrSize profile
= fixedHdrSize profile
+ pc_SIZEOF_StgSmallMutArrPtrs_NoHdr (profileConstants profile)
smallArrPtrsHdrSizeW :: Profile -> WordOff
smallArrPtrsHdrSizeW profile
= fixedHdrSizeW profile
+ (pc_SIZEOF_StgSmallMutArrPtrs_NoHdr (profileConstants profile) `quot`
platformWordSizeInBytes (profilePlatform profile))
thunkHdrSize :: Profile -> WordOff
thunkHdrSize profile = fixedHdrSizeW profile + smp_hdr
where
platform = profilePlatform profile
smp_hdr = pc_SIZEOF_StgSMPThunkHeader (platformConstants platform) `quot`
platformWordSizeInBytes platform
hdrSize :: Profile -> SMRep -> ByteOff
hdrSize profile rep = wordsToBytes (profilePlatform profile) (hdrSizeW profile rep)
hdrSizeW :: Profile -> SMRep -> WordOff
hdrSizeW profile (HeapRep _ _ _ ty) = closureTypeHdrSize profile ty
hdrSizeW profile (ArrayPtrsRep _ _) = arrPtrsHdrSizeW profile
hdrSizeW profile (SmallArrayPtrsRep _) = smallArrPtrsHdrSizeW profile
hdrSizeW profile (ArrayWordsRep _) = arrWordsHdrSizeW profile
hdrSizeW _ _ = panic "GHC.Runtime.Heap.Layout.hdrSizeW"
nonHdrSize :: Platform -> SMRep -> ByteOff
nonHdrSize platform rep = wordsToBytes platform (nonHdrSizeW rep)
nonHdrSizeW :: SMRep -> WordOff
nonHdrSizeW (HeapRep _ p np _) = p + np
nonHdrSizeW (ArrayPtrsRep elems ct) = elems + ct
nonHdrSizeW (SmallArrayPtrsRep elems) = elems
nonHdrSizeW (ArrayWordsRep words) = words
nonHdrSizeW (StackRep bs) = length bs
nonHdrSizeW (RTSRep _ rep) = nonHdrSizeW rep
heapClosureSizeW :: Profile -> SMRep -> WordOff
heapClosureSizeW profile rep = case rep of
HeapRep _ p np ty -> closureTypeHdrSize profile ty + p + np
ArrayPtrsRep elems ct -> arrPtrsHdrSizeW profile + elems + ct
SmallArrayPtrsRep elems -> smallArrPtrsHdrSizeW profile + elems
ArrayWordsRep words -> arrWordsHdrSizeW profile + words
_ -> panic "GHC.Runtime.Heap.Layout.heapClosureSize"
closureTypeHdrSize :: Profile -> ClosureTypeInfo -> WordOff
closureTypeHdrSize profile ty = case ty of
Thunk -> thunkHdrSize profile
ThunkSelector{} -> thunkHdrSize profile
BlackHole -> thunkHdrSize profile
IndStatic -> thunkHdrSize profile
_ -> fixedHdrSizeW profile
card :: Platform -> Int -> Int
card platform i = i `shiftR` pc_MUT_ARR_PTRS_CARD_BITS (platformConstants platform)
cardRoundUp :: Platform -> Int -> Int
cardRoundUp platform i =
card platform (i + ((1 `shiftL` pc_MUT_ARR_PTRS_CARD_BITS (platformConstants platform)) 1))
cardTableSizeB :: Platform -> Int -> ByteOff
cardTableSizeB platform elems = cardRoundUp platform elems
cardTableSizeW :: Platform -> Int -> WordOff
cardTableSizeW platform elems =
bytesToWordsRoundUp platform (cardTableSizeB platform elems)
#include "../includes/rts/storage/ClosureTypes.h"
#include "../includes/rts/storage/FunTypes.h"
rtsClosureType :: SMRep -> Int
rtsClosureType rep
= case rep of
RTSRep ty _ -> ty
HeapRep _ 1 0 Constr{} -> CONSTR_1_0
HeapRep _ 0 1 Constr{} -> CONSTR_0_1
HeapRep _ 2 0 Constr{} -> CONSTR_2_0
HeapRep _ 1 1 Constr{} -> CONSTR_1_1
HeapRep _ 0 2 Constr{} -> CONSTR_0_2
HeapRep _ 0 _ Constr{} -> CONSTR_NOCAF
HeapRep _ _ _ Constr{} -> CONSTR
HeapRep False 1 0 Fun{} -> FUN_1_0
HeapRep False 0 1 Fun{} -> FUN_0_1
HeapRep False 2 0 Fun{} -> FUN_2_0
HeapRep False 1 1 Fun{} -> FUN_1_1
HeapRep False 0 2 Fun{} -> FUN_0_2
HeapRep False _ _ Fun{} -> FUN
HeapRep False 1 0 Thunk -> THUNK_1_0
HeapRep False 0 1 Thunk -> THUNK_0_1
HeapRep False 2 0 Thunk -> THUNK_2_0
HeapRep False 1 1 Thunk -> THUNK_1_1
HeapRep False 0 2 Thunk -> THUNK_0_2
HeapRep False _ _ Thunk -> THUNK
HeapRep False _ _ ThunkSelector{} -> THUNK_SELECTOR
HeapRep True _ _ Fun{} -> FUN_STATIC
HeapRep True _ _ Thunk -> THUNK_STATIC
HeapRep False _ _ BlackHole -> BLACKHOLE
HeapRep False _ _ IndStatic -> IND_STATIC
_ -> panic "rtsClosureType"
rET_SMALL, rET_BIG, aRG_GEN, aRG_GEN_BIG :: Int
rET_SMALL = RET_SMALL
rET_BIG = RET_BIG
aRG_GEN = ARG_GEN
aRG_GEN_BIG = ARG_GEN_BIG
instance Outputable ClosureTypeInfo where
ppr = pprTypeInfo
instance Outputable SMRep where
ppr (HeapRep static ps nps tyinfo)
= hang (header <+> lbrace) 2 (ppr tyinfo <+> rbrace)
where
header = text "HeapRep"
<+> if static then text "static" else empty
<+> pp_n "ptrs" ps <+> pp_n "nonptrs" nps
pp_n :: String -> Int -> SDoc
pp_n _ 0 = empty
pp_n s n = int n <+> text s
ppr (ArrayPtrsRep size _) = text "ArrayPtrsRep" <+> ppr size
ppr (SmallArrayPtrsRep size) = text "SmallArrayPtrsRep" <+> ppr size
ppr (ArrayWordsRep words) = text "ArrayWordsRep" <+> ppr words
ppr (StackRep bs) = text "StackRep" <+> ppr bs
ppr (RTSRep ty rep) = text "tag:" <> ppr ty <+> ppr rep
pprTypeInfo :: ClosureTypeInfo -> SDoc
pprTypeInfo (Constr tag descr)
= text "Con" <+>
braces (sep [ text "tag:" <+> ppr tag
, text "descr:" <> text (show descr) ])
pprTypeInfo (Fun arity args)
= text "Fun" <+>
braces (sep [ text "arity:" <+> ppr arity
, ptext (sLit ("fun_type:")) <+> ppr args ])
pprTypeInfo (ThunkSelector offset)
= text "ThunkSel" <+> ppr offset
pprTypeInfo Thunk = text "Thunk"
pprTypeInfo BlackHole = text "BlackHole"
pprTypeInfo IndStatic = text "IndStatic"