Maximum and Minimum monoids

I don't know if this has been brought up before or not, but would it be possible to add the Maximum and Minimum monoids to Data.Monoid? The following implementations extend the traditional semigroups using Maybe. ****** newtype Maximum a = Maximum { getMaximum :: Maybe a } instance (Ord a) => Monoid (Maximum a) where mempty = Maximum Nothing mappend (Maximum Nothing) m2 = m2 mappend m1 (Maximum Nothing) = m1 mappend (Maximum (Just a1)) (Maximum (Just a2)) = Maximum (Just (max a1 a2)) newtype Minimum a = Minimum { getMinimum :: Maybe a } instance (Ord a) => Monoid (Minimum a) where mempty = Minimum Nothing mappend (Minimum Nothing) m2 = m2 mappend m1 (Minimum Nothing) = m1 mappend (Minimum (Just a1)) (Minimum (Just a2)) = Minimum (Just (min a1 a2)) ****** These also give the correct behavior when folding empty structures by returning Nothing. The reason I'm asking is that my `pipes` library uses `WriterT` to implement folds and having the above monoids lets me implement minimum and maximum folds elegantly. I can always provide these monoids myself, but I feel like they belong in Data.Monoid.

On Thu, Dec 27, 2012 at 8:45 PM, Gabriel Gonzalez
I don't know if this has been brought up before or not, but would it be possible to add the Maximum and Minimum monoids to Data.Monoid? The following implementations extend the traditional semigroups using Maybe.
******
newtype Maximum a = Maximum { getMaximum :: Maybe a }
instance (Ord a) => Monoid (Maximum a) where mempty = Maximum Nothing
mappend (Maximum Nothing) m2 = m2 mappend m1 (Maximum Nothing) = m1 mappend (Maximum (Just a1)) (Maximum (Just a2)) = Maximum (Just (max a1 a2))
newtype Minimum a = Minimum { getMinimum :: Maybe a }
instance (Ord a) => Monoid (Minimum a) where mempty = Minimum Nothing
mappend (Minimum Nothing) m2 = m2 mappend m1 (Minimum Nothing) = m1 mappend (Minimum (Just a1)) (Minimum (Just a2)) = Minimum (Just (min a1 a2))
******
These also give the correct behavior when folding empty structures by returning Nothing.
The reason I'm asking is that my `pipes` library uses `WriterT` to implement folds and having the above monoids lets me implement minimum and maximum folds elegantly. I can always provide these monoids myself, but I feel like they belong in Data.Monoid.
+1, I've had to implement at least one of these in the past. In my case, I think I ended up doing it something like: newtype Maximum a = Maximum { getMaximum :: a } instance (Ord a, Bounded a) => Monoid (Maximum a) where mempty = Maximum minBound mappend (Maximum x) (Maximum y) = Maximum (max x y) It made sense in my specific use case, but I think Gabriel's version is better as the general approach. Michael

