-- (c) The University of Glasgow 2006
-- (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
--
-- Storage manager representation of closures

{-# LANGUAGE CPP,GeneralizedNewtypeDeriving #-}

module GHC.Runtime.Heap.Layout (
        -- * Words and bytes
        WordOff, ByteOff,
        wordsToBytes, bytesToWordsRoundUp,
        roundUpToWords, roundUpTo,

        StgWord, fromStgWord, toStgWord,
        StgHalfWord, fromStgHalfWord, toStgHalfWord,
        halfWordSize, halfWordSizeInBits,

        -- * Closure representation
        SMRep(..), -- CmmInfo sees the rep; no one else does
        IsStatic,
        ClosureTypeInfo(..), ArgDescr(..), Liveness,
        ConstrDescription,

        -- ** Construction
        mkHeapRep, blackHoleRep, indStaticRep, mkStackRep, mkRTSRep, arrPtrsRep,
        smallArrPtrsRep, arrWordsRep,

        -- ** Predicates
        isStaticRep, isConRep, isThunkRep, isFunRep, isStaticNoCafCon,
        isStackRep,

        -- ** Size-related things
        heapClosureSizeW,
        fixedHdrSizeW, arrWordsHdrSize, arrWordsHdrSizeW, arrPtrsHdrSize,
        arrPtrsHdrSizeW, profHdrSize, thunkHdrSize, nonHdrSize, nonHdrSizeW,
        smallArrPtrsHdrSize, smallArrPtrsHdrSizeW, hdrSize, hdrSizeW,
        fixedHdrSize,

        -- ** RTS closure types
        rtsClosureType, rET_SMALL, rET_BIG,
        aRG_GEN, aRG_GEN_BIG,

        -- ** Arrays
        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.ByteString (ByteString)

{-
************************************************************************
*                                                                      *
                Words and bytes
*                                                                      *
************************************************************************
-}

-- | Byte offset, or byte count
type ByteOff = Int

-- | Round up the given byte count to the next byte count that's a
-- multiple of the machine's word size.
roundUpToWords :: Platform -> ByteOff -> ByteOff
roundUpToWords :: Platform -> ByteOff -> ByteOff
roundUpToWords Platform
platform ByteOff
n = ByteOff -> ByteOff -> ByteOff
roundUpTo ByteOff
n (Platform -> ByteOff
platformWordSizeInBytes Platform
platform)

-- | Round up @base@ to a multiple of @size@.
roundUpTo :: ByteOff -> ByteOff -> ByteOff
roundUpTo :: ByteOff -> ByteOff -> ByteOff
roundUpTo ByteOff
base ByteOff
size = (ByteOff
base ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ (ByteOff
size ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
- ByteOff
1)) ByteOff -> ByteOff -> ByteOff
forall a. Bits a => a -> a -> a
.&. (ByteOff -> ByteOff
forall a. Bits a => a -> a
complement (ByteOff
size ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
- ByteOff
1))

-- | 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.
wordsToBytes :: Num a => Platform -> a -> a
wordsToBytes :: Platform -> a -> a
wordsToBytes Platform
platform a
n = ByteOff -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Platform -> ByteOff
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 #-}

-- | First round the given byte count up to a multiple of the
-- machine's word size and then convert the result to words.
bytesToWordsRoundUp :: Platform -> ByteOff -> WordOff
bytesToWordsRoundUp :: Platform -> ByteOff -> ByteOff
bytesToWordsRoundUp Platform
platform ByteOff
n = (ByteOff
n ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
word_size ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
- ByteOff
1) ByteOff -> ByteOff -> ByteOff
forall a. Integral a => a -> a -> a
`quot` ByteOff
word_size
 where word_size :: ByteOff
word_size = Platform -> ByteOff
platformWordSizeInBytes Platform
platform
-- StgWord is a type representing an StgWord on the target platform.
-- A Word64 is large enough to hold a Word for either a 32bit or 64bit 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
/= :: StgWord -> StgWord -> Bool
$c/= :: StgWord -> StgWord -> Bool
== :: StgWord -> StgWord -> Bool
$c== :: StgWord -> StgWord -> Bool
Eq, Eq StgWord
StgWord
Eq StgWord
-> (StgWord -> StgWord -> StgWord)
-> (StgWord -> StgWord -> StgWord)
-> (StgWord -> StgWord -> StgWord)
-> (StgWord -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> StgWord
-> (ByteOff -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff -> Bool)
-> (StgWord -> Maybe ByteOff)
-> (StgWord -> ByteOff)
-> (StgWord -> Bool)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff -> StgWord)
-> (StgWord -> ByteOff)
-> Bits StgWord
ByteOff -> StgWord
StgWord -> Bool
StgWord -> ByteOff
StgWord -> Maybe ByteOff
StgWord -> StgWord
StgWord -> ByteOff -> Bool
StgWord -> ByteOff -> StgWord
StgWord -> StgWord -> StgWord
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> ByteOff -> a)
-> (a -> ByteOff -> a)
-> a
-> (ByteOff -> a)
-> (a -> ByteOff -> a)
-> (a -> ByteOff -> a)
-> (a -> ByteOff -> a)
-> (a -> ByteOff -> Bool)
-> (a -> Maybe ByteOff)
-> (a -> ByteOff)
-> (a -> Bool)
-> (a -> ByteOff -> a)
-> (a -> ByteOff -> a)
-> (a -> ByteOff -> a)
-> (a -> ByteOff -> a)
-> (a -> ByteOff -> a)
-> (a -> ByteOff -> a)
-> (a -> ByteOff)
-> Bits a
popCount :: StgWord -> ByteOff
$cpopCount :: StgWord -> ByteOff
rotateR :: StgWord -> ByteOff -> StgWord
$crotateR :: StgWord -> ByteOff -> StgWord
rotateL :: StgWord -> ByteOff -> StgWord
$crotateL :: StgWord -> ByteOff -> StgWord
unsafeShiftR :: StgWord -> ByteOff -> StgWord
$cunsafeShiftR :: StgWord -> ByteOff -> StgWord
shiftR :: StgWord -> ByteOff -> StgWord
$cshiftR :: StgWord -> ByteOff -> StgWord
unsafeShiftL :: StgWord -> ByteOff -> StgWord
$cunsafeShiftL :: StgWord -> ByteOff -> StgWord
shiftL :: StgWord -> ByteOff -> StgWord
$cshiftL :: StgWord -> ByteOff -> StgWord
isSigned :: StgWord -> Bool
$cisSigned :: StgWord -> Bool
bitSize :: StgWord -> ByteOff
$cbitSize :: StgWord -> ByteOff
bitSizeMaybe :: StgWord -> Maybe ByteOff
$cbitSizeMaybe :: StgWord -> Maybe ByteOff
testBit :: StgWord -> ByteOff -> Bool
$ctestBit :: StgWord -> ByteOff -> Bool
complementBit :: StgWord -> ByteOff -> StgWord
$ccomplementBit :: StgWord -> ByteOff -> StgWord
clearBit :: StgWord -> ByteOff -> StgWord
$cclearBit :: StgWord -> ByteOff -> StgWord
setBit :: StgWord -> ByteOff -> StgWord
$csetBit :: StgWord -> ByteOff -> StgWord
bit :: ByteOff -> StgWord
$cbit :: ByteOff -> StgWord
zeroBits :: StgWord
$czeroBits :: StgWord
rotate :: StgWord -> ByteOff -> StgWord
$crotate :: StgWord -> ByteOff -> StgWord
shift :: StgWord -> ByteOff -> StgWord
$cshift :: StgWord -> ByteOff -> StgWord
complement :: StgWord -> StgWord
$ccomplement :: StgWord -> StgWord
xor :: StgWord -> StgWord -> StgWord
$cxor :: StgWord -> StgWord -> StgWord
.|. :: StgWord -> StgWord -> StgWord
$c.|. :: StgWord -> StgWord -> StgWord
.&. :: StgWord -> StgWord -> StgWord
$c.&. :: StgWord -> StgWord -> StgWord
$cp1Bits :: Eq StgWord
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
      -- These conversions mean that things like toStgWord (-1)
      -- do the right thing
      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
integer (Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger Word64
i)

--

-- A Word32 is large enough to hold half a Word for either a 32bit or
-- 64bit platform
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
/= :: StgHalfWord -> StgHalfWord -> Bool
$c/= :: StgHalfWord -> StgHalfWord -> Bool
== :: StgHalfWord -> StgHalfWord -> Bool
$c== :: 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
      -- These conversions mean that things like toStgHalfWord (-1)
      -- do the right thing
      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
integer (Word32 -> Integer
forall a. Integral a => a -> Integer
toInteger Word32
w)

-- | Half word size in bytes
halfWordSize :: Platform -> ByteOff
halfWordSize :: Platform -> ByteOff
halfWordSize Platform
platform = Platform -> ByteOff
platformWordSizeInBytes Platform
platform ByteOff -> ByteOff -> ByteOff
forall a. Integral a => a -> a -> a
`div` ByteOff
2

halfWordSizeInBits :: Platform -> Int
halfWordSizeInBits :: Platform -> ByteOff
halfWordSizeInBits Platform
platform = Platform -> ByteOff
platformWordSizeInBits Platform
platform ByteOff -> ByteOff -> ByteOff
forall a. Integral a => a -> a -> a
`div` ByteOff
2

{-
************************************************************************
*                                                                      *
\subsubsection[SMRep-datatype]{@SMRep@---storage manager representation}
*                                                                      *
************************************************************************
-}

-- | A description of the layout of a closure.  Corresponds directly
-- to the closure types in includes\/rts\/storage\/ClosureTypes.h.
data SMRep
  = HeapRep              -- GC routines consult sizes in info tbl
        IsStatic
        !WordOff         --  # ptr words
        !WordOff         --  # non-ptr words INCLUDING SLOP (see mkHeapRep below)
        ClosureTypeInfo  -- type-specific info

  | ArrayPtrsRep
        !WordOff        -- # ptr words
        !WordOff        -- # card table words

  | SmallArrayPtrsRep
        !WordOff        -- # ptr words

  | ArrayWordsRep
        !WordOff        -- # bytes expressed in words, rounded up

  | StackRep            -- Stack frame (RET_SMALL or RET_BIG)
        Liveness

  | RTSRep              -- The RTS needs to declare info tables with specific
        Int             -- type tags, so this form lets us override the default
        SMRep           -- tag for an SMRep.

-- | 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]
type IsStatic = Bool

-- From an SMRep you can get to the closure type defined in
-- includes/rts/storage/ClosureTypes.h. Described by the function
-- rtsClosureType below.

data ClosureTypeInfo
  = Constr        ConTagZ ConstrDescription
  | Fun           FunArity ArgDescr
  | Thunk
  | ThunkSelector SelectorOffset
  | BlackHole
  | IndStatic

type ConstrDescription = ByteString -- result of dataConIdentity
type FunArity          = Int
type SelectorOffset    = Int

-----------------------------------------------------------------------------
-- Construction

mkHeapRep :: Profile -> IsStatic -> WordOff -> WordOff -> ClosureTypeInfo
          -> SMRep
mkHeapRep :: Profile -> Bool -> ByteOff -> ByteOff -> ClosureTypeInfo -> SMRep
mkHeapRep Profile
profile Bool
is_static ByteOff
ptr_wds ByteOff
nonptr_wds ClosureTypeInfo
cl_type_info
  = Bool -> ByteOff -> ByteOff -> ClosureTypeInfo -> SMRep
HeapRep Bool
is_static
            ByteOff
ptr_wds
            (ByteOff
nonptr_wds ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
slop_wds)
            ClosureTypeInfo
cl_type_info
  where
     slop_wds :: ByteOff
slop_wds
      | Bool
is_static = ByteOff
0
      | Bool
otherwise = ByteOff -> ByteOff -> ByteOff
forall a. Ord a => a -> a -> a
max ByteOff
0 (Profile -> ByteOff
minClosureSize Profile
profile ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
- (ByteOff
hdr_size ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
payload_size))

     hdr_size :: ByteOff
hdr_size     = Profile -> ClosureTypeInfo -> ByteOff
closureTypeHdrSize Profile
profile ClosureTypeInfo
cl_type_info
     payload_size :: ByteOff
payload_size = ByteOff
ptr_wds ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
nonptr_wds

mkRTSRep :: Int -> SMRep -> SMRep
mkRTSRep :: ByteOff -> SMRep -> SMRep
mkRTSRep = ByteOff -> SMRep -> SMRep
RTSRep

mkStackRep :: [Bool] -> SMRep
mkStackRep :: [Bool] -> SMRep
mkStackRep [Bool]
liveness = [Bool] -> SMRep
StackRep [Bool]
liveness

blackHoleRep :: SMRep
blackHoleRep :: SMRep
blackHoleRep = Bool -> ByteOff -> ByteOff -> ClosureTypeInfo -> SMRep
HeapRep Bool
False ByteOff
0 ByteOff
0 ClosureTypeInfo
BlackHole

indStaticRep :: SMRep
indStaticRep :: SMRep
indStaticRep = Bool -> ByteOff -> ByteOff -> ClosureTypeInfo -> SMRep
HeapRep Bool
True ByteOff
1 ByteOff
0 ClosureTypeInfo
IndStatic

arrPtrsRep :: Platform -> WordOff -> SMRep
arrPtrsRep :: Platform -> ByteOff -> SMRep
arrPtrsRep Platform
platform ByteOff
elems = ByteOff -> ByteOff -> SMRep
ArrayPtrsRep ByteOff
elems (Platform -> ByteOff -> ByteOff
cardTableSizeW Platform
platform ByteOff
elems)

smallArrPtrsRep :: WordOff -> SMRep
smallArrPtrsRep :: ByteOff -> SMRep
smallArrPtrsRep ByteOff
elems = ByteOff -> SMRep
SmallArrayPtrsRep ByteOff
elems

arrWordsRep :: Platform -> ByteOff -> SMRep
arrWordsRep :: Platform -> ByteOff -> SMRep
arrWordsRep Platform
platform ByteOff
bytes = ByteOff -> SMRep
ArrayWordsRep (Platform -> ByteOff -> ByteOff
bytesToWordsRoundUp Platform
platform ByteOff
bytes)

-----------------------------------------------------------------------------
-- Predicates

isStaticRep :: SMRep -> IsStatic
isStaticRep :: SMRep -> Bool
isStaticRep (HeapRep Bool
is_static ByteOff
_ ByteOff
_ ClosureTypeInfo
_) = Bool
is_static
isStaticRep (RTSRep ByteOff
_ SMRep
rep)            = SMRep -> Bool
isStaticRep SMRep
rep
isStaticRep SMRep
_                         = Bool
False

isStackRep :: SMRep -> Bool
isStackRep :: SMRep -> Bool
isStackRep StackRep{}     = Bool
True
isStackRep (RTSRep ByteOff
_ SMRep
rep) = SMRep -> Bool
isStackRep SMRep
rep
isStackRep SMRep
_              = Bool
False

isConRep :: SMRep -> Bool
isConRep :: SMRep -> Bool
isConRep (HeapRep Bool
_ ByteOff
_ ByteOff
_ Constr{}) = Bool
True
isConRep SMRep
_                        = Bool
False

isThunkRep :: SMRep -> Bool
isThunkRep :: SMRep -> Bool
isThunkRep (HeapRep Bool
_ ByteOff
_ ByteOff
_ ClosureTypeInfo
Thunk)           = Bool
True
isThunkRep (HeapRep Bool
_ ByteOff
_ ByteOff
_ ThunkSelector{}) = Bool
True
isThunkRep (HeapRep Bool
_ ByteOff
_ ByteOff
_ ClosureTypeInfo
BlackHole)       = Bool
True
isThunkRep (HeapRep Bool
_ ByteOff
_ ByteOff
_ ClosureTypeInfo
IndStatic)       = Bool
True
isThunkRep SMRep
_                               = Bool
False

isFunRep :: SMRep -> Bool
isFunRep :: SMRep -> Bool
isFunRep (HeapRep Bool
_ ByteOff
_ ByteOff
_ Fun{}) = Bool
True
isFunRep SMRep
_                     = Bool
False

isStaticNoCafCon :: SMRep -> Bool
-- This should line up exactly with CONSTR_NOCAF below
-- See Note [Static NoCaf constructors]
isStaticNoCafCon :: SMRep -> Bool
isStaticNoCafCon (HeapRep Bool
_ ByteOff
0 ByteOff
_ Constr{}) = Bool
True
isStaticNoCafCon SMRep
_                        = Bool
False


-----------------------------------------------------------------------------
-- Size-related things

fixedHdrSize :: Profile -> ByteOff
fixedHdrSize :: Profile -> ByteOff
fixedHdrSize Profile
profile = Platform -> ByteOff -> ByteOff
forall a. Num a => Platform -> a -> a
wordsToBytes (Profile -> Platform
profilePlatform Profile
profile) (Profile -> ByteOff
fixedHdrSizeW Profile
profile)

-- | Size of a closure header (StgHeader in includes\/rts\/storage\/Closures.h)
fixedHdrSizeW :: Profile -> WordOff
fixedHdrSizeW :: Profile -> ByteOff
fixedHdrSizeW Profile
profile = PlatformConstants -> ByteOff
pc_STD_HDR_SIZE (Profile -> PlatformConstants
profileConstants Profile
profile) ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ Profile -> ByteOff
profHdrSize Profile
profile

-- | Size of the profiling part of a closure header
-- (StgProfHeader in includes\/rts\/storage\/Closures.h)
profHdrSize :: Profile -> WordOff
profHdrSize :: Profile -> ByteOff
profHdrSize Profile
profile =
   if Profile -> Bool
profileIsProfiling Profile
profile
      then PlatformConstants -> ByteOff
pc_PROF_HDR_SIZE (Profile -> PlatformConstants
profileConstants Profile
profile)
      else ByteOff
0

-- | The garbage collector requires that every closure is at least as
--   big as this.
minClosureSize :: Profile -> WordOff
minClosureSize :: Profile -> ByteOff
minClosureSize Profile
profile
 = Profile -> ByteOff
fixedHdrSizeW Profile
profile
   ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ PlatformConstants -> ByteOff
pc_MIN_PAYLOAD_SIZE (Profile -> PlatformConstants
profileConstants Profile
profile)

arrWordsHdrSize :: Profile -> ByteOff
arrWordsHdrSize :: Profile -> ByteOff
arrWordsHdrSize Profile
profile
 = Profile -> ByteOff
fixedHdrSize Profile
profile
   ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ PlatformConstants -> ByteOff
pc_SIZEOF_StgArrBytes_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile)

