| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Random.Source
Contents
Synopsis
- class Monad m => MonadRandom m where- getRandomWord8 :: m Word8
- getRandomWord16 :: m Word16
- getRandomWord32 :: m Word32
- getRandomWord64 :: m Word64
- getRandomDouble :: m Double
- getRandomNByteInteger :: MonadRandom m => Int -> m Integer
 
- class Monad m => RandomSource m s where- getRandomWord8From :: s -> m Word8
- getRandomWord16From :: s -> m Word16
- getRandomWord32From :: s -> m Word32
- getRandomWord64From :: s -> m Word64
- getRandomDoubleFrom :: s -> m Double
- getRandomNByteIntegerFrom :: s -> Int -> m Integer
 
- monadRandom :: Q [Dec] -> Q [Dec]
- randomSource :: Q [Dec] -> Q [Dec]
Documentation
class Monad m => MonadRandom m where Source #
A typeclass for monads with a chosen source of entropy.  For example,
 RVar is such a monad - the source from which it is (eventually) sampled
 is the only source from which a random variable is permitted to draw, so
 when directly requesting entropy for a random variable these functions
 are used.
Minimum implementation is either the internal getRandomPrim or all
 other functions.  Additionally, this class's interface is subject to 
 extension at any time, so it is very, very strongly recommended that
 the monadRandom Template Haskell function be used to implement this 
 function rather than directly implementing it.  That function takes care
 of choosing default implementations for any missing functions; as long as
 at least one function is implemented, it will derive sensible 
 implementations of all others.
To use monadRandom, just wrap your instance declaration as follows (and
 enable the TemplateHaskell and GADTs language extensions):
$(monadRandom [d|
        instance MonadRandom FooM where
            getRandomDouble = return pi
            getRandomWord16 = return 4
            {- etc... -}
    |])Minimal complete definition
Nothing
Methods
getRandomWord8 :: m Word8 Source #
Generate a uniformly distributed random Word8
getRandomWord16 :: m Word16 Source #
Generate a uniformly distributed random Word16
getRandomWord32 :: m Word32 Source #
Generate a uniformly distributed random Word32
getRandomWord64 :: m Word64 Source #
Generate a uniformly distributed random Word64
getRandomDouble :: m Double Source #
Generate a uniformly distributed random Double in the range 0 <= U < 1
getRandomNByteInteger :: MonadRandom m => Int -> m Integer Source #
Generate a uniformly distributed random Integer in the range 0 <= U < 256^n
Instances
class Monad m => RandomSource m s where Source #
A source of entropy which can be used in the given monad.
See also MonadRandom.
Minimum implementation is either the internal getRandomPrimFrom or all
 other functions.  Additionally, this class's interface is subject to 
 extension at any time, so it is very, very strongly recommended that
 the randomSource Template Haskell function be used to implement this 
 function rather than directly implementing it.  That function takes care
 of choosing default implementations for any missing functions; as long as
 at least one function is implemented, it will derive sensible 
 implementations of all others.
To use randomSource, just wrap your instance declaration as follows (and
 enable the TemplateHaskell, MultiParamTypeClasses and GADTs language
 extensions, as well as any others required by your instances, such as
 FlexibleInstances):
$(randomSource [d|
        instance RandomSource FooM Bar where
            {- at least one RandomSource function... -}
    |])Minimal complete definition
Nothing
Methods
getRandomWord8From :: s -> m Word8 Source #
Generate a uniformly distributed random Word8
getRandomWord16From :: s -> m Word16 Source #
Generate a uniformly distributed random Word16
getRandomWord32From :: s -> m Word32 Source #
Generate a uniformly distributed random Word32
getRandomWord64From :: s -> m Word64 Source #
Generate a uniformly distributed random Word64
getRandomDoubleFrom :: s -> m Double Source #
Generate a uniformly distributed random Double in the range 0 <= U < 1
getRandomNByteIntegerFrom :: s -> Int -> m Integer Source #
Generate a uniformly distributed random Integer in the range 0 <= U < 256^n
Instances
monadRandom :: Q [Dec] -> Q [Dec] Source #
Complete a possibly-incomplete Context implementation.  It is 
 recommended that this macro be used even if the implementation is currently
 complete, as the Context class may be extended at any time.
To use monadRandom, just wrap your instance declaration as follows (and
 enable the TemplateHaskell and GADTs language extensions):
$(monadRandom [d|
        instance MonadRandom FooM where
            getRandomDouble = return pi
            getRandomWord16 = return 4
            {- etc... -}
    |])randomSource :: Q [Dec] -> Q [Dec] Source #
Complete a possibly-incomplete Context implementation.  It is 
 recommended that this macro be used even if the implementation is currently
 complete, as the Context class may be extended at any time.
To use randomSource, just wrap your instance declaration as follows (and
 enable the TemplateHaskell, MultiParamTypeClasses and GADTs language
 extensions, as well as any others required by your instances, such as
 FlexibleInstances):
$(randomSource [d|
        instance RandomSource FooM Bar where
            {- at least one RandomSource function... -}
    |])