connections-0.0.2: Partial orders & Galois connections.

Safe HaskellSafe
LanguageHaskell2010

Data.Prd

Synopsis

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.

Methods

maximal :: a Source #

Instances
Max Bool Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Bool Source #

Max Int Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Int Source #

Max Int8 Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Int8 Source #

Max Int16 Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Int16 Source #

Max Int32 Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Int32 Source #

Max Int64 Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Int64 Source #

Max Ordering Source # 
Instance details

Defined in Data.Prd

Max Word Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Word Source #

Max Word8 Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Word8 Source #

Max Word16 Source # 
Instance details

Defined in Data.Prd

Max Word32 Source # 
Instance details

Defined in Data.Prd

Max Word64 Source # 
Instance details

Defined in Data.Prd

Max () Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: () Source #

Max All Source # 
Instance details

Defined in Data.Prd.Lattice

Methods

maximal :: All Source #

Max Any Source # 
Instance details

Defined in Data.Prd.Lattice

Methods

maximal :: Any Source #

Max Ulp32 Source # 
Instance details

Defined in Data.Connection.Float

Methods

maximal :: Ulp32 Source #

Max a => Max (Maybe a) Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Maybe a Source #

Min a => Max (Down a) Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Down a Source #

(Prd a, Max b) => Max (Either a b) Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Either a b Source #