arrWordsHdrSizeW :: Profile -> WordOff
arrWordsHdrSizeW :: Profile -> ByteOff
arrWordsHdrSizeW Profile
profile
 = Profile -> ByteOff
fixedHdrSizeW Profile
profile
   ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ (PlatformConstants -> ByteOff
pc_SIZEOF_StgArrBytes_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile) ByteOff -> ByteOff -> ByteOff
forall a. Integral a => a -> a -> a
`quot`
      Platform -> ByteOff
platformWordSizeInBytes (Profile -> Platform
profilePlatform Profile
profile))

arrPtrsHdrSize :: Profile -> ByteOff
arrPtrsHdrSize :: Profile -> ByteOff
arrPtrsHdrSize Profile
profile
 = Profile -> ByteOff
fixedHdrSize Profile
profile
   ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ PlatformConstants -> ByteOff
pc_SIZEOF_StgMutArrPtrs_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile)

arrPtrsHdrSizeW :: Profile -> WordOff
arrPtrsHdrSizeW :: Profile -> ByteOff
arrPtrsHdrSizeW Profile
profile
 = Profile -> ByteOff
fixedHdrSizeW Profile
profile
   ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ (PlatformConstants -> ByteOff
pc_SIZEOF_StgMutArrPtrs_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile) ByteOff -> ByteOff -> ByteOff
forall a. Integral a => a -> a -> a
`quot`
      Platform -> ByteOff
