| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Eventlog.Types
Synopsis
- data InfoTableLocStatus
- = None
- | Missing
- | Here InfoTableLoc
- data InfoTablePtr = InfoTablePtr Word64
- data InfoTableLoc = InfoTableLoc {}
- data TickySample = TickySample {}
- data TickyCounter = TickyCounter {}
- data TickyCounterArgs = TickyCounterArgs {
- tickyCounterType :: Text
- tickyCounterFVs :: [Char]
- tickyCounterArgs :: [Char]
- newtype TickyCounterId = TickyCounterId Word64
- data ProfData = ProfData {
- profHeader :: Header
- profTotals :: Map Bucket BucketInfo
- profCCMap :: Map Word32 CostCentre
- profFrames :: [Frame]
- profTraces :: [Trace]
- profHeap :: HeapInfo
- profItl :: Map InfoTablePtr InfoTableLoc
- profTickyCounters :: Map TickyCounterId TickyCounter
- profTickySamples :: [TickySample]
- profTotalAllocations :: Word64
- data HeapInfo = HeapInfo {}
- data Trace = Trace Double Text
- data Frame = Frame Double [Sample]
- data HeapSample = HeapSample Double Word64
- data Sample = Sample Bucket Double
- data CostCentre = CC {}
- data BucketInfo = BucketInfo {
- shortDescription :: Text
- longDescription :: Maybe [Word32]
- bucketTotal :: Double
- bucketStddev :: Double
- bucketGradient :: !(Maybe (Double, Double, Double))
- newtype Bucket = Bucket Text
- data Header = Header {
- hJob :: Text
- hDate :: Text
- hHeapProfileType :: Maybe HeapProfBreakdown
- hSamplingRate :: Text
- hSampleUnit :: Text
- hValueUnit :: Text
- hCount :: Int
- hProgPath :: Maybe FilePath
- toItblPointer :: Bucket -> InfoTablePtr
- mkMissing :: Maybe InfoTableLoc -> InfoTableLocStatus
- mkClosureInfo :: (k -> a -> InfoTablePtr) -> Map k a -> Map InfoTablePtr InfoTableLoc -> Map k (InfoTableLocStatus, a)
- data HeapProfBreakdown
- data ClosureType
Documentation
data InfoTableLocStatus Source #
Constructors
| None | |
| Missing | |
| Here InfoTableLoc |
data InfoTablePtr Source #
Constructors
| InfoTablePtr Word64 |
Instances
| Show InfoTablePtr Source # | |
Defined in Eventlog.Types Methods showsPrec :: Int -> InfoTablePtr -> ShowS # show :: InfoTablePtr -> String # showList :: [InfoTablePtr] -> ShowS # | |
| Eq InfoTablePtr Source # | |
Defined in Eventlog.Types | |
| Ord InfoTablePtr Source # | |
Defined in Eventlog.Types Methods compare :: InfoTablePtr -> InfoTablePtr -> Ordering # (<) :: InfoTablePtr -> InfoTablePtr -> Bool # (<=) :: InfoTablePtr -> InfoTablePtr -> Bool # (>) :: InfoTablePtr -> InfoTablePtr -> Bool # (>=) :: InfoTablePtr -> InfoTablePtr -> Bool # max :: InfoTablePtr -> InfoTablePtr -> InfoTablePtr # min :: InfoTablePtr -> InfoTablePtr -> InfoTablePtr # | |
data InfoTableLoc Source #
Constructors
| InfoTableLoc | |
Instances
| Show InfoTableLoc Source # | |
Defined in Eventlog.Types Methods showsPrec :: Int -> InfoTableLoc -> ShowS # show :: InfoTableLoc -> String # showList :: [InfoTableLoc] -> ShowS # | |
data TickySample Source #
Constructors
| TickySample | |
Instances
| Show TickySample Source # | |
Defined in Eventlog.Types Methods showsPrec :: Int -> TickySample -> ShowS # show :: TickySample -> String # showList :: [TickySample] -> ShowS # | |
data TickyCounter Source #
Constructors
| TickyCounter | |
Fields | |
Instances
| Show TickyCounter Source # | |
Defined in Eventlog.Types Methods showsPrec :: Int -> TickyCounter -> ShowS # show :: TickyCounter -> String # showList :: [TickyCounter] -> ShowS # | |
data TickyCounterArgs Source #
Constructors
| TickyCounterArgs | |
Fields
| |
Instances
| FromJSON TickyCounterArgs Source # | |
Defined in Eventlog.Types Methods parseJSON :: Value -> Parser TickyCounterArgs # parseJSONList :: Value -> Parser [TickyCounterArgs] # | |
| Show TickyCounterArgs Source # | |
Defined in Eventlog.Types Methods showsPrec :: Int -> TickyCounterArgs -> ShowS # show :: TickyCounterArgs -> String # showList :: [TickyCounterArgs] -> ShowS # | |
newtype TickyCounterId Source #
Constructors
| TickyCounterId Word64 |
Instances
| Show TickyCounterId Source # | |
Defined in Eventlog.Types Methods showsPrec :: Int -> TickyCounterId -> ShowS # show :: TickyCounterId -> String # showList :: [TickyCounterId] -> ShowS # | |
| Eq TickyCounterId Source # | |
Defined in Eventlog.Types Methods (==) :: TickyCounterId -> TickyCounterId -> Bool # (/=) :: TickyCounterId -> TickyCounterId -> Bool # | |
| Ord TickyCounterId Source # | |
Defined in Eventlog.Types Methods compare :: TickyCounterId -> TickyCounterId -> Ordering # (<) :: TickyCounterId -> TickyCounterId -> Bool # (<=) :: TickyCounterId -> TickyCounterId -> Bool # (>) :: TickyCounterId -> TickyCounterId -> Bool # (>=) :: TickyCounterId -> TickyCounterId -> Bool # max :: TickyCounterId -> TickyCounterId -> TickyCounterId # min :: TickyCounterId -> TickyCounterId -> TickyCounterId # | |
Constructors
| ProfData | |
Fields
| |
Constructors
| HeapInfo | |
Fields
| |
A trace we also want to show on the graph
data HeapSample Source #
Constructors
| HeapSample Double Word64 |
Instances
| Show HeapSample Source # | |
Defined in Eventlog.Types Methods showsPrec :: Int -> HeapSample -> ShowS # show :: HeapSample -> String # showList :: [HeapSample] -> ShowS # | |
data CostCentre Source #
Instances
| Show CostCentre Source # | |
Defined in Eventlog.Types Methods showsPrec :: Int -> CostCentre -> ShowS # show :: CostCentre -> String # showList :: [CostCentre] -> ShowS # | |
data BucketInfo Source #
Constructors
| BucketInfo | |
Fields
| |
Instances
| Show BucketInfo Source # | |
Defined in Eventlog.Types Methods showsPrec :: Int -> BucketInfo -> ShowS # show :: BucketInfo -> String # showList :: [BucketInfo] -> ShowS # | |
Constructors
| Header | |
Fields
| |
toItblPointer :: Bucket -> InfoTablePtr Source #
mkClosureInfo :: (k -> a -> InfoTablePtr) -> Map k a -> Map InfoTablePtr InfoTableLoc -> Map k (InfoTableLocStatus, a) Source #
data HeapProfBreakdown #
Sample break-down types in heap profiling
Constructors
Instances
| Show HeapProfBreakdown | |
Defined in GHC.RTS.EventTypes Methods showsPrec :: Int -> HeapProfBreakdown -> ShowS # show :: HeapProfBreakdown -> String # showList :: [HeapProfBreakdown] -> ShowS # | |
| Binary HeapProfBreakdown | |
Defined in GHC.RTS.EventTypes Methods put :: HeapProfBreakdown -> Put # get :: Get HeapProfBreakdown # putList :: [HeapProfBreakdown] -> Put # | |
data ClosureType #