weigh-0.0.14: Measure allocations of a Haskell functions/values

Safe HaskellNone
LanguageHaskell2010

Weigh

Contents

Description

Framework for seeing how much a function allocates.

WARNING: weigh is incompatible with profiling. It reports much more allocations with profiling turned on.

Example:

import Weigh
main =
  mainWith (do func "integers count 0" count 0
               func "integers count 1" count 1
               func "integers count 2" count 2
               func "integers count 3" count 3
               func "integers count 10" count 10
               func "integers count 100" count 100)
  where count :: Integer -> ()
        count 0 = ()
        count a = count (a - 1)

Use wgroup to group sets of tests.

Synopsis

Main entry points

mainWith :: Weigh a -> IO () Source #

Just run the measuring and print a report. Uses weighResults.

weighResults :: Weigh a -> IO ([Grouped (Weight, Maybe String)], Config) Source #

Run the measuring and return all the results, each one may have an error.

Configuration

setColumns :: [Column] -> Weigh () Source #

Set the columns to display in the config

data Column Source #

Table column.

Constructors

Case 
Allocated 
GCs 
Live 
Check 
Max 
Instances
Enum Column Source # 
Instance details

Defined in Weigh

Eq Column Source # 
Instance details

Defined in Weigh

Methods

(==) :: Column -> Column -> Bool #

(/=) :: Column -> Column -> Bool #

Show Column Source # 
Instance details

Defined in Weigh

setFormat :: Format -> Weigh () Source #

Set the output format in the config

data Format Source #

Constructors

Plain 
Markdown 
Instances
Show Format Source # 
Instance details

Defined in Weigh

setConfig :: Config -> Weigh () Source #

Set the config. Default is: defaultConfig.

data Config Source #

Weigh configuration.

Constructors

Config 
Instances
Show Config Source # 
Instance details

Defined in Weigh

defaultConfig :: Config Source #

Default config.

Simple combinators

func Source #

Arguments

:: NFData a 
=> String

Name of the case.

-> (b -> a)

Function that does some action to measure.

-> b

Argument to that function.

-> Weigh () 

Weigh a function applied to an argument.

Implemented in terms of validateFunc.

io Source #

Arguments

:: NFData a 
=> String

Name of the case.

-> (b -> IO a)

Aciton that does some IO to measure.

-> b

Argument to that function.

-> Weigh () 

Weigh an action applied to an argument.

Implemented in terms of validateAction.

value Source #

Arguments

:: NFData a 
=> String

Name for the value.

-> a

The value to measure.

-> Weigh () 

Weigh a value.

Implemented in terms of action.

action Source #

Arguments

:: NFData a 
=> String

Name for the value.

-> IO a

The action to measure.

-> Weigh () 

Weigh an IO action.

Implemented in terms of validateAction.

wgroup :: String -> Weigh () -> Weigh () Source #

Make a grouping of tests.

Validating combinators

validateAction Source #

Arguments

:: NFData a 
=> String

Name of the action.

-> (b -> IO a)

The function which performs some IO.

-> b

Argument to the function. Doesn't have to be forced.

-> (Weight -> Maybe String)

A validating function, returns maybe an error.

-> Weigh () 

Weigh an IO action, validating the result.

validateFunc Source #

Arguments

:: NFData a 
=> String

Name of the function.

-> (b -> a)

The function which calculates something.

-> b

Argument to the function. Doesn't have to be forced.

-> (Weight -> Maybe String)

A validating function, returns maybe an error.

-> Weigh () 

Weigh a function, validating the result

Validators

maxAllocs Source #

Arguments

:: Int64

The upper bound.

-> Weight -> Maybe String 

Make a validator that set sthe maximum allocations.

Types

data Weigh a Source #

Weigh specification monad.

Instances
Monad Weigh Source # 
Instance details

Defined in Weigh

Methods

(>>=) :: Weigh a -> (a -> Weigh b) -> Weigh b #

(>>) :: Weigh a -> Weigh b -> Weigh b #

return :: a -> Weigh a #

fail :: String -> Weigh a #

Functor Weigh Source # 
Instance details

Defined in Weigh

Methods

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

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

Applicative Weigh Source # 
Instance details

Defined in Weigh

Methods

pure :: a -> Weigh a #

(<*>) :: Weigh (a -> b) -> Weigh a -> Weigh b #

liftA2 :: (a -> b -> c) -> Weigh a -> Weigh b -> Weigh c #

(*>) :: Weigh a -> Weigh b -> Weigh b #

