If you want a more uniform factoring, then at the risk of further exploding the number of options under consideration, there is an obvious choice:

class Semigroup s where
   sappend :: s -> s -> s

-- ^ like how Functor m => Monoid m, you get the obvious 'spiritual but unenforced' Semigroup m => Monoid m

newtype Min a = Min a deriving (Eq,Ord,Data,Typeable)

instance Ord a => Semigroup (Min a) where
   Min a `sappend` Min b = Min (a `min` b)

instance (Ord a, Bounded a) => Monoid (Min a) where
   mempty = maxBound
   mappend = sappend

newtype Max a = Max a deriving (Eq,Ord,Data,Typeable)

instance Ord a => Semigroup (Max a) where
   Max a `sappend` Max b = Max (a `max` b)

instance (Ord a, Bounded a) => Monoid (Max a) where
   mempty = minBound
   mappend = sappend

data Unital m = Unit | Semi m deriving (Eq, Data, Typeable)

instance Semigroup s => Semigroup (Unital s)
    Unit `mappend` b = b
    a `mappend` Unit = a
    Semi a `mappend` Semi b = Semi (a `sappend` b)

instance (Semigroup s) => Monoid (Unital s) where
    mempty = Unit
    mappend = sappend

With that Min a, Max a, Unital (Min a), Unital (Max b) would all work, and you'd pick up a type that plays the role that the Maybe monoid purports to play, which is the trivial lifting of a semigroup into a monoid by adding an additional unit.

A real proposal would probably want to flesh Unital out with a couple more combinators like

-- 'maybe'
unital :: a -> (m -> a) -> Unital m -> a
unital z _ Unit = z
unital _ f (Semi a) = f a

The only real consequence other than trying to figure out where Semigroup would fit, and fighting the 'added complexity' battle:

* MinPriority and MaxPriority can be smart enough to provide a correct Ord instance for the composite. The 'factored' version cannot without other chicanery.

Given a blank slate, this would be my favorite option.

-Edward

On Fri, Sep 24, 2010 at 3:50 AM, wren ng thornton <wren@community.haskell.org> wrote:
On 9/23/10 6:46 PM, Ross Paterson wrote:
On Thu, Sep 23, 2010 at 03:08:48PM -0400, Edward Kmett wrote:
On the other hand, composing AddBounds introduces another element on the other
side, which serves as an annihilator when composed with Min and Max. This is
fine for some applications, but I don't believe it subsumes MinPriority and
MaxPriority.

This extra element at the other end introduced by AddBounds bothers
me too.  So I agree with the conclusion that we need both versions that
add a maximum/minimum, and ones that take it from Bounded.  That leaves
the question of which variant deserves to be called Max/Min.

For my part, I like the Min/Max being the Bounded Ord one, as in the monoids library.

One amendment I'd like to bring up is that I think PriorityMin/PriorityMax should instead be (Priority Min)/(Priority Max), that is, make Priority --or whatever it's called-- take Min/Max as a phantom type argument. This can help to simplify things once you start adding in other ordering variants like

   newtype Arg  Min/Max a b = Arg  (Maybe (b,a))
   newtype Args Min/Max a b = Args (Maybe (b,[a]))

etc. I'm not suggesting that these ones be added to base, but it'd be nice to have a uniform API for handling all the different monoids of ordering.

--
Live well,
~wren

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