Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- decode :: Text -> Either String Profile
- decode' :: Text -> Either String Profile
- profile :: Parser Profile
- data CostCentreTree
- aggregatedCostCentres :: Profile -> [AggregatedCostCentre]
- aggregatedCostCentresOrderBy :: Ord a => (AggregatedCostCentre -> a) -> Profile -> [AggregatedCostCentre]
- costCentres :: Profile -> Maybe (Tree CostCentre)
- costCentresOrderBy :: Ord a => (CostCentre -> a) -> Profile -> Maybe (Tree CostCentre)
- aggregateCallSites :: Text -> Text -> Profile -> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
- aggregateCallSitesOrderBy :: Ord a => (CallSite AggregatedCostCentre -> a) -> Text -> Text -> Profile -> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
- callSites :: Text -> Text -> Profile -> Maybe (AggregatedCostCentre, [CallSite CostCentre])
- callSitesOrderBy :: Ord a => (CallSite CostCentre -> a) -> Text -> Text -> Profile -> Maybe (AggregatedCostCentre, [CallSite CostCentre])
- aggregateModules :: Profile -> [AggregateModule]
- aggregateModulesOrderBy :: Ord a => (AggregateModule -> a) -> Profile -> [AggregateModule]
- data Profile = Profile {}
- data TotalTime = TotalTime {}
- newtype TotalAlloc = TotalAlloc {}
- data AggregatedCostCentre = AggregatedCostCentre {
- aggregatedCostCentreName :: !Text
- aggregatedCostCentreModule :: !Text
- aggregatedCostCentreSrc :: !(Maybe Text)
- aggregatedCostCentreEntries :: !(Maybe Integer)
- aggregatedCostCentreTime :: !Scientific
- aggregatedCostCentreAlloc :: !Scientific
- aggregatedCostCentreTicks :: !(Maybe Integer)
- aggregatedCostCentreBytes :: !(Maybe Integer)
- data CostCentre = CostCentre {
- costCentreNo :: !CostCentreNo
- costCentreName :: !Text
- costCentreModule :: !Text
- costCentreSrc :: !(Maybe Text)
- costCentreEntries :: !Integer
- costCentreIndTime :: !Scientific
- costCentreIndAlloc :: !Scientific
- costCentreInhTime :: !Scientific
- costCentreInhAlloc :: !Scientific
- costCentreTicks :: !(Maybe Integer)
- costCentreBytes :: !(Maybe Integer)
- type CostCentreNo = Int
- data CallSite cc = CallSite {}
- data AggregateModule = AggregateModule {}
Documentation
decode :: Text -> Either String Profile Source #
Decode a GHC time allocation profiling report from a lazy Text
decode' :: Text -> Either String Profile Source #
Decode a GHC time allocation profiling report from a strict Text
Parser
Cost-centre tree
data CostCentreTree Source #
Instances
Show CostCentreTree Source # | |
Defined in GHC.Prof.Types showsPrec :: Int -> CostCentreTree -> ShowS # show :: CostCentreTree -> String # showList :: [CostCentreTree] -> ShowS # |
aggregatedCostCentres :: Profile -> [AggregatedCostCentre] Source #
Build a list of cost-centres from a profiling report ordered by the time spent and the amount of allocation.
aggregatedCostCentresOrderBy Source #
:: Ord a | |
=> (AggregatedCostCentre -> a) | Sorting key function |
-> Profile | |
-> [AggregatedCostCentre] |
Build a list of cost-centres from a profling report ordered by the given key.
costCentres :: Profile -> Maybe (Tree CostCentre) Source #
Build a tree of cost-centres from a profiling report.
:: Ord a | |
=> (CostCentre -> a) | Sorting key function |
-> Profile | |
-> Maybe (Tree CostCentre) |
Build a tree of cost-centres from a profiling report. Nodes are sorted by the given key function for each level of the tree.
:: Text | Cost centre name |
-> Text | Module name |
-> Profile | |
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre]) |
Build a list of call sites (caller functions of a cost centre) aggregated by their cost centre names and module names.
aggregateCallSitesOrderBy Source #
:: Ord a | |
=> (CallSite AggregatedCostCentre -> a) | Sorting key function |
-> Text | Cost centre name |
-> Text | Module name |
-> Profile | |
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre]) |
Build a list of call sites (caller functions of a cost centre) aggregated by their cost centre names and module names. Call sites are sorted by the given key function.
:: Text | Cost-centre name |
-> Text | Module name |
-> Profile | |
-> Maybe (AggregatedCostCentre, [CallSite CostCentre]) |
Build a list of call-sites (caller functions) for a specified cost-centre name and module name.
:: Ord a | |
=> (CallSite CostCentre -> a) | Sorting key function |
-> Text | Cost-centre name |
-> Text | Module name |
-> Profile | |
-> Maybe (AggregatedCostCentre, [CallSite CostCentre]) |
Build a list of call-sites (caller function) for a specified cost-centre name and module name. Nodes are sorted by the given key function.
aggregateModules :: Profile -> [AggregateModule] Source #
Break down aggregate cost centres by module sorted by total time and allocation.
aggregateModulesOrderBy Source #
:: Ord a | |
=> (AggregateModule -> a) | Sorting key function |
-> Profile | |
-> [AggregateModule] |
Break odwn aggregate cost centres by module.
Types
Top-level profiling report
total time
in the profiling reports
TotalTime | |
|
newtype TotalAlloc Source #
total alloc
in the profiling reports
TotalAlloc | |
|
Instances
Show TotalAlloc Source # | |
Defined in GHC.Prof.Types showsPrec :: Int -> TotalAlloc -> ShowS # show :: TotalAlloc -> String # showList :: [TotalAlloc] -> ShowS # |
data AggregatedCostCentre Source #
AggregatedCostCentre | |
|
Instances
Eq AggregatedCostCentre Source # | |
Defined in GHC.Prof.Types (==) :: AggregatedCostCentre -> AggregatedCostCentre -> Bool # (/=) :: AggregatedCostCentre -> AggregatedCostCentre -> Bool # | |
Ord AggregatedCostCentre Source # | |
Defined in GHC.Prof.Types compare :: AggregatedCostCentre -> AggregatedCostCentre -> Ordering # (<) :: AggregatedCostCentre -> AggregatedCostCentre -> Bool # (<=) :: AggregatedCostCentre -> AggregatedCostCentre -> Bool # (>) :: AggregatedCostCentre -> AggregatedCostCentre -> Bool # (>=) :: AggregatedCostCentre -> AggregatedCostCentre -> Bool # max :: AggregatedCostCentre -> AggregatedCostCentre -> AggregatedCostCentre # min :: AggregatedCostCentre -> AggregatedCostCentre -> AggregatedCostCentre # | |
Show AggregatedCostCentre Source # | |
Defined in GHC.Prof.Types showsPrec :: Int -> AggregatedCostCentre -> ShowS # show :: AggregatedCostCentre -> String # showList :: [AggregatedCostCentre] -> ShowS # |
data CostCentre Source #
Cost-centre node
CostCentre | |
|
Instances
Eq CostCentre Source # | |
Defined in GHC.Prof.Types (==) :: CostCentre -> CostCentre -> Bool # (/=) :: CostCentre -> CostCentre -> Bool # | |
Ord CostCentre Source # | |
Defined in GHC.Prof.Types compare :: CostCentre -> CostCentre -> Ordering # (<) :: CostCentre -> CostCentre -> Bool # (<=) :: CostCentre -> CostCentre -> Bool # (>) :: CostCentre -> CostCentre -> Bool # (>=) :: CostCentre -> CostCentre -> Bool # max :: CostCentre -> CostCentre -> CostCentre # min :: CostCentre -> CostCentre -> CostCentre # | |
Show CostCentre Source # | |
Defined in GHC.Prof.Types showsPrec :: Int -> CostCentre -> ShowS # show :: CostCentre -> String # showList :: [CostCentre] -> ShowS # |
type CostCentreNo = Int Source #
CallSite | |
|
data AggregateModule Source #
AggregateModule | |
|
Instances
Eq AggregateModule Source # | |
Defined in GHC.Prof.Types (==) :: AggregateModule -> AggregateModule -> Bool # (/=) :: AggregateModule -> AggregateModule -> Bool # | |
Ord AggregateModule Source # | |
Defined in GHC.Prof.Types compare :: AggregateModule -> AggregateModule -> Ordering # (<) :: AggregateModule -> AggregateModule -> Bool # (<=) :: AggregateModule -> AggregateModule -> Bool # (>) :: AggregateModule -> AggregateModule -> Bool # (>=) :: AggregateModule -> AggregateModule -> Bool # max :: AggregateModule -> AggregateModule -> AggregateModule # min :: AggregateModule -> AggregateModule -> AggregateModule # | |
Show AggregateModule Source # | |
Defined in GHC.Prof.Types showsPrec :: Int -> AggregateModule -> ShowS # show :: AggregateModule -> String # showList :: [AggregateModule] -> ShowS # |