Safe Haskell | None |
---|---|
Language | Haskell98 |
- data PartialOrdering
- leqPO :: PartialOrdering -> PartialOrdering -> Bool
- 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_leqPO_sound :: PartialOrdering -> PartialOrdering -> Bool
- prop_orPO_sound :: PartialOrdering -> PartialOrdering -> Bool
- prop_associative_orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> Bool
- prop_commutative_orPO :: PartialOrdering -> PartialOrdering -> Bool
- prop_idempotent_orPO :: 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_idempotent_seqPO :: 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).
POLT | Less than. |
POLE | Less or equal than. |
POEQ | Equal |
POGE | Greater or equal. |
POGT | Greater than. |
POAny | No information (incomparable). |
Bounded PartialOrdering Source | |
Enum PartialOrdering Source | |
Eq PartialOrdering Source | |
Show PartialOrdering Source | |
Monoid PartialOrdering Source | Partial ordering forms a monoid under sequencing. |
Arbitrary PartialOrdering Source | |
PartialOrd PartialOrdering Source | Less is ``less general'' (i.e., more precise). |
leqPO :: PartialOrdering -> PartialOrdering -> Bool Source
Comparing the information content of two elements of
PartialOrdering
. More precise information is smaller.
Includes equality: x
.leqPO
x == True
oppPO :: PartialOrdering -> PartialOrdering Source
Opposites.
related a po b
iff related b (oppPO po) a
.
orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering Source
Combining two pieces of information (picking the least information). Used for the dominance ordering on tuples.
orPO
is associative, commutative, and idempotent.
orPO
has dominant element POAny
, but no neutral element.
seqPO :: PartialOrdering -> PartialOrdering -> PartialOrdering Source
Chains (transitivity) x R y S z
.
seqPO
is associative, commutative, and idempotent.
seqPO
has dominant element POAny
and neutral element (unit) POEQ
.
fromOrdering :: Ordering -> PartialOrdering Source
Embed Ordering
.
fromOrderings :: [Ordering] -> PartialOrdering Source
Represent a non-empty disjunction of Ordering
s as PartialOrdering
.
toOrderings :: PartialOrdering -> [Ordering] Source
A PartialOrdering
information is a disjunction of Ordering
informations.
Comparison with partial result
type Comparable a = a -> a -> PartialOrdering Source
class PartialOrd a where Source
Decidable partial orderings.
comparable :: Comparable a Source
PartialOrd Int Source | |
PartialOrd Integer Source | |
PartialOrd () Source | |
PartialOrd ISet Source | |
PartialOrd PartialOrdering Source | Less is ``less general'' (i.e., more precise). |
PartialOrd Order Source | 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) Source |
Partial ordering for |
Ord a => PartialOrd (Inclusion [a]) Source | Sublist for ordered lists. |
Ord a => PartialOrd (Inclusion (Set a)) Source | Sets are partially ordered by inclusion. |
PartialOrd a => PartialOrd (Pointwise [a]) Source | The pointwise ordering for lists of the same length. There are other partial orderings for lists, e.g., prefix, sublist, subset, lexicographic, simultaneous order. |
PartialOrd (CallMatrixAug cinfo) Source | |
PartialOrd a => PartialOrd (CallMatrix' a) Source | |
(PartialOrd a, PartialOrd b) => PartialOrd (Either a b) Source | Partial ordering for disjoint sums: |
(PartialOrd a, PartialOrd b) => PartialOrd (a, b) Source | Pointwise partial ordering for tuples.
|
(Ord i, PartialOrd a) => PartialOrd (Matrix i a) Source | Pointwise comparison. Only matrices with the same dimension are comparable. |
comparableOrd :: Ord a => Comparable a Source
Any Ord
is a PartialOrd
.
related :: PartialOrd a => a -> PartialOrdering -> a -> Bool Source
Are two elements related in a specific way?
related a o b
holds iff comparable a b
is contained in o
.
Totally ordered types.
Generic partially ordered types.
Pointwise comparison wrapper.
Functor Pointwise Source | |
Eq a => Eq (Pointwise a) Source | |
Show a => Show (Pointwise a) Source | |
PartialOrd a => PartialOrd (Pointwise [a]) Source | The pointwise ordering for lists of the same length. There are other partial orderings for lists, e.g., prefix, sublist, subset, lexicographic, simultaneous order. |
Inclusion comparison wrapper.
PartialOrdering is itself partially ordered!
Properties
We test our properties on integer sets ordered by inclusion.
prop_comparable_related :: ISet -> ISet -> Bool Source
Any two elements are related
in the way comparable
computes.
prop_oppPO :: ISet -> ISet -> Bool Source
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 -> Bool Source
orPO
is associative.
prop_commutative_orPO :: PartialOrdering -> PartialOrdering -> Bool Source
orPO
is commutative.
prop_idempotent_orPO :: PartialOrdering -> Bool Source
orPO
is idempotent.
property_seqPO :: ISet -> PartialOrdering -> ISet -> PartialOrdering -> ISet -> Property Source
Soundness of seqPO
.
As QuickCheck test, this property is inefficient, see prop_seqPO
.
prop_seqPO :: ISet -> ISet -> ISet -> Bool Source
A more efficient way of stating soundness of seqPO
.
prop_associative_seqPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> Bool Source
seqPO
is associative.
prop_commutative_seqPO :: PartialOrdering -> PartialOrdering -> Bool Source
seqPO
is also commutative.
prop_idempotent_seqPO :: PartialOrdering -> Bool Source
seqPO
is idempotent.
prop_distributive_seqPO_orPO :: PartialOrdering -> PartialOrdering -> PartialOrdering -> Bool Source
prop_sorted_toOrderings :: PartialOrdering -> Bool Source
The result of toOrderings
is a sorted list without duplicates.
prop_toOrderings_after_fromOrdering :: Ordering -> Bool Source
From Ordering
to PartialOrdering
and back is the identity.
prop_fromOrderings_after_toOrderings :: PartialOrdering -> Bool Source
From PartialOrdering
to Orderings
and back is the identity.
prop_toOrderings_after_fromOrderings :: NonEmptyList Ordering -> Bool Source
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 -> Bool Source
Pairs are related iff both components are related.
prop_comparable_PartialOrdering :: PartialOrdering -> PartialOrdering -> Bool Source
Comparing PartialOrdering
s amounts to compare their representation as
Ordering
sets.