Move MonadIO to base
wren ng thornton
wren at community.haskell.org
Sun Apr 18 17:12:55 EDT 2010
wren ng thornton wrote:
> Heinrich Apfelmus wrote:
>> Anders Kaseorg wrote:
>>> This concept can also be generalized to monad transformers:
>>>
>>> class MonadTrans t => MonadTransMorph t where
>>> morph :: Monad m => (forall b. (t m a -> m b) -> m b) -> t m a
>>
>> [...]
>> However, not all control operators can be lifted this way. Essentially,
>> while you may "downgrade" an arbitrary selection of t m a values you
>> may only promote one m a in return and all have to share the same
>> return type a . In particular, it's not possible to implement
>>
>> lift :: (Monad m, MonadTrans t) => m a -> t m a
>
> Why not?
> * morph says m(t m a) is a subset of (t m a)
> * Monad m says we can fmap :: (a->b) -> (m a->m b)
> * Monad (t m) says we can return :: a -> t m a
>
> lift ma = morph (\k -> k (fmap return ma))
Or rather,
lift ma = morph (\k -> join (fmap (k . return) ma))
That's what I get for typing without checking. The type of morph
requires us to Church-encode things needlessly; what we mean to say is:
morph (fmap return ma).
--
Live well,
~wren
More information about the Libraries
mailing list