Dylan Thurston wrote:
>
> I've started writing up a more concrete proposal for what I'd like the
> Prelude to look like in terms of numeric classes.

I like this proposal a lot.  The organization is closer to
traditional mathematical structures than the current
Prelude, but not as intimidating as Mechveliani's
Basic Algebra Proposal.  A very nice balance, IMO.

A couple of requests:

> > module Lattice where
> > class Lattice a where
> >     meet, join :: a -> a -> a

Could this be split into

    class SemiLattice a where
        join :: a -> a -> a

and

    class (SemiLattice a) => Lattice a where
        meet :: a -> a -> a

I run across a lot of structures which could usefully
be modeled as semilattices, but lack a 'meet' operation.

> It would be reasonable to make Ord a
> subclass of this, but it would probably complicate the class heirarchy
> too much for the gain.

In a similar vein, I'd really like to see the Ord class
split up:

    class PartialOrder a where
        (<), (>)   :: a -> a -> Bool

    class (Eq a, PartialOrder a) => Ord a where
        compare    :: a -> a -> Ordering
        (<=), (>=) :: a -> a -> Bool
        max, min   :: a -> a -> a

Perhaps it would make sense for PartialOrder to be a
superclass of Lattice?


--Joe English

  [EMAIL PROTECTED]

_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to