| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Runtime.Heap.Layout
Synopsis
- type WordOff = Int
 - type ByteOff = Int
 - wordsToBytes :: Num a => Platform -> a -> a
 - bytesToWordsRoundUp :: Platform -> ByteOff -> WordOff
 - roundUpToWords :: Platform -> ByteOff -> ByteOff
 - roundUpTo :: ByteOff -> ByteOff -> ByteOff
 - data StgWord
 - fromStgWord :: StgWord -> Integer
 - toStgWord :: Platform -> Integer -> StgWord
 - data StgHalfWord
 - fromStgHalfWord :: StgHalfWord -> Integer
 - toStgHalfWord :: Platform -> Integer -> StgHalfWord
 - halfWordSize :: Platform -> ByteOff
 - halfWordSizeInBits :: Platform -> Int
 - data SMRep
 - type IsStatic = Bool
 - data ClosureTypeInfo
- = Constr ConTagZ ConstrDescription
 - | Fun FunArity ArgDescr
 - | Thunk
 - | ThunkSelector SelectorOffset
 - | BlackHole
 - | IndStatic
 
 - data ArgDescr
- = ArgSpec !Int
 - | ArgGen Liveness
 - | ArgUnknown
 
 - type Liveness = [Bool]
 - type ConstrDescription = ByteString
 - mkHeapRep :: Profile -> IsStatic -> WordOff -> WordOff -> ClosureTypeInfo -> SMRep
 - blackHoleRep :: SMRep
 - indStaticRep :: SMRep
 - mkStackRep :: [Bool] -> SMRep
 - mkRTSRep :: Int -> SMRep -> SMRep
 - arrPtrsRep :: Platform -> WordOff -> SMRep
 - smallArrPtrsRep :: WordOff -> SMRep
 - arrWordsRep :: Platform -> ByteOff -> SMRep
 - isStaticRep :: SMRep -> IsStatic
 - isConRep :: SMRep -> Bool
 - isThunkRep :: SMRep -> Bool
 - isFunRep :: SMRep -> Bool
 - isStaticNoCafCon :: SMRep -> Bool
 - isStackRep :: SMRep -> Bool
 - heapClosureSizeW :: Profile -> SMRep -> WordOff
 - fixedHdrSizeW :: Profile -> WordOff
 - arrWordsHdrSize :: Profile -> ByteOff
 - arrWordsHdrSizeW :: Profile -> WordOff
 - arrPtrsHdrSize :: Profile -> ByteOff
 - arrPtrsHdrSizeW :: Profile -> WordOff
 - profHdrSize :: Profile -> WordOff
 - thunkHdrSize :: Profile -> WordOff
 - nonHdrSize :: Platform -> SMRep -> ByteOff
 - nonHdrSizeW :: SMRep -> WordOff
 - smallArrPtrsHdrSize :: Profile -> ByteOff
 - smallArrPtrsHdrSizeW :: Profile -> WordOff
 - hdrSize :: Profile -> SMRep -> ByteOff
 - hdrSizeW :: Profile -> SMRep -> WordOff
 - fixedHdrSize :: Profile -> ByteOff
 - rtsClosureType :: SMRep -> Int
 - rET_SMALL :: Int
 - rET_BIG :: Int
 - aRG_GEN :: Int
 - aRG_GEN_BIG :: Int
 - card :: Platform -> Int -> Int
 - cardRoundUp :: Platform -> Int -> Int
 - cardTableSizeB :: Platform -> Int -> ByteOff
 - cardTableSizeW :: Platform -> Int -> WordOff
 
Words and bytes
wordsToBytes :: Num a => Platform -> a -> a Source #
Convert the given number of words to a number of bytes.
This function morally has type WordOff -> ByteOff, but uses Num
 a to allow for overloading.
