Retrospective type-class extension

We all know that "class (Functor f) => Monad f" is preferable but its absence is a historical mistake. We've all probably tried once: instance (Functor f) => Monad f where ... However, is there a type system extension (even proposed but not implemented) that allows me to retrospectively apply such a notion? Ideally something like this would be handy if it could somehow be retrospectively applied: Monad <- Applicative <- Pointed <- Functor -- Tony Morris http://tmorris.net/

On 20 May 2010 14:42, Tony Morris
We all know that "class (Functor f) => Monad f" is preferable but its absence is a historical mistake. We've all probably tried once:
instance (Functor f) => Monad f where
Do you mean the reverse of this (instance (Monad m) => Functor m where) ?
...
However, is there a type system extension (even proposed but not implemented) that allows me to retrospectively apply such a notion?
Ideally something like this would be handy if it could somehow be retrospectively applied: Monad <- Applicative <- Pointed <- Functor
-- Tony Morris http://tmorris.net/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Ivan Miljenovic wrote:
On 20 May 2010 14:42, Tony Morris
wrote: We all know that "class (Functor f) => Monad f" is preferable but its absence is a historical mistake. We've all probably tried once:
instance (Functor f) => Monad f where
Do you mean the reverse of this (instance (Monad m) => Functor m where) ?
Yes. -- Tony Morris http://tmorris.net/

Then it would be:
class Functor f where
fmap :: (a -> b) -> f a -> f b
class (Functor f) => Pointed f where
pure :: a -> f a
class (Pointed f) => Applicative f where
(<*>) :: f (a -> b) -> f a -> f b
class (Applicative f) => Monad f where
join :: f (f a) -> f a
This would be a great idea, for the sake of logic, first (a monad which is
not a functor doesn't make sense), and also to eliminate redudancy (fmap =
liftM, ap = (<*>), etc.)
2010/5/20 Tony Morris
Ivan Miljenovic wrote:
On 20 May 2010 14:42, Tony Morris
wrote: We all know that "class (Functor f) => Monad f" is preferable but its absence is a historical mistake. We've all probably tried once:
instance (Functor f) => Monad f where
Do you mean the reverse of this (instance (Monad m) => Functor m where) ?
Yes.
-- Tony Morris http://tmorris.net/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

