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

Copyright(C) 2010-2015 Maximilian Bolingbroke 2015-2019 Oleg Grenrus
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 Lattice a where Source #

An algebraic structure with joins and meets.

See http://en.wikipedia.org/wiki/Lattice_(order) and http://en.wikipedia.org/wiki/Absorption_law.

Lattice is very symmetric, which is seen from the laws:

Associativity

x \/ (y \/ z) ≡ (x \/ y) \/ z
x /\ (y /\ z) ≡ (x /\ y) /\ z

Commputativity

x \/ y ≡ y \/ x
x /\ y ≡ y /\ x

Idempotency

x \/ x ≡ x
x /\ x ≡ x

Absorption

a \/ (a /\ b) ≡ a
a /\ (a \/ b) ≡ a

Methods

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

join

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

meet

Instances
Lattice Bool Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

Lattice () Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

Lattice Property Source # 
Instance details

Defined in Algebra.Lattice

Lattice Void Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

Lattice All Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

Lattice Any Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

Lattice IntSet Source # 
Instance details

Defined in Algebra.Lattice

Lattice N5 Source # 
Instance details

Defined in Algebra.Lattice.N5

Methods

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

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

Lattice M3 Source # 
Instance details

Defined in Algebra.Lattice.M3

Methods

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

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

Lattice ZeroHalfOne Source # 
Instance details

Defined in Algebra.Lattice.ZeroHalfOne

Lattice M2 Source # 
Instance details

Defined in Algebra.Lattice.M2

Methods

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

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

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

Defined in Algebra.Lattice

Methods

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

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

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

Defined in Algebra.Lattice

Methods

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

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

Lattice v => Lattice (IntMap v) Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

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

Defined in Algebra.Lattice

Methods

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

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

