{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE UndecidableInstances #-}
module Rerefined.Predicate.Relational.Internal where
import Data.Typeable ( Typeable )
import GHC.TypeNats
import Data.Type.Ord ( OrdCond )
data RelOp
= LT'
| LTE
| EQ'
| NEQ
| GTE
| GT'
class Typeable op => ReifyRelOp (op :: RelOp) where
reifyRelOp :: forall a. (Num a, Ord a) => a -> a -> Bool
reifyRelOpPretty :: String
instance ReifyRelOp LT' where
reifyRelOp :: forall a. (Num a, Ord a) => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<)
reifyRelOpPretty :: String
reifyRelOpPretty = String
"<"
instance ReifyRelOp LTE where
reifyRelOp :: forall a. (Num a, Ord a) => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
reifyRelOpPretty :: String
reifyRelOpPretty = String
"<="
instance ReifyRelOp EQ' where
reifyRelOp :: forall a. (Num a, Ord a) => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
reifyRelOpPretty :: String
reifyRelOpPretty = String
"=="
instance ReifyRelOp NEQ where
reifyRelOp :: forall a. (Num a, Ord a) => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(/=)
reifyRelOpPretty :: String
reifyRelOpPretty = String
"/="
instance ReifyRelOp GTE where
reifyRelOp :: forall a. (Num a, Ord a) => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>=)
reifyRelOpPretty :: String
reifyRelOpPretty = String
">="
instance ReifyRelOp GT' where
reifyRelOp :: forall a. (Num a, Ord a) => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>)
reifyRelOpPretty :: String
reifyRelOpPretty = String
">"
type family WidenRelOp (op :: RelOp) (n :: Natural) (m :: Natural) 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 _ _ _ = False