lattices-1.6.0: Fine-grained library for constructing and manipulating lattices

Copyright(C) 2010-2015 Maximilian Bolingbroke
LicenseBSD-3-Clause (see the file LICENSE)
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellSafe
LanguageHaskell2010

Algebra.Lattice

Contents

Description

In mathematics, a lattice is a partially ordered set in which every two elements have a unique supremum (also called a least upper bound or join) and a unique infimum (also called a greatest lower bound or meet).

In this module lattices are defined using meet and join operators, as it's constructive one.

Synopsis

Unbounded lattices

class JoinSemiLattice a where Source #

A algebraic structure with element joins: http://en.wikipedia.org/wiki/Semilattice

Associativity: x \/ (y \/ z) == (x \/ y) \/ z
Commutativity: x \/ y == y \/ x
Idempotency:   x \/ x == x

Minimal complete definition

(\/) | join

Methods

(\/) :: a -> a -> a infixr 5 Source #

join :: a -> a -> a Source #

Deprecated: Use \/ infix operator

Instances

JoinSemiLattice Bool Source # 

Methods

(\/) :: Bool -> Bool -> Bool Source #

join :: Bool -> Bool -> Bool Source #

JoinSemiLattice () Source # 

Methods

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

join :: () -> () -> () Source #

JoinSemiLattice Void Source # 

Methods

(\/) :: Void -> Void -> Void Source #

join :: Void -> Void -> Void Source #

JoinSemiLattice All Source # 

Methods

(\/) :: All -> All -> All Source #

join :: All -> All -> All Source #

JoinSemiLattice Any Source # 

Methods

(\/) :: Any -> Any -> Any Source #

join :: Any -> Any -> Any Source #

JoinSemiLattice IntSet Source # 
JoinSemiLattice a => JoinSemiLattice (Identity a) Source # 

Methods

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

join :: Identity a -> Identity a -> Identity a Source #

JoinSemiLattice a => JoinSemiLattice (Endo a) Source # 

Methods

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

join :: Endo a -> Endo a -> Endo a Source #

JoinSemiLattice v => JoinSemiLattice (IntMap v) Source # 

Methods

(\/) :: IntMap v -> IntMap v -> IntMap v Source #

join :: IntMap v -> IntMap v -> IntMap v Source #

Ord a => JoinSemiLattice (Set a) Source # 

Methods

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

join :: Set a -> Set a -> Set a Source #

(Eq a, Hashable a) => JoinSemiLattice (HashSet a) Source # 

Methods

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

join :: HashSet a -> HashSet a -> HashSet a Source #

Integral a => JoinSemiLattice (Divisibility a) Source # 
JoinSemiLattice a => JoinSemiLattice (Dropped a) Source # 

Methods

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

join :: Dropped a -> Dropped a -> Dropped a Source #

JoinSemiLattice (FreeLattice a) Source # 
JoinSemiLattice (FreeJoinSemiLattice a) Source # 
JoinSemiLattice a => JoinSemiLattice (Levitated a) Source # 
JoinSemiLattice a => JoinSemiLattice (Lifted a) Source # 

Methods

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

join :: Lifted a -> Lifted a -> Lifted a Source #

MeetSemiLattice a => JoinSemiLattice (Op a) Source # 

Methods

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

join :: Op a -> Op a -> Op a Source #

Ord a => JoinSemiLattice (Ordered a) Source # 

Methods

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

join :: Ordered a -> Ordered a -> Ordered a Source #

JoinSemiLattice v => JoinSemiLattice (k -> v) Source # 

Methods

(\/) :: (k -> v) -> (k -> v) -> k -> v Source #

join :: (k -> v) -> (k -> v) -> k -> v Source #

(JoinSemiLattice a, JoinSemiLattice b) => JoinSemiLattice (a, b) Source # 

Methods

(\/) :: (a, b) -> (a, b) -> (a, b) Source #

