{-

Hi.

May we please have a partial order class in Haskell at some stage?  It
can be done outside the prelude (see below), but would be nicer inside
(see below, removing all the tildes and primes).

Something similar could be done with abstract algebra above the Num
and Fractional classes: Group defining (+), negate, (-), and zero;
Ring defining (*); and Field defining (/), recip, and one.  I'm not so
fussed about these, though.

Regards,
Tom

-}

data PartialOrdering = PLT | PEQ | PGT | PUnrelated
    deriving (Eq, Ord, Ix, Enum, Read, Show, Bounded)

class Eq a => PartialOrd a where
    partialCompare :: a -> a -> PartialOrdering
    (<=~), (<~), (>=~), (>~) :: a -> a -> Bool

    -- Minimal complete definition: partialCompare or (<=~)

    partialCompare x y | x ==  y   = PEQ
                       | x <=~ y   = PLT
                       | y <=~ x   = PGT
                       | otherwise = PUnrelated

    x <=~ y = partialCompare x y <  PGT
    x <~  y = partialCompare x y == PLT
    x >=~ y = partialCompare y x <  PGT
    x >~  y = partialCompare y x == PLT

class PartialOrd a => Ord' a where
    compare' :: a -> a -> Ordering
    max', min' :: a -> a -> a

    -- Minimal complete definition: None

    compare' x y | x ==  y   = EQ
                 | x <=~ y   = LT
                 | otherwise = GT

    max' x y | x >=~ y   = x
             | otherwise = y
    min' x y | x <=~ y   = x
             | otherwise = y

Reply via email to