{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# OPTIONS_HADDOCK hide #-} {-| Module : Graphics.Mars.ReaderStateRandom Description : A triple-stack convenience monad. Copyright : (c) Christopher Howard, 2016 License : GPL-3 Maintainer : ch.howard@zoho.com Stacks the Reader, Lazy State, and Random monads together. -} module Graphics.Mars.ReaderStateRandom ( module System.Random , module Control.Monad.Reader , module Control.Monad.State.Lazy , module Control.Monad.Random , ReaderStateRandom(..) , runRSR , evalRSR , execRSR ) where import System.Random import Control.Applicative import Control.Monad.Random import Control.Monad.State.Lazy import Control.Monad.Reader newtype ReaderStateRandom r s g a = RSR { rSR :: ReaderT r (StateT s (Rand g)) a } deriving (Functor, Applicative, Monad, MonadReader r, MonadState s) instance RandomGen g => MonadRandom (ReaderStateRandom r s g) where getRandom = (RSR . lift . lift) getRandom getRandoms = (RSR . lift . lift) getRandoms getRandomR = \a -> (RSR . lift . lift) (getRandomR a) getRandomRs = \a -> (RSR . lift . lift) (getRandomRs a) runRSR m r s g = let ((a', s'), g') = runRand (runStateT (runReaderT (rSR m) r) s) g in (a', (s', g')) evalRSR m r s = fst . runRSR m r s execRSR m r s = snd . runRSR m r s