HaLeX-1.1: HaLeX enables modelling, manipulation and animation of regular languagesSource codeContentsIndex
Language.HaLex.Ndfa
Portabilityportable
Stabilityprovisional
Maintainerjas@di.uminho.pt
Contents
Data type
Acceptance
Transformation
Transitions
Printing
Properties of Ndfa
Properties of States
Description

Non-Deterministic Finite Automata in Haskell.

Code Included in the Lecture Notes on Language Processing (with a functional flavour).

Synopsis
data Ndfa st sy = Ndfa [sy] [st] [st] [st] (st -> Maybe sy -> [st])
ndfaaccept :: Ord st => Ndfa st sy -> [sy] -> Bool
ndfawalk :: Ord st => (st -> Maybe sy -> [st]) -> [st] -> [sy] -> [st]
epsilon_closure :: Ord st => (st -> Maybe sy -> [st]) -> [st] -> [st]
ttNdfa2Ndfa :: (Eq st, Eq sy) => ([sy], [st], [st], [st], [(st, Maybe sy, st)]) -> Ndfa st sy
ndfaTransitionsFromTo :: Eq st => (st -> Maybe sy -> [st]) -> [sy] -> st -> st -> [Maybe sy]
ndfadestinationsFrom :: Ord st => (st -> Maybe sy -> [st]) -> [sy] -> st -> [st]
transitionTableNdfa :: Ndfa st sy -> [(st, Maybe sy, st)]
ndfareachedStatesFrom :: Ord st => (st -> Maybe sy -> [st]) -> [sy] -> st -> [st]
toHaskell :: Show fa => fa -> [Char] -> IO ()
renameNdfa :: Eq st => Ndfa st sy -> Int -> Ndfa Int sy
sizeNdfa :: Ndfa st sy -> Int
ndfadeadstates :: Ord st => Ndfa st sy -> [st]
ndfaIsStDead :: Ord st => (st -> Maybe sy -> [st]) -> [sy] -> [st] -> st -> Bool
ndfanumberIncomingArrows :: Eq st => (st -> Maybe sy -> [st]) -> [sy] -> [st] -> st -> Int
ndfanumberOutgoingArrows :: Ord st => (st -> Maybe sy -> [st]) -> [sy] -> st -> Int
Data type
data Ndfa st sy Source
Type of Non-Deterministic Finite Automata. Parameterized with the type st of states and sy of symbols.
Constructors
Ndfa [sy] [st] [st] [st] (st -> Maybe sy -> [st])
show/hide Instances
(Show st, Show sy, Ord st, Ord sy) => Fa Ndfa st sy
(Eq st, Show st, Show sy) => Show (Ndfa st sy)
Acceptance
ndfaacceptSource
:: Ord st
=> Ndfa st syAutomaton
-> [sy]Input symbols
-> Bool
Test whether the given automaton accepts the given list of input symbols.
ndfawalkSource
:: Ord st
=> st -> Maybe sy -> [st]Transition function
-> [st]Initial states
-> [sy]Input symbols
-> [st]Reached states
Execute the transition function of a Ndfa on an initial state and list of input symbol. Return the final state when all input symbols have been consumed.
epsilon_closureSource
:: Ord st
=> st -> Maybe sy -> [st]Transition function
-> [st]Current states
-> [st]Reached states
Compute the eplison closure of a Ndfa.
Transformation
ttNdfa2NdfaSource
:: (Eq st, Eq sy)
=> ([sy], [st], [st], [st], [(st, Maybe sy, st)])Tuple-based Ndfa
-> Ndfa st syAutomaton
Reconstruct a Ndfa from a transition table. Given a Ndfa expressed by a transition table (ie a list of triples of the form (Origin,Maybe Symbol,Destination) it constructs a Ndfa. The other elements of the input tuple are the vocabulary, a set of states, and the sets of initial and final states
Transitions
ndfaTransitionsFromTo :: Eq st => (st -> Maybe sy -> [st]) -> [sy] -> st -> st -> [Maybe sy]Source
Compute the labels with the same (giving) origin and destination
ndfadestinationsFromSource
:: Ord st
=> st -> Maybe sy -> [st]Transition Function
-> [sy]Vocabulary
-> stOrigin
-> [st]Destination States
Compute the destination states giving the origin state
transitionTableNdfaSource
::
=> Ndfa st syAutomaton
-> [(st, Maybe sy, st)]Transition table

Produce the transition table of a given Ndfa.

Given a Ndfa it returns a list of triples of the form (Origin,Symbol,Destination) defining all the transitions of the Ndfa.

ndfareachedStatesFromSource
:: Ord st
=> st -> Maybe sy -> [st]Transition Function
-> [sy]Vocabulary
-> stOrigin
-> [st]Reached States
Compute the states that can be reached from a given state according to a given transition function and vocabulary
Printing
toHaskellSource
:: Show fa
=> faAutomaton
-> [Char]Haskell module or file name
-> IO ()

Helper function to show the transition function of a Ndfa.

Produce the transition table of a given finite automaton.

renameNdfaSource
:: Eq st
=> Ndfa st syAutomaton
-> IntInitial integer number
-> Ndfa Int syRenamed Automaton
Renames a Ndfa.
Properties of Ndfa
sizeNdfaSource
::
=> Ndfa st syAutomaton
-> IntSize
The size of an automaton is the number of its states.
ndfadeadstatesSource
:: Ord st
=> Ndfa st syAutomaton
-> [st]Dead States
Compute the dead states of a Ndfa
Properties of States
ndfaIsStDeadSource
:: Ord st
=> st -> Maybe sy -> [st]Transition Function
-> [sy]Vocabulary
-> [st]Set of Final States
-> stState
-> Bool
Checks whether a Ndfa state is dead or not.
ndfanumberIncomingArrowsSource
:: Eq st
=> st -> Maybe sy -> [st]Transition Function
-> [sy]Vocabulary
-> [st]Set of States
-> stDestination
-> IntNumber of Arrows
Compute the number of incoming arrows for a given state
ndfanumberOutgoingArrowsSource
:: Ord st
=> st -> Maybe sy -> [st]Transition Function
-> [sy]Vocabulary
-> stOrigin
-> IntNumber of Arrows
Compute the number of outgoing arrows for a given state
Produced by Haddock version 2.3.0