
Hi, I'm trying to learn Haskell by writing a library for automata functions. So far I finished some functions that I use to calculate the union and intersection of 2 automata for the case of finite words. I wonder if somebody is willing to give comments on the code? For example how I could write a function to be nicer, better to understand etc. Please note that I don't know monads yet. Thanks for your time! Below is my code (I left out some functions to make it shorter) Greetings, Heinrich ------------------ Code import Text.Show.Functions import qualified Data.List as List import Data.Maybe import Prelude hiding (init) -- b is the type for the alphabet. -- Meaning of the parameters are (States, Alphabet, InitStates, Trans.Function, FinalStates) data NFA l = NFA [State] [l] [State] [(State, l, State)] [State] instance Show l => Show (NFA l) where show (NFA states alphabet init delta final) = "States: " ++ show states ++ "\n" ++ "Alphabet: " ++ show alphabet ++ "\n" ++ "Init: " ++ show init ++ "\n" ++ "Delta: " ++ show delta ++ "\n" ++ "Final: " ++ show final data State = I Integer | S [State] deriving Eq instance Show State where show (I i) = show i show (S xs) = show xs -- Advance all states in the set by one step, for the given input letter setTransition :: Eq l => [(State, l, State)] -> [State] -> l -> [State] setTransition delta xs l = [s' | (s, l', s') <- delta, s `List.elem` xs, l' == l] -- naivly test whether a given word is accepted -- for this we forward propagate the current state sets on our input word -- we assume the automaton is complete isAccepted :: Eq l => NFA l -> [l] -> Maybe Bool isAccepted (NFA states alphabet init delta final) word = if (List.nub word) `subset` alphabet then let f xs sigma = setTransition delta xs sigma in Just (((/= []) . (List.intersect final) . (List.foldl f init)) word) else Nothing -- makes an automaton complete s.t. for each pair in (States x Alphabet) a the transition function returns a state. -- For this a sink state is added to States which is the result of all previously unassigned pairs in (States x Alphabet). -- This function keeps DFA deterministc. It adds the sinkstate, but it will be unreachable. makeComplete :: Eq l => NFA l -> NFA l makeComplete (NFA states alphabet init delta final) = NFA (e:states) alphabet init (unassigned `List.union` delta) final where -- e is a new state, whose integer value does not occur in states e = I ((minState states) -1) r = ([e] `List.union` states) `times` alphabet unassigned = [(s,l,e) | (s,l) <- r, (s,l) `List.notElem` (map proj3' delta)] -- checks if 1st parameter is (non-strict) subset of 2nd parameter -- Assumes that there are no duplicates subset :: Eq l => [l] -> [l] -> Bool subset xs ys = (xs List.\\ ys) == [] -- comparision of lists where index of elements is ignored -- Assumes that there are no duplicates seteq :: Eq l => [l] -> [l] -> Bool seteq xs ys = (xs List.\\ ys) == (ys List.\\ xs) -- cartesian product going from states to states stateTimes :: [State] -> [State] -> [State] stateTimes xs ys = [ S [x,y] | x <- xs, y <- ys] -- Normal cartesian product times :: [a] -> [b] -> [(a,b)] times xs ys = [(x,y) | x <- xs, y <- ys] -- Normal cartesian product for three lists times3 :: [a] -> [b] -> [c] -> [(a,b,c)] times3 xs ys zs = [(x,y,z) | x <- xs, y <- ys, z <- zs] -- removes the last element from the tuple proj3' :: (a,b,c) -> (a,b) proj3' (x,y,z) = (x,y) -- adds the 2nd parameter as last element of the input tupple addToTuple :: (a,b) -> c -> (a,b,c) addToTuple (x,y) z = (x,y,z)

On Sat, Mar 16, 2013 at 11:25:18AM +0100, Heinrich Ody wrote:
Hi,
I'm trying to learn Haskell by writing a library for automata functions. So far I finished some functions that I use to calculate the union and intersection of 2 automata for the case of finite words.
I wonder if somebody is willing to give comments on the code? For example how I could write a function to be nicer, better to understand etc. Please note that I don't know monads yet.
Thanks for your time! Below is my code (I left out some functions to make it shorter) Greetings, Heinrich
------------------ Code import Text.Show.Functions import qualified Data.List as List import Data.Maybe import Prelude hiding (init)
-- b is the type for the alphabet. -- Meaning of the parameters are (States, Alphabet, InitStates, Trans.Function, FinalStates) data NFA l = NFA [State] [l] [State] [(State, l, State)] [State]
You store a list of tuples [(State, l, State)] for the transition map and then convert it to a function with setTransition. Why not just store a function of type State -> l -> [State] in the first place instead of a list of tuples? Actually, l -> State -> [State] would probably be even more useful. Then to get a function of type l -> [State] -> [State] you can use 'concatMap'. However, you can end up with duplicate States this way. So in fact I would actually recommend using (Set State) in place of [State] (Set is from Data.Set).
data State = I Integer | S [State] deriving Eq
Hmm, I don't understand what the S constructor is for. Why can a State be a list of States? Hmm, I see from below that this is to support the 'stateTimes' operation. In that case I think it would be better to have something like newtype State a = S a and then stateTimes :: [State a] -> [State b] -> [State (a,b)] which makes State less complicated, and has the added benefit that the type of stateTimes is more informative. This also means you will have to make the state type a parameter of NFA, i.e. data NFA l s = NFA [State s] ... but that seems nice to me too. All your algorithms should only depend on e.g. an Eq or Ord constraint on s.
-- naivly test whether a given word is accepted -- for this we forward propagate the current state sets on our input word -- we assume the automaton is complete isAccepted :: Eq l => NFA l -> [l] -> Maybe Bool isAccepted (NFA states alphabet init delta final) word = if (List.nub word) `subset` alphabet then let f xs sigma = setTransition delta xs sigma in Just (((/= []) . (List.intersect final) . (List.foldl f init)) word) else Nothing
Use foldl' instead of foldl. Also, the uses of List.nub and List.intersect strongly suggest that you really should be using Data.Set instead of lists. -Brent
-- makes an automaton complete s.t. for each pair in (States x Alphabet) a the transition function returns a state. -- For this a sink state is added to States which is the result of all previously unassigned pairs in (States x Alphabet). -- This function keeps DFA deterministc. It adds the sinkstate, but it will be unreachable. makeComplete :: Eq l => NFA l -> NFA l makeComplete (NFA states alphabet init delta final) = NFA (e:states) alphabet init (unassigned `List.union` delta) final where -- e is a new state, whose integer value does not occur in states e = I ((minState states) -1) r = ([e] `List.union` states) `times` alphabet unassigned = [(s,l,e) | (s,l) <- r, (s,l) `List.notElem` (map proj3' delta)]
Given my proposed changes above, the type of makeComplete should probably be something like makeComplete :: Eq l => NFA l s -> NFA l (Maybe s) i.e. you can use Nothing to indicate the new "sink" state. -Brent
participants (2)
-
Brent Yorgey
-
Heinrich Ody