polysemy-RandomFu-0.4.0.0: Experimental, RandomFu effect and interpreters for polysemy

Safe HaskellNone
LanguageHaskell2010

Polysemy.RandomFu

Contents

Description

Polysemy "random-fu" effect. This can be run in a few ways: 1. Directly in IO 2. Using any RandomSource from "random-fu" 3. In IO, using a given PureMT source. (IO is used to put the source in an IORef)

This module also contains the type-class instances to enable "absorbing" MonadRandom, ala Polysemy.MTL. See the tests for MTL or RandomFu for examples of that in use.

Synopsis

Effect

data RandomFu m r where Source #

An effect capable of sampling from a "random-fu" RVar or generating a single random-variate of any type, t with a Data.Random.Prim t constructor, currently one of Word8, Word16, Word32, Word64, Double or N-byte integer.

Constructors

SampleRVar :: RVar t -> RandomFu m t 
GetRandomPrim :: Prim t -> RandomFu m t 
Instances
type DefiningModule (RandomFu :: k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.RandomFu

type DefiningModule (RandomFu :: k -> Type -> Type) = "Polysemy.RandomFu"

Actions

sampleRVar :: forall r t. MemberWithError RandomFu r => RVar t -> Sem r t Source #

getRandomPrim :: forall r t. MemberWithError RandomFu r => Prim t -> Sem r t Source #

sampleDist :: (Member RandomFu r, Distribution d t) => d t -> Sem r t Source #

use the RandomFu effect to sample from a "random-fu" Distribution.

Interpretations

runRandomSource :: forall s m r a. (RandomSource m s, Member (Embed m) r) => s -> Sem (RandomFu ': r) a -> Sem r a Source #

Run a Random effect using a given RandomSource

runRandomIO :: forall r a. MonadIO (Sem r) => Sem (RandomFu ': r) a -> Sem r a Source #

Run a Random effect by using the default "random-fu" IO source

runRandomIOPureMT :: Member (Embed IO) r => PureMT -> Sem (RandomFu ': r) a -> Sem r a Source #

Run in IO, using the given PureMT source, stored in an IORef