join :: (a, b) -> (a, b) -> (a, b) Source #

JoinSemiLattice (Proxy * a) Source # 

Methods

(\/) :: Proxy * a -> Proxy * a -> Proxy * a Source #

join :: Proxy * a -> Proxy * a -> Proxy * a Source #

(Ord k, JoinSemiLattice v) => JoinSemiLattice (Map k v) Source # 

Methods

(\/) :: Map k v -> Map k v -> Map k v Source #

join :: Map k v -> Map k v -> Map k v Source #

(Eq k, Hashable k) => JoinSemiLattice (HashMap k v) Source # 

Methods

(\/) :: HashMap k v -> HashMap k v -> HashMap k v Source #

join :: HashMap k v -> HashMap k v -> HashMap k v Source #

(PartialOrd k, JoinSemiLattice k, BoundedJoinSemiLattice v) => JoinSemiLattice (Lexicographic k v) Source # 
JoinSemiLattice a => JoinSemiLattice (Const * a b) Source # 

Methods

(\/) :: Const * a b -> Const * a b -> Const * a b Source #

join :: Const * a b -> Const * a b -> Const * a b Source #

JoinSemiLattice a => JoinSemiLattice (Tagged * t a) Source # 

Methods

(\/) :: Tagged * t a -> Tagged * t a -> Tagged * t a Source #

join :: Tagged * t a -> Tagged * t a -> Tagged * t a Source #

class MeetSemiLattice a where Source #

A algebraic structure with element meets: http://en.wikipedia.org/wiki/Semilattice

Associativity: x /\ (y /\ z) == (x /\ y) /\ z
Commutativity: x /\ y == y /\ x
Idempotency:   x /\ x == x

Minimal complete definition

(/\) | meet

Methods

(/\) :: a -> a -> a infixr 6 Source #

meet :: a -> a -> a Source #

Deprecated: Use /\ infix operator

Instances

MeetSemiLattice Bool Source # 

Methods

(/\) :: Bool -> Bool -> Bool Source #

meet :: Bool -> Bool -> Bool Source #

MeetSemiLattice () Source # 

Methods

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

meet :: () -> () -> () Source #

MeetSemiLattice Void Source # 

Methods

(/\) :: Void -> Void -> Void Source #

meet :: Void -> Void -> Void Source #

MeetSemiLattice All Source # 

Methods

(/\) :: All -> All -> All Source #

meet :: All -> All -> All Source #

MeetSemiLattice Any Source # 

Methods

(/\) :: Any -> Any -> Any Source #

meet :: Any -> Any -> Any Source #

MeetSemiLattice IntSet Source # 
MeetSemiLattice a => MeetSemiLattice (Identity a) Source # 

Methods

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

meet :: Identity a -> Identity a -> Identity a Source #

MeetSemiLattice a => MeetSemiLattice (Endo a) Source # 

Methods

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

meet :: Endo a -> Endo a -> Endo a Source #

MeetSemiLattice v => MeetSemiLattice (IntMap v) Source # 

Methods

(/\) :: IntMap v -> IntMap v -> IntMap v Source #

meet :: IntMap v -> IntMap v -> IntMap v Source #

Ord a => MeetSemiLattice (Set a) Source # 

Methods

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

meet :: Set a -> Set a -> Set a Source #

(Eq a, Hashable a) => MeetSemiLattice (HashSet a) Source # 

Methods

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

meet :: HashSet a -> HashSet a -> HashSet a Source #

Integral a => MeetSemiLattice (Divisibility a) Source # 
MeetSemiLattice a => MeetSemiLattice (Dropped a) Source # 

Methods

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

meet :: Dropped a -> Dropped a -> Dropped a Source #

MeetSemiLattice (FreeLattice a) Source # 
MeetSemiLattice (FreeMeetSemiLattice a) Source # 
MeetSemiLattice a => MeetSemiLattice (Levitated a) Source # 
MeetSemiLattice a => MeetSemiLattice (Lifted a) Source # 

