monte-carlo-0.6.2: A monad and transformer for Monte Carlo calculations.

CopyrightCopyright (c) 2010 Patrick Perry <patperry@gmail.com>
LicenseBSD3
MaintainerPatrick Perry <patperry@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Data.Summary.Bool

Contents

Description

Summary statistics for Bools.

Synopsis

Summary type

data Summary Source #

A type for storing summary statistics for a data set of booleans. Specifically, this just keeps track of the number of True events and gives estimates for the success probability. True is interpreted as a one, and False is interpreted as a zero.

Instances

Eq Summary Source # 

Methods

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

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

Data Summary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Summary -> c Summary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Summary #

toConstr :: Summary -> Constr #

dataTypeOf :: Summary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Summary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Summary) #

gmapT :: (forall b. Data b => b -> b) -> Summary -> Summary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Summary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Summary -> r #

gmapQ :: (forall d. Data d => d -> u) -> Summary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Summary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Summary -> m Summary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Summary -> m Summary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Summary -> m Summary #

Show Summary Source # 
Monoid Summary Source # 

Properties

Sum

size :: Summary -> Int Source #

Number of observations.

sum :: Summary -> Int Source #

Number of True values.

Mean

mean :: Summary -> Double Source #

Proportion of True values.

meanSE :: Summary -> Double Source #

Standard error for the mean (proportion of True values).

meanCI :: Double -> Summary -> (Double, Double) Source #

Central Limit Theorem based confidence interval for the population mean (proportion) at the specified coverage level. The level must be in the range (0,1).

Construction

empty :: Summary Source #

Get an empty summary.

singleton :: Bool -> Summary Source #

Summarize a single value.

Insertion

insert :: Bool -> Summary -> Summary Source #

Update the summary with a data point.

insertWith :: (a -> Bool) -> a -> Summary -> Summary Source #

Apply a function and update the summary with the result.

Combination

union :: Summary -> Summary -> Summary Source #

Take the union of two summaries.

unions :: [Summary] -> Summary Source #

Take the union of a list of summaries.

Conversion

Lists

fromList :: [Bool] -> Summary Source #

Get a summary of a list of values.

fromListWith :: (a -> Bool) -> [a] -> Summary Source #

Map a function over a list of values and summarize the results.

Statistics

toStats :: Summary -> (Int, Int) Source #

Convert to (size,sum).

fromStats :: Int -> Int -> Summary Source #

Convert from (size,sum). No validation is performed.