park-bench-0.1.0: A quick-and-dirty, low-friction benchmark tool with immediate feedback
Safe HaskellNone
LanguageHaskell2010

ParkBench.Internal

Synopsis

Benchmarking

benchmark1 :: forall a. Roll a => (Word64 -> IO (Timed a)) -> Pull1 a Source #

Like benchmark, but optimized for only running one benchmark.

newtype Pull1 a Source #

Constructors

Pull1 (IO (Estimate a, Pull1 a)) 

benchmark :: forall a. Roll a => (Word64 -> IO (Timed a)) -> IO (IO (Estimate a), Pull a) Source #

data Pull a Source #

data Pulls a Source #

A Pulls represents the suspended state of a collection of 1+ benchmarks.

pulls :: NonEmpty (Pull a) -> Pulls a Source #

Construct a Pulls from a non-empty list of Pull.

pull :: Pulls a -> IO (Pulls a) Source #

Pull on a Pulls, which blocks until the benchmark that has heretofore accumulated the smallest amount of runtime runs once more.

Returns the Pulls to use next time, which reflects the latest benchmark run that just completed.

Low-level

whnf :: (a -> b) -> a -> Word64 -> IO () Source #

whnfIO :: IO a -> Word64 -> IO () Source #

measure :: IO () -> IO (Timed RtsStats) Source #

Measure the time/memory usage of an IO action.

Statistics

data Timed a Source #

A value that took a certan time to compute.

Constructors

Timed 

Fields

Instances

Instances details
Functor Timed Source # 
Instance details

Defined in ParkBench.Statistics

Methods

fmap :: (a -> b) -> Timed a -> Timed b #

(<$) :: a -> Timed b -> Timed a #

Show a => Show (Timed a) Source # 
Instance details

Defined in ParkBench.Statistics

Methods

showsPrec :: Int -> Timed a -> ShowS #

show :: Timed a -> String #

showList :: [Timed a] -> ShowS #

Semigroup a => Semigroup (Timed a) Source # 
Instance details

Defined in ParkBench.Statistics

Methods

(<>) :: Timed a -> Timed a -> Timed a #

sconcat :: NonEmpty (Timed a) -> Timed a #

stimes :: Integral b => b -> Timed a -> Timed a #

Monoid a => Monoid (Timed a) Source # 
Instance details

Defined in ParkBench.Statistics

Methods

mempty :: Timed a #

mappend :: Timed a -> Timed a -> Timed a #

mconcat :: [Timed a] -> Timed a #

data Estimate a Source #

Constructors

Estimate 

Fields

Instances

Instances details
Functor Estimate Source # 
Instance details

Defined in ParkBench.Statistics

Methods

fmap :: (a -> b) -> Estimate a -> Estimate b #

(<$) :: a -> Estimate b -> Estimate a #

Show a => Show (Estimate a) Source # 
Instance details

Defined in ParkBench.Statistics

Methods

showsPrec :: Int -> Estimate a -> ShowS #

show :: Estimate a -> String #

showList :: [Estimate a] -> ShowS #

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.

class Roll a where Source #

Methods

roll :: (Rational -> Rational -> Rational) -> a -> a -> a Source #

Instances

Instances details
Roll RtsStats Source # 
Instance details

Defined in ParkBench.RtsStats

RTS stats

data RtsStats Source #

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_*

Instances

Instances details
Roll RtsStats Source # 
Instance details

Defined in ParkBench.RtsStats

Table rendering

High-level row/cell machinery

data R a b Source #

Constructors

R Cell (a -> Maybe b) 

class Ord a => Cellular a where Source #

Methods

cellDelta :: a -> a -> Double Source #

cellString :: a -> Builder Source #

Instances

Instances details
Cellular IncomparableWord3Cell Source # 
Instance details

Defined in ParkBench.Pretty

Cellular PercentageCell' Source # 
Instance details

Defined in ParkBench.Pretty

Cellular PercentageCell Source # 
Instance details

Defined in ParkBench.Pretty

Cellular NanosecondsCell Source # 
Instance details

Defined in ParkBench.Pretty

Cellular NumberCell' Source # 
Instance details

Defined in ParkBench.Pretty

Cellular NumberCell Source # 
Instance details

Defined in ParkBench.Pretty

Cellular IncomparablePercentageCell Source # 
Instance details

Defined in ParkBench.Pretty

Cellular BytesPerSecondCell Source # 
Instance details

Defined in ParkBench.Pretty

Cellular BytesCell Source # 
Instance details

Defined in ParkBench.Pretty

newtype BytesCell Source #

Constructors

BytesCell Double 

rowMaker :: forall a. NonEmpty a -> forall b. Cellular b => R a b -> Row Source #

Table machinery

data Table Source #

Constructors

Table ![Cell] ![RowGroup] 

data RowGroup Source #

Constructors

RowGroup !Text ![Row] 

data Row Source #

Constructors

Row ![Cell]

Invariant: 1+ cells; not all cells are empty

EmptyRow 

data Cell Source #

Constructors

EmptyCell 
Cell !Color !Text 

Instances

Instances details
IsString Cell Source # 
Instance details

Defined in ParkBench.Pretty

Methods

fromString :: String -> Cell #

data Color Source #

Constructors

Blue 
Green 
Red 
White