| Safe Haskell | None |
|---|
Agda.Utils.PartialOrd
Contents
- data PartialOrdering
- oppPO :: PartialOrdering -> PartialOrdering
- orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering
- seqPO :: PartialOrdering -> PartialOrdering -> PartialOrdering
- fromOrdering :: Ordering -> PartialOrdering
- fromOrderings :: [Ordering] -> PartialOrdering
- toOrderings :: PartialOrdering -> [Ordering]
- type Comparable a = a -> a -> PartialOrdering
- class PartialOrd a where
- comparable :: Comparable a
- comparableOrd :: Ord a => Comparable a
- related :: PartialOrd a => a -> PartialOrdering -> a -> Bool
- newtype Pointwise a = Pointwise {
- pointwise :: a
- newtype Inclusion a = Inclusion {
- inclusion :: a
- newtype ISet = ISet {}
- prop_comparable_related :: ISet -> ISet -> Bool
- prop_oppPO :: ISet -> ISet -> Bool
- sortUniq :: [Ordering] -> [Ordering]
- prop_orPO_sound :: PartialOrdering -> PartialOrdering -> Bool
- prop_associative_orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> Bool
- prop_commutative_orPO :: PartialOrdering -> PartialOrdering -> Bool
- prop_zero_orPO :: PartialOrdering -> Bool
- property_seqPO :: ISet -> PartialOrdering -> ISet -> PartialOrdering -> ISet -> Property
- prop_seqPO :: ISet -> ISet -> ISet -> Bool
- prop_identity_seqPO :: PartialOrdering -> Bool
- prop_zero_seqPO :: PartialOrdering -> Bool
- prop_associative_seqPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> Bool
- prop_commutative_seqPO :: PartialOrdering -> PartialOrdering -> Bool
- prop_distributive_seqPO_orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> Bool
- prop_sorted_toOrderings :: PartialOrdering -> Bool
- prop_toOrderings_after_fromOrdering :: Ordering -> Bool
- prop_fromOrderings_after_toOrderings :: PartialOrdering -> Bool
- prop_toOrderings_after_fromOrderings :: NonEmptyList Ordering -> Bool
- prop_related_pair :: ISet -> ISet -> ISet -> ISet -> PartialOrdering -> Bool
- prop_comparable_PartialOrdering :: PartialOrdering -> PartialOrdering -> Bool
- tests :: IO Bool
Documentation
data PartialOrdering Source
The result of comparing two things (of the same type).
Constructors
| POLT | Less than. |
| POLE | Less or equal than. |
| POEQ | Equal |
| POGE | Greater or equal. |
| POGT | Greater than. |
| POAny | No information (incomparable). |
Instances
| Bounded PartialOrdering | |
| Enum PartialOrdering | |
| Eq PartialOrdering | |
| Show PartialOrdering | |
| Arbitrary PartialOrdering | |
| Monoid PartialOrdering | Partial ordering forms a monoid under sequencing. |
| SemiRing PartialOrdering | Partial ordering forms a semiring under supremum (disjunction) and composition (transitivity, sequencing) |
| PartialOrd PartialOrdering | Less is ``less general'' (i.e., more precise). |
oppPO :: PartialOrdering -> PartialOrderingSource
Opposites.
related a po b iff related b (oppPO po) a.
orPO :: PartialOrdering -> PartialOrdering -> PartialOrderingSource
What if either of two facts hold?
x R y || x S y
seqPO :: PartialOrdering -> PartialOrdering -> PartialOrderingSource
Chains (transitivity) x R y S z.
Also: conjunction (trying to get the best information out).
fromOrdering :: Ordering -> PartialOrderingSource
Embed Ordering.
fromOrderings :: [Ordering] -> PartialOrderingSource
Represent a non-empty disjunction of Orderings as PartialOrdering.
toOrderings :: PartialOrdering -> [Ordering]Source
A PartialOrdering information is a disjunction of Ordering informations.
Comparison with partial result
type Comparable a = a -> a -> PartialOrderingSource
class PartialOrd a whereSource
Decidable partial orderings.
Methods
Instances
| PartialOrd () | |
| PartialOrd ISet | |
| PartialOrd PartialOrdering | Less is ``less general'' (i.e., more precise). |
| PartialOrd Order | Information order: When having comparable call-matrices, we keep the lesser one. Call graph completion works toward losing the good calls, tending towards Unknown (the least information). |
| PartialOrd a => PartialOrd (Maybe a) |
Partial ordering for |
| Ord a => PartialOrd (Inclusion [a]) | Sublist for ordered lists. |
| Ord a => PartialOrd (Inclusion (Set a)) | Sets are partially ordered by inclusion. |
| PartialOrd a => PartialOrd (Pointwise [a]) | Lifting the pointwise ordering for tuples to lists. There are other partial orderings for lists, e.g., prefix, sublist, subset. |
| PartialOrd (CallMatrixAug cinfo) | |
| PartialOrd a => PartialOrd (CallMatrix' a) | |
| (PartialOrd a, PartialOrd b) => PartialOrd (Either a b) | Partial ordering for disjoint sums: |
| (PartialOrd a, PartialOrd b) => PartialOrd (a, b) | Pointwise partial ordering for tuples.
|
| (Ord i, PartialOrd a) => PartialOrd (Matrix i a) | Pointwise comparison. Only matrices with the same dimension are comparable. |
comparableOrd :: Ord a => Comparable aSource
Any Ord is a PartialOrd.
related :: PartialOrd a => a -> PartialOrdering -> a -> BoolSource
Are two elements related in a specific way?
related a o b holds iff comparable a b is contained in o.
Generic partially ordered types.
Pointwise comparison wrapper.
Inclusion comparison wrapper.
PartialOrdering is itself partially ordered!
Properties
We test our properties on integer sets ordered by inclusion.
prop_comparable_related :: ISet -> ISet -> BoolSource
Any two elements are related in the way comparable computes.
prop_oppPO :: ISet -> ISet -> BoolSource
flip comparable a b == oppPO (comparable a b)
sortUniq :: [Ordering] -> [Ordering]Source
Auxiliary function: lists to sets = sorted duplicate-free lists.
prop_associative_orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> BoolSource
orPO is associative.
prop_commutative_orPO :: PartialOrdering -> PartialOrdering -> BoolSource
orPO is communtative.
property_seqPO :: ISet -> PartialOrdering -> ISet -> PartialOrdering -> ISet -> PropertySource
Soundness of seqPO.
As QuickCheck test, this property is inefficient, see prop_seqPO.
prop_associative_seqPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> BoolSource
seqPO is associative.
prop_commutative_seqPO :: PartialOrdering -> PartialOrdering -> BoolSource
seqPO is also commutative.
prop_sorted_toOrderings :: PartialOrdering -> BoolSource
The result of toOrderings is a sorted list without duplicates.
prop_toOrderings_after_fromOrdering :: Ordering -> BoolSource
From Ordering to PartialOrdering and back is the identity.
prop_fromOrderings_after_toOrderings :: PartialOrdering -> BoolSource
From PartialOrdering to Orderings and back is the identity.
prop_toOrderings_after_fromOrderings :: NonEmptyList Ordering -> BoolSource
From Orderings to PartialOrdering and back is the identity.
Except for [LT,GT] which is a non-canonical representative of POAny.
prop_related_pair :: ISet -> ISet -> ISet -> ISet -> PartialOrdering -> BoolSource
Pairs are related iff both components are related.
prop_comparable_PartialOrdering :: PartialOrdering -> PartialOrdering -> BoolSource
Comparing PartialOrderings amounts to compare their representation as
Ordering sets.
All tests
All tests as collected by quickCheckAll.
Using quickCheckAll is convenient and superior to the manual
enumeration of tests, since the name of the property is
added automatically.