ghc-debug-client-0.1.0.0: Useful functions for writing heap analysis tools which use ghc-debug.
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Debug.Client

Description

The main API for creating debuggers. For example, this API can be used to connect to an instrumented process, query the GC roots and then decode the first root up to depth 10 and displayed to the user.

main = withDebuggeeConnect "/tmp/ghc-debug" p1

p1 :: Debuggee -> IO ()
p1 e = do
  pause e
  g <- run e $ do
        precacheBlocks
        (r:_) <- gcRoots
        buildHeapGraph (Just 10) r
  putStrLn (ppHeapGraph (const "") h)
Synopsis

Running/Connecting to a debuggee

debuggeeRun Source #

Arguments

:: FilePath

path to executable to run as the debuggee

-> FilePath

filename of socket (e.g. "/tmp/ghc-debug")

-> IO Debuggee 

Run a debuggee and connect to it. Use debuggeeClose when you're done.

debuggeeConnect Source #

Arguments

:: FilePath

filename of socket (e.g. "/tmp/ghc-debug")

-> IO Debuggee 

Connect to a debuggee on the given socket. Use debuggeeClose when you're done.

debuggeeClose :: Debuggee -> IO () Source #

Close the connection to the debuggee.

withDebuggeeRun Source #

Arguments

:: FilePath

path to executable to run as the debuggee

-> FilePath

filename of socket (e.g. "/tmp/ghc-debug")

-> (Debuggee -> IO a) 
-> IO a 

Bracketed version of debuggeeRun. Runs a debuggee, connects to it, runs the action, kills the process, then closes the debuggee.

withDebuggeeConnect Source #

Arguments

:: FilePath

filename of socket (e.g. "/tmp/ghc-debug")

-> (Debuggee -> IO a) 
-> IO a 

Bracketed version of debuggeeConnect. Connects to a debuggee, runs the action, then closes the debuggee.

snapshotRun :: FilePath -> (Debuggee -> IO a) -> IO a Source #

Start an analysis session using a snapshot. This will not connect to a debuggee. The snapshot is created by snapshot.

Running DebugM

run :: Debuggee -> DebugM a -> IO a Source #

Run a DebugM a in the given environment.

runAnalysis :: DebugM a -> (a -> IO r) -> Debuggee -> IO r Source #

Perform the given analysis whilst the debuggee is paused, then resume and apply the continuation to the result.

Pause/Resume

pause :: Debuggee -> IO () Source #

Pause the debuggee

resume :: Debuggee -> IO () Source #

Resume the debuggee

pausePoll :: Debuggee -> IO () Source #

Like pause, but wait for the debuggee to pause itself. It currently impossible to resume after a pause caused by a poll.?????????? Is that true???? can we not just call resume????

withPause :: Debuggee -> IO a -> IO a Source #

Bracketed version of pause/resume.

Basic Requests

version :: DebugM Word32 Source #

Query the debuggee for the protocol version

gcRoots :: DebugM [ClosurePtr] Source #

Query the debuggee for the list of GC Roots

allBlocks :: DebugM [RawBlock] Source #

Query the debuggee for all the blocks it knows about

getSourceInfo :: InfoTablePtr -> DebugM (Maybe SourceInformation) Source #

Query the debuggee for source information about a specific info table. This requires your executable to be built with -finfo-table-map.

savedObjects :: DebugM [ClosurePtr] Source #

Query the debuggee for the list of saved objects.

precacheBlocks :: DebugM [RawBlock] Source #

Fetch all the blocks from the debuggee and add them to the block cache

dereferenceClosure :: ClosurePtr -> DebugM SizedClosure Source #

Consult the BlockCache for the block which contains a specific closure, if it's not there then try to fetch the right block, if that fails, call dereferenceClosureDirect

dereferenceStack :: StackCont -> DebugM StackFrames Source #

Deference some StackFrames from a given StackCont

dereferencePapPayload :: PayloadCont -> DebugM PapPayload Source #

Derference the PapPayload from the PayloadCont

dereferenceConDesc :: ConstrDescCont -> DebugM ConstrDesc Source #

class Quadtraversable (m :: TYPE LiftedRep -> TYPE LiftedRep -> TYPE LiftedRep -> TYPE LiftedRep -> TYPE LiftedRep) where #

Methods

quadtraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> m a c e h -> f (m b d g i) #

Instances

Instances details
Quadtraversable DebugClosure 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

quadtraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> DebugClosure a c e h -> f (DebugClosure b d g i) #

Quadtraversable (DebugClosureWithExtra x) 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

quadtraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> DebugClosureWithExtra x a c e h -> f (DebugClosureWithExtra x b d g i) #

Building a Heap Graph

buildHeapGraph :: Maybe Int -> ClosurePtr -> DebugM (HeapGraph Size) Source #

Build a heap graph starting from the given root. The first argument controls how many levels to recurse. You nearly always want to set this to a small number ~ 10, as otherwise you can easily run out of memory.

multiBuildHeapGraph :: Maybe Int -> NonEmpty ClosurePtr -> DebugM (HeapGraph Size) Source #

Build a heap graph starting from multiple roots. The first argument controls how many levels to recurse. You nearly always want to set this value to a small number ~ 10 as otherwise you can easily run out of memory.

data HeapGraph a #

Constructors

HeapGraph 

Instances

Instances details
Foldable HeapGraph 
Instance details

Defined in GHC.Debug.Types.Graph

Methods

fold :: Monoid m => HeapGraph m -> m #

foldMap :: Monoid m => (a -> m) -> HeapGraph a -> m #

foldMap' :: Monoid m => (a -> m) -> HeapGraph a -> m #

foldr :: (a -> b -> b) -> b -> HeapGraph a -> b #

