
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).

Just manually unrolling the definitions for ReaterT and StateT, I think
this is correct.
instance RandomGen g => MonadRandom (ReaderStateRandom r s g) where
getRandom = RSR (ReaderT (\r -> StateT (\s -> getRandom >>= (\random ->
return (random,s)))))
Or, using TupleSelections,
RSR (ReaderT (\r -> StateT (\s -> (,s) <$> getRandom)))
You could also write this out in terms of execReaderT, execStateT, etc. but
I couldn't be arsed.
You also have to add Applicative and Functor instances to RSR.
Cheers,
Will
On Mon, Jun 20, 2016 at 11:12 PM, Christopher Howard
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.

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
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

On 2016-06-21 at 02:12, Christopher Howard
However, it seems that I must implement MonadRandom myself, as there is no instance for this sort of arrangement already.
Deriving the class also works, at least with GHC-7.10.3: newtype ReaderStateRandom r s g a = RSR { rSR :: ReaderT r (StateT s (Rand g)) a } deriving (Functor, Applicative, Monad, MonadReader r, MonadState s, MonadRandom) bergey

This doesn't seem to work for me, but I'm using 7.6.3 from Debian Jessie. I'm curious what the difference is. What extensions and modules do you import? I get error ReaderStateRandom.hs:19:73: No instance for (MonadRandom (ReaderT r (StateT s (Rand g)))) arising from the 'deriving' clause of a data type declaration Possible fix: add an instance declaration for (MonadRandom (ReaderT r (StateT s (Rand g)))) or use a standalone 'deriving instance' declaration, so you can specify the instance context yourself When deriving the instance for (MonadRandom (ReaderStateRandom r s g)) On 06/21/2016 09:33 AM, Daniel Bergey wrote:
On 2016-06-21 at 02:12, Christopher Howard
wrote: However, it seems that I must implement MonadRandom myself, as there is no instance for this sort of arrangement already.
Deriving the class also works, at least with GHC-7.10.3:
newtype ReaderStateRandom r s g a = RSR { rSR :: ReaderT r (StateT s (Rand g)) a } deriving (Functor, Applicative, Monad, MonadReader r, MonadState s, MonadRandom)
bergey
-- 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).

On 2016-06-21 at 21:12, Christopher Howard
This doesn't seem to work for me, but I'm using 7.6.3 from Debian Jessie. I'm curious what the difference is. What extensions and modules do you import? I get error
That's very interesting. Here's my full code. I needed to add the `Control.Applicative` import for GHC-7.6. In GHC-7.10, Applicative is in Prelude. {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Test where import Control.Applicative import Control.Monad.Random import Control.Monad.Reader import Control.Monad.State.Lazy newtype ReaderStateRandom r s g a = RSR { rSR :: ReaderT r (StateT s (Rand g)) a } deriving (Functor, Applicative, Monad, MonadReader r, MonadState s, MonadRandom)
participants (4)
-
Chris Wong
-
Christopher Howard
-
Daniel Bergey
-
William Yager