{-# LANGUAGE MagicHash, UnboxedTuples, CPP, ForeignFunctionInterface, GHCForeignImportPrim, UnliftedFFITypes, BangPatterns, RecordWildCards, DeriveFunctor, DeriveFoldable, DeriveTraversable, PatternGuards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module GHC.HeapView (
GenClosure(..),
Closure,
allClosures,
ClosureType(..),
StgInfoTable(..),
HalfWord,
getClosureData,
getBoxedClosureData,
getClosureRaw,
ppClosure,
HeapTree(..),
buildHeapTree,
ppHeapTree,
HeapGraphEntry(..),
HeapGraphIndex,
HeapGraph(..),
lookupHeapGraph,
heapGraphRoot,
buildHeapGraph,
multiBuildHeapGraph,
addHeapGraph,
annotateHeapGraph,
updateHeapGraph,
ppHeapGraph,
Box(..),
asBox,
areBoxesEqual,
disassembleBCO,
)
where
import GHC.Exts ( Any,
Ptr(..), Addr#, Int(..), Word(..),
ByteArray#, Array#, sizeofByteArray#, sizeofArray#, indexArray#, indexWordArray#,
unsafeCoerce# )
import GHC.Exts.Heap
import GHC.Exts.Heap.Constants
import GHC.Arr (Array(..))
import Foreign hiding ( void )
import Data.Char
import Data.List
import Data.Maybe ( catMaybes )
import Data.Monoid ( Monoid, (<>), mempty )
import Data.Functor
import Data.Function
import Data.Foldable ( Foldable )
import qualified Data.Foldable as F
import Data.Traversable ( Traversable )
import qualified Data.Traversable as T
import qualified Data.IntMap as M
import Control.Monad
import Control.Monad.Trans.State
import Control.Monad.Trans.Class
import Control.Monad.IO.Class
import Control.Monad.Trans.Writer.Strict
import Control.Exception.Base (evaluate)
import GHC.Disassembler
#include "ghcautoconf.h"
deriving instance Functor GenClosure
deriving instance Foldable GenClosure
deriving instance Traversable GenClosure
instance Storable StgInfoTable where
sizeOf itbl
= sum
[
fieldSz ptrs itbl,
fieldSz nptrs itbl,
sizeOf (undefined :: HalfWord),
fieldSz srtlen itbl
]
alignment _
= wORD_SIZE
poke _a0 _itbl
= error "Storable StgInfoTable is read-only"
peek a0
= flip (evalStateT) (castPtr a0)
$ do
ptrs' <- load
nptrs' <- load
tipe' <- load
srtlen' <- load
return
StgInfoTable {
entry = Nothing,
ptrs = ptrs',
nptrs = nptrs',
tipe = toEnum (fromIntegral (tipe'::HalfWord)),
srtlen = srtlen',
code = Nothing
}
fieldSz :: Storable b => (a -> b) -> a -> Int
fieldSz sel x = sizeOf (sel x)
load :: Storable a => PtrIO a
load = do addr <- advance
lift (peek addr)
type PtrIO = StateT (Ptr Word8) IO
advance :: Storable a => PtrIO (Ptr a)
advance = StateT adv where
adv addr = case castPtr addr of { addrCast -> return
(addrCast, addr `plusPtr` sizeOfPointee addrCast) }
sizeOfPointee :: (Storable a) => Ptr a -> Int
sizeOfPointee addr = sizeOf (typeHack addr)
where typeHack = undefined :: Ptr a -> a
foreign import prim "stg_unpackClosurezh" unpackClosurezh# :: Any -> (# Addr#, ByteArray#, Array# b #)
getClosureRaw :: a -> IO (Ptr StgInfoTable, [Word], [Box])
getClosureRaw x =
case unpackClosurezh# (unsafeCoerce# x) of
(# iptr, dat, ptrs #) -> do
let nelems = (I# (sizeofByteArray# dat)) `div` wORD_SIZE
rawWords = [W# (indexWordArray# dat i) | I# i <- [0.. fromIntegral nelems -1] ]
pelems = I# (sizeofArray# ptrs)
ptrList = amap' Box $ Array 0 (pelems - 1) pelems ptrs
mapM_ evaluate ptrList
void $ evaluate nelems
mapM_ evaluate rawWords
return (Ptr iptr, rawWords, ptrList)
amap' :: (t -> b) -> Array Int t -> [b]
amap' f (Array i0 i _ arr#) = map g [0 .. i - i0]
where g (I# i#) = case indexArray# arr# i# of
(# e #) -> f e
isChar :: GenClosure b -> Maybe Char
isChar (ConstrClosure { name = "C#", dataArgs = [ch], ptrArgs = []}) = Just (chr (fromIntegral ch))
isChar _ = Nothing
isCons :: GenClosure b -> Maybe (b, b)
isCons (ConstrClosure { name = ":", dataArgs = [], ptrArgs = [h,t]}) = Just (h,t)
isCons _ = Nothing
isTup :: GenClosure b -> Maybe [b]
isTup (ConstrClosure { dataArgs = [], ..}) =
if length name >= 3 &&
head name == '(' && last name == ')' &&
all (==',') (tail (init name))
then Just ptrArgs else Nothing
isTup _ = Nothing
isNil :: GenClosure b -> Bool
isNil (ConstrClosure { name = "[]", dataArgs = [], ptrArgs = []}) = True
isNil _ = False
ppClosure :: (Int -> b -> String) -> Int -> GenClosure b -> String
ppClosure showBox prec c = case c of
_ | Just ch <- isChar c -> app $
["C#", show ch]
_ | Just (h,t) <- isCons c -> addBraces (5 <= prec) $
showBox 5 h ++ " : " ++ showBox 4 t
_ | Just vs <- isTup c ->
"(" ++ intercalate "," (map (showBox 0) vs) ++ ")"
ConstrClosure {..} -> app $
name : map (showBox 10) ptrArgs ++ map show dataArgs
ThunkClosure {..} -> app $
"_thunk" : map (showBox 10) ptrArgs ++ map show dataArgs
SelectorClosure {..} -> app
["_sel", showBox 10 selectee]
IndClosure {..} -> app
["_ind", showBox 10 indirectee]
BlackholeClosure {..} -> app
["_bh", showBox 10 indirectee]
APClosure {..} -> app $ map (showBox 10) $
fun : payload
PAPClosure {..} -> app $ map (showBox 10) $
fun : payload
APStackClosure {..} -> app $ map (showBox 10) $
fun : payload
BCOClosure {..} -> app
["_bco", showBox 10 bcoptrs]
ArrWordsClosure {..} -> app
["toArray", "("++show (length arrWords) ++ " words)", intercalate "," (shorten (map show arrWords)) ]
MutArrClosure {..} -> app
["[", intercalate ", " (shorten (map (showBox 10) mccPayload)),"]"]
MutVarClosure {..} -> app $
["_mutVar", (showBox 10) var]
MVarClosure {..} -> app $
["MVar", (showBox 10) value]
FunClosure {..} ->
"_fun" ++ braceize (map (showBox 0) ptrArgs ++ map show dataArgs)
BlockingQueueClosure {..} ->
"_blockingQueue"
IntClosure {..} -> app
["Int", show intVal]
WordClosure {..} -> app
["Word", show wordVal]
Int64Closure {..} -> app
["Int64", show int64Val]
Word64Closure {..} -> app
["Word64", show word64Val]
AddrClosure {..} -> app
["Addr", show addrVal]
FloatClosure {..} -> app
["Float", show floatVal]
DoubleClosure {..} -> app
["Double", show doubleVal]
OtherClosure {..} ->
"_other"
UnsupportedClosure {..} ->
"_unsupported"
where
app [a] = a ++ "()"
app xs = addBraces (10 <= prec) (intercalate " " xs)
shorten xs = if length xs > 20 then take 20 xs ++ ["(and more)"] else xs
data HeapTree = HeapTree Box (GenClosure HeapTree) | EndOfHeapTree
heapTreeClosure :: HeapTree -> Maybe (GenClosure HeapTree)
heapTreeClosure (HeapTree _ c) = Just c
heapTreeClosure EndOfHeapTree = Nothing
buildHeapTree :: Int -> Box -> IO HeapTree
buildHeapTree 0 _ = do
return $ EndOfHeapTree
buildHeapTree n b = do
c <- getBoxedClosureData b
c' <- T.mapM (buildHeapTree (n-1)) c
return $ HeapTree b c'
ppHeapTree :: HeapTree -> String
ppHeapTree = go 0
where
go _ EndOfHeapTree = "..."
go prec t@(HeapTree _ c')
| Just s <- isHeapTreeString t = show s
| Just l <- isHeapTreeList t = "[" ++ intercalate "," (map ppHeapTree l) ++ "]"
| Just bc <- disassembleBCO heapTreeClosure c'
= app ("_bco" : map (go 10) (concatMap F.toList bc))
| otherwise = ppClosure go prec c'
where
app [a] = a ++ "()"
app xs = addBraces (10 <= prec) (intercalate " " xs)
isHeapTreeList :: HeapTree -> Maybe ([HeapTree])
isHeapTreeList tree = do
c <- heapTreeClosure tree
if isNil c
then return []
else do
(h,t) <- isCons c
t' <- isHeapTreeList t
return $ (:) h t'
isHeapTreeString :: HeapTree -> Maybe String
isHeapTreeString t = do
list <- isHeapTreeList t
if (null list)
then Nothing
else mapM (isChar <=< heapTreeClosure) list
data HeapGraphEntry a = HeapGraphEntry {
hgeBox :: Box,
hgeClosure :: GenClosure (Maybe HeapGraphIndex),
hgeLive :: Bool,
hgeData :: a}
deriving (Show, Functor)
type HeapGraphIndex = Int
newtype HeapGraph a = HeapGraph (M.IntMap (HeapGraphEntry a))
deriving (Show)
lookupHeapGraph :: HeapGraphIndex -> (HeapGraph a) -> Maybe (HeapGraphEntry a)
lookupHeapGraph i (HeapGraph m) = M.lookup i m
heapGraphRoot :: HeapGraphIndex
heapGraphRoot = 0
buildHeapGraph
:: Monoid a
=> Int
-> a
-> Box
-> IO (HeapGraph a)
buildHeapGraph limit rootD initialBox =
fst <$> multiBuildHeapGraph limit [(rootD, initialBox)]
multiBuildHeapGraph
:: Monoid a
=> Int
-> [(a, Box)]
-> IO (HeapGraph a, [(a, HeapGraphIndex)])
multiBuildHeapGraph limit = generalBuildHeapGraph limit (HeapGraph M.empty)
addHeapGraph
:: Monoid a
=> Int
-> a
-> Box
-> HeapGraph a
-> IO (HeapGraphIndex, HeapGraph a)
addHeapGraph limit d box hg = do
(hg', [(_,i)]) <- generalBuildHeapGraph limit hg [(d,box)]
return (i, hg')
annotateHeapGraph :: Monoid a => a -> HeapGraphIndex -> HeapGraph a -> HeapGraph a
annotateHeapGraph d i (HeapGraph hg) = HeapGraph $ M.update go i hg
where
go hge = Just $ hge { hgeData = hgeData hge <> d }
generalBuildHeapGraph
:: Monoid a
=> Int
-> HeapGraph a
-> [(a,Box)]
-> IO (HeapGraph a, [(a, HeapGraphIndex)])
generalBuildHeapGraph limit _ _ | limit <= 0 = error "buildHeapGraph: limit has to be positive"
generalBuildHeapGraph limit (HeapGraph hg) addBoxes = do
let boxList = [ (hgeBox hge, i) | (i, hge) <- M.toList hg ]
indices | M.null hg = [0..]
| otherwise = [1 + fst (M.findMax hg)..]
initialState = (boxList, indices, [])
(is, hg') <- runWriterT (evalStateT run initialState)
let hg'' = foldl' (flip (uncurry annotateHeapGraph)) (HeapGraph hg') is
return (hg'', is)
where
run = do
lift $ tell hg
forM addBoxes $ \(d, b) -> do
Just i <- add limit b
return (d, i)
add 0 _ = return Nothing
add n b = do
(existing,_,_) <- get
mbI <- liftIO $ findM (areBoxesEqual b . fst) existing
case mbI of
Just (_,i) -> return $ Just i
Nothing -> do
i <- nextI
modify (\(x,y,z) -> ((b,i):x, y, z))
c <- liftIO $ getBoxedClosureData b
c' <- T.mapM (add (n-1)) c
lift $ tell (M.singleton i (HeapGraphEntry b c' True mempty))
return $ Just i
nextI = do
i <- gets (head . (\(_,b,_) -> b))
modify (\(a,b,c) -> (a, tail b, c))
return i
updateHeapGraph :: Monoid a => Int -> HeapGraph a -> IO (HeapGraph a, HeapGraphIndex -> HeapGraphIndex)
updateHeapGraph limit (HeapGraph startHG) = do
(hg', indexMap) <- runWriterT $ foldM go (HeapGraph M.empty) (M.toList startHG)
return (hg', (M.!) indexMap)
where
go hg (i, hge) = do
(j, hg') <- liftIO $ addHeapGraph limit (hgeData hge) (hgeBox hge) hg
tell (M.singleton i j)
return hg'
ppHeapGraph :: HeapGraph a -> String
ppHeapGraph (HeapGraph m) = letWrapper ++ ppRef 0 (Just heapGraphRoot)
where
bindings = boundMultipleTimes (HeapGraph m) [heapGraphRoot]
letWrapper =
if null bindings
then ""
else "let " ++ intercalate "\n " (map ppBinding bindings) ++ "\nin "
bindingLetter i = case hgeClosure (iToE i) of
ThunkClosure {..} -> 't'
SelectorClosure {..} -> 't'
APClosure {..} -> 't'
PAPClosure {..} -> 'f'
BCOClosure {..} -> 't'
FunClosure {..} -> 'f'
_ -> 'x'
ppBindingMap = M.fromList $
concat $
map (zipWith (\j (i,c) -> (i, [c] ++ show j)) [(1::Int)..]) $
groupBy ((==) `on` snd) $
sortBy (compare `on` snd)
[ (i, bindingLetter i) | i <- bindings ]
ppVar i = ppBindingMap M.! i
ppBinding i = ppVar i ++ " = " ++ ppEntry 0 (iToE i)
ppEntry prec hge
| Just s <- isString hge = show s
| Just l <- isList hge = "[" ++ intercalate "," (map (ppRef 0) l) ++ "]"
| Just bc <- disassembleBCO (fmap (hgeClosure . iToE)) (hgeClosure hge)
= app ("_bco" : map (ppRef 10) (concatMap F.toList bc))
| otherwise = ppClosure ppRef prec (hgeClosure hge)
where
app [a] = a ++ "()"
app xs = addBraces (10 <= prec) (intercalate " " xs)
ppRef _ Nothing = "..."
ppRef prec (Just i) | i `elem` bindings = ppVar i
| otherwise = ppEntry prec (iToE i)
iToE i = m M.! i
iToUnboundE i = if i `elem` bindings then Nothing else M.lookup i m
isList :: HeapGraphEntry a -> Maybe ([Maybe HeapGraphIndex])
isList hge =
if isNil (hgeClosure hge)
then return []
else do
(h,t) <- isCons (hgeClosure hge)
ti <- t
e <- iToUnboundE ti
t' <- isList e
return $ (:) h t'
isString :: HeapGraphEntry a -> Maybe String
isString e = do
list <- isList e
if (null list)
then Nothing
else mapM (isChar . hgeClosure <=< iToUnboundE <=< id) list
boundMultipleTimes :: HeapGraph a -> [HeapGraphIndex] -> [HeapGraphIndex]
boundMultipleTimes (HeapGraph m) roots = map head $ filter (not.null) $ map tail $ group $ sort $
roots ++ concatMap (catMaybes . allClosures . hgeClosure) (M.elems m)
disassembleBCO :: (a -> Maybe (GenClosure b)) -> GenClosure a -> Maybe [BCI b]
disassembleBCO _ _ | id True = Nothing
disassembleBCO deref (BCOClosure {..}) = do
opsC <- deref instrs
litsC <- deref literals
ptrsC <- deref bcoptrs
return $ disassemble (mccPayload ptrsC) (arrWords litsC) (toBytes (bytes opsC) (arrWords opsC))
disassembleBCO _ _ = Nothing
findM :: (a -> IO Bool) -> [a] -> IO (Maybe a)
findM _p [] = return Nothing
findM p (x:xs) = do
b <- p x
if b then return (Just x) else findM p xs
addBraces :: Bool -> String -> String
addBraces True t = "(" ++ t ++ ")"
addBraces False t = t
braceize :: [String] -> String
braceize [] = ""
braceize xs = "{" ++ intercalate "," xs ++ "}"