Copyright | (c) Andrey Mokhov 2016-2022 |
---|---|
License | MIT (see the file LICENSE) |
Maintainer | andrey.mokhov@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Alga is a library for algebraic construction and manipulation of graphs in Haskell. See this paper for the motivation behind the library, the underlying theory, and implementation details.
This module provides basic data types and type classes for representing edge labels in edge-labelled graphs, e.g. see Algebra.Graph.Labelled.
Synopsis
- class (Monoid a, Semigroup a) => Semiring a where
- zero :: Monoid a => a
- (<+>) :: Semigroup a => a -> a -> a
- class Semiring a => StarSemiring a where
- star :: a -> a
- class Semiring a => Dioid a
- data NonNegative a
- finite :: (Num a, Ord a) => a -> Maybe (NonNegative a)
- finiteWord :: Word -> NonNegative Word
- unsafeFinite :: a -> NonNegative a
- infinite :: NonNegative a
- getFinite :: NonNegative a -> Maybe a
- data Distance a
- distance :: NonNegative a -> Distance a
- getDistance :: Distance a -> NonNegative a
- data Capacity a
- capacity :: NonNegative a -> Capacity a
- getCapacity :: Capacity a -> NonNegative a
- data Count a
- count :: NonNegative a -> Count a
- getCount :: Count a -> NonNegative a
- newtype PowerSet a = PowerSet {
- getPowerSet :: Set a
- data Minimum a
- getMinimum :: Minimum a -> Maybe a
- noMinimum :: Minimum a
- type Path a = [(a, a)]
- data Label a
- isZero :: Label a -> Bool
- type RegularExpression a = Label a
- data Optimum o a = Optimum {
- getOptimum :: o
- getArgument :: a
- type ShortestPath e a = Optimum (Distance e) (Minimum (Path a))
- type AllShortestPaths e a = Optimum (Distance e) (PowerSet (Path a))
- type CountShortestPaths e = Optimum (Distance e) (Count Integer)
- type WidestPath e a = Optimum (Capacity e) (Minimum (Path a))
Semirings and dioids
class (Monoid a, Semigroup a) => Semiring a where Source #
A semiring extends a commutative Monoid
with operation <.>
that acts
similarly to multiplication over the underlying (additive) monoid and has one
as the identity. This module also provides two convenient aliases: zero
for
mempty
, and <+>
for <>
, which makes the interface more uniform.
Instances of this type class must satisfy the following semiring laws:
x <+> (y <+> z) == (x <+> y) <+> z x <.> (y <.> z) == (x <.> y) <.> z
zero <+> x == x == x <+> zero one <.> x == x == x <.> one
Commutativity of
<+>
:x <+> y == y <+> x
Annihilating
zero
:x <.> zero == zero zero <.> x == zero
Distributivity:
x <.> (y <+> z) == x <.> y <+> x <.> z (x <+> y) <.> z == x <.> z <+> y <.> z
Instances
Semiring Any Source # | |
Semiring (Label a) Source # | |
(Monoid a, Ord a) => Semiring (PowerSet a) Source # | |
(Monoid a, Ord a) => Semiring (Minimum a) Source # | |
(Num a, Ord a) => Semiring (Distance a) Source # | |
(Num a, Ord a) => Semiring (Count a) Source # | |
(Num a, Ord a) => Semiring (Capacity a) Source # | |
(Eq o, Semiring a, Semiring o) => Semiring (Optimum o a) Source # | |
class Semiring a => StarSemiring a where Source #
A star semiring is a Semiring
with an additional unary operator star
satisfying the following two laws:
star a = one <+> a <.> star a star a = one <+> star a <.> a
Instances
StarSemiring Any Source # | |
StarSemiring (Label a) Source # | |
(Num a, Ord a) => StarSemiring (Distance a) Source # | |
(Num a, Ord a) => StarSemiring (Count a) Source # | |
(Num a, Ord a) => StarSemiring (Capacity a) Source # | |
(Eq o, StarSemiring a, StarSemiring o) => StarSemiring (Optimum o a) Source # | |
class Semiring a => Dioid a Source #
A dioid is an idempotent semiring, i.e. it satisfies the following
idempotence law in addition to the Semiring
laws:
x <+> x == x
Instances
Dioid Any Source # | |
Defined in Algebra.Graph.Label | |
(Monoid a, Ord a) => Dioid (PowerSet a) Source # | |
Defined in Algebra.Graph.Label | |
(Monoid a, Ord a) => Dioid (Minimum a) Source # | |
Defined in Algebra.Graph.Label | |
(Num a, Ord a) => Dioid (Distance a) Source # | |
Defined in Algebra.Graph.Label | |
(Num a, Ord a) => Dioid (Capacity a) Source # | |
Defined in Algebra.Graph.Label | |
(Eq o, Dioid a, Dioid o) => Dioid (Optimum o a) Source # | |
Defined in Algebra.Graph.Label |
Data types for edge labels
data NonNegative a Source #
A non-negative value that can be finite
or infinite
. Note: the current
implementation of the Num
instance raises an error on negative literals
and on the negate
method.
Instances
finite :: (Num a, Ord a) => a -> Maybe (NonNegative a) Source #
A finite non-negative value or Nothing
if the argument is negative.
finiteWord :: Word -> NonNegative Word Source #
A finite Word
.
unsafeFinite :: a -> NonNegative a Source #
A non-negative finite value, created unsafely: the argument is not
checked for being non-negative, so unsafeFinite (-1)
compiles just fine.
infinite :: NonNegative a Source #
The (non-negative) infinite value.
getFinite :: NonNegative a -> Maybe a Source #
Get a finite value or Nothing
if the value is infinite.
A distance is a non-negative value that can be finite
or infinite
.
Distances form a Dioid
as follows:
zero
=distance
infinite
one
= 0 (<+>
) =min
(<.>
) = (+
)
Instances
Num a => Bounded (Distance a) Source # | |
Eq a => Eq (Distance a) Source # | |
(Num a, Ord a) => Num (Distance a) Source # | |
Defined in Algebra.Graph.Label | |
Ord a => Ord (Distance a) Source # | |
Show a => Show (Distance a) Source # | |
Ord a => Semigroup (Distance a) Source # | |
(Ord a, Num a) => Monoid (Distance a) Source # | |
(Num a, Ord a) => Dioid (Distance a) Source # | |
Defined in Algebra.Graph.Label | |
(Num a, Ord a) => StarSemiring (Distance a) Source # | |
(Num a, Ord a) => Semiring (Distance a) Source # | |
distance :: NonNegative a -> Distance a Source #
A non-negative distance.
getDistance :: Distance a -> NonNegative a Source #
Get the value of a distance.
A capacity is a non-negative value that can be finite
or infinite
.
Capacities form a Dioid
as follows:
zero
= 0one
=capacity
infinite
(<+>
) =max
(<.>
) =min
Instances
Num a => Bounded (Capacity a) Source # | |
Eq a => Eq (Capacity a) Source # | |
(Num a, Ord a) => Num (Capacity a) Source # | |
Defined in Algebra.Graph.Label | |
Ord a => Ord (Capacity a) Source # | |
Show a => Show (Capacity a) Source # | |
Ord a => Semigroup (Capacity a) Source # | |
(Ord a, Num a) => Monoid (Capacity a) Source # | |
(Num a, Ord a) => Dioid (Capacity a) Source # | |
Defined in Algebra.Graph.Label | |
(Num a, Ord a) => StarSemiring (Capacity a) Source # | |
(Num a, Ord a) => Semiring (Capacity a) Source # | |
capacity :: NonNegative a -> Capacity a Source #
A non-negative capacity.
getCapacity :: Capacity a -> NonNegative a Source #
Get the value of a capacity.
A count is a non-negative value that can be finite
or infinite
.
Counts form a Semiring
as follows:
zero
= 0one
= 1 (<+>
) = (+
) (<.>
) = (*
)
Instances
Num a => Bounded (Count a) Source # | |
Eq a => Eq (Count a) Source # | |
(Num a, Ord a) => Num (Count a) Source # | |
Ord a => Ord (Count a) Source # | |
Show a => Show (Count a) Source # | |
(Num a, Ord a) => Semigroup (Count a) Source # | |
(Num a, Ord a) => Monoid (Count a) Source # | |
(Num a, Ord a) => StarSemiring (Count a) Source # | |
(Num a, Ord a) => Semiring (Count a) Source # | |
count :: NonNegative a -> Count a Source #
A non-negative count.
getCount :: Count a -> NonNegative a Source #
Get the value of a count.
The power set over the underlying set of elements a
. If a
is a
monoid, then the power set forms a Dioid
as follows:
zero
= PowerSet Set.empty
one
= PowerSet $ Set.singleton
mempty
x<+>
y = PowerSet $ Set.union
(getPowerSet x) (getPowerSet y) x<.>
y = PowerSet $cartesianProductWith
mappend
(getPowerSet x) (getPowerSet y)
PowerSet | |
|
Instances
Eq a => Eq (PowerSet a) Source # | |
Ord a => Ord (PowerSet a) Source # | |
Show a => Show (PowerSet a) Source # | |
Ord a => Semigroup (PowerSet a) Source # | |
Ord a => Monoid (PowerSet a) Source # | |
(Monoid a, Ord a) => Dioid (PowerSet a) Source # | |
Defined in Algebra.Graph.Label | |
(Monoid a, Ord a) => Semiring (PowerSet a) Source # | |
If a
is a monoid, Minimum
a
forms the following Dioid
:
zero
=noMinimum
one
=pure
mempty
(<+>
) =liftA2
min
(<.>
) =liftA2
mappend
To create a singleton value of type Minimum
a
use the pure
function.
For example:
getMinimum (pure
"Hello, "<+>
pure
"World!") == Just "Hello, " getMinimum (pure
"Hello, "<.>
pure
"World!") == Just "Hello, World!"
Instances
Monad Minimum Source # | |
Functor Minimum Source # | |
Applicative Minimum Source # | |
IsList a => IsList (Minimum a) Source # | |
Eq a => Eq (Minimum a) Source # | |
Ord a => Ord (Minimum a) Source # | |
Defined in Algebra.Graph.Label | |
Show a => Show (Minimum a) Source # | |
Ord a => Semigroup (Minimum a) Source # | |
(Monoid a, Ord a) => Monoid (Minimum a) Source # | |
(Monoid a, Ord a) => Dioid (Minimum a) Source # | |
Defined in Algebra.Graph.Label | |
(Monoid a, Ord a) => Semiring (Minimum a) Source # | |
type Item (Minimum a) Source # | |
Defined in Algebra.Graph.Label |
getMinimum :: Minimum a -> Maybe a Source #
Extract the minimum or Nothing
if it does not exist.
noMinimum :: Minimum a Source #
The value corresponding to the lack of minimum, e.g. the minimum of the empty set.
The type of free labels over the underlying set of symbols a
. This data
type is an instance of classes StarSemiring
and Dioid
.
type RegularExpression a = Label a Source #
A type synonym for regular expressions, built on top of free labels.
Combining edge labels
An optimum semiring obtained by combining a semiring o
that defines an
optimisation criterion, and a semiring a
that describes the arguments
of an optimisation problem. For example, by choosing o =
and
and Distance
Inta =
, we obtain the shortest path semiring
for computing the shortest path in an Minimum
(Path
String)Int
-labelled graph with String
vertices.
We assume that the semiring o
is selective i.e. for all x
and y
:
x <+> y == x || x <+> y == y
In words, the operation <+>
always simply selects one of its arguments. For
example, the Capacity
and Distance
semirings are selective, whereas the
the Count
semiring is not.
Optimum | |
|
Instances
(Eq o, Eq a) => Eq (Optimum o a) Source # | |
(Ord o, Ord a) => Ord (Optimum o a) Source # | |
Defined in Algebra.Graph.Label | |
(Show o, Show a) => Show (Optimum o a) Source # | |
(Eq o, Monoid a, Monoid o) => Semigroup (Optimum o a) Source # | |
(Eq o, Monoid a, Monoid o) => Monoid (Optimum o a) Source # | |
(Eq o, Dioid a, Dioid o) => Dioid (Optimum o a) Source # | |
Defined in Algebra.Graph.Label | |
(Eq o, StarSemiring a, StarSemiring o) => StarSemiring (Optimum o a) Source # | |
(Eq o, Semiring a, Semiring o) => Semiring (Optimum o a) Source # | |
type ShortestPath e a = Optimum (Distance e) (Minimum (Path a)) Source #
The Optimum
semiring specialised to
finding the lexicographically smallest shortest path.
type AllShortestPaths e a = Optimum (Distance e) (PowerSet (Path a)) Source #
The Optimum
semiring specialised to finding all shortest paths.