It made sense in my specific use case, but I think Gabriel's version is better as the general approach.
Can Gabriel derive his version from Michael's with:
instance Bounded (Maybe a) where
maxBound = Nothing
minBound = Nothing
The Bounded constraint seems right to me. If Bounded doesn't apply to your
datatype, maybe a Semigroup would be more appropriate than a Monoid?
Thanks,
Greg
On Thu, Dec 27, 2012 at 11:07 AM, Michael Snoyman
On Thu, Dec 27, 2012 at 8:45 PM, Gabriel Gonzalez
wrote: I don't know if this has been brought up before or not, but would it be possible to add the Maximum and Minimum monoids to Data.Monoid? The following implementations extend the traditional semigroups using Maybe.
******
newtype Maximum a = Maximum { getMaximum :: Maybe a }
instance (Ord a) => Monoid (Maximum a) where mempty = Maximum Nothing
mappend (Maximum Nothing) m2 = m2 mappend m1 (Maximum Nothing) = m1 mappend (Maximum (Just a1)) (Maximum (Just a2)) = Maximum (Just (max a1 a2))
newtype Minimum a = Minimum { getMinimum :: Maybe a }
instance (Ord a) => Monoid (Minimum a) where mempty = Minimum Nothing
mappend (Minimum Nothing) m2 = m2 mappend m1 (Minimum Nothing) = m1 mappend (Minimum (Just a1)) (Minimum (Just a2)) = Minimum (Just (min a1 a2))
******
These also give the correct behavior when folding empty structures by returning Nothing.
The reason I'm asking is that my `pipes` library uses `WriterT` to implement folds and having the above monoids lets me implement minimum and maximum folds elegantly. I can always provide these monoids myself, but I feel like they belong in Data.Monoid.
+1, I've had to implement at least one of these in the past. In my case, I think I ended up doing it something like:
newtype Maximum a = Maximum { getMaximum :: a } instance (Ord a, Bounded a) => Monoid (Maximum a) where mempty = Maximum minBound mappend (Maximum x) (Maximum y) = Maximum (max x y)
It made sense in my specific use case, but I think Gabriel's version is better as the general approach.
Michael
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 12/27/2012 02:02 PM, Greg Fitzgerald wrote:
It made sense in my specific use case, but I think Gabriel's version is better as the general approach.
Can Gabriel derive his version from Michael's with:
instance Bounded (Maybe a) where maxBound = Nothing minBound = Nothing
The Bounded constraint seems right to me. If Bounded doesn't apply to your datatype, maybe a Semigroup would be more appropriate than a Monoid?
In principle the two approaches are equivalent, but I can think of some "touchy feely" differences, though. The first is that while the Bounded approach you propose does recapitulate my approach in theory, in practice it encourages people to use minBound (without the Maybe) as the default way to fold values. The problem with using a non-Maybe minBound as the default is: * It loses information (because you can't tell the difference between "minimum []" and "minimum [minBound, ...]" * It gives a weird result on empty lists. "minimimum [] = minBound" feels a little weird. * It requires implementing "Bounded" for the type in question, when really an "Ord" constraint is enough to do maximums and minimums. Also, you can recapitulate the Bounded approach with my approach by using "fromMaybe minBound"/"fromMaybe maxBound". The next issue is whether it will be obvious to users that Maybe is a bounded type. You would need to document that so that users know to use that trick and that only works if users read the haddocks. If they study the type in ghci, for example, or any context other than the haddocks they will lose that key piece of information. More philosophically, it's not clear why that Maybe instance for Bounded makes any sense. It seems like a workaround, rather than a natural solution. Also, it's not clear why something needs to be bounded to have a maximum. Real numbers are unbounded, yet you can still take a maximum of a set of real numbers.

Gabriel Gonzalez
Also, it's not clear why something needs to be bounded to have a maximum. Real numbers are unbounded, yet you can still take a maximum of a set of real numbers.
I just realized what confuses me about this bounded maximum/minimum definitions: In the math literature I've been exposed to so far (see also [1][2]), to satisify the definition of a maximal/minimal element of a set that said element has to be actually contained in that set. So it seems very confusing to me to call the element resulting from (Ord a, Bounded a) => Monoid (Max a) with 'Max a' isomorphic to 'a' a proper "maximum" (as it violates the definition for 'mempty'); on the other hand, the term "supremum"[3] seems to match the semantics of the Monoid above better. [1]: http://en.wikipedia.org/wiki/Maximal_element#Definition [2]: http://mathworld.wolfram.com/Maximum.html [3]: http://en.wikipedia.org/wiki/Supremum cheers, hvr

On 28/12/2012, Herbert Valerio Riedel
I just realized what confuses me about this bounded maximum/minimum definitions: In the math literature I've been exposed to so far (see also [1][2]), to satisify the definition of a maximal/minimal element of a set that said element has to be actually contained in that set.
So it seems very confusing to me to call the element resulting from
(Ord a, Bounded a) => Monoid (Max a)
with 'Max a' isomorphic to 'a' a proper "maximum" (as it violates the definition for 'mempty'); on the other hand, the term "supremum"[3] seems to match the semantics of the Monoid above better.
[1]: http://en.wikipedia.org/wiki/Maximal_element#Definition [2]: http://mathworld.wolfram.com/Maximum.html [3]: http://en.wikipedia.org/wiki/Supremum
Ah. Yes, thanks for the clarification, to me at least. So it seems that our type of "maximum" and "minimum" is wrong; rather, it ought to be this: maximum, minimum :: (Ord a, Foldable v) => v a -> Maybe a and (Max a) and (Min a) are not properly monoids. We could define these: Supr, Infi :: * -> * instance (Ord a, Bounded a) => Monoid (Supr a) instance (Ord a, Bounded a) => Monoid (Infi a) but I'm not sure whether we ought to. Cheers, Strake

On Thu, 27 Dec 2012, Gabriel Gonzalez wrote:
I don't know if this has been brought up before or not, but would it be possible to add the Maximum and Minimum monoids to Data.Monoid? The following implementations extend the traditional semigroups using Maybe.
I remember there was a discussion on this topic some years ago. If you want I may search for the old discussion.

On Thu, 27 Dec 2012, Henning Thielemann wrote:
On Thu, 27 Dec 2012, Gabriel Gonzalez wrote:
I don't know if this has been brought up before or not, but would it be possible to add the Maximum and Minimum monoids to Data.Monoid? The following implementations extend the traditional semigroups using Maybe.
I remember there was a discussion on this topic some years ago. If you want I may search for the old discussion.
I think that it was the discussion on "Proposal: Max and Min for Monoid" started by Jake McArthur: http://www.haskell.org/pipermail/libraries/2010-September/014347.html But it seems that the discussion was already performed once more.

I kicked off a discussion 5 years ago (according to trac) and suggested the Bounded solution. I still miss these instances and find myself redefining them. It bothers me, however that the Bounded constraint is unnecessarily restrictive. We only need UpperBounded for Min and LowerBounded for Max. -- Conal On Sat, Dec 29, 2012 at 3:02 PM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
On Thu, 27 Dec 2012, Henning Thielemann wrote:
On Thu, 27 Dec 2012, Gabriel Gonzalez wrote:
I don't know if this has been brought up before or not, but would it be
possible to add the Maximum and Minimum monoids to Data.Monoid? The following implementations extend the traditional semigroups using Maybe.
I remember there was a discussion on this topic some years ago. If you want I may search for the old discussion.
I think that it was the discussion on "Proposal: Max and Min for Monoid" started by Jake McArthur: http://www.haskell.org/**pipermail/libraries/2010-** September/014347.htmlhttp://www.haskell.org/pipermail/libraries/2010-September/014347.html
But it seems that the discussion was already performed once more.
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries

On 12/29/12 10:28 PM, Conal Elliott wrote:
I kicked off a discussion 5 years ago (according to trac) and suggested the Bounded solution. I still miss these instances and find myself redefining them. It bothers me, however that the Bounded constraint is unnecessarily restrictive. We only need UpperBounded for Min and LowerBounded for Max.
Indeed. And this isn't the only place the distinction is worth making. Those two classes are in the prelude I've been developing over the past few years (for personal/internal work). One of these days I'll push it to Hackage, and maybe one day it'll make it's way into Haskell'. -- Live well, ~wren

Wouldn't it be better to have a real algebraic type instead of wrapping
Maybe?
Something like
data Maximum a = MinusInfinity | Maximum a
data Minimum a = PlusInfinity | Minimum a
Maximum x is more concise than Maximum (Just x), and MinusInfinity is
more descriptive than Maximum Nothing. getMaximum/getMinimum functions
can still return Maybes.
Anyway, I'm +1 to having something along these lines.
Roman
* Gabriel Gonzalez
I don't know if this has been brought up before or not, but would it be possible to add the Maximum and Minimum monoids to Data.Monoid? The following implementations extend the traditional semigroups using Maybe.
******
newtype Maximum a = Maximum { getMaximum :: Maybe a }
instance (Ord a) => Monoid (Maximum a) where mempty = Maximum Nothing
mappend (Maximum Nothing) m2 = m2 mappend m1 (Maximum Nothing) = m1 mappend (Maximum (Just a1)) (Maximum (Just a2)) = Maximum (Just (max a1 a2))
newtype Minimum a = Minimum { getMinimum :: Maybe a }
instance (Ord a) => Monoid (Minimum a) where mempty = Minimum Nothing
mappend (Minimum Nothing) m2 = m2 mappend m1 (Minimum Nothing) = m1 mappend (Minimum (Just a1)) (Minimum (Just a2)) = Minimum (Just (min a1 a2))
******
These also give the correct behavior when folding empty structures by returning Nothing.
The reason I'm asking is that my `pipes` library uses `WriterT` to implement folds and having the above monoids lets me implement minimum and maximum folds elegantly. I can always provide these monoids myself, but I feel like they belong in Data.Monoid.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 12/27/2012 02:25 PM, Roman Cheplyaka wrote:
Wouldn't it be better to have a real algebraic type instead of wrapping Maybe?
Something like
data Maximum a = MinusInfinity | Maximum a data Minimum a = PlusInfinity | Minimum a
Maximum x is more concise than Maximum (Just x), and MinusInfinity is more descriptive than Maximum Nothing. getMaximum/getMinimum functions can still return Maybes.
Anyway, I'm +1 to having something along these lines.
Roman
Interesting. Then you can recapitulate the original Maybe API using: getMaximum :: Maximum a -> Maybe a getMinimum :: Minimum a -> Maybe a One slight disadvantage is that there might be a tiny overhead for converting between Maximum/Minimum and Maybe, but I doubt that would be a bottle-neck in any application. Another disadvantage is then it sets a precedent for redefining the First and Last Monoids to similarly more descriptive types. When I did it the Maybe way I was just copying the way First and Last worked.

* Gabriel Gonzalez
On 12/27/2012 02:25 PM, Roman Cheplyaka wrote:
Wouldn't it be better to have a real algebraic type instead of wrapping Maybe?
Something like
data Maximum a = MinusInfinity | Maximum a data Minimum a = PlusInfinity | Minimum a
Maximum x is more concise than Maximum (Just x), and MinusInfinity is more descriptive than Maximum Nothing. getMaximum/getMinimum functions can still return Maybes.
Anyway, I'm +1 to having something along these lines.
Roman
Interesting. Then you can recapitulate the original Maybe API using:
getMaximum :: Maximum a -> Maybe a getMinimum :: Minimum a -> Maybe a
One slight disadvantage is that there might be a tiny overhead for converting between Maximum/Minimum and Maybe, but I doubt that would be a bottle-neck in any application.
But the type isn't abstract, so nothing prevents one from using direct pattern matching in tight loops.
Another disadvantage is then it sets a precedent for redefining the First and Last Monoids to similarly more descriptive types. When I did it the Maybe way I was just copying the way First and Last worked.
I don't think the analogy holds. First and Last are wrappers for Maybe by intention — they are needed because we can't have two different instances for Maybe (although both of them make sense). In this case, however, Maybe is used artificially to "lift" numbers. Monoidal instance for Maybe corresponding to 'max' would look rather weird. Finally, we have nice names for mempty of Maximum/Minimum but not of First/Last. Roman

On 12/27/2012 02:45 PM, Roman Cheplyaka wrote:
I don't think the analogy holds. First and Last are wrappers for Maybe by intention — they are needed because we can't have two different instances for Maybe (although both of them make sense).
In this case, however, Maybe is used artificially to "lift" numbers. Monoidal instance for Maybe corresponding to 'max' would look rather weird.
Finally, we have nice names for mempty of Maximum/Minimum but not of First/Last.
Roman Good point. Now I'm slightly in favor of Roman's approach. Count me as +0.2 for Roman's version.

Can't you use Option (Max a) from the semigroups package?
Sjoerd
On Dec 27, 2012, at 7:45 PM, Gabriel Gonzalez
I don't know if this has been brought up before or not, but would it be possible to add the Maximum and Minimum monoids to Data.Monoid? The following implementations extend the traditional semigroups using Maybe.
******
newtype Maximum a = Maximum { getMaximum :: Maybe a }
instance (Ord a) => Monoid (Maximum a) where mempty = Maximum Nothing
mappend (Maximum Nothing) m2 = m2 mappend m1 (Maximum Nothing) = m1 mappend (Maximum (Just a1)) (Maximum (Just a2)) = Maximum (Just (max a1 a2))
newtype Minimum a = Minimum { getMinimum :: Maybe a }
instance (Ord a) => Monoid (Minimum a) where mempty = Minimum Nothing
mappend (Minimum Nothing) m2 = m2 mappend m1 (Minimum Nothing) = m1 mappend (Minimum (Just a1)) (Minimum (Just a2)) = Minimum (Just (min a1 a2))
******
These also give the correct behavior when folding empty structures by returning Nothing.
The reason I'm asking is that my `pipes` library uses `WriterT` to implement folds and having the above monoids lets me implement minimum and maximum folds elegantly. I can always provide these monoids myself, but I feel like they belong in Data.Monoid.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I agree that it's more correct to leave them as semigroups. The real path should be to move the semigroup package into the platform for the next release. (And, eventually, subsequent to that, to remove First and Last from Data.Monoid entirely). Cheers, Gershom On 12/27/12 7:13 PM, Herbert Valerio Riedel wrote:
Sjoerd Visscher
writes: Can't you use Option (Max a) from the semigroups package? This was my first thought as well; IMHO, the elementary Minimum/Maximum operation forms a semigroup rather than a monoid.
cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Thu, Dec 27, 2012 at 9:26 PM, Gershom Bazerman
The real path should be to move the semigroup package into the platform for the next release. (And, eventually, subsequent to that, to remove First and Last from Data.Monoid entirely).
+1, Completely agree.
--
Gregory Collins

On Fri, Dec 28, 2012 at 8:14 AM, Gregory Collins
On Thu, Dec 27, 2012 at 9:26 PM, Gershom Bazerman
wrote: The real path should be to move the semigroup package into the platform for the next release. (And, eventually, subsequent to that, to remove First and Last from Data.Monoid entirely).
+1, Completely agree.
+1 for moving semigroups into the platform, but what's the motivation for removing First and Last from Data.Monoid? Michael

On 12/28/12 1:20 AM, Michael Snoyman wrote:
+1 for moving semigroups into the platform, but what's the motivation for removing First and Last from Data.Monoid?
Because they're properly represented as semigroups too, just like Min and Max (i.e. they don't behave sensibly "out of the box" on empty lists). The semigroups package already provides the proper types and instances. And just like Min and Max, the semigroups package lets you "lift" its First and Last into Monoids with the Option type. --Gershom

On Fri, Dec 28, 2012 at 8:30 AM, Gershom Bazerman
On 12/28/12 1:20 AM, Michael Snoyman wrote:
+1 for moving semigroups into the platform, but what's the motivation for removing First and Last from Data.Monoid?
Because they're properly represented as semigroups too, just like Min and Max (i.e. they don't behave sensibly "out of the box" on empty lists). The semigroups package already provides the proper types and instances. And just like Min and Max, the semigroups package lets you "lift" its First and Last into Monoids with the Option type.
Just because such a lifting is possible doesn't mean that it will be intuitive or obvious to new users. (I wouldn't know how to make this switch, for example.) First and Last as currently provided by the Data.Monoid module provide some very useful functionality; I've used them in the past for such things as representing nested config files. I wouldn't want to provide a default value for the options, but want to use the first (or last) value in the file. So count me as -1 to modifications to First and Last. Michael

Hi,
Michael Snoyman
Because they're properly represented as semigroups too, just like Min and Max (i.e. they don't behave sensibly "out of the box" on empty lists). The semigroups package already provides the proper types and instances. And just like Min and Max, the semigroups package lets you "lift" its First and Last into Monoids with the Option type.
Just because such a lifting is possible doesn't mean that it will be intuitive or obvious to new users. (I wouldn't know how to make this switch, for example.)
...this seems to call for better documentation (including examples) of the Data.Semigroup.Option Monoid instance then. Do you have an example where it might not be obvious how to use Option (Semigroup.First a) instead of Monoid.First a ? cheers, hvr