Methods

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

meet :: Lifted a -> Lifted a -> Lifted a Source #

JoinSemiLattice a => MeetSemiLattice (Op a) Source # 

Methods

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

meet :: Op a -> Op a -> Op a Source #

Ord a => MeetSemiLattice (Ordered a) Source # 

Methods

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

meet :: Ordered a -> Ordered a -> Ordered a Source #

MeetSemiLattice v => MeetSemiLattice (k -> v) Source # 

Methods

(/\) :: (k -> v) -> (k -> v) -> k -> v Source #

meet :: (k -> v) -> (k -> v) -> k -> v Source #

(MeetSemiLattice a, MeetSemiLattice b) => MeetSemiLattice (a, b) Source # 

Methods

(/\) :: (a, b) -> (a, b) -> (a, b) Source #

meet :: (a, b) -> (a, b) -> (a, b) Source #

MeetSemiLattice (Proxy * a) Source # 

Methods

(/\) :: Proxy * a -> Proxy * a -> Proxy * a Source #

meet :: Proxy * a -> Proxy * a -> Proxy * a Source #

(Ord k, MeetSemiLattice v) => MeetSemiLattice (Map k v) Source # 

Methods

(/\) :: Map k v -> Map k v -> Map k v Source #

meet :: Map k v -> Map k v -> Map k v Source #

(Eq k, Hashable k) => MeetSemiLattice (HashMap k v) Source # 

Methods

(/\) :: HashMap k v -> HashMap k v -> HashMap k v Source #

meet :: HashMap k v -> HashMap k v -> HashMap k v Source #

(PartialOrd k, MeetSemiLattice k, BoundedMeetSemiLattice v) => MeetSemiLattice (Lexicographic k v) Source # 
MeetSemiLattice a => MeetSemiLattice (Const * a b) Source # 

Methods

(/\) :: Const * a b -> Const * a b -> Const * a b Source #

meet :: Const * a b -> Const * a b -> Const * a b Source #

MeetSemiLattice a => MeetSemiLattice (Tagged * t a) Source # 

Methods

(/\) :: Tagged * t a -> Tagged * t a -> Tagged * t a Source #

meet :: Tagged * t a -> Tagged * t a -> Tagged * t a Source #

class (JoinSemiLattice a, MeetSemiLattice a) => Lattice a Source #

The combination of two semi lattices makes a lattice if the absorption law holds: see http://en.wikipedia.org/wiki/Absorption_law and http://en.wikipedia.org/wiki/Lattice_(order)

Absorption: a \/ (a /\ b) == a /\ (a \/ b) == a

joinLeq :: (Eq a, JoinSemiLattice a) => a -> a -> Bool Source #

The partial ordering induced by the join-semilattice structure

joins1 :: (JoinSemiLattice a, Foldable1 f) => f a -> a Source #

The join of at a list of join-semilattice elements (of length at least one)

meetLeq :: (Eq a, MeetSemiLattice a) => a -> a -> Bool Source #

The partial ordering induced by the meet-semilattice structure

meets1 :: (MeetSemiLattice a, Foldable1 f) => f a -> a Source #

The meet of at a list of meet-semilattice elements (of length at least one)

Bounded lattices

class JoinSemiLattice a => BoundedJoinSemiLattice a where Source #

A join-semilattice with some element |bottom| that / approaches.

Identity: x \/ bottom == x

Minimal complete definition

bottom

Methods

bottom :: a Source #

Instances

BoundedJoinSemiLattice Bool Source # 

Methods

bottom :: Bool Source #

BoundedJoinSemiLattice () Source # 

Methods

bottom :: () Source #

BoundedJoinSemiLattice All Source # 

Methods

bottom :: All Source #

BoundedJoinSemiLattice Any Source # 

Methods

bottom :: Any Source #

BoundedJoinSemiLattice IntSet Source # 

Methods

bottom :: IntSet Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Identity a) Source # 

