Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread Bas van Dijk
On 16 December 2011 16:26, Yves Parès limestr...@gmail.com wrote:
 1) What about the First type? Do we {-# DEPRECATE #-} it?

 Personnaly, I'm in favor of following the same logic than Int:
 Int itself is not a monoid. You have to be specific: it's either Sum or
 Mult.

 It should be the same for Maybe: we remove its instance of Monoid, and we
 only use First and Last.

The reason you need to be specific with Int is that it's not clear
which semantics (sum or product) you want. The semantics of Maybe are
clear: it's failure-and-prioritized-choice.

Changing the order of the arguments of mappend should be the job of Dual.

If we really want to drop the Monoid instance for Maybe and keep First
and Last and also want to be consistent we should also drop the Monoid
instances of [a], a-b, Endo a and of all the tuples. And instead
define Monoid instance for First [a], Last [a], First (a-b), Last
(a-b), etc. I don't think this is what we want.

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread Erik Hesselink
On Wed, Dec 21, 2011 at 14:10, Bas van Dijk v.dijk@gmail.com wrote:
 On 16 December 2011 16:26, Yves Parès limestr...@gmail.com wrote:
 1) What about the First type? Do we {-# DEPRECATE #-} it?

 Personnaly, I'm in favor of following the same logic than Int:
 Int itself is not a monoid. You have to be specific: it's either Sum or
 Mult.

 It should be the same for Maybe: we remove its instance of Monoid, and we
 only use First and Last.

 The reason you need to be specific with Int is that it's not clear
 which semantics (sum or product) you want. The semantics of Maybe are
 clear: it's failure-and-prioritized-choice.

Are you sure? There are (at least) four Monoid instances for Maybe
[1]. With a direct instance for Maybe and its Dual you have only
covered two.

Erik

[1] https://byorgey.wordpress.com/2011/04/18/monoids-for-maybe/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread Conor McBride





On 21 Dec 2011, at 14:07, Erik Hesselink hessel...@gmail.com wrote:

On Wed, Dec 21, 2011 at 14:10, Bas van Dijk v.dijk@gmail.com  
wrote:



 The semantics of Maybe are


clear: it's failure-and-prioritized-choice.


Are you sure?


Yes.


There are (at least) four Monoid instances for Maybe
[1]. With a direct instance for Maybe and its Dual you have only
covered two.


Types don't just give data a representation: types evoke structure.  
The data stored by Maybe can be made into a monoid in several ways,  
but the failure-management role of Maybe makes just one of them  
appropriate.


Cheers

Conor




Erik

[1] https://byorgey.wordpress.com/2011/04/18/monoids-for-maybe/

___
Libraries mailing list
librar...@haskell.org
http://www.haskell.org/mailman/listinfo/libraries


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread David Menendez
On Wed, Dec 21, 2011 at 12:20 PM, Conor McBride
co...@strictlypositive.org wrote:

 On 21 Dec 2011, at 14:07, Erik Hesselink hessel...@gmail.com wrote:

 On Wed, Dec 21, 2011 at 14:10, Bas van Dijk v.dijk@gmail.com wrote:


  The semantics of Maybe are


 clear: it's failure-and-prioritized-choice.


 Are you sure?


 Yes.


 There are (at least) four Monoid instances for Maybe
 [1]. With a direct instance for Maybe and its Dual you have only
 covered two.


 Types don't just give data a representation: types evoke structure. The data
 stored by Maybe can be made into a monoid in several ways, but the
 failure-management role of Maybe makes just one of them appropriate.

This is my view as well.

While it's true that the current Monoid instance for Maybe is the only
one that isn't captured by an obvious adaptor, I think we'd be better
off with a dedicated type for that sort of semigroup-to-monoid
transformation.


Those obvious adaptors, by the way:

newtype MPlus m a = MPlus (m a)

instance MonadPlus m = Monoid (MPlus m a) where
mempty = MPlus mzero
mappend (MPlus x) (MPlus y) = MPlus (mplus x y)

newtype LiftA2 m a = LiftA2 (m a)

instance (Applicative m, Monoid a) = Monoid (LiftA2 m a) where
mempty = LiftA2 (pure mempty)
mappend (LiftA2 x) (LiftA2 y) = LiftA2 (liftA2 mappend x y)

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread Matthew Farkas-Dyck
On 21/12/2011, Bas van Dijk v.dijk@gmail.com wrote:
 On 16 December 2011 16:26, Yves Parès limestr...@gmail.com wrote:
 1) What about the First type? Do we {-# DEPRECATE #-} it?

 Personnaly, I'm in favor of following the same logic than Int:
 Int itself is not a monoid. You have to be specific: it's either Sum or
 Mult.

 It should be the same for Maybe: we remove its instance of Monoid, and we
 only use First and Last.

 The reason you need to be specific with Int is that it's not clear
 which semantics (sum or product) you want. The semantics of Maybe are
 clear: it's failure-and-prioritized-choice.

 Changing the order of the arguments of mappend should be the job of Dual.

 If we really want to drop the Monoid instance for Maybe and keep First
 and Last and also want to be consistent we should also drop the Monoid
 instances of [a], a-b, Endo a and of all the tuples. And instead
 define Monoid instance for First [a], Last [a], First (a-b), Last
 (a-b), etc. I don't think this is what we want.

 Regards,

 Bas

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


Fair point. I concede.

If Monoid were necessarily inner-type-gnostic then we'd also have to
drop instance Monoid [a].

Cheers,
Matthew Farkas-Dyck

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread David Menendez
On Wed, Dec 21, 2011 at 8:10 AM, Bas van Dijk v.dijk@gmail.com wrote:
 On 16 December 2011 16:26, Yves Parès limestr...@gmail.com wrote:
 1) What about the First type? Do we {-# DEPRECATE #-} it?

 Personnaly, I'm in favor of following the same logic than Int:
 Int itself is not a monoid. You have to be specific: it's either Sum or
 Mult.

 It should be the same for Maybe: we remove its instance of Monoid, and we
 only use First and Last.

 The reason you need to be specific with Int is that it's not clear
 which semantics (sum or product) you want. The semantics of Maybe are
 clear: it's failure-and-prioritized-choice.

 Changing the order of the arguments of mappend should be the job of Dual.

 If we really want to drop the Monoid instance for Maybe and keep First
 and Last and also want to be consistent we should also drop the Monoid
 instances of [a], a-b, Endo a and of all the tuples.

Interestingly, every one of these examples can been seen as an adaptor
from another class.

For [a], the monoid is (mzero,mplus).
For a - b and the tuples, the monoid is (pure mempty, liftA2 mappend).
For Endo, the monoid is (id, (.))  (from Category)

The current monoid instances for [a], a - a, and the tuples feel like
natural choices (in contrast to Maybe), but knowing which operations
are used requires some understanding of the design history of the
library. That's why I recommend only using mempty and mappend with
polymorphic code.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-17 Thread Matthew Farkas-Dyck
On 17/12/2011, Gregory Crosswhite gcrosswh...@gmail.com wrote:

 On Dec 17, 2011, at 12:51 PM, Matthew Farkas-Dyck wrote:

 By my reason, the instance (Monoid a = Monoid (Maybe a)) is
 appropriate, since we have another class for inner-type-agnostic
 choice -- Alternative! (and MonadPlus, but that's essentially the
 same, and would be if (Functor m = Applicative m = Monad m), as it
 ought).

 Yes, but the problem here is that having different behavior for Alternative,
 MonadPlus, and Monoid instances is inherently confusing, in the sense that
 this would almost certainly surprise someone who wasn't already aware of the
 difference between the instances.

On 17/12/2011, Conor McBride co...@strictlypositive.org wrote:
 So your argument is to create incoherence because we can. I'm not
 convinced.

No, my argument is that Monoid and Alternative ought to have nonsame
semantics, since one is a class of types of kind (*), and the other,
(* - *). Thus, Monoid operations ought to mean the whole type, and
Alternative operations, just the outer type.

It shouldn't be a surprise -- it's impossible to put a constraint on
the inner type for an Alternative instance, since there is none (^_~)

  (Functor m = Applicative m = Monad m), as it ought.
 and as it already is in Strathclyde...

By default superclass instances, you mean? If so (and I understand
correctly), that's not quite the same; If I write, for (Applicative
FooBar - FooBar)
instance Monad FooBar where x = f = ...
then return would be undefined, despite pure (which ought to be in its
own class, anyhow (ō_ō)).