On Fri, Dec 28, 2012 at 11:42 AM, Herbert Valerio Riedel
Hi,
Michael Snoyman
writes: [...] Because they're properly represented as semigroups too, just like Min and Max (i.e. they don't behave sensibly "out of the box" on empty lists). The semigroups package already provides the proper types and instances. And just like Min and Max, the semigroups package lets you "lift" its First and Last into Monoids with the Option type.
Just because such a lifting is possible doesn't mean that it will be intuitive or obvious to new users. (I wouldn't know how to make this switch, for example.)
...this seems to call for better documentation (including examples) of the Data.Semigroup.Option Monoid instance then.
Do you have an example where it might not be obvious how to use
Option (Semigroup.First a)
instead of
Monoid.First a
?
cheers, hvr
I'm simply approaching this from the standpoint of a new user. Monoid is enough of a hurdle to try and learn and understand properly. Now that the user has learnt about Monoid, he/she goes to Data.Monoid because the Hoogle documentation leads there, and currently finds the First and Last datatypes. Case closed, objective achieved. If we remove First and Last, then the user now needs to: 1. Realize that semigroups exist 2. Realize that they are related to Monoid 3. Find the documentation for them 4. Understand that Option can be composed with First to create a Monoid Perhaps adding a bunch of documentation to Data.Monoid could solve this, but I simply don't see that the current First and Last datatypes are problematic enough that they should actually be removed. Michael