platformWordSizeInBytes (Profile -> Platform
profilePlatform Profile
profile))

smallArrPtrsHdrSize :: Profile -> ByteOff
smallArrPtrsHdrSize :: Profile -> ByteOff
smallArrPtrsHdrSize Profile
profile
 = Profile -> ByteOff
fixedHdrSize Profile
profile
   ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ PlatformConstants -> ByteOff
pc_SIZEOF_StgSmallMutArrPtrs_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile)

smallArrPtrsHdrSizeW :: Profile -> WordOff
smallArrPtrsHdrSizeW :: Profile -> ByteOff
smallArrPtrsHdrSizeW Profile
profile
 = Profile -> ByteOff
fixedHdrSizeW Profile
profile
   ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ (PlatformConstants -> ByteOff
pc_SIZEOF_StgSmallMutArrPtrs_NoHdr (Profile -> PlatformConstants
profileConstants Profile
profile) ByteOff -> ByteOff -> ByteOff
forall a. Integral a => a -> a -> a
`quot`
      Platform -> ByteOff
platformWordSizeInBytes (Profile -> Platform
profilePlatform Profile
profile))

-- Thunks have an extra header word on SMP, so the update doesn't
-- splat the payload.
thunkHdrSize :: Profile -> WordOff
thunkHdrSize :: Profile -> ByteOff
thunkHdrSize Profile
profile = Profile -> ByteOff
fixedHdrSizeW Profile
profile ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
smp_hdr
        where
         platform :: Platform