(Max a, Max b) => Max (a, b) Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: (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.

Methods

minimal :: a Source #

Instances
Min Bool Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Bool Source #

Min Int Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Int Source #

Min Int8 Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Int8 Source #

Min Int16 Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Int16 Source #

Min Int32 Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Int32 Source #

Min Int64 Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Int64 Source #

Min Natural Source # 
Instance details

Defined in Data.Prd

Min Ordering Source # 
Instance details

Defined in Data.Prd

Min Word Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Word Source #

Min Word8 Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Word8 Source #

Min Word16 Source # 
Instance details

Defined in Data.Prd

Min Word32 Source # 
Instance details

Defined in Data.Prd

Min Word64 Source # 
Instance details

Defined in Data.Prd

Min () Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: () Source #

Min All Source # 
Instance details

Defined in Data.Prd.Lattice

Methods

minimal :: All Source #

Min Any Source # 
Instance details

Defined in Data.Prd.Lattice

Methods

minimal :: Any Source #

Min Ulp32 Source # 
Instance details

Defined in Data.Connection.Float

Methods

minimal :: Ulp32 Source #

Prd a => Min (Maybe a) Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Maybe a Source #

Max a => Min (Down a) Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Down a Source #

Prd a => Min (IntMap a) Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: IntMap a Source #

Ord a => Min (Set a) Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Set a Source #

(Min a, Prd b) => Min (Either a b) Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Either a b Source #

(Min a, Min b) => Min (a, b) Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: (a, b) Source #

(Ord k, Prd a) => Min (Map k a) Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Map k a Source #

type Bound a = (Min a, Max a) Source #

newtype Ordered a Source #

Constructors

Ordered 

Fields

Instances
Functor Ordered Source # 
Instance details

Defined in Data.Prd

Methods

fmap :: (a -> b) -> Ordered a -> Ordered b #

(<$) :: a -> Ordered b -> Ordered a #

Foldable Ordered Source # 
Instance details

Defined in Data.Prd

Methods

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 #

toList :: Ordered a -> [a] #

null :: Ordered a -> Bool #

length :: Ordered a -> Int #

elem :: Eq a => a -> Ordered a -> Bool #

maximum :: Ord a => Ordered a -> a #

minimum :: Ord a => Ordered a -> a #

sum :: Num a => Ordered a -> a #

product :: Num a => Ordered a -> a #

Traversable Ordered Source # 
Instance details

Defined in Data.Prd

Methods

traverse :: Applicative f => (a -> f b) -> Ordered a -> f (Ordered b) #

sequenceA :: Applicative f => Ordered (f a) -> f (Ordered a) #

mapM :: Monad m => (a -> m b) -> Ordered a -> m (Ordered b) #

sequence :: Monad m => Ordered (m a) -> m (Ordered a) #

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

Defined in Data.Prd

Methods

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

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

Data a => Data (Ordered a) Source # 
Instance details

Defined in Data.Prd

Methods

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 # 
Instance details

Defined in Data.Prd

Methods

compare :: Ordered a -> Ordered a -> Ordering #

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

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

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

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

max :: Ordered a -> Ordered a -> Ordered a #

min :: Ordered a -> Ordered a -> Ordered a #

Show a => Show (Ordered a) Source # 
Instance details

Defined in Data.Prd

Methods

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

show :: Ordered a -> String #

showList :: [Ordered a] -> ShowS #

Generic (Ordered a) Source # 
Instance details

Defined in Data.Prd

Associated Types

type Rep (Ordered a) :: Type -> Type #

Methods

from :: Ordered a -> Rep (Ordered a) x #

to :: Rep (Ordered a) x -> Ordered a #

Ord a => Prd (Ordered a) Source # 
Instance details

Defined in Data.Prd

Ord a => Lattice (Ordered a) Source # 
Instance details

Defined in Data.Prd.Lattice

Generic1 Ordered Source # 
Instance details

Defined in Data.Prd

Associated Types

type Rep1 Ordered :: k -> Type #

Methods

from1 :: Ordered a -> Rep1 Ordered a #

to1 :: Rep1 Ordered a -> Ordered a #

type Rep (Ordered a) Source # 
Instance details

Defined in Data.Prd

type Rep (Ordered a) = D1 (MetaData "Ordered" "Data.Prd" "connections-0.0.2-3bGTwkYWIphGQUrhB8xvK6" True) (C1 (MetaCons "Ordered" PrefixI True) (S1 (MetaSel (Just "getOrdered") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Ordered Source # 
Instance details

Defined in Data.Prd

type Rep1 Ordered = D1 (MetaData "Ordered" "Data.Prd" "connections-0.0.2-3bGTwkYWIphGQUrhB8xvK6" True) (C1 (MetaCons "Ordered" PrefixI True) (S1 (MetaSel (Just "getOrdered") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

class Prd a where 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.

Minimal complete definition

(<~) | (>~)

Methods

(<~) :: 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
Prd Bool Source # 
Instance details

Defined in Data.Prd

Prd Char Source # 
Instance details

Defined in Data.Prd

Prd Double Source # 
Instance details

Defined in Data.Prd

Prd Float Source # 
Instance details

Defined in Data.Prd

Prd Int Source # 
Instance details

Defined in Data.Prd

Prd Int8 Source # 
Instance details

Defined in Data.Prd

Prd Int16 Source # 
Instance details

Defined in Data.Prd

Prd Int32 Source # 
Instance details

Defined in Data.Prd

Prd Int64 Source # 
Instance details

Defined in Data.Prd

Prd Integer Source # 
Instance details

Defined in Data.Prd

Prd Natural Source # 
Instance details

Defined in Data.Prd

Prd Ordering Source # 
Instance details

Defined in Data.Prd

Prd Word Source # 
Instance details

Defined in Data.Prd

Prd Word8 Source # 
Instance details

Defined in Data.Prd

Prd Word16 Source # 
Instance details

Defined in Data.Prd

Prd Word32 Source # 
Instance details

Defined in Data.Prd

Prd Word64 Source # 
Instance details

Defined in Data.Prd

Prd () Source # 
Instance details

Defined in Data.Prd

Methods

(<~) :: () -> () -> Bool Source #

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

(=~) :: () -> () -> Bool Source #

(?~) :: () -> () -> Bool Source #

pcompare :: () -> () -> Maybe Ordering Source #

Prd All Source # 
Instance details

Defined in Data.Prd

Prd Any Source # 
Instance details

Defined in Data.Prd

Prd IntSet Source # 
Instance details

Defined in Data.Prd

Prd Ulp32 Source # 
Instance details

Defined in Data.Connection.Float

Prd a => Prd [a] Source # 
Instance details

Defined in Data.Prd

Methods

(<~) :: [a] -> [a] -> Bool Source #

(>~) :: [a] -> [a] -> Bool Source #

(=~) :: [a] -> [a] -> Bool Source #

(?~) :: [a] -> [a] -> Bool Source #

pcompare :: [a] -> [a] -> Maybe Ordering Source #

Prd a => Prd (Maybe a) Source # 
Instance details

Defined in Data.Prd

Methods

(<~) :: Maybe a -> Maybe a -> Bool Source #

(>~) :: Maybe a -> Maybe a -> Bool Source #

(=~) :: Maybe a -> Maybe a -> Bool Source #

(?~) :: Maybe a -> Maybe a -> Bool Source #

pcompare :: Maybe a -> Maybe a -> Maybe Ordering Source #

(Prd a, Integral a) => Prd (Ratio a) Source # 
Instance details

Defined in Data.Prd

Methods

(<~) :: Ratio a -> Ratio a -> Bool Source #

(>~) :: Ratio a -> Ratio a -> Bool Source #

(=~) :: Ratio a -> Ratio a -> Bool Source #

(?~) :: Ratio a -> Ratio a -> Bool Source #

pcompare :: Ratio a -> Ratio a -> Maybe Ordering Source #

Prd a => Prd (Dual a) Source # 
Instance details

Defined in Data.Prd

Methods

(<~) :: Dual a -> Dual a -> Bool Source #

(>~) :: Dual a -> Dual a -> Bool Source #

(=~) :: Dual a -> Dual a -> Bool Source #

(?~) :: Dual a -> Dual a -> Bool Source #

pcompare :: Dual a -> Dual a -> Maybe Ordering Source #

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

Defined in Data.Prd

Methods

(<~) :: Down a -> Down a -> Bool Source #

(>~) :: Down a -> Down a -> Bool Source #

(=~) :: Down a -> Down a -> Bool Source #

(?~) :: Down a -> Down a -> Bool Source #

pcompare :: Down a -> Down a -> Maybe Ordering Source #

Prd a => Prd (NonEmpty a) Source # 
Instance details

Defined in Data.Prd

Prd a => Prd (IntMap a) Source # 
Instance details

Defined in Data.Prd

Ord a => Prd (Set a) Source # 
Instance details

Defined in Data.Prd

Methods

(<~) :: Set a -> Set a -> Bool Source #

(>~) :: Set a -> Set a -> Bool Source #

(=~) :: Set a -> Set a -> Bool Source #

(?~) :: Set a -> Set a -> Bool Source #

pcompare :: Set a -> Set a -> Maybe Ordering Source #

Ord a => Prd (Ordered a) Source # 
Instance details

Defined in Data.Prd

(Eq a, Lattice a) => Prd (Join a) Source # 
Instance details

Defined in Data.Prd.Lattice

Methods

(<~) :: Join a -> Join a -> Bool Source #

(>~) :: Join a -> Join a -> Bool Source #

(=~) :: Join a -> Join a -> Bool Source #

(?~) :: Join a -> Join a -> Bool Source #

pcompare :: Join a -> Join a -> Maybe Ordering Source #

Prd a => Prd (Nan a) Source # 
Instance details

Defined in Data.Prd.Nan

Methods

(<~) :: Nan a -> Nan a -> Bool Source #

(>~) :: Nan a -> Nan a -> Bool Source #

(=~) :: Nan a -> Nan a -> Bool Source #

(?~) :: Nan a -> Nan a -> Bool Source #

pcompare :: Nan a -> Nan a -> Maybe Ordering Source #

(Prd a, Prd b) => Prd (Either a b) Source # 
Instance details

Defined in Data.Prd

Methods

(<~) :: Either a b -> Either a b -> Bool Source #

(>~) :: Either a b -> Either a b -> Bool Source #

(=~) :: Either a b -> Either a b -> Bool Source #

(?~) :: Either a b -> Either a b -> Bool Source #

pcompare :: Either a b -> Either a b -> Maybe Ordering Source #

(Prd a, Prd b) => Prd (a, b) Source # 
Instance details

Defined in Data.Prd

Methods

(<~) :: (a, b) -> (a, b) -> Bool Source #

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

(=~) :: (a, b) -> (a, b) -> Bool Source #

(?~) :: (a, b) -> (a, b) -> Bool Source #

pcompare :: (a, b) -> (a, b) -> Maybe Ordering Source #

(Ord k, Prd a) => Prd (Map k a) Source # 
Instance details

Defined in Data.Prd

Methods

(<~) :: Map k a -> Map k a -> Bool Source #

(>~) :: Map k a -> Map k a -> Bool Source #

(=~) :: Map k a -> Map k a -> Bool Source #

(?~) :: Map k a -> Map k a -> Bool Source #

pcompare :: Map k a -> Map k a -> Maybe Ordering Source #

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

Defined in Data.Prd

Methods

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

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

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

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

pcompare :: (a, b, c) -> (a, b, c) -> Maybe Ordering Source #

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

Defined in Data.Prd

Methods

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

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

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

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

pcompare :: (a, b, c, d) -> (a, b, c, d) -> Maybe Ordering Source #

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

Defined in Data.Prd

Methods

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

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

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

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

pcompare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Maybe Ordering Source #

(~~) :: Eq a => Prd a => a -> a -> Bool infix 4 Source #

Similarity relation on a.

~~ is reflexive and symmetric, but not necessarily transitive.

Note this is only equivalent to == in a total (i.e. linear) order.

(/~) :: Eq a => Prd a => a -> a -> Bool infix 4 Source #

Negation of ~~.

pcomparePrd :: Prd a => a -> a -> Maybe Ordering Source #

Version of pcompare that uses the derived equivalence relation.

This can be useful if there is no Eq instance or if it is compromised, for example when a is a floating point number.

pcompareOrd :: Ord a => a -> a -> Maybe Ordering Source #

Version of pcompare that uses compare.

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)

lt :: Eq a => Prd a => a -> a -> Bool infix 4 Source #

Strict partial order relation on a.

lt is irreflexive, asymmetric, and transitive.

 lt x y = maybe False (< EQ) (pcompare x y)

If a implements Ord then (ideally) x lt y = x < y.

gt :: Eq a => Prd a => a -> a -> Bool infix 4 Source #

Converse strict partial order relation on a.

gt is irreflexive, asymmetric, and transitive.

 gt x y = maybe False (> EQ) (pcompare x y)

If a implements Ord then (ideally) x gt y = x > y.

peq :: Eq a => Prd a => a -> a -> Maybe Bool infix 4 Source #

A partial version of (=~)

Returns Nothing instead of False when the two values are not comparable.

pne :: Eq a => Prd a => a -> a -> Maybe Bool infix 4 Source #

A partial version of (/~)

Returns Nothing instead of False when the two values are not comparable.

ple :: Eq a => Prd a => a -> a -> Maybe Bool infix 4 Source #

A partial version of (<~)

Returns Nothing instead of False when the two values are not comparable.

pge :: Eq a => Prd a => a -> a -> Maybe Bool infix 4 Source #

A partial version of (>~)

Returns Nothing instead of False when the two values are not comparable.

plt :: Eq a => Prd a => a -> a -> Maybe Bool infix 4 Source #

A partial version of (<)

Returns Nothing instead of False when the two values are not comparable.

lt x y == maybe False id $ plt x y

pgt :: Eq a => Prd a => a -> a -> Maybe Bool infix 4 Source #

A partial version of (>)

Returns Nothing instead of False when the two values are not comparable.

gt x y == maybe False id $ pgt 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.

pjoin :: Eq a => Min a => Foldable f => f a -> Maybe a Source #

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.

pmeet :: Eq a => Max a => Foldable f => f a -> Maybe a Source #

sign :: Eq a => Num a => Prd a => a -> Maybe Ordering Source #

zero :: Eq a => Num a => Prd a => a -> Bool Source #

positive :: Eq a => Num a => Prd a => a -> Bool Source #

negative :: Eq a => Num a => Prd a => a -> Bool Source #

indeterminate :: Eq a => Num a => Prd a => a -> Bool Source #

until :: (a -> Bool) -> (a -> a -> Bool) -> (a -> a) -> a -> a Source #

while :: (a -> Bool) -> (a -> a -> Bool) -> (a -> a) -> a -> a Source #

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.

newtype Down a #

The Down type allows you to reverse sort order conveniently. A value of type Down a contains a value of type a (represented as Down a). If a has an Ord 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: then sortWith by Down x

Since: base-4.6.0.0

Constructors

Down a 
Instances
Monad Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(>>=) :: Down a -> (a -> Down b) -> Down b #

(>>) :: Down a -> Down b -> Down b #

return :: a -> Down a #

fail :: String -> Down a #

Functor Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

fmap :: (a -> b) -> Down a -> Down b #

(<$) :: a -> Down b -> Down a #

Applicative Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

pure :: a -> Down a #

(<*>) :: Down (a -> b) -> Down a -> Down b #

liftA2 :: (a -> b -> c) -> Down a -> Down b -> Down c #

(*>) :: Down a -> Down b -> Down b #

(<*) :: Down a -> Down b -> Down a #

Foldable Down

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

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 #

toList :: Down a -> [a] #

null :: Down a -> Bool #

length :: Down a -> Int #

elem :: Eq a => a -> Down a -> Bool #

maximum :: Ord a => Down a -> a #

minimum :: Ord a => Down a -> a #

sum :: Num a => Down a -> a #

product :: Num a => Down a -> a #

Traversable Down

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Down a -> f (Down b) #

sequenceA :: Applicative f => Down (f a) -> f (Down a) #

mapM :: Monad m => (a -> m b) -> Down a -> m (Down b) #

sequence :: Monad m => Down (m a) -> m (Down a) #

Eq1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Down a -> Down b -> Bool #

Ord1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Down a -> Down b -> Ordering #

Read1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Down a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Down a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Down a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Down a] #

Show1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Down a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Down a] -> ShowS #

Eq a => Eq (Down a)

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Methods

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

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

Data a => Data (Down a)

Since: base-4.12.0.0

Instance details

Defined in Data.Data

Methods

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

Instance details

Defined in Data.Ord

Methods

(+) :: Down a -> Down a -> Down a #

(-) :: Down a -> Down a -> Down a #

(*) :: Down a -> Down a -> Down a #

negate :: Down a -> Down a #

abs :: Down a -> Down a #

signum :: Down a -> Down a #

fromInteger :: Integer -> Down a #

Ord a => Ord (Down a)

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Methods

compare :: Down a -> Down a -> Ordering #

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

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

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

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

max :: Down a -> Down a -> Down a #

min :: Down a -> Down a -> Down a #

Read a => Read (Down a)

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Show a => Show (Down a)

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Methods

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

show :: Down a -> String #

showList :: [Down a] -> ShowS #

Generic (Down a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type #

Methods

from :: Down a -> Rep (Down a) x #

to :: Rep (Down a) x -> Down a #

Semigroup a => Semigroup (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

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

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

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

Monoid a => Monoid (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a #

mappend :: Down a -> Down a -> Down a #

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

Min a => Max (Down a) Source # 
Instance details

Defined in Data.Prd

Methods

maximal :: Down a Source #

Max a => Min (Down a) Source # 
Instance details

Defined in Data.Prd

Methods

minimal :: Down a Source #

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

Defined in Data.Prd

Methods

(<~) :: Down a -> Down a -> Bool Source #

(>~) :: Down a -> Down a -> Bool Source #

(=~) :: Down a -> Down a -> Bool Source #

(?~) :: Down a -> Down a -> Bool Source #

pcompare :: Down a -> Down a -> Maybe Ordering Source #

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

Defined in Data.Prd.Lattice

Methods

(\/) :: Down a -> Down a -> Down a Source #

(/\) :: Down a -> Down a -> Down a Source #

fromSubset :: Set (Down a) -> Down a Source #

Generic1 Down 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Down :: k -> Type #

Methods

from1 :: Down a -> Rep1 Down a #

to1 :: Rep1 Down a -> Down a #

type Rep (Down a)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

type Rep (Down a) Source # 
Instance details

Defined in Data.Connection.Yoneda

type Rep (Down a) = Down (Rep a)
type Rep1 Down

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics