
On May 10, 2020, at 3:20 PM, Viktor Dukhovni
wrote: I ended going with the below, with my module exporting only a higher-level interface that uses RWST internally, but exports a more abstract monad, hiding the implementation details.
{-# LANGUAGE ScopedTypeVariables #-} import qualified Control.Monad.Trans.RWS.CPS as RWS import Data.Coerce (coerce)
newtype RWST r w s m a = RWST (RWS.RWST r w s m a) deriving instance MonadTrans (RWST r w s) deriving instance (Monad m) => Functor (RWST r w s m) deriving instance (Monad m) => Applicative (RWST r w s m) deriving instance (Monad m) => Monad (RWST r w s m)
type EvalM f r w s m a = (Monoid w, Monad m) => f r w s m a -> r -> s -> m (a, w) evalRWST :: forall r w s m a. EvalM RWST r w s m a evalRWST = coerce (RWS.evalRWST :: EvalM RWS.RWST r w s m a)
[...]
I should probably mention that the reason I'm having to jump through these hoops with boilerplate code is that neither "mtl", nor "transformers" provide "MonadReader", "MonadWriter", "MonadState" or just "MonadRWS" instances for RWS.CPS, which might otherwise have made it possible to just replace all the coercions with: -- here MyRWST == a newtype-wrapped actual RWS.CPS.RWST deriving instance Monad m => MonadRWS r w s (MyRWST r w s m) along the lines of: https://hackage.haskell.org/package/writer-cps-mtl-0.1.1.6 Are there reasons why MTL cannot or should not do this? Or is this just something that the maintainer have not had a chance to consider or implement? [ The "mtl" MonadWriter type class has a narrower signature for "pass" where the inner monoid is the same as the outer monoid, but that's sufficient for my needs. ] -- Viktor.