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

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

Algebra.Graph.Label

Contents

Description

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

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:

  • Associativity of <+> and <.>:

    x <+> (y <+> z) == (x <+> y) <+> z
    x <.> (y <.> z) == (x <.> y) <.> z
  • Identities of <+> and <.>:

    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

Methods

one :: a Source #

(<.>) :: a -> a -> a infixr 7 Source #

Instances
Semiring Any Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

one :: Any Source #

(<.>) :: Any -> Any -> Any Source #

Semiring (Label a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

one :: Label a Source #

(<.>) :: Label a -> Label a -> Label a Source #

(Monoid a, Ord a) => Semiring (PowerSet a) Source # 
Instance details

Defined in Algebra.Graph.Label

(Monoid a, Ord a) => Semiring (Minimum a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

one :: Minimum a Source #

(<.>) :: Minimum a -> Minimum a -> Minimum a Source #

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

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

Methods

one :: Count a Source #

(<.>) :: Count a -> Count a -> Count a Source #

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

Defined in Algebra.Graph.Label

(Eq o, Semiring a, Semiring o) => Semiring (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

one :: Optimum o a Source #

(<.>) :: Optimum o a -> Optimum o a -> Optimum o a Source #

zero :: Monoid a => a Source #

An alias for mempty.

(<+>) :: Semigroup a => a -> a -> a infixr 6 Source #

An alias for <>.

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

Methods

star :: a -> a Source #

Instances
StarSemiring Any Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

star :: Any -> Any Source #

StarSemiring (Label a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

star :: Label a -> Label a Source #

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

Defined in Algebra.Graph.Label

Methods

star :: Distance a -> Distance a Source #

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

Defined in Algebra.Graph.Label

Methods

star :: Count a -> Count a Source #

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

Defined in Algebra.Graph.Label

Methods

star :: Capacity a -> Capacity a Source #

(Eq o, StarSemiring a, StarSemiring o) => StarSemiring (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

star :: Optimum o a -> 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 # 
Instance details

Defined in Algebra.Graph.Label

(Monoid a, Ord a) => Dioid (PowerSet a) Source # 
Instance details

Defined in Algebra.Graph.Label

(Monoid a, Ord a) => Dioid (Minimum a) Source # 
Instance details

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

(Eq o, Dioid a, Dioid o) => Dioid (Optimum o a) Source # 
Instance details

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
Monad NonNegative Source # 
Instance details

Defined in Algebra.Graph.Label

Functor NonNegative Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

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

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

Applicative NonNegative Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

pure :: a -> NonNegative a #

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

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

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

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

Num a => Bounded (NonNegative a) Source # 
Instance details

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

Ord a => Ord (NonNegative a) Source # 
Instance details

Defined in Algebra.Graph.Label

(Num a, Show a) => Show (NonNegative a) Source # 
Instance details

Defined in Algebra.Graph.Label

finite :: (Num a, Ord a) => a -> Maybe (NonNegative a) Source #

A finite non-negative value or Nothing if the argument is negative.

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.

data Distance a Source #

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

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

Methods

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

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

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

Defined in Algebra.Graph.Label

Ord a => Ord (Distance a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

compare :: Distance a -> Distance a -> Ordering #

(<) :: Distance a -> Distance a -> Bool #

(<=) :: Distance a -> Distance a -> Bool #

(>) :: Distance a -> Distance a -> Bool #

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

max :: Distance a -> Distance a -> Distance a #

min :: Distance a -> Distance a -> Distance a #

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

Defined in Algebra.Graph.Label

Methods

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

show :: Distance a -> String #

showList :: [Distance a] -> ShowS #

Ord a => Semigroup (Distance a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

(<>) :: Distance a -> Distance a -> Distance a #

sconcat :: NonEmpty (Distance a) -> Distance a #

stimes :: Integral b => b -> Distance a -> Distance a #

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

Defined in Algebra.Graph.Label

Methods

mempty :: Distance a #

mappend :: Distance a -> Distance a -> Distance a #

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

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

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

Methods

star :: Distance a -> Distance a Source #

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

Defined in Algebra.Graph.Label

distance :: NonNegative a -> Distance a Source #

A non-negative distance.

getDistance :: Distance a -> NonNegative a Source #

Get the value of a distance.

data Capacity a Source #

A capacity is a non-negative value that can be finite or infinite. Capacities form a Dioid as follows:

zero  = 0
one   = capacity infinite
(<+>) = max
(<.>) = min
Instances
Num a => Bounded (Capacity a) Source # 
Instance details

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

Methods

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

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

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

Defined in Algebra.Graph.Label

Ord a => Ord (Capacity a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

compare :: Capacity a -> Capacity a -> Ordering #

(<) :: Capacity a -> Capacity a -> Bool #

(<=) :: Capacity a -> Capacity a -> Bool #

(>) :: Capacity a -> Capacity a -> Bool #

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

max :: Capacity a -> Capacity a -> Capacity a #

min :: Capacity a -> Capacity a -> Capacity a #

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

Defined in Algebra.Graph.Label

Methods

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

show :: Capacity a -> String #

showList :: [Capacity a] -> ShowS #

Ord a => Semigroup (Capacity a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

(<>) :: Capacity a -> Capacity a -> Capacity a #

sconcat :: NonEmpty (Capacity a) -> Capacity a #

stimes :: Integral b => b -> Capacity a -> Capacity a #

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

Defined in Algebra.Graph.Label

Methods

mempty :: Capacity a #

mappend :: Capacity a -> Capacity a -> Capacity a #

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

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

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

Methods

star :: Capacity a -> Capacity a Source #

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

Defined in Algebra.Graph.Label

capacity :: NonNegative a -> Capacity a Source #

A non-negative capacity.

getCapacity :: Capacity a -> NonNegative a Source #

Get the value of a capacity.

data Count a Source #

A count is a non-negative value that can be finite or infinite. Counts form a Semiring as follows:

zero  = 0
one   = 1
(<+>) = (+)
(<.>) = (*)
Instances
Num a => Bounded (Count a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

minBound :: Count a #

maxBound :: Count a #

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

Defined in Algebra.Graph.Label

Methods

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

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

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

Defined in Algebra.Graph.Label

Methods

(+) :: Count a -> Count a -> Count a #

(-) :: Count a -> Count a -> Count a #

(*) :: Count a -> Count a -> Count a #

negate :: Count a -> Count a #

abs :: Count a -> Count a #

signum :: Count a -> Count a #

fromInteger :: Integer -> Count a #

Ord a => Ord (Count a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

compare :: Count a -> Count a -> Ordering #

(<) :: Count a -> Count a -> Bool #

(<=) :: Count a -> Count a -> Bool #

(>) :: Count a -> Count a -> Bool #

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

max :: Count a -> Count a -> Count a #

min :: Count a -> Count a -> Count a #

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

Defined in Algebra.Graph.Label

Methods

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

show :: Count a -> String #

showList :: [Count a] -> ShowS #

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

Defined in Algebra.Graph.Label

Methods

(<>) :: Count a -> Count a -> Count a #

sconcat :: NonEmpty (Count a) -> Count a #

stimes :: Integral b => b -> Count a -> Count a #

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

Defined in Algebra.Graph.Label

Methods

mempty :: Count a #

mappend :: Count a -> Count a -> Count a #

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

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

Defined in Algebra.Graph.Label

Methods

star :: Count a -> Count a Source #

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

Defined in Algebra.Graph.Label

Methods

one :: Count a Source #

(<.>) :: Count a -> Count a -> 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.

newtype PowerSet a Source #

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 $ setProductWith mappend (getPowerSet x) (getPowerSet y)

Constructors

PowerSet 

Fields

Instances
Eq a => Eq (PowerSet a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

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

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

Ord a => Ord (PowerSet a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

compare :: PowerSet a -> PowerSet a -> Ordering #

(<) :: PowerSet a -> PowerSet a -> Bool #

(<=) :: PowerSet a -> PowerSet a -> Bool #

(>) :: PowerSet a -> PowerSet a -> Bool #

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

max :: PowerSet a -> PowerSet a -> PowerSet a #

min :: PowerSet a -> PowerSet a -> PowerSet a #

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

Defined in Algebra.Graph.Label

Methods

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

show :: PowerSet a -> String #

showList :: [PowerSet a] -> ShowS #

Ord a => Semigroup (PowerSet a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

(<>) :: PowerSet a -> PowerSet a -> PowerSet a #

sconcat :: NonEmpty (PowerSet a) -> PowerSet a #

stimes :: Integral b => b -> PowerSet a -> PowerSet a #

Ord a => Monoid (PowerSet a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

mempty :: PowerSet a #

mappend :: PowerSet a -> PowerSet a -> PowerSet a #

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

(Monoid a, Ord a) => Dioid (PowerSet a) Source # 
Instance details

Defined in Algebra.Graph.Label

(Monoid a, Ord a) => Semiring (PowerSet a) Source # 
Instance details

Defined in Algebra.Graph.Label

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

Defined in Algebra.Graph.Label

Methods

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

(>>) :: Minimum a -> Minimum b -> Minimum b #

return :: a -> Minimum a #

fail :: String -> Minimum a #

Functor Minimum Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

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

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

Applicative Minimum Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

pure :: a -> Minimum a #

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

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

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

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

IsList a => IsList (Minimum a) Source # 
Instance details

Defined in Algebra.Graph.Label

Associated Types

type Item (Minimum a) :: Type #

Methods

fromList :: [Item (Minimum a)] -> Minimum a #

fromListN :: Int -> [Item (Minimum a)] -> Minimum a #

toList :: Minimum a -> [Item (Minimum a)] #

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

Defined in Algebra.Graph.Label

Methods

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

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

Ord a => Ord (Minimum a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

compare :: Minimum a -> Minimum a -> Ordering #

(<) :: Minimum a -> Minimum a -> Bool #

(<=) :: Minimum a -> Minimum a -> Bool #

(>) :: Minimum a -> Minimum a -> Bool #

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

max :: Minimum a -> Minimum a -> Minimum a #

min :: Minimum a -> Minimum a -> Minimum a #

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

Defined in Algebra.Graph.Label

Methods

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

show :: Minimum a -> String #

showList :: [Minimum a] -> ShowS #

Ord a => Semigroup (Minimum a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

(<>) :: Minimum a -> Minimum a -> Minimum a #

sconcat :: NonEmpty (Minimum a) -> Minimum a #

stimes :: Integral b => b -> Minimum a -> Minimum a #

(Monoid a, Ord a) => Monoid (Minimum a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

mempty :: Minimum a #

mappend :: Minimum a -> Minimum a -> Minimum a #

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

(Monoid a, Ord a) => Dioid (Minimum a) Source # 
Instance details

Defined in Algebra.Graph.Label

(Monoid a, Ord a) => Semiring (Minimum a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

one :: Minimum a Source #

(<.>) :: Minimum a -> Minimum a -> Minimum a Source #

type Item (Minimum a) Source # 
Instance details

Defined in Algebra.Graph.Label

type Item (Minimum a) = Item a

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.

type Path a = [(a, a)] Source #

A path is a list of edges.

data Label a Source #

The type of free labels over the underlying set of symbols a. This data type is an instance of classes StarSemiring and Dioid.

Instances
Functor Label Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

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

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

IsList (Label a) Source # 
Instance details

Defined in Algebra.Graph.Label

Associated Types

type Item (Label a) :: Type #

Methods

fromList :: [Item (Label a)] -> Label a #

fromListN :: Int -> [Item (Label a)] -> Label a #

toList :: Label a -> [Item (Label a)] #

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

Defined in Algebra.Graph.Label

Methods

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

show :: Label a -> String #

showList :: [Label a] -> ShowS #

Semigroup (Label a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

(<>) :: Label a -> Label a -> Label a #

sconcat :: NonEmpty (Label a) -> Label a #

stimes :: Integral b => b -> Label a -> Label a #

Monoid (Label a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

mempty :: Label a #

mappend :: Label a -> Label a -> Label a #

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

StarSemiring (Label a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

star :: Label a -> Label a Source #

Semiring (Label a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

one :: Label a Source #

(<.>) :: Label a -> Label a -> Label a Source #

type Item (Label a) Source # 
Instance details

Defined in Algebra.Graph.Label

type Item (Label a) = a

isZero :: Label a -> Bool Source #

Check if a Label is zero.

type RegularExpression a = Label a Source #

A type synonym for regular expressions, built on top of free labels.

Combining edge labels

data Optimum o a Source #

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 = Distance Int and and a = Minimum (Path String), we obtain the shortest path semiring for computing the shortest path in an 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.

Constructors

Optimum 

Fields

Instances
(Eq o, Eq a) => Eq (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

(==) :: Optimum o a -> Optimum o a -> Bool #

(/=) :: Optimum o a -> Optimum o a -> Bool #

(Ord o, Ord a) => Ord (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

compare :: Optimum o a -> Optimum o a -> Ordering #

(<) :: Optimum o a -> Optimum o a -> Bool #

(<=) :: Optimum o a -> Optimum o a -> Bool #

(>) :: Optimum o a -> Optimum o a -> Bool #

(>=) :: Optimum o a -> Optimum o a -> Bool #

max :: Optimum o a -> Optimum o a -> Optimum o a #

min :: Optimum o a -> Optimum o a -> Optimum o a #

(Show o, Show a) => Show (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

showsPrec :: Int -> Optimum o a -> ShowS #

show :: Optimum o a -> String #

showList :: [Optimum o a] -> ShowS #

(Eq o, Monoid a, Monoid o) => Semigroup (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

(<>) :: Optimum o a -> Optimum o a -> Optimum o a #

sconcat :: NonEmpty (Optimum o a) -> Optimum o a #

stimes :: Integral b => b -> Optimum o a -> Optimum o a #

(Eq o, Monoid a, Monoid o) => Monoid (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

mempty :: Optimum o a #

mappend :: Optimum o a -> Optimum o a -> Optimum o a #

mconcat :: [Optimum o a] -> Optimum o a #

(Eq o, Dioid a, Dioid o) => Dioid (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

(Eq o, StarSemiring a, StarSemiring o) => StarSemiring (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

star :: Optimum o a -> Optimum o a Source #

(Eq o, Semiring a, Semiring o) => Semiring (Optimum o a) Source # 
Instance details

Defined in Algebra.Graph.Label

Methods

one :: Optimum o a Source #

(<.>) :: Optimum o a -> Optimum o a -> 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.

type CountShortestPaths e = Optimum (Distance e) (Count Integer) Source #

The Optimum semiring specialised to counting all shortest paths.

type WidestPath e a = Optimum (Capacity e) (Minimum (Path a)) Source #

The Optimum semiring specialised to finding the lexicographically smallest widest path.