platform = Profile -> Platform
profilePlatform Profile
profile
         smp_hdr :: ByteOff
smp_hdr  = PlatformConstants -> ByteOff
pc_SIZEOF_StgSMPThunkHeader (Platform -> PlatformConstants
platformConstants Platform
platform) ByteOff -> ByteOff -> ByteOff
forall a. Integral a => a -> a -> a
`quot`
                         Platform -> ByteOff
platformWordSizeInBytes Platform
platform

hdrSize :: Profile -> SMRep -> ByteOff
hdrSize :: Profile -> SMRep -> ByteOff
hdrSize Profile
profile SMRep
rep = Platform -> ByteOff -> ByteOff
forall a. Num a => Platform -> a -> a
wordsToBytes (Profile -> Platform
profilePlatform Profile
profile) (Profile -> SMRep -> ByteOff
hdrSizeW Profile
profile SMRep
rep)

hdrSizeW :: Profile -> SMRep -> WordOff
hdrSizeW :: Profile -> SMRep -> ByteOff
hdrSizeW Profile
profile (HeapRep Bool
_ ByteOff
_ ByteOff
_ ClosureTypeInfo
ty)    = Profile -> ClosureTypeInfo -> ByteOff
closureTypeHdrSize Profile
profile ClosureTypeInfo
ty
hdrSizeW Profile
profile (ArrayPtrsRep ByteOff
_ ByteOff
_)    = Profile -> ByteOff
arrPtrsHdrSizeW Profile
profile
hdrSizeW Profile
profile (SmallArrayPtrsRep ByteOff
_) = Profile -> ByteOff
smallArrPtrsHdrSizeW Profile
profile
hdrSizeW Profile
profile (ArrayWordsRep ByteOff
_)     = Profile -> ByteOff
arrWordsHdrSizeW Profile
profile
hdrSizeW Profile
_ SMRep
_                           = String -> ByteOff
forall a. String -> a
panic String
"GHC.Runtime.Heap.Layout.hdrSizeW"

