random-fu-0.0.3: Random number generationSource codeContentsIndex
Data.Random.Distribution.Ziggurat
Synopsis
data Ziggurat t = Ziggurat {
zTable_xs :: Vector t
zTable_x_ratios :: Vector t
zTable_ys :: Vector t
zGetIU :: RVar (Int, t)
zTailDist :: RVar t
zUniform :: t -> t -> RVar t
zFunc :: t -> t
zMirror :: Bool
}
mkZigguratRec
mkZiggurat :: (RealFloat t, Storable t, Distribution Uniform t) => Bool -> (t -> t) -> (t -> t) -> (t -> t) -> t -> Int -> RVar (Int, t) -> (t -> RVar t) -> Ziggurat t
mkZiggurat_ :: (RealFloat t, Storable t, Distribution Uniform t) => Bool -> (t -> t) -> (t -> t) -> Int -> t -> t -> RVar (Int, t) -> RVar t -> Ziggurat t
findBin0
runZiggurat :: (Num a, Ord a, Storable a) => Ziggurat a -> RVar a
Documentation
data Ziggurat t Source
Constructors
Ziggurat
zTable_xs :: Vector t
zTable_x_ratios :: Vector t
zTable_ys :: Vector t
zGetIU :: RVar (Int, t)
zTailDist :: RVar t
zUniform :: t -> t -> RVar t
zFunc :: t -> t
zMirror :: Bool
show/hide Instances
mkZigguratRec
mkZiggurat :: (RealFloat t, Storable t, Distribution Uniform t) => Bool -> (t -> t) -> (t -> t) -> (t -> t) -> t -> Int -> RVar (Int, t) -> (t -> RVar t) -> Ziggurat tSource

Build the tables to implement the ziggurat algorithm devised by Marsaglia & Tang, attempting to automatically compute the R and V values.

Arguments are the same as for |mkZigguratRec|, with an additional argument for the tail distribution as a function of the selected R value.

mkZiggurat_ :: (RealFloat t, Storable t, Distribution Uniform t) => Bool -> (t -> t) -> (t -> t) -> Int -> t -> t -> RVar (Int, t) -> RVar t -> Ziggurat tSource

Build the tables to implement the ziggurat algorithm devised by Marsaglia & Tang, attempting to automatically compute the R and V values.

Arguments:

  • flag indicating whether to mirror the distribution * the (one-sided antitone) CDF * the inverse of the CDF * the number of bins * R, the x value of the first bin * V, the volume of each bin * an RVar providing a random tuple consisting of: - a bin index, uniform over [0,c) :: Int - a uniformly distributed fractional value, from -1 to 1 if not mirrored, from 0 to 1 otherwise. * an RVar sampling from the tail (the region where x > R)
findBin0
runZiggurat :: (Num a, Ord a, Storable a) => Ziggurat a -> RVar aSource
Produced by Haddock version 2.4.2