partialord-0.1.1: Data structure supporting partial orders
Safe HaskellNone
LanguageHaskell2010

Data.PartialOrd

Description

Partial orders

Synopsis

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').

Constructors

EQ' 
LT' 
GT' 
NT' 

Instances

Instances details
Monoid PartialOrdering Source # 
Instance details

Defined in Data.PartialOrd

Semigroup PartialOrdering Source #

A comparison (less than or equal, greater than or equal) holds if and only if it does on both arguments.

Instance details

Defined in Data.PartialOrd

Show PartialOrdering Source # 
Instance details

Defined in Data.PartialOrd

Eq PartialOrdering Source # 
Instance details

Defined in Data.PartialOrd

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 #

Convert from leq and geq to a partial ordering

fromCompare :: Ord a => a -> a -> PartialOrdering Source #

Lift a compare to a compare'

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.

Minimal complete definition

compare' | leq

Methods

compare' :: a -> a -> PartialOrdering Source #

leq :: a -> a -> Bool Source #

geq :: a -> a -> Bool Source #

Instances

Instances details
PartialOrd Void Source # 
Instance details

Defined in Data.PartialOrd

PartialOrd IntSet Source #

Sets of integers, with the subset partial order

Instance details

Defined in Data.PartialOrd

PartialOrd Integer Source #

It's hard to imagine another sensible instance

Instance details

Defined in Data.PartialOrd

PartialOrd () Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: () -> () -> PartialOrdering Source #

leq :: () -> () -> Bool Source #

geq :: () -> () -> Bool Source #

PartialOrd Int Source #

It's hard to imagine another sensible instance

Instance details

Defined in Data.PartialOrd

