heyting-algebras-0.0.1.2: Heyting and Boolean algebras

Safe HaskellSafe
LanguageHaskell2010

Algebra.Heyting

Contents

Synopsis

Documentation

class BoundedLattice a => HeytingAlgebra a where Source #

Heyting algebra is a bounded semi-lattice with implication which should satisfy the following law:

x ∧ a ≤ b ⇔ x ≤ (a ⇒ b)

This means a ⇒ b is an exponential object, which makes any Heyting algebra a cartesian closed category.

Some useful properties of Heyting algebras:

(a ⇒ b) ∧ a ≤ b
b ≤ a ⇒ a ∧ b
a ≤ b  iff a ⇒ b = ⊤
b ≤ b' then a ⇒ b ≤ a ⇒ b'
a'≤ a  then a' ⇒ b ≤ a ⇒ b

Minimal complete definition

(==>) | not

Methods

(==>) :: a -> a -> a infixr 4 Source #

Default implementation: a ==> b = not a / b, it requires not to satisfy Boolean axioms, which will make it into a Boolean algebra.

not :: a -> a Source #

Default implementation: not a = a ==> bottom

It is useful for optimisation reasons.

Instances
HeytingAlgebra Bool Source # 
Instance details

Defined in Algebra.Heyting

Methods

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

not :: Bool -> Bool Source #

HeytingAlgebra () Source # 
Instance details

Defined in Algebra.Heyting

Methods

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

not :: () -> () Source #

HeytingAlgebra All Source # 
Instance details

Defined in Algebra.Heyting

Methods

(==>) :: All -> All -> All Source #

not :: All -> All Source #

HeytingAlgebra Any Source # 
Instance details

Defined in Algebra.Heyting

Methods

(==>) :: Any -> Any -> Any Source #

not :: Any -> Any Source #

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

Defined in Algebra.Heyting

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

Defined in Algebra.Heyting

Methods

(==>) :: Endo a -> Endo a -> Endo a Source #

not :: Endo a -> Endo a Source #

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

Power set: the cannoical example of a Boolean algebra

Instance details

Defined in Algebra.Heyting

Methods

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

not :: Set a -> Set a Source #

(Eq a, HeytingAlgebra a) => HeytingAlgebra (Dropped a) Source # 
Instance details

Defined in Algebra.Heyting

Methods

(==>) :: Dropped a -> Dropped a -> Dropped a Source #

not :: Dropped a -> Dropped a Source #

(Eq a, HeytingAlgebra a) => HeytingAlgebra (Levitated a) Source # 
Instance details

Defined in Algebra.Heyting

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

Defined in Algebra.Heyting

Methods

(==>) :: Lifted a -> Lifted a -> Lifted a Source #

not :: Lifted a -> Lifted a Source #

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

Defined in Algebra.Heyting

Methods

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

not :: Ordered a -> Ordered a Source #

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

Defined in Algebra.Heyting

Methods

(==>) :: HashSet a -> HashSet a -> HashSet a Source #

not :: HashSet a -> HashSet a Source #

HeytingAlgebra a => HeytingAlgebra (Boolean a) Source # 
Instance details

Defined in Algebra.Boolean

Methods

(==>) :: Boolean a -> Boolean a -> Boolean a Source #

not :: Boolean a -> Boolean a Source #

HeytingAlgebra (FreeBoolean a) Source # 
Instance details

Defined in Algebra.Boolean.Free

HeytingAlgebra (FreeHeyting a) Source # 
Instance details

Defined in Algebra.Heyting.Free

HeytingAlgebra b => HeytingAlgebra (a -> b) Source # 
Instance details

Defined in Algebra.Heyting

Methods

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

not :: (a -> b) -> a -> b Source #

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

Defined in Algebra.Heyting

Methods

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

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

HeytingAlgebra (Proxy a) Source # 
Instance details

Defined in Algebra.Heyting

Methods

(==>) :: Proxy a -> Proxy a -> Proxy a Source #

not :: Proxy a -> Proxy a Source #

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

It is not a boolean algebra (even if values are).

Instance details

Defined in Algebra.Heyting

Methods

(==>) :: Map k v -> Map k v -> Map k v Source #

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

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

Defined in Algebra.Heyting

Methods

(==>) :: HashMap k v -> HashMap k v -> HashMap k v Source #

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

(HeytingAlgebra a, HeytingAlgebra b, Eq a) => HeytingAlgebra (Layered a b) Source # 
Instance details

Defined in Algebra.Heyting.Layered

Methods

(==>) :: Layered a b -> Layered a b -> Layered a b Source #

not :: Layered a b -> Layered a b Source #

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

Defined in Algebra.Heyting

Methods

(==>) :: Const a b -> Const a b -> Const a b Source #

not :: Const a b -> Const a b Source #

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

Defined in Algebra.Heyting

Methods

(==>) :: Tagged t a -> Tagged t a -> Tagged t a Source #

not :: Tagged t a -> Tagged t a Source #

iff :: HeytingAlgebra a => a -> a -> a Source #

Less than fixity of both \/ and /\.

iff' :: (Eq a, HeytingAlgebra a) => a -> a -> Bool Source #

toBoolean :: HeytingAlgebra a => a -> a Source #

Every Heyting algebra contains a Boolean algebra. toBoolean maps onto it; moreover it is a monad (Heyting algebra is a category as every poset is) which preserves finite infima.

Properties

Properties are exported only if export-properties cabal flag is defined.

prop_BoundedMeetSemiLattice :: (BoundedMeetSemiLattice a, Eq a, Show a) => a -> a -> a -> Property Source #

Verfifies bounded meet semilattice laws.

prop_BoundedJoinSemiLattice :: (BoundedJoinSemiLattice a, Eq a, Show a) => a -> a -> a -> Property Source #

Verfifies bounded join semilattice laws.

prop_HeytingAlgebra :: (HeytingAlgebra a, Eq a, Show a) => a -> a -> a -> Property Source #

Usefull for testing valid instances of HeytingAlgebra type class. It validates:

prop_implies :: (HeytingAlgebra a, Eq a, Show a) => a -> a -> a -> Property Source #

Verifies the Heyting algebra law for ==>: for all a: _ / a is left adjoint to a ==>