Proposal: Add Alternative adapter to Data.Monoid

I found myself needing this type in my current overhaul of Data.Foldable, but it seems to be generally useful: newtype Alt f a = Alt { getAlt :: f a } deriving (Eq,Ord,Show,Read,Typeable,Data,Generic,Num,Real, Floating, Fractional, RealFrac, RealFloat, Integral, Enum, Bounded,Ix,Functor,Foldable,Traversable,Applicative, Alternative,Monad,MonadPlus,MonadFix, IsString, IsList) -- The laundry list of derived instances is as recommended by Edward Kmett, who would probably want more added if someone can think of more. Some of them would, of course, need to be derived in other modules. The key instance is this: instance Alternative t => Monoid (Alt t a) where mempty = Alt empty (Alt m) `mappend` (Alt n) = Alt (m <|> n)

+1, I think I've defined one-off, specialized versions of this a dozen
times.
On Thu, Oct 30, 2014 at 9:46 AM, David Feuer
I found myself needing this type in my current overhaul of Data.Foldable, but it seems to be generally useful:
newtype Alt f a = Alt { getAlt :: f a } deriving (Eq,Ord,Show,Read,Typeable,Data,Generic,Num,Real, Floating, Fractional, RealFrac, RealFloat, Integral, Enum, Bounded,Ix,Functor,Foldable,Traversable,Applicative, Alternative,Monad,MonadPlus,MonadFix, IsString, IsList) -- The laundry list of derived instances is as recommended by Edward Kmett, who would probably want more added if someone can think of more. Some of them would, of course, need to be derived in other modules. The key instance is this:
instance Alternative t => Monoid (Alt t a) where mempty = Alt empty (Alt m) `mappend` (Alt n) = Alt (m <|> n)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

+1 from me.
I'll happily delete my versions in `reducers` and `monoids`.
On Thu, Oct 30, 2014 at 12:46 PM, David Feuer
I found myself needing this type in my current overhaul of Data.Foldable, but it seems to be generally useful:
newtype Alt f a = Alt { getAlt :: f a } deriving (Eq,Ord,Show,Read,Typeable,Data,Generic,Num,Real, Floating, Fractional, RealFrac, RealFloat, Integral, Enum, Bounded,Ix,Functor,Foldable,Traversable,Applicative, Alternative,Monad,MonadPlus,MonadFix, IsString, IsList) -- The laundry list of derived instances is as recommended by Edward Kmett, who would probably want more added if someone can think of more. Some of them would, of course, need to be derived in other modules. The key instance is this:
instance Alternative t => Monoid (Alt t a) where mempty = Alt empty (Alt m) `mappend` (Alt n) = Alt (m <|> n)

Oh right. This is what I joined this list to propose in the first
place, then forgot about. Uh, do I get a vote? If I have one, I'm
obviously +1 on the idea.
On Thu, Oct 30, 2014 at 10:54 AM, Oliver Charles
David Feuer
writes: I found myself needing this type in my current overhaul of Data.Foldable, but it seems to be generally useful:
+1, I can see myself wanting to reach for this.
-- ocharles _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

The one change I'd offer is this:
instance Alternative f => Monoid (Alt f a) where
mempty = Alt empty
* mappend = coerce ((<|>) :: f a -> f a -> f a)*
That way it doesn't eta-expand (<|>).
-Edward
On Fri, Oct 31, 2014 at 12:35 PM, Carl Howells
Oh right. This is what I joined this list to propose in the first place, then forgot about. Uh, do I get a vote? If I have one, I'm obviously +1 on the idea.
On Thu, Oct 30, 2014 at 10:54 AM, Oliver Charles
wrote: David Feuer
writes: I found myself needing this type in my current overhaul of Data.Foldable, but it seems to be generally useful:
+1, I can see myself wanting to reach for this.
-- ocharles _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

And one more change: this can't go in Data.Monoid; it needs to go in
Control.Applicative. I can't imagine anyone will care.
On Oct 31, 2014 12:47 PM, "Edward Kmett"
The one change I'd offer is this:
instance Alternative f => Monoid (Alt f a) where mempty = Alt empty * mappend = coerce ((<|>) :: f a -> f a -> f a)*
That way it doesn't eta-expand (<|>).
-Edward
On Fri, Oct 31, 2014 at 12:35 PM, Carl Howells
wrote: Oh right. This is what I joined this list to propose in the first place, then forgot about. Uh, do I get a vote? If I have one, I'm obviously +1 on the idea.
On Thu, Oct 30, 2014 at 10:54 AM, Oliver Charles
wrote: David Feuer
writes: I found myself needing this type in my current overhaul of Data.Foldable, but it seems to be generally useful:
+1, I can see myself wanting to reach for this.
-- ocharles _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Actually that feels like a very wrong place for it.
It may wind up having to go there, but I do care. =P
-Edward
On Fri, Oct 31, 2014 at 12:49 PM, David Feuer
And one more change: this can't go in Data.Monoid; it needs to go in Control.Applicative. I can't imagine anyone will care. On Oct 31, 2014 12:47 PM, "Edward Kmett"
wrote: The one change I'd offer is this:
instance Alternative f => Monoid (Alt f a) where mempty = Alt empty * mappend = coerce ((<|>) :: f a -> f a -> f a)*
That way it doesn't eta-expand (<|>).
-Edward
On Fri, Oct 31, 2014 at 12:35 PM, Carl Howells
wrote: Oh right. This is what I joined this list to propose in the first place, then forgot about. Uh, do I get a vote? If I have one, I'm obviously +1 on the idea.
On Thu, Oct 30, 2014 at 10:54 AM, Oliver Charles
wrote: David Feuer
writes: I found myself needing this type in my current overhaul of Data.Foldable, but it seems to be generally useful:
+1, I can see myself wanting to reach for this.
-- ocharles _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

We might be able to put it in Data.Monoid. I though I had some kind of
weird problem with that, but I don't remember.
On Fri, Oct 31, 2014 at 12:50 PM, Edward Kmett
Actually that feels like a very wrong place for it.
It may wind up having to go there, but I do care. =P
-Edward
On Fri, Oct 31, 2014 at 12:49 PM, David Feuer
wrote: And one more change: this can't go in Data.Monoid; it needs to go in Control.Applicative. I can't imagine anyone will care. On Oct 31, 2014 12:47 PM, "Edward Kmett"
wrote: The one change I'd offer is this:
instance Alternative f => Monoid (Alt f a) where mempty = Alt empty * mappend = coerce ((<|>) :: f a -> f a -> f a)*
That way it doesn't eta-expand (<|>).
-Edward
On Fri, Oct 31, 2014 at 12:35 PM, Carl Howells
wrote: Oh right. This is what I joined this list to propose in the first place, then forgot about. Uh, do I get a vote? If I have one, I'm obviously +1 on the idea.
On Thu, Oct 30, 2014 at 10:54 AM, Oliver Charles
wrote: David Feuer
writes: I found myself needing this type in my current overhaul of Data.Foldable, but it seems to be generally useful:
+1, I can see myself wanting to reach for this.
-- ocharles _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (6)
-
Carl Howells
-
David Feuer
-
Edward Kmett
-
John Lato
-
Mario Blažević
-
Oliver Charles