| Safe Haskell | Safe-Inferred |
|---|
Control.Monad.Random
Description
This module provides efficient and intuitive ways to build and manipulate random variables of all kinds.
The following is an example of generating combinations for a slot machine.
import Control.Monad.Random
import Control.Applicative
import Control.Monad
data Slot = Lemon
| Cherry
| Strawberry
| Orange
| Bar
| Seven
deriving (Enum, Show)
data Combination = Combination Slot Slot Slot deriving Show
fairSlot = oneOf [Lemon .. Seven]
fairCombination = Combination <$> fairSlot <*> fairSlot <*> fairSlot
biasedSlot = fromFreqs [Lemon `withFreq` 1,
Cherry `withFreq` 1,
Strawberry `withFreq` 1.2,
Orange `withFreq` 1.1,
Bar `withFreq` 0.9,
Seven `withFreq` 0.8]
biasedCombination = Combination <$> biasedSlot
<*> biasedSlot
<*> biasedSlot
aTripToAMachine = do
combination <- fromFreqs [fairCombination `withFreq` 10,
biasedCombination `withFreq` 5]
rounds <- inRange (5, 50)
replicateM rounds combination
aTripToTheCasino = do
trips <- fmap (*3) $ inRange (1, 10)
fmap concat $ replicateM trips aTripToAMachine
main = pick aTripToTheCasino >>= print
- class RandPicker m where
- type MonadRand m = (Monad m, RandPicker m)
- newtype Rand a = Rand {}
- evalRand :: RandomGen g => Rand a -> g -> a
- execRand :: RandomGen g => Rand a -> g -> g
- rand :: Random a => Rand a
- oneOf :: [a] -> Rand a
- inRange :: Random a => (a, a) -> Rand a
- fromFreqs :: Real b => [(a, b)] -> Rand a
- withFreq :: Real b => a -> b -> (a, b)
- newtype RandT m a = RandT {}
- evalRandT :: (RandomGen g, Monad m) => RandT m a -> g -> m a
- execRandT :: (RandomGen g, Monad m) => RandT m a -> g -> m g
RandPicker class
class RandPicker m whereSource
Class supporting the return of a random element.
Instances
| RandPicker IO | |
| RandPicker Rand | |
| Monad m => RandPicker (RandT m) |
type MonadRand m = (Monad m, RandPicker m)Source
Rand Monad
Random variable of a.
Instances
evalRand :: RandomGen g => Rand a -> g -> aSource
Run the random variable and returns only its value. The new generator is lost.
execRand :: RandomGen g => Rand a -> g -> gSource
Run the random variable and returns only the new RandomGen.
Creation of random variables
inRange :: Random a => (a, a) -> Rand aSource
Distribution within a given range, provided by randomR.
fromFreqs :: Real b => [(a, b)] -> Rand aSource
Distribution of elements proportionately to their indicated frequency.
RandT Monad
Instances
| MonadTrans RandT | |
| (Monad (RandT m), MonadReader r m) => MonadReader r (RandT m) | |
| (Monad (RandT m), MonadState s m) => MonadState s (RandT m) | |
| (Monoid w, Monad (RandT m), MonadWriter w m) => MonadWriter w (RandT m) | |
| Monad m => Monad (RandT m) | |
| Functor m => Functor (RandT m) | |
| (Monad (RandT m), MonadPlus m) => MonadPlus (RandT m) | |
| (Functor (RandT m), Applicative m) => Applicative (RandT m) | |
| (Monad (RandT m), MonadIO m) => MonadIO (RandT m) | |
| Monad m => RandPicker (RandT m) |