Proposal: Applicative => Monad: Call for consensus

The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834 make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility. Advantages: The class hierarchy correctly models the logical relationship between Applicative and Monad. Boilerplate Applicative instances that duplicate Monad functions will no longer be required. Disadvantage: All Monads will be Applicatives, even if you're only interested in the Monad interface. This is akin to all Ords being Eqs, even if you're not using ==. Backwards Compatibility: Existing Monad definitions will have to be changed to declare Applicative. The original function bodies can be used unchanged, but they are now declared in a different class. Calling code should work unchanged. This ticket has already been discussed on the mailing lists. The purpose of this message is to call for consensus by the deadline of 1 February. Please note that although the ticket references the wiki page at http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal, the patches attached to the ticket are much more conservative than the more ambitious reforms on the wiki. (I would like to change the ticket description to make this clearer, but I can't edit it.)

Are there patches somewhere to implement all of this in GHC?
Particularly the MonadFail changes, as that is a change to how the
compiler works - not just a change to libraries.
Also, that wiki seems to be two different proposals - one with the
Pointed class and one without.
Take Care,
Antoine
On Sun, Jan 2, 2011 at 6:04 AM, John Smith
The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834 make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility.
Advantages: The class hierarchy correctly models the logical relationship between Applicative and Monad. Boilerplate Applicative instances that duplicate Monad functions will no longer be required.
Disadvantage: All Monads will be Applicatives, even if you're only interested in the Monad interface. This is akin to all Ords being Eqs, even if you're not using ==.
Backwards Compatibility: Existing Monad definitions will have to be changed to declare Applicative. The original function bodies can be used unchanged, but they are now declared in a different class. Calling code should work unchanged.
This ticket has already been discussed on the mailing lists. The purpose of this message is to call for consensus by the deadline of 1 February.
Please note that although the ticket references the wiki page at http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal, the patches attached to the ticket are much more conservative than the more ambitious reforms on the wiki. (I would like to change the ticket description to make this clearer, but I can't edit it.)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 02/01/2011 17:19, Antoine Latter wrote:
Are there patches somewhere to implement all of this in GHC? Particularly the MonadFail changes, as that is a change to how the compiler works - not just a change to libraries.
Also, that wiki seems to be two different proposals - one with the Pointed class and one without.
Patches are attached to the ticket. They do not involve MonadFail or Pointed, these could be future patches/proposals.

On 02/01/2011 14:04, John Smith wrote:
Please note that although the ticket references the wiki page at http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal, the patches attached to the ticket are much more conservative than the more ambitious reforms on the wiki. (I would like to change the ticket description to make this clearer, but I can't edit it.)
To clarify - this proposal is to implement just the patches attached to the ticket, /not/ everything in the related wiki page.

Ah! Yup, I just noticed.
I can't read, apparently :-)
Yeah, I get irritated whenever I come across a Monad instance and I
cannot use the Applicative combinators. So I guess I'm in favor.
Is there a reason this is appropriate for the libraries process? Do
any of these changes spill out into the public interface of base or
GHC.Ext?
Sorry for the confusion,
Antoine
On Sun, Jan 2, 2011 at 9:46 AM, John Smith
On 02/01/2011 14:04, John Smith wrote:
Please note that although the ticket references the wiki page at http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal, the patches attached to the ticket are much more conservative than the more ambitious reforms on the wiki. (I would like to change the ticket description to make this clearer, but I can't edit it.)
To clarify - this proposal is to implement just the patches attached to the ticket, /not/ everything in the related wiki page.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Okay, I still can't read. Now I was confusing this with the GHC only patch.
I'll back away slowly, now.
On Sun, Jan 2, 2011 at 9:49 AM, Antoine Latter
Ah! Yup, I just noticed.
I can't read, apparently :-)
Yeah, I get irritated whenever I come across a Monad instance and I cannot use the Applicative combinators. So I guess I'm in favor.
Is there a reason this is appropriate for the libraries process? Do any of these changes spill out into the public interface of base or GHC.Ext?
Sorry for the confusion, Antoine
On Sun, Jan 2, 2011 at 9:46 AM, John Smith
wrote: On 02/01/2011 14:04, John Smith wrote:
Please note that although the ticket references the wiki page at http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal, the patches attached to the ticket are much more conservative than the more ambitious reforms on the wiki. (I would like to change the ticket description to make this clearer, but I can't edit it.)
To clarify - this proposal is to implement just the patches attached to the ticket, /not/ everything in the related wiki page.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Maybe the linked wiki could have a list of the tickets involved and
how they relate/do not relate to each other?
On Sun, Jan 2, 2011 at 9:46 AM, John Smith
On 02/01/2011 14:04, John Smith wrote:
Please note that although the ticket references the wiki page at http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal, the patches attached to the ticket are much more conservative than the more ambitious reforms on the wiki. (I would like to change the ticket description to make this clearer, but I can't edit it.)
To clarify - this proposal is to implement just the patches attached to the ticket, /not/ everything in the related wiki page.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sun, Jan 2, 2011 at 7:04 AM, John Smith
The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834 make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility.
Monad is defined in the Haskell 98 and Haskell 2010 reports. How are
you planning to maintain compatibility with them?
--
Dave Menendez

On 02/01/2011 19:14, David Menendez wrote:
On Sun, Jan 2, 2011 at 7:04 AM, John Smith
wrote: The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834 make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility.
Monad is defined in the Haskell 98 and Haskell 2010 reports. How are you planning to maintain compatibility with them?
The Haskell' process expects proposals to have already been implemented, so I'll propose it there after acceptance by GHC. If the patches are accepted for HEAD, this may be adequate for proposing towards the next Haskell report, so GHC and the report will only be out of sync for a minimal time.

On 2 January 2011 17:50, John Smith
The Haskell' process expects proposals to have already been implemented, so I'll propose it there after acceptance by GHC. If the patches are accepted for HEAD, this may be adequate for proposing towards the next Haskell report, so GHC and the report will only be out of sync for a minimal time.
Someone in the previous discussion (might have been me...) suggested that the Haskell Prime committee might want a different criteria for library changes than the one it has language extensions. A change like this one would be particularly disruptive outside a language revision, but a lot more tolerable as part of one.

On 01/02/11 12:50, John Smith wrote:
On 02/01/2011 19:14, David Menendez wrote:
On Sun, Jan 2, 2011 at 7:04 AM, John Smith
wrote: The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834 make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility.
Monad is defined in the Haskell 98 and Haskell 2010 reports. How are you planning to maintain compatibility with them?
The Haskell' process expects proposals to have already been implemented, so I'll propose it there after acceptance by GHC. If the patches are accepted for HEAD, this may be adequate for proposing towards the next Haskell report, so GHC and the report will only be out of sync for a minimal time.
Even GHC 7.100 is intended to maintain compatibility with Haskell 98. We desire a way to implement the change that allows Haskell 98 and Haskell 2010 programs to compile unchanged, *even if* Haskell 2011 Report includes libraries with a Monad hierarchy change. The naive way to do this is to make a different Monad class, without any superclasses, and put it in the haskell98 package. This has the general issue that instances of the two "class Monad"s aren't compatible. I think it also has a particular difficulty related to "do"-notation.

On Sun, Jan 2, 2011 at 9:04 PM, Isaac Dupree
On 01/02/11 12:50, John Smith wrote:
On 02/01/2011 19:14, David Menendez wrote:
On Sun, Jan 2, 2011 at 7:04 AM, John Smith
wrote: The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834 make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility.
Monad is defined in the Haskell 98 and Haskell 2010 reports. How are you planning to maintain compatibility with them?
The Haskell' process expects proposals to have already been implemented, so I'll propose it there after acceptance by GHC. If the patches are accepted for HEAD, this may be adequate for proposing towards the next Haskell report, so GHC and the report will only be out of sync for a minimal time.
Even GHC 7.100 is intended to maintain compatibility with Haskell 98. We desire a way to implement the change that allows Haskell 98 and Haskell 2010 programs to compile unchanged, *even if* Haskell 2011 Report includes libraries with a Monad hierarchy change.
The naive way to do this is to make a different Monad class, without any superclasses, and put it in the haskell98 package. This has the general issue that instances of the two "class Monad"s aren't compatible. I think it also has a particular difficulty related to "do"-notation.
GHC supports the notion of a 'language' command line switch. I don't know how hard it would be to co-opt it to control 'do' desugaring. Also, there would need to be a value for language other than 'haskell98' and 'haskell2010' to turn on the new behavior. This is all brainstorming, and may not be appropriate for a consensus discussion, and may not be feasible for other reasons. I also don't know if other implementations (or even GHC) would be willing to take on this sort of complexity burden. Antoine
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

2011/1/2 Isaac Dupree
On 01/02/11 12:50, John Smith wrote:
On 02/01/2011 19:14, David Menendez wrote:
On Sun, Jan 2, 2011 at 7:04 AM, John Smith
wrote: The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834 make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility.
Monad is defined in the Haskell 98 and Haskell 2010 reports. How are you planning to maintain compatibility with them?
The Haskell' process expects proposals to have already been implemented, so I'll propose it there after acceptance by GHC. If the patches are accepted for HEAD, this may be adequate for proposing towards the next Haskell report, so GHC and the report will only be out of sync for a minimal time.
Even GHC 7.100 is intended to maintain compatibility with Haskell 98. We desire a way to implement the change that allows Haskell 98 and Haskell 2010 programs to compile unchanged, *even if* Haskell 2011 Report includes libraries with a Monad hierarchy change.
The naive way to do this is to make a different Monad class, without any superclasses, and put it in the haskell98 package. This has the general issue that instances of the two "class Monad"s aren't compatible. I think it also has a particular difficulty related to "do"-notation.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
How about some magic to automatically declare an Applicative superclass if it doesn't already exist? Alexander Dunlap

Hello,
I think that reorganizing the Monad/Applicative/Functor classes is a good
idea, despite the fact that it would break lots of code. However, I think
that it would be useful if there was a wiki page which describes the
proposal exactly, so that we can discuss the details (having the patches is
nice, but they are hard to read).
-Iavor
On Sun, Jan 2, 2011 at 4:04 AM, John Smith
The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility.
Advantages: The class hierarchy correctly models the logical relationship between Applicative and Monad. Boilerplate Applicative instances that duplicate Monad functions will no longer be required.
Disadvantage: All Monads will be Applicatives, even if you're only interested in the Monad interface. This is akin to all Ords being Eqs, even if you're not using ==.
Backwards Compatibility: Existing Monad definitions will have to be changed to declare Applicative. The original function bodies can be used unchanged, but they are now declared in a different class. Calling code should work unchanged.
This ticket has already been discussed on the mailing lists. The purpose of this message is to call for consensus by the deadline of 1 February.
Please note that although the ticket references the wiki page at http://haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal, the patches attached to the ticket are much more conservative than the more ambitious reforms on the wiki. (I would like to change the ticket description to make this clearer, but I can't edit it.)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sun, Jan 02, 2011 at 06:27:04PM -0800, Iavor Diatchki wrote:
I think that it would be useful if there was a wiki page which describes the proposal exactly, so that we can discuss the details
I agree. I'm confused as to what is part of the proposal, what are other changes necessary due to the classes changing, what are orthogonal cleanups, and what is not being proposed. Thanks Ian

On Mon, Jan 3, 2011 at 12:43 PM, Ian Lynagh
On Sun, Jan 02, 2011 at 06:27:04PM -0800, Iavor Diatchki wrote:
I think that it would be useful if there was a wiki page which describes the proposal exactly, so that we can discuss the details
I agree. I'm confused as to what is part of the proposal, what are other changes necessary due to the classes changing, what are orthogonal cleanups, and what is not being proposed.
The patch for base makes a few changes: 1) Make Applicative a superclass of Monad. So the new hierarchy becomes: class Functor f where fmap :: (a -> b) -> f a -> f b (<$) :: a -> f b -> f a (<$) = fmap . const class Functor f => Applicative f where pure :: a -> f a (<*>) :: f (a -> b) -> f a -> f b (*>) :: f a -> f b -> f b a *> b = fmap (const id) a <*> b (<*) :: f a -> f b -> f a a <* b = fmap const a <*> b class Applicative m => Monad m where (>>=) :: forall a b. m a -> (a -> m b) -> m b m >>= f = join $ fmap f m join :: m (m a) -> m a join m = m >>= id (>>) :: forall a b. m a -> m b -> m b (>>) = (*>) return :: a -> m a return = pure fail :: String -> m a fail s = error s 2) Make 'join' a method of Monad. 3) Export Applicative(pure, (<*>), (*>), (<*)) from the Prelude. (Maybe we shouldn't export the (*>) and (<*) methods.) 4) Also export the join method from the Prelude. 5) Add Applicative instances for all monads in base. 6) Add a Monad instance for ((,) a): (There are already Functor and Applicative instances for it.) instance Monoid a => Monad ((,) a) where (u, x) >>= f = let (v, y) = f x in (u `mappend` v, y) (Maybe this one should be left out of the patch) The patch for ghc simply adds Applicative instances for all monads in ghc. Also included in the ghc patch bundle are some refactoring patches that will make the transition easier: * Added (<>) = mappend to compiler/utils/Util.hs. * Add a Monoid instance for AGraph and remove the <*> splice operator. Instead of <*>, the (<>) = mappend operator is now used to splice AGraphs. This change is needed because <*> clashes with the Applicative apply operator <*>, which is probably going to be exported from the Prelude when the new Monad hierarchy is going through. (Simply hiding <*> from the Prelude is also possible of course. However, I think this makes things easier to understand) * Make SDoc an abstract newtype and add a Monoid instance for it. The (<>) combinator of SDocs is removed and replaced by the more general (<>) = mappend combinator from Util. Note that all the ghc patches can be applied independently of the base patch. Now which notable things are not included in the patch for base: * fmap is not renamed to map. * return and (>>) are not removed as a method. * fail is not removed as a method. * All the liftM functions are not removed in favour of fmap and liftAs. I think these are better left as separate proposals. Regards, Bas

On 01/03/11 17:30, Bas van Dijk wrote:
... The patch for base makes a few changes:
1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
2) Make 'join' a method of Monad. ... class Applicative m => Monad m where ... (>>) :: forall a b. m a -> m b -> m b (>>) = (*>)
The former/current default definition of (>>) was based on (>>=), not (*>) (which if itself is undefined, itself defaults to (fmap (const id) a <*> b). That's a change. You also added defaults for most of the Monad methods, though they're obvious and I approve. The (>>) default might have worse performance than the previous default though? (>>) is used in do-notation desugaring, and yet many (most?) Monad instance writers do not explicitly define it, so its default makes some difference. Does anyone know how to test? -Isaac

On 1/3/11 7:22 PM, Isaac Dupree wrote:
On 01/03/11 17:30, Bas van Dijk wrote:
... The patch for base makes a few changes:
1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
2) Make 'join' a method of Monad. ... class Applicative m => Monad m where ... (>>) :: forall a b. m a -> m b -> m b (>>) = (*>)
The former/current default definition of (>>) was based on (>>=), not (*>) (which if itself is undefined, itself defaults to (fmap (const id) a <*> b). That's a change.
Yes, that is a change.
You also added defaults for most of the Monad methods, though they're obvious and I approve. The (>>) default might have worse performance than the previous default though?
Nope. Since (*>) is a class method it can be given the most efficient implementation possible for the given type. Since (>>) is logically the same function, then it should default to (*>) so that the efficient implementation doesn't need to be duplicated. In the event that neither is defined explicitly, then they will both default to the same definition as pre-patch. -- Live well, ~wren

On Tue, Jan 4, 2011 at 1:22 AM, Isaac Dupree
You also added defaults for most of the Monad methods, though they're obvious and I approve. The (>>) default might have worse performance than the previous default though? (>>) is used in do-notation desugaring, and yet many (most?) Monad instance writers do not explicitly define it, so its default makes some difference. Does anyone know how to test?
Has there been any performance testing of this change? One way to test it would be test the change on some performance sensitive code that uses monads. vector-algorithms [1] (which uses the PrimMonad) comes to mind as a good candidate. Some monadic parser packages, like binary [2] or attoparsec [3], would be interesting to include in the performance test too. Johan 1. http://hackage.haskell.org/package/vector-algorithms 2. http://hackage.haskell.org/package/binary 3. http://hackage.haskell.org/package/attoparsec

Thanks for the detailed clarification, I've copied this message to the wiki page On 04/01/2011 00:30, Bas van Dijk wrote:
The patch for base makes a few changes:
1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
class Functor f where fmap :: (a -> b) -> f a -> f b
(<$) :: a -> f b -> f a (<$) = fmap . const
class Functor f => Applicative f where pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
(*>) :: f a -> f b -> f b a *> b = fmap (const id) a<*> b
(<*) :: f a -> f b -> f a a<* b = fmap const a<*> b
class Applicative m => Monad m where (>>=) :: forall a b. m a -> (a -> m b) -> m b m>>= f = join $ fmap f m
join :: m (m a) -> m a join m = m>>= id
(>>) :: forall a b. m a -> m b -> m b (>>) = (*>)
return :: a -> m a return = pure
fail :: String -> m a fail s = error s
2) Make 'join' a method of Monad.
3) Export Applicative(pure, (<*>), (*>), (<*)) from the Prelude. (Maybe we shouldn't export the (*>) and (<*) methods.)
4) Also export the join method from the Prelude.
5) Add Applicative instances for all monads in base.
6) Add a Monad instance for ((,) a): (There are already Functor and Applicative instances for it.)
instance Monoid a => Monad ((,) a) where (u, x)>>= f = let (v, y) = f x in (u `mappend` v, y)
(Maybe this one should be left out of the patch)
The patch for ghc simply adds Applicative instances for all monads in ghc. Also included in the ghc patch bundle are some refactoring patches that will make the transition easier:
* Added (<>) = mappend to compiler/utils/Util.hs. * Add a Monoid instance for AGraph and remove the<*> splice operator. Instead of<*>, the (<>) = mappend operator is now used to splice AGraphs. This change is needed because<*> clashes with the Applicative apply operator<*>, which is probably going to be exported from the Prelude when the new Monad hierarchy is going through. (Simply hiding<*> from the Prelude is also possible of course. However, I think this makes things easier to understand) * Make SDoc an abstract newtype and add a Monoid instance for it. The (<>) combinator of SDocs is removed and replaced by the more general (<>) = mappend combinator from Util.
Note that all the ghc patches can be applied independently of the base patch.
Now which notable things are not included in the patch for base:
* fmap is not renamed to map. * return and (>>) are not removed as a method. * fail is not removed as a method. * All the liftM functions are not removed in favour of fmap and liftAs.
I think these are better left as separate proposals.
Regards,
Bas

On Mon, Jan 03, 2011 at 11:30:44PM +0100, Bas van Dijk wrote:
1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
class Applicative m => Monad m where
Now which notable things are not included in the patch for base:
* fmap is not renamed to map. * return and (>>) are not removed as a method. * fail is not removed as a method. * All the liftM functions are not removed in favour of fmap and liftAs.
I think these are better left as separate proposals.
OK, but I think it would be good to get any changes into a single release, so people only need to fix their instances once.
(>>=) :: forall a b. m a -> (a -> m b) -> m b m >>= f = join $ fmap f m
join :: m (m a) -> m a join m = m >>= id
Have you got an example of a Monad for which you'd want to define join but not (>>=)?
(>>) :: forall a b. m a -> m b -> m b (>>) = (*>)
return :: a -> m a return = pure
fail :: String -> m a fail s = error s
2) Make 'join' a method of Monad.
Why?
6) Add a Monad instance for ((,) a): (There are already Functor and Applicative instances for it.)
(Maybe this one should be left out of the patch)
It does sound like a separate issue. Thanks Ian

On Tue, Jan 4, 2011 at 1:25 PM, Ian Lynagh
On Mon, Jan 03, 2011 at 11:30:44PM +0100, Bas van Dijk wrote:
1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
class Applicative m => Monad m where
Now which notable things are not included in the patch for base:
* fmap is not renamed to map. * return and (>>) are not removed as a method. * fail is not removed as a method. * All the liftM functions are not removed in favour of fmap and liftAs.
I think these are better left as separate proposals.
OK, but I think it would be good to get any changes into a single release, so people only need to fix their instances once.
(>>=) :: forall a b. m a -> (a -> m b) -> m b m >>= f = join $ fmap f m
join :: m (m a) -> m a join m = m >>= id
Have you got an example of a Monad for which you'd want to define join but not (>>=)?
(>>) :: forall a b. m a -> m b -> m b (>>) = (*>)
return :: a -> m a return = pure
fail :: String -> m a fail s = error s
2) Make 'join' a method of Monad.
Why?
Of course I'm only a sample size of one, but I find join a lot easier to think about and implement than (>>=). Even trying to look at it objectively and factor out my own potential idiosyncracies, it's obvious that it only has one argument to (>>=)'s two, and the type signature looks a lot more straightforward any way I slice it. I was very glad to see this proposal to make it possible to define a Monad using return (pure), fmap, and join, rather than return and (>>=). I also recall reading somewhere that mathematically speaking join is the more significant operation but I'll leave that to the experts.
6) Add a Monad instance for ((,) a): (There are already Functor and Applicative instances for it.)
(Maybe this one should be left out of the patch)
It does sound like a separate issue.
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Work is punishment for failing to procrastinate effectively.

On Tue, 2011-01-04 at 13:49 +0100, Gábor Lehel wrote:
2) Make 'join' a method of Monad.
Why?
Of course I'm only a sample size of one, but I find join a lot easier to think about and implement than (>>=). Even trying to look at it objectively and factor out my own potential idiosyncracies, it's obvious that it only has one argument to (>>=)'s two, and the type signature looks a lot more straightforward any way I slice it. I was very glad to see this proposal to make it possible to define a Monad using return (pure), fmap, and join, rather than return and (>>=).
I also recall reading somewhere that mathematically speaking join is the more significant operation but I'll leave that to the experts.
+1. I also find join easier. This particular change can be done right now without breaking anything I believe [even if whole proposal is rejected]: class 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 join = (>>= id) mkBind :: Monad m => ((a -> b) -> m a -> m b) -> m a -> (a -> m b) -> m b mkBind map mv mf = join (map mf mv) ... instance Monad m where join = ... return = ... (>>=) = mkBind fmap However with this proposal it is even nicer (no need for mkBind). Regards

Gábor Lehel schrieb:
On Tue, Jan 4, 2011 at 1:25 PM, Ian Lynagh
wrote: On Mon, Jan 03, 2011 at 11:30:44PM +0100, Bas van Dijk wrote:
2) Make 'join' a method of Monad.
Why?
Of course I'm only a sample size of one, but I find join a lot easier to think about and implement than (>>=). Even trying to look at it objectively and factor out my own potential idiosyncracies, it's obvious that it only has one argument to (>>=)'s two, and the type signature looks a lot more straightforward any way I slice it. I was very glad to see this proposal to make it possible to define a Monad using return (pure), fmap, and join, rather than return and (>>=).
Mathematically I like 'join' more than '>>=', but for RMonads like StorableVector you will in general be able to define a '>>=' but not 'join'. Of course, you can ignore this reason, because Monad is not RMonad, but for reasons of consistency it might count.

On January 4, 2011 07:25:36 Ian Lynagh wrote:
Have you got an example of a Monad for which you'd want to define join but not (>>=)?
(>>) :: forall a b. m a -> m b -> m b (>>) = (*>)
return :: a -> m a return = pure
fail :: String -> m a fail s = error s
2) Make 'join' a method of Monad.
Why?
It seems to me that while join is more of a value transformer as apposed to a flow combining operator, which makes it fit in better with the rest applicative. That is, (<*>) :: f (a -> b) -> f a -> f b -- (<*>) f -- transforms f join :: f (f a) -> f a -- join y -- transforms y return :: a -> f a -- return x -- transforms x Cheers! -Tyson

