lattices-1.4: 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 HaskellTrustworthy
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

Nothing

Methods

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

join :: a -> a -> 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

Nothing

Methods

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

meet :: a -> a -> 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

Instances

Lattice Bool 
Lattice () 
Lattice All 
Lattice Any 
Lattice Void 
Lattice a => Lattice (Endo a) 
Ord a => Lattice (Set a) 
Lattice a => Lattice (Dropped a) 
Lattice a => Lattice (Levitated a) 
Lattice a => Lattice (Lifted a) 
Lattice v => Lattice (k -> v) 
(Lattice a, Lattice b) => Lattice (a, b) 
Lattice (Proxy * a) 
(Ord k, Lattice v) => Lattice (Map k v) 
Lattice a => Lattice (Tagged * t a) 

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

The partial ordering induced by the join-semilattice structure

joins1 :: JoinSemiLattice a => [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 => [a] -> a Source

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

Bounded lattices

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

getMeet :: a
 

Instances

Bounded a => Bounded (Meet a) 
Eq a => Eq (Meet a) 
Data a => Data (Meet a) 
Ord a => Ord (Meet a) 
Read a => Read (Meet a) 
Show a => Show (Meet a) 
BoundedMeetSemiLattice a => Monoid (Meet a) 
MeetSemiLattice a => Semigroup (Meet a) 
Typeable (* -> *) Meet 

newtype Join a Source

Monoid wrapper for JoinSemiLattice

Constructors

Join 

Fields

getJoin :: a
 

Instances

Bounded a => Bounded (Join a) 
Eq a => Eq (Join a) 
Data a => Data (Join a) 
Ord a => Ord (Join a) 
Read a => Read (Join a) 
Show a => Show (Join a) 
BoundedJoinSemiLattice a => Monoid (Join a) 
JoinSemiLattice a => Semigroup (Join a) 
Typeable (* -> *) Join 

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.