{-# LANGUAGE CPP #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeOperators #-}
#if __GLASGOW_HASKELL__ >= 810
{-# LANGUAGE StandaloneKindSignatures #-}
#endif
module Data.OrdP (
OrdP (..),
) where
import Control.Applicative (Const (..))
import Data.Kind (Type)
import Data.Proxy (Proxy (..))
import Data.Semigroup ((<>))
import Data.Type.Equality ((:~:) (..), (:~~:) (..))
import GHC.Generics ((:*:) (..), (:+:) (..))
#if MIN_VERSION_base(4,18,0)
import Data.Functor.Product (Product (..))
import Data.Functor.Sum (Sum (..))
import qualified GHC.TypeLits as TL
import qualified GHC.TypeNats as TN
#endif
#if !MIN_VERSION_base(4,19,0)
import Data.Orphans ()
#endif
import qualified Type.Reflection as TR
#if __GLASGOW_HASKELL__ >= 810
import Data.Kind (Constraint)
#endif
import Data.EqP
#if __GLASGOW_HASKELL__ >= 810
type OrdP :: (k -> Type) -> Constraint
#endif
class (EqP f, forall a. Ord (f a)) => OrdP (f :: k -> Type) where
comparep :: f a -> f b -> Ordering
instance OrdP ((:~:) a) where
comparep :: forall (a :: k) (b :: k). (a :~: a) -> (a :~: b) -> Ordering
comparep a :~: a
_ a :~: b
_ = Ordering
EQ
instance OrdP ((:~~:) a) where
comparep :: forall (a :: k) (b :: k). (a :~~: a) -> (a :~~: b) -> Ordering
comparep a :~~: a
_ a :~~: b
_ = Ordering
EQ
#if MIN_VERSION_base(4,18,0)
instance (OrdP a, OrdP b) => OrdP (Sum a b) where
comparep (InL x) (InL y) = comparep x y
comparep (InL _) (InR _) = LT
comparep (InR x) (InR y) = comparep x y
comparep (InR _) (InL _) = GT
instance (OrdP a, OrdP b) => OrdP (Product a b) where
comparep (Pair x y) (Pair x' y') = comparep x x' <> comparep y y'
#endif
instance (OrdP f, OrdP g) => OrdP (f :+: g) where
comparep :: forall (a :: k) (b :: k). (:+:) f g a -> (:+:) f g b -> Ordering
comparep (L1 f a
x) (L1 f b
y) = forall k (f :: k -> *) (a :: k) (b :: k).
OrdP f =>
f a -> f b -> Ordering
comparep f a
x f b
y
comparep (L1 f a
_) (R1 g b
_) = Ordering
LT
comparep (R1 g a
x) (R1 g b
y) = forall k (f :: k -> *) (a :: k) (b :: k).
OrdP f =>
f a -> f b -> Ordering
comparep g a
x g b
y
comparep (R1 g a
_) (L1 f b
_) = Ordering
GT
instance (OrdP a, OrdP b) => OrdP (a :*: b) where
comparep :: forall (a :: k) (b :: k). (:*:) a b a -> (:*:) a b b -> Ordering
comparep (a a
x :*: b a
y) (a b
x' :*: b b
y') = forall k (f :: k -> *) (a :: k) (b :: k).
OrdP f =>
f a -> f b -> Ordering
comparep a a
x a b
x' forall a. Semigroup a => a -> a -> a
<> forall k (f :: k -> *) (a :: k) (b :: k).
OrdP f =>
f a -> f b -> Ordering
comparep b a
y b b
y'
instance OrdP TR.TypeRep where
comparep :: forall (a :: k) (b :: k). TypeRep a -> TypeRep b -> Ordering
comparep TypeRep a
x TypeRep b
y = forall a. Ord a => a -> a -> Ordering
compare (forall k (a :: k). TypeRep a -> SomeTypeRep
TR.SomeTypeRep TypeRep a
x) (forall k (a :: k). TypeRep a -> SomeTypeRep
TR.SomeTypeRep TypeRep b
y)
#if MIN_VERSION_base(4,18,0)
instance OrdP TL.SChar where
comparep x y = compare (TL.fromSChar x) (TL.fromSChar y)
instance OrdP TL.SSymbol where
comparep x y = compare (TL.fromSSymbol x) (TL.fromSSymbol y)
instance OrdP TN.SNat where
comparep x y = compare (TN.fromSNat x) (TN.fromSNat y)
#endif
instance OrdP Proxy where
comparep :: forall (a :: k) (b :: k). Proxy a -> Proxy b -> Ordering
comparep Proxy a
_ Proxy b
_ = Ordering
EQ
instance Ord a => OrdP (Const a) where
comparep :: forall (a :: k) (b :: k). Const a a -> Const a b -> Ordering
comparep (Const a
x) (Const a
y) = forall a. Ord a => a -> a -> Ordering
compare a
x a
y