Hello,
I am also skeptical about the need to add "join" to the monad class. My
reasoning is that I doubt that one can define an instance where "join" and
"bind" perform differently, so we are just adding overhead, both cognitive
(because the Monad class get more complex) and resource-wise (because
dictionaries need to carry an additional method).
Note that if you find "join" easier to define then "bind" (which I'd be
surprised for any monad other then lists), you can still do just that:
define "join", and then define "bind" in the usual way.
In terms of the "symmetry" that Tyson mention, this is how I like to think
about the three applications:
fmap :: (a -> b) -> f a -> f b
(<*>) :: f (a -> b) -> f a -> f b
(=<<) :: (a -> f b) -> f a -> f b
So really, (=<<) seems the most symmetric to me, but I don't think that the
pain of changing the class to use (=<<) would really be justified.
I completely agree with Ian that it'd be better to get all changes in a
single proposal, so that we only need to fix things once, so let's at least
drop the duplicated methods.
-Iavor
On Tue, Jan 4, 2011 at 7:51 AM, Tyson Whitehead
On January 4, 2011 07:25:36 Ian Lynagh wrote:
Have you got an example of a Monad for which you'd want to define join but not (>>=)?
(>>) :: forall a b. m a -> m b -> m b (>>) = (*>)
return :: a -> m a return = pure
fail :: String -> m a fail s = error s
2) Make 'join' a method of Monad.
Why?
It seems to me that while join is more of a value transformer as apposed to a flow combining operator, which makes it fit in better with the rest applicative.
That is,
(<*>) :: f (a -> b) -> f a -> f b -- (<*>) f -- transforms f join :: f (f a) -> f a -- join y -- transforms y return :: a -> f a -- return x -- transforms x
Cheers! -Tyson
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Tue, 2011-01-04 at 10:06 -0800, Iavor Diatchki wrote:
Note that if you find "join" easier to define then "bind" (which I'd be surprised for any monad other then lists), you can still do just that: define "join", and then define "bind" in the usual way.
newtype CPS a = CPS (forall r. (a -> r) -> r) join (CPS f) = f id (CPS f) >>= g = f g newtype Cont r a = Cont {runCont :: (a -> r) -> r} join (Cont f) = Cont (\c -> f (\a -> runCont a c)) (Cont f) >>= g = Cont (\c -> f (\a -> runCont (g a) c)) newtype Identity a = Identity a join (Identity x) = x Identity v >>= f = f v newtype Reader r a = Reader {runReader :: r -> a} join (Reader f) = Reader (\e -> runReader (f e) e) (Reader f) >>= g = Reader (\e -> runReader (g (f e)) e) data Writer w a = Writer w a join (Writer w (Writer w' a)) = Writer (w `mappend` w') a (Writer (w, v)) >>= g = let Writer w' a = g v in Writer (w `mappend` w') a newtype Maybe a = Just a | Nothing join (Just x) = x join Nothing = Nothing Just x >>= g = g x Nothing >>= _ = Nothing data [a] = a:[a] | [] join [] = [] join (x:xs) = x ++ join xs [] >>= _ = [] (x:xs) >>= g = g x ++ (xs >>= g) The bind is always harder as join x == x >>= id so join have 1 parameter known. In some cases it is large simplification (see Writer). Regards

On January 4, 2011 13:53:22 Maciej Piechotka wrote:
The bind is always harder as join x == x >>= id so join have 1 parameter known. In some cases it is large simplification (see Writer).
That's a very nice explanation. I also find join is quite a bit clearer for me to think about in terms of exactly what additional power monad gives you over applicative. In applicative the outer computations can not access the results of inner computations to react to them (values can only be injected inwards). Thus the sequence/structure of the outer computation is independent of the inner one. (presumably this strong guarantee makes various optimizations possible -- making it a shame to use a full blown monad when only applicative is needed) Join makes makes the results of inner computations available to outer ones. This allows the outer computation to react to the specifics of the inner one, which is the additional power/complexity of a monad (e.g., my next IO action can depend on the actual content of the file read in my previous IO action). Cheers! -Tyson

On Tue, 4 Jan 2011, Iavor Diatchki wrote:
Hello, I am also skeptical about the need to add "join" to the monad class. My reasoning is that I doubt that one can define an instance where "join" and "bind" perform differently, so we are just adding overhead, both cognitive (because the Monad class get more complex) and resource-wise (because dictionaries need to carry an additional method).
In my completion monad, "join" is more efficent than "bind id" Here are the functions (see Chapter 10 of http://r6.ca/thesis.pdf): return a = \eps -> a fmap f x = \eps -> f (x ((modulus f eps)/2)) join x = \eps -> x (eps/2) (eps/2) bind f x = join (fmap f x) Now look at the value of "bind id x" bind id x = join (fmap id x) = \eps -> (fmap id x) (eps/2) (eps/2) = \eps -> id (x ((modulus id (eps/2)/2)) (eps/2) = \eps -> id (x ((id (eps/2)/2)) (eps/2) -- modulus id = id = \eps -> x (eps/4) (eps/2) compared with join x = \eps -> x (eps/2) (eps/2) The two results are equivalent under the equivalence relation for completion type: x == y iff forall eps1 eps2. |(x eps1) - (y eps2)| <= eps1 + eps2. but the direct definition of join is more efficent than the definition using bind id. (as an aside, one would think (or at least I thought) that one could define fmap f x = \eps -> f (x (modulus f eps)) and then join and bind id would be equivalent. But it turns out that this definition of fmap doesn't work in general. See the paragraph after Definition 10.14 on page 71 of my thesis for a counterexample.) -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id"
This suggests that your monad will work less efficiently if you use it with the do-notation. Join and bind are very similar and, at least in standard Haskell code, I think that "bind" has proven to be a lot more useful then "join". Also, as I mentioned before, if people find "join" easier to define then "bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class. -Iavor

On Wed, Jan 05, 2011 at 10:03:51AM -0800, Iavor Diatchki wrote:
Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
wrote: On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id"
This suggests that your monad will work less efficiently if you use it with the do-notation.
Join and bind are very similar and, at least in standard Haskell code, I think that "bind" has proven to be a lot more useful then "join".
Also, as I mentioned before, if people find "join" easier to define then "bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class.
However, people who think in terms of join might also have client code that uses join, perhaps even more than bind. Such people still want their faster implementations of join, which they cannot easily get under the name join if join is not a class member. This is the usual trade-off: Small classes are nice for machine-asserted coherence (the equation |join = bind id| will hold), but not good for performance. Default definitions take a lot of the pain out of large classes: The naive implementor is allowed to believe it is a small class. Ord is a good example for such a large class --- they typically will come with documentation clarifying that ``A minimal implementation would comprise either ... or ...''. You might point to the alternative to provide a RULE for your private implementations, but even if that were portable, and guaranteed to fire, it still would be a much less natural mechanism to bind a name from the Monad ``theory'' to a custom implementation. I therefore vote, in general, for ``large'' Haskell type classes in the sense that what might be considered a derived item is still made a member, and suggest to not just include default definitions inside the class, but also export ``default definition constructor functions'' together with the class. Wolfram

On Wed, 2011-01-05 at 10:03 -0800, Iavor Diatchki wrote:
Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
wrote: On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id" This suggests that your monad will work less efficiently if you use it with the do-notation.
Join and bind are very similar and, at least in standard Haskell code, I think that "bind" has proven to be a lot more useful then "join".
Also, as I mentioned before, if people find "join" easier to define then "bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class.
-Iavor
I think that's the least of the problems. The method may not even be exported by Prelude just like (<$), which can be defined in terms of fmap. Regards

On Wed, 5 Jan 2011, Iavor Diatchki wrote:
Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
wrote: On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id" This suggests that your monad will work less efficiently if you use it with the do-notation.
No. If I need to use fmap, there is no getting around it. Only if I use "bind id" is it faster to use "join".
Join and bind are very similar and, at least in standard Haskell code, I think that "bind" has proven to be a lot more useful then "join".
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
Also, as I mentioned before, if people find "join" easier to define then "bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class.
If people find "bind" easier to define "join", then they can define "bind", and then define "join" in terms of that---Your argument is totally symetric in the terms "bind" and "join". -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

Hi,
On Wed, Jan 5, 2011 at 3:29 PM,
On Wed, 5 Jan 2011, Iavor Diatchki wrote:
Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
wrote: On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id" This suggests that your monad will work less efficiently if you use it with the do-notation.
No. If I need to use fmap, there is no getting around it. Only if I use "bind id" is it faster to use "join".
I am not familiar with your monad but if you are not making essential use of "bind" (or join and fmap together), then perhaps the monadic structure is not particularly important?
Join and bind are very similar and, at least in standard Haskell code, I
think that "bind" has proven to be a lot more useful then "join".
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
I am not sure what you mean here, I find the "do" notation quite useful.
Also, as I mentioned before, if people find "join" easier to define then
"bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class.
If people find "bind" easier to define "join", then they can define "bind", and then define "join" in terms of that---Your argument is totally symetric in the terms "bind" and "join".
The situation is not symmetric because we already have a class with ">>=" and lots of code which depends on it---so I don't think that replacing ">>=" with "join" is really plausible (I would certainly not support such a change). I am not convinced that adding "join" to the class, in addition to ">>=", buys us anything but complexity. -Iavor

On January 6, 2011 11:42:09 Iavor Diatchki wrote:
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
I am not sure what you mean here, I find the "do" notation quite useful.
I think he was meaning when you are using monads in a more "function style" (applicative) than "imperative style" (do notation). As an example, consider the definition of ">>=" using join and the "$" and "<$>" application operators x >>= f = join $ f <$> x versus that using "do" notation x >>= f = do x' <- x f x' Obviously both notations have their places, "do" is usually nicer if I want to use values multiple times, while "applicative style" is usually nicer if I am just unpacking values for an application. I suspect "do", however, tends to get overused simply because that is what monad tutorials teach. Cheers! -Tyson

On Thu, 6 Jan 2011, Tyson Whitehead wrote:
On January 6, 2011 11:42:09 Iavor Diatchki wrote:
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
I am not sure what you mean here, I find the "do" notation quite useful.
I think he was meaning when you are using monads in a more "function style" (applicative) than "imperative style" (do notation).
As an example, consider the definition of ">>=" using join and the "$" and "<$>" application operators
x >>= f = join $ f <$> x
versus that using "do" notation
x >>= f = do x' <- x f x'
Notice that in the applicative style we didn't need to name the "x'" value. To add to this excellet comment, the idea of applicative style is to use a long string of functions and parameters with various <$> and <*> in between them with the occassional peppering of join and other combinators. I understand this is becomming quite popular with parser combinators. e.g. (this example is from mm_freak): char '(' *> skipSpace *> someToken <* skipSpace <* char ')' Haskell is famous for allowing users the choice of multiple programming styles: * matching on the LHS vs case statements on the RHS * where clauses vs let statements * 2-D layout vs braces and semi-colons Given this, it seems only appropriate to support both applicative style and do notation programming. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On Thu, 2011-01-06 at 12:35 -0500, Tyson Whitehead wrote:
On January 6, 2011 11:42:09 Iavor Diatchki wrote:
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
I am not sure what you mean here, I find the "do" notation quite useful.
I think he was meaning when you are using monads in a more "function style" (applicative) than "imperative style" (do notation).
As an example, consider the definition of ">>=" using join and the "$" and "<$>" application operators
x >>= f = join $ f <$> x
versus that using "do" notation
x >>= f = do x' <- x f x'
I guess that in both cases it should be written as x >>= f. Maybe better example: doA :: String -> String -> String -> IO String doB :: IO String doC = join $ doA <$> doB <*> doB <*> doB vs. doC = do x <- doB y <- doB z <- doB doA x y z
Obviously both notations have their places, "do" is usually nicer if I want to use values multiple times, while "applicative style" is usually nicer if I am just unpacking values for an application. I suspect "do", however, tends to get overused simply because that is what monad tutorials teach.
Cheers! -Tyson
I noticed that for people unfamiliar with Haskell the do notation is simpler. However as they get used to they learn to appreciate: data Function = Function Ident Args Type function = Function <$> ident <*> args <*> returnType or similar constructions in simpler ('applicative') cases. Regards

On Thu, 6 Jan 2011, Maciej Piechotka wrote:
Maybe better example:
doA :: String -> String -> String -> IO String doB :: IO String
doC = join $ doA <$> doB <*> doB <*> doB
vs.
doC = do x <- doB y <- doB z <- doB doA x y z
This is a good illustration. Notice how the intermediate variables don't have to be named. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On Thu, Jan 6, 2011 at 5:42 PM, Iavor Diatchki
Hi,
On Wed, Jan 5, 2011 at 3:29 PM,
wrote: On Wed, 5 Jan 2011, Iavor Diatchki wrote:
Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
wrote: On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id" This suggests that your monad will work less efficiently if you use it with the do-notation.
No. If I need to use fmap, there is no getting around it. Only if I use "bind id" is it faster to use "join".
I am not familiar with your monad but if you are not making essential use of "bind" (or join and fmap together), then perhaps the monadic structure is not particularly important?
Join and bind are very similar and, at least in standard Haskell code, I think that "bind" has proven to be a lot more useful then "join".
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
I am not sure what you mean here, I find the "do" notation quite useful.
Also, as I mentioned before, if people find "join" easier to define then "bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class.
If people find "bind" easier to define "join", then they can define "bind", and then define "join" in terms of that---Your argument is totally symetric in the terms "bind" and "join".
The situation is not symmetric because we already have a class with ">>=" and lots of code which depends on it---so I don't think that replacing ">>=" with "join" is really plausible (I would certainly not support such a change). I am not convinced that adding "join" to the class, in addition to ">>=", buys us anything but complexity. -Iavor
I'm not sure what you mean here by "replace" -- to _remove_ bind from Monad, and add join instead? I don't know of anyone proposing this. You're perfectly correct that it's possible to define a standalone join function yourself, and then write in what would be the proposed default definition for bind manually -- but roconnor is also perfectly correct that if the situation were the other way around, the same thing would be true in reverse. In other words, the argument is that the situation with bind being a method of Monad and join not being such is a historical accident, and not one supported by the merits. The fact that you can still write the function outside the class and define the class method in terms of it manually is true of approximately every class method and standalone function ever written. We could write all of our classes so that the most complicated and impressive functions are the methods, while defining the simple ones standalone in terms of those, with perhaps only a small amount of annoyance overhead resulting for our users -- but we don't. We tend to seek the ability to write minimal class definitions using the simplest and most straightforward methods we can find. It sends a message: this is the easiest/best way to write an instance. If you resort to writing what should've been a method as a standalone function instead and defining the method in terms of it, the message it sends is "the definition of this class is flawed and I'm working around it". But most people probably don't think of doing this, and just define the simplest out of whatever methods they are given. After all, writing simple functions and then defining the more complex ones as combinations of those is what Haskell is all about, isn't it? So we should strive to support that, even if it can be done in our spite when we don't. And as has been argued at length in this thread, for a great many types it is easier, cognitively if not physically, to define fmap and join than to define bind. (And for the others, like Oleg's example, they can just say fmap = liftM and keep merrily on.) It was actually thinking about the type signature of join which made the whole Monad thing finally 'click' for me, which isn't bad considering that Applicative has only about halfway clicked so far. It absolutely feels more fundamental as an operation than bind does, even if bind might be the more useful combinator. There's also the consideration that when defining instances for a new type, many (most?) people tend to write an instance for the superest class in a hierarchy first, and then to work their way down. (Even without the hierarchy being explicit a lot of people, myself included, already do this for Functor/Applicative/Monad). So by the time they get to Monad they have an fmap already written, and they're like -- "why do I have to reimplement essentially the same functionality again as part of (>>=)? Oh wait, here's join instead, that'll be easier."
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Work is punishment for failing to procrastinate effectively.

Since this seems to be a contentious part of this proposal, can we
table it and have it in its own proposal?
I think having it on its own would make a lot of since, as this is the
sort of change that can happen with almost no concern for backwards
compatibility - we don't need to tie it to the rest of the
compatibility breaking changes.
Antoine
2011/1/6 Gábor Lehel
On Thu, Jan 6, 2011 at 5:42 PM, Iavor Diatchki
wrote: Hi,
On Wed, Jan 5, 2011 at 3:29 PM,
wrote: On Wed, 5 Jan 2011, Iavor Diatchki wrote:
Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
wrote: On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id" This suggests that your monad will work less efficiently if you use it with the do-notation.
No. If I need to use fmap, there is no getting around it. Only if I use "bind id" is it faster to use "join".
I am not familiar with your monad but if you are not making essential use of "bind" (or join and fmap together), then perhaps the monadic structure is not particularly important?
Join and bind are very similar and, at least in standard Haskell code, I think that "bind" has proven to be a lot more useful then "join".
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
I am not sure what you mean here, I find the "do" notation quite useful.
Also, as I mentioned before, if people find "join" easier to define then "bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class.
If people find "bind" easier to define "join", then they can define "bind", and then define "join" in terms of that---Your argument is totally symetric in the terms "bind" and "join".
The situation is not symmetric because we already have a class with ">>=" and lots of code which depends on it---so I don't think that replacing ">>=" with "join" is really plausible (I would certainly not support such a change). I am not convinced that adding "join" to the class, in addition to ">>=", buys us anything but complexity. -Iavor
I'm not sure what you mean here by "replace" -- to _remove_ bind from Monad, and add join instead? I don't know of anyone proposing this.
You're perfectly correct that it's possible to define a standalone join function yourself, and then write in what would be the proposed default definition for bind manually -- but roconnor is also perfectly correct that if the situation were the other way around, the same thing would be true in reverse. In other words, the argument is that the situation with bind being a method of Monad and join not being such is a historical accident, and not one supported by the merits.
The fact that you can still write the function outside the class and define the class method in terms of it manually is true of approximately every class method and standalone function ever written. We could write all of our classes so that the most complicated and impressive functions are the methods, while defining the simple ones standalone in terms of those, with perhaps only a small amount of annoyance overhead resulting for our users -- but we don't. We tend to seek the ability to write minimal class definitions using the simplest and most straightforward methods we can find. It sends a message: this is the easiest/best way to write an instance. If you resort to writing what should've been a method as a standalone function instead and defining the method in terms of it, the message it sends is "the definition of this class is flawed and I'm working around it". But most people probably don't think of doing this, and just define the simplest out of whatever methods they are given. After all, writing simple functions and then defining the more complex ones as combinations of those is what Haskell is all about, isn't it? So we should strive to support that, even if it can be done in our spite when we don't.
And as has been argued at length in this thread, for a great many types it is easier, cognitively if not physically, to define fmap and join than to define bind. (And for the others, like Oleg's example, they can just say fmap = liftM and keep merrily on.) It was actually thinking about the type signature of join which made the whole Monad thing finally 'click' for me, which isn't bad considering that Applicative has only about halfway clicked so far. It absolutely feels more fundamental as an operation than bind does, even if bind might be the more useful combinator.
There's also the consideration that when defining instances for a new type, many (most?) people tend to write an instance for the superest class in a hierarchy first, and then to work their way down. (Even without the hierarchy being explicit a lot of people, myself included, already do this for Functor/Applicative/Monad). So by the time they get to Monad they have an fmap already written, and they're like -- "why do I have to reimplement essentially the same functionality again as part of (>>=)? Oh wait, here's join instead, that'll be easier."
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Work is punishment for failing to procrastinate effectively.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Why is this so contentious? The proposal gives default definitions for bind and join in terms of each other; implementers can choose which they prefer to define. Am I being naive? On 06/01/2011 22:11, Antoine Latter wrote:
Since this seems to be a contentious part of this proposal, can we table it and have it in its own proposal?
I think having it on its own would make a lot of since, as this is the sort of change that can happen with almost no concern for backwards compatibility - we don't need to tie it to the rest of the compatibility breaking changes.
Antoine
2011/1/6 Gábor Lehel
: On Thu, Jan 6, 2011 at 5:42 PM, Iavor Diatchki
wrote: Hi,
On Wed, Jan 5, 2011 at 3:29 PM,
wrote: On Wed, 5 Jan 2011, Iavor Diatchki wrote:
Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
wrote: On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id" This suggests that your monad will work less efficiently if you use it with the do-notation.
No. If I need to use fmap, there is no getting around it. Only if I use "bind id" is it faster to use "join".
I am not familiar with your monad but if you are not making essential use of "bind" (or join and fmap together), then perhaps the monadic structure is not particularly important?
Join and bind are very similar and, at least in standard Haskell code, I think that "bind" has proven to be a lot more useful then "join".
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
I am not sure what you mean here, I find the "do" notation quite useful.
Also, as I mentioned before, if people find "join" easier to define then "bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class.
If people find "bind" easier to define "join", then they can define "bind", and then define "join" in terms of that---Your argument is totally symetric in the terms "bind" and "join".
The situation is not symmetric because we already have a class with ">>=" and lots of code which depends on it---so I don't think that replacing ">>=" with "join" is really plausible (I would certainly not support such a change). I am not convinced that adding "join" to the class, in addition to ">>=", buys us anything but complexity. -Iavor
I'm not sure what you mean here by "replace" -- to _remove_ bind from Monad, and add join instead? I don't know of anyone proposing this.
You're perfectly correct that it's possible to define a standalone join function yourself, and then write in what would be the proposed default definition for bind manually -- but roconnor is also perfectly correct that if the situation were the other way around, the same thing would be true in reverse. In other words, the argument is that the situation with bind being a method of Monad and join not being such is a historical accident, and not one supported by the merits.
The fact that you can still write the function outside the class and define the class method in terms of it manually is true of approximately every class method and standalone function ever written. We could write all of our classes so that the most complicated and impressive functions are the methods, while defining the simple ones standalone in terms of those, with perhaps only a small amount of annoyance overhead resulting for our users -- but we don't. We tend to seek the ability to write minimal class definitions using the simplest and most straightforward methods we can find. It sends a message: this is the easiest/best way to write an instance. If you resort to writing what should've been a method as a standalone function instead and defining the method in terms of it, the message it sends is "the definition of this class is flawed and I'm working around it". But most people probably don't think of doing this, and just define the simplest out of whatever methods they are given. After all, writing simple functions and then defining the more complex ones as combinations of those is what Haskell is all about, isn't it? So we should strive to support that, even if it can be done in our spite when we don't.
And as has been argued at length in this thread, for a great many types it is easier, cognitively if not physically, to define fmap and join than to define bind. (And for the others, like Oleg's example, they can just say fmap = liftM and keep merrily on.) It was actually thinking about the type signature of join which made the whole Monad thing finally 'click' for me, which isn't bad considering that Applicative has only about halfway clicked so far. It absolutely feels more fundamental as an operation than bind does, even if bind might be the more useful combinator.
There's also the consideration that when defining instances for a new type, many (most?) people tend to write an instance for the superest class in a hierarchy first, and then to work their way down. (Even without the hierarchy being explicit a lot of people, myself included, already do this for Functor/Applicative/Monad). So by the time they get to Monad they have an fmap already written, and they're like -- "why do I have to reimplement essentially the same functionality again as part of (>>=)? Oh wait, here's join instead, that'll be easier."
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Work is punishment for failing to procrastinate effectively.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

2011/1/6 Gábor Lehel
On Thu, Jan 6, 2011 at 5:42 PM, Iavor Diatchki
wrote: Hi,
On Wed, Jan 5, 2011 at 3:29 PM,
wrote: On Wed, 5 Jan 2011, Iavor Diatchki wrote:
Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
wrote: On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id" This suggests that your monad will work less efficiently if you use it with the do-notation.
No. If I need to use fmap, there is no getting around it. Only if I use "bind id" is it faster to use "join".
I am not familiar with your monad but if you are not making essential use of "bind" (or join and fmap together), then perhaps the monadic structure is not particularly important?
Join and bind are very similar and, at least in standard Haskell code, I think that "bind" has proven to be a lot more useful then "join".
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
I am not sure what you mean here, I find the "do" notation quite useful.
Also, as I mentioned before, if people find "join" easier to define then "bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class.
If people find "bind" easier to define "join", then they can define "bind", and then define "join" in terms of that---Your argument is totally symetric in the terms "bind" and "join".
The situation is not symmetric because we already have a class with ">>=" and lots of code which depends on it---so I don't think that replacing ">>=" with "join" is really plausible (I would certainly not support such a change). I am not convinced that adding "join" to the class, in addition to ">>=", buys us anything but complexity. -Iavor
I'm not sure what you mean here by "replace" -- to _remove_ bind from Monad, and add join instead? I don't know of anyone proposing this.
You're perfectly correct that it's possible to define a standalone join function yourself, and then write in what would be the proposed default definition for bind manually -- but roconnor is also perfectly correct that if the situation were the other way around, the same thing would be true in reverse. In other words, the argument is that the situation with bind being a method of Monad and join not being such is a historical accident, and not one supported by the merits.
The fact that you can still write the function outside the class and define the class method in terms of it manually is true of approximately every class method and standalone function ever written. We could write all of our classes so that the most complicated and impressive functions are the methods, while defining the simple ones standalone in terms of those, with perhaps only a small amount of annoyance overhead resulting for our users -- but we don't. We tend to seek the ability to write minimal class definitions using the simplest and most straightforward methods we can find. It sends a message: this is the easiest/best way to write an instance. If you resort to writing what should've been a method as a standalone function instead and defining the method in terms of it, the message it sends is "the definition of this class is flawed and I'm working around it". But most people probably don't think of doing this, and just define the simplest out of whatever methods they are given. After all, writing simple functions and then defining the more complex ones as combinations of those is what Haskell is all about, isn't it? So we should strive to support that, even if it can be done in our spite when we don't.
And as has been argued at length in this thread, for a great many types it is easier, cognitively if not physically, to define fmap and join than to define bind. (And for the others, like Oleg's example, they can just say fmap = liftM and keep merrily on.) It was actually thinking about the type signature of join which made the whole Monad thing finally 'click' for me, which isn't bad considering that Applicative has only about halfway clicked so far. It absolutely feels more fundamental as an operation than bind does, even if bind might be the more useful combinator.
There's also the consideration that when defining instances for a new type, many (most?) people tend to write an instance for the superest class in a hierarchy first, and then to work their way down. (Even without the hierarchy being explicit a lot of people, myself included, already do this for Functor/Applicative/Monad). So by the time they get to Monad they have an fmap already written, and they're like -- "why do I have to reimplement essentially the same functionality again as part of (>>=)? Oh wait, here's join instead, that'll be easier."
As a yet further note, it seems that the comonads package[1] defines the Comonad class in an analogous way, with the analogues for return, join, and bind (extract, duplicate, and extend) being the methods, default definitions given in terms of each other, and also an external liftW function defined in terms of extend (~bind) which is recommended as a simple definition for fmap for when extend has already been defined. So I'm not the only one who feels this structure is logical. [1] http://hackage.haskell.org/packages/archive/comonad/0.1.1/doc/html/Control-C...
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Work is punishment for failing to procrastinate effectively.
-- Work is punishment for failing to procrastinate effectively.

I'm delighted to see the possibility of adding join as a Monad method. I
almost always have an easier time thinking about join than (>>=) and wish I
could define join instead of (>>=), without having to pay the cost of
defining an additional joinFoo function and then having the actual join
function end up implemented via (>>=) via joinFoo.
I relate to Gábor's points that
* The familiarity advantage of (>>=) is a historical accident. I like to see
the language improve over time, rather than accumulate accidents.
* I prefer functions & methods with simpler interfaces over more complex
interfaces. I'm happy to compose these simpler operations to get more
complex operations, e.g. join+fmap vs (>>=).
- Conal
2011/1/6 Gábor Lehel
Hi,
On Wed, Jan 5, 2011 at 3:29 PM,
wrote: On Wed, 5 Jan 2011, Iavor Diatchki wrote:
Hi,
On Wed, Jan 5, 2011 at 8:04 AM,
wrote: On Tue, 4 Jan 2011, Iavor Diatchki wrote: In my completion monad, "join" is more efficent than "bind id" This suggests that your monad will work less efficiently if you use it with the do-notation.
No. If I need to use fmap, there is no getting around it. Only if I
use
"bind id" is it faster to use "join".
I am not familiar with your monad but if you are not making essential use of "bind" (or join and fmap together), then perhaps the monadic structure is not particularly important?
Join and bind are very similar and, at least in standard Haskell code,
I
think that "bind" has proven to be a lot more useful then "join".
AFAIU, In applicative style programming "join" has proven to be a lot more useful than "bind".
I am not sure what you mean here, I find the "do" notation quite useful.
Also, as I mentioned before, if people find "join" easier to define
On Thu, Jan 6, 2011 at 5:42 PM, Iavor Diatchki
wrote: then "bind", then they can define "join", and then define "bind" in terms of that---I am still not convinced that we need a new method added to the Monad class.
If people find "bind" easier to define "join", then they can define "bind", and then define "join" in terms of that---Your argument is totally symetric in the terms "bind" and "join".
The situation is not symmetric because we already have a class with ">>=" and lots of code which depends on it---so I don't think that replacing ">>=" with "join" is really plausible (I would certainly not support such a change). I am not convinced that adding "join" to the class, in addition to ">>=", buys us anything but complexity. -Iavor
I'm not sure what you mean here by "replace" -- to _remove_ bind from Monad, and add join instead? I don't know of anyone proposing this.
You're perfectly correct that it's possible to define a standalone join function yourself, and then write in what would be the proposed default definition for bind manually -- but roconnor is also perfectly correct that if the situation were the other way around, the same thing would be true in reverse. In other words, the argument is that the situation with bind being a method of Monad and join not being such is a historical accident, and not one supported by the merits.
The fact that you can still write the function outside the class and define the class method in terms of it manually is true of approximately every class method and standalone function ever written. We could write all of our classes so that the most complicated and impressive functions are the methods, while defining the simple ones standalone in terms of those, with perhaps only a small amount of annoyance overhead resulting for our users -- but we don't. We tend to seek the ability to write minimal class definitions using the simplest and most straightforward methods we can find. It sends a message: this is the easiest/best way to write an instance. If you resort to writing what should've been a method as a standalone function instead and defining the method in terms of it, the message it sends is "the definition of this class is flawed and I'm working around it". But most people probably don't think of doing this, and just define the simplest out of whatever methods they are given. After all, writing simple functions and then defining the more complex ones as combinations of those is what Haskell is all about, isn't it? So we should strive to support that, even if it can be done in our spite when we don't.
And as has been argued at length in this thread, for a great many types it is easier, cognitively if not physically, to define fmap and join than to define bind. (And for the others, like Oleg's example, they can just say fmap = liftM and keep merrily on.) It was actually thinking about the type signature of join which made the whole Monad thing finally 'click' for me, which isn't bad considering that Applicative has only about halfway clicked so far. It absolutely feels more fundamental as an operation than bind does, even if bind might be the more useful combinator.
There's also the consideration that when defining instances for a new type, many (most?) people tend to write an instance for the superest class in a hierarchy first, and then to work their way down. (Even without the hierarchy being explicit a lot of people, myself included, already do this for Functor/Applicative/Monad). So by the time they get to Monad they have an fmap already written, and they're like -- "why do I have to reimplement essentially the same functionality again as part of (>>=)? Oh wait, here's join instead, that'll be easier."
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Work is punishment for failing to procrastinate effectively.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hello,
In my experience, defining monads in terms of "fmap" and "join" leads to
code duplication. The examples we have seen in this thread---so far---are a
bit misleading because they compare a partial implementation of a monad
(join without fmap) with a complete implementation (bind). Here is an
example of what I mean:
data SP a = PutChar Char (SP a)
| GetChar (Char -> SP a)
| Return a
fmapSP :: (a -> b) -> (SP a -> SP b)
fmapSP f (PutChar c sp) = PutChar c (fmapSP f sp)
fmapSP f (GetChar k) = GetChar (\c -> fmapSP f (k c))
fmapSP f (Return a) = Return (f a)
joinSP :: SP (SP a) -> SP a
joinSP (PutChar c sp) = PutChar c (joinSP sp)
joinSP (GetChar k) = GetChar (\c -> joinSP (k c))
joinSP (Return sp) = sp
bindSP :: (a -> SP b) -> (SP a -> SP b)
bindSP f (PutChar c sp) = PutChar c (bindSP f sp)
bindSP f (GetChar k) = GetChar (\c -> bindSP f (k c))
bindSP f (Return a) = f a
I chose this example because I think that it illustrates nicely how the
three operators work, I hope that other readers find it useful.
2011/1/9 Conal Elliott
* The familiarity advantage of (>>=) is a historical accident. I like to see the language improve over time, rather than accumulate accidents.
I would be surprised if choosing ">>=" was an accident: it seems more likely that it was chosen because it matches a commonly occurring pattern in functional programs, and abstraction is all about giving names to common patterns. I completely agree with the sentiment of your second sentence but I think that adding "join" to the Monad class would be an example of "accumulating an accident" rather then simplifying things. -Iavor

I always define Functor instances, so fmap is already covered, leaving me
with a simpler join vs a more complicated bind (comparing complexity of
interface, specification and implementation).
- Conal
On Sun, Jan 9, 2011 at 6:16 PM, Iavor Diatchki
Hello, In my experience, defining monads in terms of "fmap" and "join" leads to code duplication. The examples we have seen in this thread---so far---are a bit misleading because they compare a partial implementation of a monad (join without fmap) with a complete implementation (bind). Here is an example of what I mean:
data SP a = PutChar Char (SP a) | GetChar (Char -> SP a) | Return a
fmapSP :: (a -> b) -> (SP a -> SP b) fmapSP f (PutChar c sp) = PutChar c (fmapSP f sp) fmapSP f (GetChar k) = GetChar (\c -> fmapSP f (k c)) fmapSP f (Return a) = Return (f a)
joinSP :: SP (SP a) -> SP a joinSP (PutChar c sp) = PutChar c (joinSP sp) joinSP (GetChar k) = GetChar (\c -> joinSP (k c)) joinSP (Return sp) = sp
bindSP :: (a -> SP b) -> (SP a -> SP b) bindSP f (PutChar c sp) = PutChar c (bindSP f sp) bindSP f (GetChar k) = GetChar (\c -> bindSP f (k c)) bindSP f (Return a) = f a
I chose this example because I think that it illustrates nicely how the three operators work, I hope that other readers find it useful.
2011/1/9 Conal Elliott
* The familiarity advantage of (>>=) is a historical accident. I like to see the language improve over time, rather than accumulate accidents.
I would be surprised if choosing ">>=" was an accident: it seems more likely that it was chosen because it matches a commonly occurring pattern in functional programs, and abstraction is all about giving names to common patterns. I completely agree with the sentiment of your second sentence but I think that adding "join" to the Monad class would be an example of "accumulating an accident" rather then simplifying things.
-Iavor

On Sun, 2011-01-09 at 18:16 -0800, Iavor Diatchki wrote:
Hello, In my experience, defining monads in terms of "fmap" and "join" leads to code duplication. The examples we have seen in this thread---so far---are a bit misleading because they compare a partial implementation of a monad (join without fmap) with a complete implementation (bind). Here is an example of what I mean:
data SP a = PutChar Char (SP a) | GetChar (Char -> SP a) | Return a
fmapSP :: (a -> b) -> (SP a -> SP b) fmapSP f (PutChar c sp) = PutChar c (fmapSP f sp) fmapSP f (GetChar k) = GetChar (\c -> fmapSP f (k c)) fmapSP f (Return a) = Return (f a)
joinSP :: SP (SP a) -> SP a joinSP (PutChar c sp) = PutChar c (joinSP sp) joinSP (GetChar k) = GetChar (\c -> joinSP (k c)) joinSP (Return sp) = sp
bindSP :: (a -> SP b) -> (SP a -> SP b) bindSP f (PutChar c sp) = PutChar c (bindSP f sp) bindSP f (GetChar k) = GetChar (\c -> bindSP f (k c)) bindSP f (Return a) = f a
I chose this example because I think that it illustrates nicely how the three operators work, I hope that other readers find it useful.
Yes and no: 1. In monad transformers & co. you want weakened conditions on Functor and Applicative so you cannot reuse (>>=) in them - you end up with a function anyway. 2. I don't recall anyone claiming it is shorter - the only claim was that it was simpler to think of (for some people) and 'nicer' from mathematical standpoint. Simplifying problem is common technique so I guess that defence of join is unharmed. Say - you want to prove linearity of function φ - you can either: 1. Prove aφ(x) = φ(ax) and φ(x) ⊕ φ(y) = φ(x + y) 2. Prove aφ(x) ⊕ bφ(y) = φ(ax + by) Which one do you choose? well it depends on φ and your skills. If φ is simple you and you have done it before you may prefer the 2. Otherwise you may prefer 1 even if it longer.
2011/1/9 Conal Elliott
* The familiarity advantage of (>>=) is a historical accident. I like to see the language improve over time, rather than accumulate accidents. I would be surprised if choosing ">>=" was an accident: it seems more likely that it was chosen because it matches a commonly occurring pattern in functional programs, and abstraction is all about giving names to common patterns.
Yes and no. Common pattern is function of form (read :: Read a => String -> a) - surprisingly it is not the one you define as it is too limited. (>>=) is probably better described as 'what happens' and functional programming is not about what happens but what people want to achieve (usually (>>=) but not always) or what people find easier to think about (quick survey of this thread point into direction of join). PS. As of simplifying. I have a feeling that the thread is: around 6 people with opinion (sorry if I've counted incorrectly): - Ok - sometimes (>>=) is simpler for implementation sometimes join so adding join would allow to choose simpler one or favourite 1 person with opinion - But (>>=) is great and noone is using join so why bother with join PPS. As of tutorials - somehow I don't recall anyone bothering with getting in deep of Read class on my Haskell course. Tutorial may not even mentioning it as class method and novice will not notice that the method existed

On Sun, Jan 9, 2011 at 10:41 PM, Maciej Piechotka
On Sun, 2011-01-09 at 18:16 -0800, Iavor Diatchki wrote:
Hello, In my experience, defining monads in terms of "fmap" and "join" leads to code duplication. The examples we have seen in this thread---so far---are a bit misleading because they compare a partial implementation of a monad (join without fmap) with a complete implementation (bind). Here is an example of what I mean:
data SP a = PutChar Char (SP a) | GetChar (Char -> SP a) | Return a
fmapSP :: (a -> b) -> (SP a -> SP b) fmapSP f (PutChar c sp) = PutChar c (fmapSP f sp) fmapSP f (GetChar k) = GetChar (\c -> fmapSP f (k c)) fmapSP f (Return a) = Return (f a)
joinSP :: SP (SP a) -> SP a joinSP (PutChar c sp) = PutChar c (joinSP sp) joinSP (GetChar k) = GetChar (\c -> joinSP (k c)) joinSP (Return sp) = sp
bindSP :: (a -> SP b) -> (SP a -> SP b) bindSP f (PutChar c sp) = PutChar c (bindSP f sp) bindSP f (GetChar k) = GetChar (\c -> bindSP f (k c)) bindSP f (Return a) = f a
I chose this example because I think that it illustrates nicely how the three operators work, I hope that other readers find it useful.
Yes and no:
1. In monad transformers & co. you want weakened conditions on Functor and Applicative so you cannot reuse (>>=) in them - you end up with a function anyway.
Is this true? Applicative functors compose, so you shouldn't need to
use monad transformers. Of the common monad transformers, the only
ones where the Applicative instance can be defined in terms of the
underlying Applicative instance are Identity, Reader, and Writer, all
of which are equivalent to composition (that is, you don't gain
anything by using the transformer instead of composition).
--
Dave Menendez

On Mon, 2011-01-10 at 19:01 -0500, David Menendez wrote:
On Sun, Jan 9, 2011 at 10:41 PM, Maciej Piechotka
wrote: On Sun, 2011-01-09 at 18:16 -0800, Iavor Diatchki wrote:
Hello, In my experience, defining monads in terms of "fmap" and "join" leads to code duplication. The examples we have seen in this thread---so far---are a bit misleading because they compare a partial implementation of a monad (join without fmap) with a complete implementation (bind). Here is an example of what I mean:
data SP a = PutChar Char (SP a) | GetChar (Char -> SP a) | Return a
fmapSP :: (a -> b) -> (SP a -> SP b) fmapSP f (PutChar c sp) = PutChar c (fmapSP f sp) fmapSP f (GetChar k) = GetChar (\c -> fmapSP f (k c)) fmapSP f (Return a) = Return (f a)
joinSP :: SP (SP a) -> SP a joinSP (PutChar c sp) = PutChar c (joinSP sp) joinSP (GetChar k) = GetChar (\c -> joinSP (k c)) joinSP (Return sp) = sp
bindSP :: (a -> SP b) -> (SP a -> SP b) bindSP f (PutChar c sp) = PutChar c (bindSP f sp) bindSP f (GetChar k) = GetChar (\c -> bindSP f (k c)) bindSP f (Return a) = f a
I chose this example because I think that it illustrates nicely how the three operators work, I hope that other readers find it useful.
Yes and no:
1. In monad transformers & co. you want weakened conditions on Functor and Applicative so you cannot reuse (>>=) in them - you end up with a function anyway.
Is this true? Applicative functors compose, so you shouldn't need to use monad transformers. Of the common monad transformers, the only ones where the Applicative instance can be defined in terms of the underlying Applicative instance are Identity, Reader, and Writer, all of which are equivalent to composition (that is, you don't gain anything by using the transformer instead of composition).
1. Add MaybeT and ListT to 'the only ones'. 2. As of non-trivial Applicative see InterleaveT from last MonadReader (issue 17). Regards

On Tue, Jan 11, 2011 at 4:53 AM, Maciej Piechotka
On Mon, 2011-01-10 at 19:01 -0500, David Menendez wrote:
On Sun, Jan 9, 2011 at 10:41 PM, Maciej Piechotka
wrote: On Sun, 2011-01-09 at 18:16 -0800, Iavor Diatchki wrote:
Hello, In my experience, defining monads in terms of "fmap" and "join" leads to code duplication. The examples we have seen in this thread---so far---are a bit misleading because they compare a partial implementation of a monad (join without fmap) with a complete implementation (bind). Here is an example of what I mean:
data SP a = PutChar Char (SP a) | GetChar (Char -> SP a) | Return a
fmapSP :: (a -> b) -> (SP a -> SP b) fmapSP f (PutChar c sp) = PutChar c (fmapSP f sp) fmapSP f (GetChar k) = GetChar (\c -> fmapSP f (k c)) fmapSP f (Return a) = Return (f a)
joinSP :: SP (SP a) -> SP a joinSP (PutChar c sp) = PutChar c (joinSP sp) joinSP (GetChar k) = GetChar (\c -> joinSP (k c)) joinSP (Return sp) = sp
bindSP :: (a -> SP b) -> (SP a -> SP b) bindSP f (PutChar c sp) = PutChar c (bindSP f sp) bindSP f (GetChar k) = GetChar (\c -> bindSP f (k c)) bindSP f (Return a) = f a
I chose this example because I think that it illustrates nicely how the three operators work, I hope that other readers find it useful.
Yes and no:
1. In monad transformers & co. you want weakened conditions on Functor and Applicative so you cannot reuse (>>=) in them - you end up with a function anyway.
Is this true? Applicative functors compose, so you shouldn't need to use monad transformers. Of the common monad transformers, the only ones where the Applicative instance can be defined in terms of the underlying Applicative instance are Identity, Reader, and Writer, all of which are equivalent to composition (that is, you don't gain anything by using the transformer instead of composition).
1. Add MaybeT and ListT to 'the only ones'.
If you want the <*> = ap, then you need Monad f => Applicative (MaybeT f). Otherwise, it's just composition. The Applicative instance for ListT is just composition with []. Also, ListT only produces monads when applied to Identity or Reader.
2. As of non-trivial Applicative see InterleaveT from last MonadReader (issue 17).
InterleaveT is not a monad transformer. It requires a monad, but
produces a non-monad applicative functor.
--
Dave Menendez

2011/1/9 Conal Elliott
... [fair points deleted.] I relate to Gábor's points that
* The familiarity advantage of (>>=) is a historical accident. I like to see the language improve over time, rather than accumulate accidents. * I prefer functions & methods with simpler interfaces over more complex interfaces. I'm happy to compose these simpler operations to get more complex operations, e.g. join+fmap vs (>>=).
I find this pretty funny, actually, because the early papers on monads in a programming context still used the categorical formulation in terms of join, and were pretty opaque reading as a consequence! When things are re-stated in terms of >>=, the parallels with interchange of let-bindings suddenly becomes obvious and it becomes possible to start to explain this stuff to programmers or computer architects (rather than mathematicians). This is a bias I developed from actually trying to teach this stuff in 1-2 lectures to advanced undergrads and grad students. Which of course says nothing about which form is easier to *write*, but I'm inclined to believe that it's easiest to read and write the form whose use you understand best (ie brevity is not the sole criterion here by any means; understandability has to be paramount). My bias is to assume my reader is, like me, a programmer first and a mathematician second. For example, I find it relatively easy to understand >>= in the continuation monad, but have to spend a long time puzzling my way through join. For simple stuff like [] and Maybe, of course, the code complexity argument is moot, and join is pretty natural unless you spend your time re-formulating list comprehensions for fun. -Jan-Willem Maessen

On Sat, 2011-01-15 at 22:43 -0500, Jan-Willem Maessen wrote:
Which of course says nothing about which form is easier to *write*, but I'm inclined to believe that it's easiest to read and write the form whose use you understand best (ie brevity is not the sole criterion here by any means; understandability has to be paramount). My bias is to assume my reader is, like me, a programmer first and a mathematician second. For example, I find it relatively easy to understand >>= in the continuation monad, but have to spend a long time puzzling my way through join. For simple stuff like [] and Maybe, of course, the code complexity argument is moot, and join is pretty natural unless you spend your time re-formulating list comprehensions for fun.
-Jan-Willem Maessen
I agree that there are advantages of both ways and they are perfectly compatible with each other. While I don't know about GHC internals I'd assume that class v-tables (term borrowed from C++ I'm not sure about Haskell terminology) is per-class and not copied for each function invocation. Therefore if we can include both ways which can be interleaved (Monad written by 'join' person can be used by 'bind' person and vice-versa) why don't do that? I don't think there is anyone who propose to remove (>>=) from Monad class. As of simplification - I find join simpler as it allows to pattern match in some cases and have one 'complicated' parameter less. You may find bind simpler as it is closer to imperative style. However I often use (>>=)/do notation. Regards PS. I don't think I constitute a mathematician - I don't know much about theory of categories except pieces I learn along Haskell.

Maciej Piechotka schrieb:
I agree that there are advantages of both ways and they are perfectly compatible with each other. While I don't know about GHC internals I'd assume that class v-tables (term borrowed from C++ I'm not sure about Haskell terminology) is per-class and not copied for each function invocation.
"Method dictionary" http://www.haskell.org/haskellwiki/OOP_vs_type_classes

On 1/16/11 12:43 PM, Henning Thielemann wrote:
Maciej Piechotka schrieb:
I agree that there are advantages of both ways and they are perfectly compatible with each other. While I don't know about GHC internals I'd assume that class v-tables (term borrowed from C++ I'm not sure about Haskell terminology) is per-class and not copied for each function invocation.
"Method dictionary"
Perhaps I missed it, but I don't see anything in that page clarifying whether the actual underlying table is shared (i.e., the dictionary is just a pointer to a global table) or not (i.e., the dictionary is a constructed copy of the table). As far as the surface language is concerned the distinction doesn't matter, but as far as people worrying about performance considerations due to the size of dictionaries it does. -- Live well, ~wren

On Sun, 16 Jan 2011, wren ng thornton wrote:
On 1/16/11 12:43 PM, Henning Thielemann wrote:
Maciej Piechotka schrieb:
I agree that there are advantages of both ways and they are perfectly compatible with each other. While I don't know about GHC internals I'd assume that class v-tables (term borrowed from C++ I'm not sure about Haskell terminology) is per-class and not copied for each function invocation.
"Method dictionary"
Perhaps I missed it, but I don't see anything in that page clarifying whether the actual underlying table is shared (i.e., the dictionary is just a pointer to a global table) or not (i.e., the dictionary is a constructed copy of the table). As far as the surface language is concerned the distinction doesn't matter, but as far as people worrying about performance considerations due to the size of dictionaries it does.
Sorry, I just wanted to answer the question how these class v-tables are called in Haskell.

On Sunday 16 January 2011 7:08:59 pm wren ng thornton wrote:
Perhaps I missed it, but I don't see anything in that page clarifying whether the actual underlying table is shared (i.e., the dictionary is just a pointer to a global table) or not (i.e., the dictionary is a constructed copy of the table). As far as the surface language is concerned the distinction doesn't matter, but as far as people worrying about performance considerations due to the size of dictionaries it does.
I can't give a definitive answer, however... I would be surprised if dictionaries for any given base-case instance weren't essentially global. So, Num Int and Monoid [a], for instance, I'd expect to just be pointer passing, if that isn't eliminated entirely. However, there are cases where I'd be surprised if the dictionary is global. Polymorphic recursion, for instance, is almost certain to lead to dictionaries being constructed per-call at runtime, like: foo :: Show a => Integer -> a -> String foo 0 x = show x foo (n+1) x = foo n (x, x) This makes use of a dictionary determined by its first parameter, and I wouldn't expect GHC to memoize all of them (that seems like a bad performance strategy). In between, it probably depends on how much information is available statically about which dictionaries are actually used. -- Dan

On January 15, 2011 22:43:32 Jan-Willem Maessen wrote:
For example, I find it relatively easy to understand >>= in the continuation monad, but have to spend a long time puzzling my way through join.
It's not that bad once you get used to thinking of it. Join simply merges an inner computation into an outer one. To put this in the continuation passing framework. You have a series of computations A, B, etc. strung together by continuation passing A--B--C--D--E ... For a predetermined string, you have a strictly applicative framework. If, say, you want to dynamically compute the next bit of the string of computations C1--C2--C3 based of A--B--C, you requires a monad (i.e., join). Join allows you to merge the C1--C2--C3 dynamically determined from A--B--C into the continuation passing string to get A--B--C--C1--C2--C3--D--E ... (C1--C2--C3 is determined by A--B--C) This is actually relatively clear from join's type join :: Monad m => m (m a) -> m a It takes a string of computations (as indicated by the outer m) that generates a string of computations generating an a (as indicated by the inner m a). It changes this into just a string of computations generating an a. How can it do this? It must set things up to first run the given string of computations in order to determine the string of computations that give a. Once it gets this, it must then run it in order to get a. join (CPS f) = CPS $ \k -> unCPS (f id) k That is, when invoked (i.e., when given a continuation k), invoke f with the continuation id. This will cause f to return the inner computation it computes. Then invoke this returned computation by passing it k. What would the actual haskell code look like for the string of computations? It's a bit messy in applicative style because it is sequence/flow orientated E <*> (D <*> join (C <*> (B <*> A))) - run A and feed the results in B, - run B and feed the results in C, - run the results of this (join) and feed them into D, and - run D and feed the results in E. Something a lot more friendly to the notation would be if A, B, and C were independent computations whose combined results were to determine another computation via a function g. This result, along with D and E, where then to be fed into yet another function f. This is simply expressed as f <$> join (g <$> A <*> B <*> C) <*> D <*> E - run A and bind the result as the first argument of g, - run B and bind the result as the second argument of g, - run C and bind the result as the third argument of g, - run g to dynamically determine the next thing to run, - run this (join) and bind its result as the first argument of f, - run D and bind the result as the second argument of f, and - run E and bind the result as the third argument of f. (run A, etc. may not do any more work than bind a thunk due to laziness) It is exactly what you would expect "f (g A B C) D E" to do. The difference is the interaction can be a lot more than just a pure application. You can have side effects, backtracking, outer joins, and so on. Although in the above I used pure functions (hence the <$>), this extends to functions too. The unfortunate pain you pay for this additional power is manually having to specify the application (<$> and <*>) and merging (join). If the compiler could figure this all out for you based on the underlying types, wow! Cheers! -Tyson PS: I hope the above example makes it clear exactly where join is required. This is precisely the additional power of a monad gives you over applicative.

Ahem On 17 Jan 2011, at 17:22, Tyson Whitehead wrote:
On January 15, 2011 22:43:32 Jan-Willem Maessen wrote:
For example, I find it relatively easy to understand >>= in the continuation monad, but have to spend a long time puzzling my way through join.
It's not that bad once you get used to thinking of it. Join simply merges an inner computation into an outer one.
[..]
Something a lot more friendly to the notation would be if A, B, and C were independent computations whose combined results were to determine another computation via a function g. This result, along with D and E, where then to be fed into yet another function f. This is simply expressed as
f <$> join (g <$> A <*> B <*> C) <*> D <*> E
Funnily enough, SHE lets you write (| f (| g A B C @ |) D E |) where the postfixed @ denotes a join: g's effects happen "after" those of A, B and C, but "before" those of D and E. [..] I'm tempted to support if <- b then t else f for (b >>= \ z -> if z then t else f) and case <- s of {p1 -> e1; ..} similarly.
The unfortunate pain you pay for this additional power is manually having to specify the application (<$> and <*>) and merging (join). If the compiler could figure this all out for you based on the underlying types, wow!
To achieve such a thing, one would need to ensure a slightly more deliberate separation of "value" and "computation" in the presentation of types. In Haskell, we use, e.g., [Int], for * pure computations of lists of integers * nondeterministic computations of integers and we spend syntax (do-notation, lifting operators) to distinguish the two modes of usage. If every type was clearly decomposable into its computation and value components, the above possibilities would be distinct (but isomorphic) and we could spend less syntax on plumbing in programs. I fear it's too late to reorganize Haskell along these lines, but it's bound to happen in some language (Disciple? Eff?) sometime. As any ML programmer will tell you, functional programming is really cool, even when it isn't purely functional programming. All the best Conor

On 1/17/11 4:20 PM, Conor McBride wrote:
I'm tempted to support
if <- b then t else f
for
(b >>= \ z -> if z then t else f)
and
case <- s of {p1 -> e1; ..}
similarly.
Habit[1] supports both of these shorthands ---both the semantics, and the syntax even--- and I'd love to have them in Haskell proper (whether GHC Haskell or SHE Haskell :) [1] http://hasp.cs.pdx.edu/habit-report-Aug2009.pdf -- Live well, ~wren

Hi,
On Mon, Jan 17, 2011 at 1:20 PM, Conor McBride
I'm tempted to support
if <- b then t else f
for
(b >>= \ z -> if z then t else f)
and
case <- s of {p1 -> e1; ..}
similarly.
Habit (from PSU) uses this syntax. (ref. p. 22 http://hasp.cs.pdx.edu/habit-report-Aug2009.pdf) They also allow one-armed monadic if-then-else, like in C, where the omitted "else" branch is filled in with "return ()". -Iavor PS: sorry that this is not at all on topic but I thought it might of interest to folks.

On 1/17/11 5:47 PM, wren ng thornton wrote:
Habit[1] supports both of these shorthands ---both the semantics, and the syntax even--- and I'd love to have them in Haskell proper (whether GHC Haskell or SHE Haskell :)
On 1/17/11 5:48 PM, Iavor Diatchki wrote:
Habit (from PSU) uses this syntax. (ref. p. 22 http://hasp.cs.pdx.edu/habit-report-Aug2009.pdf) They also allow one-armed monadic if-then-else, like in C, where the omitted "else" branch is filled in with "return ()".
Jinx! -- Live well, ~wren

On January 17, 2011 16:20:22 Conor McBride wrote:
Ahem
: )
The unfortunate pain you pay for this additional power is manually having to specify the application (<$> and <*>) and merging (join). If the compiler could figure this all out for you based on the underlying types, wow!
To achieve such a thing, one would need to ensure a slightly more deliberate separation of "value" and "computation" in the presentation of types. In Haskell, we use, e.g., [Int], for
* pure computations of lists of integers * nondeterministic computations of integers
and we spend syntax (do-notation, lifting operators) to distinguish the two modes of usage. If every type was clearly decomposable into its computation and value components, the above possibilities would be distinct (but isomorphic) and we could spend less syntax on plumbing in programs.
I'm pretty sure I know what "pure computations of lists of integers" is, but I'm not so sure about "nondeterministic computations of integers". If it is not too much of an effort, could you clarify with a quick example? Thanks! -Tyson

On 1/19/11 1:24 PM, Tyson Whitehead wrote:
On January 17, 2011 16:20:22 Conor McBride wrote:
To achieve such a thing, one would need to ensure a slightly more deliberate separation of "value" and "computation" in the presentation of types. In Haskell, we use, e.g., [Int], for
* pure computations of lists of integers * nondeterministic computations of integers
and we spend syntax (do-notation, lifting operators) to distinguish the two modes of usage. If every type was clearly decomposable into its computation and value components, the above possibilities would be distinct (but isomorphic) and we could spend less syntax on plumbing in programs.
I'm pretty sure I know what "pure computations of lists of integers" is, but I'm not so sure about "nondeterministic computations of integers".
Consider I have two black boxes, each with a shiny button on them. The first box is a deterministic machine, and when I press the button it gives me a sequence of integers. The second box is a nondeterministic machine, and when I press the button it gives me a superposition of many versions of one integer. For deterministic purposes I can just select one of those versions at random. Or, if I have another nondeterministic machine, I can just feed it the whole superposition as the new machine's starting (multi)state. The difference is just that for the first box I like to think of the result as many numbers, like a list of phone numbers for all my friends; whereas I like to think of the second box as only giving me one number, but it's a bit fuzzy about which number that is. In a lot of ways lists are actually a horrible model for nondeterminism. Because lists have an order, and because of how that order is preserved by the list monad, one of the major pieces of information lists work at preserving is the history of choices that lead to each particular possibility. But in practice we usually don't care about that history. We often just want to know which possibilities are viable, in which case a set or skiplist is a more helpful representation (or weighted variants if we care about multiplicity). Or we care about possibilities in order of how "good" they are, in which case we really want a priority queue or similar structure. Any monad which behaves sufficiently like a container (lists, sets, multisets, priority queues,...) can serve as a model for nondeterminism. They just vary in what sorts of information they preserve about the versions of the value they contain. -- Live well, ~wren

On 1/17/11 12:22 PM, Tyson Whitehead wrote:
On January 15, 2011 22:43:32 Jan-Willem Maessen wrote:
For example, I find it relatively easy to understand>>= in the continuation monad, but have to spend a long time puzzling my way through join.
It's not that bad once you get used to thinking of it. Join simply merges an inner computation into an outer one.
I've been doing a lot more of that lately, or rather _not_ doing it. In particular, there's often a desire when working in monads like IO to do some computation now (and share it) and then do some computation later (possibly many times). The natural way of doing this is to have your function return IO(IO X) where the outer IO is run now and the inner IO is run later. If you want to do both of them now you just call join. One example where this is especially helpful is when dealing with file handling based on commandline flags. In most programs we'd like to run the commandline sanity checks as early as possible so that we can fail fast, but the actual file manipulation can happen much later and far away from main. In the conventional (>>=) style of thinking ---often seen in imperative languages--- we'd have to do something like open the files early and then pass filehandles throughout the program (or worse, pass the file names throughout the program and open/close the files repeatedly). This is not only against what we'd like to do, it's also unsightly, error prone, and a maintenence nightmare. But once we switch over to a join style of thinking, the IO(IO X) approach becomes obvious. We simply check the flags now and return a thunk that will manipulate the file later. We have to pass the thunk around, but the action encapsulates whatever we want to do with the file rather than being the file itself. An added benefit of this style is that it allows us to keep the code that verifies commandline flags close by the code that makes use of that information, instead of smearing it across the whole program and loosing track of the interrelatedness. -- Live well, ~wren

I should mention Re: the original topic of discussion that I'm
actually a class completist, and was roundly shouted down and told to
use RULEs when I suggested moving a method into a class for efficiency
purposes (no, don't remember quite what function in question
was---except that it actually improved asymptotic complexity, which I
thought was pretty compelling at the time).
But I originally chimed in to the side conversation about whether >>=
or join is more natural when explaining monads computationally (as
opposed to mathematically) and thus when writing code intended to be
read (as all good code should).
I think Tyson Whitehead unwittingly made my point rather well using
the example of the CPS monad. I believe his simple explanation of
join in CPS actually leads to an incorrect definition, whereas
explaining >>= in CPS is about as straightforward as anything
involving CPS can be (which is to say, more than a little convoluted).
On Mon, Jan 17, 2011 at 12:22 PM, Tyson Whitehead
On January 15, 2011 22:43:32 Jan-Willem Maessen wrote:
For example, I find it relatively easy to understand >>= in the continuation monad, but have to spend a long time puzzling my way through join.
It's not that bad once you get used to thinking of it. Join simply merges an inner computation into an outer one.
Sure, I understand this much. And I argued that it was hard to think about CPS in terms of fmap and join, so you argued otherwise:
... Join allows you to merge the C1--C2--C3 dynamically determined from A--B--C into the continuation passing string to get
A--B--C--C1--C2--C3--D--E ... (C1--C2--C3 is determined by A--B--C)
This is actually relatively clear from join's type
join :: Monad m => m (m a) -> m a
It takes a string of computations (as indicated by the outer m) that generates a string of computations generating an a (as indicated by the inner m a). It changes this into just a string of computations generating an a.
How can it do this? It must set things up to first run the given string of computations in order to determine the string of computations that give a. Once it gets this, it must then run it in order to get a.
join (CPS f) = CPS $ \k -> unCPS (f id) k
That is, when invoked (i.e., when given a continuation k), invoke f with the continuation id. This will cause f to return the inner computation it computes. Then invoke this returned computation by passing it k.
Except that I believe this definition is incorrect, as it introduces a fresh continuation (id) that is not constructed from k! Moreover, it begs the question of how the mechanics of continuation-passing are accomplished. Here's a rather natural definition of the CPS monad, written from the top of my head: return x = CPS (\k -> k x) CPS ca >>= fb = CPS (\k -> ca (\a -> unCPS (fb a) k)) Here we have a computation returning an a (ca), and we construct a continuation to pass to it that receives the a and passes it on to fb, then passes our continuation on to that. It lays bare the essence of continuation passing (well, we might need to erase the CPS/unCPS operations to make it really clear, but it's reasonably easy to convey). Using these definitions, and join = (>>= id), we obtain: join (CPS cca) = CPS (\k -> cca (\ca -> unCPS ca k)) That is, we construct a fresh continuation that we pass to cca, that receives the computation ca returning an a, and invokes ca with continuation k. I believe this is rather different from your definition, as the type of the continuation that we pass to cca is (say) a -> r in the above definition, but is a -> a in yours. I derived >>= in terms of your definition of join, as well, but it's rather unenlightening. I think the resulting monad might be isomorphic to the Identity, but I'm pretty sure call/cc doesn't really do anything. -Jan-Willem Maessen

On Mon, Jan 17, 2011 at 7:24 PM, Jan-Willem Maessen
Using these definitions, and join = (>>= id), we obtain:
join (CPS cca) = CPS (\k -> cca (\ca -> unCPS ca k))
That is, we construct a fresh continuation that we pass to cca, that receives the computation ca returning an a, and invokes ca with continuation k. I believe this is rather different from your definition, as the type of the continuation that we pass to cca is (say) a -> r in the above definition, but is a -> a in yours.
Argh, I meant ca -> r and ca -> ca in the types above. Which just goes to show, I suppose. -Jan

On January 17, 2011 19:24:12 Jan-Willem Maessen wrote:
join (CPS f) = CPS $ \k -> unCPS (f id) k
<snip>
Using these definitions, and join = (>>= id), we obtain:
join (CPS cca) = CPS (\k -> cca (\ca -> unCPS ca k))
That is the same. The key is that the final computation here is unCPS ca k. Delaying the application of k (returning unCPS ca and then applying k gives the same result as directly applying unCPS ca k and returning it) we get join (CPS cca) = CPS (\k -> cca (\ca -> unCPS ca k)) join (CPS cca) = CPS (\k -> cca (\ca -> unCPS ca) k) Now, delaying the transformation by unCPS (returning ca and then forming unCPS ca gives the same result as directly forming unCPS ca and returning it) we get join (CPS cca) = CPS (\k -> unCPS (cca (\ca -> ca)) k) join (CPS cca) = CPS (\k -> unCPS (cca id) k) which brings us back to the above. Cheers! -Tyson

On Mon, Jan 17, 2011 at 10:36 PM, Tyson Whitehead
On January 17, 2011 19:24:12 Jan-Willem Maessen wrote:
join (CPS f) = CPS $ \k -> unCPS (f id) k
<snip>
Using these definitions, and join = (>>= id), we obtain:
join (CPS cca) = CPS (\k -> cca (\ca -> unCPS ca k))
That is the same. The key is that the final computation here is unCPS ca k. Delaying the application of k (returning unCPS ca and then applying k gives the same result as directly applying unCPS ca k and returning it) we get
join (CPS cca) = CPS (\k -> cca (\ca -> unCPS ca k)) join (CPS cca) = CPS (\k -> cca (\ca -> unCPS ca) k)
Now, delaying the transformation by unCPS (returning ca and then forming unCPS ca gives the same result as directly forming unCPS ca and returning it) we get
join (CPS cca) = CPS (\k -> unCPS (cca (\ca -> ca)) k) join (CPS cca) = CPS (\k -> unCPS (cca id) k)
which brings us back to the above.
How are you defining CPS? In order to use id as a continuation in
these circumstances, you pretty much need
newtype CPS a = CPS { unCPS :: forall w. (a -> w) -> w }
But that's (mostly) isomorphic to the Identity monad (i.e., you can't
define callCC).
The advantage of Jan-Willem's definition is that you can use it with
the more-familiar Cont monad. I'd argue that it's truer to the sense
of continuation passing as well.
--
Dave Menendez

On 1/17/11 11:10 PM, David Menendez wrote:
How are you defining CPS? In order to use id as a continuation in these circumstances, you pretty much need
newtype CPS a = CPS { unCPS :: forall w. (a -> w) -> w }
That tends to be my first thought when I think about CPS. In particular, the above gets at the fact that the CPS transform compilers do is just double negation.
But that's (mostly) isomorphic to the Identity monad
Indeed. But then, my first thoughts about CPS are more about the compiler transformation rather than about callCC. Cont is certainly valuable, but it's not the first thing that comes to mind for me. -- Live well, ~wren

Am Montag, den 17.01.2011, 19:24 -0500 schrieb Jan-Willem Maessen:
I think Tyson Whitehead unwittingly made my point rather well using the example of the CPS monad. I believe his simple explanation of join in CPS actually leads to an incorrect definition, whereas explaining >>= in CPS is about as straightforward as anything involving CPS can be (which is to say, more than a little convoluted).
If both (>>=) and join are class methods with default implementations that use the respective other method, you can still define the Cont monad instance in terms of (>>=), while you can use join where it is easier (e.g. in the [] instance). So instead of arguing whether join or (>>=) is easier, more natural or whatever, just let us make both a method of Monad. Best wishes, Wolfgang

On Tue, Jan 18, 2011 at 10:00 AM, Wolfgang Jeltsch
Am Montag, den 17.01.2011, 19:24 -0500 schrieb Jan-Willem Maessen:
I think Tyson Whitehead unwittingly made my point rather well using the example of the CPS monad. I believe his simple explanation of join in CPS actually leads to an incorrect definition, whereas explaining >>= in CPS is about as straightforward as anything involving CPS can be (which is to say, more than a little convoluted).
If both (>>=) and join are class methods with default implementations that use the respective other method, you can still define the Cont monad instance in terms of (>>=), while you can use join where it is easier (e.g. in the [] instance). So instead of arguing whether join or (>>=) is easier, more natural or whatever, just let us make both a method of Monad.
Right. "Easier" is something of a subjective quality. A significant share of the people contributing to this thread have expressed the sentiment that they find join easier, at least for many Monads, and I find it unlikely that any amount of reasoned debate is going to convince them that their subjective experiences aren't what they are. The question becomes whether the benefits of making join a method -- making it easier and more obvious for these people to define their Monads using join -- outweigh the costs: having another method in the Monad class, the sense that this is unnecessary, GHC potentially not optimizing it as well in do statements, and that in some cases for some people join+fmap would be harder and/or more verbose/duplicative to define than bind and they might accidentally define join+fmap instead when they should've used bind(?).
Best wishes, Wolfgang
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Work is punishment for failing to procrastinate effectively.

Wolfgang Jeltsch wrote:
If both (>>=) and join are class methods with default implementations that use the respective other method, you can still define the Cont monad instance in terms of (>>=), while you can use join where it is easier (e.g. in the [] instance). So instead of arguing whether join or (>>=) is easier, more natural or whatever, just let us make both a method of Monad.
Does anyone want to comment on my comparison with restricted monads, where '>>=' can be defined, but 'join' cannot?

On Thu, Jan 20, 2011 at 6:58 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
Wolfgang Jeltsch wrote:
So instead of arguing whether join or
(>>=) is easier, more natural or whatever, just let us make both a method of Monad.
Does anyone want to comment on my comparison with restricted monads, where '>>=' can be defined, but 'join' cannot?
I am in favor of being able to choose between join and >>= when defining Monad instances and don't consider consistency with RMonad very important. Sebastian

On 20 January 2011 10:58, Henning Thielemann
Wolfgang Jeltsch wrote:
If both (>>=) and join are class methods with default implementations that use the respective other method, you can still define the Cont monad instance in terms of (>>=), while you can use join where it is easier (e.g. in the [] instance). So instead of arguing whether join or (>>=) is easier, more natural or whatever, just let us make both a method of Monad.
Does anyone want to comment on my comparison with restricted monads, where '>>=' can be defined, but 'join' cannot?
Just for clarity, are you referring to the restricted monads from the rmonad package[1]? If so, I see no reason (yet) why the RMonad type class can't be defined as: class RMonad m where join :: Suitable m a => m (m a) -> m a Where the Set instance becomes: instance RMonad Set where join ss = withResConstraints $ \SetConstraints -> fold union empty ss Regards, Bas [1] http://hackage.haskell.org/package/rmonad

Bas van Dijk wrote:
On 20 January 2011 10:58, Henning Thielemann
wrote: Wolfgang Jeltsch wrote:
If both (>>=) and join are class methods with default implementations that use the respective other method, you can still define the Cont monad instance in terms of (>>=), while you can use join where it is easier (e.g. in the [] instance). So instead of arguing whether join or (>>=) is easier, more natural or whatever, just let us make both a method of Monad.
Does anyone want to comment on my comparison with restricted monads, where '>>=' can be defined, but 'join' cannot?
Just for clarity, are you referring to the restricted monads from the rmonad package[1]?
If so, I see no reason (yet) why the RMonad type class can't be defined as:
class RMonad m where join :: Suitable m a => m (m a) -> m a
Where the Set instance becomes:
instance RMonad Set where join ss = withResConstraints $ \SetConstraints -> fold union empty ss
I haven't tried it, but I think you'd need Suitable m (m a) in the constraints, either of join itself, or of (>>=) to make the default definition typecheck. I ran into similar problems with trying to make RApplicative. Many of the Applicative combinators use intermediate functions heavily, leading to a need for Suitable m (a -> b) for various a and b, and there are often multiple different possible definitions of the combinators that lead to different constraints being needed. My suspicion is that the monad/applicative laws imply some rules about the Suitable instances, but I haven't thought this through properly. In that sense RMonad is something of an unprincipled hack :-) Ganesh =============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ===============================================================================

Sittampalam, Ganesh schrieb:
Bas van Dijk wrote:
Just for clarity, are you referring to the restricted monads from the rmonad package[1]?
yes
If so, I see no reason (yet) why the RMonad type class can't be defined as:
class RMonad m where join :: Suitable m a => m (m a) -> m a
Where the Set instance becomes:
instance RMonad Set where join ss = withResConstraints $ \SetConstraints -> fold union empty ss
I haven't tried it, but I think you'd need Suitable m (m a) in the constraints, either of join itself, or of (>>=) to make the default definition typecheck.
I ran into similar problems with trying to make RApplicative. Many of the Applicative combinators use intermediate functions heavily, leading to a need for Suitable m (a -> b) for various a and b, and there are often multiple different possible definitions of the combinators that lead to different constraints being needed.
I tried the same and got the same problems. My favorite example is a list like monad on StorableVector. Suitable StorableVector a means Storable a and there is no Storable (a -> b) I could define an RApplicative class only if I introduced an auxiliary type, in the example a stream-fusion:Stream. Then I could define a ZipList instance for StorableVector by converting each StorableVector to Stream and the zipped resulting Stream back to StorableVector.

On Thursday 20 January 2011 3:26:53 pm Henning Thielemann wrote:
I could define an RApplicative class only if I introduced an auxiliary type, in the example a stream-fusion:Stream. Then I could define a ZipList instance for StorableVector by converting each StorableVector to Stream and the zipped resulting Stream back to StorableVector.
Relating to my other mail, applicatives are already sort of equipped to be restricted, because their category theoretic analogues are lax monoidal functors. However, you need to look at their first-order interface: unit :: f () pair :: (f a, f b) -> f (a, b) The Applicative class takes advantage of the existence of exponential objects to provide a nicer interface to program with, but the above is the closer to the category theory. So, we can probably define a restricted applicative like so: let Suitable identify a monoidal subcategory of Hask, with Suitable () and (Suitable a, Suitable b) => Suitable (a, b) A restricted applicative is a lax monoidal functor from the subcategory to Hask, so: unit :: f () pair :: (Suitable a, Suitable b) => (f a, f b) -> f (a, b) Satisfying some coherence conditions. In general, the subcategory needn't have (all) exponential objects, so we cannot provide the Applicative interface. The only problem with this in Haskell might be enforcing the conditions on Suitable. -- Dan

Dan Doel schrieb:
On Thursday 20 January 2011 3:26:53 pm Henning Thielemann wrote:
I could define an RApplicative class only if I introduced an auxiliary type, in the example a stream-fusion:Stream. Then I could define a ZipList instance for StorableVector by converting each StorableVector to Stream and the zipped resulting Stream back to StorableVector.
Relating to my other mail, applicatives are already sort of equipped to be restricted, because their category theoretic analogues are lax monoidal functors. However, you need to look at their first-order interface:
unit :: f () pair :: (f a, f b) -> f (a, b)
The Applicative class takes advantage of the existence of exponential objects to provide a nicer interface to program with, but the above is the closer to the category theory. So, we can probably define a restricted applicative like so:
let Suitable identify a monoidal subcategory of Hask, with Suitable () and (Suitable a, Suitable b) => Suitable (a, b) A restricted applicative is a lax monoidal functor from the subcategory to Hask, so:
unit :: f () pair :: (Suitable a, Suitable b) => (f a, f b) -> f (a, b)
Satisfying some coherence conditions. In general, the subcategory needn't have (all) exponential objects, so we cannot provide the Applicative interface. The only problem with this in Haskell might be enforcing the conditions on Suitable.
Translating for me: liftA2 is essentially pair with subsequent fmap. I already though about this and came to the conclusion, that this does not help in my case. A zipWith3 written as pure f <*> storableVectorA <*> storableVectorB <*> storableVectorC would require a Storable instance for pairs. I provided that in storable-tuple, but then it is not efficient to store intermediate pairs in StorableVector. That's why I think that an optimal solution would neither require (Suitable a, Suitable b) => Suitable (a -> b) nor (Suitable a, Suitable b) => Suitable (a, b) but would best have no such constraint at all. Using an intermediate type does not have such an constraint, but unfortunately does not look nice. Maybe I should switch thread topic now ...

On Thursday 20 January 2011 5:23:56 pm Henning Thielemann wrote:
Translating for me: liftA2 is essentially pair with subsequent fmap.
Yes. And I didn't mention it, but there's a similar restricted functor underlying the restricted applicative, which is a functor from a subcategory of Hask to Hask. So: rfmap :: (Suitable a, Suitable b) => (a -> b) -> f a -> f b In the normal applicative case: pure x = fmap (const x) unit f <*> x = fmap eval (pair (f, x)) where eval = uncurry ($) But the latter doesn't make sense if exponentials don't exist.
I already though about this and came to the conclusion, that this does not help in my case. A zipWith3 written as pure f <*> storableVectorA <*> storableVectorB <*> storableVectorC would require a Storable instance for pairs. I provided that in storable-tuple, but then it is not efficient to store intermediate pairs in StorableVector.
I can believe it isn't efficient. But it's possible. An implementation more like vector (for instance) would obviously work out better, because: unit = UnitVector pair (l, r) = PairVector l r instead of building a new vector and copying all the elements. Anyhow, my mails were more concerned with whether or not these things are 'unprincipled hacks,' not whether they're practically useful. -- Dan

On Thu, 20 Jan 2011, Dan Doel wrote:
I can believe it isn't efficient. But it's possible. An implementation more like vector (for instance) would obviously work out better, because:
unit = UnitVector pair (l, r) = PairVector l r
Yes, this one is much easier. It means that actual zipping is defered to the final fmap. This gives me the idea to use such pairs of vectors as temporary types, and not stream-fusion:Stream.
instead of building a new vector and copying all the elements. Anyhow, my mails were more concerned with whether or not these things are 'unprincipled hacks,' not whether they're practically useful.
I wonder whether practically useful definitions would require unprincipled hacks. :-)

On Thursday 20 January 2011 8:24:36 am Sittampalam, Ganesh wrote:
My suspicion is that the monad/applicative laws imply some rules about the Suitable instances, but I haven't thought this through properly. In that sense RMonad is something of an unprincipled hack :-)
RMonad is actually given a category theoretic analogue in Monads Need Not Be Endofunctors.* There one has: Two categories J and C A functor F : J -> C A mapping T of J objects to C objects A family of morphisms eta_A : JA -> TA for each object A of J For A,B objects of J, and k : JA -> TB, k* : TA -> TB satisfying some monad-like laws. For RMonad we have (I think this is close): J is some full subcategory of C = Hask identified by Suitable F is the inclusion functor from J to Hask T is the RMonad type constructor eta : forall a. Suitable m a => a -> m a ext : forall a b. (Suitable m a, Suitable m b) => (a -> m b) -> m a -> m b But T cannot be composed with itself, obviously. So join doesn't make sense. However, you can also count me as another person who doesn't care what difficulties exist for RMonad with regard to deciding what functions should go in the Monad class. I think both (>>=) and join should be in the latter. -- Dan [*] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.156.7931

Dan Doel wrote:
However, you can also count me as another person who doesn't care what difficulties exist for RMonad with regard to deciding what functions should go in the Monad class.
I agree, this small and unimportant tail certainly shouldn't wag the dog. Ganesh =============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ===============================================================================

Am 18.01.2011 10:00, schrieb Wolfgang Jeltsch:
If both (>>=) and join are class methods with default implementations that use the respective other method,
The same mutual recursion exists between == and /= in the class Eq and I don't like it, because for an empty instance you do not get a warning but a runtime error (<<loop>>). Cheers Christian

On January 17, 2011 19:24:12 Jan-Willem Maessen wrote:
Join allows you to merge the C1--C2--C3 dynamically determined from A--B--C into the continuation passing string to get
A--B--C--C1--C2--C3--D--E ... (C1--C2--C3 is determined by A--B--C)
This is actually relatively clear from join's type
join :: Monad m => m (m a) -> m a
It takes a string of computations (as indicated by the outer m) that generates a string of computations generating an a (as indicated by the inner m a). It changes this into just a string of computations generating an a.
How can it do this? It must set things up to first run the given string of computations in order to determine the string of computations that give a. Once it gets this, it must then run it in order to get a.
join (CPS f) = CPS $ \k -> unCPS (f id) k
That is, when invoked (i.e., when given a continuation k), invoke f with the continuation id. This will cause f to return the inner computation it computes. Then invoke this returned computation by passing it k.
You guys are both right. It shouldn't be any reflection on join or the description I gave for it though. I simply screwed up by lifting operations out of the continuation without thinking about preserving callCC. Let me restate the last little bit of the above. --- join (CPS f) = CPS $ \k -> f (g -> unCPS g k) That is, when invoked (i.e., when given a continuation k), invoke f with a continuation that takes the computation g generated by f and invokes it next by passing it k. --- My mistake in simplifying this expression was assuming f ends with returning unCPS k0 k1 (letting me lift the unCPS transformation and application of k1 out of the lambda giving id). callCC allows f to not end with unCPS k0 k1. The net effect of lifting these operations out was that it stops f from being able to discard them (i.e., escape past the join). Well subtle, I'm not sure it was too subtle. It is pretty clearly reflected in the types newtype Cont r a = CPS { unCPS :: (a -> r) -> r } join :: Cont (Cont r a) (Cont r a) -> Cont r a join (CPS f) = CPS $ \k -> unCPS (f id) k vs join :: Cont r (Cont r a) -> Cont r a join (CPS f) = CPS $ \k -> f (g -> unCPS g k) Cheers! -Tyson PS: I don't have anything against bind. I just find join is also nice to have for more functional/applicative style programming. It is also conceptually nice as it is quite clear about what additional complexity a monad gives you.

On Tue, Jan 4, 2011 at 10:51 AM, Tyson Whitehead
It seems to me that while join is more of a value transformer as apposed to a flow combining operator, which makes it fit in better with the rest applicative.
Join can't be defined in terms of Applicative combinators alone. Being an Applicative with join is enough to be a Monad.

On 04/01/2011 14:25, Ian Lynagh wrote:
Now which notable things are not included in the patch for base:
* fmap is not renamed to map. * return and (>>) are not removed as a method. * fail is not removed as a method. * All the liftM functions are not removed in favour of fmap and liftAs.
I think these are better left as separate proposals.
OK, but I think it would be good to get any changes into a single release, so people only need to fix their instances once.
Further patches can be proposed for the next release of GHC after this change is accepted.

On Tue, Jan 04, 2011 at 07:59:40PM +0200, John Smith wrote:
On 04/01/2011 14:25, Ian Lynagh wrote:
Now which notable things are not included in the patch for base:
* fmap is not renamed to map. * return and (>>) are not removed as a method. * fail is not removed as a method. * All the liftM functions are not removed in favour of fmap and liftAs.
I think these are better left as separate proposals.
OK, but I think it would be good to get any changes into a single release, so people only need to fix their instances once.
Further patches can be proposed for the next release of GHC after this change is accepted.
Agreed, but if we also agree that all these breaking changes should be made at once, it may be better to not actually apply the patch once the decision is made until we have also made a decision about the others. That way we won't accidentally release with only some of the changes. Thanks Ian

On 03/01/2011 22:30, Bas van Dijk wrote:
On Mon, Jan 3, 2011 at 12:43 PM, Ian Lynagh
wrote: On Sun, Jan 02, 2011 at 06:27:04PM -0800, Iavor Diatchki wrote:
I think that it would be useful if there was a wiki page which describes the proposal exactly, so that we can discuss the details
I agree. I'm confused as to what is part of the proposal, what are other changes necessary due to the classes changing, what are orthogonal cleanups, and what is not being proposed.
The patch for base makes a few changes:
1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
class Functor f where fmap :: (a -> b) -> f a -> f b
(<$) :: a -> f b -> f a (<$) = fmap . const
class Functor f => Applicative f where pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
(*>) :: f a -> f b -> f b a *> b = fmap (const id) a<*> b
(<*) :: f a -> f b -> f a a<* b = fmap const a<*> b
class Applicative m => Monad m where (>>=) :: forall a b. m a -> (a -> m b) -> m b m>>= f = join $ fmap f m
join :: m (m a) -> m a join m = m>>= id
(>>) :: forall a b. m a -> m b -> m b (>>) = (*>)
return :: a -> m a return = pure
fail :: String -> m a fail s = error s
We have a hard time explaining Monads to people already. But now the entire API goes from being one class with 3 methods (only 2 of which you need to care about) to being 3 classes with a total of 11 methods, with a lot of complex interactions. That's a significant increase in cognitive overhead. It might well be the "right" thing in some sense, but is it really worth the pain? What about all those monad tutorials? They now have to include some Functor/Applicative boilerplate, and hope it doesn't put the reader off too much. I like Applicative, I really do, but I want it to be something you only have to buy into if you want to. Someone knocking up a monad for a simple job now has to define 3 instances, not one. So it affects not just people learning the language, but also those already familiar with it and trying to get the job done. Furthermore, we have some significant compatibility issues with Haskell 98/2010 code. I wouldn't be in favour of doing this unless we can retain Haskell 98/2010 compatibility somehow (e.g. with superclass defaults or class aliases). Cheers, Simon

On Wed, Jan 5, 2011 at 11:33 AM, Simon Marlow
Furthermore, we have some significant compatibility issues with Haskell 98/2010 code. I wouldn't be in favour of doing this unless we can retain Haskell 98/2010 compatibility somehow (e.g. with superclass defaults or class aliases).
It would indeed be really nice to have something like this: {-# LANGUAGE DefaultInstances #-} class Functor f where fmap :: (a → b) → f a → f b class Functor f ⇒ Applicative f where pure :: a → f a (<*>) :: f (a → b) → f a → f b instance Functor f where fmap f m = pure f <*> m class Applicative m ⇒ Monad m where return :: a → m a (>>=) :: m a → (a → m b) → m b instance Applicative m where pure = return mf <*> mx = do f ← mf x ← mx return (f x) -- The following is nicer -- but may cause a circular definition: mf <*> mx = do f ← mf fmap f mx Now to make a type (for example Maybe) an instance of Monad the only thing to do is to declare: instance Monad Maybe where return = Just Nothing >>= _ = Nothing Just x >>= f = f x And you will get the Applicative and Functor instances for free. The Eq and Ord classes also benefit from this language extension: class Eq a where (==) :: a → a → Bool class Eq a ⇒ Ord a where compare :: a → a → Ordering instance Eq a where x == y = compare x y == Eq Just like default methods, default instances can be overwritten by a user defined instance. There's the question whether a default instance should be required to be a super class of the class that defines the default instance. For example, should the following be allowed: class Foo a where instance Bar a class Bar a I can't see a use of this yet, but I also can't see a reason why it shouldn't be allowed. Now only someone has to implement it :-) Regards, Bas

Er, hi... On 5 Jan 2011, at 11:24, Bas van Dijk wrote:
On Wed, Jan 5, 2011 at 11:33 AM, Simon Marlow
wrote: Furthermore, we have some significant compatibility issues with Haskell 98/2010 code. I wouldn't be in favour of doing this unless we can retain Haskell 98/2010 compatibility somehow (e.g. with superclass defaults or class aliases).
It would indeed be really nice to have something like this:
{-# LANGUAGE DefaultInstances #-}
class Functor f where fmap :: (a → b) → f a → f b
class Functor f ⇒ Applicative f where pure :: a → f a (<*>) :: f (a → b) → f a → f b
instance Functor f where fmap f m = pure f <*> m
[..]
Now only someone has to implement it :-)
(ahem) cabal install she http://personal.cis.strath.ac.uk/~conor/pub/she/superclass.html [ducks and runs] Conor

On Wed, Jan 5, 2011 at 8:05 AM, Conor McBride
On 5 Jan 2011, at 12:31, Bas van Dijk wrote:
On Wed, Jan 5, 2011 at 1:14 PM, Conor McBride
wrote: cabal install she
I knew about her but not that she supported default superclass instances. Nice!
She didn't. But she does now.
How does she handle multiple subclasses?
E.g., Functor can be defined in terms of Applicative (fmap = liftA)
and in terms of Traversable (fmap = liftT). There are plenty of types
which are both.
--
Dave Menendez

Hi Dave On 5 Jan 2011, at 17:25, David Menendez wrote:
On Wed, Jan 5, 2011 at 8:05 AM, Conor McBride
wrote: On 5 Jan 2011, at 12:31, Bas van Dijk wrote:
On Wed, Jan 5, 2011 at 1:14 PM, Conor McBride
wrote: cabal install she
I knew about her but not that she supported default superclass instances. Nice!
She didn't. But she does now.
How does she handle multiple subclasses?
E.g., Functor can be defined in terms of Applicative (fmap = liftA) and in terms of Traversable (fmap = liftT). There are plenty of types which are both.
She lets you opt out. This is vital to any such default subclass scheme. I can write instance Monad Maybe where return = Just Nothing >>= _ = Nothing Just x >>= f = f x hiding instance Functor Maybe -- notation renegotiable and I'll get the Monad and Applicative instances, but not the Functor. Of course, if I don't otherwise provide a Functor instance, GHC will complain that it's missing. Crucially, however, I'm not forced to take the default. The ability to opt out of the default is crucial for several reasons: (1) You might have a choice of defaults, e.g. indeed, Functor from Applicative or Traversable, and you must choose at most one, even if they are extensionally equal. (2) You might have inherited a Functor from a library whose author did not know or care that it was Applicative (because it was obviously not a Monad, of course). You should not be prevented from declaring an Applicative instance by the prior Functor instance. (3) In the case of monad transformers, I might not want an instance Monad m => Functor (T m), especially if it prevents me from defining an instance Functor f => Functor (T f). (cf Oleg's example.) Please note that it's the cheapness of opting in, not requiring the user to assign the methods to their superclasses which assists with backward compatibility. It's been pointed out to me that one might consider class (A x, A y) => B x y where bthingy = .. instance A x where aring = .. ading = .. instance A y where aring = .. ading = .. with *two* default A instances. If we were to allow this, we should need to be able to switch at least one off in some instance B x x and, otherwise, to write stuff like instance B Int Bool where bthingy = .. instance A Int where aring = .. to be clear which A instance gets the overridden aring. At the moment, she doesn't handle this terribly well: you can have both defaults (unmodified) or neither. It's been helpful thinking about the problem in preprocessor terms, because it helps to figure out where the controls need to be. I hope this is progress, anyway. Cheers Conor

On 05/01/2011 12:33, Simon Marlow wrote:
We have a hard time explaining Monads to people already. But now the entire API goes from being one class with 3 methods (only 2 of which you need to care about) to being 3 classes with a total of 11 methods, with a lot of complex interactions. That's a significant increase in cognitive overhead. It might well be the "right" thing in some sense, but is it really worth the pain? What about all those monad tutorials? They now have to include some Functor/Applicative boilerplate, and hope it doesn't put the reader off too much. I like Applicative, I really do, but I want it to be something you only have to buy into if you want to.
The original Arrow was one class with a few simple methods, and extremely easy to explain. There are now several classes in the Arrow module, and Arrow itself is a subclass of Category. Tutorials simply use the original Arrow definition, which gets the concept across fine. The learner can then proceed to understand the richer, and better factored, current implementation.
Someone knocking up a monad for a simple job now has to define 3 instances, not one. So it affects not just people learning the language, but also those already familiar with it and trying to get the job done.
This creates a little extra work for those who don't want Functor or Applicative (the methods have to be defined anyway, it's just split across the new class hierarchy). Those who do want Functor or Applicative now have them where they belong, without writing boilerplate definitions. Much like anyone declaring an instance of Ord also needs an instance of Eq, even if they're not going to use it.
Furthermore, we have some significant compatibility issues with Haskell 98/2010 code. I wouldn't be in favour of doing this unless we can retain Haskell 98/2010 compatibility somehow (e.g. with superclass defaults or class aliases).
This is part of a larger problem. Is Haskell to be forever frozen as something which can be easily made compatible with Haskell 98? Haskell 98 an earlier made many non-backwards compatible changes, including changes to the Monad class.

Hi On 5 Jan 2011, at 15:22, John Smith wrote:
On 05/01/2011 12:33, Simon Marlow wrote:
We have a hard time explaining Monads to people already. But now the entire API goes from being one class with 3 methods (only 2 of which you need to care about) to being 3 classes with a total of 11 methods, with a lot of complex interactions. That's a significant increase in cognitive overhead. It might well be the "right" thing in some sense, but is it really worth the pain? What about all those monad tutorials? They now have to include some Functor/Applicative boilerplate, and hope it doesn't put the reader off too much. I like Applicative, I really do, but I want it to be something you only have to buy into if you want to.
I think a lot of people take that entirely reasonable position, and it's worth thinking about how to choreograph a good compromise if possible. I believe it is.
The original Arrow was one class with a few simple methods, and extremely easy to explain. There are now several classes in the Arrow module, and Arrow itself is a subclass of Category. Tutorials simply use the original Arrow definition, which gets the concept across fine. The learner can then proceed to understand the richer, and better factored, current implementation.
Arrows (rightly or wrongly) tend to be a pedagogical step beyond Monad, anyway, so one can expect more of Arrow-learners. It's better to avoid unlearning experiences, so it's worth thinking about how to ensure that people can engage with the Monad concept, as available when they fire up ghci, without needing to see its further refinements.
Someone knocking up a monad for a simple job now has to define 3 instances, not one.
It's one interesting instance, plus a copy-paste mantra, but it's still annoying, even if you actually want to use those extra instances.
So it affects not just people learning the language, but also those already familiar with it and trying to get the job done.
This creates a little extra work for those who don't want Functor or Applicative (the methods have to be defined anyway, it's just split across the new class hierarchy). Those who do want Functor or Applicative now have them where they belong, without writing boilerplate definitions.
They must still write boilerplate instances, but not those awful (Functor m, Monad m) contexts.
Much like anyone declaring an instance of Ord also needs an instance of Eq, even if they're not going to use it.
Furthermore, we have some significant compatibility issues with Haskell 98/2010 code. I wouldn't be in favour of doing this unless we can retain Haskell 98/2010 compatibility somehow (e.g. with superclass defaults or class aliases).
This is part of a larger problem. Is Haskell to be forever frozen as something which can be easily made compatible with Haskell 98? Haskell 98 an earlier made many non-backwards compatible changes, including changes to the Monad class.
Change that breaks stuff gets more expensive as uptake grows, so the H98 comparison needs refinement: the cost-benefit analysis is different. I'm in favour of Applicative => Monad in principle, and as soon as is practicable. I just think that if there are helpful measures we can take first to reduce the cost of that change, then we should try to do it the easier way around. The choreography matters. To that end, a little joyride...
{-# OPTIONS_GHC -F -pgmF she #-} {-# LANGUAGE NoImplicitPrelude #-}
module NewMonad where
import Prelude hiding (Functor, Monad, return, (>>=), fmap)
class Functor f where fmap :: (s -> t) -> f s -> f t
class Functor f => Applicative f where return :: x -> f x (<*>) :: f (s -> t) -> f s -> f t instance Functor f where fmap = (<*>) . return
pure :: Applicative f => x -> f x pure = return -- for backward compatibility
class Applicative f => Monad f where (>>=) :: f s -> (s -> f t) -> f t instance Applicative f where ff <*> fs = ff >>= \f -> fs >>= \s -> return (f s)
Now, hark at the dog not barking in the nighttime.
instance Monad [] where return x = [x] [] >>= f = [] (x : xs) >>= f = f x ++ xs >>= f
And away we go!
ex1 :: [Bool] ex1 = fmap (>2) [0..9]
ex2 :: [Int] ex2 = (| [1..6] + [1..6] |) -- she has idiom brackets
ex3 :: [Int] ex3 = do n <- [0..5] [0..n]
Let's go for win-win, or as close as we can get. All the best Conor

On 5 January 2011 15:22, John Smith
There are now several classes in the Arrow module, and Arrow itself is a subclass of Category. Tutorials simply use the original Arrow definition, which gets the concept across fine. The learner can then proceed to understand the richer, and better factored, current implementation.
Now that someone has brought Arrows up... Personally I find the current arrows situation unpleasant and frustrating. I only use arrows infrequently so I haven't built up an intuition about them the way I have with monads. The current code is unlike the best tutorial (John Hughes's AFP lecture notes), and last night when I was looking for tutorial material covering the new classes I couldn't find any, all I had to work with was the code in Base and Ross Paterson's arrow transformer package. There isn't even an explanation in the Control.Arrow Haddock docs elucidating the changes. For me this isn't progress, and if I were a beginner encountering this, I'd seriously be asking myself is this really a language I'd want to be using.

On January 5, 2011 11:06:52 Stephen Tetley wrote:
Now that someone has brought Arrows up...
Personally I find the current arrows situation unpleasant and frustrating. I only use arrows infrequently so I haven't built up an intuition about them the way I have with monads. The current code is unlike the best tutorial (John Hughes's AFP lecture notes), and last night when I was looking for tutorial material covering the new classes I couldn't find any, all I had to work with was the code in Base and Ross Paterson's arrow transformer package. There isn't even an explanation in the Control.Arrow Haddock docs elucidating the changes.
The arrow stuff seems a bit unpleasant/squishy to me as well. I wonder if Patai hit upon the root of the issue when in his blog (which includes a nice hierarchy diagram) he suggested/proposed that "Arrow is strictly the intersection of Applicative and Category". http://just-bottom.blogspot.com/2010/04/programming-with-effects-story-so- far.html I haven't really seen any reason to believe otherwise myself. If true, it greatly clarifies my understanding of exactly what additional power you get (and possibly suggests that hierarchy needs some care too). Cheers! -Tyson

On Wed, Jan 05, 2011 at 12:10:36PM -0500, Tyson Whitehead wrote:
I wonder if Patai hit upon the root of the issue when in his blog (which includes a nice hierarchy diagram) he suggested/proposed that "Arrow is strictly the intersection of Applicative and Category".
http://just-bottom.blogspot.com/2010/04/programming-with-effects-story-so-fa...
I don't think that's quite true. Category(~>) + forall a. Applicative(a~>) gives you the arrow constants, but not the arrow laws, without some additional conditions relating the two, like fmap f (g >>> h) = g >>> fmap f h liftA2 (,) id id = arr (\x -> (x,x)) liftA2 const f id = f arr f >>> g &&& h = (arr f >>> g) &&& (arr f >>> h) first f >>> first g = first (f >>> g)

Bas van Dijk schrieb:
The patch for base makes a few changes:
1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
class Functor f where fmap :: (a -> b) -> f a -> f b
(<$) :: a -> f b -> f a (<$) = fmap . const
class Functor f => Applicative f where pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
(*>) :: f a -> f b -> f b a *> b = fmap (const id) a <*> b
(<*) :: f a -> f b -> f a a <* b = fmap const a <*> b
class Applicative m => Monad m where (>>=) :: forall a b. m a -> (a -> m b) -> m b
Is the explicit 'forall' intended?
m >>= f = join $ fmap f m
join :: m (m a) -> m a join m = m >>= id
(>>) :: forall a b. m a -> m b -> m b (>>) = (*>)
return :: a -> m a return = pure
fail :: String -> m a fail s = error s
2) Make 'join' a method of Monad.
Is there a need for it?
3) Export Applicative(pure, (<*>), (*>), (<*)) from the Prelude. (Maybe we shouldn't export the (*>) and (<*) methods.)
No, please avoid that. Importing Applicative explicitly is completely ok for me. I use (<*>) already for scalar product in NumericPrelude. For me it looks like a commutative operator, which Applicative.<*> is not. The existence of (<*>) in Applicative module is ok for me, but I do not want name clashes with it when automatically imported by Prelude. If at all, Functor stuff should be moved from Control.Applicative and Control.Monad to a new module Control.Functor (and could be re-exported by Control.Applicative and Control.Monad for compatibility reasons). Then fmap could be renamed to 'map' and used as F.map (using "import qualified Control.Functor as F"). All those infix operators for Monad and Functor are not so important for me to be imported automatically from Prelude. Thus I would not like to move Applicative in this direction.
4) Also export the join method from the Prelude.
no please, as above
5) Add Applicative instances for all monads in base.
+1
6) Add a Monad instance for ((,) a): (There are already Functor and Applicative instances for it.)
That is, a Writer instance? I am uncertain about it, because using it may hide a bug. So far I am happy with Writer from transformers package. Using Writer explicitly shows everybody, what I am doing and that I do it intentionally.
The patch for ghc simply adds Applicative instances for all monads in ghc. Also included in the ghc patch bundle are some refactoring patches that will make the transition easier:
* Added (<>) = mappend to compiler/utils/Util.hs. * Add a Monoid instance for AGraph and remove the <*> splice operator. Instead of <*>, the (<>) = mappend operator is now used to splice AGraphs. This change is needed because <*> clashes with the Applicative apply operator <*>, which is probably going to be exported from the Prelude when the new Monad hierarchy is going through. (Simply hiding <*> from the Prelude is also possible of course. However, I think this makes things easier to understand)
For me this is another argument against automatic import of (<*>).
* Make SDoc an abstract newtype and add a Monoid instance for it. The (<>) combinator of SDocs is removed and replaced by the more general (<>) = mappend combinator from Util.
An infix operator for monoids would be nice, indeed. Why not use something that resembles (++), which is the "mappend" for lists? I am uncertain. Maybe something containing '+' looks too commutative. :-) But '<>' looks too much like 'not equal' in other languages.

