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