random-fu-0.2.7.0: Random number generation

Safe HaskellNone
LanguageHaskell98

Data.Random.Distribution.Uniform

Synopsis

Documentation

data Uniform t Source #

A definition of a uniform distribution over the type t. See also uniform.

Constructors

Uniform !t !t

A uniform distribution defined by a lower and upper range bound. For Integral and Enum types, the range is inclusive. For Fractional types the range includes the lower bound but not the upper.

Instances

CDF Uniform Bool Source # 

Methods

cdf :: Uniform Bool -> Bool -> Double Source #

CDF Uniform Char Source # 

Methods

cdf :: Uniform Char -> Char -> Double Source #

CDF Uniform Double Source # 
CDF Uniform Float Source # 

Methods

cdf :: Uniform Float -> Float -> Double Source #

CDF Uniform Int Source # 

Methods

cdf :: Uniform Int -> Int -> Double Source #

CDF Uniform Int8 Source # 

Methods

cdf :: Uniform Int8 -> Int8 -> Double Source #

CDF Uniform Int16 Source # 

Methods

cdf :: Uniform Int16 -> Int16 -> Double Source #

CDF Uniform Int32 Source # 

Methods

cdf :: Uniform Int32 -> Int32 -> Double Source #

CDF Uniform Int64 Source # 

Methods

cdf :: Uniform Int64 -> Int64 -> Double Source #

CDF Uniform Integer Source # 
CDF Uniform Ordering Source # 
CDF Uniform Word Source # 

Methods

cdf :: Uniform Word -> Word -> Double Source #

CDF Uniform Word8 Source # 

Methods

cdf :: Uniform Word8 -> Word8 -> Double Source #

CDF Uniform Word16 Source # 
CDF Uniform Word32 Source # 
CDF Uniform Word64 Source # 
CDF Uniform () Source # 

Methods

cdf :: Uniform () -> () -> Double Source #

Distribution Uniform Bool Source # 
Distribution Uniform Char Source # 
Distribution Uniform Double Source # 
Distribution Uniform Float Source # 
Distribution Uniform Int Source # 
Distribution Uniform Int8 Source # 
Distribution Uniform Int16 Source # 
Distribution Uniform Int32 Source # 
Distribution Uniform Int64 Source # 
Distribution Uniform Integer Source # 
Distribution Uniform Ordering Source # 
Distribution Uniform Word Source # 
Distribution Uniform Word8 Source # 
Distribution Uniform Word16 Source # 
Distribution Uniform Word32 Source # 
Distribution Uniform Word64 Source # 
Distribution Uniform () Source # 

Methods

rvar :: Uniform () -> RVar () Source #

rvarT :: Uniform () -> RVarT n () Source #

HasResolution r => CDF Uniform (Fixed r) Source # 

Methods

cdf :: Uniform (Fixed r) -> Fixed r -> Double Source #

HasResolution r => Distribution Uniform (Fixed r) Source # 

Methods

rvar :: Uniform (Fixed r) -> RVar (Fixed r) Source #

rvarT :: Uniform (Fixed r) -> RVarT n (Fixed r) Source #

uniform :: Distribution Uniform a => a -> a -> RVar a Source #

uniformT :: Distribution Uniform a => a -> a -> RVarT m a Source #

data StdUniform t Source #

A name for the "standard" uniform distribution over the type t, if one exists. See also stdUniform.

For Integral and Enum types that are also Bounded, this is the uniform distribution over the full range of the type. For un-Bounded Integral types this is not defined. For Fractional types this is a random variable in the range [0,1) (that is, 0 to 1 including 0 but not including 1).

Constructors

StdUniform 

Instances

CDF StdUniform Bool Source # 
CDF StdUniform Char Source # 
CDF StdUniform Double Source # 
CDF StdUniform Float Source # 
CDF StdUniform Int Source # 

Methods

cdf :: StdUniform Int -> Int -> Double Source #

CDF StdUniform Int8 Source # 
CDF StdUniform Int16 Source # 
CDF StdUniform Int32 Source # 
CDF StdUniform Int64 Source # 
CDF StdUniform Ordering Source # 
CDF StdUniform Word Source # 
CDF StdUniform Word8 Source # 
CDF StdUniform Word16 Source # 
CDF StdUniform Word32 Source # 
CDF StdUniform Word64 Source # 
CDF StdUniform () Source # 