Methods

bottom :: Identity a Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Endo a) Source # 

Methods

bottom :: Endo a Source #

JoinSemiLattice v => BoundedJoinSemiLattice (IntMap v) Source # 

Methods

bottom :: IntMap v Source #

Ord a => BoundedJoinSemiLattice (Set a) Source # 

Methods

bottom :: Set a Source #

(Eq a, Hashable a) => BoundedJoinSemiLattice (HashSet a) Source # 

Methods

bottom :: HashSet a Source #

Integral a => BoundedJoinSemiLattice (Divisibility a) Source # 
BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Dropped a) Source # 

Methods

bottom :: Dropped a Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (FreeLattice a) Source # 
BoundedJoinSemiLattice a => BoundedJoinSemiLattice (FreeJoinSemiLattice a) Source # 
JoinSemiLattice a => BoundedJoinSemiLattice (Levitated a) Source # 

Methods

bottom :: Levitated a Source #

JoinSemiLattice a => BoundedJoinSemiLattice (Lifted a) Source # 

Methods

bottom :: Lifted a Source #

BoundedMeetSemiLattice a => BoundedJoinSemiLattice (Op a) Source # 

Methods

bottom :: Op a Source #

(Ord a, Bounded a) => BoundedJoinSemiLattice (Ordered a) Source # 

Methods

bottom :: Ordered a Source #

BoundedJoinSemiLattice v => BoundedJoinSemiLattice (k -> v) Source # 

Methods

bottom :: k -> v Source #

(BoundedJoinSemiLattice a, BoundedJoinSemiLattice b) => BoundedJoinSemiLattice (a, b) Source # 

Methods

bottom :: (a, b) Source #

BoundedJoinSemiLattice (Proxy * a) Source # 

Methods

bottom :: Proxy * a Source #

(Ord k, JoinSemiLattice v) => BoundedJoinSemiLattice (Map k v) Source # 

Methods

bottom :: Map k v Source #

(Eq k, Hashable k) => BoundedJoinSemiLattice (HashMap k v) Source # 

Methods

bottom :: HashMap k v Source #

(PartialOrd k, BoundedJoinSemiLattice k, BoundedJoinSemiLattice v) => BoundedJoinSemiLattice (Lexicographic k v) Source # 
BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Const * a b) Source # 

Methods

bottom :: Const * a b Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Tagged * t a) Source # 

Methods

bottom :: Tagged * t a Source #

class MeetSemiLattice a => BoundedMeetSemiLattice a where Source #

A meet-semilattice with some element |top| that / approaches.

Identity: x /\ top == x

Minimal complete definition

top

Methods

top :: a Source #

Instances

BoundedMeetSemiLattice Bool Source # 

Methods

top :: Bool Source #

BoundedMeetSemiLattice () Source # 

Methods

top :: () Source #

BoundedMeetSemiLattice All Source # 

Methods

top :: All Source #

BoundedMeetSemiLattice Any Source # 

Methods

top :: Any Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Identity a) Source # 

Methods

top :: Identity a Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Endo a) Source # 

Methods

top :: Endo a Source #

(Ord a, Finite a) => BoundedMeetSemiLattice (Set a) Source # 

Methods

top :: Set a Source #

MeetSemiLattice a => BoundedMeetSemiLattice (Dropped a) Source # 

Methods

top :: Dropped a Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (FreeLattice a) Source # 

Methods

top :: FreeLattice a Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (FreeMeetSemiLattice a) Source # 
MeetSemiLattice a => BoundedMeetSemiLattice (Levitated a) Source # 

Methods

top :: Levitated a Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Lifted a) Source # 

Methods

top :: Lifted a Source #

BoundedJoinSemiLattice a => BoundedMeetSemiLattice (Op a) Source # 

Methods

top :: Op a Source #

(Ord a, Bounded a) => BoundedMeetSemiLattice (Ordered a) Source # 

Methods

top :: Ordered a Source #