On Fri, Jan 07, 2011 at 11:59:53AM +0100, Henning Thielemann wrote:
If at all, Functor stuff should be moved from Control.Applicative and Control.Monad to a new module Control.Functor (and could be re-exported by Control.Applicative and Control.Monad for compatibility reasons).
Or perhaps Data.Functor: http://www.haskell.org/ghc/docs/7.0.1/html/libraries/base-4.3.0.0/Data-Funct...

On Fri, Jan 7, 2011 at 11:59 AM, Henning Thielemann
Bas van Dijk schrieb:
class Applicative m => Monad m where (>>=) :: forall a b. m a -> (a -> m b) -> m b
Is the explicit 'forall' intended?
The explicit 'forall' was already there with the following comment: -- Explicit for-alls so that we know what order to -- give type arguments when desugaring
2) Make 'join' a method of Monad.
Is there a need for it?
Like others in this thread have shown, I believe it allows you to write shorter/simpler/elegant Monad instances. However, maybe it's better to move this to its own proposal so we can focus our attention to the proposed hierarchy.
3) Export Applicative(pure, (<*>), (*>), (<*)) from the Prelude. (Maybe we shouldn't export the (*>) and (<*) methods.)
No, please avoid that. Importing Applicative explicitly is completely ok for me.
Currently you can define a Functor and Monad instance without importing anything (because they are both exported by the Prelude). When Applicative becomes a superclass of Monad users _have_ to write an instance for it. I think it would be weird and irritating that you can define the Functor and Monad instances without importing anything but you do have to import Applicative. I would rather either export all the three classes from the Prelude or export none of them.
I use (<*>) already for scalar product in NumericPrelude. For me it looks like a commutative operator, which Applicative.<*> is not. The existence of (<*>) in Applicative module is ok for me, but I do not want name clashes with it when automatically imported by Prelude.
Personally, I'm not the biggest fan of the '<*>' symbol either. I would rather like something which doesn't look commutative and features a '$' somewhere to indicate its "applicative" nature. However, I don't think we should be proposing name changes in this proposal. Is there a possibility you can rename your scalar product combinator to something else? '.*.' maybe?
If at all, Functor stuff should be moved from Control.Applicative and Control.Monad to a new module Control.Functor (and could be re-exported by Control.Applicative and Control.Monad for compatibility reasons). Then fmap could be renamed to 'map' and used as F.map (using "import qualified Control.Functor as F"). All those infix operators for Monad and Functor are not so important for me to be imported automatically from Prelude. Thus I would not like to move Applicative in this direction.
4) Also export the join method from the Prelude.
no please, as above
Fair enough.
5) Add Applicative instances for all monads in base.
+1
6) Add a Monad instance for ((,) a): (There are already Functor and Applicative instances for it.)
That is, a Writer instance?
I am uncertain about it, because using it may hide a bug. So far I am happy with Writer from transformers package. Using Writer explicitly shows everybody, what I am doing and that I do it intentionally.
Yes, I think I need to remove this from the patch. However, I do believe we either need to have both Functor, Applicative and Monad instances or none of them. It feels weird to only have Functor and Applicative instances.
The patch for ghc simply adds Applicative instances for all monads in ghc. Also included in the ghc patch bundle are some refactoring patches that will make the transition easier:
* Added (<>) = mappend to compiler/utils/Util.hs. * Add a Monoid instance for AGraph and remove the <*> splice operator. Instead of <*>, the (<>) = mappend operator is now used to splice AGraphs. This change is needed because <*> clashes with the Applicative apply operator <*>, which is probably going to be exported from the Prelude when the new Monad hierarchy is going through. (Simply hiding <*> from the Prelude is also possible of course. However, I think this makes things easier to understand)
For me this is another argument against automatic import of (<*>).
* Make SDoc an abstract newtype and add a Monoid instance for it. The (<>) combinator of SDocs is removed and replaced by the more general (<>) = mappend combinator from Util.
An infix operator for monoids would be nice, indeed. Why not use something that resembles (++), which is the "mappend" for lists? I am uncertain. Maybe something containing '+' looks too commutative. :-) But '<>' looks too much like 'not equal' in other languages.
I choose '<>' because it was already the append for SDocs. I too like something featuring '++'. Or maybe '++' itself. Regards, Bas

