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

CopyrightCopyright (c) 2009 Tracy Wadleigh
LicenseBSD3
MaintainerPatrick Perry <patperry@stanford.edu>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

GSL.Random.Quasi

Contents

Description

Quasi-random number generators.

Synopsis

Data types

newtype QRNG Source #

Constructors

MkQRNG (ForeignPtr QRNG) 

Instances

Eq QRNG Source # 

Methods

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

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

Data QRNG Source # 

Methods

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

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

toConstr :: QRNG -> Constr #

dataTypeOf :: QRNG -> DataType #

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

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

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

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

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

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

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

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

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

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

Show QRNG Source # 

Methods

showsPrec :: Int -> QRNG -> ShowS #

show :: QRNG -> String #

showList :: [QRNG] -> ShowS #

data QRNGType Source #

Instances

Eq QRNGType Source # 
Data QRNGType Source # 

Methods

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

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

toConstr :: QRNGType -> Constr #

dataTypeOf :: QRNGType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show QRNGType Source # 

Initializing

newQRNG :: QRNGType -> Int -> IO QRNG Source #

Allocate a new quasi-random number generator of the given type, generating points with the given number of dimensions.

resetQRNG :: QRNG -> IO () Source #

Reset the generator to the beginning of its sequence.

Sampling

getSample :: QRNG -> Ptr Double -> IO () Source #

Stores the next point from the generator in the given buffer. The space available in the buffer must match the dimension of the generator. The components of the sample will each lie in the range (0,1).

getListSample :: QRNG -> IO [Double] Source #

Gets the next sample point as a list.

Auxiliary functions

getName :: QRNG -> IO String Source #

Get the name of the generator.

getDimension :: QRNG -> IO Int Source #

The dimension of the sequence.

getSize :: QRNG -> IO Word64 Source #

Get the size of the generator state, in bytes.

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

Get the generator state.

setState :: QRNG -> [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

copyQRNG :: QRNG -> QRNG -> IO () Source #

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

cloneQRNG :: QRNG -> IO QRNG Source #

Allocate a new quasi-random number generator that is exact copy of another generator.

Algorithms

maxDimension :: QRNGType -> Int Source #

The maximum dimension of samples that the given generator supports.