That won't be a great idea; if I just want my monad to be declared as one, I would have to write instance Functor MyMonad where fmap = ... instance Pointed MyMonad where pure = ... instance Applicative MyMonad where (<*>) = ... instance Monad MyMonad where join = ... Compare this with instance Monad MyMonad where return = ... (>>=) = ... and take into account that (>>=) is usually easier to write than join. Limestraël wrote:
Then it would be:
class Functor f where fmap :: (a -> b) -> f a -> f b
class (Functor f) => Pointed f where pure :: a -> f a
class (Pointed f) => Applicative f where (<*>) :: f (a -> b) -> f a -> f b
class (Applicative f) => Monad f where join :: f (f a) -> f a
This would be a great idea, for the sake of logic, first (a monad which is not a functor doesn't make sense), and also to eliminate redudancy (fmap = liftM, ap = (<*>), etc.)
2010/5/20 Tony Morris
mailto:tonymorris@gmail.com> Ivan Miljenovic wrote: > On 20 May 2010 14:42, Tony Morris
mailto:tonymorris@gmail.com> wrote: > >> We all know that "class (Functor f) => Monad f" is preferable but its >> absence is a historical mistake. We've all probably tried once: >> >> instance (Functor f) => Monad f where >> > > Do you mean the reverse of this (instance (Monad m) => Functor m where) ? > Yes. -- Tony Morris http://tmorris.net/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I've compared and clearly the former is significantly superior :) I'm rather interested if there are any sound suggestions to resolve the general issue of retrospective type-class extension. Miguel Mitrofanov wrote:
That won't be a great idea; if I just want my monad to be declared as one, I would have to write
instance Functor MyMonad where fmap = ... instance Pointed MyMonad where pure = ... instance Applicative MyMonad where (<*>) = ... instance Monad MyMonad where join = ...
Compare this with
instance Monad MyMonad where return = ... (>>=) = ...
and take into account that (>>=) is usually easier to write than join.
Limestraël wrote:
Then it would be:
class Functor f where fmap :: (a -> b) -> f a -> f b
class (Functor f) => Pointed f where pure :: a -> f a
class (Pointed f) => Applicative f where (<*>) :: f (a -> b) -> f a -> f b
class (Applicative f) => Monad f where join :: f (f a) -> f a
This would be a great idea, for the sake of logic, first (a monad which is not a functor doesn't make sense), and also to eliminate redudancy (fmap = liftM, ap = (<*>), etc.)
2010/5/20 Tony Morris
mailto:tonymorris@gmail.com> Ivan Miljenovic wrote: > On 20 May 2010 14:42, Tony Morris
mailto:tonymorris@gmail.com> wrote: > >> We all know that "class (Functor f) => Monad f" is preferable but its >> absence is a historical mistake. We've all probably tried once: >> >> instance (Functor f) => Monad f where >> > > Do you mean the reverse of this (instance (Monad m) => Functor m where) ? > Yes. -- Tony Morris http://tmorris.net/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Tony Morris http://tmorris.net/

With "retrospective type-class extension" in place whatever they look like, wouldn't everyone would have to import the same retrospectively extended instances ("orphan retrospective extensions" anyone?). Thus there seems no benefit over recoding the hierarchy directly and importing it, vis:
import NewHierachyPrelude
Best wishes Stephen

Am 20.05.2010 um 14:16 schrieb Tony Morris:
I've compared and clearly the former is significantly superior :)
I'm rather interested if there are any sound suggestions to resolve the general issue of retrospective type-class extension.
I would like to have something like parent class Functor f <= Applicative f where fmap f x = pure f <*> x Then one could write instance Applicative MyApplicative deriving parent Functor where (<*>) = ... pure = ... as an abbreviation for instance Functor MyApplicative where fmap f x = pure f <*> x This way, we do not only save some keystrokes, but now it is clear that (fmap f x == pure f <*> x) is expected to hold for type MyApplicative. One could also write parent class Applicative a <= Monad a deriving parent Functor where (<*>) = ap pure = return fmap = liftM overriding the default definition of Functor's fmap. Then instance Monad MyMonad deriving parent Applicative where (>>=) = ... return = ... would be an abbreviation for instance Functor MyMonad where fmap = liftM instance Applicative MyMonad where (<*>) = ap pure = return Now the compiler can even conclude that (liftM f x == pure f <*> x) is expected to hold for type MyMonad. But there is an ambiguity if one also defines parent class Functor f <= Monad f where fmap f x = trace "boo!" (liftM f x) Then it might not be clear which definition of fmap should be used, because there are two possible paths: (Monad => Applicative => Functor) and (Monad => Functor). But then the programmer has to decide whether he writes 'deriving parent Applicative' or 'deriving parent Functor'. Thus, as long as every class or instance declaration contains at most one 'deriving parent' statement, there will always be one unambiguous path, so that this will not become a problem. This extension would have three advantages: - it is merely syntactic sugar, so that it can easily be implemented, - it does not involve tricky resolution of methods or types, so that it is easy to comprehend, and - it allows to encode knowledge about the laws class instances (should) follow.
Miguel Mitrofanov wrote:
That won't be a great idea; if I just want my monad to be declared as one, I would have to write
instance Functor MyMonad where fmap = ... instance Pointed MyMonad where pure = ... instance Applicative MyMonad where (<*>) = ... instance Monad MyMonad where join = ...
Compare this with
instance Monad MyMonad where return = ... (>>=) = ...
and take into account that (>>=) is usually easier to write than join.
Limestraël wrote:
Then it would be:
class Functor f where fmap :: (a -> b) -> f a -> f b
class (Functor f) => Pointed f where pure :: a -> f a
class (Pointed f) => Applicative f where (<*>) :: f (a -> b) -> f a -> f b
class (Applicative f) => Monad f where join :: f (f a) -> f a
This would be a great idea, for the sake of logic, first (a monad which is not a functor doesn't make sense), and also to eliminate redudancy (fmap = liftM, ap = (<*>), etc.)
2010/5/20 Tony Morris
mailto:tonymorris@gmail.com> Ivan Miljenovic wrote:
On 20 May 2010 14:42, Tony Morris
mailto:tonymorris@gmail.com> wrote: We all know that "class (Functor f) => Monad f" is preferable but its absence is a historical mistake. We've all probably tried once:
instance (Functor f) => Monad f where
Do you mean the reverse of this (instance (Monad m) => Functor m where) ?
Yes.
-- Tony Morris http://tmorris.net/

On Thu, May 20, 2010 at 10:16:29PM +1000, Tony Morris wrote:
I've compared and clearly the former is significantly superior :)
I'm rather interested if there are any sound suggestions to resolve the general issue of retrospective type-class extension.
Hi, my 'class aliases' proposal was meant to solve this issue with type classes. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

On 20 May 2010 13:10, Miguel Mitrofanov
That won't be a great idea; if I just want my monad to be declared as one, I would have to write
instance Functor MyMonad where fmap = ... instance Pointed MyMonad where pure = ... instance Applicative MyMonad where (<*>) = ... instance Monad MyMonad where join = ...
There are also some Monads where a Functor instance wouldn't add anything useful, Andy Gill's Dot monad is one (Text.Dot), Oleg Kiselyov's RenderMonad in the CSXML library is another.
participants (7)
-
Holger Siegel
-
Ivan Miljenovic
-
John Meacham
-
Limestraël
-
Miguel Mitrofanov
-
Stephen Tetley
-
Tony Morris