polysemy-RandomFu-0.1.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 r. Member RandomFu r => RVar r -> Sem r r Source #

getRandomPrim :: forall r r. Member RandomFu r => Prim r -> Sem r r 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 r a. RandomSource (Sem r) s => 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 :: MonadIO (Sem r) => PureMT -> Sem (RandomFu ': r) a -> Sem r a Source #

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

Constraint absorber

absorbMonadRandom :: Member RandomFu r => (MonadRandom (Sem r) => Sem r a) -> Sem r a Source #

Absorb an MonadRandom constraint. That is, use a Member RandomFu r constraint to satisfy the MonadRandom constraint in a (forall m. MonadRandom m => m a), returning a Sem r a@. See MTL for details.

Orphan instances

ReifiableConstraint1 MonadRandom Source # 
Instance details

Associated Types

data Dict1 MonadRandom m :: Type

Methods

reifiedInstance :: Monad m => Reifies s (Dict1 MonadRandom m) :- MonadRandom (ConstrainedAction MonadRandom m s)

Member (RandomFu :: (Type -> Type) -> Type -> Type) r => IsCanonicalEffect MonadRandom r Source # 
Instance details

Methods

canonicalDictionary :: Dict1 MonadRandom (Sem r)

(Monad m, Reifies s' (Dict1 MonadRandom m)) => MonadRandom (ConstrainedAction MonadRandom m s') Source # 
Instance details

Methods

getRandomPrim :: Prim t -> ConstrainedAction MonadRandom m s' t

getRandomWord8 :: ConstrainedAction MonadRandom m s' Word8

getRandomWord16 :: ConstrainedAction MonadRandom m s' Word16

getRandomWord32 :: ConstrainedAction MonadRandom m s' Word32

getRandomWord64 :: ConstrainedAction MonadRandom m s' Word64

getRandomDouble :: ConstrainedAction MonadRandom m s' Double

getRandomNByteInteger :: Int -> ConstrainedAction MonadRandom m s' Integer