Coercing newtype-wrapped monad transformers?

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, (' ':))

Hello, I think I can answer. In the failing code, the type of "M.ask" have no constraint, so it gets the type "(Monad m0) => M.RWST r0 w0 s0 m0 r0", where "r0, w0, s0, m0" are some unconstrained types. To resolve "Coercible (M.RWST r0 w0 s0 m0 r0) (FooT r w s m r)", you can You want "m0" be equal to "m", but it can't be inferred.
ask :: Monad m => RWST r w s m r -- You mean FooT? ask = coerce M.ask
This error can be fixed by specifying concrete type you want.
{-# LANGUAGE ScopedTypeVariables #-}
ask :: forall m r w s. Monad m => FooT r w s m r
ask = coerce (M.ask :: M.RWST r w s m r)
Or, you can make a specialized coerce function:
{-# LANGUAGE PolyKinds #-}
coerce5 :: Coercible f g => f r w s m a -> g r w s m a
coerce5 = coerce
ask :: Monad m => FooT r w s m r
ask = coerce5 M.ask
--
/* Koji Miyazato

On Sun, May 10, 2020 at 11:28:43PM +0900, 宮里洸司 wrote:
Hello, I think I can answer.
Many thanks, you answer was perfect.
In the failing code, the type of "M.ask" have no constraint, so it gets the type "(Monad m0) => M.RWST r0 w0 s0 m0 r0", where "r0, w0, s0, m0" are some unconstrained types.
To resolve "Coercible (M.RWST r0 w0 s0 m0 r0) (FooT r w s m r)", you can
You want "m0" be equal to "m", but it can't be inferred.
ask :: Monad m => RWST r w s m r -- You mean FooT? [yes] ask = coerce M.ask
This error can be fixed by specifying concrete type you want.
{-# LANGUAGE ScopedTypeVariables #-} ask :: forall m r w s. Monad m => FooT r w s m r ask = coerce (M.ask :: M.RWST r w s m r)
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) type AskM f r w s m = Monad m => f r w s m r ask :: forall r w s m. AskM RWST r w s m ask = coerce (RWS.ask :: AskM RWS.RWST r w s m) type GetM f r w s m = Monad m => f r w s m s get :: forall r w s m. GetM RWST r w s m get = coerce (RWS.get :: GetM RWS.RWST r w s m) type PutM f r w s m = (Monad m) => s -> f r w s m () put :: forall r w s m. PutM RWST r w s m put = coerce (RWS.put :: PutM RWS.RWST r w s m) type TellM f r w s m = (Monoid w, Monad m) => w -> f r w s m () tell :: forall r w s m. TellM RWST r w s m tell = coerce (RWS.tell :: TellM RWS.RWST r w s m) type GetsM f r w s m a = Monad m => (s -> a) -> f r w s m a gets :: forall r w s m a. GetsM RWST r w s m a gets = coerce (RWS.gets :: GetsM RWS.RWST r w s m a) type LocalM f r w s m a = Monad m => (r -> r) -> f r w s m a -> f r w s m a local :: forall r w s m a. LocalM RWST r w s m a local = coerce (RWS.local :: LocalM RWS.RWST r w s m a) type PassM f r w s m a w' = (Monoid w, Monoid w', Monad m) => f r w' s m (a, w' -> w) -> f r w s m a pass :: forall r w s m a w'. PassM RWST r w s m a w' pass = coerce (RWS.pass :: PassM RWS.RWST r w s m a w') ... etc. if/as more are needed later ... -- Viktor.

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.

On May 10, 2020, at 19:55, Viktor Dukhovni
wrote: 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,
The instances are already present on master (I added them) but they have not yet been released to Hackage. Remarkably, mtl seems to be without a maintainer. See https://github.com/haskell/mtl/issues/69 https://github.com/haskell/mtl/issues/69. Alexis

On May 11, 2020, at 2:30 PM, Alexis King
wrote: 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,
The instances are already present on master (I added them) but they have not yet been released to Hackage. Remarkably, mtl seems to be without a maintainer. See https://github.com/haskell/mtl/issues/69.
Thanks! Good to know these are at least in the pipeline. Perhaps some day I'll get to trim the boilerplate down to just: "deriving instance MonadRWS". Good luck finding someone to cut the release... -- Viktor.
participants (3)
-
Alexis King
-
Viktor Dukhovni
-
宮里洸司