Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- 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 :: (Ord a, PartialOrd a) => [a] -> [a]
- newtype Minima a = Minima {}
- minima :: (Ord a, PartialOrd a) => [a] -> [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]
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 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 (<>) :: PartialOrdering -> PartialOrdering -> PartialOrdering # sconcat :: NonEmpty PartialOrdering -> PartialOrdering # stimes :: Integral b => b -> PartialOrdering -> PartialOrdering # | |
Show PartialOrdering Source # | |
Defined in Data.PartialOrd showsPrec :: Int -> PartialOrdering -> ShowS # show :: PartialOrdering -> String # showList :: [PartialOrdering] -> ShowS # | |
Eq PartialOrdering Source # | |
Defined in Data.PartialOrd (==) :: 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 #
Partial orderings
class PartialOrd a where Source #
A typeclass expressing partially ordered types: any two elements
are related by a PartialOrdering
.
Instances
PartialOrd IntSet Source # | |
PartialOrd Integer Source # | It's hard to imagine another sensible instance |
PartialOrd () Source # | |
PartialOrd Int Source # | It's hard to imagine another sensible instance |
Ord a => PartialOrd (Set a) Source # | |
Eq a => PartialOrd (Discrete a) Source # | |
Ord a => PartialOrd (FullyOrd a) Source # | |
Eq a => PartialOrd (Infix a) Source # | |
Eq a => PartialOrd (Prefix a) Source # | |
Eq a => PartialOrd (Subseq a) Source # | |
Eq a => PartialOrd (Suffix a) Source # | |
(PartialOrd a, PartialOrd b) => PartialOrd (a, b) Source # | This is equivalent to compare' (a,b) (c,d) = compare' a c <> compare' b d but may be more efficient: if compare' a1 a2 is LT' or GT' we seek less information about b1 and b2 (and this can be faster). |
(PartialOrd a, PartialOrd b, PartialOrd c) => PartialOrd (a, b, c) Source # | |
(PartialOrd a, PartialOrd b, PartialOrd c, PartialOrd d) => PartialOrd (a, b, c, d) Source # | |
(PartialOrd a, PartialOrd b, PartialOrd c, PartialOrd d, PartialOrd e) => PartialOrd (a, b, c, d, e) Source # | |
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.
Discrete | |
|
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 :: (Ord a, PartialOrd a) => [a] -> [a] Source #
Find the maxima of a list (passing it through the machinery above)
As above, but with minima
minima :: (Ord a, PartialOrd a) => [a] -> [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