Proposal: Max and Min for Monoid (ticket # 1952)

I'd like to add two instances to Data.Monoid, alongside of All/Any, Sum/Product, and First/Last. Here's a current instance (as a style example): -- | Boolean monoid under conjunction. newtype All = All { getAll :: Bool } deriving (Eq, Ord, Read, Show, Bounded) instance Monoid All where mempty = All True All x `mappend` All y = All (x && y) My proposed addition: -- | Ordered monoid under 'max'. newtype Max a = Max { getMax :: a } deriving (Eq, Ord, Read, Show, Bounded) instance (Ord a, Bounded a) => Monoid (Max a) where mempty = Max minBound Max a `mappend` Max b = Max (a `max` b) -- | Ordered monoid under 'min'. newtype Min a = Min { getMin :: a } deriving (Eq, Ord, Read, Show, Bounded) instance (Ord a, Bounded a) => Monoid (Min a) where mempty = Min minBound Min a `mappend` Min b = Min (a `min` b) I have a niggling uncertainty about the Ord & Bounded instances for Min a? Is there a reason flip the a ordering instead of preserving it? Suggested review period: two weeks (ending December 16). Comments? - Conal

oops! copy/paste/edit error. thanks for catching.
On Dec 2, 2007 11:26 AM, Ian Lynagh
On Sun, Dec 02, 2007 at 09:57:50AM -0800, Conal Elliott wrote:
instance (Ord a, Bounded a) => Monoid (Min a) where mempty = Min minBound
I think you mean:
mempty = Min maxBound
Min a `mappend` Min b = Min (a `min` b)
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sun, Dec 02, 2007 at 09:57:50AM -0800, Conal Elliott wrote:
My proposed addition:
-- | Ordered monoid under 'max'. newtype Max a = Max { getMax :: a } deriving (Eq, Ord, Read, Show, Bounded)
instance (Ord a, Bounded a) => Monoid (Max a) where mempty = Max minBound Max a `mappend` Max b = Max (a `max` b)
Funny, I was thinking of proposing a Max type that adjoined a synthetic identity, as we did in the finger tree paper: data Max a = NoMax | Max a deriving (Eq, Ord, Read, Show) instance Ord a => Monoid (Max a) where mempty = NoMax NoMax `mappend` b = b a `mappend` NoMax = a Max x `mappend` Max y = Max (x `max` y) and similarly for Min. One could even define getMax :: Bounded a => Max a -> a getMax NoMax = minBound getMax (Max x) = x

Ross Paterson wrote:
Funny, I was thinking of proposing a Max type that adjoined a synthetic identity, as we did in the finger tree paper:
data Max a = NoMax | Max a deriving (Eq, Ord, Read, Show)
instance Ord a => Monoid (Max a) where mempty = NoMax NoMax `mappend` b = b a `mappend` NoMax = a Max x `mappend` Max y = Max (x `max` y)
and similarly for Min. One could even define
getMax :: Bounded a => Max a -> a getMax NoMax = minBound getMax (Max x) = x
I was thinking you could get that with some version of the (Maybe (Max a)) Monoid, but you are right: your version doesn't require (a) to be Bounded, thus works with Integers etc. Isaac

Ross Paterson wrote:
data Max a = NoMax | Max a deriving (Eq, Ord, Read, Show)
and similarly for Min.
data Min a = Min a | NoMin so that the deriving Ord works as expected The newtypes don't add a possible bottom, but data does... should (Max undefined) be non-bottom, or should the data types have strictness annotations perhaps? Isaac

Similarly, I'm using the following to get around type parameters that don't
provide Bounded:
data AddBounds a = MinBound | NoBound a | MaxBound
deriving (Eq, Ord, Read, Show)
instance Bounded (AddBounds a) where
minBound = MinBound
maxBound = MaxBound
On Dec 2, 2007 3:25 PM, Ross Paterson
On Sun, Dec 02, 2007 at 09:57:50AM -0800, Conal Elliott wrote:
My proposed addition:
-- | Ordered monoid under 'max'. newtype Max a = Max { getMax :: a } deriving (Eq, Ord, Read, Show, Bounded)
instance (Ord a, Bounded a) => Monoid (Max a) where mempty = Max minBound Max a `mappend` Max b = Max (a `max` b)
Funny, I was thinking of proposing a Max type that adjoined a synthetic identity, as we did in the finger tree paper:
data Max a = NoMax | Max a deriving (Eq, Ord, Read, Show)
instance Ord a => Monoid (Max a) where mempty = NoMax NoMax `mappend` b = b a `mappend` NoMax = a Max x `mappend` Max y = Max (x `max` y)
and similarly for Min. One could even define
getMax :: Bounded a => Max a -> a getMax NoMax = minBound getMax (Max x) = x _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (4)
-
Conal Elliott
-
Ian Lynagh
-
Isaac Dupree
-
Ross Paterson