nonHdrSize :: Platform -> SMRep -> ByteOff
nonHdrSize :: Platform -> SMRep -> ByteOff
nonHdrSize Platform
platform SMRep
rep = Platform -> ByteOff -> ByteOff
forall a. Num a => Platform -> a -> a
wordsToBytes Platform
platform (SMRep -> ByteOff
nonHdrSizeW SMRep
rep)

nonHdrSizeW :: SMRep -> WordOff
nonHdrSizeW :: SMRep -> ByteOff
nonHdrSizeW (HeapRep Bool
_ ByteOff
p ByteOff
np ClosureTypeInfo
_) = ByteOff
p ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
np
nonHdrSizeW (ArrayPtrsRep ByteOff
elems ByteOff
ct) = ByteOff
elems ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
ct
nonHdrSizeW (SmallArrayPtrsRep ByteOff
elems) = ByteOff
elems
nonHdrSizeW (ArrayWordsRep ByteOff
words) = ByteOff
words
nonHdrSizeW (StackRep [Bool]
bs)      = [Bool] -> ByteOff
forall (t :: * -> *) a. Foldable t => t a -> ByteOff
length [Bool]
bs
nonHdrSizeW (RTSRep ByteOff
_ SMRep
rep)     = SMRep -> ByteOff
nonHdrSizeW SMRep
rep

