{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Kinds.Ord
(
Compare
, type (<?), type (<=?), type (==?), type (/=?), type (>=?), type (>?)
, type (<), type (<=), type (==), type (/=), type (>=), type (>)
, Max, Min
, OrderingI(..)
, Proven, OrdCond, CompareCond
) where
#if MIN_VERSION_base(4, 16, 0)
import Data.Type.Ord
( Compare, OrdCond
, type (<?), type (>?), type (<=?), type (>=?)
, type (<=), type (>=), type (>)
, Max, Min, OrderingI(..)
)
#else
import GHC.TypeLits (CmpNat)
type family Compare (x :: k) (y :: k) :: Ordering
type instance Compare x y = CmpNat x y
#endif
type CompareCond x y lt eq gt = OrdCond (Compare x y) lt eq gt
#if !MIN_VERSION_base(4, 16, 0)
type family OrdCond (o :: Ordering) (lt :: k) (eq :: k) (gt :: k) :: k where
OrdCond 'LT lt eq gt = lt
OrdCond 'EQ lt eq gt = eq
OrdCond 'GT lt eq gt = gt
infix 4 <?, >?, <=?, >=?
type x <? y = CompareCond x y True False False
type x >? y = CompareCond x y False False True
type x <=? y = CompareCond x y True True False
type x >=? y = CompareCond x y False True True
#endif
infix ==?, /=?
type x ==? y = CompareCond x y False True False
type x /=? y = CompareCond x y True False True
type Proven b = b ~ 'True
#if !MIN_VERSION_base(4, 16, 0)
infix 4 <=, >=, >
type x <= y = Proven (x <=? y)
type x >= y = Proven (x >=? y)
type x > y = Proven (x >? y)
#endif
infix 4 <, ==, /=
type x < y = Proven (x <? y)
type x == y = Proven (x ==? y)
type x /= y = Proven (x /=? y)
#if !MIN_VERSION_base(4, 16, 0)
type Min x y = CompareCond x y x x y
type Max x y = CompareCond x y y y x
data OrderingI m n where
LTI :: Compare m n ~ 'LT => OrderingI m n
EQI :: Compare m m ~ 'EQ => OrderingI m m
GTI :: Compare m n ~ 'GT => OrderingI m n
#endif