Cheers,
Matthew Farkas-Dyck

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Bas van Dijk
On 16 December 2011 05:26, Brent Yorgey byor...@seas.upenn.edu wrote:
 I, for one, would be
 quite in favor of changing the current Monoid (Maybe a) instance to
 correspond to the failure-and-prioritized-choice semantics

So lets do this. Some questions:

1) What about the First type? Do we {-# DEPRECATE #-} it?

2) What about the Last type? It could be deprecated in favor of Dual.

3) Do we need a new type (like the current Maybe) for lifting
semigroups into a Monoid? IMHO we don't since the semigroup package
does a better job with the Option type (like Brent mentioned).

4) How much code will break from this change?

5) Anyone up for proposing this to librar...@haskell.org?

Regards,

Bas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Bas van Dijk
Attached is a git patch for base which makes the proposed changes.
From 824bdca994b3fcceff21fcb68e1b18f1d4f03bd5 Mon Sep 17 00:00:00 2001
From: Bas van Dijk v.dijk@gmail.com
Date: Fri, 16 Dec 2011 15:16:14 +0100
Subject: [PATCH] Give the Maybe Monoid the expected
 failure-and-prioritized-choice semantics instead of the
 lift-a-semigroup-to-a-monoid semantics. The old semantics
 didn't even achieve the latter since it required a Monoid
 instance on a, rather than a semigroup Also DEPRECATE First
 in favor of Maybe and Last in favor of Dual.

---
 Data/Monoid.hs |   46 --
 1 files changed, 20 insertions(+), 26 deletions(-)

diff --git a/Data/Monoid.hs b/Data/Monoid.hs
index 228e254..d1d9564 100644
--- a/Data/Monoid.hs
+++ b/Data/Monoid.hs
@@ -186,14 +186,14 @@ instance Num a = Monoid (Product a) where
 --
 -- @
 -- findLast :: Foldable t = (a - Bool) - t a - Maybe a
--- findLast pred = getLast . foldMap (\x - if pred x
---then Last (Just x)
---else Last Nothing)
+-- findLast pred = getDual . foldMap (\x - if pred x
+--then Dual (Just x)
+--else Dual Nothing)
 -- @
 --
 -- Much of Data.Map's interface can be implemented with
 -- Data.Map.alter. Some of the rest can be implemented with a new
--- @alterA@ function and either 'First' or 'Last':
+-- @alterA@ function and either 'Maybe' or 'Dual Maybe':
 --
 --  alterA :: (Applicative f, Ord k) =
 --(Maybe a - f (Maybe a)) - k - Map k a - f (Map k a)
@@ -204,28 +204,21 @@ instance Num a = Monoid (Product a) where
 -- insertLookupWithKey :: Ord k = (k - v - v - v) - k - v
 -- - Map k v - (Maybe v, Map k v)
 -- insertLookupWithKey combine key value =
---   Arrow.first getFirst . alterA doChange key
+--   alterA doChange key
 --   where
---   doChange Nothing = (First Nothing, Just value)
---   doChange (Just oldValue) =
--- (First (Just oldValue),
---  Just (combine key value oldValue))
+--   doChange m@Nothing = (m, Just value)
+--   doChange m@(Just oldValue) = (m, Just (combine key value oldValue))
 -- @
 
--- | Lift a semigroup into 'Maybe' forming a 'Monoid' according to
--- http://en.wikipedia.org/wiki/Monoid: \Any semigroup @S@ may be
--- turned into a monoid simply by adjoining an element @e@ not in @S@
--- and defining @e*e = e@ and @e*s = s = s*e@ for all @s ∈ S@.\ Since
--- there is no \Semigroup\ typeclass providing just 'mappend', we
--- use 'Monoid' instead.
-instance Monoid a = Monoid (Maybe a) where
+instance Monoid (Maybe a) where
   mempty = Nothing
-  Nothing `mappend` m = m
-  m `mappend` Nothing = m
-  Just m1 `mappend` Just m2 = Just (m1 `mappend` m2)
-
+  Nothing `mappend` r = r
+  l   `mappend` _ = l
 
 -- | Maybe monoid returning the leftmost non-Nothing value.
