perf-0.3.1.1: low-level performance statistics

Safe HaskellNone
LanguageHaskell2010

Perf

Description

PerfT is a monad transformer designed to collect performance information. The transformer can be used to add performance measurent to an existing code base using Measures.

For example, here's some code doing some cheesey stuff:

  -- prior to Perfification
  result <- do
      txt <- readFile "examples/examples.hs"
      let n = Text.length txt
      let x = foldl' (+) 0 [1..n]
      putStrLn $ "sum of one to number of characters is: " <>
          (show x :: Text)
      pure (n, x)

And here's the code after Perfification, measuring performance of the components.

  (result', ms) <- runPerfT $ do
          txt <- perf "file read" cycles $ readFile "examples/examples.hs"
          n <- perf "length" cycles $ pure (Text.length txt)
          x <- perf "sum" cycles $ pure (foldl' (+) 0 [1..n])
          perf "print to screen" cycles $
              putStrLn $ "sum of one to number of characters is: " <>
              (show x :: Text)
          pure (n, x)

Running the code produces a tuple of the original computation results, and a Map of performance measurements that were specified. Indicative results:

file read                               4.92e5 cycles
length                                  1.60e6 cycles
print to screen                         1.06e5 cycles
sum                                     8.12e3 cycles

Synopsis

Documentation

data PerfT m b a Source #

PerfT is polymorphic in the type of measurement being performed. The monad stores and produces a Map of labelled measurement values

Instances

Monad m => Monad (PerfT m b) Source # 

Methods

(>>=) :: PerfT m b a -> (a -> PerfT m b b) -> PerfT m b b #

(>>) :: PerfT m b a -> PerfT m b b -> PerfT m b b #

return :: a -> PerfT m b a #

fail :: String -> PerfT m b a #

Functor m => Functor (PerfT m b) Source # 

Methods

fmap :: (a -> b) -> PerfT m b a -> PerfT m b b #

(<$) :: a -> PerfT m b b -> PerfT m b a #

Monad m => Applicative (PerfT m b) Source # 

Methods

pure :: a -> PerfT m b a #

(<*>) :: PerfT m b (a -> b) -> PerfT m b a -> PerfT m b b #

liftA2 :: (a -> b -> c) -> PerfT m b a -> PerfT m b b -> PerfT m b c #

(*>) :: PerfT m b a -> PerfT m b b -> PerfT m b b #

(<*) :: PerfT m b a -> PerfT m b b -> PerfT m b a #

MonadIO m => MonadIO (PerfT m b) Source # 

Methods

liftIO :: IO a -> PerfT m b a #

type Perf b a = PerfT Identity b a Source #

The obligatory transformer over Identity

perf :: (MonadIO m, Additive b) => Text -> Measure m b -> m a -> PerfT m b a Source #

Lift a monadic computation to a PerfT m, providing a label and a Measure.

perfN :: (MonadIO m, Semigroup b, Monoid b) => Int -> Text -> Measure m b -> m a -> PerfT m b a Source #

Lift a monadic computation to a PerfT m, and carry out the computation multiple times.

runPerfT :: PerfT m b a -> m (a, Map Text b) Source #

Consume the PerfT layer and return a (result, measurement).

>>> :set -XOverloadedStrings
>>> (cs, result) <- runPerfT $ perf "sum" cycles (pure $ foldl' (+) 0 [0..10000])
(50005000,fromList [("sum",562028)])

evalPerfT :: Monad m => PerfT m b a -> m a Source #

Consume the PerfT layer and return the original monadic result. Fingers crossed, PerfT structure should be completely compiled away.

>>> result <- evalPerfT $ perf "sum" cycles (pure $ foldl' (+) 0 [0..10000])
50005000

execPerfT :: Monad m => PerfT m b a -> m (Map Text b) Source #

Consume a PerfT layer and return the measurement.

>>> cs <- execPerfT $ perf "sum" cycles (pure $ foldl' (+) 0 [0..10000])
fromList [("sum",562028)]

module Perf.Cycle