never executed always true always false
    1 -- (c) The University of Glasgow 2006
    2 -- (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
    3 --
    4 -- Storage manager representation of closures
    5 
    6 {-# LANGUAGE CPP #-}
    7 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
    8 
    9 module GHC.Runtime.Heap.Layout (
   10         -- * Words and bytes
   11         WordOff, ByteOff,
   12         wordsToBytes, bytesToWordsRoundUp,
   13         roundUpToWords, roundUpTo,
   14 
   15         StgWord, fromStgWord, toStgWord,
   16         StgHalfWord, fromStgHalfWord, toStgHalfWord,
   17         halfWordSize, halfWordSizeInBits,
   18 
   19         -- * Closure representation
   20         SMRep(..), -- CmmInfo sees the rep; no one else does
   21         IsStatic,
   22         ClosureTypeInfo(..), ArgDescr(..), Liveness,
   23         ConstrDescription,
   24 
   25         -- ** Construction
   26         mkHeapRep, blackHoleRep, indStaticRep, mkStackRep, mkRTSRep, arrPtrsRep,
   27         smallArrPtrsRep, arrWordsRep,
   28 
   29         -- ** Predicates
   30         isStaticRep, isConRep, isThunkRep, isFunRep, isStaticNoCafCon,
   31         isStackRep,
   32 
   33         -- ** Size-related things
   34         heapClosureSizeW,
   35         fixedHdrSizeW, arrWordsHdrSize, arrWordsHdrSizeW, arrPtrsHdrSize,
   36         arrPtrsHdrSizeW, profHdrSize, thunkHdrSize, nonHdrSize, nonHdrSizeW,
   37         smallArrPtrsHdrSize, smallArrPtrsHdrSizeW, hdrSize, hdrSizeW,
   38         fixedHdrSize,
   39 
   40         -- ** RTS closure types
   41         rtsClosureType, rET_SMALL, rET_BIG,
   42         aRG_GEN, aRG_GEN_BIG,
   43 
   44         -- ** Arrays
   45         card, cardRoundUp, cardTableSizeB, cardTableSizeW
   46     ) where
   47 
   48 import GHC.Prelude
   49 
   50 import GHC.Types.Basic( ConTagZ )
   51 import GHC.Driver.Session
   52 import GHC.Platform
   53 import GHC.Platform.Profile
   54 import GHC.StgToCmm.Types
   55 
   56 import GHC.Utils.Outputable
   57 import GHC.Utils.Panic
   58 
   59 import Data.Word
   60 import Data.ByteString (ByteString)
   61 
   62 {-
   63 ************************************************************************
   64 *                                                                      *
   65                 Words and bytes
   66 *                                                                      *
   67 ************************************************************************
   68 -}
   69 
   70 -- | Byte offset, or byte count
   71 type ByteOff = Int
   72 
   73 -- | Round up the given byte count to the next byte count that's a
   74 -- multiple of the machine's word size.
   75 roundUpToWords :: Platform -> ByteOff -> ByteOff
   76 roundUpToWords platform n = roundUpTo n (platformWordSizeInBytes platform)
   77 
   78 -- | Round up @base@ to a multiple of @size@.
   79 roundUpTo :: ByteOff -> ByteOff -> ByteOff
   80 roundUpTo base size = (base + (size - 1)) .&. (complement (size - 1))
   81 
   82 -- | Convert the given number of words to a number of bytes.
   83 --
   84 -- This function morally has type @WordOff -> ByteOff@, but uses @Num
   85 -- a@ to allow for overloading.
   86 wordsToBytes :: Num a => Platform -> a -> a
   87 wordsToBytes platform n = fromIntegral (platformWordSizeInBytes platform) * n
   88 {-# SPECIALIZE wordsToBytes :: Platform -> Int -> Int #-}
   89 {-# SPECIALIZE wordsToBytes :: Platform -> Word -> Word #-}
   90 {-# SPECIALIZE wordsToBytes :: Platform -> Integer -> Integer #-}
   91 
   92 -- | First round the given byte count up to a multiple of the
   93 -- machine's word size and then convert the result to words.
   94 bytesToWordsRoundUp :: Platform -> ByteOff -> WordOff
   95 bytesToWordsRoundUp platform n = (n + word_size - 1) `quot` word_size
   96  where word_size = platformWordSizeInBytes platform
   97 -- StgWord is a type representing an StgWord on the target platform.
   98 -- A Word64 is large enough to hold a Word for either a 32bit or 64bit platform
   99 newtype StgWord = StgWord Word64
  100     deriving (Eq, Bits)
  101 
  102 fromStgWord :: StgWord -> Integer
  103 fromStgWord (StgWord i) = toInteger i
  104 
  105 toStgWord :: Platform -> Integer -> StgWord
  106 toStgWord platform i
  107     = case platformWordSize platform of
  108       -- These conversions mean that things like toStgWord (-1)
  109       -- do the right thing
  110       PW4 -> StgWord (fromIntegral (fromInteger i :: Word32))
  111       PW8 -> StgWord (fromInteger i)
  112 
  113 instance Outputable StgWord where
  114     ppr (StgWord i) = integer (toInteger i)
  115 
  116 --
  117 
  118 -- A Word32 is large enough to hold half a Word for either a 32bit or
  119 -- 64bit platform
  120 newtype StgHalfWord = StgHalfWord Word32
  121     deriving Eq
  122 
  123 fromStgHalfWord :: StgHalfWord -> Integer
  124 fromStgHalfWord (StgHalfWord w) = toInteger w
  125 
  126 toStgHalfWord :: Platform -> Integer -> StgHalfWord
  127 toStgHalfWord platform i
  128     = case platformWordSize platform of
  129       -- These conversions mean that things like toStgHalfWord (-1)
  130       -- do the right thing
  131       PW4 -> StgHalfWord (fromIntegral (fromInteger i :: Word16))
  132       PW8 -> StgHalfWord (fromInteger i :: Word32)
  133 
  134 instance Outputable StgHalfWord where
  135     ppr (StgHalfWord w) = integer (toInteger w)
  136 
  137 -- | Half word size in bytes
  138 halfWordSize :: Platform -> ByteOff
  139 halfWordSize platform = platformWordSizeInBytes platform `div` 2
  140 
  141 halfWordSizeInBits :: Platform -> Int
  142 halfWordSizeInBits platform = platformWordSizeInBits platform `div` 2
  143 
  144 {-
  145 ************************************************************************
  146 *                                                                      *
  147 \subsubsection[SMRep-datatype]{@SMRep@---storage manager representation}
  148 *                                                                      *
  149 ************************************************************************
  150 -}
  151 
  152 -- | A description of the layout of a closure.  Corresponds directly
  153 -- to the closure types in includes\/rts\/storage\/ClosureTypes.h.
  154 data SMRep
  155   = HeapRep              -- GC routines consult sizes in info tbl
  156         IsStatic
  157         !WordOff         --  # ptr words
  158         !WordOff         --  # non-ptr words INCLUDING SLOP (see mkHeapRep below)
  159         ClosureTypeInfo  -- type-specific info
  160 
  161   | ArrayPtrsRep
  162         !WordOff        -- # ptr words
  163         !WordOff        -- # card table words
  164 
  165   | SmallArrayPtrsRep
  166         !WordOff        -- # ptr words
  167 
  168   | ArrayWordsRep
  169         !WordOff        -- # bytes expressed in words, rounded up
  170 
  171   | StackRep            -- Stack frame (RET_SMALL or RET_BIG)
  172         Liveness
  173 
  174   | RTSRep              -- The RTS needs to declare info tables with specific
  175         Int             -- type tags, so this form lets us override the default
  176         SMRep           -- tag for an SMRep.
  177   deriving Eq
  178 
  179 -- | True \<=> This is a static closure.  Affects how we garbage-collect it.
  180 -- Static closure have an extra static link field at the end.
  181 -- Constructors do not have a static variant; see Note [static constructors]
  182 type IsStatic = Bool
  183 
  184 -- From an SMRep you can get to the closure type defined in
  185 -- rts/include/rts/storage/ClosureTypes.h. Described by the function
  186 -- rtsClosureType below.
  187 
  188 data ClosureTypeInfo
  189   = Constr        ConTagZ ConstrDescription
  190   | Fun           FunArity ArgDescr
  191   | Thunk
  192   | ThunkSelector SelectorOffset
  193   | BlackHole
  194   | IndStatic
  195   deriving Eq
  196 
  197 type ConstrDescription = ByteString -- result of dataConIdentity
  198 type FunArity          = Int
  199 type SelectorOffset    = Int
  200 
  201 -----------------------------------------------------------------------------
  202 -- Construction
  203 
  204 mkHeapRep :: Profile -> IsStatic -> WordOff -> WordOff -> ClosureTypeInfo
  205           -> SMRep
  206 mkHeapRep profile is_static ptr_wds nonptr_wds cl_type_info
  207   = HeapRep is_static
  208             ptr_wds
  209             (nonptr_wds + slop_wds)
  210             cl_type_info
  211   where
  212      slop_wds
  213       | is_static = 0
  214       | otherwise = max 0 (minClosureSize profile - (hdr_size + payload_size))
  215 
  216      hdr_size     = closureTypeHdrSize profile cl_type_info
  217      payload_size = ptr_wds + nonptr_wds
  218 
  219 mkRTSRep :: Int -> SMRep -> SMRep
  220 mkRTSRep = RTSRep
  221 
  222 mkStackRep :: [Bool] -> SMRep
  223 mkStackRep liveness = StackRep liveness
  224 
  225 blackHoleRep :: SMRep
  226 blackHoleRep = HeapRep False 0 0 BlackHole
  227 
  228 indStaticRep :: SMRep
  229 indStaticRep = HeapRep True 1 0 IndStatic
  230 
  231 arrPtrsRep :: Platform -> WordOff -> SMRep
  232 arrPtrsRep platform elems = ArrayPtrsRep elems (cardTableSizeW platform elems)
  233 
  234 smallArrPtrsRep :: WordOff -> SMRep
  235 smallArrPtrsRep elems = SmallArrayPtrsRep elems
  236 
  237 arrWordsRep :: Platform -> ByteOff -> SMRep
  238 arrWordsRep platform bytes = ArrayWordsRep (bytesToWordsRoundUp platform bytes)
  239 
  240 -----------------------------------------------------------------------------
  241 -- Predicates
  242 
  243 isStaticRep :: SMRep -> IsStatic
  244 isStaticRep (HeapRep is_static _ _ _) = is_static
  245 isStaticRep (RTSRep _ rep)            = isStaticRep rep
  246 isStaticRep _                         = False
  247 
  248 isStackRep :: SMRep -> Bool
  249 isStackRep StackRep{}     = True
  250 isStackRep (RTSRep _ rep) = isStackRep rep
  251 isStackRep _              = False
  252 
  253 isConRep :: SMRep -> Bool
  254 isConRep (HeapRep _ _ _ Constr{}) = True
  255 isConRep _                        = False
  256 
  257 isThunkRep :: SMRep -> Bool
  258 isThunkRep (HeapRep _ _ _ Thunk)           = True
  259 isThunkRep (HeapRep _ _ _ ThunkSelector{}) = True
  260 isThunkRep (HeapRep _ _ _ BlackHole)       = True
  261 isThunkRep (HeapRep _ _ _ IndStatic)       = True
  262 isThunkRep _                               = False
  263 
  264 isFunRep :: SMRep -> Bool
  265 isFunRep (HeapRep _ _ _ Fun{}) = True
  266 isFunRep _                     = False
  267 
  268 isStaticNoCafCon :: SMRep -> Bool
  269 -- This should line up exactly with CONSTR_NOCAF below
  270 -- See Note [Static NoCaf constructors]
  271 isStaticNoCafCon (HeapRep _ 0 _ Constr{}) = True
  272 isStaticNoCafCon _                        = False
  273 
  274 
  275 -----------------------------------------------------------------------------
  276 -- Size-related things
  277 
  278 fixedHdrSize :: Profile -> ByteOff
  279 fixedHdrSize profile = wordsToBytes (profilePlatform profile) (fixedHdrSizeW profile)
  280 
  281 -- | Size of a closure header (StgHeader in includes\/rts\/storage\/Closures.h)
  282 fixedHdrSizeW :: Profile -> WordOff
  283 fixedHdrSizeW profile = pc_STD_HDR_SIZE (profileConstants profile) + profHdrSize profile
  284 
  285 -- | Size of the profiling part of a closure header
  286 -- (StgProfHeader in includes\/rts\/storage\/Closures.h)
  287 profHdrSize :: Profile -> WordOff
  288 profHdrSize profile =
  289    if profileIsProfiling profile
  290       then pc_PROF_HDR_SIZE (profileConstants profile)
  291       else 0
  292 
  293 -- | The garbage collector requires that every closure is at least as
  294 --   big as this.
  295 minClosureSize :: Profile -> WordOff
  296 minClosureSize profile
  297  = fixedHdrSizeW profile
  298    + pc_MIN_PAYLOAD_SIZE (profileConstants profile)
  299 
  300 arrWordsHdrSize :: Profile -> ByteOff
  301 arrWordsHdrSize profile
  302  = fixedHdrSize profile
  303    + pc_SIZEOF_StgArrBytes_NoHdr (profileConstants profile)
  304 
  305 arrWordsHdrSizeW :: Profile -> WordOff
  306 arrWordsHdrSizeW profile
  307  = fixedHdrSizeW profile
  308    + (pc_SIZEOF_StgArrBytes_NoHdr (profileConstants profile) `quot`
  309       platformWordSizeInBytes (profilePlatform profile))
  310 
  311 arrPtrsHdrSize :: Profile -> ByteOff
  312 arrPtrsHdrSize profile
  313  = fixedHdrSize profile
  314    + pc_SIZEOF_StgMutArrPtrs_NoHdr (profileConstants profile)
  315 
  316 arrPtrsHdrSizeW :: Profile -> WordOff
  317 arrPtrsHdrSizeW profile
  318  = fixedHdrSizeW profile
  319    + (pc_SIZEOF_StgMutArrPtrs_NoHdr (profileConstants profile) `quot`
  320       platformWordSizeInBytes (profilePlatform profile))
  321 
  322 smallArrPtrsHdrSize :: Profile -> ByteOff
  323 smallArrPtrsHdrSize profile
  324  = fixedHdrSize profile
  325    + pc_SIZEOF_StgSmallMutArrPtrs_NoHdr (profileConstants profile)
  326 
  327 smallArrPtrsHdrSizeW :: Profile -> WordOff
  328 smallArrPtrsHdrSizeW profile
  329  = fixedHdrSizeW profile
  330    + (pc_SIZEOF_StgSmallMutArrPtrs_NoHdr (profileConstants profile) `quot`
  331       platformWordSizeInBytes (profilePlatform profile))
  332 
  333 -- Thunks have an extra header word on SMP, so the update doesn't
  334 -- splat the payload.
  335 thunkHdrSize :: Profile -> WordOff
  336 thunkHdrSize profile = fixedHdrSizeW profile + smp_hdr
  337         where
  338          platform = profilePlatform profile
  339          smp_hdr  = pc_SIZEOF_StgSMPThunkHeader (platformConstants platform) `quot`
  340                          platformWordSizeInBytes platform
  341 
  342 hdrSize :: Profile -> SMRep -> ByteOff
  343 hdrSize profile rep = wordsToBytes (profilePlatform profile) (hdrSizeW profile rep)
  344 
  345 hdrSizeW :: Profile -> SMRep -> WordOff
  346 hdrSizeW profile (HeapRep _ _ _ ty)    = closureTypeHdrSize profile ty
  347 hdrSizeW profile (ArrayPtrsRep _ _)    = arrPtrsHdrSizeW profile
  348 hdrSizeW profile (SmallArrayPtrsRep _) = smallArrPtrsHdrSizeW profile
  349 hdrSizeW profile (ArrayWordsRep _)     = arrWordsHdrSizeW profile
  350 hdrSizeW _ _                           = panic "GHC.Runtime.Heap.Layout.hdrSizeW"
  351 
  352 nonHdrSize :: Platform -> SMRep -> ByteOff
  353 nonHdrSize platform rep = wordsToBytes platform (nonHdrSizeW rep)
  354 
  355 nonHdrSizeW :: SMRep -> WordOff
  356 nonHdrSizeW (HeapRep _ p np _) = p + np
  357 nonHdrSizeW (ArrayPtrsRep elems ct) = elems + ct
  358 nonHdrSizeW (SmallArrayPtrsRep elems) = elems
  359 nonHdrSizeW (ArrayWordsRep words) = words
  360 nonHdrSizeW (StackRep bs)      = length bs
  361 nonHdrSizeW (RTSRep _ rep)     = nonHdrSizeW rep
  362 
  363 -- | The total size of the closure, in words.
  364 heapClosureSizeW :: Profile -> SMRep -> WordOff
  365 heapClosureSizeW profile rep = case rep of
  366    HeapRep _ p np ty       -> closureTypeHdrSize profile ty + p + np
  367    ArrayPtrsRep elems ct   -> arrPtrsHdrSizeW profile + elems + ct
  368    SmallArrayPtrsRep elems -> smallArrPtrsHdrSizeW profile + elems
  369    ArrayWordsRep words     -> arrWordsHdrSizeW profile + words
  370    _                       -> panic "GHC.Runtime.Heap.Layout.heapClosureSize"
  371 
  372 closureTypeHdrSize :: Profile -> ClosureTypeInfo -> WordOff
  373 closureTypeHdrSize profile ty = case ty of
  374                   Thunk           -> thunkHdrSize profile
  375                   ThunkSelector{} -> thunkHdrSize profile
  376                   BlackHole       -> thunkHdrSize profile
  377                   IndStatic       -> thunkHdrSize profile
  378                   _               -> fixedHdrSizeW profile
  379         -- All thunks use thunkHdrSize, even if they are non-updatable.
  380         -- this is because we don't have separate closure types for
  381         -- updatable vs. non-updatable thunks, so the GC can't tell the
  382         -- difference.  If we ever have significant numbers of non-
  383         -- updatable thunks, it might be worth fixing this.
  384 
  385 -- ---------------------------------------------------------------------------
  386 -- Arrays
  387 
  388 -- | The byte offset into the card table of the card for a given element
  389 card :: Platform -> Int -> Int
  390 card platform i = i `shiftR` pc_MUT_ARR_PTRS_CARD_BITS (platformConstants platform)
  391 
  392 -- | Convert a number of elements to a number of cards, rounding up
  393 cardRoundUp :: Platform -> Int -> Int
  394 cardRoundUp platform i =
  395   card platform (i + ((1 `shiftL` pc_MUT_ARR_PTRS_CARD_BITS (platformConstants platform)) - 1))
  396 
  397 -- | The size of a card table, in bytes
  398 cardTableSizeB :: Platform -> Int -> ByteOff
  399 cardTableSizeB platform elems = cardRoundUp platform elems
  400 
  401 -- | The size of a card table, in words
  402 cardTableSizeW :: Platform -> Int -> WordOff
  403 cardTableSizeW platform elems =
  404   bytesToWordsRoundUp platform (cardTableSizeB platform elems)
  405 
  406 -----------------------------------------------------------------------------
  407 -- deriving the RTS closure type from an SMRep
  408 
  409 #include "ClosureTypes.h"
  410 #include "FunTypes.h"
  411 -- Defines CONSTR, CONSTR_1_0 etc
  412 
  413 -- | Derives the RTS closure type from an 'SMRep'
  414 rtsClosureType :: SMRep -> Int
  415 rtsClosureType rep
  416     = case rep of
  417       RTSRep ty _ -> ty
  418 
  419       -- See Note [static constructors]
  420       HeapRep _     1 0 Constr{} -> CONSTR_1_0
  421       HeapRep _     0 1 Constr{} -> CONSTR_0_1
  422       HeapRep _     2 0 Constr{} -> CONSTR_2_0
  423       HeapRep _     1 1 Constr{} -> CONSTR_1_1
  424       HeapRep _     0 2 Constr{} -> CONSTR_0_2
  425       HeapRep _     0 _ Constr{} -> CONSTR_NOCAF
  426            -- See Note [Static NoCaf constructors]
  427       HeapRep _     _ _ Constr{} -> CONSTR
  428 
  429       HeapRep False 1 0 Fun{} -> FUN_1_0
  430       HeapRep False 0 1 Fun{} -> FUN_0_1
  431       HeapRep False 2 0 Fun{} -> FUN_2_0
  432       HeapRep False 1 1 Fun{} -> FUN_1_1
  433       HeapRep False 0 2 Fun{} -> FUN_0_2
  434       HeapRep False _ _ Fun{} -> FUN
  435 
  436       HeapRep False 1 0 Thunk -> THUNK_1_0
  437       HeapRep False 0 1 Thunk -> THUNK_0_1
  438       HeapRep False 2 0 Thunk -> THUNK_2_0
  439       HeapRep False 1 1 Thunk -> THUNK_1_1
  440       HeapRep False 0 2 Thunk -> THUNK_0_2
  441       HeapRep False _ _ Thunk -> THUNK
  442 
  443       HeapRep False _ _ ThunkSelector{} ->  THUNK_SELECTOR
  444 
  445       HeapRep True _ _ Fun{}      -> FUN_STATIC
  446       HeapRep True _ _ Thunk      -> THUNK_STATIC
  447       HeapRep False _ _ BlackHole -> BLACKHOLE
  448       HeapRep False _ _ IndStatic -> IND_STATIC
  449 
  450       StackRep _ -> STACK
  451 
  452       _ -> panic "rtsClosureType"
  453 
  454 -- We export these ones
  455 rET_SMALL, rET_BIG, aRG_GEN, aRG_GEN_BIG :: Int
  456 rET_SMALL   = RET_SMALL
  457 rET_BIG     = RET_BIG
  458 aRG_GEN     = ARG_GEN
  459 aRG_GEN_BIG = ARG_GEN_BIG
  460 
  461 {-
  462 Note [static constructors]
  463 ~~~~~~~~~~~~~~~~~~~~~~~~~~
  464 
  465 We used to have a CONSTR_STATIC closure type, and each constructor had
  466 two info tables: one with CONSTR (or CONSTR_1_0 etc.), and one with
  467 CONSTR_STATIC.
  468 
  469 This distinction was removed, because when copying a data structure
  470 into a compact region, we must copy static constructors into the
  471 compact region too.  If we didn't do this, we would need to track the
  472 references from the compact region out to the static constructors,
  473 because they might (indirectly) refer to CAFs.
  474 
  475 Since static constructors will be copied to the heap, if we wanted to
  476 use different info tables for static and dynamic constructors, we
  477 would have to switch the info pointer when copying the constructor
  478 into the compact region, which means we would need an extra field of
  479 the static info table to point to the dynamic one.
  480 
  481 However, since the distinction between static and dynamic closure
  482 types is never actually needed (other than for assertions), we can
  483 just drop the distinction and use the same info table for both.
  484 
  485 The GC *does* need to distinguish between static and dynamic closures,
  486 but it does this using the HEAP_ALLOCED() macro which checks whether
  487 the address of the closure resides within the dynamic heap.
  488 HEAP_ALLOCED() doesn't read the closure's info table.
  489 
  490 Note [Static NoCaf constructors]
  491 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  492 If we know that a top-level binding 'x' is not Caffy (ie no CAFs are
  493 reachable from 'x'), then a statically allocated constructor (Just x)
  494 is also not Caffy, and the garbage collector need not follow its
  495 argument fields.  Exploiting this would require two static info tables
  496 for Just, for the two cases where the argument was Caffy or non-Caffy.
  497 
  498 Currently we don't do this; instead we treat nullary constructors
  499 as non-Caffy, and the others as potentially Caffy.
  500 
  501 
  502 ************************************************************************
  503 *                                                                      *
  504              Pretty printing of SMRep and friends
  505 *                                                                      *
  506 ************************************************************************
  507 -}
  508 
  509 instance Outputable ClosureTypeInfo where
  510    ppr = pprTypeInfo
  511 
  512 instance Outputable SMRep where
  513    ppr (HeapRep static ps nps tyinfo)
  514      = hang (header <+> lbrace) 2 (ppr tyinfo <+> rbrace)
  515      where
  516        header = text "HeapRep"
  517                 <+> if static then text "static" else empty
  518                 <+> pp_n "ptrs" ps <+> pp_n "nonptrs" nps
  519        pp_n :: String -> Int -> SDoc
  520        pp_n _ 0 = empty
  521        pp_n s n = int n <+> text s
  522 
  523    ppr (ArrayPtrsRep size _) = text "ArrayPtrsRep" <+> ppr size
  524 
  525    ppr (SmallArrayPtrsRep size) = text "SmallArrayPtrsRep" <+> ppr size
  526 
  527    ppr (ArrayWordsRep words) = text "ArrayWordsRep" <+> ppr words
  528 
  529    ppr (StackRep bs) = text "StackRep" <+> ppr bs
  530 
  531    ppr (RTSRep ty rep) = text "tag:" <> ppr ty <+> ppr rep
  532 
  533 pprTypeInfo :: ClosureTypeInfo -> SDoc
  534 pprTypeInfo (Constr tag descr)
  535   = text "Con" <+>
  536     braces (sep [ text "tag:" <+> ppr tag
  537                 , text "descr:" <> text (show descr) ])
  538 
  539 pprTypeInfo (Fun arity args)
  540   = text "Fun" <+>
  541     braces (sep [ text "arity:"    <+> ppr arity
  542                 , text "fun_type:" <+> ppr args ])
  543 
  544 pprTypeInfo (ThunkSelector offset)
  545   = text "ThunkSel" <+> ppr offset
  546 
  547 pprTypeInfo Thunk     = text "Thunk"
  548 pprTypeInfo BlackHole = text "BlackHole"
  549 pprTypeInfo IndStatic = text "IndStatic"