On Sat, 8 Jan 2011, Bas van Dijk wrote:
I use (<*>) already for scalar product in NumericPrelude. For me it looks like a commutative operator, which Applicative.<*> is not. The existence of (<*>) in Applicative module is ok for me, but I do not want name clashes with it when automatically imported by Prelude.
Personally, I'm not the biggest fan of the '<*>' symbol either. I would rather like something which doesn't look commutative and features a '$' somewhere to indicate its "applicative" nature. However, I don't think we should be proposing name changes in this proposal.
FWIW, I personally use <@> for ap in my non-Haskell work, or some other variation like @@. Though I do agree that we shoudn't be proposing name changes in this proposal. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On Sunday 02 January 2011 13:04:30 you wrote:
The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834 make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility.
I looked at the Prelude of the referenced documentation in the ticket: http://bifunctor.homelinux.net/~bas/doc/ghc/html/libraries/base-4.4.0.0/Prel... Would it be useful to include liftM and ap in the Prelude, so that you can use it as a default implementation for fmap, when defining Functor instances? Then you can write... instance Functor Something where fmap = liftM instance Applicative Something where pure x = ... (<*>) = ap instance Monad Something where (>>=) = ... This way you don't need to write explicit implementations of fmap and <*> for every monad you define. An alternative name for liftM would be fmapMonad... There is a similar approach in Data.Traversable: fmapDefault :: Traversable t => (a -> b) -> t a -> t b However as Functor, Applicative and Monad are part of the Prelude, it might be useful, to include a default implementation for fmap in the Prelude. Regards Jan