-- | The total size of the closure, in words.
heapClosureSizeW :: Profile -> SMRep -> WordOff
heapClosureSizeW :: Profile -> SMRep -> ByteOff
heapClosureSizeW Profile
profile SMRep
rep = case SMRep
rep of
   HeapRep Bool
_ ByteOff
p ByteOff
np ClosureTypeInfo
ty       -> Profile -> ClosureTypeInfo -> ByteOff
closureTypeHdrSize Profile
profile ClosureTypeInfo
ty ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
p ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
np
   ArrayPtrsRep ByteOff
elems ByteOff
ct   -> Profile -> ByteOff
arrPtrsHdrSizeW Profile
profile ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
elems ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
ct
   SmallArrayPtrsRep ByteOff
elems -> Profile -> ByteOff
smallArrPtrsHdrSizeW Profile
profile ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
elems
   ArrayWordsRep ByteOff
words     -> Profile -> ByteOff
arrWordsHdrSizeW Profile
profile ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ByteOff
words
   SMRep
_                       -> String -> ByteOff
forall a. String -> a
panic String
"GHC.Runtime.Heap.Layout.heapClosureSize"

closureTypeHdrSize :: Profile -> ClosureTypeInfo -> WordOff
closureTypeHdrSize :: Profile -> ClosureTypeInfo -> ByteOff
closureTypeHdrSize Profile
profile ClosureTypeInfo
ty = case ClosureTypeInfo
ty of
                  ClosureTypeInfo
Thunk           -> Profile -> ByteOff
thunkHdrSize Profile
profile
                  ThunkSelector{} -> Profile -> ByteOff
thunkHdrSize Profile
profile
                  ClosureTypeInfo
BlackHole       -> Profile -> ByteOff
thunkHdrSize Profile
profile
                  ClosureTypeInfo
IndStatic       -> Profile -> ByteOff
thunkHdrSize Profile
profile
                  ClosureTypeInfo
_               -> Profile -> ByteOff
fixedHdrSizeW Profile
profile
        -- All thunks use thunkHdrSize, even if they are non-updatable.
        -- this is because we don't have separate closure types for
        -- updatable vs. non-updatable thunks, so the GC can't tell the
        -- difference.  If we ever have significant numbers of non-
        -- updatable thunks, it might be worth fixing this.

-- ---------------------------------------------------------------------------
-- Arrays

-- | The byte offset into the card table of the card for a given element
card :: Platform -> Int -> Int
card :: Platform -> ByteOff -> ByteOff
card Platform
platform ByteOff
i = ByteOff
i ByteOff -> ByteOff -> ByteOff
forall a. Bits a => a -> ByteOff -> a
`shiftR` PlatformConstants -> ByteOff
pc_MUT_ARR_PTRS_CARD_BITS (Platform -> PlatformConstants
platformConstants Platform
platform)

-- | Convert a number of elements to a number of cards, rounding up
cardRoundUp :: Platform -> Int -> Int
cardRoundUp :: Platform -> ByteOff -> ByteOff
cardRoundUp Platform
platform ByteOff
i =
  Platform -> ByteOff -> ByteOff
card Platform
platform (ByteOff
i ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
+ ((ByteOff
1 ByteOff -> ByteOff -> ByteOff
forall a. Bits a => a -> ByteOff -> a
`shiftL` PlatformConstants -> ByteOff
pc_MUT_ARR_PTRS_CARD_BITS (Platform -> PlatformConstants
platformConstants Platform
platform)) ByteOff -> ByteOff -> ByteOff
forall a. Num a => a -> a -> a
- ByteOff
1))

-- | The size of a card table, in bytes
cardTableSizeB :: Platform -> Int -> ByteOff
cardTableSizeB :: Platform -> ByteOff -> ByteOff
cardTableSizeB Platform
platform ByteOff
elems = Platform -> ByteOff -> ByteOff
cardRoundUp Platform
platform ByteOff
elems

-- | The size of a card table, in words
cardTableSizeW :: Platform -> Int -> WordOff
cardTableSizeW :: Platform -> ByteOff -> ByteOff
cardTableSizeW Platform
platform ByteOff
elems =
  Platform -> ByteOff -> ByteOff
bytesToWordsRoundUp Platform
platform (Platform -> ByteOff -> ByteOff
cardTableSizeB Platform
platform ByteOff
elems)

-----------------------------------------------------------------------------
-- deriving the RTS closure type from an SMRep

#include "rts/storage/ClosureTypes.h"
#include "rts/storage/FunTypes.h"
-- Defines CONSTR, CONSTR_1_0 etc

-- | Derives the RTS closure type from an 'SMRep'
rtsClosureType :: SMRep -> Int
rtsClosureType :: SMRep -> ByteOff
rtsClosureType SMRep
rep
    = case SMRep
rep of
      RTSRep ByteOff
ty SMRep
_ -> ByteOff
ty

      -- See Note [static constructors]
      HeapRep Bool
_     ByteOff
1 ByteOff
0 Constr{} -> CONSTR_1_0
      HeapRep Bool