BoundedMeetSemiLattice v => BoundedMeetSemiLattice (k -> v) Source # 

Methods

top :: k -> v Source #

(BoundedMeetSemiLattice a, BoundedMeetSemiLattice b) => BoundedMeetSemiLattice (a, b) Source # 

Methods

top :: (a, b) Source #

BoundedMeetSemiLattice (Proxy * a) Source # 

Methods

top :: Proxy * a Source #

(Ord k, Finite k, BoundedMeetSemiLattice v) => BoundedMeetSemiLattice (Map k v) Source # 

Methods

top :: Map k v Source #

(PartialOrd k, BoundedMeetSemiLattice k, BoundedMeetSemiLattice v) => BoundedMeetSemiLattice (Lexicographic k v) Source # 

Methods

top :: Lexicographic k v Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Const * a b) Source # 

Methods

top :: Const * a b Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Tagged * t a) Source # 

Methods

top :: Tagged * t a Source #

joins :: (BoundedJoinSemiLattice a, Foldable f) => f a -> a Source #

The join of a list of join-semilattice elements

meets :: (BoundedMeetSemiLattice a, Foldable f) => f a -> a Source #

The meet of a list of meet-semilattice elements

Monoid wrappers

newtype Meet a Source #

Monoid wrapper for MeetSemiLattice

Constructors

Meet 

Fields

Instances

Monad Meet Source # 

Methods

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

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

return :: a -> Meet a #

fail :: String -> Meet a #

Functor Meet Source # 

Methods

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

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

Applicative Meet Source # 

Methods

pure :: a -> Meet a #

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

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

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

MonadZip Meet Source # 

Methods

mzip :: Meet a -> Meet b -> Meet (a, b) #

mzipWith :: (a -> b -> c) -> Meet a -> Meet b -> Meet c #

munzip :: Meet (a, b) -> (Meet a, Meet b) #

Bounded a => Bounded (Meet a) Source # 

Methods

minBound :: Meet a #

maxBound :: Meet a #

Eq a => Eq (Meet a) Source # 

Methods

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

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

Data a => Data (Meet a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Meet a -> c (Meet a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Meet a) #

toConstr :: Meet a -> Constr #

dataTypeOf :: Meet a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Meet a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Meet a)) #

