| Copyright | (c) João Saraiva 20012002200320042005 2016 | 
|---|---|
| License | LGPL | 
| Maintainer | saraiva@di.uminho.pt | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Language.HaLex.Ndfa
Description
Non-Deterministic Finite Automata in Haskell.
Code Included in the Lecture Notes on Language Processing (with a functional flavour).
- 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 t1, Show a, Show t, Eq t) => [t1] -> [a] -> (t1 -> Maybe a -> [t]) -> 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
 - ndfaIsSyncState :: 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.
Acceptance
Test whether the given automaton accepts the given list of input symbols.
Arguments
| :: 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.
Arguments
| :: Ord st | |
| => (st -> Maybe sy -> [st]) | Transition function  | 
| -> [st] | Current states  | 
| -> [st] | Reached states  | 
Compute the eplison closure of a Ndfa.
Transformation
Transitions
ndfaTransitionsFromTo :: Eq st => (st -> Maybe sy -> [st]) -> [sy] -> st -> st -> [Maybe sy] Source #
Compute the labels with the same (giving) origin and destination
Arguments
| :: Ord st | |
| => (st -> Maybe sy -> [st]) | Transition Function  | 
| -> [sy] | Vocabulary  | 
| -> st | Origin  | 
| -> [st] | Destination States  | 
Compute the destination states giving the origin state
ndfareachedStatesFrom Source #
Arguments
| :: Ord st | |
| => (st -> Maybe sy -> [st]) | Transition Function  | 
| -> [sy] | Vocabulary  | 
| -> st | Origin  | 
| -> [st] | Reached States  | 
Compute the states that can be reached from a given state according to a given transition function and vocabulary
Printing
Produce the transition table of a given finite automaton.
Renames a Ndfa.
showNdfaDelta :: (Show t1, Show a, Show t, Eq t) => [t1] -> [a] -> (t1 -> Maybe a -> [t]) -> String -> String Source #
Helper function to show the transition function of a Ndfa.
Properties of Ndfa
The size of an automaton is the number of its states.
Compute the dead states of a Ndfa
Properties of States
Arguments
| :: Ord st | |
| => (st -> Maybe sy -> [st]) | Transition Function  | 
| -> [sy] | Vocabulary  | 
| -> [st] | Set of Final States  | 
| -> st | State  | 
| -> Bool | 
Checks whether a Ndfa state is dead or not.
Arguments
| :: Ord st | |
| => (st -> Maybe sy -> [st]) | Transition Function  | 
| -> [sy] | Vocabulary  | 
| -> [st] | Set of Final States  | 
| -> st | State  | 
| -> Bool | 
Checks whether a Ndfa state is a sync state or not