_     ByteOff
0 ByteOff
1 Constr{} -> CONSTR_0_1
      HeapRep Bool
_     ByteOff
2 ByteOff
0 Constr{} -> CONSTR_2_0
      HeapRep Bool
_     ByteOff
1 ByteOff
1 Constr{} -> CONSTR_1_1
      HeapRep Bool
_     ByteOff
0 ByteOff
2 Constr{} -> CONSTR_0_2
      HeapRep Bool
_     ByteOff
0 ByteOff
_ Constr{} -> CONSTR_NOCAF
           -- See Note [Static NoCaf constructors]
      HeapRep Bool
_     ByteOff
_ ByteOff
_ Constr{} -> CONSTR

      HeapRep Bool
False ByteOff
1 ByteOff
0 Fun{} -> FUN_1_0
      HeapRep Bool
False ByteOff
0 ByteOff
1 Fun{} -> FUN_0_1
      HeapRep Bool
False ByteOff
2 ByteOff
0 Fun{} -> FUN_2_0
      HeapRep Bool
False ByteOff
1 ByteOff
1 Fun{} -> FUN_1_1
      HeapRep Bool
False ByteOff
0 ByteOff
2 Fun{} -> FUN_0_2
      HeapRep Bool
False ByteOff
_ ByteOff
_ Fun{} -> FUN

      HeapRep Bool
False ByteOff
1 ByteOff
0 ClosureTypeInfo
Thunk -> THUNK_1_0
      HeapRep Bool
False ByteOff
0 ByteOff
1 ClosureTypeInfo
Thunk -> THUNK_0_1
      HeapRep Bool
False ByteOff
2 ByteOff
0 ClosureTypeInfo
Thunk -> THUNK_2_0
      HeapRep Bool
False ByteOff
1 ByteOff
1 ClosureTypeInfo
Thunk -> THUNK_1_1
      HeapRep Bool
False ByteOff
0 ByteOff
2 ClosureTypeInfo
Thunk -> THUNK_0_2
      HeapRep Bool
False ByteOff
_ ByteOff
_ ClosureTypeInfo
Thunk -> THUNK

      HeapRep Bool
False ByteOff
_ ByteOff
_ ThunkSelector{} ->  THUNK_SELECTOR

      HeapRep Bool
True ByteOff
_ ByteOff
_ Fun{}      -> FUN_STATIC
      HeapRep Bool
True ByteOff
_ ByteOff
_ ClosureTypeInfo
Thunk      -> THUNK_STATIC
      HeapRep Bool
False ByteOff
_ ByteOff
_ ClosureTypeInfo
BlackHole -> BLACKHOLE
      HeapRep Bool
False ByteOff
_ ByteOff
_ ClosureTypeInfo
IndStatic -> IND_STATIC

      SMRep
_ -> String -> ByteOff
forall a. String -> a
panic String
"rtsClosureType"

-- We export these ones
rET_SMALL, rET_BIG, aRG_GEN, aRG_GEN_BIG :: Int
rET_SMALL :: ByteOff
rET_SMALL   = RET_SMALL
rET_BIG :: ByteOff
rET_BIG     = RET_BIG
aRG_GEN :: ByteOff
aRG_GEN     = ARG_GEN
aRG_GEN_BIG :: ByteOff
aRG_GEN_BIG = ARG_GEN_BIG

{-
Note [static constructors]
~~~~~~~~~~~~~~~~~~~~~~~~~~

We used to have a CONSTR_STATIC closure type, and each constructor had
two info tables: one with CONSTR (or CONSTR_1_0 etc.), and one with
CONSTR_STATIC.

This distinction was removed, because when copying a data structure
into a compact region, we must copy static constructors into the
compact region too.  If we didn't do this, we would need to track the
references from the compact region out to the static constructors,
because they might (indirectly) refer to CAFs.

Since static constructors will be copied to the heap, if we wanted to
use different info tables for static and dynamic constructors, we
would have to switch the info pointer when copying the constructor
into the compact region, which means we would need an extra field of
the static info table to point to the dynamic one.

However, since the distinction between static and dynamic closure
types is never actually needed (other than for assertions), we can
just drop the distinction and use the same info table for both.

The GC *does* need to distinguish between static and dynamic closures,
but it does this using the HEAP_ALLOCED() macro which checks whether
the address of the closure resides within the dynamic heap.
HEAP_ALLOCED() doesn't read the closure's info table.

Note [Static NoCaf constructors]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
If we know that a top-level binding 'x' is not Caffy (ie no CAFs are
reachable from 'x'), then a statically allocated constructor (Just x)
is also not Caffy, and the garbage collector need not follow its
argument fields.  Exploiting this would require two static info tables
for Just, for the two cases where the argument was Caffy or non-Caffy.

Currently we don't do this; instead we treat nullary constructors
as non-Caffy, and the others as potentially Caffy.


************************************************************************
*                                                                      *
             Pretty printing of SMRep and friends
*                                                                      *
************************************************************************
-}

