Copyright | (c) L. S. Leary 2025 |
---|---|
Safe Haskell | None |
Language | GHC2021 |
Data.Hetero.Ord
Contents
Description
Heterogeneous comparison with evidence capture.
Synopsis
- data HetOrdering (r :: RoleKind) (a :: k) (b :: k)
- mapHO :: forall {k1} {k2} (r :: RoleKind) (a :: k1) (b :: k1) (s :: RoleKind) (c :: k2) (d :: k2). (AtLeast r a b -> AtLeast s c d) -> HetOrdering r a b -> HetOrdering s c d
- bindHO :: forall {k1} {k2} (r :: RoleKind) (a :: k1) (b :: k1) (s :: RoleKind) (c :: k2) (d :: k2). HetOrdering r a b -> (AtLeast r a b -> HetOrdering s c d) -> HetOrdering s c d
- class HetEq f => HetOrd (f :: k -> Type) where
- hcompare :: forall (a :: k) (b :: k). f a -> f b -> HetOrdering (Strength f) a b
- type HetOrd' (f :: k -> Type) = (KnownRole (Strength f), HetOrd f)
- defaultHEq :: forall {k} f (a :: k) (b :: k). HetOrd f => f a -> f b -> Maybe (AtLeast (Strength f) a b)
- hcompareVia :: forall {k} f y (a :: k) (b :: k). (HetEq f, Ord y) => (forall (x :: k). f x -> y) -> f a -> f b -> HetOrdering (Strength f) a b
HetOrdering
data HetOrdering (r :: RoleKind) (a :: k) (b :: k) Source #
Ordering
with captured evidence.
Arguments
:: forall {k1} {k2} (r :: RoleKind) (a :: k1) (b :: k1) (s :: RoleKind) (c :: k2) (d :: k2). (AtLeast r a b -> AtLeast s c d) | |
-> HetOrdering r a b | |
-> HetOrdering s c d |
Map over the contained
.AtLeast
r a b
Arguments
:: forall {k1} {k2} (r :: RoleKind) (a :: k1) (b :: k1) (s :: RoleKind) (c :: k2) (d :: k2). HetOrdering r a b | |
-> (AtLeast r a b -> HetOrdering s c d) | |
-> HetOrdering s c d |
Bind the contained
.AtLeast
r a b
HetOrd
class HetEq f => HetOrd (f :: k -> Type) where Source #
Heterogeneous comparison with evidence capture of type equivalence.
Methods
hcompare :: forall (a :: k) (b :: k). f a -> f b -> HetOrdering (Strength f) a b Source #
Compare an f a
and an f b
, opportunistically capturing the strongest
type-equivalence evidence we can given the arguments.
Instances
defaultHEq :: forall {k} f (a :: k) (b :: k). HetOrd f => f a -> f b -> Maybe (AtLeast (Strength f) a b) Source #
Arguments
:: forall {k} f y (a :: k) (b :: k). (HetEq f, Ord y) | |
=> (forall (x :: k). f x -> y) | |
-> f a | |
-> f b | |
-> HetOrdering (Strength f) a b |