| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.PartialOrd
Description
Partial orders
Synopsis
- data PartialOrdering
- fromOrd :: Ordering -> PartialOrdering
- toMaybeOrd :: PartialOrdering -> Maybe Ordering
- fromMaybeOrd :: Maybe Ordering -> PartialOrdering
- fromLeqGeq :: Bool -> Bool -> PartialOrdering
- fromCompare :: Ord a => a -> a -> PartialOrdering
- isLeq :: PartialOrdering -> Bool
- isGeq :: PartialOrdering -> Bool
- reversePartial :: PartialOrdering -> PartialOrdering
- class PartialOrd a where
- comparable :: PartialOrd a => a -> a -> Bool
- newtype FullyOrd a = FullyOrd {
- getOrd :: a
- newtype Discrete a = Discrete {
- getDiscrete :: a
- newtype Maxima a = Maxima {}
- maxima :: (Foldable f, Ord a, PartialOrd a) => f a -> Set a
- newtype Minima a = Minima {}
- minima :: (Foldable f, Ord a, PartialOrd a) => f a -> Set a
- newtype Infix a = Infix {
- unInfix :: [a]
- newtype Prefix a = Prefix {
- unPrefix :: [a]
- newtype Suffix a = Suffix {
- unSuffix :: [a]
- newtype Subseq a = Subseq {
- unSubseq :: [a]
- newtype Join a b = Join {}
- newtype Disjoint a b = Disjoint {
- getDisjoint :: Either a b
- newtype PointwisePositive k v = PointwisePositive {
- getPointwisePositive :: Map k v
Comparisons in partial orders
data PartialOrdering Source #
A data type representing relationships between two objects in a poset: they can be related (by EQ', LT' or GT'; like EQ, LT or GT), or unrelated (NT').
Instances
| Monoid PartialOrdering Source # | |
Defined in Data.PartialOrd Methods mappend :: PartialOrdering -> PartialOrdering -> PartialOrdering # mconcat :: [PartialOrdering] -> PartialOrdering # | |
| Semigroup PartialOrdering Source # | A comparison (less than or equal, greater than or equal) holds if and only if it does on both arguments. |
Defined in Data.PartialOrd Methods (<>) :: PartialOrdering -> PartialOrdering -> PartialOrdering # sconcat :: NonEmpty PartialOrdering -> PartialOrdering # stimes :: Integral b => b -> PartialOrdering -> PartialOrdering # | |
| Show PartialOrdering Source # | |
Defined in Data.PartialOrd Methods showsPrec :: Int -> PartialOrdering -> ShowS # show :: PartialOrdering -> String # showList :: [PartialOrdering] -> ShowS # | |
| Eq PartialOrdering Source # | |
Defined in Data.PartialOrd Methods (==) :: PartialOrdering -> PartialOrdering -> Bool # (/=) :: PartialOrdering -> PartialOrdering -> Bool # | |
fromOrd :: Ordering -> PartialOrdering Source #
Convert an ordering into a partial ordering
toMaybeOrd :: PartialOrdering -> Maybe Ordering Source #
Convert a partial ordering to an ordering
fromMaybeOrd :: Maybe Ordering -> PartialOrdering Source #
Convert an ordering into a partial ordering
fromLeqGeq :: Bool -> Bool -> PartialOrdering Source #
fromCompare :: Ord a => a -> a -> PartialOrdering Source #
isLeq :: PartialOrdering -> Bool Source #
isGeq :: PartialOrdering -> Bool Source #
Partial orderings
class PartialOrd a where Source #
A typeclass expressing partially ordered types: any two elements
are related by a PartialOrdering.
In some cases leq can be quicker to run than compare. The
provided implementations such as `PartialOrd (a,b)` take advantage
of this.
Instances
comparable :: PartialOrd a => a -> a -> Bool Source #
Are they LT', EQ', GT'
Special partial orderings
A helper type for constructing partial orderings from total orderings (using deriving via)
Instances
| Show a => Show (FullyOrd a) Source # | |
| Eq a => Eq (FullyOrd a) Source # | |
| Ord a => Ord (FullyOrd a) Source # | |
| Ord a => PartialOrd (FullyOrd a) Source # | |
A helper type for constructing partial orderings where everything is equal or incomparable.
Constructors
| Discrete | |
Fields
| |
Maxima and minima
Sets of incomparable elements, with a monoidal structure obtained by taking the maximal ones.
Unfortunately, we need a full ordering for these to work (since they use sets), though we don't assume this ordering has any compatibility with the partial order. The monoid structures are most efficient with pre-reduced sets as the left-hand argument.
maxima :: (Foldable f, Ord a, PartialOrd a) => f a -> Set a Source #
Find the maxima of a list (passing it through the machinery above)
As above, but with minima
minima :: (Foldable f, Ord a, PartialOrd a) => f a -> Set a Source #
Find the minima of a list (passing it through the machinery above)
Partial orders on lists
Lists partially ordered by infix inclusion
Lists partially ordered by prefix inclusion
Lists partially ordered by suffix inclusion
Lists partially ordered by the subsequence relation
Partial orders on Either
All elements on the left are less than all those on the right
Instances
| (PartialOrd a, PartialOrd b) => PartialOrd (Join a b) Source # | |
All elements on the left are incomparable with all those on the right
Constructors
| Disjoint | |
Fields
| |
Instances
| (PartialOrd a, PartialOrd b) => PartialOrd (Disjoint a b) Source # | |
Partial orders on Map
newtype PointwisePositive k v Source #
Maps partially ordered for pointwise comparison, where empty values are considered minimal.
This is commonplace, but by no means the only conceivably ordering on Map.
Constructors
| PointwisePositive | |
Fields
| |
Instances
| (Ord k, PartialOrd v) => PartialOrd (PointwisePositive k v) Source # | |
Defined in Data.PartialOrd Methods compare' :: PointwisePositive k v -> PointwisePositive k v -> PartialOrdering Source # leq :: PointwisePositive k v -> PointwisePositive k v -> Bool Source # geq :: PointwisePositive k v -> PointwisePositive k v -> Bool Source # | |