instance Outputable ClosureTypeInfo where
   ppr :: ClosureTypeInfo -> SDoc
ppr = ClosureTypeInfo -> SDoc
pprTypeInfo

instance Outputable SMRep where
   ppr :: SMRep -> SDoc
ppr (HeapRep Bool
static ByteOff
ps ByteOff
nps ClosureTypeInfo
tyinfo)
     = SDoc -> ByteOff -> SDoc -> SDoc
hang (SDoc
header SDoc -> SDoc -> SDoc
<+> SDoc
lbrace) ByteOff
2 (ClosureTypeInfo -> SDoc
forall a. Outputable a => a -> SDoc
ppr ClosureTypeInfo
tyinfo SDoc -> SDoc -> SDoc
<+> SDoc
rbrace)
     where
       header :: SDoc
header = String -> SDoc
text String
"HeapRep"
                SDoc -> SDoc -> SDoc
<+> if Bool
static then String -> SDoc
text String
"static" else SDoc
empty
                SDoc -> SDoc -> SDoc
<+> String -> ByteOff -> SDoc
pp_n String
"ptrs" ByteOff
ps SDoc -> SDoc -> SDoc
<+> String -> ByteOff -> SDoc
pp_n String
"nonptrs" ByteOff
nps
       pp_n :: String -> Int -> SDoc
       pp_n :: String -> ByteOff -> SDoc
pp_n String
_ ByteOff
0 = SDoc
empty
       pp_n String
s ByteOff
n = ByteOff -> SDoc
int ByteOff
n SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
s

   ppr (ArrayPtrsRep ByteOff
size ByteOff
_) = String -> SDoc
text String
"ArrayPtrsRep" SDoc -> SDoc -> SDoc
<+> ByteOff -> SDoc
forall a. Outputable a => a -> SDoc
ppr ByteOff
size

   ppr (SmallArrayPtrsRep ByteOff
size) = String -> SDoc
text String
"SmallArrayPtrsRep" SDoc -> SDoc -> SDoc
<+> ByteOff -> SDoc
forall a. Outputable a => a -> SDoc
ppr ByteOff
size

   ppr (ArrayWordsRep ByteOff
words) = String -> SDoc
text String
"ArrayWordsRep" SDoc -> SDoc -> SDoc
<+> ByteOff -> SDoc
forall a. Outputable a => a -> SDoc
ppr ByteOff
words

   ppr (StackRep [Bool]
bs) = String -> SDoc
text String
"StackRep" SDoc -> SDoc -> SDoc
<+> [Bool] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Bool]
bs

   ppr (RTSRep ByteOff
ty SMRep
rep) = String -> SDoc
text String
"tag:" SDoc -> SDoc -> SDoc
<> ByteOff -> SDoc
forall a. Outputable a => a -> SDoc
ppr ByteOff
ty SDoc -> SDoc -> SDoc
<+> SMRep -> SDoc
forall a. Outputable a => a -> SDoc
ppr SMRep
rep

pprTypeInfo :: ClosureTypeInfo -> SDoc
pprTypeInfo :: ClosureTypeInfo -> SDoc
pprTypeInfo (Constr ByteOff
tag ConstrDescription
descr)
  = String -> SDoc
text String
"Con" SDoc -> SDoc -> SDoc
<+>
    SDoc -> SDoc
braces ([SDoc] -> SDoc
sep [ String -> SDoc
text String
"tag:" SDoc -> SDoc -> SDoc
<+> ByteOff -> SDoc
forall a. Outputable a => a -> SDoc
ppr ByteOff
tag
                , String -> SDoc
text String
"descr:" SDoc -> SDoc -> SDoc
<> String -> SDoc
text (ConstrDescription -> String
forall a. Show a => a -> String
show ConstrDescription
descr) ])

pprTypeInfo (Fun ByteOff
arity ArgDescr
args)
  = String -> SDoc
text String
"Fun" SDoc -> SDoc -> SDoc
<+>
    SDoc -> SDoc
braces ([SDoc] -> SDoc
sep [ String -> SDoc
text String
"arity:" SDoc -> SDoc -> SDoc
<+> ByteOff -> SDoc
forall a. Outputable a => a -> SDoc
ppr ByteOff
arity
                , PtrString -> SDoc
ptext (String -> PtrString
sLit (String
"fun_type:")) SDoc -> SDoc -> SDoc
<+> ArgDescr -> SDoc
forall a. Outputable a => a -> SDoc
ppr ArgDescr
args ])

pprTypeInfo (ThunkSelector ByteOff
offset)
  = String -> SDoc
text String
"ThunkSel" SDoc -> SDoc -> SDoc
<+> ByteOff -> SDoc
forall a. Outputable a => a -> SDoc
ppr ByteOff
offset

pprTypeInfo ClosureTypeInfo
Thunk     = String -> SDoc
text String
"Thunk"
pprTypeInfo ClosureTypeInfo
BlackHole = String -> SDoc
text String
"BlackHole"
pprTypeInfo ClosureTypeInfo
IndStatic = String -> SDoc
text String
"IndStatic"