[Haskell-cafe] Coercing newtype-wrapped monad transformers?
宮里洸司
viercc at gmail.com
Sun May 10 14:28:43 UTC 2020
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 <viercc at gmail.com> */
More information about the Haskell-Cafe
mailing list