module Algebra.Indexable (
    C(compare),
    ordCompare,
    liftCompare,
    ToOrd,
    toOrd,
    fromOrd,
    ) where
import Prelude hiding (compare)
import qualified Prelude as P
class Eq a => C a where
   compare :: a -> a -> Ordering
ordCompare :: Ord a => a -> a -> Ordering
ordCompare :: a -> a -> Ordering
ordCompare = a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
P.compare
liftCompare :: C b => (a -> b) -> a -> a -> Ordering
liftCompare :: (a -> b) -> a -> a -> Ordering
liftCompare a -> b
f a
x a
y = b -> b -> Ordering
forall a. C a => a -> a -> Ordering
compare (a -> b
f a
x) (a -> b
f a
y)
instance (C a, C b) => C (a,b) where
   compare :: (a, b) -> (a, b) -> Ordering
compare (a
x0,b
x1) (a
y0,b
y1) =
      let res :: Ordering
res = a -> a -> Ordering
forall a. C a => a -> a -> Ordering
compare a
x0 a
y0
      in  case Ordering
res of
             Ordering
EQ -> b -> b -> Ordering
forall a. C a => a -> a -> Ordering
compare b
x1 b
y1
             Ordering
_  -> Ordering
res
instance C a => C [a] where
   compare :: [a] -> [a] -> Ordering
compare [] [] = Ordering
EQ
   compare [] [a]
_  = Ordering
LT
   compare [a]
_  [] = Ordering
GT
   compare (a
x:[a]
xs) (a
y:[a]
ys) = (a, [a]) -> (a, [a]) -> Ordering
forall a. C a => a -> a -> Ordering
compare (a
x,[a]
xs) (a
y,[a]
ys)
instance C Integer where
   compare :: Integer -> Integer -> Ordering
compare = Integer -> Integer -> Ordering
forall a. Ord a => a -> a -> Ordering
ordCompare
newtype ToOrd a = ToOrd {ToOrd a -> a
fromOrd :: a} deriving (ToOrd a -> ToOrd a -> Bool
(ToOrd a -> ToOrd a -> Bool)
-> (ToOrd a -> ToOrd a -> Bool) -> Eq (ToOrd a)
forall a. Eq a => ToOrd a -> ToOrd a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ToOrd a -> ToOrd a -> Bool
$c/= :: forall a. Eq a => ToOrd a -> ToOrd a -> Bool
== :: ToOrd a -> ToOrd a -> Bool
$c== :: forall a. Eq a => ToOrd a -> ToOrd a -> Bool
Eq, Int -> ToOrd a -> ShowS
[ToOrd a] -> ShowS
ToOrd a -> String
(Int -> ToOrd a -> ShowS)
-> (ToOrd a -> String) -> ([ToOrd a] -> ShowS) -> Show (ToOrd a)
forall a. Show a => Int -> ToOrd a -> ShowS
forall a. Show a => [ToOrd a] -> ShowS
forall a. Show a => ToOrd a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ToOrd a] -> ShowS
$cshowList :: forall a. Show a => [ToOrd a] -> ShowS
show :: ToOrd a -> String
$cshow :: forall a. Show a => ToOrd a -> String
showsPrec :: Int -> ToOrd a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ToOrd a -> ShowS
Show)
toOrd :: a -> ToOrd a
toOrd :: a -> ToOrd a
toOrd = a -> ToOrd a
forall a. a -> ToOrd a
ToOrd
instance C a => Ord (ToOrd a) where
   compare :: ToOrd a -> ToOrd a -> Ordering
compare (ToOrd a
x) (ToOrd a
y) = a -> a -> Ordering
forall a. C a => a -> a -> Ordering
compare a
x a
y