
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.