module Data.Singletons.Prelude.Ord (
POrd(..), SOrd(..),
thenCmp, ThenCmp, sThenCmp,
Sing(SLT, SEQ, SGT),
ThenCmpSym0, ThenCmpSym1, ThenCmpSym2,
LTSym0, EQSym0, GTSym0,
CompareSym0, CompareSym1, CompareSym2,
(:<$), (:<$$), (:<$$$),
(:<=$), (:<=$$), (:<=$$$),
(:>$), (:>$$), (:>$$$),
(:>=$), (:>=$$), (:>=$$$),
MaxSym0, MaxSym1, MaxSym2,
MinSym0, MinSym1, MinSym2
) where
import Data.Singletons.Single
import Data.Singletons.Prelude.Eq
import Data.Singletons.Prelude.Instances
import Data.Singletons.Prelude.Bool
import Data.Singletons.Util
$(singletonsOnly [d|
class (Eq a) => Ord a where
compare :: a -> a -> Ordering
(<), (<=), (>), (>=) :: a -> a -> Bool
infix 4 <=
infix 4 <
infix 4 >
infix 4 >=
max, min :: a -> a -> a
compare x y = if x == y then EQ
else if x <= y then LT
else GT
x < y = case compare x y of { LT -> True; EQ -> False; GT -> False }
x <= y = case compare x y of { LT -> True; EQ -> True; GT -> False }
x > y = case compare x y of { LT -> False; EQ -> False; GT -> True }
x >= y = case compare x y of { LT -> False; EQ -> True; GT -> True }
max x y = if x <= y then y else x
min x y = if x <= y then x else y
|])
$(singletons [d|
thenCmp :: Ordering -> Ordering -> Ordering
thenCmp EQ x = x
thenCmp LT _ = LT
thenCmp GT _ = GT
|])
$(singOrdInstances basicTypes)