SciBaseTypes-0.0.0.1: Base types and classes for statistics, sciences and humanities

Safe HaskellNone
LanguageHaskell2010

Statistics.Probability

Contents

Description

Probability-related types.

TODO instances for serialization and further stuff TODO vector instances

Synopsis

Documentation

Probability in linear space

newtype Prob (n :: IsNormalized) x Source #

Prob wraps a Double that encodes probabilities. If Prob is tagged as Normalized, the contained values are in the range [0,...,1], otherwise they are in the range [0,...,∞].

Constructors

Prob 

Fields

Instances
Unbox x => Vector Vector (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Prob n x) -> m (Vector (Prob n x)) #

basicUnsafeThaw :: PrimMonad m => Vector (Prob n x) -> m (Mutable Vector (PrimState m) (Prob n x)) #

basicLength :: Vector (Prob n x) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Prob n x) -> Vector (Prob n x) #

basicUnsafeIndexM :: Monad m => Vector (Prob n x) -> Int -> m (Prob n x) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Prob n x) -> Vector (Prob n x) -> m () #

elemseq :: Vector (Prob n x) -> Prob n x -> b -> b #

Unbox x => MVector MVector (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

basicLength :: MVector s (Prob n x) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Prob n x) -> MVector s (Prob n x) #

basicOverlaps :: MVector s (Prob n x) -> MVector s (Prob n x) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Prob n x)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Prob n x) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Prob n x -> m (MVector (PrimState m) (Prob n x)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Prob n x) -> Int -> m (Prob n x) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Prob n x) -> Int -> Prob n x -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Prob n x) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Prob n x) -> Prob n x -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Prob n x) -> MVector (PrimState m) (Prob n x) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Prob n x) -> MVector (PrimState m) (Prob n x) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Prob n x) -> Int -> m (MVector (PrimState m) (Prob n x)) #

