<div dir="ltr">Interesting. It&#39;s similar in spirit to basically a safe Coerce typeclass, but for * -&gt; * types.<div><br></div><div>    class Coerce a b where</div><div>      coerce :: a -&gt; b</div><div><br></div><div>

    class Coerce1 f g where</div><div>      coerce1 :: f a -&gt; g a</div><div><br></div><div><br></div></div><div class="gmail_extra"><br clear="all"><div>-- Dan Burton</div>
<br><br><div class="gmail_quote">On Tue, Oct 1, 2013 at 11:00 AM, John Wiegley <span dir="ltr">&lt;<a href="mailto:johnw@fpcomplete.com" target="_blank">johnw@fpcomplete.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">

<div class="im">&gt;&gt;&gt;&gt;&gt; Yitzchak Gale &lt;<a href="mailto:gale@sefer.org">gale@sefer.org</a>&gt; writes:<br>
<br>
&gt; In fact, it even makes sense to define it as FunctorIO, with the only laws<br>
&gt; being that liftIO commutes with fmap and preserves id, i.e., that it is a<br>
&gt; natural transformation. (Those laws are also needed for ApplicativeIO and<br>
&gt; MonadIO.)<br>
<br>
</div>Given that we are moving toward Applicative (and thus Functor) as a superclass<br>
of Monad, why not just solve the MonadIO problem and similar type classes with<br>
natural transformations?  It requires 3 extensions, but these are extensions I<br>
believe should become part of Haskell anyway:<br>
<br>
    {-# LANGUAGE FlexibleInstances #-}<br>
    {-# LANGUAGE MultiParamTypeClasses #-}<br>
    {-# LANGUAGE RankNTypes #-}<br>
<br>
    module NatTrans where<br>
<br>
    import Control.Monad.IO.Class<br>
    import Control.Monad.Trans.Maybe<br>
<br>
    class (Functor s, Functor t) =&gt; NatTrans s t where<br>
        nmap :: forall a. s a -&gt; t a<br>
        -- Such that: nmap . fmap f = fmap f . nmap<br>
<br>
    -- In 7.10, this Functor constraint becomes redundant<br>
    instance (Functor m, MonadIO m) =&gt; NatTrans IO m where<br>
        nmap = liftIO<br>
<br>
    main :: IO ()<br>
    main = void $ runMaybeT $ nmap $ print (10 :: Int)<br>
<br>
Now if I have a functor of one kind and need another, I reach for nmap in the<br>
same way that I reach for fmap to transform the mapped type.<br>
<span class="HOEnZb"><font color="#888888"><br>
--<br>
John Wiegley<br>
FP Complete                         Haskell tools, training and consulting<br>
<a href="http://fpcomplete.com" target="_blank">http://fpcomplete.com</a>               johnw on #haskell/<a href="http://irc.freenode.net" target="_blank">irc.freenode.net</a><br>
</font></span><div class="HOEnZb"><div class="h5">_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</div></div></blockquote></div><br></div>