(Eq a, Hashable a) => Lattice (HashSet a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

Eq a => Lattice (Wide a) Source # 
Instance details

Defined in Algebra.Lattice.Wide

Methods

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

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

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

Defined in Algebra.Lattice.Op

Methods

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

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

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

Defined in Algebra.Lattice.Lifted

Methods

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

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

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

Defined in Algebra.Lattice.Levitated

Lattice (FBoundedLattice a) Source # 
Instance details

Defined in Algebra.Lattice.Free.Final

Lattice (FLattice a) Source # 
Instance details

Defined in Algebra.Lattice.Free.Final

Methods

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

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

Lattice (Free a) Source # 
Instance details

Defined in Algebra.Lattice.Free

Methods

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

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

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

Defined in Algebra.Lattice.Dropped

Methods

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

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

Integral a => Lattice (Divisibility a) Source # 
Instance details

Defined in Algebra.Lattice.Divisibility

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

Defined in Algebra.Lattice.Ordered

Methods

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

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

Lattice (Free a) Source # 
Instance details

Defined in Algebra.Heyting.Free

Methods

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

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

Lattice v => Lattice (k -> v) Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

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

Defined in Algebra.Lattice

Methods

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

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

Lattice (Proxy a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

(Ord k, Lattice v) => Lattice (Map k v) Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

(Eq k, Hashable k, Lattice v) => Lattice (HashMap k v) Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

(Lattice a, Lattice b) => Lattice (Stacked a b) Source # 
Instance details

Defined in Algebra.Lattice.Stacked

Methods

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

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

(PartialOrd k, Lattice k, BoundedJoinSemiLattice v, BoundedMeetSemiLattice v) => Lattice (Lexicographic k v) Source # 
Instance details

Defined in Algebra.Lattice.Lexicographic

Lattice a => Lattice (Const a b) Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

Lattice a => Lattice (Tagged t a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

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

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

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

The partial ordering induced by the join-semilattice structure

joins1 :: (Lattice 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, Lattice a) => a -> a -> Bool Source #

meets1 :: (Lattice 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 Lattice a => BoundedJoinSemiLattice a where Source #

A join-semilattice with an identity element bottom for \/.

Laws

x \/ bottom ≡ x

Corollary

x /\ bottom
  ≡⟨ identity ⟩
(x /\ bottom) \/ bottom
  ≡⟨ absorption ⟩
bottom

Methods

bottom :: a Source #

Instances
BoundedJoinSemiLattice Bool Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: Bool Source #

BoundedJoinSemiLattice () Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: () Source #

BoundedJoinSemiLattice Property Source # 
Instance details

Defined in Algebra.Lattice

BoundedJoinSemiLattice All Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: All Source #

BoundedJoinSemiLattice Any Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: Any Source #

BoundedJoinSemiLattice IntSet Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: IntSet Source #

BoundedJoinSemiLattice N5 Source # 
Instance details

Defined in Algebra.Lattice.N5

Methods

bottom :: N5 Source #

BoundedJoinSemiLattice M3 Source # 
Instance details

Defined in Algebra.Lattice.M3

Methods

bottom :: M3 Source #

BoundedJoinSemiLattice ZeroHalfOne Source # 
Instance details

Defined in Algebra.Lattice.ZeroHalfOne

BoundedJoinSemiLattice M2 Source # 
Instance details

Defined in Algebra.Lattice.M2

Methods

bottom :: M2 Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Identity a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: Identity a Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Endo a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: Endo a Source #

Lattice v => BoundedJoinSemiLattice (IntMap v) Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: IntMap v Source #

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

Defined in Algebra.Lattice

Methods

bottom :: Set a Source #

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

Defined in Algebra.Lattice

Methods

bottom :: HashSet a Source #

Eq a => BoundedJoinSemiLattice (Wide a) Source # 
Instance details

Defined in Algebra.Lattice.Wide

Methods

bottom :: Wide a Source #

BoundedMeetSemiLattice a => BoundedJoinSemiLattice (Op a) Source # 
Instance details

Defined in Algebra.Lattice.Op

Methods

bottom :: Op a Source #

Lattice a => BoundedJoinSemiLattice (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

bottom :: Lifted a Source #

Lattice a => BoundedJoinSemiLattice (Levitated a) Source # 
Instance details

Defined in Algebra.Lattice.Levitated

Methods

bottom :: Levitated a Source #

BoundedJoinSemiLattice (FBoundedLattice a) Source # 
Instance details

Defined in Algebra.Lattice.Free.Final

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (FLattice a) Source # 
Instance details

Defined in Algebra.Lattice.Free.Final

Methods

bottom :: FLattice a Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Dropped a) Source # 
Instance details

Defined in Algebra.Lattice.Dropped

Methods

bottom :: Dropped a Source #

Integral a => BoundedJoinSemiLattice (Divisibility a) Source # 
Instance details

Defined in Algebra.Lattice.Divisibility

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

Defined in Algebra.Lattice.Ordered

Methods

bottom :: Ordered a Source #

BoundedJoinSemiLattice (Free a) Source # 
Instance details

Defined in Algebra.Heyting.Free

Methods

bottom :: Free a Source #

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

Defined in Algebra.Lattice

Methods

bottom :: k -> v Source #

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

Defined in Algebra.Lattice

Methods

bottom :: (a, b) Source #

BoundedJoinSemiLattice (Proxy a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: Proxy a Source #

(Ord k, Lattice v) => BoundedJoinSemiLattice (Map k v) Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: Map k v Source #

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

Defined in Algebra.Lattice

Methods

bottom :: HashMap k v Source #

(BoundedJoinSemiLattice a, Lattice b) => BoundedJoinSemiLattice (Stacked a b) Source # 
Instance details

Defined in Algebra.Lattice.Stacked

Methods

bottom :: Stacked a b Source #

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

Defined in Algebra.Lattice.Lexicographic

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Const a b) Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: Const a b Source #

BoundedJoinSemiLattice a => BoundedJoinSemiLattice (Tagged t a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

bottom :: Tagged t a Source #

class Lattice a => BoundedMeetSemiLattice a where Source #

A meet-semilattice with an identity element top for /\.

Laws

x /\ top ≡ x

Corollary

x \/ top
  ≡⟨ identity ⟩
(x \/ top) /\ top
  ≡⟨ absorption ⟩
top

Methods

top :: a Source #

Instances
BoundedMeetSemiLattice Bool Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: Bool Source #

BoundedMeetSemiLattice () Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: () Source #

BoundedMeetSemiLattice Property Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: Property Source #

BoundedMeetSemiLattice All Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: All Source #

BoundedMeetSemiLattice Any Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: Any Source #

BoundedMeetSemiLattice N5 Source # 
Instance details

Defined in Algebra.Lattice.N5

Methods

top :: N5 Source #

BoundedMeetSemiLattice M3 Source # 
Instance details

Defined in Algebra.Lattice.M3

Methods

top :: M3 Source #

BoundedMeetSemiLattice ZeroHalfOne Source # 
Instance details

Defined in Algebra.Lattice.ZeroHalfOne

BoundedMeetSemiLattice M2 Source # 
Instance details

Defined in Algebra.Lattice.M2

Methods

top :: M2 Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Identity a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: Identity a Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Endo a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: Endo a Source #

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

Defined in Algebra.Lattice

Methods

top :: Set a Source #

(Eq a, Hashable a, Finite a) => BoundedMeetSemiLattice (HashSet a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: HashSet a Source #

Eq a => BoundedMeetSemiLattice (Wide a) Source # 
Instance details

Defined in Algebra.Lattice.Wide

Methods

top :: Wide a Source #

BoundedJoinSemiLattice a => BoundedMeetSemiLattice (Op a) Source # 
Instance details

Defined in Algebra.Lattice.Op

Methods

top :: Op a Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Lifted a) Source # 
Instance details

Defined in Algebra.Lattice.Lifted

Methods

top :: Lifted a Source #

Lattice a => BoundedMeetSemiLattice (Levitated a) Source # 
Instance details

Defined in Algebra.Lattice.Levitated

Methods

top :: Levitated a Source #

BoundedMeetSemiLattice (FBoundedLattice a) Source # 
Instance details

Defined in Algebra.Lattice.Free.Final

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (FLattice a) Source # 
Instance details

Defined in Algebra.Lattice.Free.Final

Methods

top :: FLattice a Source #

Lattice a => BoundedMeetSemiLattice (Dropped a) Source # 
Instance details

Defined in Algebra.Lattice.Dropped

Methods

top :: Dropped a Source #

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

Defined in Algebra.Lattice.Ordered

Methods

top :: Ordered a Source #

BoundedMeetSemiLattice (Free a) Source # 
Instance details

Defined in Algebra.Heyting.Free

Methods

top :: Free a Source #

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

Defined in Algebra.Lattice

Methods

top :: k -> v Source #

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

Defined in Algebra.Lattice

Methods

top :: (a, b) Source #

BoundedMeetSemiLattice (Proxy a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: Proxy a Source #

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

Defined in Algebra.Lattice

Methods

top :: Map k v Source #

(Eq k, Hashable k, Finite k, BoundedMeetSemiLattice v) => BoundedMeetSemiLattice (HashMap k v) Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: HashMap k v Source #

(Lattice a, BoundedMeetSemiLattice b) => BoundedMeetSemiLattice (Stacked a b) Source # 
Instance details

Defined in Algebra.Lattice.Stacked

Methods

top :: Stacked a b Source #

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

Defined in Algebra.Lattice.Lexicographic

Methods

top :: Lexicographic k v Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Const a b) Source # 
Instance details

Defined in Algebra.Lattice

Methods

top :: Const a b Source #

BoundedMeetSemiLattice a => BoundedMeetSemiLattice (Tagged t a) Source # 
Instance details

Defined in Algebra.Lattice

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 meet-Lattice

Constructors

Meet 

Fields

Instances
Monad Meet Source # 
Instance details

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

Methods

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

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

Applicative Meet Source # 
Instance details

Defined in Algebra.Lattice

Methods

pure :: a -> Meet a #

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

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

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

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

MonadZip Meet Source # 
Instance details

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

Methods

minBound :: Meet a #

maxBound :: Meet a #

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

Defined in Algebra.Lattice

Methods

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

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

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

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

Methods

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

show :: Meet a -> String #

showList :: [Meet a] -> ShowS #

Generic (Meet a) Source # 
Instance details

Defined in Algebra.Lattice

Associated Types

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

Methods

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

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

Lattice a => Semigroup (Meet a) Source # 
Instance details

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

Methods

mempty :: Meet a #

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

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

Universe a => Universe (Meet a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

universe :: [Meet a] #

Finite a => Finite (Meet a) Source # 
Instance details

Defined in Algebra.Lattice

(Eq a, Lattice a) => PartialOrd (Meet a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

leq :: Meet a -> Meet a -> Bool Source #

comparable :: Meet a -> Meet a -> Bool Source #

type Rep (Meet a) Source # 
Instance details

Defined in Algebra.Lattice

type Rep (Meet a) = D1 (MetaData "Meet" "Algebra.Lattice" "lattices-2.0.2-HdMTcqWeXqlAAQvdNaFFrQ" True) (C1 (MetaCons "Meet" PrefixI True) (S1 (MetaSel (Just "getMeet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype Join a Source #

Monoid wrapper for join-Lattice

Constructors

Join 

Fields

Instances
Monad Join Source # 
Instance details

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

Methods

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

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

Applicative Join Source # 
Instance details

Defined in Algebra.Lattice

Methods

pure :: a -> Join a #

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

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

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

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

MonadZip Join Source # 
Instance details

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

Methods

minBound :: Join a #

maxBound :: Join a #

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

Defined in Algebra.Lattice

Methods

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

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

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

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

Methods

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

show :: Join a -> String #

showList :: [Join a] -> ShowS #

Generic (Join a) Source # 
Instance details

Defined in Algebra.Lattice

Associated Types

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

Methods

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

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

Lattice a => Semigroup (Join a) Source # 
Instance details

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

Methods

mempty :: Join a #

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

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

Universe a => Universe (Join a) Source # 
Instance details

Defined in Algebra.Lattice

Methods

universe :: [Join a] #

Finite a => Finite (Join a) Source # 
Instance details

Defined in Algebra.Lattice

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

Defined in Algebra.Lattice

Methods

leq :: Join a -> Join a -> Bool Source #

comparable :: Join a -> Join a -> Bool Source #

type Rep (Join a) Source # 
Instance details

Defined in Algebra.Lattice

type Rep (Join a) = D1 (MetaData "Join" "Algebra.Lattice" "lattices-2.0.2-HdMTcqWeXqlAAQvdNaFFrQ" True) (C1 (MetaCons "Join" PrefixI True) (S1 (MetaSel (Just "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.