algebraic-graphs-0.2: A library for algebraic graph construction and transformation

Copyright(c) Andrey Mokhov 2016-2018
LicenseMIT (see the file LICENSE)
Maintainerandrey.mokhov@gmail.com
Stabilityunstable
Safe HaskellNone
LanguageHaskell2010

Algebra.Graph.Relation.InternalDerived

Contents

Description

This module exposes the implementation of derived binary relation data types. The API is unstable and unsafe, and is exposed only for documentation. You should use the non-internal modules Algebra.Graph.Relation.Reflexive, Algebra.Graph.Relation.Symmetric, Algebra.Graph.Relation.Transitive and Algebra.Graph.Relation.Preorder instead.

Synopsis

Implementation of derived binary relations

newtype ReflexiveRelation a Source #

The ReflexiveRelation data type represents a reflexive binary relation over a set of elements. Reflexive relations satisfy all laws of the Reflexive type class and, in particular, the self-loop axiom:

vertex x == vertex x * vertex x

The Show instance produces reflexively closed expressions:

show (1     :: ReflexiveRelation Int) == "edge 1 1"
show (1 * 2 :: ReflexiveRelation Int) == "edges [(1,1),(1,2),(2,2)]"

Constructors

ReflexiveRelation 

Fields

Instances
Ord a => Eq (ReflexiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

(Ord a, Num a) => Num (ReflexiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

(Ord a, Show a) => Show (ReflexiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

NFData a => NFData (ReflexiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Methods

rnf :: ReflexiveRelation a -> () #

Ord a => Reflexive (ReflexiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Ord a => Graph (ReflexiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Associated Types

type Vertex (ReflexiveRelation a) :: * Source #

type Vertex (ReflexiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

newtype SymmetricRelation a Source #

The SymmetricRelation data type represents a symmetric binary relation over a set of elements. Symmetric relations satisfy all laws of the Undirected type class and, in particular, the commutativity of connect:

connect x y == connect y x

The Show instance produces symmetrically closed expressions:

show (1     :: SymmetricRelation Int) == "vertex 1"
show (1 * 2 :: SymmetricRelation Int) == "edges [(1,2),(2,1)]"

Constructors

SymmetricRelation 

Fields

Instances
Ord a => Eq (SymmetricRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

(Ord a, Num a) => Num (SymmetricRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

(Ord a, Show a) => Show (SymmetricRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

NFData a => NFData (SymmetricRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Methods

rnf :: SymmetricRelation a -> () #

Ord a => Undirected (SymmetricRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Ord a => Graph (SymmetricRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Associated Types

type Vertex (SymmetricRelation a) :: * Source #

type Vertex (SymmetricRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

newtype TransitiveRelation a Source #

The TransitiveRelation data type represents a transitive binary relation over a set of elements. Transitive relations satisfy all laws of the Transitive type class and, in particular, the closure axiom:

y /= empty ==> x * y + x * z + y * z == x * y + y * z

For example, the following holds:

path xs == (clique xs :: TransitiveRelation Int)

The Show instance produces transitively closed expressions:

show (1 * 2         :: TransitiveRelation Int) == "edge 1 2"
show (1 * 2 + 2 * 3 :: TransitiveRelation Int) == "edges [(1,2),(1,3),(2,3)]"

Constructors

TransitiveRelation 
Instances
Ord a => Eq (TransitiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

(Ord a, Num a) => Num (TransitiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

(Ord a, Show a) => Show (TransitiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

NFData a => NFData (TransitiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Methods

rnf :: TransitiveRelation a -> () #

Ord a => Transitive (TransitiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Ord a => Graph (TransitiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Associated Types

type Vertex (TransitiveRelation a) :: * Source #

type Vertex (TransitiveRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

newtype PreorderRelation a Source #

The PreorderRelation data type represents a binary relation that is both reflexive and transitive. Preorders satisfy all laws of the Preorder type class and, in particular, the self-loop axiom:

vertex x == vertex x * vertex x

and the closure axiom:

y /= empty ==> x * y + x * z + y * z == x * y + y * z

For example, the following holds:

path xs == (clique xs :: PreorderRelation Int)

The Show instance produces reflexively and transitively closed expressions:

show (1             :: PreorderRelation Int) == "edge 1 1"
show (1 * 2         :: PreorderRelation Int) == "edges [(1,1),(1,2),(2,2)]"
show (1 * 2 + 2 * 3 :: PreorderRelation Int) == "edges [(1,1),(1,2),(1,3),(2,2),(2,3),(3,3)]"

Constructors

PreorderRelation 

Fields

Instances
Ord a => Eq (PreorderRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

(Ord a, Num a) => Num (PreorderRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

(Ord a, Show a) => Show (PreorderRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

NFData a => NFData (PreorderRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Methods

rnf :: PreorderRelation a -> () #

Ord a => Preorder (PreorderRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Ord a => Transitive (PreorderRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Ord a => Reflexive (PreorderRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Ord a => Graph (PreorderRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived

Associated Types

type Vertex (PreorderRelation a) :: * Source #

type Vertex (PreorderRelation a) Source # 
Instance details

Defined in Algebra.Graph.Relation.InternalDerived