On Friday 28 January 2011 15:13:44 Jan Behrens wrote:
On Sunday 02 January 2011 13:04:30 you wrote:
The patches attached to http://hackage.haskell.org/trac/ghc/ticket/4834 make Applicative a superclass of Monad. Default definitions are provided for backwards compatibility.
I looked at the Prelude of the referenced documentation in the ticket: http://bifunctor.homelinux.net/~bas/doc/ghc/html/libraries/base-4.4.0.0/Pre lude.html
Would it be useful to include liftM and ap in the Prelude, so that you can use it as a default implementation for fmap, when defining Functor instances?
I have to correct myself. It should be "liftA" and "ap", as liftA is more abstract than liftM and can thus be used as a default fmap implementation for BOTH monads and applicative functors.
Then you can write...
instance Functor Something where fmap = liftM
instance Applicative Something where pure x = ... (<*>) = ap
instance Monad Something where (>>=) = ...
This way you don't need to write explicit implementations of fmap and <*> for every monad you define.
The example would read then as follows: instance Functor Something where fmap = liftA instance Applicative Something where pure x = ... (<*>) = ap instance Monad Something where (>>=) = ...
An alternative name for liftM would be fmapMonad...
There is a similar approach in Data.Traversable:
fmapDefault :: Traversable t => (a -> b) -> t a -> t b
However as Functor, Applicative and Monad are part of the Prelude, it might be useful, to include a default implementation for fmap in the Prelude.
Regards Jan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (29)
-
Alexander Dunlap
-
Antoine Latter
-
Bas van Dijk
-
Christian Maeder
-
Conal Elliott
-
Conor McBride
-
Dan Doel
-
David Menendez
-
Edward Kmett
-
Gábor Lehel
-
Henning Thielemann
-
Ian Lynagh
-
Iavor Diatchki
-
Isaac Dupree
-
Jan Behrens
-
Jan-Willem Maessen
-
Johan Tibell
-
John Smith
-
kahl@cas.mcmaster.ca
-
Maciej Piechotka
-
roconnor@theorem.ca
-
Ross Paterson
-
Sebastian Fischer
-
Simon Marlow
-
Sittampalam, Ganesh
-
Stephen Tetley
-
Tyson Whitehead
-
Wolfgang Jeltsch
-
wren ng thornton