Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- class Prd a => Max a where
- maximal :: a
- class Prd a => Min a where
- minimal :: a
- type Bound a = (Min a, Max a)
- newtype Ordered a = Ordered {
- getOrdered :: a
- class Prd a where
- (~~) :: Eq a => Prd a => a -> a -> Bool
- (/~) :: Eq a => Prd a => a -> a -> Bool
- pcomparePrd :: Prd a => a -> a -> Maybe Ordering
- pcompareOrd :: Ord a => a -> a -> Maybe Ordering
- eq :: Prd a => a -> a -> Bool
- ne :: Prd a => a -> a -> Bool
- le :: Prd a => a -> a -> Bool
- ge :: Prd a => a -> a -> Bool
- lt :: Eq a => Prd a => a -> a -> Bool
- gt :: Eq a => Prd a => a -> a -> Bool
- peq :: Eq a => Prd a => a -> a -> Maybe Bool
- pne :: Eq a => Prd a => a -> a -> Maybe Bool
- ple :: Eq a => Prd a => a -> a -> Maybe Bool
- pge :: Eq a => Prd a => a -> a -> Maybe Bool
- plt :: Eq a => Prd a => a -> a -> Maybe Bool
- pgt :: Eq a => Prd a => a -> a -> Maybe Bool
- pmax :: Eq a => Prd a => a -> a -> Maybe a
- pjoin :: Eq a => Min a => Foldable f => f a -> Maybe a
- pmin :: Eq a => Prd a => a -> a -> Maybe a
- pmeet :: Eq a => Max a => Foldable f => f a -> Maybe a
- sign :: Eq a => Num a => Prd a => a -> Maybe Ordering
- zero :: Eq a => Num a => Prd a => a -> Bool
- positive :: Eq a => Num a => Prd a => a -> Bool
- negative :: Eq a => Num a => Prd a => a -> Bool
- indeterminate :: Eq a => Num a => Prd a => a -> Bool
- until :: (a -> Bool) -> (a -> a -> Bool) -> (a -> a) -> a -> a
- while :: (a -> Bool) -> (a -> a -> Bool) -> (a -> a) -> a -> a
- fixed :: (a -> a -> Bool) -> (a -> a) -> a -> a
- newtype Down a = Down a
Documentation
class Prd a => Max a where Source #
Max element of a partially ordered set.
\( \forall x: x \le maximal \)
This means that maximal
must be comparable to all values in a.
Instances
Max Bool Source # | |
Max Int Source # | |
Max Int8 Source # | |
Max Int16 Source # | |
Max Int32 Source # | |
Max Int64 Source # | |
Max Ordering Source # | |
Max Word Source # | |
Max Word8 Source # | |
Max Word16 Source # | |
Max Word32 Source # | |
Max Word64 Source # | |
Max () Source # | |
Max All Source # | |
Defined in Data.Prd.Lattice | |
Max Any Source # | |
Defined in Data.Prd.Lattice | |
Max Ulp32 Source # | |
Defined in Data.Connection.Float | |
Max a => Max (Maybe a) Source # | |
Min a => Max (Down a) Source # | |
(Prd a, Max b) => Max (Either a b) Source # | |
(Max a, Max b) => Max (a, b) Source # | |
class Prd a => Min a where Source #
Min element of a partially ordered set.
\( \forall x: x \ge minimal \)
This means that minimal
must be comparable to all values in a.
Instances
Min Bool Source # | |
Min Int Source # | |
Min Int8 Source # | |
Min Int16 Source # | |
Min Int32 Source # | |
Min Int64 Source # | |
Min Natural Source # | |
Min Ordering Source # | |
Min Word Source # | |
Min Word8 Source # | |
Min Word16 Source # | |
Min Word32 Source # | |
Min Word64 Source # | |
Min () Source # | |
Min All Source # | |
Defined in Data.Prd.Lattice | |
Min Any Source # | |
Defined in Data.Prd.Lattice | |
Min Ulp32 Source # | |
Defined in Data.Connection.Float | |
Prd a => Min (Maybe a) Source # | |
Max a => Min (Down a) Source # | |
Prd a => Min (IntMap a) Source # | |
Ord a => Min (Set a) Source # | |
(Min a, Prd b) => Min (Either a b) Source # | |
(Min a, Min b) => Min (a, b) Source # | |
(Ord k, Prd a) => Min (Map k a) Source # | |
Ordered | |
|
Instances
Functor Ordered Source # | |
Foldable Ordered Source # | |
Defined in Data.Prd fold :: Monoid m => Ordered m -> m # foldMap :: Monoid m => (a -> m) -> Ordered a -> m # foldr :: (a -> b -> b) -> b -> Ordered a -> b # foldr' :: (a -> b -> b) -> b -> Ordered a -> b # foldl :: (b -> a -> b) -> b -> Ordered a -> b # foldl' :: (b -> a -> b) -> b -> Ordered a -> b # foldr1 :: (a -> a -> a) -> Ordered a -> a # foldl1 :: (a -> a -> a) -> Ordered a -> a # elem :: Eq a => a -> Ordered a -> Bool # maximum :: Ord a => Ordered a -> a # minimum :: Ord a => Ordered a -> a # | |
Traversable Ordered Source # | |
Eq a => Eq (Ordered a) Source # | |
Data a => Data (Ordered a) Source # | |
Defined in Data.Prd gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordered a -> c (Ordered a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ordered a) # toConstr :: Ordered a -> Constr # dataTypeOf :: Ordered a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ordered a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ordered a)) # gmapT :: (forall b. Data b => b -> b) -> Ordered a -> Ordered a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordered a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordered a -> r # gmapQ :: (forall d. Data d => d -> u) -> Ordered a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordered a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordered a -> m (Ordered a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordered a -> m (Ordered a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordered a -> m (Ordered a) # | |
Ord a => Ord (Ordered a) Source # | |
Defined in Data.Prd | |
Show a => Show (Ordered a) Source # | |
Generic (Ordered a) Source # | |
Ord a => Prd (Ordered a) Source # | |
Ord a => Lattice (Ordered a) Source # | |
Generic1 Ordered Source # | |
type Rep (Ordered a) Source # | |
type Rep1 Ordered Source # | |
A partial order on the set a.
A poset relation <~
must satisfy the following three partial order axioms:
\( \forall x: x \leq x \) (reflexivity)
\( \forall a, b: (a \leq b) \Leftrightarrow \neg (b \leq a) \) (anti-symmetry)
\( \forall a, b, c: ((a \leq b) \wedge (b \leq c)) \Rightarrow (a \leq c) \) (transitivity)
If a prior equality relation is available, then a valid Prd a
instance may be derived from a semiorder relation lt
as:
x<~
y =lt
x y||
x==
y
If a is derived from a semiorder then the definition of lt
must satisfy
the three semiorder axioms:
\( \forall x, y: x \lt y \Rightarrow \neg y \lt x \) (asymmetry)
\( \forall x, y, z, w: x \lt y \wedge y \sim z \wedge z \lt w \Rightarrow x \lt w \) (2-2 chain)
\( \forall x, y, z, w: x \lt y \wedge y \lt z \wedge y \sim w \Rightarrow \neg (x \sim w \wedge z \sim w) \) (3-1 chain)
The poset axioms on <~
then follow from the first & second axioms on lt
,
however the converse is not true. While the first semiorder axiom on lt
follows, the second
and third semiorder axioms forbid partial orders of four items forming two disjoint chains:
- the second axiom forbids two chains of two items each (the (2+2) free poset)
- the third axiom forbids a three-item chain with one unrelated item
See also the wikipedia definitions of partially ordered set and semiorder.
(<~) :: a -> a -> Bool infix 4 Source #
Non-strict partial order relation on a.
<~
is reflexive, anti-symmetric, and transitive.
(>~) :: a -> a -> Bool infix 4 Source #
Converse non-strict partial order relation on a.
>~
is reflexive, anti-symmetric, and transitive.
(=~) :: Prd a => a -> a -> Bool infix 4 Source #
Equivalence relation on a.
=~
is reflexive, symmetric, and transitive.
@ x =~ y = maybe False (== EQ) (pcomparePrd x y)
If a implements Eq
then (ideally) x =~ y = x == y
.
(?~) :: Prd a => a -> a -> Bool infix 4 Source #
Comparability relation on a.
?~
is reflexive, symmetric, and transitive.
x ?~ y = maybe False (const True) (pcomparePrd x y)
If a implements Ord
then (ideally) x ?~ y = True
.
pcompare :: Eq a => a -> a -> Maybe Ordering Source #
Partial version of compare
.
Instances
eq :: Prd a => a -> a -> Bool infix 4 Source #
Prefix version of =~
.
@ eq x y = maybe False (== EQ) (pcomparePrd x y)
ne :: Prd a => a -> a -> Bool infix 4 Source #
Negation of eq
.
@ ne x y = maybe False (/= EQ) (pcomparePrd x y)
le :: Prd a => a -> a -> Bool infix 4 Source #
Prefix version of <~
.
@ le x y = maybe False (<= EQ) (pcomparePrd x y)
ge :: Prd a => a -> a -> Bool infix 4 Source #
Prefix version of >~
.
@ ge x y = maybe False (>= EQ) (pcomparePrd x y)
pmax :: Eq a => Prd a => a -> a -> Maybe a infix 4 Source #
A partial version of max
.
Default instance returns the connr argument in the case of equality.
pmin :: Eq a => Prd a => a -> a -> Maybe a infix 4 Source #
A partial version of min
.
Default instance returns the connr argument in the case of equality.
fixed :: (a -> a -> Bool) -> (a -> a) -> a -> a Source #
Greatest (resp. least) fixed point of a monitone (resp. antitone) function.
Does not check that the function is monitone (resp. antitone).
See also http://en.wikipedia.org/wiki/Kleene_fixed-point_theorem.
The Down
type allows you to reverse sort order conveniently. A value of type
contains a value of type Down
aa
(represented as
).
If Down
aa
has an
instance associated with it then comparing two
values thus wrapped will give you the opposite of their normal sort order.
This is particularly useful when sorting in generalised list comprehensions,
as in: Ord
then sortWith by
Down
x
Since: base-4.6.0.0
Down a |
Instances
Monad Down | Since: base-4.11.0.0 |
Functor Down | Since: base-4.11.0.0 |
Applicative Down | Since: base-4.11.0.0 |
Foldable Down | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Down m -> m # foldMap :: Monoid m => (a -> m) -> Down a -> m # foldr :: (a -> b -> b) -> b -> Down a -> b # foldr' :: (a -> b -> b) -> b -> Down a -> b # foldl :: (b -> a -> b) -> b -> Down a -> b # foldl' :: (b -> a -> b) -> b -> Down a -> b # foldr1 :: (a -> a -> a) -> Down a -> a # foldl1 :: (a -> a -> a) -> Down a -> a # elem :: Eq a => a -> Down a -> Bool # maximum :: Ord a => Down a -> a # | |
Traversable Down | Since: base-4.12.0.0 |
Eq1 Down | Since: base-4.12.0.0 |
Ord1 Down | Since: base-4.12.0.0 |
Defined in Data.Functor.Classes | |
Read1 Down | Since: base-4.12.0.0 |
Defined in Data.Functor.Classes | |
Show1 Down | Since: base-4.12.0.0 |
Eq a => Eq (Down a) | Since: base-4.6.0.0 |
Data a => Data (Down a) | Since: base-4.12.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Down a -> c (Down a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Down a) # toConstr :: Down a -> Constr # dataTypeOf :: Down a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Down a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Down a)) # gmapT :: (forall b. Data b => b -> b) -> Down a -> Down a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Down a -> r # gmapQ :: (forall d. Data d => d -> u) -> Down a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Down a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Down a -> m (Down a) # | |
Num a => Num (Down a) | Since: base-4.11.0.0 |
Ord a => Ord (Down a) | Since: base-4.6.0.0 |
Read a => Read (Down a) | Since: base-4.7.0.0 |
Show a => Show (Down a) | Since: base-4.7.0.0 |
Generic (Down a) | |
Semigroup a => Semigroup (Down a) | Since: base-4.11.0.0 |
Monoid a => Monoid (Down a) | Since: base-4.11.0.0 |
Min a => Max (Down a) Source # | |
Max a => Min (Down a) Source # | |
Prd a => Prd (Down a) Source # | |
Lattice a => Lattice (Down a) Source # | |
Generic1 Down | |
type Rep (Down a) | Since: base-4.12.0.0 |
Defined in GHC.Generics | |
type Rep (Down a) Source # | |
Defined in Data.Connection.Yoneda | |
type Rep1 Down | Since: base-4.12.0.0 |
Defined in GHC.Generics |