Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- benchmark1 :: forall a. Roll a => (Word64 -> IO (Timed a)) -> Pull1 a
- newtype Pull1 a = Pull1 (IO (Estimate a, Pull1 a))
- benchmark :: forall a. Roll a => (Word64 -> IO (Timed a)) -> IO (IO (Estimate a), Pull a)
- data Pull a
- data Pulls a
- pulls :: NonEmpty (Pull a) -> Pulls a
- pull :: Pulls a -> IO (Pulls a)
- whnf :: (a -> b) -> a -> Word64 -> IO ()
- whnfIO :: IO a -> Word64 -> IO ()
- measure :: IO () -> IO (Timed RtsStats)
- data Timed a = Timed {
- nanoseconds :: !Rational
- value :: !a
- data Estimate a = Estimate {}
- initialEstimate :: Timed a -> Estimate a
- updateEstimate :: Roll a => Word64 -> Timed a -> Estimate a -> Estimate a
- stdev :: Estimate a -> Double
- variance :: Estimate a -> Rational
- class Roll a where
- data RtsStats = RtsStats !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational !Rational
- allocated_bytes_per_second :: RtsStats -> Rational
- average_live_data :: RtsStats -> Rational
- gc_average_ns :: RtsStats -> Rational
- gc_cpu_percent :: RtsStats -> Rational
- gc_wall_percent :: RtsStats -> Rational
- max_normal_objects_bytes :: RtsStats -> Rational
- minor_gcs :: RtsStats -> Rational
- mut_cpu_percent :: RtsStats -> Rational
- mut_wall_percent :: RtsStats -> Rational
- work_balance :: RtsStats -> Maybe Rational
- data R a b = R Cell (a -> Maybe b)
- class Ord a => Cellular a where
- cellDelta :: a -> a -> Double
- cellString :: a -> Builder
- newtype BytesCell = BytesCell Double
- newtype BytesPerSecondCell = BytesPerSecondCell Double
- newtype IncomparableWord3Cell = IncomparableWord3Cell Word64
- newtype IncomparablePercentageCell = IncomparablePercentageCell Double
- newtype NanosecondsCell = NanosecondsCell Double
- newtype NumberCell = NumberCell Double
- newtype NumberCell' = NumberCell' Double
- newtype PercentageCell = PercentageCell Double
- newtype PercentageCell' = PercentageCell' Double
- rowMaker :: forall a. NonEmpty a -> forall b. Cellular b => R a b -> Row
- data Table = Table ![Cell] ![RowGroup]
- renderTable :: Table -> Builder
- data RowGroup = RowGroup !Text ![Row]
- data Row
- data Cell
- isEmptyCell :: Cell -> Bool
- data Color
Benchmarking
benchmark1 :: forall a. Roll a => (Word64 -> IO (Timed a)) -> Pull1 a Source #
Like benchmark
, but optimized for only running one benchmark.
Low-level
Statistics
A value that took a certan time to compute.
Timed | |
|
initialEstimate :: Timed a -> Estimate a Source #
initialEstimate v
creates an estimate per thing-that-took-time v
that was a run of 1 iteration.
updateEstimate :: Roll a => Word64 -> Timed a -> Estimate a -> Estimate a Source #
updateEstimate n v e
updates estimate e
per thing-that-took-time v
that was a run of n
iterations.
RTS stats
RTS stats type.
This type is intentionally not a record, because it's kind of large, and generated record accessors cause quadratic time to compile.
The hand-written accessors do, too, but we don't need the generated setters at all, so there are some savings by writing it all out by hand.
TODO nonmoving_gc_*
average_live_data :: RtsStats -> Rational Source #
gc_average_ns :: RtsStats -> Rational Source #
gc_cpu_percent :: RtsStats -> Rational Source #
gc_wall_percent :: RtsStats -> Rational Source #
mut_cpu_percent :: RtsStats -> Rational Source #
mut_wall_percent :: RtsStats -> Rational Source #
Table rendering
High-level row/cell machinery
class Ord a => Cellular a where Source #
Instances
newtype BytesPerSecondCell Source #
Instances
Eq BytesPerSecondCell Source # | |
Defined in ParkBench.Pretty (==) :: BytesPerSecondCell -> BytesPerSecondCell -> Bool # (/=) :: BytesPerSecondCell -> BytesPerSecondCell -> Bool # | |
Ord BytesPerSecondCell Source # | |
Defined in ParkBench.Pretty compare :: BytesPerSecondCell -> BytesPerSecondCell -> Ordering # (<) :: BytesPerSecondCell -> BytesPerSecondCell -> Bool # (<=) :: BytesPerSecondCell -> BytesPerSecondCell -> Bool # (>) :: BytesPerSecondCell -> BytesPerSecondCell -> Bool # (>=) :: BytesPerSecondCell -> BytesPerSecondCell -> Bool # max :: BytesPerSecondCell -> BytesPerSecondCell -> BytesPerSecondCell # min :: BytesPerSecondCell -> BytesPerSecondCell -> BytesPerSecondCell # | |
Cellular BytesPerSecondCell Source # | |
Defined in ParkBench.Pretty |
newtype IncomparableWord3Cell Source #
Instances
Eq IncomparableWord3Cell Source # | |
Defined in ParkBench.Pretty (==) :: IncomparableWord3Cell -> IncomparableWord3Cell -> Bool # (/=) :: IncomparableWord3Cell -> IncomparableWord3Cell -> Bool # | |
Ord IncomparableWord3Cell Source # | |
Defined in ParkBench.Pretty compare :: IncomparableWord3Cell -> IncomparableWord3Cell -> Ordering # (<) :: IncomparableWord3Cell -> IncomparableWord3Cell -> Bool # (<=) :: IncomparableWord3Cell -> IncomparableWord3Cell -> Bool # (>) :: IncomparableWord3Cell -> IncomparableWord3Cell -> Bool # (>=) :: IncomparableWord3Cell -> IncomparableWord3Cell -> Bool # max :: IncomparableWord3Cell -> IncomparableWord3Cell -> IncomparableWord3Cell # min :: IncomparableWord3Cell -> IncomparableWord3Cell -> IncomparableWord3Cell # | |
Cellular IncomparableWord3Cell Source # | |
Defined in ParkBench.Pretty |
newtype IncomparablePercentageCell Source #
Instances
newtype NanosecondsCell Source #
Instances
Eq NanosecondsCell Source # | |
Defined in ParkBench.Pretty (==) :: NanosecondsCell -> NanosecondsCell -> Bool # (/=) :: NanosecondsCell -> NanosecondsCell -> Bool # | |
Ord NanosecondsCell Source # | |
Defined in ParkBench.Pretty compare :: NanosecondsCell -> NanosecondsCell -> Ordering # (<) :: NanosecondsCell -> NanosecondsCell -> Bool # (<=) :: NanosecondsCell -> NanosecondsCell -> Bool # (>) :: NanosecondsCell -> NanosecondsCell -> Bool # (>=) :: NanosecondsCell -> NanosecondsCell -> Bool # max :: NanosecondsCell -> NanosecondsCell -> NanosecondsCell # min :: NanosecondsCell -> NanosecondsCell -> NanosecondsCell # | |
Cellular NanosecondsCell Source # | |
Defined in ParkBench.Pretty cellDelta :: NanosecondsCell -> NanosecondsCell -> Double Source # cellString :: NanosecondsCell -> Builder Source # |
newtype NumberCell Source #
Instances
Eq NumberCell Source # | |
Defined in ParkBench.Pretty (==) :: NumberCell -> NumberCell -> Bool # (/=) :: NumberCell -> NumberCell -> Bool # | |
Ord NumberCell Source # | |
Defined in ParkBench.Pretty compare :: NumberCell -> NumberCell -> Ordering # (<) :: NumberCell -> NumberCell -> Bool # (<=) :: NumberCell -> NumberCell -> Bool # (>) :: NumberCell -> NumberCell -> Bool # (>=) :: NumberCell -> NumberCell -> Bool # max :: NumberCell -> NumberCell -> NumberCell # min :: NumberCell -> NumberCell -> NumberCell # | |
Cellular NumberCell Source # | |
Defined in ParkBench.Pretty cellDelta :: NumberCell -> NumberCell -> Double Source # cellString :: NumberCell -> Builder Source # |
newtype NumberCell' Source #
Instances
Eq NumberCell' Source # | |
Defined in ParkBench.Pretty (==) :: NumberCell' -> NumberCell' -> Bool # (/=) :: NumberCell' -> NumberCell' -> Bool # | |
Ord NumberCell' Source # | |
Defined in ParkBench.Pretty compare :: NumberCell' -> NumberCell' -> Ordering # (<) :: NumberCell' -> NumberCell' -> Bool # (<=) :: NumberCell' -> NumberCell' -> Bool # (>) :: NumberCell' -> NumberCell' -> Bool # (>=) :: NumberCell' -> NumberCell' -> Bool # max :: NumberCell' -> NumberCell' -> NumberCell' # min :: NumberCell' -> NumberCell' -> NumberCell' # | |
Cellular NumberCell' Source # | |
Defined in ParkBench.Pretty cellDelta :: NumberCell' -> NumberCell' -> Double Source # cellString :: NumberCell' -> Builder Source # |
newtype PercentageCell Source #
Instances
Eq PercentageCell Source # | |
Defined in ParkBench.Pretty (==) :: PercentageCell -> PercentageCell -> Bool # (/=) :: PercentageCell -> PercentageCell -> Bool # | |
Ord PercentageCell Source # | |
Defined in ParkBench.Pretty compare :: PercentageCell -> PercentageCell -> Ordering # (<) :: PercentageCell -> PercentageCell -> Bool # (<=) :: PercentageCell -> PercentageCell -> Bool # (>) :: PercentageCell -> PercentageCell -> Bool # (>=) :: PercentageCell -> PercentageCell -> Bool # max :: PercentageCell -> PercentageCell -> PercentageCell # min :: PercentageCell -> PercentageCell -> PercentageCell # | |
Cellular PercentageCell Source # | |
Defined in ParkBench.Pretty cellDelta :: PercentageCell -> PercentageCell -> Double Source # cellString :: PercentageCell -> Builder Source # |
newtype PercentageCell' Source #
Instances
Eq PercentageCell' Source # | |
Defined in ParkBench.Pretty (==) :: PercentageCell' -> PercentageCell' -> Bool # (/=) :: PercentageCell' -> PercentageCell' -> Bool # | |
Ord PercentageCell' Source # | |
Defined in ParkBench.Pretty compare :: PercentageCell' -> PercentageCell' -> Ordering # (<) :: PercentageCell' -> PercentageCell' -> Bool # (<=) :: PercentageCell' -> PercentageCell' -> Bool # (>) :: PercentageCell' -> PercentageCell' -> Bool # (>=) :: PercentageCell' -> PercentageCell' -> Bool # max :: PercentageCell' -> PercentageCell' -> PercentageCell' # min :: PercentageCell' -> PercentageCell' -> PercentageCell' # | |
Cellular PercentageCell' Source # | |
Defined in ParkBench.Pretty cellDelta :: PercentageCell' -> PercentageCell' -> Double Source # cellString :: PercentageCell' -> Builder Source # |
Table machinery
renderTable :: Table -> Builder Source #
Instances
IsString Cell Source # | |
Defined in ParkBench.Pretty fromString :: String -> Cell # |
isEmptyCell :: Cell -> Bool Source #