language-toolkit-1.2.0.1: A set of tools for analyzing languages via logic and automata
Copyright(c) 2014-2024 Dakotah Lambert
LicenseMIT
Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • Cpp
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses

LTK.FSA

Description

The purpose of this module is to define an interface to a generic, reusable impementation of finite-state automata (FSAs). The primary motivation for this is to allow for efficient analysis of stringsets in a linguistic context, although the nature of the project should allow more general use.

Synopsis

Documentation

data FSA n e Source #

A finite-state automaton (FSA) is represented by a directed graph, the edges of which are labelled by formal symbols.

Constructors

FSA 

Fields

Instances

Instances details
HasAlphabet (FSA n) Source # 
Instance details

Defined in LTK.FSA

Methods

alphabet :: FSA n e -> Set e Source #

(Enum n, Ord n, Ord e) => Monoid (FSA n e) Source # 
Instance details

Defined in LTK.FSA

Methods

mempty :: FSA n e #

mappend :: FSA n e -> FSA n e -> FSA n e #

mconcat :: [FSA n e] -> FSA n e #

(Enum n, Ord n, Ord e) => Semigroup (FSA n e) Source # 
Instance details

Defined in LTK.FSA

Methods

(<>) :: FSA n e -> FSA n e -> FSA n e #

sconcat :: NonEmpty (FSA n e) -> FSA n e #

stimes :: Integral b => b -> FSA n e -> FSA n e #

(Read e, Read n, Ord e, Ord n) => Read (FSA n e) Source # 
Instance details

Defined in LTK.FSA

Methods

readsPrec :: Int -> ReadS (FSA n e) #

readList :: ReadS [FSA n e] #

readPrec :: ReadPrec (FSA n e) #

readListPrec :: ReadPrec [FSA n e] #

(Show e, Show n) => Show (FSA n e) Source # 
Instance details

Defined in LTK.FSA

Methods

showsPrec :: Int -> FSA n e -> ShowS #

show :: FSA n e -> String #

showList :: [FSA n e] -> ShowS #

(NFData n, NFData e) => NFData (FSA n e) Source # 
Instance details

Defined in LTK.FSA

Methods

rnf :: FSA n e -> () #

(Ord e, Ord n) => Eq (FSA n e) Source # 
Instance details

Defined in LTK.FSA

Methods

(==) :: FSA n e -> FSA n e -> Bool #

(/=) :: FSA n e -> FSA n e -> Bool #

(Ord e, Ord n) => Ord (FSA n e) Source # 
Instance details

Defined in LTK.FSA

Methods

compare :: FSA n e -> FSA n e -> Ordering #

(<) :: FSA n e -> FSA n e -> Bool #

(<=) :: FSA n e -> FSA n e -> Bool #

(>) :: FSA n e -> FSA n e -> Bool #

(>=) :: FSA n e -> FSA n e -> Bool #

max :: FSA n e -> FSA n e -> FSA n e #

min :: FSA n e -> FSA n e -> FSA n e #

(Enum n, Ord n, Ord e) => Container (FSA n e) [e] Source # 
Instance details

Defined in LTK.FSA

Methods

isIn :: FSA n e -> [e] -> Bool Source #

isNotIn :: FSA n e -> [e] -> Bool Source #

contains :: [e] -> FSA n e -> Bool Source #

doesNotContain :: [e] -> FSA n e -> Bool Source #

isEmpty :: FSA n e -> Bool Source #

union :: FSA n e -> FSA n e -> FSA n e Source #

intersection :: FSA n e -> FSA n e -> FSA n e Source #

difference :: FSA n e -> FSA n e -> FSA n e Source #

symmetricDifference :: FSA n e -> FSA n e -> FSA n e Source #

empty :: FSA n e Source #

insert :: [e] -> FSA n e -> FSA n e Source #

singleton :: [e] -> FSA n e Source #

isSubsetOf :: FSA n e -> FSA n e -> Bool Source #

isSupersetOf :: FSA n e -> FSA n e -> Bool Source #

isProperSubsetOf :: FSA n e -> FSA n e -> Bool Source #

isProperSupersetOf :: FSA n e -> FSA n e -> Bool Source #

states :: (Ord e, Ord n) => FSA n e -> Set (State n) Source #

