{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fsimpl-tick-factor=200 #-}
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 :: Profile -> [AggregatedCostCentre]
aggregatedCostCentres = (AggregatedCostCentre -> (Scientific, Scientific))
-> Profile -> [AggregatedCostCentre]
forall a.
Ord a =>
(AggregatedCostCentre -> a) -> Profile -> [AggregatedCostCentre]
aggregatedCostCentresOrderBy AggregatedCostCentre -> (Scientific, Scientific)
sortKey
where
sortKey :: AggregatedCostCentre -> (Scientific, Scientific)
sortKey = AggregatedCostCentre -> Scientific
aggregatedCostCentreTime (AggregatedCostCentre -> Scientific)
-> (AggregatedCostCentre -> Scientific)
-> AggregatedCostCentre
-> (Scientific, Scientific)
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& AggregatedCostCentre -> Scientific
aggregatedCostCentreAlloc
aggregatedCostCentresOrderBy
:: Ord a
=> (AggregatedCostCentre -> a)
-> Profile
-> [AggregatedCostCentre]
aggregatedCostCentresOrderBy :: forall a.
Ord a =>
(AggregatedCostCentre -> a) -> Profile -> [AggregatedCostCentre]
aggregatedCostCentresOrderBy AggregatedCostCentre -> a
sortKey =
(AggregatedCostCentre -> a)
-> CostCentreTree -> [AggregatedCostCentre]
forall a.
Ord a =>
(AggregatedCostCentre -> a)
-> CostCentreTree -> [AggregatedCostCentre]
buildAggregatedCostCentresOrderBy AggregatedCostCentre -> a
sortKey (CostCentreTree -> [AggregatedCostCentre])
-> (Profile -> CostCentreTree) -> Profile -> [AggregatedCostCentre]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Profile -> CostCentreTree
profileCostCentreTree
costCentres :: Profile -> Maybe (Tree CostCentre)
costCentres :: Profile -> Maybe (Tree CostCentre)
costCentres = (CostCentre
-> (Scientific, (Scientific, (Scientific, Scientific))))
-> Profile -> Maybe (Tree CostCentre)
forall a.
Ord a =>
(CostCentre -> a) -> Profile -> Maybe (Tree CostCentre)
costCentresOrderBy CostCentre -> (Scientific, (Scientific, (Scientific, Scientific)))
sortKey
where
sortKey :: CostCentre -> (Scientific, (Scientific, (Scientific, Scientific)))
sortKey =
CostCentre -> Scientific
costCentreInhTime (CostCentre -> Scientific)
-> (CostCentre -> (Scientific, (Scientific, Scientific)))
-> CostCentre
-> (Scientific, (Scientific, (Scientific, Scientific)))
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& CostCentre -> Scientific
costCentreIndTime (CostCentre -> Scientific)
-> (CostCentre -> (Scientific, Scientific))
-> CostCentre
-> (Scientific, (Scientific, Scientific))
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&&
CostCentre -> Scientific
costCentreInhAlloc (CostCentre -> Scientific)
-> (CostCentre -> Scientific)
-> CostCentre
-> (Scientific, Scientific)
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& CostCentre -> Scientific
costCentreIndAlloc
costCentresOrderBy
:: Ord a
=> (CostCentre -> a)
-> Profile
-> Maybe (Tree CostCentre)
costCentresOrderBy :: forall a.
Ord a =>
(CostCentre -> a) -> Profile -> Maybe (Tree CostCentre)
costCentresOrderBy CostCentre -> a
sortKey =
(CostCentre -> a) -> CostCentreTree -> Maybe (Tree CostCentre)
forall a.
Ord a =>
(CostCentre -> a) -> CostCentreTree -> Maybe (Tree CostCentre)
buildCostCentresOrderBy CostCentre -> a
sortKey (CostCentreTree -> Maybe (Tree CostCentre))
-> (Profile -> CostCentreTree)
-> Profile
-> Maybe (Tree CostCentre)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Profile -> CostCentreTree
profileCostCentreTree
aggregateCallSites
:: Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
aggregateCallSites :: Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
aggregateCallSites = (CallSite AggregatedCostCentre
-> (Scientific, (Scientific, (Scientific, Scientific))))
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
forall a.
Ord a =>
(CallSite AggregatedCostCentre -> a)
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
aggregateCallSitesOrderBy CallSite AggregatedCostCentre
-> (Scientific, (Scientific, (Scientific, Scientific)))
sortKey
where
sortKey :: CallSite AggregatedCostCentre
-> (Scientific, (Scientific, (Scientific, Scientific)))
sortKey = CallSite AggregatedCostCentre -> Scientific
forall cc. CallSite cc -> Scientific
callSiteContribTime (CallSite AggregatedCostCentre -> Scientific)
-> (CallSite AggregatedCostCentre
-> (Scientific, (Scientific, Scientific)))
-> CallSite AggregatedCostCentre
-> (Scientific, (Scientific, (Scientific, Scientific)))
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& CallSite AggregatedCostCentre -> Scientific
forall cc. CallSite cc -> Scientific
callSiteContribAlloc
(CallSite AggregatedCostCentre -> Scientific)
-> (CallSite AggregatedCostCentre -> (Scientific, Scientific))
-> CallSite AggregatedCostCentre
-> (Scientific, (Scientific, Scientific))
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& AggregatedCostCentre -> Scientific
aggregatedCostCentreTime (AggregatedCostCentre -> Scientific)
-> (CallSite AggregatedCostCentre -> AggregatedCostCentre)
-> CallSite AggregatedCostCentre
-> Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CallSite AggregatedCostCentre -> AggregatedCostCentre
forall cc. CallSite cc -> cc
callSiteCostCentre
(CallSite AggregatedCostCentre -> Scientific)
-> (CallSite AggregatedCostCentre -> Scientific)
-> CallSite AggregatedCostCentre
-> (Scientific, Scientific)
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& AggregatedCostCentre -> Scientific
aggregatedCostCentreAlloc (AggregatedCostCentre -> Scientific)
-> (CallSite AggregatedCostCentre -> AggregatedCostCentre)
-> CallSite AggregatedCostCentre
-> Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CallSite AggregatedCostCentre -> AggregatedCostCentre
forall cc. CallSite cc -> cc
callSiteCostCentre
aggregateCallSitesOrderBy
:: Ord a
=> (CallSite AggregatedCostCentre -> a)
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
aggregateCallSitesOrderBy :: forall a.
Ord a =>
(CallSite AggregatedCostCentre -> a)
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
aggregateCallSitesOrderBy CallSite AggregatedCostCentre -> a
sortKey Text
name Text
modName =
(CallSite AggregatedCostCentre -> a)
-> Text
-> Text
-> CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
forall a.
Ord a =>
(CallSite AggregatedCostCentre -> a)
-> Text
-> Text
-> CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
buildAggregateCallSitesOrderBy CallSite AggregatedCostCentre -> a
sortKey Text
name Text
modName (CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre]))
-> (Profile -> CostCentreTree)
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Profile -> CostCentreTree
profileCostCentreTree
callSites
:: Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
callSites :: Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
callSites = (CallSite CostCentre
-> (Scientific, (Scientific, (Scientific, Scientific))))
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
forall a.
Ord a =>
(CallSite CostCentre -> a)
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
callSitesOrderBy CallSite CostCentre
-> (Scientific, (Scientific, (Scientific, Scientific)))
sortKey
where
sortKey :: CallSite CostCentre
-> (Scientific, (Scientific, (Scientific, Scientific)))
sortKey = CallSite CostCentre -> Scientific
forall cc. CallSite cc -> Scientific
callSiteContribTime (CallSite CostCentre -> Scientific)
-> (CallSite CostCentre -> (Scientific, (Scientific, Scientific)))
-> CallSite CostCentre
-> (Scientific, (Scientific, (Scientific, Scientific)))
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& CallSite CostCentre -> Scientific
forall cc. CallSite cc -> Scientific
callSiteContribAlloc
(CallSite CostCentre -> Scientific)
-> (CallSite CostCentre -> (Scientific, Scientific))
-> CallSite CostCentre
-> (Scientific, (Scientific, Scientific))
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& CostCentre -> Scientific
costCentreIndTime (CostCentre -> Scientific)
-> (CallSite CostCentre -> CostCentre)
-> CallSite CostCentre
-> Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CallSite CostCentre -> CostCentre
forall cc. CallSite cc -> cc
callSiteCostCentre
(CallSite CostCentre -> Scientific)
-> (CallSite CostCentre -> Scientific)
-> CallSite CostCentre
-> (Scientific, Scientific)
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& CostCentre -> Scientific
costCentreIndAlloc (CostCentre -> Scientific)
-> (CallSite CostCentre -> CostCentre)
-> CallSite CostCentre
-> Scientific
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CallSite CostCentre -> CostCentre
forall cc. CallSite cc -> cc
callSiteCostCentre
callSitesOrderBy
:: Ord a
=> (CallSite CostCentre -> a)
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
callSitesOrderBy :: forall a.
Ord a =>
(CallSite CostCentre -> a)
-> Text
-> Text
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
callSitesOrderBy CallSite CostCentre -> a
sortKey Text
name Text
modName =
(CallSite CostCentre -> a)
-> Text
-> Text
-> CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
forall a.
Ord a =>
(CallSite CostCentre -> a)
-> Text
-> Text
-> CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
buildCallSitesOrderBy CallSite CostCentre -> a
sortKey Text
name Text
modName (CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite CostCentre]))
-> (Profile -> CostCentreTree)
-> Profile
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Profile -> CostCentreTree
profileCostCentreTree
aggregateModules
:: Profile
-> [AggregateModule]
aggregateModules :: Profile -> [AggregateModule]
aggregateModules = (AggregateModule -> (Scientific, Scientific))
-> Profile -> [AggregateModule]
forall a.
Ord a =>
(AggregateModule -> a) -> Profile -> [AggregateModule]
aggregateModulesOrderBy AggregateModule -> (Scientific, Scientific)
sortKey
where
sortKey :: AggregateModule -> (Scientific, Scientific)
sortKey = AggregateModule -> Scientific
aggregateModuleTime (AggregateModule -> Scientific)
-> (AggregateModule -> Scientific)
-> AggregateModule
-> (Scientific, Scientific)
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& AggregateModule -> Scientific
aggregateModuleAlloc
aggregateModulesOrderBy
:: Ord a
=> (AggregateModule -> a)
-> Profile
-> [AggregateModule]
aggregateModulesOrderBy :: forall a.
Ord a =>
(AggregateModule -> a) -> Profile -> [AggregateModule]
aggregateModulesOrderBy AggregateModule -> a
sortKey =
(AggregateModule -> a) -> CostCentreTree -> [AggregateModule]
forall a.
Ord a =>
(AggregateModule -> a) -> CostCentreTree -> [AggregateModule]
buildAggregateModulesOrderBy AggregateModule -> a
sortKey (CostCentreTree -> [AggregateModule])
-> (Profile -> CostCentreTree) -> Profile -> [AggregateModule]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Profile -> CostCentreTree
profileCostCentreTree
buildAggregatedCostCentresOrderBy
:: Ord a
=> (AggregatedCostCentre -> a)
-> CostCentreTree
-> [AggregatedCostCentre]
buildAggregatedCostCentresOrderBy :: forall a.
Ord a =>
(AggregatedCostCentre -> a)
-> CostCentreTree -> [AggregatedCostCentre]
buildAggregatedCostCentresOrderBy AggregatedCostCentre -> a
sortKey CostCentreTree {Map (Text, Text) (Set CostCentre)
Map Text (Map Text AggregatedCostCentre)
IntMap CostCentreNo
IntMap (Set CostCentre)
IntMap CostCentre
costCentreNodes :: IntMap CostCentre
costCentreParents :: IntMap CostCentreNo
costCentreChildren :: IntMap (Set CostCentre)
costCentreCallSites :: Map (Text, Text) (Set CostCentre)
costCentreAggregate :: Map Text (Map Text AggregatedCostCentre)
costCentreNodes :: CostCentreTree -> IntMap CostCentre
costCentreParents :: CostCentreTree -> IntMap CostCentreNo
costCentreChildren :: CostCentreTree -> IntMap (Set CostCentre)
costCentreCallSites :: CostCentreTree -> Map (Text, Text) (Set CostCentre)
costCentreAggregate :: CostCentreTree -> Map Text (Map Text AggregatedCostCentre)
..} =
(AggregatedCostCentre -> AggregatedCostCentre -> Ordering)
-> [AggregatedCostCentre] -> [AggregatedCostCentre]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((a -> a -> Ordering) -> a -> a -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (a -> a -> Ordering)
-> (AggregatedCostCentre -> a)
-> AggregatedCostCentre
-> AggregatedCostCentre
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` AggregatedCostCentre -> a
sortKey) ([AggregatedCostCentre] -> [AggregatedCostCentre])
-> [AggregatedCostCentre] -> [AggregatedCostCentre]
forall a b. (a -> b) -> a -> b
$
(Map Text AggregatedCostCentre -> [AggregatedCostCentre])
-> [Map Text AggregatedCostCentre] -> [AggregatedCostCentre]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Map Text AggregatedCostCentre -> [AggregatedCostCentre]
forall k a. Map k a -> [a]
Map.elems ([Map Text AggregatedCostCentre] -> [AggregatedCostCentre])
-> [Map Text AggregatedCostCentre] -> [AggregatedCostCentre]
forall a b. (a -> b) -> a -> b
$ Map Text (Map Text AggregatedCostCentre)
-> [Map Text AggregatedCostCentre]
forall k a. Map k a -> [a]
Map.elems (Map Text (Map Text AggregatedCostCentre)
-> [Map Text AggregatedCostCentre])
-> Map Text (Map Text AggregatedCostCentre)
-> [Map Text AggregatedCostCentre]
forall a b. (a -> b) -> a -> b
$ Map Text (Map Text AggregatedCostCentre)
costCentreAggregate
buildCostCentresOrderBy
:: Ord a
=> (CostCentre -> a)
-> CostCentreTree
-> Maybe (Tree CostCentre)
buildCostCentresOrderBy :: forall a.
Ord a =>
(CostCentre -> a) -> CostCentreTree -> Maybe (Tree CostCentre)
buildCostCentresOrderBy CostCentre -> a
sortKey CostCentreTree {Map (Text, Text) (Set CostCentre)
Map Text (Map Text AggregatedCostCentre)
IntMap CostCentreNo
IntMap (Set CostCentre)
IntMap CostCentre
costCentreNodes :: CostCentreTree -> IntMap CostCentre
costCentreParents :: CostCentreTree -> IntMap CostCentreNo
costCentreChildren :: CostCentreTree -> IntMap (Set CostCentre)
costCentreCallSites :: CostCentreTree -> Map (Text, Text) (Set CostCentre)
costCentreAggregate :: CostCentreTree -> Map Text (Map Text AggregatedCostCentre)
costCentreNodes :: IntMap CostCentre
costCentreParents :: IntMap CostCentreNo
costCentreChildren :: IntMap (Set CostCentre)
costCentreCallSites :: Map (Text, Text) (Set CostCentre)
costCentreAggregate :: Map Text (Map Text AggregatedCostCentre)
..} = do
CostCentreNo
rootKey <- [CostCentreNo] -> Maybe CostCentreNo
forall a. [a] -> Maybe a
listToMaybe ([CostCentreNo] -> Maybe CostCentreNo)
-> [CostCentreNo] -> Maybe CostCentreNo
forall a b. (a -> b) -> a -> b
$ IntMap CostCentre -> [CostCentreNo]
forall a. IntMap a -> [CostCentreNo]
IntMap.keys IntMap CostCentre
costCentreNodes
(CostCentreNo -> Maybe (CostCentre, [CostCentreNo]))
-> CostCentreNo -> Maybe (Tree CostCentre)
forall (m :: * -> *) b a.
Monad m =>
(b -> m (a, [b])) -> b -> m (Tree a)
Tree.unfoldTreeM CostCentreNo -> Maybe (CostCentre, [CostCentreNo])
build CostCentreNo
rootKey
where
build :: CostCentreNo -> Maybe (CostCentre, [CostCentreNo])
build CostCentreNo
key = do
CostCentre
node <- CostCentreNo -> IntMap CostCentre -> Maybe CostCentre
forall a. CostCentreNo -> IntMap a -> Maybe a
IntMap.lookup CostCentreNo
key IntMap CostCentre
costCentreNodes
(CostCentre, [CostCentreNo]) -> Maybe (CostCentre, [CostCentreNo])
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (CostCentre
node, [CostCentreNo]
children)
where
!children :: [CostCentreNo]
children = [CostCentreNo]
-> ([CostCentreNo] -> [CostCentreNo])
-> Maybe [CostCentreNo]
-> [CostCentreNo]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] [CostCentreNo] -> [CostCentreNo]
forall a. [a] -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Fold.toList (Maybe [CostCentreNo] -> [CostCentreNo])
-> Maybe [CostCentreNo] -> [CostCentreNo]
forall a b. (a -> b) -> a -> b
$ do
Set CostCentre
nodes <- CostCentreNo -> IntMap (Set CostCentre) -> Maybe (Set CostCentre)
forall a. CostCentreNo -> IntMap a -> Maybe a
IntMap.lookup CostCentreNo
key IntMap (Set CostCentre)
costCentreChildren
[CostCentreNo] -> Maybe [CostCentreNo]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return ([CostCentreNo] -> Maybe [CostCentreNo])
-> [CostCentreNo] -> Maybe [CostCentreNo]
forall a b. (a -> b) -> a -> b
$ CostCentre -> CostCentreNo
costCentreNo
(CostCentre -> CostCentreNo) -> [CostCentre] -> [CostCentreNo]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CostCentre -> CostCentre -> Ordering)
-> [CostCentre] -> [CostCentre]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((a -> a -> Ordering) -> a -> a -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (a -> a -> Ordering)
-> (CostCentre -> a) -> CostCentre -> CostCentre -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` CostCentre -> a
sortKey) (Set CostCentre -> [CostCentre]
forall a. Set a -> [a]
Set.toList Set CostCentre
nodes)
buildAggregateCallSitesOrderBy
:: Ord a
=> (CallSite AggregatedCostCentre -> a)
-> Text
-> Text
-> CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
buildAggregateCallSitesOrderBy :: forall a.
Ord a =>
(CallSite AggregatedCostCentre -> a)
-> Text
-> Text
-> CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
buildAggregateCallSitesOrderBy CallSite AggregatedCostCentre -> a
sortKey Text
name Text
modName tree :: CostCentreTree
tree@CostCentreTree {Map (Text, Text) (Set CostCentre)
Map Text (Map Text AggregatedCostCentre)
IntMap CostCentreNo
IntMap (Set CostCentre)
IntMap CostCentre
costCentreNodes :: CostCentreTree -> IntMap CostCentre
costCentreParents :: CostCentreTree -> IntMap CostCentreNo
costCentreChildren :: CostCentreTree -> IntMap (Set CostCentre)
costCentreCallSites :: CostCentreTree -> Map (Text, Text) (Set CostCentre)
costCentreAggregate :: CostCentreTree -> Map Text (Map Text AggregatedCostCentre)
costCentreNodes :: IntMap CostCentre
costCentreParents :: IntMap CostCentreNo
costCentreChildren :: IntMap (Set CostCentre)
costCentreCallSites :: Map (Text, Text) (Set CostCentre)
costCentreAggregate :: Map Text (Map Text AggregatedCostCentre)
..} =
(,) (AggregatedCostCentre
-> [CallSite AggregatedCostCentre]
-> (AggregatedCostCentre, [CallSite AggregatedCostCentre]))
-> Maybe AggregatedCostCentre
-> Maybe
([CallSite AggregatedCostCentre]
-> (AggregatedCostCentre, [CallSite AggregatedCostCentre]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AggregatedCostCentre
callee Maybe
([CallSite AggregatedCostCentre]
-> (AggregatedCostCentre, [CallSite AggregatedCostCentre]))
-> Maybe [CallSite AggregatedCostCentre]
-> Maybe (AggregatedCostCentre, [CallSite AggregatedCostCentre])
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe [CallSite AggregatedCostCentre]
callers
where
callee :: Maybe AggregatedCostCentre
callee = Text
-> Text
-> Map Text (Map Text AggregatedCostCentre)
-> Maybe AggregatedCostCentre
lookupAggregate Text
name Text
modName Map Text (Map Text AggregatedCostCentre)
costCentreAggregate
callers :: Maybe [CallSite AggregatedCostCentre]
callers = do
Set CostCentre
callees <- (Text, Text)
-> Map (Text, Text) (Set CostCentre) -> Maybe (Set CostCentre)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Text
name, Text
modName) Map (Text, Text) (Set CostCentre)
costCentreCallSites
(CallSite AggregatedCostCentre
-> CallSite AggregatedCostCentre -> Ordering)
-> [CallSite AggregatedCostCentre]
-> [CallSite AggregatedCostCentre]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((a -> a -> Ordering) -> a -> a -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (a -> a -> Ordering)
-> (CallSite AggregatedCostCentre -> a)
-> CallSite AggregatedCostCentre
-> CallSite AggregatedCostCentre
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` CallSite AggregatedCostCentre -> a
sortKey) ([CallSite AggregatedCostCentre]
-> [CallSite AggregatedCostCentre])
-> (Map (Text, Text) (CallSite AggregatedCostCentre)
-> [CallSite AggregatedCostCentre])
-> Map (Text, Text) (CallSite AggregatedCostCentre)
-> [CallSite AggregatedCostCentre]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map (Text, Text) (CallSite AggregatedCostCentre)
-> [CallSite AggregatedCostCentre]
forall k a. Map k a -> [a]
Map.elems
(Map (Text, Text) (CallSite AggregatedCostCentre)
-> [CallSite AggregatedCostCentre])
-> Maybe (Map (Text, Text) (CallSite AggregatedCostCentre))
-> Maybe [CallSite AggregatedCostCentre]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Map (Text, Text) (CallSite AggregatedCostCentre)
-> CostCentre
-> Maybe (Map (Text, Text) (CallSite AggregatedCostCentre)))
-> Map (Text, Text) (CallSite AggregatedCostCentre)
-> [CostCentre]
-> Maybe (Map (Text, Text) (CallSite AggregatedCostCentre))
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (CostCentreTree
-> Map (Text, Text) (CallSite AggregatedCostCentre)
-> CostCentre
-> Maybe (Map (Text, Text) (CallSite AggregatedCostCentre))
buildAggregateCallSite CostCentreTree
tree) Map (Text, Text) (CallSite AggregatedCostCentre)
forall k a. Map k a
Map.empty (Set CostCentre -> [CostCentre]
forall a. Set a -> [a]
Set.toList Set CostCentre
callees)
buildAggregateCallSite
:: CostCentreTree
-> Map.Map (Text, Text) (CallSite AggregatedCostCentre)
-> CostCentre
-> Maybe (Map.Map (Text, Text) (CallSite AggregatedCostCentre))
buildAggregateCallSite :: CostCentreTree
-> Map (Text, Text) (CallSite AggregatedCostCentre)
-> CostCentre
-> Maybe (Map (Text, Text) (CallSite AggregatedCostCentre))
buildAggregateCallSite CostCentreTree {Map (Text, Text) (Set CostCentre)
Map Text (Map Text AggregatedCostCentre)
IntMap CostCentreNo
IntMap (Set CostCentre)
IntMap CostCentre
costCentreNodes :: CostCentreTree -> IntMap CostCentre
costCentreParents :: CostCentreTree -> IntMap CostCentreNo
costCentreChildren :: CostCentreTree -> IntMap (Set CostCentre)
costCentreCallSites :: CostCentreTree -> Map (Text, Text) (Set CostCentre)
costCentreAggregate :: CostCentreTree -> Map Text (Map Text AggregatedCostCentre)
costCentreNodes :: IntMap CostCentre
costCentreParents :: IntMap CostCentreNo
costCentreChildren :: IntMap (Set CostCentre)
costCentreCallSites :: Map (Text, Text) (Set CostCentre)
costCentreAggregate :: Map Text (Map Text AggregatedCostCentre)
..} Map (Text, Text) (CallSite AggregatedCostCentre)
parents CostCentre {CostCentreNo
Integer
Maybe Integer
Maybe Text
Text
Scientific
costCentreInhTime :: CostCentre -> Scientific
costCentreIndTime :: CostCentre -> Scientific
costCentreInhAlloc :: CostCentre -> Scientific
costCentreIndAlloc :: CostCentre -> Scientific
costCentreNo :: CostCentre -> CostCentreNo
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
costCentreName :: CostCentre -> Text
costCentreModule :: CostCentre -> Text
costCentreSrc :: CostCentre -> Maybe Text
costCentreEntries :: CostCentre -> Integer
costCentreTicks :: CostCentre -> Maybe Integer
costCentreBytes :: CostCentre -> Maybe Integer
..} = do
CostCentreNo
parentNo <- CostCentreNo -> IntMap CostCentreNo -> Maybe CostCentreNo
forall a. CostCentreNo -> IntMap a -> Maybe a
IntMap.lookup CostCentreNo
costCentreNo IntMap CostCentreNo
costCentreParents
CostCentre
parent <- CostCentreNo -> IntMap CostCentre -> Maybe CostCentre
forall a. CostCentreNo -> IntMap a -> Maybe a
IntMap.lookup CostCentreNo
parentNo IntMap CostCentre
costCentreNodes
let parentName :: Text
parentName = CostCentre -> Text
Types.costCentreName CostCentre
parent
parentModule :: Text
parentModule = CostCentre -> Text
Types.costCentreModule CostCentre
parent
AggregatedCostCentre
aggregate <- Text
-> Text
-> Map Text (Map Text AggregatedCostCentre)
-> Maybe AggregatedCostCentre
lookupAggregate Text
parentName Text
parentModule Map Text (Map Text AggregatedCostCentre)
costCentreAggregate
Map (Text, Text) (CallSite AggregatedCostCentre)
-> Maybe (Map (Text, Text) (CallSite AggregatedCostCentre))
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (Map (Text, Text) (CallSite AggregatedCostCentre)
-> Maybe (Map (Text, Text) (CallSite AggregatedCostCentre)))
-> Map (Text, Text) (CallSite AggregatedCostCentre)
-> Maybe (Map (Text, Text) (CallSite AggregatedCostCentre))
forall a b. (a -> b) -> a -> b
$! (CallSite AggregatedCostCentre
-> CallSite AggregatedCostCentre -> CallSite AggregatedCostCentre)
-> (Text, Text)
-> CallSite AggregatedCostCentre
-> Map (Text, Text) (CallSite AggregatedCostCentre)
-> Map (Text, Text) (CallSite AggregatedCostCentre)
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith
CallSite AggregatedCostCentre
-> CallSite AggregatedCostCentre -> CallSite AggregatedCostCentre
forall a. CallSite a -> CallSite a -> CallSite a
mergeCallSites
(Text
parentName, Text
parentModule)
CallSite
{ callSiteCostCentre :: AggregatedCostCentre
callSiteCostCentre = AggregatedCostCentre
aggregate
, callSiteContribEntries :: Integer
callSiteContribEntries = Integer
costCentreEntries
, callSiteContribTime :: Scientific
callSiteContribTime = Scientific
costCentreIndTime
, callSiteContribAlloc :: Scientific
callSiteContribAlloc = Scientific
costCentreIndAlloc
, callSiteContribTicks :: Maybe Integer
callSiteContribTicks = Maybe Integer
costCentreTicks
, callSiteContribBytes :: Maybe Integer
callSiteContribBytes = Maybe Integer
costCentreBytes
}
Map (Text, Text) (CallSite AggregatedCostCentre)
parents
mergeCallSites :: CallSite a -> CallSite a -> CallSite a
mergeCallSites :: forall a. CallSite a -> CallSite a -> CallSite a
mergeCallSites CallSite a
a CallSite a
b = CallSite a
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 :: forall a.
Ord a =>
(CallSite CostCentre -> a)
-> Text
-> Text
-> CostCentreTree
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
buildCallSitesOrderBy CallSite CostCentre -> a
sortKey Text
name Text
modName tree :: CostCentreTree
tree@CostCentreTree {Map (Text, Text) (Set CostCentre)
Map Text (Map Text AggregatedCostCentre)
IntMap CostCentreNo
IntMap (Set CostCentre)
IntMap CostCentre
costCentreNodes :: CostCentreTree -> IntMap CostCentre
costCentreParents :: CostCentreTree -> IntMap CostCentreNo
costCentreChildren :: CostCentreTree -> IntMap (Set CostCentre)
costCentreCallSites :: CostCentreTree -> Map (Text, Text) (Set CostCentre)
costCentreAggregate :: CostCentreTree -> Map Text (Map Text AggregatedCostCentre)
costCentreNodes :: IntMap CostCentre
costCentreParents :: IntMap CostCentreNo
costCentreChildren :: IntMap (Set CostCentre)
costCentreCallSites :: Map (Text, Text) (Set CostCentre)
costCentreAggregate :: Map Text (Map Text AggregatedCostCentre)
..} =
(,) (AggregatedCostCentre
-> [CallSite CostCentre]
-> (AggregatedCostCentre, [CallSite CostCentre]))
-> Maybe AggregatedCostCentre
-> Maybe
([CallSite CostCentre]
-> (AggregatedCostCentre, [CallSite CostCentre]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AggregatedCostCentre
callee Maybe
([CallSite CostCentre]
-> (AggregatedCostCentre, [CallSite CostCentre]))
-> Maybe [CallSite CostCentre]
-> Maybe (AggregatedCostCentre, [CallSite CostCentre])
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe [CallSite CostCentre]
callers
where
callee :: Maybe AggregatedCostCentre
callee = Text
-> Text
-> Map Text (Map Text AggregatedCostCentre)
-> Maybe AggregatedCostCentre
lookupAggregate Text
name Text
modName Map Text (Map Text AggregatedCostCentre)
costCentreAggregate
callers :: Maybe [CallSite CostCentre]
callers = do
Set CostCentre
callees <- (Text, Text)
-> Map (Text, Text) (Set CostCentre) -> Maybe (Set CostCentre)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (Text
name, Text
modName) Map (Text, Text) (Set CostCentre)
costCentreCallSites
(CallSite CostCentre -> CallSite CostCentre -> Ordering)
-> [CallSite CostCentre] -> [CallSite CostCentre]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((a -> a -> Ordering) -> a -> a -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (a -> a -> Ordering)
-> (CallSite CostCentre -> a)
-> CallSite CostCentre
-> CallSite CostCentre
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` CallSite CostCentre -> a
sortKey)
([CallSite CostCentre] -> [CallSite CostCentre])
-> Maybe [CallSite CostCentre] -> Maybe [CallSite CostCentre]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CostCentre -> Maybe (CallSite CostCentre))
-> [CostCentre] -> Maybe [CallSite CostCentre]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (CostCentreTree -> CostCentre -> Maybe (CallSite CostCentre)
buildCallSite CostCentreTree
tree) (Set CostCentre -> [CostCentre]
forall a. Set a -> [a]
Set.toList Set CostCentre
callees)
buildCallSite
:: CostCentreTree
-> CostCentre
-> Maybe (CallSite CostCentre)
buildCallSite :: CostCentreTree -> CostCentre -> Maybe (CallSite CostCentre)
buildCallSite CostCentreTree {Map (Text, Text) (Set CostCentre)
Map Text (Map Text AggregatedCostCentre)
IntMap CostCentreNo
IntMap (Set CostCentre)
IntMap CostCentre
costCentreNodes :: CostCentreTree -> IntMap CostCentre
costCentreParents :: CostCentreTree -> IntMap CostCentreNo
costCentreChildren :: CostCentreTree -> IntMap (Set CostCentre)
costCentreCallSites :: CostCentreTree -> Map (Text, Text) (Set CostCentre)
costCentreAggregate :: CostCentreTree -> Map Text (Map Text AggregatedCostCentre)
costCentreNodes :: IntMap CostCentre
costCentreParents :: IntMap CostCentreNo
costCentreChildren :: IntMap (Set CostCentre)
costCentreCallSites :: Map (Text, Text) (Set CostCentre)
costCentreAggregate :: Map Text (Map Text AggregatedCostCentre)
..} CostCentre {CostCentreNo
Integer
Maybe Integer
Maybe Text
Text
Scientific
costCentreInhTime :: CostCentre -> Scientific
costCentreIndTime :: CostCentre -> Scientific
costCentreInhAlloc :: CostCentre -> Scientific
costCentreIndAlloc :: CostCentre -> Scientific
costCentreNo :: CostCentre -> CostCentreNo
costCentreName :: CostCentre -> Text
costCentreModule :: CostCentre -> Text
costCentreSrc :: CostCentre -> Maybe Text
costCentreEntries :: CostCentre -> Integer
costCentreTicks :: CostCentre -> Maybe Integer
costCentreBytes :: CostCentre -> Maybe Integer
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
..} = do
CostCentreNo
parentNo <- CostCentreNo -> IntMap CostCentreNo -> Maybe CostCentreNo
forall a. CostCentreNo -> IntMap a -> Maybe a
IntMap.lookup CostCentreNo
costCentreNo IntMap CostCentreNo
costCentreParents
CostCentre
parent <- CostCentreNo -> IntMap CostCentre -> Maybe CostCentre
forall a. CostCentreNo -> IntMap a -> Maybe a
IntMap.lookup CostCentreNo
parentNo IntMap CostCentre
costCentreNodes
CallSite CostCentre -> Maybe (CallSite CostCentre)
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return CallSite
{ callSiteCostCentre :: CostCentre
callSiteCostCentre = CostCentre
parent
, callSiteContribEntries :: Integer
callSiteContribEntries = Integer
costCentreEntries
, callSiteContribTime :: Scientific
callSiteContribTime = Scientific
costCentreIndTime
, callSiteContribAlloc :: Scientific
callSiteContribAlloc = Scientific
costCentreIndAlloc
, callSiteContribTicks :: Maybe Integer
callSiteContribTicks = Maybe Integer
costCentreTicks
, callSiteContribBytes :: Maybe Integer
callSiteContribBytes = Maybe Integer
costCentreBytes
}
buildAggregateModulesOrderBy
:: Ord a
=> (AggregateModule -> a)
-> CostCentreTree
-> [AggregateModule]
buildAggregateModulesOrderBy :: forall a.
Ord a =>
(AggregateModule -> a) -> CostCentreTree -> [AggregateModule]
buildAggregateModulesOrderBy AggregateModule -> a
sortKey CostCentreTree {Map (Text, Text) (Set CostCentre)
Map Text (Map Text AggregatedCostCentre)
IntMap CostCentreNo
IntMap (Set CostCentre)
IntMap CostCentre
costCentreNodes :: CostCentreTree -> IntMap CostCentre
costCentreParents :: CostCentreTree -> IntMap CostCentreNo
costCentreChildren :: CostCentreTree -> IntMap (Set CostCentre)
costCentreCallSites :: CostCentreTree -> Map (Text, Text) (Set CostCentre)
costCentreAggregate :: CostCentreTree -> Map Text (Map Text AggregatedCostCentre)
costCentreNodes :: IntMap CostCentre
costCentreParents :: IntMap CostCentreNo
costCentreChildren :: IntMap (Set CostCentre)
costCentreCallSites :: Map (Text, Text) (Set CostCentre)
costCentreAggregate :: Map Text (Map Text AggregatedCostCentre)
..} =
(AggregateModule -> AggregateModule -> Ordering)
-> [AggregateModule] -> [AggregateModule]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((a -> a -> Ordering) -> a -> a -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (a -> a -> Ordering)
-> (AggregateModule -> a)
-> AggregateModule
-> AggregateModule
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` AggregateModule -> a
sortKey) ([AggregateModule] -> [AggregateModule])
-> [AggregateModule] -> [AggregateModule]
forall a b. (a -> b) -> a -> b
$
(Text
-> Map Text AggregatedCostCentre
-> [AggregateModule]
-> [AggregateModule])
-> [AggregateModule]
-> Map Text (Map Text AggregatedCostCentre)
-> [AggregateModule]
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey
(\Text
modName Map Text AggregatedCostCentre
ccs [AggregateModule]
as -> Text -> Map Text AggregatedCostCentre -> AggregateModule
forall {k}. Text -> Map k AggregatedCostCentre -> AggregateModule
aggregateModule Text
modName Map Text AggregatedCostCentre
ccs AggregateModule -> [AggregateModule] -> [AggregateModule]
forall a. a -> [a] -> [a]
: [AggregateModule]
as)
[]
Map Text (Map Text AggregatedCostCentre)
costCentreAggregate
where
aggregateModule :: Text -> Map k AggregatedCostCentre -> AggregateModule
aggregateModule Text
modName = (AggregateModule -> AggregatedCostCentre -> AggregateModule)
-> AggregateModule -> Map k AggregatedCostCentre -> AggregateModule
forall a b k. (a -> b -> a) -> a -> Map k b -> a
Map.foldl' AggregateModule -> AggregatedCostCentre -> AggregateModule
add (Text -> AggregateModule
emptyAggregateModule Text
modName)
add :: AggregateModule -> AggregatedCostCentre -> AggregateModule
add AggregateModule
aggMod AggregatedCostCentre {Maybe Integer
Maybe Text
Text
Scientific
aggregatedCostCentreTime :: AggregatedCostCentre -> Scientific
aggregatedCostCentreAlloc :: AggregatedCostCentre -> Scientific
aggregatedCostCentreName :: Text
aggregatedCostCentreModule :: Text
aggregatedCostCentreSrc :: Maybe Text
aggregatedCostCentreEntries :: Maybe Integer
aggregatedCostCentreTime :: Scientific
aggregatedCostCentreAlloc :: Scientific
aggregatedCostCentreTicks :: Maybe Integer
aggregatedCostCentreBytes :: Maybe Integer
aggregatedCostCentreName :: AggregatedCostCentre -> Text
aggregatedCostCentreModule :: AggregatedCostCentre -> Text
aggregatedCostCentreSrc :: AggregatedCostCentre -> Maybe Text
aggregatedCostCentreEntries :: AggregatedCostCentre -> Maybe Integer
aggregatedCostCentreTicks :: AggregatedCostCentre -> Maybe Integer
aggregatedCostCentreBytes :: AggregatedCostCentre -> Maybe Integer
..} = AggregateModule
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 :: Text
-> Text
-> Map Text (Map Text AggregatedCostCentre)
-> Maybe AggregatedCostCentre
lookupAggregate Text
name Text
modName Map Text (Map Text AggregatedCostCentre)
m = Text
-> Map Text (Map Text AggregatedCostCentre)
-> Maybe (Map Text AggregatedCostCentre)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
modName Map Text (Map Text AggregatedCostCentre)
m Maybe (Map Text AggregatedCostCentre)
-> (Map Text AggregatedCostCentre -> Maybe AggregatedCostCentre)
-> Maybe AggregatedCostCentre
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Map Text AggregatedCostCentre -> Maybe AggregatedCostCentre
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
name