foldr' :: (a -> b -> b) -> b -> HeapGraph a -> b #

foldl :: (b -> a -> b) -> b -> HeapGraph a -> b #

foldl' :: (b -> a -> b) -> b -> HeapGraph a -> b #

foldr1 :: (a -> a -> a) -> HeapGraph a -> a #

foldl1 :: (a -> a -> a) -> HeapGraph a -> a #

toList :: HeapGraph a -> [a] #

null :: HeapGraph a -> Bool #

length :: HeapGraph a -> Int #

elem :: Eq a => a -> HeapGraph a -> Bool #

maximum :: Ord a => HeapGraph a -> a #

minimum :: Ord a => HeapGraph a -> a #

sum :: Num a => HeapGraph a -> a #

product :: Num a => HeapGraph a -> a #

Traversable HeapGraph 
Instance details

Defined in GHC.Debug.Types.Graph

Methods

traverse :: Applicative f => (a -> f b) -> HeapGraph a -> f (HeapGraph b) #

sequenceA :: Applicative f => HeapGraph (f a) -> f (HeapGraph a) #

mapM :: Monad m => (a -> m b) -> HeapGraph a -> m (HeapGraph b) #

sequence :: Monad m => HeapGraph (m a) -> m (HeapGraph a) #

Functor HeapGraph 
Instance details

Defined in GHC.Debug.Types.Graph

Methods

fmap :: (a -> b) -> HeapGraph a -> HeapGraph b #

(<$) :: a -> HeapGraph b -> HeapGraph a #

Show a => Show (HeapGraph a) 
Instance details

Defined in GHC.Debug.Types.Graph

data HeapGraphEntry a #

Constructors

HeapGraphEntry 

Fields

Instances

Instances details
Foldable HeapGraphEntry 
Instance details

Defined in GHC.Debug.Types.Graph

Methods

fold :: Monoid m => HeapGraphEntry m -> m #

foldMap :: Monoid m => (a -> m) -> HeapGraphEntry a -> m #

foldMap' :: Monoid m => (a -> m) -> HeapGraphEntry a -> m #

foldr :: (a -> b -> b) -> b -> HeapGraphEntry a -> b #

foldr' :: (a -> b -> b) -> b -> HeapGraphEntry a -> b #

foldl :: (b -> a -> b) -> b -> HeapGraphEntry a -> b #

foldl' :: (b -> a -> b) -> b -> HeapGraphEntry a -> b #

foldr1 :: (a -> a -> a) -> HeapGraphEntry a -> a #

foldl1 :: (a -> a -> a) -> HeapGraphEntry a -> a #

toList :: HeapGraphEntry a -> [a] #

null :: HeapGraphEntry a -> Bool #

length :: HeapGraphEntry a -> Int #

elem :: Eq a => a -> HeapGraphEntry a -> Bool #

maximum :: Ord a => HeapGraphEntry a -> a #

minimum :: Ord a => HeapGraphEntry a -> a #

sum :: Num a => HeapGraphEntry a -> a #

product :: Num a => HeapGraphEntry a -> a #

Traversable HeapGraphEntry 
Instance details

Defined in GHC.Debug.Types.Graph

Methods

traverse :: Applicative f => (a -> f b) -> HeapGraphEntry a -> f (HeapGraphEntry b) #

sequenceA :: Applicative f => HeapGraphEntry (f a) -> f (HeapGraphEntry a) #

mapM :: Monad m => (a -> m b) -> HeapGraphEntry a -> m (HeapGraphEntry b) #

sequence :: Monad m => HeapGraphEntry (m a) -> m (HeapGraphEntry a) #

Functor HeapGraphEntry 
Instance details

Defined in GHC.Debug.Types.Graph

Methods

fmap :: (a -> b) -> HeapGraphEntry a -> HeapGraphEntry b #

(<$) :: a -> HeapGraphEntry b -> HeapGraphEntry a #

Show a => Show (HeapGraphEntry a) 
Instance details

Defined in GHC.Debug.Types.Graph

Printing a heap graph

ppHeapGraph :: (a -> String) -> HeapGraph a -> String #

Tracing

traceWrite :: DebugMonad m => Show a => a -> m () Source #

Caching

Types

data RawBlock #

Instances

Instances details
Show RawBlock 
Instance details

Defined in GHC.Debug.Types.Ptr

Binary RawBlock 
Instance details

Defined in GHC.Debug.Types.Ptr

Methods

put :: RawBlock -> Put #

get :: Get RawBlock #

putList :: [RawBlock] -> Put #

data BlockPtr #

Instances

Instances details
Show BlockPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Binary BlockPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Methods

put :: BlockPtr -> Put #

get :: Get BlockPtr #

putList :: [BlockPtr] -> Put #

Eq BlockPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Ord BlockPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Hashable BlockPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Methods

hashWithSalt :: Int -> BlockPtr -> Int #

hash :: BlockPtr -> Int #

data StackPtr #

Instances

Instances details
Show StackPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Binary StackPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Methods

put :: StackPtr -> Put #

get :: Get StackPtr #

putList :: [StackPtr] -> Put #

Eq StackPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Ord StackPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Hashable StackPtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Methods

hashWithSalt :: Int -> StackPtr -> Int #

hash :: StackPtr -> Int #

data ClosurePtr #

Instances

Instances details
Show ClosurePtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Binary ClosurePtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Eq ClosurePtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Ord ClosurePtr 
Instance details

Defined in GHC.Debug.Types.Ptr

Hashable ClosurePtr 
Instance details

Defined in GHC.Debug.Types.Ptr

type StackHI = GenStackFrames (Maybe HeapGraphIndex) #

type PapHI = GenPapPayload (Maybe HeapGraphIndex) #