Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GHC.Debug.Profile
Description
Functions for performing whole heap census in the style of the normal - heap profiling
Synopsis
- 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 (ProfileKey, ProfileKeyArgs) CensusStats
- writeCensusByClosureType :: FilePath -> CensusByClosureType -> IO ()
- data CensusStats = CS {}
- data ProfileKey
- data ProfileKeyArgs
- = ArrKeyArgs !ProfileKey !Int
- | AllKeyArgs !(Vector ProfileKey)
- | NoArgs
- prettyProfileKey :: ProfileKey -> Text
- prettyShortProfileKey :: ProfileKey -> Text
- prettyProfileKeyArgs :: ProfileKeyArgs -> Text
- prettyProfileKeyArgs' :: (ProfileKey -> Text) -> ProfileKeyArgs -> Text
- prettyShortProfileKeyArgs :: ProfileKeyArgs -> Text
- mkCS :: ClosurePtr -> Size -> CensusStats
- newtype Count = Count {}
- closureToKey :: DebugClosure ccs srt a ConstrDesc c d -> Text
- data ConstrDescText
- packConstrDesc :: ConstrDesc -> ConstrDescText
- pkgsText :: ConstrDescText -> Text
- modlText :: ConstrDescText -> Text
- nameText :: ConstrDescText -> Text
Documentation
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 (ProfileKey, ProfileKeyArgs) CensusStats Source #
writeCensusByClosureType :: FilePath -> CensusByClosureType -> IO () Source #
data CensusStats Source #
Instances
Monoid CensusStats Source # | |
Defined in GHC.Debug.Profile.Types Methods mempty :: CensusStats # mappend :: CensusStats -> CensusStats -> CensusStats # mconcat :: [CensusStats] -> CensusStats # | |
Semigroup CensusStats Source # | |
Defined in GHC.Debug.Profile.Types Methods (<>) :: CensusStats -> CensusStats -> CensusStats # sconcat :: NonEmpty CensusStats -> CensusStats # stimes :: Integral b => b -> CensusStats -> CensusStats # | |
Show CensusStats Source # | |
Defined in GHC.Debug.Profile.Types Methods showsPrec :: Int -> CensusStats -> ShowS # show :: CensusStats -> String # showList :: [CensusStats] -> ShowS # | |
Eq CensusStats Source # | |
Defined in GHC.Debug.Profile.Types |
data ProfileKey Source #
Constructors
ProfileConstrDesc !ConstrDescText | |
ProfileClosureDesc !Text |
Instances
Show ProfileKey Source # | |
Defined in GHC.Debug.Profile Methods showsPrec :: Int -> ProfileKey -> ShowS # show :: ProfileKey -> String # showList :: [ProfileKey] -> ShowS # | |
Eq ProfileKey Source # | |
Defined in GHC.Debug.Profile | |
Ord ProfileKey Source # | |
Defined in GHC.Debug.Profile Methods compare :: ProfileKey -> ProfileKey -> Ordering # (<) :: ProfileKey -> ProfileKey -> Bool # (<=) :: ProfileKey -> ProfileKey -> Bool # (>) :: ProfileKey -> ProfileKey -> Bool # (>=) :: ProfileKey -> ProfileKey -> Bool # max :: ProfileKey -> ProfileKey -> ProfileKey # min :: ProfileKey -> ProfileKey -> ProfileKey # |
data ProfileKeyArgs Source #
Constructors
ArrKeyArgs !ProfileKey !Int | |
AllKeyArgs !(Vector ProfileKey) | |
NoArgs |
Instances
Show ProfileKeyArgs Source # | |
Defined in GHC.Debug.Profile Methods showsPrec :: Int -> ProfileKeyArgs -> ShowS # show :: ProfileKeyArgs -> String # showList :: [ProfileKeyArgs] -> ShowS # | |
Eq ProfileKeyArgs Source # | |
Defined in GHC.Debug.Profile Methods (==) :: ProfileKeyArgs -> ProfileKeyArgs -> Bool # (/=) :: ProfileKeyArgs -> ProfileKeyArgs -> Bool # | |
Ord ProfileKeyArgs Source # | |
Defined in GHC.Debug.Profile Methods compare :: ProfileKeyArgs -> ProfileKeyArgs -> Ordering # (<) :: ProfileKeyArgs -> ProfileKeyArgs -> Bool # (<=) :: ProfileKeyArgs -> ProfileKeyArgs -> Bool # (>) :: ProfileKeyArgs -> ProfileKeyArgs -> Bool # (>=) :: ProfileKeyArgs -> ProfileKeyArgs -> Bool # max :: ProfileKeyArgs -> ProfileKeyArgs -> ProfileKeyArgs # min :: ProfileKeyArgs -> ProfileKeyArgs -> ProfileKeyArgs # |
prettyProfileKey :: ProfileKey -> Text Source #
Show the full ProfileKey
, including package and module locations if available.
prettyShortProfileKey :: ProfileKey -> Text Source #
Show the ProfileKey
in a shortened form if possible.
For example, it omits package and module locations for ProfileConstrDesc
.
prettyProfileKeyArgs' :: (ProfileKey -> Text) -> ProfileKeyArgs -> Text Source #
mkCS :: ClosurePtr -> Size -> CensusStats Source #
closureToKey :: DebugClosure ccs srt a ConstrDesc c d -> Text Source #
data ConstrDescText Source #
ConstrDescText
wraps a ConstrDesc
but is backed by a Text
.
More efficient to keep around than ConstrDesc
.
Instances
Show ConstrDescText Source # | |
Defined in GHC.Debug.Profile Methods showsPrec :: Int -> ConstrDescText -> ShowS # show :: ConstrDescText -> String # showList :: [ConstrDescText] -> ShowS # | |
Eq ConstrDescText Source # | |
Defined in GHC.Debug.Profile Methods (==) :: ConstrDescText -> ConstrDescText -> Bool # (/=) :: ConstrDescText -> ConstrDescText -> Bool # | |
Ord ConstrDescText Source # | |
Defined in GHC.Debug.Profile Methods compare :: ConstrDescText -> ConstrDescText -> Ordering # (<) :: ConstrDescText -> ConstrDescText -> Bool # (<=) :: ConstrDescText -> ConstrDescText -> Bool # (>) :: ConstrDescText -> ConstrDescText -> Bool # (>=) :: ConstrDescText -> ConstrDescText -> Bool # max :: ConstrDescText -> ConstrDescText -> ConstrDescText # min :: ConstrDescText -> ConstrDescText -> ConstrDescText # |
pkgsText :: ConstrDescText -> Text Source #
modlText :: ConstrDescText -> Text Source #
nameText :: ConstrDescText -> Text Source #