gsl-random-0.5.1: Bindings the the GSL random number generation facilities.

CopyrightCopyright (c) Patrick Perry <patperry@stanford.edu>
LicenseBSD3
MaintainerPatrick Perry <patperry@stanford.edu>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

GSL.Random.Gen

Contents

Description

Random number generators.

Synopsis

Data types

newtype RNG Source #

Constructors

MkRNG (ForeignPtr ()) 

Instances

Eq RNG Source # 

Methods

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

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

Data RNG Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RNG -> c RNG #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RNG #

toConstr :: RNG -> Constr #

dataTypeOf :: RNG -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RNG) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RNG) #

gmapT :: (forall b. Data b => b -> b) -> RNG -> RNG #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RNG -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RNG -> r #

gmapQ :: (forall d. Data d => d -> u) -> RNG -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RNG -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RNG -> m RNG #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RNG -> m RNG #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RNG -> m RNG #

Show RNG Source # 

Methods

showsPrec :: Int -> RNG -> ShowS #

show :: RNG -> String #

showList :: [RNG] -> ShowS #

data RNGType Source #

Instances

Eq RNGType Source # 

Methods

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

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

Data RNGType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RNGType -> c RNGType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RNGType #

toConstr :: RNGType -> Constr #

dataTypeOf :: RNGType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RNGType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RNGType) #

gmapT :: (forall b. Data b => b -> b) -> RNGType -> RNGType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RNGType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RNGType -> r #

gmapQ :: (forall d. Data d => d -> u) -> RNGType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RNGType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RNGType -> m RNGType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RNGType -> m RNGType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RNGType -> m RNGType #

Show RNGType Source # 

Initializing

newRNG :: RNGType -> IO RNG Source #

Allocate a new random number generator of the given type and initialize it with the default seed.

setSeed :: RNG -> Word64 -> IO () Source #

Seed the generator with the given value.

Sampling

getSample :: RNG -> IO Word64 Source #

Returns a value uniform in [rngMin, rngMax]

getUniform :: RNG -> IO Double Source #

Returns a value uniform on [0,1)

getUniformPos :: RNG -> IO Double Source #

Returns a value uniform on (0,1)

getUniformInt :: RNG -> Int -> IO Int Source #

Returns an integer uniform on [0,n-1]. n must be greater than 0.

Auxiliary functions

getName :: RNG -> IO String Source #

Get the name of the generator.

getMax :: RNG -> IO Word64 Source #

Get the largest value that the generator can return.

getMin :: RNG -> IO Word64 Source #

Get the smallest value that the generator can return.

getSize :: RNG -> IO Word64 Source #

Get the size of the generator state, in bytes.

getState :: RNG -> IO [Word8] Source #

Get the generator state.

setState :: RNG -> [Word8] -> IO () Source #

Set the generator state. The input array should have size equal to getSize of the generator; otherwise, strange things will happen.

Copying state

copyRNG :: RNG -> RNG -> IO () Source #

copyRNG dst src copies the state from one generator to another. The two generators must have the same type.

cloneRNG :: RNG -> IO RNG Source #

Allocate a new random number generator that is an exact copy of another generator

Algorithms