diff options
author | Patrick Dougherty <patrick.doc@ameritech.net> | 2018-05-16 16:50:13 -0400 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2018-05-20 11:41:04 -0400 |
commit | ec22f7ddc81b40a9dbcf140e5cf44730cb776d00 (patch) | |
tree | ff014a39b87f4d0069cfa4eed28afaf124e552b8 /compiler/ghci/DebuggerUtils.hs | |
parent | 12deb9a97c05ad462ef04e8d2062c3d11c52c6ff (diff) | |
download | haskell-ec22f7ddc81b40a9dbcf140e5cf44730cb776d00.tar.gz |
Add HeapView functionality
This pulls parts of Joachim Breitner's ghc-heap-view library inside GHC.
The bits added are the C hooks into the RTS and a basic Haskell wrapper
to these C hooks. The main reason for these to be added to GHC proper
is that the code needs to be kept in sync with the closure types
defined by the RTS. It is expected that the version of HeapView shipped
with GHC will always work with that version of GHC and that extra
functionality can be layered on top with a library like ghc-heap-view
distributed via Hackage.
Test Plan: validate
Reviewers: simonmar, hvr, nomeata, austin, Phyx, bgamari, erikd
Reviewed By: bgamari
Subscribers: carter, patrickdoc, tmcgilchrist, rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3055
Diffstat (limited to 'compiler/ghci/DebuggerUtils.hs')
-rw-r--r-- | compiler/ghci/DebuggerUtils.hs | 132 |
1 files changed, 0 insertions, 132 deletions
diff --git a/compiler/ghci/DebuggerUtils.hs b/compiler/ghci/DebuggerUtils.hs deleted file mode 100644 index 9af98c1bcf..0000000000 --- a/compiler/ghci/DebuggerUtils.hs +++ /dev/null @@ -1,132 +0,0 @@ -{-# LANGUAGE CPP #-} - -module DebuggerUtils ( - dataConInfoPtrToName, - ) where - -import GhcPrelude - -import GHCi.InfoTable -import CmmInfo ( stdInfoTableSizeB ) -import DynFlags -import HscTypes -import FastString -import IfaceEnv -import Module -import OccName -import Name -import Outputable -import Util - -import Data.Char -import Foreign -import Data.List - -#include "HsVersions.h" - --- | Given a data constructor in the heap, find its Name. --- The info tables for data constructors have a field which records --- the source name of the constructor as a Ptr Word8 (UTF-8 encoded --- string). The format is: --- --- > Package:Module.Name --- --- We use this string to lookup the interpreter's internal representation of the name --- using the lookupOrig. --- -dataConInfoPtrToName :: HscEnv -> Ptr () -> IO Name -dataConInfoPtrToName hsc_env x = do - let dflags = hsc_dflags hsc_env - theString <- do - let ptr = castPtr x :: Ptr StgInfoTable - conDescAddress <- getConDescAddress dflags ptr - peekArray0 0 conDescAddress - let (pkg, mod, occ) = parse theString - pkgFS = mkFastStringByteList pkg - modFS = mkFastStringByteList mod - occFS = mkFastStringByteList occ - occName = mkOccNameFS OccName.dataName occFS - modName = mkModule (fsToUnitId pkgFS) (mkModuleNameFS modFS) - lookupOrigIO hsc_env modName occName - - where - - {- To find the string in the constructor's info table we need to consider - the layout of info tables relative to the entry code for a closure. - - An info table can be next to the entry code for the closure, or it can - be separate. The former (faster) is used in registerised versions of ghc, - and the latter (portable) is for non-registerised versions. - - The diagrams below show where the string is to be found relative to - the normal info table of the closure. - - 1) Code next to table: - - -------------- - | | <- pointer to the start of the string - -------------- - | | <- the (start of the) info table structure - | | - | | - -------------- - | entry code | - | .... | - - In this case the pointer to the start of the string can be found in - the memory location _one word before_ the first entry in the normal info - table. - - 2) Code NOT next to table: - - -------------- - info table structure -> | *------------------> -------------- - | | | entry code | - | | | .... | - -------------- - ptr to start of str -> | | - -------------- - - In this case the pointer to the start of the string can be found - in the memory location: info_table_ptr + info_table_size - -} - - getConDescAddress :: DynFlags -> Ptr StgInfoTable -> IO (Ptr Word8) - getConDescAddress dflags ptr - | ghciTablesNextToCode = do - let ptr' = ptr `plusPtr` (- wORD_SIZE dflags) - -- NB. the offset must be read as an Int32 not a Word32, so - -- that the sign is preserved when converting to an Int. - offsetToString <- fromIntegral <$> (peek ptr' :: IO Int32) - return $ (ptr `plusPtr` stdInfoTableSizeB dflags) `plusPtr` offsetToString - | otherwise = - peek $ intPtrToPtr $ ptrToIntPtr ptr + fromIntegral (stdInfoTableSizeB dflags) - -- parsing names is a little bit fiddly because we have a string in the form: - -- pkg:A.B.C.foo, and we want to split it into three parts: ("pkg", "A.B.C", "foo"). - -- Thus we split at the leftmost colon and the rightmost occurrence of the dot. - -- It would be easier if the string was in the form pkg:A.B.C:foo, but alas - -- this is not the conventional way of writing Haskell names. We stick with - -- convention, even though it makes the parsing code more troublesome. - -- Warning: this code assumes that the string is well formed. - parse :: [Word8] -> ([Word8], [Word8], [Word8]) - parse input - = ASSERT(all (`lengthExceeds` 0) ([pkg, mod, occ])) (pkg, mod, occ) - where - dot = fromIntegral (ord '.') - (pkg, rest1) = break (== fromIntegral (ord ':')) input - (mod, occ) - = (concat $ intersperse [dot] $ reverse modWords, occWord) - where - (modWords, occWord) = ASSERT(rest1 `lengthExceeds` 0) (parseModOcc [] (tail rest1)) - parseModOcc :: [[Word8]] -> [Word8] -> ([[Word8]], [Word8]) - -- We only look for dots if str could start with a module name, - -- i.e. if it starts with an upper case character. - -- Otherwise we might think that "X.:->" is the module name in - -- "X.:->.+", whereas actually "X" is the module name and - -- ":->.+" is a constructor name. - parseModOcc acc str@(c : _) - | isUpper $ chr $ fromIntegral c - = case break (== dot) str of - (top, []) -> (acc, top) - (top, _ : bot) -> parseModOcc (top : acc) bot - parseModOcc acc str = (acc, str) |