oalg-base-1.1.4.0: Algebraic structures on oriented entities and limits as a tool kit to solve algebraic problems.
Copyright(c) Erich Gut
LicenseBSD3
Maintainerzerich.gut@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

OAlg.Data.X

Description

Random variables for stochastical validation.

Synopsis

Random Variable

data X x Source #

random variable over x, possibly XEmpty. Let x be a type and xx in X x, then we use the idiom x is in the range of xx if there exist a o in Omega such that x is an element of samples xx o.

Note

  1. For the empty set O there is exactly one sigma algebra, i.e. the power set of the empty set O, and for every set X there is exactly one measurable function O -> X, i.e. the empty function, and hence exactly one random variable over O.
  2. To not run into non terminating programs, we restrict the implementation of xa >>= f to a maximal number of iterations to find a suitable sample in xa for which f a is not empty. If the iterations exceed this maximum number, a ProbablyEmpty exception will be thrown.

Constructors

XEmpty 

Instances

Instances details
MonadFail X Source # 
Instance details

Defined in OAlg.Data.X

Methods

fail :: String -> X a #

Alternative X Source # 
Instance details

Defined in OAlg.Data.X

Methods

empty :: X a #

(<|>) :: X a -> X a -> X a #

some :: X a -> X [a] #

many :: X a -> X [a] #

Applicative X Source # 
Instance details

Defined in OAlg.Data.X

Methods

pure :: a -> X a #

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

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

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

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

Functor X Source # 
Instance details

Defined in OAlg.Data.X

Methods

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

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

Monad X Source # 
Instance details

Defined in OAlg.Data.X

Methods

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

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

return :: a -> X a #

MonadPlus X Source # 
Instance details

Defined in OAlg.Data.X

Methods

mzero :: X a #

mplus :: X a -> X a -> X a #

HNFData (X x) Source # 
Instance details

Defined in OAlg.Data.X

Methods

rhnf :: X x -> () Source #

Validable a => Validable (X a) Source # 
Instance details

Defined in OAlg.Data.Validable

Methods

valid :: X a -> Statement Source #

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 '[]'.

getSamples Source #

Arguments

:: N

length of the returned list

-> X x 
-> IO [x] 

gets a list of randomly picked samples.

sample :: X x -> Omega -> x Source #

the first element of samples xx o. If xx is empty then a IsEmpty exception will be thrown.

Statistics

meanValue :: Fractional x => Int -> X x -> Omega -> x Source #

the mean value of n-samples according the state s.

Omega

data Omega Source #

A possible state of the world. It is used for run or samples to generate randomly values.

Instances

Instances details
Show Omega Source # 
Instance details

Defined in OAlg.Data.X

Methods

showsPrec :: Int -> Omega -> ShowS #

show :: Omega -> String #

showList :: [Omega] -> ShowS #

Eq Omega Source # 
Instance details

Defined in OAlg.Data.X

Methods

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

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

mkOmega :: Int -> Omega Source #

makes a state.

getOmega :: IO Omega Source #

gets randomly a state.

X

xOmega :: X Omega Source #

random variable of Omega.

xInt :: X Int Source #

uniformly distributed random variable of Ints.

xIntB :: Int -> Int -> X Int Source #

uniformly distributed random variable of Ints in the given range. If the lower bound is greater then the upper bound the result will be XEmpty.

xWord :: X Word Source #

uniformly distributed random variable of Words.

xWordB :: Word -> Word -> X Word Source #

uniformly distributed random variable of Words in the given range. If the lower bound is greater then the upper bound the result will be XEmpty.

xInteger :: X Integer Source #

uniformly distributed random variable of Integers.

xIntegerB :: Integer -> Integer -> X Integer Source #

uniformly distributed random variable of Integers in the given range. If the lower bound is greater then the upper bound the result will be XEmpty.

xChar :: X Char Source #

uniformly distributed random variable of Chars.

xCharB :: Char -> Char -> X Char Source #

uniformly distributed random variable of Chars in the given range. If the lower bound is greater then the upper bound the result will be XEmpty.

xDouble :: X Double Source #

uniformly distributed random variable of Doubles.

xDoubleB :: Double -> Double -> X Double Source #

uniformly distributed random variable of Doubles in the given range. If the lower bound is greater then the upper bound the result will be XEmpty.

xEnum :: (Enum a, Bounded a) => X a Source #

uniformly distributed random variable of a Bounded Enum in the range minBound to maxBound.

xEnumB :: Enum a => a -> a -> X a Source #

uniformly distributed random variable of a Enum in the given range. If the lower bound is greater then the upper bound the result will be XEmpty.

xBool :: X Bool Source #

uniformly distributed random variable of Bools.

xTupple2 :: X a -> X b -> X (a, b) Source #

random variable for pairs.

xTupple3 :: X a -> X b -> X c -> X (a, b, c) Source #

random variable for triples.

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.

xList :: [X x] -> X [x] Source #

random variable of list.

xOneOf :: [a] -> X a Source #

xOneOf xs is the random variable of xs in xs with a uniformly distribution of the xis, where 0 < length xs. If xs == [] then XEmpty will be the result.

xOneOfX :: [X a] -> X a Source #

as xOneOf.

xOneOfW :: [(Q, a)] -> X a Source #

xOneOfW [(w1,x1)..(wn,xn)] is the random variable of xs in [x1,x2,..xn] with a distribution of the xis 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.

xOneOfXW :: [(Q, X a)] -> X a Source #

xN :: X N Source #

uniformly distributed random variable in the given range.

xNB :: N -> N -> X N Source #

uniformly distributed random variable in the given range. If the lower bound is greater then the upper bound the result will be XEmpty.

xZ :: X Z Source #

uniformly distributed random variable of Z.

xZB :: Z -> Z -> X Z Source #

uniformly distributed random variable of Z in the given bounds. If the lower bound is greater then the upper bound the result will be XEmpty.

xQ :: X Q Source #

uniformly distributed random variable of Q.

Tools

sum' :: Num x => [x] -> x Source #

a strict and head recursive version of sum.

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.

aspCnstr :: Show x => x -> String Source #

showing the constructor as an aspect.

Exception

data XException Source #

Exceptions for random variables.

Instances

Instances details
Exception XException Source # 
Instance details

Defined in OAlg.Data.X

Show XException Source # 
Instance details

Defined in OAlg.Data.X