{-# LANGUAGE
MultiParamTypeClasses,
FlexibleInstances, FlexibleContexts,
IncoherentInstances
#-}
{-# OPTIONS_GHC -fno-warn-simplifiable-class-constraints #-}
module Data.Random.Sample where
import Control.Monad.State
import Data.Random.Distribution
import Data.Random.Lift
import Data.Random.RVar
import Data.Random.Source
import Data.Random.Source.Std
import System.Random (RandomGen)
class Sampleable d m t where
sampleFrom :: RandomSource m s => s -> d t -> m t
instance Distribution d t => Sampleable d m t where
sampleFrom src d = runRVarT (rvar d) src
instance Lift m n => Sampleable (RVarT m) n t where
sampleFrom src x = runRVarT x src
sample :: (Sampleable d m t, MonadRandom m) => d t -> m t
sample = sampleFrom StdRandom
sampleState :: (RandomGen s, Sampleable d (State s) t, MonadRandom (State s)) => d t -> s -> (t, s)
sampleState thing = runState (sample thing)
sampleStateT :: (RandomGen s, Sampleable d (StateT s m) t, MonadRandom (StateT s m)) => d t -> s -> m (t, s)
sampleStateT thing = runStateT (sample thing)