some-1.0.5: Existential type: Some
Safe HaskellSafe
LanguageHaskell2010

Data.OrdP

Synopsis

Documentation

class (EqP f, forall a. Ord (f a)) => OrdP (f :: k -> Type) where Source #

Heterogenous lifted total order.

This class is stronger version of Ord1 from base

class (forall a. Ord a => Ord (f a)) => Ord1 f where
    liftCompare :: (a -> b -> Ordering) -> f a -> f b -> Ordering

Since: 1.0.5

Methods

comparep :: f a -> f b -> Ordering Source #

Instances

Instances details
OrdP (Proxy :: k -> Type) Source # 
Instance details

Defined in Data.OrdP

Methods

comparep :: forall (a :: k0) (b :: k0). Proxy a -> Proxy b -> Ordering Source #

OrdP (TypeRep :: k -> Type) Source # 
Instance details

Defined in Data.OrdP

Methods

comparep :: forall (a :: k0) (b :: k0). TypeRep a -> TypeRep b -> Ordering Source #

Ord a => OrdP (Const a :: k -> Type) Source # 
Instance details

Defined in Data.OrdP

Methods

comparep :: forall (a0 :: k0) (b :: k0). Const a a0 -> Const a b -> Ordering Source #

OrdP ((:~:) a :: k -> Type) Source # 
Instance details

Defined in Data.OrdP

Methods

comparep :: forall (a0 :: k0) (b :: k0). (a :~: a0) -> (a :~: b) -> Ordering Source #

OrdP ((:~~:) a :: k -> Type) Source # 
Instance details

Defined in Data.OrdP

Methods

comparep :: forall (a0 :: k0) (b :: k0). (a :~~: a0) -> (a :~~: b) -> Ordering Source #

(OrdP a, OrdP b) => OrdP (a :*: b :: k -> Type) Source # 
Instance details

Defined in Data.OrdP

Methods

comparep :: forall (a0 :: k0) (b0 :: k0). (a :*: b) a0 -> (a :*: b) b0 -> Ordering Source #

(OrdP f, OrdP g) => OrdP (f :+: g :: k -> Type) Source # 
Instance details

Defined in Data.OrdP

Methods

comparep :: forall (a :: k0) (b :: k0). (f :+: g) a -> (f :+: g) b -> Ordering Source #