The collection of all states in an FSA.

isNull :: (Ord e, Ord n) => FSA n e -> Bool Source #

True iff the input accepts no strings.

follow :: (Ord n, Ord e) => FSA n e -> [Symbol e] -> State n -> Set (State n) Source #

The generalized \(\delta\) function, follow each symbol in a string in order.

Since: 0.2

accepts :: (Ord e, Ord n) => FSA n e -> [e] -> Bool Source #

Returns whether the given FSA lands in a final state after processing the given sequence.

Since: 1.1

Constructing simple automata

totalWithAlphabet :: (Ord e, Enum n, Ord n) => Set e -> FSA n e Source #

An automaton accepting every string over a given alphabet.

emptyWithAlphabet :: (Ord e, Enum n, Ord n) => Set e -> FSA n e Source #

An automaton accepting no strings over a given alphabet.

emptyLanguage :: (Ord e, Ord n, Enum n) => FSA n e Source #

A specialization of emptyWithAlphabet where the alphabet is itself empty.

singletonWithAlphabet :: (Ord e, Enum n, Ord n) => Set e -> [e] -> FSA n e Source #

An automaton that accepts only the given string, over a given alphabet.

singletonLanguage :: (Ord e, Enum n, Ord n) => [e] -> FSA n e Source #

An automaton that accepts only the given string, over the minimal alphabet required to represent this string.

Derived automata

brzozowskiDerivative :: (Ord e, Ord n) => [e] -> FSA n e -> FSA n e Source #

Return an FSA representing possible continuations from a given sequence of symbols. If the input automaton is not complete then the output may have no states when given incompatible input.

Since: 1.0

loopify :: (Ord a, Ord b) => FSA a b -> FSA a b Source #

Add self-loops on all symbols to all edges to compute an upward closure.

Since: 1.1

tierify :: (Ord a, Ord b) => Set b -> FSA a (Maybe b) -> FSA a (Maybe b) Source #

Convert a semantic automaton that represents a Local constraint into a new one that represents the same constraint in the associated Tier-Local class.

neutralize :: (Ord a, Ord b) => Set b -> FSA a b -> FSA a b Source #

Allow a given set of symbols to be freely inserted or deleted. In other words, make those symbols neutral.

Since: 1.1

quotLeft :: (Ord e, Ord n1, Ord n2) => FSA n1 e -> FSA n2 e -> FSA (Maybe (Either n1 ()), Maybe n2) e Source #

Return an FSA representing possible continuations in the second language from strings in the first language. In other words, quotLeft a b returns \(\{w : x\in a, xw\in b\}\).

Since: 1.0

quotMid :: (Ord e, Ord n1, Ord n2, Ord n3) => FSA n1 e -> FSA n2 e -> FSA n3 e -> FSA Integer e Source #

quotMid a b c is \(\{wz : wx\in a, yx\in b, yz\in c\}\). This lifts strings to a group, placing b-inverse between a and c. The time complexity of this function is abysmal, performing a left and a right quotient for each state in b.

Since: 1.0

quotRight :: (Ord e, Ord n1, Ord n2) => FSA n1 e -> FSA n2 e -> FSA Integer e Source #

Return an FSA representing possible strings in the first language which end with a string in the second language. In other words, quotRight a b is \(\{w : wx\in a, x\in b\}\).

Since: 1.0

kleeneClosure :: (Ord n, Ord e) => FSA n e -> FSA (Either n Bool) e Source #

The Kleene Closure of an automaton is the free monoid under concatenation generated by all strings in the automaton's represented stringset. The resulting automaton is nondeterministic.

powersetGraph :: (Ord e, Ord n) => FSA n e -> FSA (Set n) e Source #

Given an automaton \(M\) with stateset \(Q\), the powerset graph of \(M\) is an automaton with stateset in the powerset of \(Q\). From a node \(\{q_1,q_2,\ldots,q_n\}\), there is an edge labelled \(\sigma\) that leads to \(\{\delta(q_1,\sigma), \delta(q_2,\sigma), \ldots, \delta(q_n, \sigma)\}\), where \(\delta\) is the transition function of the input. The initial state is \(Q\), and the result is complete.