* Herbert Valerio Riedel
Hi,
Michael Snoyman
writes: [...] Because they're properly represented as semigroups too, just like Min and Max (i.e. they don't behave sensibly "out of the box" on empty lists). The semigroups package already provides the proper types and instances. And just like Min and Max, the semigroups package lets you "lift" its First and Last into Monoids with the Option type.
Just because such a lifting is possible doesn't mean that it will be intuitive or obvious to new users. (I wouldn't know how to make this switch, for example.)
...this seems to call for better documentation (including examples) of the Data.Semigroup.Option Monoid instance then.
Do you have an example where it might not be obvious how to use
Option (Semigroup.First a)
instead of
Monoid.First a
?
I disagree that Monoid.First is not useful by itself. It solves the problem when you already have a list (or another data structure) of Maybes, and want to fold them. Expressing this through Option and Semigroup.First would require more code and run-time conversions. Roman

On 12/27/12 1:45 PM, Gabriel Gonzalez wrote:
I don't know if this has been brought up before or not, but would it be possible to add the Maximum and Minimum monoids to Data.Monoid? The following implementations extend the traditional semigroups using Maybe.
If we're going to go ahead with this, I've preferred using the following suite which has a number of useful generalizations on the theme. The only downside is that some of these require FlexibleInstances and KindSignatures. ---------------------------------------------------------------- ---------------------------------------------------------------- -- | The 'Monoid' given by @('max','minBound')@ newtype Max a = Max a deriving (Eq, Ord, Show, Read, Bounded) -- | Unwrap a 'Max' value. Not using record syntax to define this, -- in order to pretty up the derived 'Show' instance. getMax :: Max a -> a getMax (Max a) = a instance Functor Max where fmap f (Max a) = Max (f a) instance (Ord a, Bounded a) => Monoid (Max a) where mempty = Max minBound mappend = max ---------------------------------------------------------------- -- | The 'Monoid' given by @('min','maxBound')@ newtype Min a = Min a deriving (Eq, Ord, Show, Read, Bounded) -- | Unwrap a 'Min' value. Not using record syntax to define this, -- in order to pretty up the derived 'Show' instance. getMin :: Min a -> a getMin (Min a) = a instance Functor Min where fmap f (Min a) = Min (f a) instance (Ord a, Bounded a) => Monoid (Min a) where mempty = Min maxBound mappend = min ---------------------------------------------------------------- ---------------------------------------------------------------- -- | Monoids for unbounded ordered types, with @Nothing@ serving -- as the extreme bound. newtype Priority (m :: * -> *) a = Priority (Maybe a) deriving (Read, Show, Eq) -- | Constructor for a 'Priority' value. mkPriority :: (Ord a) => a -> Priority m a mkPriority x = Priority (Just x) -- | Monomorphized version of 'mkPriority' for convenience. mkPriorityMax :: (Ord a) => a -> Priority Max a mkPriorityMax = mkPriority -- | Monomorphized version of 'mkPriority' for convenience. mkPriorityMin :: (Ord a) => a -> Priority Min a mkPriorityMin = mkPriority -- | Unwrap a 'Priority' value. Not using record syntax to define -- this, in order to pretty up the derived 'Show' instance. getPriority :: Priority m a -> Maybe a getPriority (Priority a) = a instance Functor (Priority m) where fmap f (Priority ma) = Priority (fmap f ma) ---------------------------------------------------------------- -- | The smallest value for @Priority Max@. minfinity :: Priority Max a minfinity = Priority Nothing instance Ord a => Ord (Priority Max a) where Priority Nothing `compare` Priority Nothing = EQ Priority Nothing `compare` _ = LT _ `compare` Priority Nothing = GT Priority (Just a) `compare` Priority (Just b) = a `compare` b instance (Ord a) => Monoid (Priority Max a) where mempty = minfinity mappend = max ---------------------------------------------------------------- -- | The largest value for @Priority Min@. infinity :: Priority Min a infinity = Priority Nothing instance Ord a => Ord (Priority Min a) where Priority Nothing `compare` Priority Nothing = EQ Priority Nothing `compare` _ = GT _ `compare` Priority Nothing = LT Priority (Just a) `compare` Priority (Just b) = a `compare` b instance (Ord a) => Monoid (Priority Min a) where mempty = infinity mappend = min ---------------------------------------------------------------- -- | Coalesce the @Nothing@ of 'Priority' and the extreme bound of -- 'Min'\/'Max'. This is helpful for maintaining sparse maps, where -- absent keys are mapped to the extreme value. class Prioritizable m where toPriority :: (Eq a, Bounded a) => m a -> Priority m a fromPriority :: (Bounded a) => Priority m a -> m a instance Prioritizable Max where toPriority (Max a) | a == minBound = Priority Nothing | otherwise = Priority (Just a) fromPriority (Priority Nothing) = Max minBound fromPriority (Priority (Just a)) = Max a instance Prioritizable Min where toPriority (Min a) | a == maxBound = Priority Nothing | otherwise = Priority (Just a) fromPriority (Priority Nothing) = Min maxBound fromPriority (Priority (Just a)) = Min a ---------------------------------------------------------------- ---------------------------------------------------------------- -- | A type for min-\/maximizing a function of type @(Ord b) => (a -> b)@. -- When there are multiple arguments with the same min-\/maximum -- value, 'mappend' returns the first one but the traversable -- functions may return an arbitrary one depending on their order -- of traversal. If the function is injective, then there can be -- no confusion (i.e., we won't need to choose). -- -- Technically, this type should also be annotated by the function -- it min-\/maximizes, but that would require dependent types. Using -- the monoid operations on values generated by different functions -- will yield meaningless results. newtype Arg (m :: * -> *) a b = Arg (Maybe (b,a)) -- N.B., we chose this order for the pair in order to -- facilitate nested argmaxing -- N.B., constructor isn't exported, for correctness. -- | Constructor for an 'Arg' value. Using the monoid operations -- on values generated by different functions will yield meaningless -- results. mkArg :: (Ord b) => (a -> b) -> a -> Arg m a b mkArg f x = Arg (Just (f x, x)) -- | Monomorphized version of 'mkArg' for convenience. mkArgMax :: (Ord b) => (a -> b) -> a -> Arg Max a b mkArgMax = mkArg -- | Monomorphized version of 'mkArg' for convenience. mkArgMin :: (Ord b) => (a -> b) -> a -> Arg Min a b mkArgMin = mkArg -- | Destructor for 'Arg' returning both the argmin\/-max and the -- min\/max. @Nothing@ represents min-\/maximization over the empty -- set. getArgWithValue :: Arg m a b -> Maybe (b,a) getArgWithValue (Arg x) = x -- | Destructor for 'Arg' returning only the argmin\/-max. @Nothing@ -- represents min-\/maximization over the empty set. getArg :: Arg m a b -> Maybe a getArg = fmap snd . getArgWithValue instance (Ord b) => Monoid (Arg Max a b) where mempty = Arg Nothing mappend ma mb = case ma of Arg Nothing -> mb Arg (Just (fa,_)) -> case mb of Arg Nothing -> ma Arg (Just (fb,_)) -> if fa >= fb then ma else mb instance (Ord b) => Monoid (Arg Min a b) where mempty = Arg Nothing mappend ma mb = case ma of Arg Nothing -> mb Arg (Just (fa,_)) -> case mb of Arg Nothing -> ma Arg (Just (fb,_)) -> if fa <= fb then ma else mb ---------------------------------------------------------------- -- | A type for min-\/maximizing a non-injective function of type -- @(Ord b) => (a -> b)@. This variant of 'Arg' will return all -- values that min-\/maximize the function. Using 'mappend' they -- will be returned in order, but the traversable functions may -- return them in an arbitrary order depending on the order of -- traversal. Duplicates will be preserved regardless. -- -- Technically, this type should also be annotated by the function -- it min-\/maximizes, but that would require dependent types. Using -- the monoid operations on values generated by different functions -- will yield meaningless results. newtype Args (m :: * -> *) a b = Args (Maybe (b,[a])) -- N.B., constructor isn't exported, for correctness. -- | Constructor for an 'Args' value. Using the monoid operations -- on values generated by different functions will yield meaningless -- results. mkArgs :: (Ord b) => (a -> b) -> a -> Args m a b mkArgs f x = Args (Just (f x, [x])) -- | Monomorphized version of 'mkArgs' for convenience. mkArgsMax :: (Ord b) => (a -> b) -> a -> Args Max a b mkArgsMax = mkArgs -- | Monomorphized version of 'mkArgs' for convenience. mkArgsMin :: (Ord b) => (a -> b) -> a -> Args Min a b mkArgsMin = mkArgs -- | Destructor for 'Args' returning both the argmins\/-maxes and -- the min\/max. @Nothing@ represents min-\/maximization over the -- empty set. getArgsWithValue :: Args m a b -> Maybe (b,[a]) getArgsWithValue (Args x) = x -- | Destructor for 'Args' returning only the argmins\/-maxes. The -- empty list represents min-\/maximization over the empty set. getArgs :: Args m a b -> [a] getArgs = maybe [] snd . getArgsWithValue instance (Ord b) => Monoid (Args Max a b) where mempty = Args Nothing mappend ma mb = case ma of Args Nothing -> mb Args (Just (fa,as)) -> case mb of Args Nothing -> ma Args (Just (fb,bs)) -> case compare fa fb of GT -> ma EQ -> Args (Just (fa, as++bs)) LT -> mb instance (Ord b) => Monoid (Args Min a b) where mempty = Args Nothing mappend ma mb = case ma of Args Nothing -> mb Args (Just (fa,as)) -> case mb of Args Nothing -> ma Args (Just (fb,bs)) -> case compare fa fb of LT -> ma EQ -> Args (Just (fa, as++bs)) GT -> mb ---------------------------------------------------------------- ----------------------------------------------------------- fin. -- Live well, ~wren
participants (12)
-
Conal Elliott
-
Gabriel Gonzalez
-
Gershom Bazerman
-
Greg Fitzgerald
-
Gregory Collins
-
Henning Thielemann
-
Herbert Valerio Riedel
-
Michael Snoyman
-
Roman Cheplyaka
-
Sjoerd Visscher
-
Strake
-
wren ng thornton