[Haskell-cafe] Why the reluctance to introduce the Functor requirement on Monad?
Victor Nazarov
asviraspossible at gmail.com
Tue Jul 26 13:39:19 CEST 2011
On Tue, Jul 26, 2011 at 1:01 PM, Alejandro Serrano Mena
<trupill at gmail.com> wrote:
> I'll give my two cents about some design I've been thinking about. Instead
> of trying to derive all instances automatically, the programmer should
> explicitly tell them (so the problems about conflicting implementations
> would be minimised). I attach a piece of code of what I think could be done:
> instance Functor a <= Monad a where -- notice the reversed "<="
> fmap = ...
> from Monad MyMonad derive Functor MyMonad
> With the from_derive_ clause, we are telling exactly from which "<="
> declaration to pull the definition from. The part of "from" should have
> already been written or derived, so we know exactly which instance the user
> is speaking about.
> More refinements to the syntax could be done, for example if we have:
> instance Functor a <= Applicative a where
> fmap = ..
> instance Applicative a <= Monad a where
> pure = ...
> (<*>) = ...
> Then, writing "from Monad MyMonad derive Functor MyMonad" would go through
> the entire tree of "reverse instance declarations" and create instances for
> Applicative, and from that a Functor one (of course, this should fail if we
> have more than one path, then the user should write the path explicitly as
> "from Monad M derive Applicative M; from Applicative M derive Functor M").
> But it has the advantage of allowing later addition of classes in the path,
> that would be derived when recompiling the code that uses it.
I want to support explicit intance derivation. But I'd like to suggest
slightly less radical syntax extention:
-- class definition:
class Fuctor m => Monad m
where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
join :: m (m a) -> m a
-- default implementations:
a >> b = a >>= (\_ -> b)
a >>= f = join . fmap f $ a
join a = a >>= id
-- default instances:
instance Functor m
where
fmap f a = a >>= (return . f)
newtype Reader a b = Reader { runReader :: a -> b }
-- instace declaration:
instance Monad (Reader r)
where
return = Reader . const
m >>= f = Reader $ \r -> runReader (f (runReader m r)) r
deriving (Functor)
So syntax changes are very minor.
--
Victor Nazarov
More information about the Haskell-Cafe
mailing list