Enum x => Enum (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

succ :: Prob n x -> Prob n x #

pred :: Prob n x -> Prob n x #

toEnum :: Int -> Prob n x #

fromEnum :: Prob n x -> Int #

enumFrom :: Prob n x -> [Prob n x] #

enumFromThen :: Prob n x -> Prob n x -> [Prob n x] #

enumFromTo :: Prob n x -> Prob n x -> [Prob n x] #

enumFromThenTo :: Prob n x -> Prob n x -> Prob n x -> [Prob n x] #

Eq x => Eq (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

(==) :: Prob n x -> Prob n x -> Bool #

(/=) :: Prob n x -> Prob n x -> Bool #

Floating x => Floating (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

pi :: Prob n x #

exp :: Prob n x -> Prob n x #

log :: Prob n x -> Prob n x #

sqrt :: Prob n x -> Prob n x #

(**) :: Prob n x -> Prob n x -> Prob n x #

logBase :: Prob n x -> Prob n x -> Prob n x #

sin :: Prob n x -> Prob n x #

cos :: Prob n x -> Prob n x #

tan :: Prob n x -> Prob n x #

asin :: Prob n x -> Prob n x #

acos :: Prob n x -> Prob n x #

atan :: Prob n x -> Prob n x #

sinh :: Prob n x -> Prob n x #

cosh :: Prob n x -> Prob n x #

tanh :: Prob n x -> Prob n x #

asinh :: Prob n x -> Prob n x #

acosh :: Prob n x -> Prob n x #

atanh :: Prob n x -> Prob n x #

log1p :: Prob n x -> Prob n x #

expm1 :: Prob n x -> Prob n x #

log1pexp :: Prob n x -> Prob n x #

log1mexp :: Prob n x -> Prob n x #

Fractional x => Fractional (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

(/) :: Prob n x -> Prob n x -> Prob n x #

recip :: Prob n x -> Prob n x #

fromRational :: Rational -> Prob n x #

Num x => Num (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

(+) :: Prob n x -> Prob n x -> Prob n x #

(-) :: Prob n x -> Prob n x -> Prob n x #

(*) :: Prob n x -> Prob n x -> Prob n x #

negate :: Prob n x -> Prob n x #

abs :: Prob n x -> Prob n x #

signum :: Prob n x -> Prob n x #

fromInteger :: Integer -> Prob n x #

Ord x => Ord (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

compare :: Prob n x -> Prob n x -> Ordering #

(<) :: Prob n x -> Prob n x -> Bool #

(<=) :: Prob n x -> Prob n x -> Bool #

(>) :: Prob n x -> Prob n x -> Bool #

(>=) :: Prob n x -> Prob n x -> Bool #

max :: Prob n x -> Prob n x -> Prob n x #

min :: Prob n x -> Prob n x -> Prob n x #

Read x => Read (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

readsPrec :: Int -> ReadS (Prob n x) #

readList :: ReadS [Prob n x] #

readPrec :: ReadPrec (Prob n x) #

readListPrec :: ReadPrec [Prob n x] #

Real x => Real (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

toRational :: Prob n x -> Rational #

RealFloat x => RealFloat (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

floatRadix :: Prob n x -> Integer #

floatDigits :: Prob n x -> Int #

floatRange :: Prob n x -> (Int, Int) #

decodeFloat :: Prob n x -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Prob n x #

exponent :: Prob n x -> Int #

significand :: Prob n x -> Prob n x #

scaleFloat :: Int -> Prob n x -> Prob n x #

isNaN :: Prob n x -> Bool #

isInfinite :: Prob n x -> Bool #

isDenormalized :: Prob n x -> Bool #

isNegativeZero :: Prob n x -> Bool #

isIEEE :: Prob n x -> Bool #

atan2 :: Prob n x -> Prob n x -> Prob n x #

RealFrac x => RealFrac (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

properFraction :: Integral b => Prob n x -> (b, Prob n x) #

truncate :: Integral b => Prob n x -> b #

round :: Integral b => Prob n x -> b #

ceiling :: Integral b => Prob n x -> b #

floor :: Integral b => Prob n x -> b #

Show x => Show (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

showsPrec :: Int -> Prob n x -> ShowS #

show :: Prob n x -> String #

showList :: [Prob n x] -> ShowS #

Unbox x => Unbox (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

Num r => SemiRing (Prob n r) Source # 
Instance details

Defined in Statistics.Probability

Methods

srplus :: Prob n r -> Prob n r -> Prob n r Source #

srmul :: Prob n r -> Prob n r -> Prob n r Source #

srzero :: Prob n r Source #

srone :: Prob n r Source #

data MVector s (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

data MVector s (Prob n x) = MV_Prob (MVector s x)
data Vector (Prob n x) Source # 
Instance details

Defined in Statistics.Probability

data Vector (Prob n x) = V_Prob (Vector x)

prob :: (Ord x, Num x, Show x) => x -> Prob Normalized x Source #

Turns a value into a normalized probability. error if the value is not in the range [0,...,1].

prob' :: (Ord x, Num x, Show x) => x -> Prob NotNormalized x Source #

Simple wrapper around Prob that fixes non-normalization.

Probability in log space. A number of operations internally cast to Log

newtype LogProb (n :: IsNormalized) x Source #

Constructors

LogProb 

Fields

Instances
Unbox x => Vector Vector (LogProb n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (LogProb n x) -> m (Vector (LogProb n x)) #

basicUnsafeThaw :: PrimMonad m => Vector (LogProb n x) -> m (Mutable Vector (PrimState m) (LogProb n x)) #

basicLength :: Vector (LogProb n x) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (LogProb n x) -> Vector (LogProb n x) #

basicUnsafeIndexM :: Monad m => Vector (LogProb n x) -> Int -> m (LogProb n x) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (LogProb n x) -> Vector (LogProb n x) -> m () #

elemseq :: Vector (LogProb n x) -> LogProb n x -> b -> b #

Unbox x => MVector MVector (LogProb n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

basicLength :: MVector s (LogProb n x) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (LogProb n x) -> MVector s (LogProb n x) #

basicOverlaps :: MVector s (LogProb n x) -> MVector s (LogProb n x) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (LogProb n x)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (LogProb n x) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> LogProb n x -> m (MVector (PrimState m) (LogProb n x)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (LogProb n x) -> Int -> m (LogProb n x) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (LogProb n x) -> Int -> LogProb n x -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (LogProb n x) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (LogProb n x) -> LogProb n x -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (LogProb n x) -> MVector (PrimState m) (LogProb n x) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (LogProb n x) -> MVector (PrimState m) (LogProb n x) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (LogProb n x) -> Int -> m (MVector (PrimState m) (LogProb n x)) #

Eq x => Eq (LogProb n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

(==) :: LogProb n x -> LogProb n x -> Bool #

(/=) :: LogProb n x -> LogProb n x -> Bool #

(Precise x, RealFloat x) => Num (LogProb n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

(+) :: LogProb n x -> LogProb n x -> LogProb n x #

(-) :: LogProb n x -> LogProb n x -> LogProb n x #

(*) :: LogProb n x -> LogProb n x -> LogProb n x #

negate :: LogProb n x -> LogProb n x #

abs :: LogProb n x -> LogProb n x #

signum :: LogProb n x -> LogProb n x #

fromInteger :: Integer -> LogProb n x #

Ord x => Ord (LogProb n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

compare :: LogProb n x -> LogProb n x -> Ordering #

(<) :: LogProb n x -> LogProb n x -> Bool #

(<=) :: LogProb n x -> LogProb n x -> Bool #

(>) :: LogProb n x -> LogProb n x -> Bool #

(>=) :: LogProb n x -> LogProb n x -> Bool #

max :: LogProb n x -> LogProb n x -> LogProb n x #

min :: LogProb n x -> LogProb n x -> LogProb n x #

Show x => Show (LogProb n x) Source # 
Instance details

Defined in Statistics.Probability

Methods

showsPrec :: Int -> LogProb n x -> ShowS #

show :: LogProb n x -> String #

showList :: [LogProb n x] -> ShowS #

Unbox x => Unbox (LogProb n x) Source # 
Instance details

Defined in Statistics.Probability

(Num d, Fractional d) => NumericLimits (LogProb n d) Source # 
Instance details

Defined in Statistics.Probability

data MVector s (LogProb n x) Source # 
Instance details

Defined in Statistics.Probability

data MVector s (LogProb n x) = MV_LogProb (MVector s x)
data Vector (LogProb n x) Source # 
Instance details

Defined in Statistics.Probability

data Vector (LogProb n x) = V_LogProb (Vector x)

withLog1 :: (Log x -> Log y) -> LogProb n x -> LogProb n y Source #

withLog2 :: (Log x -> Log y -> Log z) -> LogProb n x -> LogProb n y -> LogProb n z Source #

Conversion between probability in linear and log-space.

p2lp :: Floating x => Prob n x -> LogProb n x Source #

Turn probability into log-probability.

lp2p :: Floating x => LogProb n x -> Prob n x Source #

Turn log-probability into probability.

aslp :: Floating x => Iso' (Prob n x) (LogProb n x) Source #

An isomorphism between Prob and LogProb.