{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE UndecidableInstances #-}
module Rerefined.Predicate.Relational.Internal where
import GHC.TypeNats
import Data.Type.Ord ( OrdCond )
import GHC.TypeLits ( Symbol )
data RelOp
= RelOpEQ
| RelOpNEQ
| RelOpLT
| RelOpLTE
| RelOpGTE
| RelOpGT
class ReifyRelOp (op :: RelOp) where
type ShowRelOp op :: Symbol
reifyRelOp :: forall a. Ord a => a -> a -> Bool
instance ReifyRelOp RelOpLT where
type ShowRelOp RelOpLT = "<"
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<)
instance ReifyRelOp RelOpLTE where
type ShowRelOp RelOpLTE = "<="
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
instance ReifyRelOp RelOpEQ where
type ShowRelOp RelOpEQ = "=="
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
instance ReifyRelOp RelOpNEQ where
type ShowRelOp RelOpNEQ = "/="
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(/=)
instance ReifyRelOp RelOpGTE where
type ShowRelOp RelOpGTE = ">="
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>=)
instance ReifyRelOp RelOpGT where
type ShowRelOp RelOpGT = ">"
reifyRelOp :: forall a. Ord a => a -> a -> Bool
reifyRelOp = a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(>)
type WidenRelOp :: RelOp -> Natural -> Natural -> Bool
type family WidenRelOp op n m where
WidenRelOp op n n = True
WidenRelOp RelOpLT n m = OrdCond (CmpNat n m) True True False
WidenRelOp RelOpLTE n m = OrdCond (CmpNat n m) True True False
WidenRelOp RelOpGTE n m = OrdCond (CmpNat n m) False True True
WidenRelOp RelOpGT n m = OrdCond (CmpNat n m) False True True
WidenRelOp op n m = False
type FlipRelOp :: RelOp -> RelOp
type family FlipRelOp op where
FlipRelOp RelOpEQ = RelOpNEQ
FlipRelOp RelOpNEQ = RelOpEQ
FlipRelOp RelOpLT = RelOpGTE
FlipRelOp RelOpLTE = RelOpGT
FlipRelOp RelOpGTE = RelOpLT
FlipRelOp RelOpGT = RelOpLTE