bytesToWordsRoundUp :: Platform -> ByteOff -> WordOff Source #
First round the given byte count up to a multiple of the machine's word size and then convert the result to words.
roundUpToWords :: Platform -> ByteOff -> ByteOff Source #
Round up the given byte count to the next byte count that's a multiple of the machine's word size.
Instances
| Bits StgWord Source # | |
Defined in GHC.Runtime.Heap.Layout Methods (.&.) :: StgWord -> StgWord -> StgWord Source # (.|.) :: StgWord -> StgWord -> StgWord Source # xor :: StgWord -> StgWord -> StgWord Source # complement :: StgWord -> StgWord Source # shift :: StgWord -> Int -> StgWord Source # rotate :: StgWord -> Int -> StgWord Source # bit :: Int -> StgWord Source # setBit :: StgWord -> Int -> StgWord Source # clearBit :: StgWord -> Int -> StgWord Source # complementBit :: StgWord -> Int -> StgWord Source # testBit :: StgWord -> Int -> Bool Source # bitSizeMaybe :: StgWord -> Maybe Int Source # bitSize :: StgWord -> Int Source # isSigned :: StgWord -> Bool Source # shiftL :: StgWord -> Int -> StgWord Source # unsafeShiftL :: StgWord -> Int -> StgWord Source # shiftR :: StgWord -> Int -> StgWord Source # unsafeShiftR :: StgWord -> Int -> StgWord Source # rotateL :: StgWord -> Int -> StgWord Source #  | |
| Outputable StgWord Source # | |
| Eq StgWord Source # | |
fromStgWord :: StgWord -> Integer Source #
data StgHalfWord Source #
Instances
| Outputable StgHalfWord Source # | |
Defined in GHC.Runtime.Heap.Layout Methods ppr :: StgHalfWord -> SDoc Source #  | |
| Eq StgHalfWord Source # | |
Defined in GHC.Runtime.Heap.Layout  | |
fromStgHalfWord :: StgHalfWord -> Integer Source #
toStgHalfWord :: Platform -> Integer -> StgHalfWord Source #
halfWordSize :: Platform -> ByteOff Source #
Half word size in bytes
halfWordSizeInBits :: Platform -> Int Source #
Closure representation
A description of the layout of a closure. Corresponds directly to the closure types in includes/rts/storage/ClosureTypes.h.
True <=> This is a static closure. Affects how we garbage-collect it. Static closure have an extra static link field at the end. Constructors do not have a static variant; see Note [static constructors]
data ClosureTypeInfo Source #
Constructors
| Constr ConTagZ ConstrDescription | |
| Fun FunArity ArgDescr | |
| Thunk | |
| ThunkSelector SelectorOffset | |
| BlackHole | |
| IndStatic | 
Instances
| Outputable ClosureTypeInfo Source # | |
Defined in GHC.Runtime.Heap.Layout Methods ppr :: ClosureTypeInfo -> SDoc Source #  | |
| Eq ClosureTypeInfo Source # | |
Defined in GHC.Runtime.Heap.Layout Methods (==) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool # (/=) :: ClosureTypeInfo -> ClosureTypeInfo -> Bool #  | |
An ArgDescr describes the argument pattern of a function
Constructors
| ArgSpec !Int | |
| ArgGen Liveness | |
| ArgUnknown | 
type Liveness = [Bool] Source #
We represent liveness bitmaps as a Bitmap (whose internal representation really is a bitmap). These are pinned onto case return vectors to indicate the state of the stack for the garbage collector.
In the compiled program, liveness bitmaps that fit inside a single word (StgWord) are stored as a single word, while larger bitmaps are stored as a pointer to an array of words.
type ConstrDescription = ByteString Source #
Construction
blackHoleRep :: SMRep Source #
indStaticRep :: SMRep Source #
mkStackRep :: [Bool] -> SMRep Source #
smallArrPtrsRep :: WordOff -> SMRep Source #
Predicates
isStaticRep :: SMRep -> IsStatic Source #
isThunkRep :: SMRep -> Bool Source #
isStaticNoCafCon :: SMRep -> Bool Source #
isStackRep :: SMRep -> Bool Source #
Size-related things
fixedHdrSizeW :: Profile -> WordOff Source #
Size of a closure header (StgHeader in includes/rts/storage/Closures.h)
arrWordsHdrSize :: Profile -> ByteOff Source #
arrWordsHdrSizeW :: Profile -> WordOff Source #
arrPtrsHdrSize :: Profile -> ByteOff Source #
arrPtrsHdrSizeW :: Profile -> WordOff Source #
profHdrSize :: Profile -> WordOff Source #
Size of the profiling part of a closure header (StgProfHeader in includes/rts/storage/Closures.h)
thunkHdrSize :: Profile -> WordOff Source #
nonHdrSizeW :: SMRep -> WordOff Source #
smallArrPtrsHdrSize :: Profile -> ByteOff Source #
fixedHdrSize :: Profile -> ByteOff Source #
RTS closure types
aRG_GEN_BIG :: Int Source #
Arrays
card :: Platform -> Int -> Int Source #
The byte offset into the card table of the card for a given element