syntacticMonoid :: (Ord e, Ord n) => FSA n e -> FSA ([Maybe n], [Symbol e]) e Source #

Given an automaton \(M\) with stateset \(Q\), the syntactic monoid of \(M\) is an automaton with stateset in \((Q\rightarrow Q)\). Here these functions are represented by lists, where \(q_i\) maps to the \(i^\text{th}\) element of the list. From a node \(\langle q_1,q_2,\ldots,q_n\rangle\), there is an edge labelled \(\sigma\) that leads to \(\langle\delta(q_1,\sigma), \delta(q_2,\sigma), \ldots, \delta(q_n, \sigma)\rangle\), where \(\delta\) is the transition function of the input. The initial state is the identity function, and the result is complete.

syntacticOMonoid :: (Ord n, Ord e) => FSA n e -> OrderedSemigroup GeneratedAction Source #

The syntactic ordered monoid is the syntactic monoid alongside the same order as in the syntactic ordered semigroup. Return the transition monoid: this is syntactic if the automaton is minimal or shaped like the Cayley graph of its monoid.

Since: 1.2

syntacticSemigroup :: (Ord n, Ord e) => FSA n e -> GeneratedAction Source #

Consider each alphabetic symbol as a function from state to state. The semigroup generated by these functions is the transformation semigroup of a deterministic automaton. Return the transition semigroup: this is syntactic if the automaton is minimal or shaped like the Cayley graph of its monoid.

Since: 1.2

syntacticOSemigroup :: (Ord n, Ord e) => FSA n e -> OrderedSemigroup GeneratedAction Source #

The syntactic ordered semigroup is the syntactic semigroup alongside an order, where \(x\leq y\) if and only if whenever \(uyv\) maps the inital state to a final state, so too does \(uxv\). Return the transition semigroup: this is syntactic if the automaton is minimal or shaped like the Cayley graph of its monoid.

Since: 1.2

residue :: (Ord n, Ord e, Enum n) => FSA n e -> FSA n e -> FSA n e Source #

(residue a b) is equivalent to (difference a b). In the context of an approximation and its source, represents the strings accepted by the approximation that should not be.

coresidue :: (Ord n, Ord e, Enum n) => FSA n e -> FSA n e -> FSA n e Source #

(coresidue a b) is equivalent to (complement (residue a b)). In the context of an approximation and its source, represents unmet constraints of the source.

orderGraph :: (Ord n, Ord e) => (n -> n -> Bool) -> FSA n e -> FSA n () Source #

Create a graph whose vertices are states of the given FSA and where a directed edge exists from \(p\) to \(q\) if and only if \(p\mathcal{R}q\) under the given relation.

Since: 1.2

Primitive ideals

primitiveIdeal2 :: (Ord n, Ord e) => FSA (n, [Symbol e]) e -> State (n, [Symbol e]) -> Set (State (n, [Symbol e])) Source #

The primitive two-sided ideal.

Since: 0.2

primitiveIdealL :: (Ord n, Ord e) => FSA (n, [Symbol e]) e -> State (n, [Symbol e]) -> Set (State (n, [Symbol e])) Source #

The primitive left ideal.

Since: 0.2

primitiveIdealR :: (Ord n, Ord e) => FSA n e -> State n -> Set (State n) Source #

The primitive right ideal.

Since: 0.2

scc :: (Ord n, Ord e) => FSA n e -> n -> Set n Source #

Return the set of states in the same strongly connected component as the given state.

Since: 1.2

Transformations

sccGraph :: (Ord n, Ord e) => FSA n e -> FSA (Set n) () Source #

Return a graph of the strongly connected components of the given FSA and the directed connections between them.

Since: 1.2

flatIntersection :: (Enum n, Ord n, NFData n, Ord e, NFData e) => [FSA n e] -> FSA n e Source #

Intersect all given automata, in parallel if possible. An empty intersection is undefined. In theory it should be the total language over the total alphabet, but the latter cannot be defined. Intermediate results are evaluated to normal form.

flatUnion :: (Enum n, Ord n, NFData n, Ord e, NFData e) => [FSA n e] -> FSA n e Source #

Union all given automata, in parallel if possible. An empty union is defined as the empty language over an empty alphabet. Intermediate results are evaluated to normal form.

