
Hello all, I've been playing with some code to work with DFAs, but I'm now faced with an implementation problem. In order to have states that can transition to themselves, it seems I would need self-referential data; otherwise I would need to separate those transitions from the rest and handle them specially in the code. I tried to exploit laziness in order to get self-referential data as shown in the 'self' function below: module DFA where import Data.Map (Map) import qualified Data.Map as M data DFA a = DFA (Map a (DFA a)) -- The set of transitions functions Bool -- Is this a final state? accept :: Ord a => DFA a -> [a] -> Bool accept (DFA _ f) [] = f accept (DFA ts f) (x:xs) = maybe False (`accept` xs) (M.lookup x ts) empty :: Bool -> DFA a empty = DFA M.empty path :: Ord a => a -> DFA a -> DFA a -> DFA a path x d' (DFA ts f) = DFA (M.insert x d' ts) f self :: Ord a => a -> DFA a -> DFA a self x d = let d' = path x d' d in d' test :: String -> Bool test = accept s1 where s1 = path '0' s2 . self '1' $ empty True s2 = path '0' s1 . self '1' $ empty False The automaton I construct in the 'test' function is the example one from the wikipedia page (http://en.wikipedia.org/wiki/Deterministic_finite_automaton) on DFAs. It should accept any string formed with ones and zeros that contain an even number of zeros (or, equivalently, strings that match the regular expression "1*(0(1*)0(1*))*"). Unfortunately, this doesn't seem to give the desired effect: *DFA> test "0" False *DFA> test "00" True *DFA> test "000" False *DFA> test "0000" True *DFA> test "1" True *DFA> test "11" True *DFA> test "111" True *DFA> test "11100" False Anyone knows what I'm doing wrong here? I suspect my attempt at having self-referential data is somehow buggy; do I need to treat transitions to the same state differently? Cheers, Maxime