Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Random variables for stochastical validation.
Synopsis
- data X x = XEmpty
- samples :: X x -> Omega -> [x]
- getSamples :: N -> X x -> IO [x]
- sample :: X x -> Omega -> x
- meanValue :: Fractional x => Int -> X x -> Omega -> x
- data Omega
- mkOmega :: Int -> Omega
- getOmega :: IO Omega
- xOmega :: X Omega
- xInt :: X Int
- xIntB :: Int -> Int -> X Int
- xWord :: X Word
- xWordB :: Word -> Word -> X Word
- xInteger :: X Integer
- xIntegerB :: Integer -> Integer -> X Integer
- xChar :: X Char
- xCharB :: Char -> Char -> X Char
- xDouble :: X Double
- xDoubleB :: Double -> Double -> X Double
- xEnum :: (Enum a, Bounded a) => X a
- xEnumB :: Enum a => a -> a -> X a
- xBool :: X Bool
- xTupple2 :: X a -> X b -> X (a, b)
- xTupple3 :: X a -> X b -> X c -> X (a, b, c)
- xTakeN :: N -> X x -> X [x]
- xTakeB :: N -> N -> X x -> X [x]
- xList :: [X x] -> X [x]
- xOneOf :: [a] -> X a
- xOneOfX :: [X a] -> X a
- xOneOfW :: [(Q, a)] -> X a
- xOneOfXW :: [(Q, X a)] -> X a
- xN :: X N
- xNB :: N -> N -> X N
- xZ :: X Z
- xZB :: Z -> Z -> X Z
- xQ :: X Q
- sum' :: Num x => [x] -> x
- putDistribution :: (Show x, Ord x) => Int -> X x -> Omega -> IO ()
- putDistribution' :: (Show x, Ord x) => [x -> String] -> Int -> X x -> Omega -> IO ()
- putDistributionIO :: (Show x, Ord x) => Int -> X (IO x) -> Omega -> IO ()
- putDstr :: (x -> [String]) -> Int -> X x -> IO ()
- aspCnstr :: Show x => x -> String
- data XException
Random Variable
random variable over x
, possibly XEmpty
. Let x
be a type and
xx
in
, then we use the idiom X
xx
is in the range of
xx
if there exist a o
in Omega
such that x
is an element of
.samples
xx o
Note
- For the empty set
O
there is exactly one sigma algebra, i.e. the power set of the empty setO
, and for every setX
there is exactly one measurable functionO -> X
, i.e. the empty function, and hence exactly one random variable overO
. - To not run into non terminating programs, we restrict the implementation of
xa
to a maximal number of iterations to find a suitable sample in>>=
fxa
for whichf a
is not empty. If the iterations exceed this maximum number, aProbablyEmpty
exception will be thrown.
samples :: X x -> Omega -> [x] Source #
infinite list of randomly picked samples of xx
according to a initial omega o
. If
xx
is empty then the result will be '[]'
.
gets a list of randomly picked samples.
Statistics
meanValue :: Fractional x => Int -> X x -> Omega -> x Source #
the mean value of n
-samples according the state s
.
Omega
X
xTakeN :: N -> X x -> X [x] Source #
random variable of list with the given length for non empty random variables.
Otherwise the result will be XEmpty
.
xTakeB :: N -> N -> X x -> X [x] Source #
random variable of lists with a length between the given bounds.
xOneOf xs
is the random variable of x
s in xs
with a uniformly distribution
of the xi
s, where 0 < length xs
. If xs == []
then XEmpty
will be the result.
xOneOfW :: [(Q, a)] -> X a Source #
xOneOfW [(w1,x1)..(wn,xn)]
is the random variable of x
s in [x1,x2,..xn]
with a distribution of the xi
s of pi = wi/s
, where 0 < n
, s = w1+w2+..+wn
and 0 <= wi
for i = 1..n
. If n == 0
then XEmpty
will be the result.
uniformly distributed random variable in the given range. If the lower
bound is greater then the upper bound the result will be XEmpty
.
Tools
putDistribution :: (Show x, Ord x) => Int -> X x -> Omega -> IO () Source #
puts the distribution according of the given number of samples.
putDistribution' :: (Show x, Ord x) => [x -> String] -> Int -> X x -> Omega -> IO () Source #
puts the distribution according to the given aspects and the given number of samples.
putDistributionIO :: (Show x, Ord x) => Int -> X (IO x) -> Omega -> IO () Source #
puts the distribution of according the given number of samples.
putDstr :: (x -> [String]) -> Int -> X x -> IO () Source #
puts the distribution according of the given number of samples.
Exception
data XException Source #
Exceptions for random variables.
Instances
Exception XException Source # | |
Defined in OAlg.Data.X toException :: XException -> SomeException # fromException :: SomeException -> Maybe XException # displayException :: XException -> String # | |
Show XException Source # | |
Defined in OAlg.Data.X showsPrec :: Int -> XException -> ShowS # show :: XException -> String # showList :: [XException] -> ShowS # |