DFAs and self-referential data

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

* Maxime Henrion
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?
The problem is that when you call 'self', you record *that* state of your DFA in the map. When DFA gets updated further, the recorded self-reference is not updated appropriately. In your case a workaround is to call 'self' after all the other updates, i.e. test :: String -> Bool test = accept s1 where s1 = self '1' . path '0' s2 $ empty True s2 = self '1' . path '0' s1 $ empty False But I don't see why you need 'self' at all -- you can just use path as with any other type of transition: test :: String -> Bool test = accept s1 where s1 = path '0' s2 . path '1' s1 $ empty True s2 = path '0' s1 . path '1' s2 $ empty False -- Roman I. Cheplyaka :: http://ro-che.info/ Don't worry what people think, they don't do it very often.

On Sun, 2010-12-26 at 13:58 +0200, Roman Cheplyaka wrote:
* Maxime Henrion
[2010-12-26 12:01:31+0100] 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?
The problem is that when you call 'self', you record *that* state of your DFA in the map. When DFA gets updated further, the recorded self-reference is not updated appropriately.
In your case a workaround is to call 'self' after all the other updates, i.e.
test :: String -> Bool test = accept s1 where s1 = self '1' . path '0' s2 $ empty True s2 = self '1' . path '0' s1 $ empty False
But I don't see why you need 'self' at all -- you can just use path as with any other type of transition:
test :: String -> Bool test = accept s1 where s1 = path '0' s2 . path '1' s1 $ empty True s2 = path '0' s1 . path '1' s2 $ empty False
Indeed this just works, thanks! The reason I was using a 'self' function was that I initially thought it would be more convenient; I now see it doesn't, especially considering it doesn't even work. However I'm a bit confused as to why things just work without having to reorder the calls when using the 'path' function - my brain seems to have difficulties following the code path here :-). Cheers, Maxime

On Sun, 2010-12-26 at 13:38 +0100, Maxime Henrion wrote:
On Sun, 2010-12-26 at 13:58 +0200, Roman Cheplyaka wrote:
* Maxime Henrion
[2010-12-26 12:01:31+0100] 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?
The problem is that when you call 'self', you record *that* state of your DFA in the map. When DFA gets updated further, the recorded self-reference is not updated appropriately.
In your case a workaround is to call 'self' after all the other updates, i.e.
test :: String -> Bool test = accept s1 where s1 = self '1' . path '0' s2 $ empty True s2 = self '1' . path '0' s1 $ empty False
But I don't see why you need 'self' at all -- you can just use path as with any other type of transition:
test :: String -> Bool test = accept s1 where s1 = path '0' s2 . path '1' s1 $ empty True s2 = path '0' s1 . path '1' s2 $ empty False
Indeed this just works, thanks! The reason I was using a 'self' function was that I initially thought it would be more convenient; I now see it doesn't, especially considering it doesn't even work. However I'm a bit confused as to why things just work without having to reorder the calls when using the 'path' function - my brain seems to have difficulties following the code path here :-).
Oh, nevermind, I finally figured it out. When using my 'self' function, as you said, I point at the version of the DFA I have when calling 'self', and not the final version of the DFA after other calls to 'path'. So as soon as I was following a self transition, I was ending up with an 'old' version of the DFA. Whereas in your version, the binding I point to is the final DFA version. Thanks a lot! Maxime
participants (2)
-
Maxime Henrion
-
Roman Cheplyaka