gmapT :: (forall b. Data b => b -> b) -> Meet a -> Meet a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Meet a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Meet a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Meet a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Meet a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Meet a -> m (Meet a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Meet a -> m (Meet a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Meet a -> m (Meet a) #

Ord a => Ord (Meet a) Source # 

Methods

compare :: Meet a -> Meet a -> Ordering #

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

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

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

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

max :: Meet a -> Meet a -> Meet a #

min :: Meet a -> Meet a -> Meet a #

Read a => Read (Meet a) Source # 
Show a => Show (Meet a) Source # 

Methods

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

show :: Meet a -> String #

showList :: [Meet a] -> ShowS #

Generic (Meet a) Source # 

Associated Types

type Rep (Meet a) :: * -> * #

Methods

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

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

MeetSemiLattice a => Semigroup (Meet a) Source # 

Methods

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

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

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

BoundedMeetSemiLattice a => Monoid (Meet a) Source # 

Methods

mempty :: Meet a #

mappend :: Meet a -> Meet a -> Meet a #

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

Universe a => Universe (Meet a) Source # 

Methods

universe :: [Meet a] #

Finite a => Finite (Meet a) Source # 

Methods

universeF :: [Meet a] #

type Rep (Meet a) Source # 
type Rep (Meet a) = D1 (MetaData "Meet" "Algebra.Lattice" "lattices-1.6.0-2oKxOcsrwg99Rpe11Qz7rb" True) (C1 (MetaCons "Meet" PrefixI True) (S1 (MetaSel (Just Symbol "getMeet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype Join a Source #

Monoid wrapper for JoinSemiLattice

Constructors

Join 

Fields

Instances

Monad Join Source # 

Methods

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

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

return :: a -> Join a #

fail :: String -> Join a #

Functor Join Source # 

Methods

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

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

Applicative Join Source # 

Methods

pure :: a -> Join a #

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

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

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

MonadZip Join Source # 

Methods

mzip :: Join a -> Join b -> Join (a, b) #

mzipWith :: (a -> b -> c) -> Join a -> Join b -> Join c #

munzip :: Join (a, b) -> (Join a, Join b) #

Bounded a => Bounded (Join a) Source # 

Methods

minBound :: Join a #

maxBound :: Join a #

Eq a => Eq (Join a) Source # 

Methods

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

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

Data a => Data (Join a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Join a -> c (Join a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Join a) #

toConstr :: Join a -> Constr #

dataTypeOf :: Join a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Join a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Join a)) #

gmapT :: (forall b. Data b => b -> b) -> Join a -> Join a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Join a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Join a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Join a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Join a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Join a -> m (Join a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Join a -> m (Join a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Join a -> m (Join a) #

Ord a => Ord (Join a) Source # 

Methods

compare :: Join a -> Join a -> Ordering #

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

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

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

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

max :: Join a -> Join a -> Join a #

min :: Join a -> Join a -> Join a #

Read a => Read (Join a) Source # 
Show a => Show (Join a) Source # 

Methods

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

show :: Join a -> String #

showList :: [Join a] -> ShowS #

Generic (Join a) Source # 

Associated Types

type Rep (Join a) :: * -> * #

Methods

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

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

JoinSemiLattice a => Semigroup (Join a) Source # 

Methods

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

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

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

BoundedJoinSemiLattice a => Monoid (Join a) Source # 

Methods

mempty :: Join a #

mappend :: Join a -> Join a -> Join a #

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

Universe a => Universe (Join a) Source # 

Methods

universe :: [Join a] #

Finite a => Finite (Join a) Source # 

Methods

universeF :: [Join a] #

type Rep (Join a) Source # 
type Rep (Join a) = D1 (MetaData "Join" "Algebra.Lattice" "lattices-1.6.0-2oKxOcsrwg99Rpe11Qz7rb" True) (C1 (MetaCons "Join" PrefixI True) (S1 (MetaSel (Just Symbol "getJoin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

Fixed points of chains in lattices

lfp :: (Eq a, BoundedJoinSemiLattice a) => (a -> a) -> a Source #

Implementation of Kleene fixed-point theorem http://en.wikipedia.org/wiki/Kleene_fixed-point_theorem. Forces the function to be monotone.

lfpFrom :: (Eq a, BoundedJoinSemiLattice a) => a -> (a -> a) -> a Source #

Implementation of Kleene fixed-point theorem http://en.wikipedia.org/wiki/Kleene_fixed-point_theorem. Forces the function to be monotone.

unsafeLfp :: (Eq a, BoundedJoinSemiLattice a) => (a -> a) -> a Source #

Implementation of Kleene fixed-point theorem http://en.wikipedia.org/wiki/Kleene_fixed-point_theorem. Assumes that the function is monotone and does not check if that is correct.

gfp :: (Eq a, BoundedMeetSemiLattice a) => (a -> a) -> a Source #

Implementation of Kleene fixed-point theorem http://en.wikipedia.org/wiki/Kleene_fixed-point_theorem. Forces the function to be antinone.

gfpFrom :: (Eq a, BoundedMeetSemiLattice a) => a -> (a -> a) -> a Source #

Implementation of Kleene fixed-point theorem http://en.wikipedia.org/wiki/Kleene_fixed-point_theorem. Forces the function to be antinone.

unsafeGfp :: (Eq a, BoundedMeetSemiLattice a) => (a -> a) -> a Source #

Implementation of Kleene fixed-point theorem http://en.wikipedia.org/wiki/Kleene_fixed-point_theorem. Assumes that the function is antinone and does not check if that is correct.