Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Functions for performing whole heap census in the style of the normal - heap profiling
Synopsis
- profile :: FilePath -> Int -> Debuggee -> IO ()
- censusClosureType :: [ClosurePtr] -> DebugM CensusByClosureType
- census2LevelClosureType :: [ClosurePtr] -> DebugM CensusByClosureType
- closureCensusBy :: forall k v. (Semigroup v, Ord k) => (ClosurePtr -> SizedClosure -> DebugM (Maybe (k, v))) -> [ClosurePtr] -> DebugM (Map k v)
- type CensusByClosureType = Map Text CensusStats
- writeCensusByClosureType :: FilePath -> CensusByClosureType -> IO ()
- data CensusStats = CS {}
- mkCS :: Size -> CensusStats
- newtype Count = Count Int
- closureToKey :: DebugClosure srt a ConstrDesc c d -> Text
Documentation
profile :: FilePath -> Int -> Debuggee -> IO () Source #
Peform a profile at the given interval (in seconds), the result will
be rendered after each iteration using eventlog2html
.
censusClosureType :: [ClosurePtr] -> DebugM CensusByClosureType Source #
Perform a heap census in the same style as the -hT profile.
census2LevelClosureType :: [ClosurePtr] -> DebugM CensusByClosureType Source #
Perform a 2-level census where the keys are the type of the closure in addition to the type of ptrs of the closure. This can be used to distinguish between lists of different type for example.
closureCensusBy :: forall k v. (Semigroup v, Ord k) => (ClosurePtr -> SizedClosure -> DebugM (Maybe (k, v))) -> [ClosurePtr] -> DebugM (Map k v) Source #
General function for performing a heap census in constant memory
type CensusByClosureType = Map Text CensusStats Source #
writeCensusByClosureType :: FilePath -> CensusByClosureType -> IO () Source #
data CensusStats Source #
Instances
Monoid CensusStats Source # | |
Defined in GHC.Debug.Profile.Types mempty :: CensusStats # mappend :: CensusStats -> CensusStats -> CensusStats # mconcat :: [CensusStats] -> CensusStats # | |
Semigroup CensusStats Source # | |
Defined in GHC.Debug.Profile.Types (<>) :: CensusStats -> CensusStats -> CensusStats # sconcat :: NonEmpty CensusStats -> CensusStats # stimes :: Integral b => b -> CensusStats -> CensusStats # | |
Show CensusStats Source # | |
Defined in GHC.Debug.Profile.Types showsPrec :: Int -> CensusStats -> ShowS # show :: CensusStats -> String # showList :: [CensusStats] -> ShowS # | |
Eq CensusStats Source # | |
Defined in GHC.Debug.Profile.Types (==) :: CensusStats -> CensusStats -> Bool # (/=) :: CensusStats -> CensusStats -> Bool # |
mkCS :: Size -> CensusStats Source #
closureToKey :: DebugClosure srt a ConstrDesc c d -> Text Source #