|
| Language.HaLex.Ndfa | | Portability | portable | | Stability | provisional | | Maintainer | jas@di.uminho.pt |
|
|
|
|
|
| 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 | | | showNdfaDelta :: (Show a1, Show t, Show a, Eq a) => [a1] -> [t] -> (a1 -> Maybe t -> [a]) -> String -> String | | | 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
|
|
|
| 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]) | |
| Instances | |
|
|
| Acceptance
|
|
|
| :: Ord st | | | => Ndfa st sy | Input symbols
| | -> [sy] | | | -> Bool | | | Test whether the given automaton accepts the given list of
input symbols.
|
|
|
|
| :: Ord st | | | => st -> Maybe sy -> [st] | Initial states
| | -> [st] | Input symbols
| | -> [sy] | Reached states
| | -> [st] | | | 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.
|
|
|
|
| :: Ord st | | | => st -> Maybe sy -> [st] | Current states
| | -> [st] | Reached states
| | -> [st] | | | Compute the eplison closure of a Ndfa.
|
|
|
| Transformation
|
|
|
| :: (Eq st, Eq sy) | | | => ([sy], [st], [st], [st], [(st, Maybe sy, st)]) | Automaton
| | -> Ndfa st sy | | | 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
|
|
|
| :: Ord st | | | => st -> Maybe sy -> [st] | Vocabulary
| | -> [sy] | Origin
| | -> st | Destination States
| | -> [st] | | | Compute the destination states giving the origin state
|
|
|
|
| :: | | | => Ndfa st sy | Transition table
| | -> [(st, Maybe sy, st)] | | 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.
|
|
|
|
| :: Ord st | | | => st -> Maybe sy -> [st] | Vocabulary
| | -> [sy] | Origin
| | -> st | Reached States
| | -> [st] | | | Compute the states that can be reached from a given state
according to a given transition function and vocabulary
|
|
|
| Printing
|
|
|
| :: Show fa | | | => fa | Haskell module or file name
| | -> [Char] | | | -> IO () | | Helper function to show the transition function of a Ndfa.
Produce the transition table of a given finite automaton.
|
|
|
|
|
|
|
|
| Properties of Ndfa
|
|
|
| :: | | | => Ndfa st sy | Size
| | -> Int | | | The size of an automaton is the number of its states.
|
|
|
|
| :: Ord st | | | => Ndfa st sy | Dead States
| | -> [st] | | | Compute the dead states of a Ndfa
|
|
|
| Properties of States
|
|
|
| :: Ord st | | | => st -> Maybe sy -> [st] | Vocabulary
| | -> [sy] | Set of Final States
| | -> [st] | State
| | -> st | | | -> Bool | | | Checks whether a Ndfa state is dead or not.
|
|
|
| ndfanumberIncomingArrows | Source |
|
| :: Eq st | | | => st -> Maybe sy -> [st] | Vocabulary
| | -> [sy] | Set of States
| | -> [st] | Destination
| | -> st | Number of Arrows
| | -> Int | | | Compute the number of incoming arrows for a given state
|
|
|
| ndfanumberOutgoingArrows | Source |
|
| :: Ord st | | | => st -> Maybe sy -> [st] | Vocabulary
| | -> [sy] | Origin
| | -> st | Number of Arrows
| | -> Int | | | Compute the number of outgoing arrows for a given state
|
|
|
| Produced by Haddock version 2.6.0 |