1 {-# LANGUAGE MagicHash, UnboxedTuples, CPP, ForeignFunctionInterface, GHCForeignImportPrim, UnliftedFFITypes, BangPatterns, RecordWildCards, DeriveFunctor, DeriveFoldable, DeriveTraversable, PatternGuards #-}
4 Copyright : (c) 2012 Joachim Breitner
6 Maintainer : Joachim Breitner <mail@joachim-breitner.de>
8 With this module, you can investigate the heap representation of Haskell
9 values, i.e. to investigate sharing and lazy evaluation.
21 -- * Reading from the heap
52 import GHC.Exts ( Any,
53 Ptr(..), Addr#, Int(..), Word(..), Word#, Int#,
54 ByteArray#, Array#, sizeofByteArray#, sizeofArray#, indexArray#, indexWordArray#,
57 import GHC.Arr (Array(..))
60 import Foreign hiding ( unsafePerformIO, void )
61 import Numeric ( showHex )
64 import Data.Maybe ( catMaybes )
65 import Data.Monoid ( Monoid, (<>), mempty )
68 import Data.Foldable ( Foldable )
69 import qualified Data.Foldable as F
70 import Data.Traversable ( Traversable )
71 import qualified Data.Traversable as T
72 import qualified Data.IntMap as M
74 import Control.Monad.Trans.State
75 import Control.Monad.Trans.Class
76 import Control.Monad.IO.Class
77 import Control.Monad.Trans.Writer.Strict
78 import Control.Exception.Base (evaluate)
80 import GHC.Disassembler
82 #include "ghcautoconf.h"
84 -- | An arbitrarily Haskell value in a safe Box. The point is that even
85 -- unevaluated thunks can safely be moved around inside the Box, and when
86 -- required, e.g. in 'getBoxedClosureData', the function knows how far it has
87 -- to evalue the argument.
90 #if SIZEOF_VOID_P == 8
91 type HalfWord = Word32
93 type HalfWord = Word16
96 instance Show Box where
97 -- From libraries/base/GHC/Ptr.lhs
98 showsPrec _ (Box a) rs =
99 -- unsafePerformIO (print "↓" >> pClosure a) `seq`
100 pad_out (showHex addr "") ++ (if tag>0 then "/" ++ show tag else "") ++ rs
102 ptr = W# (aToWord# a)
103 tag = ptr .&. fromIntegral tAG_MASK -- ((1 `shiftL` TAG_BITS) -1)
105 -- want 0s prefixed to pad it out to a fixed length.
107 '0':'x':(replicate (2*wORD_SIZE - length ls) '0') ++ ls
109 -- | Boxes can be compared, but this is not pure, as different heap objects can,
110 -- after garbage collection, become the same object.
111 areBoxesEqual :: Box -> Box -> IO Bool
112 areBoxesEqual (Box a) (Box b) = case reallyUnsafePtrEqualityUpToTag# a b of
118 This takes an arbitrary value and puts it into a box. Note that calls like
122 will put the thunk \"head list\" into the box, /not/ the element at the head
123 of the list. For that, use careful case expressions:
125 > case list of x:_ -> asBox x
128 asBox x = Box (unsafeCoerce# x)
131 StgInfoTable parsing derived from ByteCodeItbls.lhs
132 Removed the code parameter for now
133 Replaced Type by an enumeration
134 Remove stuff dependent on GHCI_TABLES_NEXT_TO_CODE
137 {-| This is a somewhat faithful representation of an info table. See
138 <http://hackage.haskell.org/trac/ghc/browser/includes/rts/storage/InfoTables.h>
139 for more details on this data structure. Note that the 'Storable' instance
140 provided here does _not_ support writing.
142 data StgInfoTable = StgInfoTable {
150 instance Storable StgInfoTable where
157 sizeOf (undefined :: HalfWord),
165 = error "Storable StgInfoTable is read-only"
168 = flip (evalStateT) (castPtr a0)
178 tipe = toEnum (fromIntegral (tipe'::HalfWord)),
182 fieldSz :: (Storable a, Storable b) => (a -> b) -> a -> Int
183 fieldSz sel x = sizeOf (sel x)
185 load :: Storable a => PtrIO a
186 load = do addr <- advance
189 type PtrIO = StateT (Ptr Word8) IO
191 advance :: Storable a => PtrIO (Ptr a)
192 advance = StateT adv where
193 adv addr = case castPtr addr of { addrCast -> return
194 (addrCast, addr `plusPtr` sizeOfPointee addrCast) }
196 sizeOfPointee :: (Storable a) => Ptr a -> Int
197 sizeOfPointee addr = sizeOf (typeHack addr)
198 where typeHack = undefined :: Ptr a -> a
201 Data Type representing Closures
205 {-| A closure type enumeration, in order matching the actual value on the heap.
206 Needs to be synchronized with
207 <http://hackage.haskell.org/trac/ghc/browser/includes/rts/storage/ClosureTypes.h>
218 | CONSTR_NOCAF_STATIC
257 | MUT_ARR_PTRS_FROZEN0
258 | MUT_ARR_PTRS_FROZEN
271 deriving (Show, Eq, Enum, Ord)
273 {-| This is the main data type of this module, representing a Haskell value on
274 the heap. This reflects
275 <http://hackage.haskell.org/trac/ghc/browser/includes/rts/storage/Closures.h>
277 The data type is parametrized by the type to store references in, which
278 is usually a 'Box' with appropriate type synonym 'Closure'.
306 -- In GHCi, if Linker.h would allow a reverse looup, we could for exported
307 -- functions fun actually find the name here.
308 -- At least the other direction works via "lookupSymbol
309 -- base_GHCziBase_zpzp_closure" and yields the same address (up to tags)
348 -- Card table ignored
365 BlockingQueueClosure {
380 deriving (Show, Functor, Foldable, Traversable)
383 type Closure = GenClosure Box
385 -- | For generic code, this function returns all referenced closures.
386 allPtrs :: GenClosure b -> [b]
387 allPtrs (ConsClosure {..}) = ptrArgs
388 allPtrs (ThunkClosure {..}) = ptrArgs
389 allPtrs (SelectorClosure {..}) = [selectee]
390 allPtrs (IndClosure {..}) = [indirectee]
391 allPtrs (BlackholeClosure {..}) = [indirectee]
392 allPtrs (APClosure {..}) = fun:payload
393 allPtrs (PAPClosure {..}) = fun:payload
394 allPtrs (APStackClosure {..}) = fun:payload
395 allPtrs (BCOClosure {..}) = [instrs,literals,bcoptrs]
396 allPtrs (ArrWordsClosure {..}) = []
397 allPtrs (MutArrClosure {..}) = mccPayload
398 allPtrs (MutVarClosure {..}) = [var]
399 allPtrs (MVarClosure {..}) = [queueHead,queueTail,value]
400 allPtrs (FunClosure {..}) = ptrArgs
401 allPtrs (BlockingQueueClosure {..}) = [link, blackHole, owner, queue]
402 allPtrs (OtherClosure {..}) = hvalues
403 allPtrs (UnsupportedClosure {..}) = []
406 #ifdef PRIM_SUPPORTS_ANY
407 foreign import prim "aToWordzh" aToWord# :: Any -> Word#
408 foreign import prim "slurpClosurezh" slurpClosure# :: Any -> (# Addr#, ByteArray#, Array# b #)
409 foreign import prim "reallyUnsafePtrEqualityUpToTag" reallyUnsafePtrEqualityUpToTag# :: Any -> Any -> Int#
411 -- Workd-around code until http://hackage.haskell.org/trac/ghc/ticket/5931 was
414 -- foreign import prim "aToWordzh" aToWord'# :: Addr# -> Word#
415 foreign import prim "slurpClosurezh" slurpClosure'# :: Word# -> (# Addr#, ByteArray#, Array# b #)
417 foreign import prim "reallyUnsafePtrEqualityUpToTag" reallyUnsafePtrEqualityUpToTag'# :: Word# -> Word# -> Int#
419 -- This is a datatype that has the same layout as Ptr, so that by
420 -- unsafeCoerce'ing, we obtain the Addr of the wrapped value
423 aToWord# :: Any -> Word#
424 aToWord# a = case Ptr' a of mb@(Ptr' _) -> case unsafeCoerce# mb :: Word of W# addr -> addr
426 slurpClosure# :: Any -> (# Addr#, ByteArray#, Array# b #)
427 slurpClosure# a = slurpClosure'# (aToWord# a)
429 reallyUnsafePtrEqualityUpToTag# :: Any -> Any -> Int#
430 reallyUnsafePtrEqualityUpToTag# a b = reallyUnsafePtrEqualityUpToTag'# (aToWord# a) (aToWord# b)
434 -- getClosure x >>= print
436 -- | This returns the raw representation of the given argument. The second
437 -- component of the triple are the words on the heap, and the third component
438 -- are those words that are actually pointers. Once back in Haskell word, the
439 -- 'Word' may be outdated after a garbage collector run, but the corresponding
440 -- 'Box' will still point to the correct value.
441 getClosureRaw :: a -> IO (Ptr StgInfoTable, [Word], [Box])
443 case slurpClosure# (unsafeCoerce# x) of
444 (# iptr, dat, ptrs #) -> do
445 let nelems = (I# (sizeofByteArray# dat)) `div` wORD_SIZE
446 rawWords = [W# (indexWordArray# dat i) | I# i <- [0.. fromIntegral nelems -1] ]
447 pelems = I# (sizeofArray# ptrs)
448 ptrList = amap' Box $ Array 0 (pelems - 1) pelems ptrs
449 -- This is just for good measure, and seems to be not important.
450 mapM_ evaluate ptrList
451 -- This seems to be required to avoid crashes as well
452 void $ evaluate nelems
453 -- The following deep evaluation is crucial to avoid crashes (but why)?
454 mapM_ evaluate rawWords
455 return (Ptr iptr, rawWords, ptrList)
457 -- From compiler/ghci/RtClosureInspect.hs
458 amap' :: (t -> b) -> Array Int t -> [b]
459 amap' f (Array i0 i _ arr#) = map g [0 .. i - i0]
460 where g (I# i#) = case indexArray# arr# i# of
463 -- derived from vacuum-1.0.0.2/src/GHC/Vacuum/Internal.hs, which got it from
464 -- compiler/ghci/DebuggerUtils.hs
465 dataConInfoPtrToNames :: Ptr StgInfoTable -> IO (String, String, String)
466 dataConInfoPtrToNames ptr = do
467 conDescAddress <- getConDescAddress ptr
468 wl <- peekArray0 0 conDescAddress
469 let (pkg, modl, name) = parse wl
470 return (b2s pkg, b2s modl, b2s name)
472 b2s :: [Word8] -> String
473 b2s = fmap (chr . fromIntegral)
475 getConDescAddress :: Ptr StgInfoTable -> IO (Ptr Word8)
476 getConDescAddress ptr'
478 offsetToString <- peek (ptr' `plusPtr` (negate wORD_SIZE))
479 return $ (ptr' `plusPtr` stdInfoTableSizeB)
480 `plusPtr` (fromIntegral (offsetToString :: Word))
481 -- This is code for !ghciTablesNextToCode:
483 | otherwise = peek . intPtrToPtr
489 -- hmmmmmm. Is there any way to tell this?
490 opt_SccProfilingOn = False
492 stdInfoTableSizeW :: Int
493 -- The size of a standard info table varies with profiling/ticky etc,
494 -- so we can't get it from Constants
495 -- It must vary in sync with mkStdInfoTable
497 = size_fixed + size_prof
499 size_fixed = 2 -- layout, type
500 size_prof | opt_SccProfilingOn = 2
503 stdInfoTableSizeB :: Int
504 stdInfoTableSizeB = stdInfoTableSizeW * wORD_SIZE
506 -- From vacuum-1.0.0.2/src/GHC/Vacuum/Internal.hs
507 parse :: [Word8] -> ([Word8], [Word8], [Word8])
508 parse input = if not . all (>0) . fmap length $ [pkg,modl,occ]
509 --then (error . concat)
510 -- ["getConDescAddress:parse:"
511 -- ,"(not . all (>0) . fmap le"
512 -- ,"ngth $ [pkg,modl,occ]"]
513 then ([], [], input) -- Not in the pkg.modl.occ format, for example END_TSO_QUEUE
514 else (pkg, modl, occ)
515 -- = ASSERT (all (>0) (map length [pkg, modl, occ])) (pkg, modl, occ) -- XXXXXXXXXXXXXXXX
517 (pkg, rest1) = break (== fromIntegral (ord ':')) input
519 = (concat $ intersperse [dot] $ reverse modWords, occWord)
521 (modWords, occWord) = if (length rest1 < 1) -- XXXXXXXXx YUKX
522 --then error "getConDescAddress:parse:length rest1 < 1"
523 then parseModOcc [] []
524 else parseModOcc [] (tail rest1)
525 -- ASSERT (length rest1 > 0) (parseModOcc [] (tail rest1))
526 dot = fromIntegral (ord '.')
527 parseModOcc :: [[Word8]] -> [Word8] -> ([[Word8]], [Word8])
529 = case break (== dot) str of
530 (top, []) -> (acc, top)
531 (top, _:bot) -> parseModOcc (top : acc) bot
534 -- | This function returns parsed heap representation of the argument _at this
535 -- moment_, even if it is unevaluated or an indirection or other exotic stuff.
536 -- Beware when passing something to this function, the same caveats as for
538 getClosureData :: a -> IO Closure
539 getClosureData x = do
540 (iptr, wds, ptrs) <- getClosureRaw x
543 t | t >= CONSTR && t <= CONSTR_NOCAF_STATIC -> do
544 (pkg, modl, name) <- dataConInfoPtrToNames iptr
545 if modl == "ByteCodeInstr" && name == "BreakInfo"
546 then return $ UnsupportedClosure itbl
547 else return $ ConsClosure itbl ptrs (drop (length ptrs + 1) wds) pkg modl name
549 t | t >= THUNK && t <= THUNK_STATIC -> do
550 return $ ThunkClosure itbl ptrs (drop (length ptrs + 2) wds)
552 t | t >= FUN && t <= FUN_STATIC -> do
553 return $ FunClosure itbl ptrs (drop (length ptrs + 1) wds)
556 return $ APClosure itbl
557 (fromIntegral $ wds !! 2)
558 (fromIntegral $ shiftR (wds !! 2) (wORD_SIZE_IN_BITS `div` 2))
559 (head ptrs) (tail ptrs)
562 return $ PAPClosure itbl
563 (fromIntegral $ wds !! 2)
564 (fromIntegral $ shiftR (wds !! 2) (wORD_SIZE_IN_BITS `div` 2))
565 (head ptrs) (tail ptrs)
568 return $ APStackClosure itbl (head ptrs) (tail ptrs)
571 return $ SelectorClosure itbl (head ptrs)
574 return $ IndClosure itbl (head ptrs)
576 return $ IndClosure itbl (head ptrs)
578 return $ BlackholeClosure itbl (head ptrs)
581 return $ BCOClosure itbl (ptrs !! 0) (ptrs !! 1) (ptrs !! 2)
582 (fromIntegral $ wds !! 4)
583 (fromIntegral $ shiftR (wds !! 4) (wORD_SIZE_IN_BITS `div` 2))
587 return $ ArrWordsClosure itbl (wds !! 1) (drop 2 wds)
589 t | t == MUT_ARR_PTRS_FROZEN || t == MUT_ARR_PTRS_FROZEN0 ->
590 return $ MutArrClosure itbl (wds !! 1) (wds !! 2) ptrs
592 t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY ->
593 return $ MutVarClosure itbl (head ptrs)
595 t | t == MVAR_CLEAN || t == MVAR_DIRTY ->
596 return $ MVarClosure itbl (ptrs !! 0) (ptrs !! 1) (ptrs !! 2)
599 return $ OtherClosure itbl ptrs wds
600 -- return $ BlockingQueueClosure itbl
601 -- (ptrs !! 0) (ptrs !! 1) (ptrs !! 2) (ptrs !! 3)
603 -- return $ OtherClosure itbl ptrs wds
606 return $ UnsupportedClosure itbl
608 -- | Like 'getClosureData', but taking a 'Box', so it is easier to work with.
609 getBoxedClosureData :: Box -> IO Closure
610 getBoxedClosureData (Box a) = getClosureData a
613 isChar :: GenClosure b -> Maybe Char
614 isChar (ConsClosure { name = "C#", dataArgs = [ch], ptrArgs = []}) = Just (chr (fromIntegral ch))
617 isCons :: GenClosure b -> Maybe (b, b)
618 isCons (ConsClosure { name = ":", dataArgs = [], ptrArgs = [h,t]}) = Just (h,t)
621 isTup :: GenClosure b -> Maybe [b]
622 isTup (ConsClosure { dataArgs = [], ..}) =
623 if length name >= 3 &&
624 head name == '(' && last name == ')' &&
625 all (==',') (tail (init name))
626 then Just ptrArgs else Nothing
630 isNil :: GenClosure b -> Bool
631 isNil (ConsClosure { name = "[]", dataArgs = [], ptrArgs = []}) = True
634 -- | A pretty-printer that tries to generate valid Haskell for evalutated data.
635 -- It assumes that for the included boxes, you already replaced them by Strings
636 -- using 'Data.Foldable.map' or, if you need to do IO, 'Data.Foldable.mapM'.
638 -- The parameter gives the precedendence, to avoid avoidable parenthesises.
639 ppClosure :: (Int -> b -> String) -> Int -> GenClosure b -> String
640 ppClosure showBox prec c = case c of
641 _ | Just ch <- isChar c -> app $
643 _ | Just (h,t) <- isCons c -> addBraces (5 <= prec) $
644 showBox 5 h ++ " : " ++ showBox 4 t
645 _ | Just vs <- isTup c ->
646 "(" ++ intercalate "," (map (showBox 0) vs) ++ ")"
647 ConsClosure {..} -> app $
648 name : map (showBox 10) ptrArgs ++ map show dataArgs
649 ThunkClosure {..} -> app $
650 "_thunk" : map (showBox 10) ptrArgs ++ map show dataArgs
651 SelectorClosure {..} -> app
652 ["_sel", showBox 10 selectee]
653 IndClosure {..} -> app
654 ["_ind", showBox 10 indirectee]
655 BlackholeClosure {..} -> app
656 ["_bh", showBox 10 indirectee]
657 APClosure {..} -> app $ map (showBox 10) $
659 PAPClosure {..} -> app $ map (showBox 10) $
661 APStackClosure {..} -> app $ map (showBox 10) $
663 BCOClosure {..} -> app
665 ArrWordsClosure {..} -> app
666 ["toArray", "("++show (length arrWords) ++ " words)", intercalate "," (shorten (map show arrWords)) ]
667 MutArrClosure {..} -> app
668 ["toMutArray", "("++show (length mccPayload) ++ " ptrs)", intercalate "," (shorten (map (showBox 10) mccPayload))]
669 MutVarClosure {..} -> app $
670 ["_mutVar", (showBox 10) var]
671 MVarClosure {..} -> app $
672 ["MVar", (showBox 10) value]
674 "_fun" ++ braceize (map (showBox 0) ptrArgs ++ map show dataArgs)
675 BlockingQueueClosure {..} ->
679 UnsupportedClosure {..} ->
683 app xs = addBraces (10 <= prec) (intercalate " " xs)
685 shorten xs = if length xs > 20 then take 20 xs ++ ["(and more)"] else xs
689 For more global views of the heap, you can use heap maps. These come in
690 variations, either a trees or as graphs, depending on
691 whether you want to detect cycles and sharing or not.
693 The entries of a 'HeapGraph' can be annotated with arbitrary values. Most
694 operations expect this to be in the 'Monoid' class: They use 'mempty' to
695 annotate closures added because the passed values reference them, and they
696 use 'mappend' to combine the annotations when two values conincide, e.g.
697 during 'updateHeapGraph'.
700 -- | Heap maps as tree, i.e. no sharing, no cycles.
701 data HeapTree = HeapTree Box (GenClosure HeapTree) | EndOfHeapTree
703 heapTreeClosure :: HeapTree -> Maybe (GenClosure HeapTree)
704 heapTreeClosure (HeapTree _ c) = Just c
705 heapTreeClosure EndOfHeapTree = Nothing
707 -- | Constructing an 'HeapTree' from a boxed value. It takes a depth parameter
708 -- that prevents it from running ad infinitum for cyclic or infinite
710 buildHeapTree :: Int -> Box -> IO HeapTree
711 buildHeapTree 0 _ = do
712 return $ EndOfHeapTree
713 buildHeapTree n b = do
714 c <- getBoxedClosureData b
715 c' <- T.mapM (buildHeapTree (n-1)) c
716 return $ HeapTree b c'
718 -- | Pretty-Printing a heap Tree
720 -- Example output for @[Just 4, Nothing, *something*]@, where *something* is an
721 -- unevaluated expression depending on the command line argument.
723 -- >[Just (I# 4),Nothing,Just (_thunk ["arg1","arg2"])]
724 ppHeapTree :: HeapTree -> String
727 go _ EndOfHeapTree = "..."
728 go prec t@(HeapTree _ c')
729 | Just s <- isHeapTreeString t = show s
730 | Just l <- isHeapTreeList t = "[" ++ intercalate "," (map ppHeapTree l) ++ "]"
731 | Just bc <- disassembleBCO heapTreeClosure c'
732 = app ("_bco" : map (go 10) (concatMap F.toList bc))
733 | otherwise = ppClosure go prec c'
736 app xs = addBraces (10 <= prec) (intercalate " " xs)
738 isHeapTreeList :: HeapTree -> Maybe ([HeapTree])
739 isHeapTreeList tree = do
740 c <- heapTreeClosure tree
745 t' <- isHeapTreeList t
748 isHeapTreeString :: HeapTree -> Maybe String
749 isHeapTreeString t = do
750 list <- isHeapTreeList t
751 -- We do not want to print empty lists as "" as we do not know that they
752 -- are really strings.
755 else mapM (isChar <=< heapTreeClosure) list
757 -- | For heap graphs, i.e. data structures that also represent sharing and
758 -- cyclic structures, these are the entries. If the referenced value is
759 -- @Nothing@, then we do not have that value in the map, most likely due to
760 -- exceeding the recursion bound passed to 'buildHeapGraph'.
762 -- Besides a pointer to the stored value and the closure representation we
763 -- also keep track of whether the value was still alive at the last update of the
764 -- heap graph. In addition we have a slot for arbitrary data, for the user's convenience.
765 data HeapGraphEntry a = HeapGraphEntry {
767 hgeClosure :: GenClosure (Maybe HeapGraphIndex),
770 deriving (Show, Functor)
771 type HeapGraphIndex = Int
773 -- | The whole graph. The suggested interface is to only use 'lookupHeapGraph',
774 -- as the internal representation may change. Nevertheless, we export it here:
775 -- Sometimes the user knows better what he needs than we do.
776 newtype HeapGraph a = HeapGraph (M.IntMap (HeapGraphEntry a))
779 lookupHeapGraph :: HeapGraphIndex -> (HeapGraph a) -> Maybe (HeapGraphEntry a)
780 lookupHeapGraph i (HeapGraph m) = M.lookup i m
782 heapGraphRoot :: HeapGraphIndex
785 -- | Creates a 'HeapGraph' for the value in the box, but not recursing further
786 -- than the given limit. The initial value has index 'heapGraphRoot'.
789 => Int -- ^ Search limit
790 -> a -- ^ Data value for the root
791 -> Box -- ^ The value to start with
793 buildHeapGraph limit rootD initialBox =
794 fst <$> multiBuildHeapGraph limit [(rootD, initialBox)]
796 -- | Creates a 'HeapGraph' for the values in multiple boxes, but not recursing
797 -- further than the given limit.
799 -- Returns the 'HeapGraph' and the indices of initial values. The arbitrary
800 -- type @a@ can be used to make the connection between the input and the
801 -- resulting list of indices, and to store additional data.
804 => Int -- ^ Search limit
805 -> [(a, Box)] -- ^ Starting values with associated data entry
806 -> IO (HeapGraph a, [(a, HeapGraphIndex)])
807 multiBuildHeapGraph limit = generalBuildHeapGraph limit (HeapGraph M.empty)
809 -- | Adds an entry to an existing 'HeapGraph'.
811 -- Returns the updated 'HeapGraph' and the index of the added value.
814 => Int -- ^ Search limit
815 -> a -- ^ Data to be stored with the added value
816 -> Box -- ^ Value to add to the graph
817 -> HeapGraph a -- ^ Graph to extend
818 -> IO (HeapGraphIndex, HeapGraph a)
819 addHeapGraph limit d box hg = do
820 (hg', [(_,i)]) <- generalBuildHeapGraph limit hg [(d,box)]
823 -- | Adds the given annotation to the entry at the given index, using the
824 -- 'mappend' operation of its 'Monoid' instance.
825 annotateHeapGraph :: Monoid a => a -> HeapGraphIndex -> HeapGraph a -> HeapGraph a
826 annotateHeapGraph d i (HeapGraph hg) = HeapGraph $ M.update go i hg
828 go hge = Just $ hge { hgeData = hgeData hge <> d }
830 generalBuildHeapGraph
835 -> IO (HeapGraph a, [(a, HeapGraphIndex)])
836 generalBuildHeapGraph limit _ _ | limit <= 0 = error "buildHeapGraph: limit has to be positive"
837 generalBuildHeapGraph limit (HeapGraph hg) addBoxes = do
838 -- First collect all boxes from the existing heap graph
839 let boxList = [ (hgeBox hge, i) | (i, hge) <- M.toList hg ]
840 indices | M.null hg = [0..]
841 | otherwise = [1 + fst (M.findMax hg)..]
843 initialState = (boxList, indices, [])
844 -- It is ok to use the Monoid (IntMap a) instance here, because
845 -- we will, besides the first time, use 'tell' only to add singletons not
847 (is, hg') <- runWriterT (evalStateT run initialState)
848 -- Now add the annotations of the root values
849 let hg'' = foldl' (flip (uncurry annotateHeapGraph)) (HeapGraph hg') is
853 lift $ tell hg -- Start with the initial map
854 forM addBoxes $ \(d, b) -> do
855 -- Cannot fail, as limit is not zero here
856 Just i <- add limit b
859 add 0 _ = return Nothing
861 -- If the box is in the map, return the index
862 (existing,_,_) <- get
863 mbI <- liftIO $ findM (areBoxesEqual b . fst) existing
865 Just (_,i) -> return $ Just i
867 -- Otherwise, allocate a new index
870 modify (\(x,y,z) -> ((b,i):x, y, z))
871 -- Look up the closure
872 c <- liftIO $ getBoxedClosureData b
873 -- Find indicies for all boxes contained in the map
874 c' <- T.mapM (add (n-1)) c
875 -- Add add the resulting closure to the map
876 lift $ tell (M.singleton i (HeapGraphEntry b c' True mempty))
879 i <- gets (head . (\(_,b,_) -> b))
880 modify (\(a,b,c) -> (a, tail b, c))
883 -- | This function updates a heap graph to reflect the current state of
884 -- closures on the heap, conforming to the following specification.
886 -- * Every entry whose value has been garbage collected by now is marked as
887 -- dead by setting 'hgeLive' to @False@
888 -- * Every entry whose value is still live gets the 'hgeClosure' field updated
889 -- and newly referenced closures are, up to the given depth, added to the graph.
890 -- * A map mapping previous indicies to the corresponding new indicies is returned as well.
891 -- * The closure at 'heapGraphRoot' stays at 'heapGraphRoot'
892 updateHeapGraph :: Monoid a => Int -> HeapGraph a -> IO (HeapGraph a, HeapGraphIndex -> HeapGraphIndex)
893 updateHeapGraph limit (HeapGraph startHG) = do
894 (hg', indexMap) <- runWriterT $ foldM go (HeapGraph M.empty) (M.toList startHG)
895 return (hg', (M.!) indexMap)
898 (j, hg') <- liftIO $ addHeapGraph limit (hgeData hge) (hgeBox hge) hg
899 tell (M.singleton i j)
902 -- | Pretty-prints a HeapGraph. The resulting string contains newlines. Example
903 -- for @let s = \"Ki\" in (s, s, cycle \"Ho\")@:
906 -- > x6 = C# 'H' : C# 'o' : x6
908 ppHeapGraph :: HeapGraph a -> String
909 ppHeapGraph (HeapGraph m) = letWrapper ++ ppRef 0 (Just heapGraphRoot)
911 -- All variables occuring more than once
912 bindings = boundMultipleTimes (HeapGraph m) [heapGraphRoot]
917 else "let " ++ intercalate "\n " (map ppBinding bindings) ++ "\nin "
919 bindingLetter i = case hgeClosure (iToE i) of
920 ThunkClosure {..} -> 't'
921 SelectorClosure {..} -> 't'
922 APClosure {..} -> 't'
923 PAPClosure {..} -> 'f'
924 BCOClosure {..} -> 't'
925 FunClosure {..} -> 'f'
928 ppBindingMap = M.fromList $
930 map (zipWith (\j (i,c) -> (i, [c] ++ show j)) [(1::Int)..]) $
931 groupBy ((==) `on` snd) $
932 sortBy (compare `on` snd)
933 [ (i, bindingLetter i) | i <- bindings ]
935 ppVar i = ppBindingMap M.! i
936 ppBinding i = ppVar i ++ " = " ++ ppEntry 0 (iToE i)
939 | Just s <- isString hge = show s
940 | Just l <- isList hge = "[" ++ intercalate "," (map (ppRef 0) l) ++ "]"
941 | Just bc <- disassembleBCO (fmap (hgeClosure . iToE)) (hgeClosure hge)
942 = app ("_bco" : map (ppRef 10) (concatMap F.toList bc))
943 | otherwise = ppClosure ppRef prec (hgeClosure hge)
946 app xs = addBraces (10 <= prec) (intercalate " " xs)
948 ppRef _ Nothing = "..."
949 ppRef prec (Just i) | i `elem` bindings = ppVar i
950 | otherwise = ppEntry prec (iToE i)
953 iToUnboundE i = if i `elem` bindings then Nothing else M.lookup i m
955 isList :: HeapGraphEntry a -> Maybe ([Maybe HeapGraphIndex])
957 if isNil (hgeClosure hge)
960 (h,t) <- isCons (hgeClosure hge)
966 isString :: HeapGraphEntry a -> Maybe String
969 -- We do not want to print empty lists as "" as we do not know that they
970 -- are really strings.
973 else mapM (isChar . hgeClosure <=< iToUnboundE <=< id) list
976 -- | In the given HeapMap, list all indices that are used more than once. The
977 -- second parameter adds external references, commonly @[heapGraphRoot]@.
978 boundMultipleTimes :: HeapGraph a -> [HeapGraphIndex] -> [HeapGraphIndex]
979 boundMultipleTimes (HeapGraph m) roots = map head $ filter (not.null) $ map tail $ group $ sort $
980 roots ++ concatMap (catMaybes . allPtrs . hgeClosure) (M.elems m)
982 -- | This function integrates the disassembler in "GHC.Disassembler". The first
983 -- argument should a function that dereferences the pointer in the closure to a
986 -- If any of these return 'Nothing', then 'disassembleBCO' returns Nothing
987 disassembleBCO :: (a -> Maybe (GenClosure b)) -> GenClosure a -> Maybe [BCI b]
988 disassembleBCO deref (BCOClosure {..}) = do
990 litsC <- deref literals
991 ptrsC <- deref bcoptrs
992 return $ disassemble (mccPayload ptrsC) (arrWords litsC) (toBytes (bytes opsC) (arrWords opsC))
993 disassembleBCO _ _ = Nothing
997 findM :: (a -> IO Bool) -> [a] -> IO (Maybe a)
998 findM _p [] = return Nothing
1001 if b then return (Just x) else findM p xs
1003 addBraces :: Bool -> String -> String
1004 addBraces True t = "(" ++ t ++ ")"
1005 addBraces False t = t
1007 braceize :: [String] -> String
1009 braceize xs = "{" ++ intercalate "," xs ++ "}"
1011 -- This used to be available via GHC.Constants
1012 #include "MachDeps.h"
1013 wORD_SIZE, tAG_MASK, wORD_SIZE_IN_BITS :: Int
1014 wORD_SIZE = SIZEOF_HSWORD
1015 tAG_MASK = (1 `shift` TAG_BITS) - 1
1016 wORD_SIZE_IN_BITS = WORD_SIZE_IN_BITS