[Haskell-beginners] Beginners Code - Comments on Style
Heinrich Ody
heinrich.ody at gmail.com
Sat Mar 16 11:25:18 CET 2013
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)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130316/49abe4bb/attachment.htm>
More information about the Beginners
mailing list