
The code sample below my signature wraps RWS.CPS in a newtype, with a view to presenting a more constrained interface with specific functions that internall use the underlying RWST features. It is straightforward to construct the appropriate variants of "ask", "get", "put", "tell", ... via appropriate applications of the FooT constructor and accessor, but I expected to be able to use "coerce", along the lines of: ask :: Monad m => RWST r w s m r ask = coerce M.ask but that fails with: foo.hs:34:7: error: • Couldn't match representation of type ‘m0’ with that of ‘m’ arising from a use of ‘coerce’ ‘m’ is a rigid type variable bound by the type signature for: ask :: forall (m :: * -> *) r w s. Monad m => FooT r w s m r at foo.hs:21:1-34 • In the expression: coerce M.ask In an equation for ‘ask’: ask = coerce M.ask • Relevant bindings include ask :: FooT r w s m r (bound at foo.hs:34:1) Somehow between the various constraints and quantifiers in play, coerce is unable to do what I expected. Should it have worked? If had worked, would the effect have been in fact any different (more efficient?) than what I get with the explicit applications of the constructor and accessor? -- Viktor. {-# LANGUAGE GeneralizedNewtypeDeriving, FlexibleInstances, MultiParamTypeClasses, StandaloneDeriving #-} import Control.Monad.Trans.Class import qualified Control.Monad.Trans.RWS.CPS as M newtype FooT r w s m a = FooT { unFooT :: M.RWST r w s m a } deriving instance (Functor m) => Functor (FooT r w s m) deriving instance (Monad m) => Applicative (FooT r w s m) deriving instance (Monad m) => Monad (FooT r w s m) deriving instance MonadTrans (FooT r w s) runFooT :: (Monoid w, Monad m) => FooT r w s m a -> r -> s -> m (a, s, w) execFooT :: (Monoid w, Monad m) => FooT r w s m a -> r -> s -> m (s, w) evalFooT :: (Monoid w, Monad m) => FooT r w s m a -> r -> s -> m (a, w) ask :: (Monad m) => FooT r w s m r asks :: (Monad m) => (r -> a) -> FooT r w s m a get :: (Monad m) => FooT r w s m s gets :: (Monad m) => (s -> a) -> FooT r w s m a modify :: (Monad m) => (s -> s) -> FooT r w s m () pass :: (Monoid w, Monoid w', Monad m) => FooT r w' s m (a, w' -> w) -> FooT r w s m a put :: (Monad m) => s -> FooT r w s m () tell :: (Monoid w, Monad m) => w -> FooT r w s m () runFooT = M.runRWST . unFooT evalFooT = M.evalRWST . unFooT execFooT = M.execRWST . unFooT ask = FooT $ M.ask asks = FooT . M.asks get = FooT $ M.get gets = FooT . M.gets modify = FooT . M.modify pass = FooT . M.pass . unFooT put = FooT . M.put tell = FooT . M.tell main :: IO () main = runFooT mfoo "read me" "set me" >>= print where mfoo = do ask >>= modify . (. (" or " ++)) . (++) tell "Hello" pass $ do tell "World!" pure (42, (' ':))