+--
+-- /DEPRECATED in favor of 'Maybe'!/
+{-# DEPRECATED First Use Maybe instead #-}
 newtype First a = First { getFirst :: Maybe a }
 #ifndef __HADDOCK__
 deriving (Eq, Ord, Read, Show)
@@ -237,11 +230,13 @@ instance Show a = Show (First a)
 #endif
 
 instance Monoid (First a) where
-mempty = First Nothing
-r@(First (Just _)) `mappend` _ = r
-First Nothing `mappend` r = r
+mempty = First mempty
+First l `mappend` First r = First (l `mappend` r)
 
 -- | Maybe monoid returning the rightmost non-Nothing value.
+--
+-- /DEPRECATED in favor of 'Dual'!/
+{-# DEPRECATED Last Use Dual instead #-}
 newtype Last a = Last { getLast :: Maybe a }
 #ifndef __HADDOCK__
 deriving (Eq, Ord, Read, Show)
@@ -253,9 +248,8 @@ instance Show a = Show (Last a)
 #endif
 
 instance Monoid (Last a) where
-mempty = Last Nothing
-_ `mappend` r@(Last (Just _)) = r
-r `mappend` Last Nothing = r
+mempty = Last mempty
+Last x `mappend` Last y = Last (y `mappend` x)
 
 {-
 {
-- 
1.7.5.4

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Yves Parès
 1) What about the First type? Do we {-# DEPRECATE #-} it?

Personnaly, I'm in favor of following the same logic than Int:
Int itself is *not *a monoid. You have to be specific: it's either Sum or
Mult.

It should be the same for Maybe: we remove its instance of Monoid, and we
only use First and Last.

2011/12/16 Bas van Dijk v.dijk@gmail.com

 On 16 December 2011 05:26, Brent Yorgey byor...@seas.upenn.edu wrote:
  I, for one, would be
  quite in favor of changing the current Monoid (Maybe a) instance to
  correspond to the failure-and-prioritized-choice semantics

 So lets do this. Some questions:

 1) What about the First type? Do we {-# DEPRECATE #-} it?

 2) What about the Last type? It could be deprecated in favor of Dual.

 3) Do we need a new type (like the current Maybe) for lifting
 semigroups into a Monoid? IMHO we don't since the semigroup package
 does a better job with the Option type (like Brent mentioned).

 4) How much code will break from this change?

 5) Anyone up for proposing this to librar...@haskell.org?

 Regards,

 Bas

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Yves Parès
Sorry, I meant Sum and Product for the monoid equivalents of a Num instance.

2011/12/16 Yves Parès limestr...@gmail.com

 1) What about the First type? Do we {-# DEPRECATE #-} it?

 Personnaly, I'm in favor of following the same logic than Int:
 Int itself is *not *a monoid. You have to be specific: it's either Sum or
 Mult.

 It should be the same for Maybe: we remove its instance of Monoid, and we
 only use First and Last.


 2011/12/16 Bas van Dijk v.dijk@gmail.com

 On 16 December 2011 05:26, Brent Yorgey byor...@seas.upenn.edu wrote:
  I, for one, would be
  quite in favor of changing the current Monoid (Maybe a) instance to
  correspond to the failure-and-prioritized-choice semantics

 So lets do this. Some questions:

 1) What about the First type? Do we {-# DEPRECATE #-} it?

 2) What about the Last type? It could be deprecated in favor of Dual.

 3) Do we need a new type (like the current Maybe) for lifting
 semigroups into a Monoid? IMHO we don't since the semigroup package
 does a better job with the Option type (like Brent mentioned).

 4) How much code will break from this change?

 5) Anyone up for proposing this to librar...@haskell.org?

 Regards,

 Bas

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Matthew Farkas-Dyck
On 15/12/2011, Conor McBride co...@strictlypositive.org wrote:

 On 15 Dec 2011, at 15:19, Brent Yorgey wrote:

 On Thu, Dec 15, 2011 at 06:49:13PM +1000, Gregory Crosswhite wrote:

 So at the end of the day... what is the point of even making Maybe
 and [] instances of Alternative?

 The Alternative and Monoid instances for [] are equivalent.  However,
 the Alternative and Monoid instances for Maybe are not. To wit:

 (Just (Sum  4)) | (Just (Sum 3))
  Just (Sum {getSum = 4})

 (Just (Sum 4)) `mappend` (Just (Sum 3))
  Just (Sum {getSum = 7})

 The current monoid instance for Maybe is, in my view, unfortunate.

 Types are about semantic purpose, not just data representation.
 Many purposes can be represented in the same way. We should identify
 the purpose of a type (or type constructor), then define instances
 consistent with that purpose. And better, we acquire by instance
 inference compound instances consistent with that purpose! (A similar
 view is often articulated well by Conal Elliott. But perhaps it's
 just a Con thing.)

 The purpose of Maybe, it seems to me, is to model failure and
 prioritized choice, after the manner of exceptions. It's clear
 what the failure-and-prioritized-choice monoid is.

 It so happens that the same data representation can be used to make
 a semigroup into a monoid by attaching an identity element. That's
 a different semantic purpose, which deserves a different type.

 This really bites. I really like being able to write things like