(<*) :: Weigh a -> Weigh b -> Weigh a #

data Weight Source #

How much a computation weighed in at.

Instances
Read Weight Source # 
Instance details

Defined in Weigh

Show Weight Source # 
Instance details

Defined in Weigh

Handy utilities

commas :: (Num a, Integral a, Show a) => a -> String Source #

Formatting an integral number to 1,000,000, etc.

Internals

weighDispatch Source #

Arguments

:: Maybe String

The content of then env variable WEIGH_CASE.

-> [Grouped Action]

Weigh name:action mapping.

-> IO (Maybe [Grouped Weight]) 

Weigh a set of actions. The value of the actions are forced completely to ensure they are fully allocated.

weighFunc Source #

Arguments

:: NFData a 
=> (b -> a)

A function whose memory use we want to measure.

-> b

Argument to the function. Doesn't have to be forced.

-> IO (Int64, Int64, Int64, Int64)

Bytes allocated and garbage collections.

Weigh a pure function. This function is built on top of weighFuncResult, which is heavily documented inside

weighFuncResult Source #

Arguments

:: NFData a 
=> (b -> a)

A function whose memory use we want to measure.

-> b

Argument to the function. Doesn't have to be forced.

-> IO (a, (Int64, Int64, Int64, Int64))

Result, Bytes allocated, GCs.

Weigh a pure function and return the result. This function is heavily documented inside.

weighAction Source #

Arguments

:: NFData a 
=> (b -> IO a)

A function whose memory use we want to measure.

-> b

Argument to the function. Doesn't have to be forced.

-> IO (Int64, Int64, Int64, Int64)

Bytes allocated and garbage collections.

Weigh an IO action. This function is based on weighActionResult, which is heavily documented inside.

weighActionResult Source #

Arguments

:: NFData a 
=> (b -> IO a)

A function whose memory use we want to measure.

-> b

Argument to the function. Doesn't have to be forced.

-> IO (a, (Int64, Int64, Int64, Int64))

Result, Bytes allocated and GCs.

Weigh an IO action, and return the result. This function is heavily documented inside.

data Grouped a Source #

Some grouped thing.

Constructors

Grouped String [Grouped a] 
Singleton a 
Instances
Functor Grouped Source # 
Instance details

Defined in Weigh

Methods

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

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

Foldable Grouped Source # 
Instance details

Defined in Weigh

Methods

fold :: Monoid m => Grouped m -> m #

foldMap :: Monoid m => (a -> m) -> Grouped a -> m #

foldr :: (a -> b -> b) -> b -> Grouped a -> b #

foldr' :: (a -> b -> b) -> b -> Grouped a -> b #

foldl :: (b -> a -> b) -> b -> Grouped a -> b #

foldl' :: (b -> a -> b) -> b -> Grouped a -> b #

foldr1 :: (a -> a -> a) -> Grouped a -> a #

foldl1 :: (a -> a -> a) -> Grouped a -> a #

toList :: Grouped a -> [a] #

null :: Grouped a -> Bool #

length :: Grouped a -> Int #

elem :: Eq a => a -> Grouped a -> Bool #

maximum :: Ord a => Grouped a -> a #

minimum :: Ord a => Grouped a -> a #

sum :: Num a => Grouped a -> a #

product :: Num a => Grouped a -> a #

Traversable Grouped Source # 
Instance details

Defined in Weigh

Methods

traverse :: Applicative f => (a -> f b) -> Grouped a -> f (Grouped b) #

sequenceA :: Applicative f => Grouped (f a) -> f (Grouped a) #

mapM :: Monad m => (a -> m b) -> Grouped a -> m (Grouped b) #

sequence :: Monad m => Grouped (m a) -> m (Grouped a) #

Eq a => Eq (Grouped a) Source # 
Instance details

Defined in Weigh

Methods

(==) :: Grouped a -> Grouped a -> Bool #

(/=) :: Grouped a -> Grouped a -> Bool #

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

Defined in Weigh

Methods

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

show :: Grouped a -> String #

showList :: [Grouped a] -> ShowS #

Generic (Grouped a) Source # 
Instance details

Defined in Weigh

Associated Types

type Rep (Grouped a) :: Type -> Type #

Methods

from :: Grouped a -> Rep (Grouped a) x #

to :: Rep (Grouped a) x -> Grouped a #

NFData a => NFData (Grouped a) Source # 
Instance details

Defined in Weigh

Methods

rnf :: Grouped a -> () #

type Rep (Grouped a) Source # 
Instance details

Defined in Weigh