PartialOrd a => PartialOrd (Down a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: Down a -> Down a -> PartialOrdering Source #

leq :: Down a -> Down a -> Bool Source #

geq :: Down a -> Down a -> Bool Source #

Ord a => PartialOrd (Set a) Source #

Sets, with the subset partial order

Instance details

Defined in Data.PartialOrd

Methods

compare' :: Set a -> Set a -> PartialOrdering Source #

leq :: Set a -> Set a -> Bool Source #

geq :: Set a -> Set a -> Bool Source #

Eq a => PartialOrd (Discrete a) Source # 
Instance details

Defined in Data.PartialOrd

Ord a => PartialOrd (FullyOrd a) Source # 
Instance details

Defined in Data.PartialOrd

Eq a => PartialOrd (Infix a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: Infix a -> Infix a -> PartialOrdering Source #

leq :: Infix a -> Infix a -> Bool Source #

geq :: Infix a -> Infix a -> Bool Source #

Eq a => PartialOrd (Prefix a) Source # 
Instance details

Defined in Data.PartialOrd

Eq a => PartialOrd (Subseq a) Source # 
Instance details

Defined in Data.PartialOrd

Eq a => PartialOrd (Suffix a) Source # 
Instance details

Defined in Data.PartialOrd

(PartialOrd a, PartialOrd b) => PartialOrd (Disjoint a b) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: Disjoint a b -> Disjoint a b -> PartialOrdering Source #

leq :: Disjoint a b -> Disjoint a b -> Bool Source #

geq :: Disjoint a b -> Disjoint a b -> Bool Source #

(PartialOrd a, PartialOrd b) => PartialOrd (Join a b) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: Join a b -> Join a b -> PartialOrdering Source #

leq :: Join a b -> Join a b -> Bool Source #

geq :: Join a b -> Join a b -> Bool Source #

(Ord k, PartialOrd v) => PartialOrd (PointwisePositive k v) Source # 
Instance details

Defined in Data.PartialOrd

(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' a c is LT' or GT' we need less information about b and d.

Instance details

Defined in Data.PartialOrd

Methods

compare' :: (a, b) -> (a, b) -> PartialOrdering Source #

leq :: (a, b) -> (a, b) -> Bool Source #

geq :: (a, b) -> (a, b) -> Bool Source #

(PartialOrd a, PartialOrd b, PartialOrd c) => PartialOrd (a, b, c) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: (a, b, c) -> (a, b, c) -> PartialOrdering Source #

leq :: (a, b, c) -> (a, b, c) -> Bool Source #

geq :: (a, b, c) -> (a, b, c) -> Bool Source #

(PartialOrd a, PartialOrd b, PartialOrd c, PartialOrd d) => PartialOrd (a, b, c, d) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: (a, b, c, d) -> (a, b, c, d) -> PartialOrdering Source #

leq :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

geq :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(PartialOrd a, PartialOrd b, PartialOrd c, PartialOrd d, PartialOrd e) => PartialOrd (a, b, c, d, e) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: (a, b, c, d, e) -> (a, b, c, d, e) -> PartialOrdering Source #

leq :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

geq :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

comparable :: PartialOrd a => a -> a -> Bool Source #

Are they LT', EQ', GT'

Special partial orderings

newtype FullyOrd a Source #

A helper type for constructing partial orderings from total orderings (using deriving via)

Constructors

FullyOrd 

Fields

Instances

Instances details
Show a => Show (FullyOrd a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

showsPrec :: Int -> FullyOrd a -> ShowS #

show :: FullyOrd a -> String #

showList :: [FullyOrd a] -> ShowS #

Eq a => Eq (FullyOrd a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

(==) :: FullyOrd a -> FullyOrd a -> Bool #

(/=) :: FullyOrd a -> FullyOrd a -> Bool #

Ord a => Ord (FullyOrd a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare :: FullyOrd a -> FullyOrd a -> Ordering #

(<) :: FullyOrd a -> FullyOrd a -> Bool #

(<=) :: FullyOrd a -> FullyOrd a -> Bool #

(>) :: FullyOrd a -> FullyOrd a -> Bool #

(>=) :: FullyOrd a -> FullyOrd a -> Bool #

max :: FullyOrd a -> FullyOrd a -> FullyOrd a #

min :: FullyOrd a -> FullyOrd a -> FullyOrd a #

Ord a => PartialOrd (FullyOrd a) Source # 
Instance details

Defined in Data.PartialOrd

newtype Discrete a Source #

A helper type for constructing partial orderings where everything is equal or incomparable.

Constructors

Discrete 

Fields

Instances

Instances details
Show a => Show (Discrete a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

showsPrec :: Int -> Discrete a -> ShowS #

show :: Discrete a -> String #

showList :: [Discrete a] -> ShowS #

Eq a => Eq (Discrete a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

(==) :: Discrete a -> Discrete a -> Bool #

(/=) :: Discrete a -> Discrete a -> Bool #

Eq a => PartialOrd (Discrete a) Source # 
Instance details

Defined in Data.PartialOrd

Maxima and minima

newtype Maxima a Source #

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.

Constructors

Maxima 

Fields

Instances

Instances details
(Ord a, PartialOrd a) => Monoid (Maxima a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

mempty :: Maxima a #

mappend :: Maxima a -> Maxima a -> Maxima a #

mconcat :: [Maxima a] -> Maxima a #

(Ord a, PartialOrd a) => Semigroup (Maxima a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

(<>) :: Maxima a -> Maxima a -> Maxima a #

sconcat :: NonEmpty (Maxima a) -> Maxima a #

stimes :: Integral b => b -> Maxima a -> Maxima a #

maxima :: (Foldable f, Ord a, PartialOrd a) => f a -> Set a Source #

Find the maxima of a list (passing it through the machinery above)

newtype Minima a Source #

As above, but with minima

Constructors

Minima 

Fields

Instances

Instances details
(Ord a, PartialOrd a) => Monoid (Minima a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

mempty :: Minima a #

mappend :: Minima a -> Minima a -> Minima a #

mconcat :: [Minima a] -> Minima a #

(Ord a, PartialOrd a) => Semigroup (Minima a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

(<>) :: Minima a -> Minima a -> Minima a #

sconcat :: NonEmpty (Minima a) -> Minima a #

stimes :: Integral b => b -> Minima a -> Minima a #

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

newtype Infix a Source #

Lists partially ordered by infix inclusion

Constructors

Infix 

Fields

Instances

Instances details
Show a => Show (Infix a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

showsPrec :: Int -> Infix a -> ShowS #

show :: Infix a -> String #

showList :: [Infix a] -> ShowS #

Eq a => Eq (Infix a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

(==) :: Infix a -> Infix a -> Bool #

(/=) :: Infix a -> Infix a -> Bool #

Eq a => PartialOrd (Infix a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: Infix a -> Infix a -> PartialOrdering Source #

leq :: Infix a -> Infix a -> Bool Source #

geq :: Infix a -> Infix a -> Bool Source #

newtype Prefix a Source #

Lists partially ordered by prefix inclusion

Constructors

Prefix 

Fields

Instances

Instances details
Show a => Show (Prefix a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

showsPrec :: Int -> Prefix a -> ShowS #

show :: Prefix a -> String #

showList :: [Prefix a] -> ShowS #

Eq a => Eq (Prefix a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

(==) :: Prefix a -> Prefix a -> Bool #

(/=) :: Prefix a -> Prefix a -> Bool #

Eq a => PartialOrd (Prefix a) Source # 
Instance details

Defined in Data.PartialOrd

newtype Suffix a Source #

Lists partially ordered by suffix inclusion

Constructors

Suffix 

Fields

Instances

Instances details
Show a => Show (Suffix a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

showsPrec :: Int -> Suffix a -> ShowS #

show :: Suffix a -> String #

showList :: [Suffix a] -> ShowS #

Eq a => Eq (Suffix a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

(==) :: Suffix a -> Suffix a -> Bool #

(/=) :: Suffix a -> Suffix a -> Bool #

Eq a => PartialOrd (Suffix a) Source # 
Instance details

Defined in Data.PartialOrd

newtype Subseq a Source #

Lists partially ordered by the subsequence relation

Constructors

Subseq 

Fields

Instances

Instances details
Show a => Show (Subseq a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

showsPrec :: Int -> Subseq a -> ShowS #

show :: Subseq a -> String #

showList :: [Subseq a] -> ShowS #

Eq a => Eq (Subseq a) Source # 
Instance details

Defined in Data.PartialOrd

Methods

(==) :: Subseq a -> Subseq a -> Bool #

(/=) :: Subseq a -> Subseq a -> Bool #

Eq a => PartialOrd (Subseq a) Source # 
Instance details

Defined in Data.PartialOrd

Partial orders on Either

newtype Join a b Source #

All elements on the left are less than all those on the right

Constructors

Join 

Fields

Instances

Instances details
(PartialOrd a, PartialOrd b) => PartialOrd (Join a b) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: Join a b -> Join a b -> PartialOrdering Source #

leq :: Join a b -> Join a b -> Bool Source #

geq :: Join a b -> Join a b -> Bool Source #

newtype Disjoint a b Source #

All elements on the left are incomparable with all those on the right

Constructors

Disjoint 

Fields

Instances

Instances details
(PartialOrd a, PartialOrd b) => PartialOrd (Disjoint a b) Source # 
Instance details

Defined in Data.PartialOrd

Methods

compare' :: Disjoint a b -> Disjoint a b -> PartialOrdering Source #

leq :: Disjoint a b -> Disjoint a b -> Bool Source #

geq :: Disjoint a b -> Disjoint a b -> Bool 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

Instances details
(Ord k, PartialOrd v) => PartialOrd (PointwisePositive k v) Source # 
Instance details

Defined in Data.PartialOrd