newtype P a x = P ([a] - Maybe (x, [a])) deriving Monoid

 and then make MonadPlus/Alternative instances just by copying the
 monoid that results, but it doesn't work!

 It's unfortunate that we don't have local quantification in
 constraints, so we can't write (forall x. Monoid (f x)), hence the
 need for constructor classes doing basically the same job, with,
 of necessity, newly renamed members. I think it compounds the
 problem to choose inconsistent behaviour between the constructor
 class and the underlying type class.

 Maybe I'm an extremist, but I'd prefer it if every Alternative
 instance was constructed by duplicating a polymorphic Monoid
 instance.

 Meanwhile, as for the issue which kicked this off, I do think it's
 good to document and enforce meaningful (i.e. total on total input)
 usages of operations by types where practical. At present, refining
 one type class into several to account for subtle issues (like
 whether some/many actually work) is expensive, even if it's
 desirable. I'd once again plug default superclass instances and
 Control.Newtype, then suggest that the library might benefit from a
 little pruning.

 All the best

 Conor

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


By my reason, the instance (Monoid a = Monoid (Maybe a)) is
appropriate, since we have another class for inner-type-agnostic
choice -- Alternative! (and MonadPlus, but that's essentially the
same, and would be if (Functor m = Applicative m = Monad m), as it
ought).

Cheers,
Matthew Farkas-Dyck

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Gregory Crosswhite

On Dec 17, 2011, at 1:26 AM, Yves Parès wrote:

 1) What about the First type? Do we {-# DEPRECATE #-} it?
 
 Personnaly, I'm in favor of following the same logic than Int:
 Int itself is not a monoid. You have to be specific: it's either Sum or Mult.
 
 It should be the same for Maybe: we remove its instance of Monoid, and we 
 only use First and Last.

+1 for this idea, because it follows the principle of least surprise.

Cheers,
Greg___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Gregory Crosswhite

On Dec 17, 2011, at 1:26 AM, Yves Parès wrote:

 1) What about the First type? Do we {-# DEPRECATE #-} it?
 
 Personnaly, I'm in favor of following the same logic than Int:
 Int itself is not a monoid. You have to be specific: it's either Sum or Mult.
 
 It should be the same for Maybe: we remove its instance of Monoid, and we 
 only use First and Last.


+1 for this idea, because it follows the principle of least surprise.

Cheers,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Gregory Crosswhite

On Dec 17, 2011, at 12:51 PM, Matthew Farkas-Dyck wrote:

 By my reason, the instance (Monoid a = Monoid (Maybe a)) is
 appropriate, since we have another class for inner-type-agnostic
 choice -- Alternative! (and MonadPlus, but that's essentially the
 same, and would be if (Functor m = Applicative m = Monad m), as it
 ought).

Yes, but the problem here is that having different behavior for Alternative, 
MonadPlus, and Monoid instances is inherently confusing, in the sense that this 
would almost certainly surprise someone who wasn't already aware of the 
difference between the instances.

Regardless, even if we keep the current behavior, we *really* *really* need to 
improve the documentation for the Monoid instance of Maybe.  Currently it reads:

 Lift a semigroup into Maybe forming a Monoid according to 
http://en.wikipedia.org/wiki/Monoid: Any semigroup S may be turned into a 
monoid simply by adjoining an element e not in S and defining e*e = eand e*s = 
s = s*e for all s  S. Since there is no Semigroup typeclass providing just 
mappend, we use Monoid instead.

Now, I just happened to have recently spent time studying the properties of 
Semigroups and Monoids, so this explanation made perfect sense to me and was a 
beautiful way of explaining what is going on.  A typical user, however --- 
which would have included me roughly one month ago :-) --- would have looked at 
this and just seen goobledegook which reinforced their perception that Haskell 
is first and foremost a playground for mathematicians.  It would be much, much 
better for the documentation to be something like this:



The Monoid instance for Maybe has the property that, for all x and y, (Just x) 
wins when combined (on either side) with Nothing values, and when (Just x) is 
combined with (Just y) then the result is (Just (x `mappend` y)).

For the more mathematically inclined, you may think of this as being equivalent 
to the standard practice of turning an arbitrary semigroup into a monoid by 
simply adding a new element to the semigroup to serve as the identity element, 
where in this case the identity element is the Nothing value of Maybe;  
unfortunately, since the base libraries do not come with a Semigroup typeclass, 
this process is expressed in code as lifting from the Monoid typeclass.

NOTE THAT the behavior of the Monoid instance of Maybe is DIFFERENT from the 
behavior of the MonadPlus and Alternative instance of Maybe.  For the latter 
two typeclasses, the behavior is that when (Just x) is combined with (Just y) 
the x and y values themselves are not combined but rather y is discarded so 
(Just x) simply wins;  put another way, for all x and z, we have that (Just x) 
`mappend` z is *always* equal to (Just x), regardless of whether z is equal to 
Nothing or whether it is equal to (Just y) for some y.  For this reason, unlike 
the instance for Monoid, the instances for these MonadPlus and Alternative 
place no additional constraints on the type lifted into Maybe.



Incidentally, would people be interested in me sending a patch to update the 
documentation to be more along these lines?  (After applying your feedback, of 
course!)  If so, could you point me to where I could learn about the process 
for doing so?

Cheers,
Greg___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-16 Thread Gregory Crosswhite

On Dec 17, 2011, at 2:57 PM, Gregory Crosswhite wrote:

 +1 for this idea, because it follows the principle of least surprise.

Sorry about the double-post!  I was foolish enough not only to use 
unsafePerformIO to send my e-mail, but to forgot to mark the sending routine 
with NOINLINE pragma.  As a result, the sending action was sparked and run 
twice by the runtime environment.

Cheers,
Greg___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-15 Thread Brent Yorgey
On Thu, Dec 15, 2011 at 06:49:13PM +1000, Gregory Crosswhite wrote:
 
 So at the end of the day... what is the point of even making Maybe and [] 
 instances of Alternative?

The Alternative and Monoid instances for [] are equivalent.  However,
the Alternative and Monoid instances for Maybe are not. To wit:

   (Just (Sum  4)) | (Just (Sum 3))
  Just (Sum {getSum = 4})

   (Just (Sum 4)) `mappend` (Just (Sum 3))
  Just (Sum {getSum = 7})

-Brent

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-15 Thread Anthony Cowley
On Dec 15, 2011, at 10:19 AM, Brent Yorgey wrote:

 On Thu, Dec 15, 2011 at 06:49:13PM +1000, Gregory Crosswhite wrote:
 
 So at the end of the day... what is the point of even making Maybe and [] 
 instances of Alternative?
 
 The Alternative and Monoid instances for [] are equivalent.  However,
 the Alternative and Monoid instances for Maybe are not. To wit:
 
 (Just (Sum  4)) | (Just (Sum 3))
  Just (Sum {getSum = 4})
 
 (Just (Sum 4)) `mappend` (Just (Sum 3))
  Just (Sum {getSum = 7})

We already have,

 First (Just (Sum 4)) `mappend` First (Just (Sum 3))
First {getFirst = Just (Sum {getSum = 4})}

So the overlap of apparent Alternative and Monoid functionality remains. This 
just represents an opportunity for the caller to select the monoid they want.

Anthony
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-15 Thread Yves Parès
So why don't we use First and Last with the Alternative interface too?