flatInfiltration :: (Enum n, Ord n, NFData n, Ord e, NFData e) => [FSA n e] -> FSA n e Source #

Infiltrate all given automata, in parallel if possible. An empty infiltration is defined as the singleton language over an empty alphabet containing only the empty string. Intermediate results are evaluated to normal form.

Since: 1.1

flatShuffle :: (Enum n, Ord n, NFData n, Ord e, NFData e) => [FSA n e] -> FSA n e Source #

Shuffle all given automata, in parallel if possible. An empty shuffle is defined as the singleton language over an empty alphabet containing only the empty string. Intermediate results are evaluated to normal form.

Since: 1.1

reverse :: (Ord e, Ord n) => FSA n e -> FSA n e Source #

The reversal of an automaton accepts the reversals of all strings accepted by the original.

autDifference :: (Ord e, Ord n1, Ord n2) => FSA n1 e -> FSA n2 e -> FSA (Maybe n1, Maybe (Set n2)) e Source #

Returns an FSA accepting all and only those strings accepted by the first input but rejected by the second.

Since: 1.1

autInfiltration :: (Ord e, Ord n1, Ord n2) => FSA n1 e -> FSA n2 e -> FSA (Maybe n1, Maybe n2) e Source #

Returns the infiltration product of its two input autamata.

Since: 1.1

autShuffle :: (Ord e, Ord n1, Ord n2) => FSA n1 e -> FSA n2 e -> FSA (Maybe n1, Maybe n2) e Source #

Returns the shuffle product of its two input autamata.

Since: 1.1

autStrictOrderOverlay :: (Ord n1, Ord n2, Ord e) => FSA n1 e -> FSA n2 e -> FSA (Maybe (Either (Maybe n1) n2, Maybe n1)) e Source #

Given an FSA representing an event \(x\) and another representing an event \(y\), returns the FSA accepting all and only those strings that begin with \(x\) and end with \(y\) such that the beginning of \(y\) lies strictly later than the beginning of \(x\) yet no later than the end of \(x\).

Since: 1.2

complement :: (Ord e, Ord n) => FSA n e -> FSA (Set n) e Source #

Returns an FSA accepting all and only those strings not accepted by the input.

complementDeterministic :: (Ord e, Ord n) => FSA n e -> FSA n e Source #

Returns the complement of a deterministic FSA. The precondition that the input is deterministic is not checked.

determinize :: (Ord e, Ord n) => FSA n e -> FSA (Set n) e Source #

Returns a deterministic automaton representing the same stringset as the potentially nondeterministic input.

Minimization

minimize :: (Ord e, Ord n) => FSA n e -> FSA (Set (Set n)) e Source #

Returns a deterministic FSA recognizing the same stringset as the input, with a minimal number of states.

minimizeDeterministic :: (Ord e, Ord n) => FSA n e -> FSA (Set n) e Source #

Returns a deterministic FSA recognizing the same stringset as the input, with a minimal number of states. The precondition that the input is deterministic is not checked.

normalize :: (Ord e, Ord n) => FSA n e -> FSA Integer e Source #

Returns a normal form of the input. An FSA is in normal form if it is minimal and deterministic, and contains neither unreachable states nor nonaccepting sinks. Node labels are irrelevant, so Integer is used as a default representation.

trimUnreachables :: (Ord e, Ord n) => FSA n e -> FSA n e Source #

The input automaton with unreachable states removed.

Since: 1.0

Equivalence Classes

minimizeOver :: (Ord e, Ord n) => (FSA n e -> Set (Set (State n))) -> FSA n e -> FSA (Set n) e Source #

Returns a non-necessarily deterministic FSA minimized over a given relation. Some, but not all, relations do guarantee deterministic output. The precondition that the input is deterministic is not checked.

nerode :: (Ord e, Ord n) => FSA n e -> Set (Set (State n)) Source #

Two strings \(u\) and \(v\) are equivalent iff for all strings \(w\), \(uw\) and \(vw\) lead to states in the same equivalence class.

hEquivalence :: (Ord n, Ord e) => FSA (n, [Symbol e]) e -> Set (Set (State (n, [Symbol e]))) Source #

Given an automaton whose syntactic monoid is \(M\), two strings \(u\) and \(v\) are equivalent if \(Mu=Mv\) and \(uM=vM\).

Since: 0.2

jEquivalence :: (Ord e, Ord n) => FSA ([Maybe n], [Symbol e]) e -> Set (Set (State ([Maybe n], [Symbol e]))) Source #

Given an automaton whose syntactic monoid is \(M\), two strings \(u\) and \(v\) are equivalent iff \(MuM=MvM\)

trivialUnder :: (FSA n e -> Set (Set (State n))) -> FSA n e -> Bool Source #

An automaton is considered trivial under some equivalence relation if each of its equivalence classes is singleton.

Since: 0.2

Alphabetic Transformations

extendAlphabetTo :: (Ord a, Ord b) => Set b -> FSA a b -> FSA (Maybe Integer, Maybe a) b Source #

Add missing symbols to the alphabet of an automaton. The result is an automaton with at least the provided alphabet that licenses exactly the same set of strings as the input.

semanticallyExtendAlphabetTo :: (Ord a, Ord b) => Set b -> FSA a (Maybe b) -> FSA a (Maybe b) Source #

Add missing symbols to the alphabet of an automaton. As the symbol Nothing is taken to represent any symbol not currently in the alphabet, new edges are added in parallel to existing edges labelled by Nothing.

contractAlphabetTo :: (Ord a, Ord b) => Set b -> FSA a b -> FSA a b Source #

Remove symbols from the alphabet of an automaton.

forceAlphabetTo :: (Ord a, Ord b) => Set b -> FSA a b -> FSA (Maybe Integer, Maybe a) b Source #

Ignore the alphabet of an automaton and use a given alphabet instead.

desemantify :: (Ord a, Ord b) => FSA a (Maybe b) -> FSA a b Source #

Remove the semantic Nothing edges from an automaton and reflect this change in the type.

renameSymbolsBy :: (Ord e, Ord e1, Ord n) => (e -> e1) -> FSA n e -> FSA n e1 Source #

Transform the edge labels of an automaton using a given function. If this function is not injective, the resulting FSA may not be deterministic even if the original was.

Transformations of State labels

renameStatesBy :: (Ord e, Ord n, Ord n1) => (n -> n1) -> FSA n e -> FSA n1 e Source #

Transform the node labels of an automaton using a given function. If this function is not injective, the resulting FSA may not be deterministic even if the original was.

renameStates :: (Ord e, Ord n, Ord n1, Enum n1) => FSA n e -> FSA n1 e Source #

Equivalent to renameStatesBy \(f\), where \(f\) is an arbitrary injective function.

Miscellaneous

commonPrefix :: (Ord e, Ord n) => FSA n e -> Maybe [e] Source #

Return Just the longest sequence \(u\) of symbols such that every word in the language is \(uv\) for some \(v\). If the language is empty, return None.

Since: 1.2

commonSuffix :: (Ord e, Ord n) => FSA n e -> Maybe [e] Source #

Return Just the longest sequence \(v\) of symbols such that every word in the language is \(uv\) for some \(u\). If the language is empty, return None.

Since: 1.2

newtype State n Source #

A vertex of the graph representation of an FSA is a State, which can be labelled with any arbitrary value, so long as every vertex of a single automaton is labelled with a distinct value of the same type.

Constructors

State 

Fields

Instances

Instances details
Applicative State Source # 
Instance details

Defined in LTK.FSA

Methods

pure :: a -> State a #

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

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

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

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

Functor State Source # 
Instance details

Defined in LTK.FSA

Methods

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

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

Monad State Source # 
Instance details

Defined in LTK.FSA

Methods

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

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

return :: a -> State a #

Monoid n => Monoid (State n) Source # 
Instance details

Defined in LTK.FSA

Methods

mempty :: State n #

mappend :: State n -> State n -> State n #

mconcat :: [State n] -> State n #

Semigroup n => Semigroup (State n) Source # 
Instance details

Defined in LTK.FSA

Methods

(<>) :: State n -> State n -> State n #

sconcat :: NonEmpty (State n) -> State n #

stimes :: Integral b => b -> State n -> State n #

Read n => Read (State n) Source # 
Instance details

Defined in LTK.FSA

Show n => Show (State n) Source # 
Instance details

Defined in LTK.FSA

Methods

showsPrec :: Int -> State n -> ShowS #

show :: State n -> String #

showList :: [State n] -> ShowS #

NFData n => NFData (State n) Source # 
Instance details

Defined in LTK.FSA

Methods

rnf :: State n -> () #

Eq n => Eq (State n) Source # 
Instance details

Defined in LTK.FSA

Methods

(==) :: State n -> State n -> Bool #

(/=) :: State n -> State n -> Bool #

Ord n => Ord (State n) Source # 
Instance details

Defined in LTK.FSA

Methods

compare :: State n -> State n -> Ordering #

(<) :: State n -> State n -> Bool #

(<=) :: State n -> State n -> Bool #

(>) :: State n -> State n -> Bool #

(>=) :: State n -> State n -> Bool #

max :: State n -> State n -> State n #

min :: State n -> State n -> State n #

data Symbol e Source #

The label of a Transition.

Constructors

Epsilon

The edge may be taken without consuming input.

Symbol e

The edge requires consuming this symbol.

Instances

Instances details
Functor Symbol Source # 
Instance details

Defined in LTK.FSA

Methods

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

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

Read e => Read (Symbol e) Source # 
Instance details

Defined in LTK.FSA

Show e => Show (Symbol e) Source # 
Instance details

Defined in LTK.FSA

Methods

showsPrec :: Int -> Symbol e -> ShowS #

show :: Symbol e -> String #

showList :: [Symbol e] -> ShowS #

NFData e => NFData (Symbol e) Source # 
Instance details

Defined in LTK.FSA

Methods

rnf :: Symbol e -> () #

Eq e => Eq (Symbol e) Source # 
Instance details

Defined in LTK.FSA

Methods

(==) :: Symbol e -> Symbol e -> Bool #

(/=) :: Symbol e -> Symbol e -> Bool #

Ord e => Ord (Symbol e) Source # 
Instance details

Defined in LTK.FSA

Methods

compare :: Symbol e -> Symbol e -> Ordering #

(<) :: Symbol e -> Symbol e -> Bool #

(<=) :: Symbol e -> Symbol e -> Bool #

(>) :: Symbol e -> Symbol e -> Bool #

(>=) :: Symbol e -> Symbol e -> Bool #

max :: Symbol e -> Symbol e -> Symbol e #

min :: Symbol e -> Symbol e -> Symbol e #

unsymbols :: (Collapsible s, Container c e, Monoid c) => s (Symbol e) -> c Source #

Remove Epsilon from a Collapsible of Symbol and present the unwrapped results as a new Container.

data Transition n e Source #

The edges of an FSA.

Constructors

Transition 

Fields

Instances

Instances details
Functor (Transition n) Source # 
Instance details

Defined in LTK.FSA

Methods

fmap :: (a -> b) -> Transition n a -> Transition n b #

(<$) :: a -> Transition n b -> Transition n a #

(Read e, Read n) => Read (Transition n e) Source # 
Instance details

Defined in LTK.FSA

(Show e, Show n) => Show (Transition n e) Source # 
Instance details

Defined in LTK.FSA

Methods

showsPrec :: Int -> Transition n e -> ShowS #

show :: Transition n e -> String #

showList :: [Transition n e] -> ShowS #

(NFData n, NFData e) => NFData (Transition n e) Source # 
Instance details

Defined in LTK.FSA

Methods

rnf :: Transition n e -> () #

(Eq e, Eq n) => Eq (Transition n e) Source # 
Instance details

Defined in LTK.FSA

Methods

(==) :: Transition n e -> Transition n e -> Bool #

(/=) :: Transition n e -> Transition n e -> Bool #

(Ord e, Ord n) => Ord (Transition n e) Source # 
Instance details

Defined in LTK.FSA

Methods

compare :: Transition n e -> Transition n e -> Ordering #

(<) :: Transition n e -> Transition n e -> Bool #

(<=) :: Transition n e -> Transition n e -> Bool #

(>) :: Transition n e -> Transition n e -> Bool #

(>=) :: Transition n e -> Transition n e -> Bool #

max :: Transition n e -> Transition n e -> Transition n e #

min :: Transition n e -> Transition n e -> Transition n e #