module GHC.Prof.CostCentreTree
(
aggregatedCostCentres
, aggregatedCostCentresOrderBy
, costCentres
, costCentresOrderBy
, aggregateCallSites
, aggregateCallSitesOrderBy
, callSites
, callSitesOrderBy
, aggregateModules
, aggregateModulesOrderBy
, buildAggregatedCostCentresOrderBy
, buildCostCentresOrderBy
, buildCallSitesOrderBy
, buildAggregateCallSitesOrderBy
) where
import Control.Applicative
import Control.Arrow ((&&&))
import Control.Monad
import Data.Function (on)
import Data.List
import Data.Maybe (listToMaybe)
import Prelude hiding (mapM)
import qualified Data.Foldable as Fold
import Data.Text (Text)
import Data.Tree (Tree)
import qualified Data.Set as Set
import qualified Data.Tree as Tree
import Control.Monad.Extras (seqM)
import GHC.Prof.Types as Types
#if MIN_VERSION_containers(0, 5, 0)
import qualified Data.IntMap.Strict as IntMap
import qualified Data.Map.Strict as Map
#else
import qualified Data.IntMap as IntMap
import qualified Data.Map as Map
#endif
aggregatedCostCentres :: Profile -> [AggregatedCostCentre]
aggregatedCostCentres = aggregatedCostCentresOrderBy sortKey
where
sortKey = aggregatedCostCentreTime &&& aggregatedCostCentreAlloc
aggregatedCostCentresOrderBy
:: Ord a
=> (AggregatedCostCentre -> a)
-> Profile
-> [AggregatedCostCentre]
aggregatedCostCentresOrderBy sortKey =
buildAggregatedCostCentresOrderBy sortKey . profileCostCentreTree
costCentres :: Profile -> Maybe (Tree CostCentre)
costCentres = costCentresOrderBy sortKey
where
sortKey =
costCentreInhTime &&& costCentreIndTime &&&
costCentreInhAlloc &&& costCentreIndAlloc
costCentresOrderBy
:: Ord a
=> (CostCentre -> a)
-> Profile
-> Maybe (Tree CostCentre)
costCentresOrderBy sortKey =
buildCostCentresOrderBy sortKey . profileCostCentreTree
aggregateCallSites
:: Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
aggregateCallSites = aggregateCallSitesOrderBy sortKey
where
sortKey = callSiteContribTime &&& callSiteContribAlloc
&&& aggregatedCostCentreTime . callSiteCostCentre
&&& aggregatedCostCentreAlloc . callSiteCostCentre
aggregateCallSitesOrderBy
:: Ord a
=> (CallSite AggregatedCostCentre -> a)
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
aggregateCallSitesOrderBy sortKey name modName =
buildAggregateCallSitesOrderBy sortKey name modName . profileCostCentreTree
callSites
:: Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
callSites = callSitesOrderBy sortKey
where
sortKey = callSiteContribTime &&& callSiteContribAlloc
&&& costCentreIndTime . callSiteCostCentre
&&& costCentreIndAlloc . callSiteCostCentre
callSitesOrderBy
:: Ord a
=> (CallSite CostCentre -> a)
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
callSitesOrderBy sortKey name modName =
buildCallSitesOrderBy sortKey name modName . profileCostCentreTree
aggregateModules
:: Profile
-> [AggregateModule]
aggregateModules = aggregateModulesOrderBy sortKey
where
sortKey = aggregateModuleTime &&& aggregateModuleAlloc
aggregateModulesOrderBy
:: Ord a
=> (AggregateModule -> a)
-> Profile
-> [AggregateModule]
aggregateModulesOrderBy sortKey =
buildAggregateModulesOrderBy sortKey . profileCostCentreTree
buildAggregatedCostCentresOrderBy
:: Ord a
=> (AggregatedCostCentre -> a)
-> CostCentreTree
-> [AggregatedCostCentre]
buildAggregatedCostCentresOrderBy sortKey CostCentreTree {..} =
sortBy (flip compare `on` sortKey) $
concatMap Map.elems $ Map.elems $ costCentreAggregate
buildCostCentresOrderBy
:: Ord a
=> (CostCentre -> a)
-> CostCentreTree
-> Maybe (Tree CostCentre)
buildCostCentresOrderBy sortKey CostCentreTree {..} = do
rootKey <- listToMaybe $ IntMap.keys costCentreNodes
Tree.unfoldTreeM build rootKey
where
build key = do
node <- IntMap.lookup key costCentreNodes
return (node, children)
where
!children = maybe [] Fold.toList $ do
nodes <- IntMap.lookup key costCentreChildren
return $ costCentreNo
<$> sortBy (flip compare `on` sortKey) (Set.toList nodes)
buildAggregateCallSitesOrderBy
:: Ord a
=> (CallSite AggregatedCostCentre -> a)
-> Text
-> Text
-> CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
buildAggregateCallSitesOrderBy sortKey name modName tree@CostCentreTree {..} =
(,) <$> callee <*> callers
where
callee = lookupAggregate name modName costCentreAggregate
callers = do
callees <- Map.lookup (name, modName) costCentreCallSites
sortBy (flip compare `on` sortKey) . Map.elems
<$> foldM (buildAggregateCallSite tree) Map.empty (Set.toList callees)
buildAggregateCallSite
:: CostCentreTree
-> Map.Map (Text, Text) (CallSite AggregatedCostCentre)
-> CostCentre
-> Maybe (Map.Map (Text, Text) (CallSite AggregatedCostCentre))
buildAggregateCallSite CostCentreTree {..} parents CostCentre {..} = do
parentNo <- IntMap.lookup costCentreNo costCentreParents
parent <- IntMap.lookup parentNo costCentreNodes
let parentName = Types.costCentreName parent
parentModule = Types.costCentreModule parent
aggregate <- lookupAggregate parentName parentModule costCentreAggregate
return $! Map.insertWith
mergeCallSites
(parentName, parentModule)
CallSite
{ callSiteCostCentre = aggregate
, callSiteContribEntries = costCentreEntries
, callSiteContribTime = costCentreIndTime
, callSiteContribAlloc = costCentreIndAlloc
, callSiteContribTicks = costCentreTicks
, callSiteContribBytes = costCentreBytes
}
parents
mergeCallSites :: CallSite a -> CallSite a -> CallSite a
mergeCallSites a b = a
{ callSiteContribEntries = callSiteContribEntries a + callSiteContribEntries b
, callSiteContribTime = callSiteContribTime a + callSiteContribTime b
, callSiteContribAlloc = callSiteContribAlloc a + callSiteContribAlloc b
, callSiteContribTicks = seqM $ (+)
<$> callSiteContribTicks a
<*> callSiteContribTicks b
, callSiteContribBytes = seqM $ (+)
<$> callSiteContribBytes a
<*> callSiteContribBytes b
}
buildCallSitesOrderBy
:: Ord a
=> (CallSite CostCentre -> a)
-> Text
-> Text
-> CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
buildCallSitesOrderBy sortKey name modName tree@CostCentreTree {..} =
(,) <$> callee <*> callers
where
callee = lookupAggregate name modName costCentreAggregate
callers = do
callees <- Map.lookup (name, modName) costCentreCallSites
sortBy (flip compare `on` sortKey)
<$> mapM (buildCallSite tree) (Set.toList callees)
buildCallSite
:: CostCentreTree
-> CostCentre
-> Maybe (CallSite CostCentre)
buildCallSite CostCentreTree {..} CostCentre {..} = do
parentNo <- IntMap.lookup costCentreNo costCentreParents
parent <- IntMap.lookup parentNo costCentreNodes
return CallSite
{ callSiteCostCentre = parent
, callSiteContribEntries = costCentreEntries
, callSiteContribTime = costCentreIndTime
, callSiteContribAlloc = costCentreIndAlloc
, callSiteContribTicks = costCentreTicks
, callSiteContribBytes = costCentreBytes
}
buildAggregateModulesOrderBy
:: Ord a
=> (AggregateModule -> a)
-> CostCentreTree
-> [AggregateModule]
buildAggregateModulesOrderBy sortKey CostCentreTree {..} =
sortBy (flip compare `on` sortKey) $
Map.foldrWithKey
(\modName ccs as -> aggregateModule modName ccs : as)
[]
costCentreAggregate
where
aggregateModule modName = Map.foldl' add (emptyAggregateModule modName)
add aggMod AggregatedCostCentre {..} = aggMod
{ aggregateModuleEntries = seqM $ (+)
<$> aggregateModuleEntries aggMod
<*> aggregatedCostCentreEntries
, aggregateModuleTime =
aggregateModuleTime aggMod + aggregatedCostCentreTime
, aggregateModuleAlloc =
aggregateModuleAlloc aggMod + aggregatedCostCentreAlloc
, aggregateModuleTicks = seqM $ (+)
<$> aggregateModuleTicks aggMod
<*> aggregatedCostCentreTicks
, aggregateModuleBytes = seqM $ (+)
<$> aggregateModuleBytes aggMod
<*> aggregatedCostCentreBytes
}
lookupAggregate
:: Text
-> Text
-> Map.Map Text (Map.Map Text AggregatedCostCentre)
-> Maybe AggregatedCostCentre
lookupAggregate name modName m = Map.lookup modName m >>= Map.lookup name