It's indeed weird the Maybe doesn't react the same way with Alternative and
Monoid.

2011/12/15 Anthony Cowley acow...@gmail.com

 On Dec 15, 2011, at 10:19 AM, Brent Yorgey wrote:

  On Thu, Dec 15, 2011 at 06:49:13PM +1000, Gregory Crosswhite wrote:
 
  So at the end of the day... what is the point of even making Maybe and
 [] instances of Alternative?
 
  The Alternative and Monoid instances for [] are equivalent.  However,
  the Alternative and Monoid instances for Maybe are not. To wit:
 
  (Just (Sum  4)) | (Just (Sum 3))
   Just (Sum {getSum = 4})
 
  (Just (Sum 4)) `mappend` (Just (Sum 3))
   Just (Sum {getSum = 7})

 We already have,

  First (Just (Sum 4)) `mappend` First (Just (Sum 3))
 First {getFirst = Just (Sum {getSum = 4})}

 So the overlap of apparent Alternative and Monoid functionality remains.
 This just represents an opportunity for the caller to select the monoid
 they want.

 Anthony
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-15 Thread Carl Howells
Monoid and Alternative are not the same.  There is a very important
difference between them:

class Alternative f where
(|) :: f a - f a - f a
...

class Monoid a where
mappend :: a - a - a
...

The equivalent to Alternative is MonadPlus, not Monoid.  The kinds
matter.  In Alternative, you are guaranteed that the type that f is
applied to cannot affect the semantics of (|).  As has been already
demonstrated aptly, the type a in the instance Monoid a = Monoid
(Maybe a) matters quite a lot.

Carl

On Thu, Dec 15, 2011 at 8:04 AM, Yves Parès limestr...@gmail.com wrote:
 So why don't we use First and Last with the Alternative interface too?

 It's indeed weird the Maybe doesn't react the same way with Alternative and
 Monoid.


 2011/12/15 Anthony Cowley acow...@gmail.com

 On Dec 15, 2011, at 10:19 AM, Brent Yorgey wrote:

  On Thu, Dec 15, 2011 at 06:49:13PM +1000, Gregory Crosswhite wrote:
 
  So at the end of the day... what is the point of even making Maybe and
  [] instances of Alternative?
 
  The Alternative and Monoid instances for [] are equivalent.  However,
  the Alternative and Monoid instances for Maybe are not. To wit:
 
  (Just (Sum  4)) | (Just (Sum 3))
   Just (Sum {getSum = 4})
 
  (Just (Sum 4)) `mappend` (Just (Sum 3))
   Just (Sum {getSum = 7})

 We already have,

  First (Just (Sum 4)) `mappend` First (Just (Sum 3))
 First {getFirst = Just (Sum {getSum = 4})}

 So the overlap of apparent Alternative and Monoid functionality remains.
 This just represents an opportunity for the caller to select the monoid they
 want.

 Anthony
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-15 Thread Conor McBride


On 15 Dec 2011, at 15:19, Brent Yorgey wrote:


On Thu, Dec 15, 2011 at 06:49:13PM +1000, Gregory Crosswhite wrote:


So at the end of the day... what is the point of even making Maybe  
and [] instances of Alternative?


The Alternative and Monoid instances for [] are equivalent.  However,
the Alternative and Monoid instances for Maybe are not. To wit:


(Just (Sum  4)) | (Just (Sum 3))

 Just (Sum {getSum = 4})


(Just (Sum 4)) `mappend` (Just (Sum 3))

 Just (Sum {getSum = 7})


The current monoid instance for Maybe is, in my view, unfortunate.

Types are about semantic purpose, not just data representation.
Many purposes can be represented in the same way. We should identify
the purpose of a type (or type constructor), then define instances
consistent with that purpose. And better, we acquire by instance
inference compound instances consistent with that purpose! (A similar
view is often articulated well by Conal Elliott. But perhaps it's
just a Con thing.)

The purpose of Maybe, it seems to me, is to model failure and
prioritized choice, after the manner of exceptions. It's clear
what the failure-and-prioritized-choice monoid is.

It so happens that the same data representation can be used to make
a semigroup into a monoid by attaching an identity element. That's
a different semantic purpose, which deserves a different type.

