{-# LANGUAGE RecordWildCards #-}
module GHC.Prof.Types where
import Data.Monoid
import Prelude
import Data.IntMap (IntMap)
import Data.Map (Map)
import Data.Scientific (Scientific)
import Data.Set (Set)
import Data.Text (Text)
import Data.Time (DiffTime, LocalTime)
data Profile = Profile
{ profileTimestamp :: !LocalTime
, profileCommandLine :: !Text
, profileTotalTime :: !TotalTime
, profileTotalAlloc :: !TotalAlloc
, profileTopCostCentres :: [AggregatedCostCentre]
, profileCostCentreTree :: !CostCentreTree
} deriving Show
data TotalTime = TotalTime
{ totalTimeElapsed :: !DiffTime
, totalTimeTicks :: !Integer
, totalTimeResolution :: !DiffTime
, totalTimeProcessors :: !(Maybe Int)
} deriving Show
newtype TotalAlloc = TotalAlloc
{ totalAllocBytes :: Integer
} deriving Show
data AggregatedCostCentre = AggregatedCostCentre
{ aggregatedCostCentreName :: !Text
, aggregatedCostCentreModule :: !Text
, aggregatedCostCentreSrc :: !(Maybe Text)
, aggregatedCostCentreEntries :: !(Maybe Integer)
, aggregatedCostCentreTime :: !Scientific
, aggregatedCostCentreAlloc :: !Scientific
, aggregatedCostCentreTicks :: !(Maybe Integer)
, aggregatedCostCentreBytes :: !(Maybe Integer)
} deriving (Show, Eq, Ord)
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)
} deriving (Show, Eq, Ord)
type CostCentreNo = Int
data CostCentreTree = CostCentreTree
{ costCentreNodes :: !(IntMap CostCentre)
, costCentreParents :: !(IntMap CostCentreNo)
, costCentreChildren :: !(IntMap (Set CostCentre))
, costCentreCallSites :: !(Map (Text, Text) (Set CostCentre))
, costCentreAggregate :: !(Map Text (Map Text AggregatedCostCentre))
} deriving Show
emptyCostCentreTree :: CostCentreTree
emptyCostCentreTree = CostCentreTree
{ costCentreNodes = mempty
, costCentreParents = mempty
, costCentreChildren = mempty
, costCentreCallSites = mempty
, costCentreAggregate = mempty
}
data CallSite cc = CallSite
{ callSiteCostCentre :: cc
, callSiteContribEntries :: !Integer
, callSiteContribTime :: !Scientific
, callSiteContribAlloc :: !Scientific
, callSiteContribTicks :: !(Maybe Integer)
, callSiteContribBytes :: !(Maybe Integer)
} deriving Show
data AggregateModule = AggregateModule
{ aggregateModuleName :: !Text
, aggregateModuleEntries :: !(Maybe Integer)
, aggregateModuleTime :: !Scientific
, aggregateModuleAlloc :: !Scientific
, aggregateModuleTicks :: !(Maybe Integer)
, aggregateModuleBytes :: !(Maybe Integer)
} deriving (Show, Eq, Ord)
emptyAggregateModule :: Text -> AggregateModule
emptyAggregateModule name = AggregateModule
{ aggregateModuleName = name
, aggregateModuleEntries = Just 0
, aggregateModuleTime = 0
, aggregateModuleAlloc = 0
, aggregateModuleTicks = Just 0
, aggregateModuleBytes = Just 0
}