Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Perf.Types
Description
Abstract types of performance measurement.
Synopsis
- newtype Measure m t = Measure {
- measure :: forall a b. (a -> b) -> a -> m (t, b)
- repeated :: Applicative m => Int -> Measure m t -> Measure m [t]
- data StepMeasure m t = forall i.StepMeasure {}
- toMeasure :: Monad m => StepMeasure m t -> Measure m t
- toMeasureN :: Monad m => Int -> StepMeasure m t -> Measure m [t]
- step :: Monad m => m i -> (i -> m t) -> (a -> b) -> a -> m (t, b)
- stepM :: Monad m => m i -> (i -> m t) -> m a -> m (t, a)
- multi :: Monad m => ((a -> b) -> a -> m (t, b)) -> Int -> (a -> b) -> a -> m ([t], b)
- multiM :: Monad m => (m a -> m (t, a)) -> Int -> m a -> m ([t], a)
- multiN :: (b -> t) -> (a -> b) -> a -> Int -> IO t
- fap :: (MonadIO m, Semigroup t) => Text -> (a -> b) -> a -> PerfT m t b
- afap :: (NFData a, MonadIO m, Semigroup t) => Text -> (a -> b) -> a -> PerfT m t b
- ffap :: (NFData a, NFData b, MonadIO m, Semigroup t) => Text -> (a -> b) -> a -> PerfT m t b
- fan :: (MonadIO m, Num t) => Text -> (a -> b) -> a -> PerfT m t b
- fam :: (MonadIO m, Semigroup t) => Text -> m a -> PerfT m t a
- (|$|) :: Semigroup t => (a -> b) -> a -> PerfT IO t b
- ($|) :: Semigroup t => IO a -> PerfT IO t a
- (|+|) :: Num t => (a -> b) -> a -> PerfT IO t b
- newtype PerfT m t a = PerfT {
- measurePerf :: StateT (Measure m t, Map Text t) m a
- type Perf t a = PerfT Identity t a
- runPerfT :: Functor m => Measure m t -> PerfT m t a -> m (a, Map Text t)
- evalPerfT :: Monad m => Measure m t -> PerfT m t a -> m a
- execPerfT :: Monad m => Measure m t -> PerfT m t a -> m (Map Text t)
- outer :: (MonadIO m, Semigroup s) => Text -> Measure m s -> Measure m t -> PerfT m t a -> m (a, (Map Text s, Map Text t))
- slop :: (MonadIO m, Num t, Semigroup t) => Text -> Measure m t -> PerfT m t a -> m (a, Map Text t)
- slops :: (MonadIO m, Num t, Semigroup t) => Int -> Measure m t -> PerfT m [t] a -> m (a, (Map Text t, Map Text [t]))
Measure
Abstraction of a performance measurement within a monadic context.
- measure applies a function to a value, returning a tuple of the performance measure, and the computation result.
- measureM evaluates a monadic value and returns a performance-result tuple.
Instances
Applicative m => Applicative (Measure m) Source # | An inefficient application that runs the inner action twice. |
Functor m => Functor (Measure m) Source # | |
repeated :: Applicative m => Int -> Measure m t -> Measure m [t] Source #
Convert a Measure into a multi measure.
data StepMeasure m t Source #
Abstraction of a performance measurement with a pre and a post step wrapping the computation.
Constructors
forall i. StepMeasure | |
Instances
Applicative m => Applicative (StepMeasure m) Source # | |
Defined in Perf.Types Methods pure :: a -> StepMeasure m a # (<*>) :: StepMeasure m (a -> b) -> StepMeasure m a -> StepMeasure m b # liftA2 :: (a -> b -> c) -> StepMeasure m a -> StepMeasure m b -> StepMeasure m c # (*>) :: StepMeasure m a -> StepMeasure m b -> StepMeasure m b # (<*) :: StepMeasure m a -> StepMeasure m b -> StepMeasure m a # | |
Functor m => Functor (StepMeasure m) Source # | |
Defined in Perf.Types Methods fmap :: (a -> b) -> StepMeasure m a -> StepMeasure m b # (<$) :: a -> StepMeasure m b -> StepMeasure m a # |
toMeasureN :: Monad m => Int -> StepMeasure m t -> Measure m [t] Source #
Convert a StepMeasure into a Measure running the computation multiple times.
step :: Monad m => m i -> (i -> m t) -> (a -> b) -> a -> m (t, b) Source #
A single step measurement.
multi :: Monad m => ((a -> b) -> a -> m (t, b)) -> Int -> (a -> b) -> a -> m ([t], b) Source #
Return one result but multiple measurements.
function application
fap :: (MonadIO m, Semigroup t) => Text -> (a -> b) -> a -> PerfT m t b Source #
Lift an application to a PerfT m, providing a label and a Measure
.
Measurements with the same label will be mappended
afap :: (NFData a, MonadIO m, Semigroup t) => Text -> (a -> b) -> a -> PerfT m t b Source #
Lift an application to a PerfT m, forcing the argument.
ffap :: (NFData a, NFData b, MonadIO m, Semigroup t) => Text -> (a -> b) -> a -> PerfT m t b Source #
Lift an application to a PerfT m, forcing argument and result.
fan :: (MonadIO m, Num t) => Text -> (a -> b) -> a -> PerfT m t b Source #
Lift a number to a PerfT m, providing a label, function, and input.
Measurements with the same label will be added
fam :: (MonadIO m, Semigroup t) => Text -> m a -> PerfT m t a Source #
Lift a monadic value to a PerfT m, providing a label and a Measure
.
Measurements with the same label will be added
(|$|) :: Semigroup t => (a -> b) -> a -> PerfT IO t b Source #
lift a pure, unnamed function application to PerfT
($|) :: Semigroup t => IO a -> PerfT IO t a Source #
lift a monadic, unnamed function application to PerfT
PerfT monad
Performance measurement transformer storing a Measure
and a map of named results.
runPerfT :: Functor m => Measure m t -> PerfT m t a -> m (a, Map Text t) Source #
Run the performance measure, returning (computational result, measurement).
evalPerfT :: Monad m => Measure m t -> PerfT m t a -> m a Source #
Consume the PerfT layer and return the original monadic result. Fingers crossed, PerfT structure should be completely compiled away.
execPerfT :: Monad m => Measure m t -> PerfT m t a -> m (Map Text t) Source #
Consume a PerfT layer and return the measurement.
outer :: (MonadIO m, Semigroup s) => Text -> Measure m s -> Measure m t -> PerfT m t a -> m (a, (Map Text s, Map Text t)) Source #
run a PerfT and also calculate performance over the entire computation