{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE UndecidableInstances #-}
module Rerefined.Predicate.Relational.Internal where
import Rerefined.Predicate.Logical.Or
import GHC.TypeNats
import Data.Type.Ord ( OrdCond )
import GHC.TypeLits ( Symbol )
import Data.Kind ( Type )
type LTE = LT `Or` EQ
type NEQ = LT `Or` GT
type GTE = GT `Or` EQ
class ReifyRelOp op where
type ShowRelOp op :: Symbol
reifyRelOp :: forall a. Ord a => a -> a -> Bool
instance ReifyRelOp LT where
type ShowRelOp LT = "<"
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<)
instance ReifyRelOp LTE where
type ShowRelOp LTE = "<="
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
deriving via LTE instance ReifyRelOp (EQ `Or` LT)
instance ReifyRelOp EQ where
type ShowRelOp EQ = "=="
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
instance ReifyRelOp NEQ where
type ShowRelOp NEQ = "/="
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(/=)
deriving via NEQ instance ReifyRelOp (GT `Or` LT)
instance ReifyRelOp GTE where
type ShowRelOp GTE = ">="
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>=)
deriving via GTE instance ReifyRelOp (EQ `Or` GT)
instance ReifyRelOp GT where
type ShowRelOp GT = ">"
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>)
type WidenRelOp :: k -> Natural -> Natural -> Bool
type family WidenRelOp op n m where
WidenRelOp op n n = True
WidenRelOp LT n m = OrdCond (CmpNat n m) True True False
WidenRelOp LTE n m = OrdCond (CmpNat n m) True True False
WidenRelOp GTE n m = OrdCond (CmpNat n m) False True True
WidenRelOp GT n m = OrdCond (CmpNat n m) False True True
WidenRelOp (EQ `Or` LT) n m =
OrdCond (CmpNat n m) True True False
WidenRelOp (EQ `Or` GT) n m =
OrdCond (CmpNat n m) False True True
WidenRelOp _ _ _ = False
type NormalizeOrRelOp :: Type -> Type
type family NormalizeOrRelOp op where
NormalizeOrRelOp (EQ `Or` LT) = LTE
NormalizeOrRelOp (GT `Or` LT) = NEQ
NormalizeOrRelOp (EQ `Or` GT) = GTE