[Haskell-cafe] Help with triple stack monad

Chris Wong lambda.fairy at gmail.com
Tue Jun 21 09:57:57 UTC 2016


Since the monad type `m` only appears to the right of the arrow, we
can write the instance using `lift`:

instance RandomGen g => MonadRandom (ReaderStateRandom r s g) where
    getRandom = RSR . lift . lift $ getRandom

On Tue, Jun 21, 2016 at 6:12 PM, Christopher Howard <ch.howard at zoho.com> wrote:
> Hi, I was expanding on my earlier learning, to try a triple monad stack:
>
> {-# LANGUAGE GeneralizedNewtypeDeriving #-}
>
> <...snip...>
>
> import System.Random
> 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 (Monad, MonadReader r, MonadState s)
>
> However, it seems that I must implement MonadRandom myself, as there is
> no instance for this sort of arrangement already. Probably this is
> trivial, but I'm having trouble wrapping my mind around how to do it.
> Would anybody perhaps assist me in implementing one function, to help
> guide me in the correct direction?
>
> instance MonadRandom (ReaderStateRandom r s g) where
>
>   getRandom = ...?
>
>
> --
> http://justonemoremathproblem.com
> To protect my privacy, please use PGP encryption. It's free and easy
> to use! My public key ID is 0x340EA95A (pgp.mit.edu).
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.



-- 
Chris Wong (https://lambda.xyz)

"I had not the vaguest idea what this meant and when I could not
remember the words, my tutor threw the book at my head, which did not
stimulate my intellect in any way." -- Bertrand Russell


More information about the Haskell-Cafe mailing list