Methods

cdf :: StdUniform () -> () -> Double Source #

PDF StdUniform Double Source # 
PDF StdUniform Float Source # 
Distribution StdUniform Bool Source # 
Distribution StdUniform Char Source # 
Distribution StdUniform Double Source # 
Distribution StdUniform Float Source # 
Distribution StdUniform Int Source # 
Distribution StdUniform Int8 Source # 
Distribution StdUniform Int16 Source # 
Distribution StdUniform Int32 Source # 
Distribution StdUniform Int64 Source # 
Distribution StdUniform Ordering Source # 
Distribution StdUniform Word Source # 
Distribution StdUniform Word8 Source # 
Distribution StdUniform Word16 Source # 
Distribution StdUniform Word32 Source # 
Distribution StdUniform Word64 Source # 
Distribution StdUniform () Source # 

Methods

rvar :: StdUniform () -> RVar () Source #

rvarT :: StdUniform () -> RVarT n () Source #

HasResolution r => CDF StdUniform (Fixed r) Source # 

Methods

cdf :: StdUniform (Fixed r) -> Fixed r -> Double Source #

HasResolution r => Distribution StdUniform (Fixed r) Source # 

Methods

rvar :: StdUniform (Fixed r) -> RVar (Fixed r) Source #

rvarT :: StdUniform (Fixed r) -> RVarT n (Fixed r) Source #

stdUniform :: Distribution StdUniform a => RVar a Source #

Get a "standard" uniformly distributed variable. For integral types, this means uniformly distributed over the full range of the type (there is no support for Integer). For fractional types, this means uniformly distributed on the interval [0,1).

stdUniformT :: Distribution StdUniform a => RVarT m a Source #

Get a "standard" uniformly distributed process. For integral types, this means uniformly distributed over the full range of the type (there is no support for Integer). For fractional types, this means uniformly distributed on the interval [0,1).

stdUniformPos :: (Distribution StdUniform a, Num a, Eq a) => RVar a Source #

Like stdUniform but only returns positive values.

stdUniformPosT :: (Distribution StdUniform a, Num a, Eq a) => RVarT m a Source #

Like stdUniform but only returns positive values.

integralUniform :: Integral a => a -> a -> RVarT m a Source #

Compute a random Integral value between the 2 values provided (inclusive).

realFloatUniform :: RealFloat a => a -> a -> RVarT m a Source #

realFloatUniform a b computes a uniform random value in the range [a,b) for any RealFloat type

floatUniform :: Float -> Float -> RVarT m Float Source #

floatUniform a b computes a uniform random Float value in the range [a,b)

doubleUniform :: Double -> Double -> RVarT m Double Source #

doubleUniform a b computes a uniform random Double value in the range [a,b)

fixedUniform :: HasResolution r => Fixed r -> Fixed r -> RVarT m (Fixed r) Source #

fixedUniform a b computes a uniform random Fixed value in the range [a,b), with any desired precision.

enumUniform :: Enum a => a -> a -> RVarT m a Source #

realFloatUniform a b computes a uniform random value in the range [a,b) for any Enum type

boundedStdUniform :: (Distribution Uniform a, Bounded a) => RVar a Source #

Compute a random value for a Bounded type, between minBound and maxBound (inclusive for Integral or Enum types, in [minBound, maxBound) for Fractional types.)

boundedEnumStdUniform :: (Enum a, Bounded a) => RVarT m a Source #

Compute a random value for a Bounded Enum type, between minBound and maxBound (inclusive)

realFloatStdUniform :: RealFloat a => RVarT m a Source #

Compute a uniform random value in the range [0,1) for any RealFloat type

fixedStdUniform :: HasResolution r => RVarT m (Fixed r) Source #

Compute a uniform random Fixed value in the range [0,1), with any desired precision.

floatStdUniform :: RVarT m Float Source #

Compute a uniform random Float value in the range [0,1)

doubleStdUniform :: RVarT m Double Source #

Compute a uniform random Double value in the range [0,1)

realStdUniformCDF :: Real a => a -> Double Source #

The CDF of the random variable realFloatStdUniform.

realUniformCDF :: RealFrac a => a -> a -> a -> Double Source #

realUniformCDF a b is the CDF of the random variable realFloatUniform a b.

enumUniformCDF :: (Enum a, Ord a) => a -> a -> a -> Double Source #