This really bites. I really like being able to write things like

  newtype P a x = P ([a] - Maybe (x, [a])) deriving Monoid

and then make MonadPlus/Alternative instances just by copying the
monoid that results, but it doesn't work!

It's unfortunate that we don't have local quantification in
constraints, so we can't write (forall x. Monoid (f x)), hence the
need for constructor classes doing basically the same job, with,
of necessity, newly renamed members. I think it compounds the
problem to choose inconsistent behaviour between the constructor
class and the underlying type class.

Maybe I'm an extremist, but I'd prefer it if every Alternative
instance was constructed by duplicating a polymorphic Monoid
instance.

Meanwhile, as for the issue which kicked this off, I do think it's
good to document and enforce meaningful (i.e. total on total input)
usages of operations by types where practical. At present, refining
one type class into several to account for subtle issues (like
whether some/many actually work) is expensive, even if it's
desirable. I'd once again plug default superclass instances and
Control.Newtype, then suggest that the library might benefit from a
little pruning.

All the best

Conor

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-15 Thread Gregory Crosswhite

On Dec 16, 2011, at 3:59 AM, Carl Howells wrote:

 Monoid and Alternative are not the same.  There is a very important
 difference between them:
 
 class Alternative f where
(|) :: f a - f a - f a
...
 
 class Monoid a where
mappend :: a - a - a
...
 
 The equivalent to Alternative is MonadPlus, not Monoid.  The kinds
 matter.  In Alternative, you are guaranteed that the type that f is
 applied to cannot affect the semantics of (|).

I understand that one needs to worry about kinds in general, but in this 
particular case such a subtlety is non-issue because you would always be 
defining Monad for a particular type.  That is to say, given an alternative f, 
the instance of Monoid would be

instance Monoid (f a) where { ... }

where in the above a is an arbitrary type variable.

To give you a more concrete example, the following code compiles and runs, 
producing the output [1,2,3,4,5,6]



import Data.Monoid

newtype L a = L [a] deriving (Show,Eq)

instance Monoid (L a) where
   mempty = L []
   mappend (L x) (L y) = L (x ++ y)

main = putStrLn . show $ (L [1,2,3]) `mappend` (L [4,5,6])



Cheers,
Greg___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Alternative versus Monoid

2011-12-15 Thread Brent Yorgey
On Thu, Dec 15, 2011 at 09:05:13PM +, Conor McBride wrote:
 
 On 15 Dec 2011, at 15:19, Brent Yorgey wrote:
 
 On Thu, Dec 15, 2011 at 06:49:13PM +1000, Gregory Crosswhite wrote:
 
 So at the end of the day... what is the point of even making
 Maybe and [] instances of Alternative?
 
 The Alternative and Monoid instances for [] are equivalent.  However,
 the Alternative and Monoid instances for Maybe are not. To wit:
 
 (Just (Sum  4)) | (Just (Sum 3))
  Just (Sum {getSum = 4})
 
 (Just (Sum 4)) `mappend` (Just (Sum 3))
  Just (Sum {getSum = 7})
 
 The current monoid instance for Maybe is, in my view, unfortunate.
 
 Types are about semantic purpose, not just data representation.
 Many purposes can be represented in the same way. We should identify
 the purpose of a type (or type constructor), then define instances
 consistent with that purpose. And better, we acquire by instance
 inference compound instances consistent with that purpose! (A similar
 view is often articulated well by Conal Elliott. But perhaps it's
 just a Con thing.)
 
 The purpose of Maybe, it seems to me, is to model failure and
 prioritized choice, after the manner of exceptions. It's clear
 what the failure-and-prioritized-choice monoid is.
 
 It so happens that the same data representation can be used to make
 a semigroup into a monoid by attaching an identity element. That's
 a different semantic purpose, which deserves a different type.

I agree.  Moreover, the current Monoid instance for (Maybe a) does not
even achieve this, since it requires a *Monoid* instance on a, rather
than a semigroup.  

Note that the 'semigroups' package defines an 'Option' type which does
lift Semigroup instances to Monoid instances.  I, for one, would be
quite in favor of changing the current Monoid (Maybe a) instance to
correspond to the failure-and-prioritized-choice semantics (i.e. the
semantics currently given to the 'First' wrapper).

-Brent

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe