Non Deterministic Finite Automata (NFA)

The definition of DFA is easily extended to nondeterministic finite automata simply by changing the type of the transition function.

type NFA st = ([st],[Char],st -> Char -> [st],st,[st])

Notice that the above definition corresponds to NFA without ϵ-transitions. We define one more type corresponding to NFAs that can follow a transition without reading any input. We model this by making the Char input to the transition function optional.

type NFAeps st = ([st],[Char],st -> Maybe Char -> [st],st,[st])

It easy to see that DFAs can be converted into equivalent NFAs, and NFAs can be converted into equivalent NFA with ϵ-transitions.

convertDFA2NFA :: DFA st -> NFA st
convertDFA2NFA (qs,sigma,delta,s,fs) = (qs,sigma,delta',s,fs)
  where delta' q a = [delta q a]

convertNFA2NFAeps :: NFA st -> NFAeps st
convertNFA2NFAeps (qs,sigma,delta',s,fs) = (qs,sigma,delta'',s,fs)
  where delta'' q (Just a) = delta' q a
        delta'' q Nothing  = []

convertDFA2NFAeps :: DFA st -> NFAeps st
convertDFA2NFAeps = convertNFA2NFAeps . convertDFA2NFA

The last function simply combines the two transformations into a single one that turns any DFA into a corresponding NFAeps. Notice how we were able to turn DFAs into NFAs without changing the set of states: essentially all we had to do was to change the syntax of the transition function, so that it outputs singleton sets rather than single elements.

Converting NFAs into DFAs

Next, we turn into the reverse transformations, showing that for any nondeterministic automaton, there is an equivalent deterministic one. We first consider NFAs without ϵ-transitions. The following function directly implements the powerset construction described in the textbook. We represent sets of states by listing the elements in ascending order (and without repetitions), so that each set corresponds to precisely one list. The transformation uses the standard library functions sort to sort a list, and nub to remove repeated elements.

convertNFA2DFA :: (Ord st) => NFA st -> DFA [st]
convertNFA2DFA (qs,sigma,delta,s,fs) = (qs0,sigma,delta0,[s],fs0)
  where qs0 = subsequences (sort qs)
        delta0 ql a = sort (nub (concat [ delta q a | q <- ql ]))
        fs0 = [ ql | ql <- qs0, intersect ql fs /= [] ]

Next, we turn to NFAs with ϵ-transitions. To this end, it is useful to first define a function computing the transitive closure of a set. Given a function f : X → 2X, the transitive closure of a set Y ⊆ X under f is the set of all elements that can be obtained from X by applying f any finite number of times. As usual, we represent sets as lists of elements.

transitiveClosure :: (Eq a) => (a -> [a]) -> [a] -> [a]
transitiveClosure f xs = 
  let ys = nub (concat (map f xs)) \\ xs
  in if (null ys) then xs
     else transitiveClosure f (xs ++ ys)

Using this function, it is easy to eliminate ϵ-transitions from an NFA.

convertNFAeps2NFA :: (Ord st) => NFAeps st -> NFA st
convertNFAeps2NFA (qs,sigma,delta,s,fs) = (qs,sigma,delta0,s,fs0)
  where delta0 q a = concat [delta q' (Just a) | q' <- eps [q]]
        fs0 = [q | q <- qs, intersect (eps [q]) fs /= []]
        eps = transitiveClosure (\x -> delta x Nothing)

convertNFAeps2DFA :: (Ord st) => NFAeps st -> DFA [st]
convertNFAeps2DFA = convertNFA2DFA . convertNFAeps2NFA

Other useful functions

The transitive closure operation used to remove ϵ-transitions can be used to defined several other useful functions. For example, we can use it to define the set of reachable states of an automaton, i.e., the states that can be reached from the start state using any sequence of zero or more transitions.

reachableStatesNFA :: (Eq st) => NFA st -> [st]
reachableStatesNFA (_,alphabet,delta,startState,_) =
  let f q = nub (concat [ delta q a | a <- alphabet])
  in transitiveClosure f [startState]

Here we defined the function for NFAs. The set of reachable states of a DFA can be defined by first transforming it into an equivalent NFA, and using the fact that this transformation preserves the set of states. We use these functions to simply automata by removing the set of unreachable (or useless) states, and to test if the language of an automaton is empty.

simplifyNFA :: (Eq st) => NFA st -> NFA st
simplifyNFA nfa@(states,sigma,delta,startState,finalStates) =
  (reachableStatesNFA nfa,sigma,delta,startState,finalStates)

simplifyDFA :: (Eq st) => DFA st -> DFA st
simplifyDFA dfa@(states,sigma,delta,startState,finalStates) =
  (reachableStatesNFA (convertDFA2NFA dfa),sigma,delta,startState,finalStates)

isEmptyNFA :: (Eq st) => NFA st -> Bool
isEmptyNFA nfa@(_,_,_,startState,finalStates) =
  let rejecting q = not (elem q finalStates)
  in all rejecting (reachableStatesNFA nfa)

All functions defined in these notes can be found in the module NFA.hs.