[Haskell-beginners] Beginners Code - Comments on Style

Brent Yorgey byorgey at seas.upenn.edu
Thu Mar 21 16:09:34 CET 2013


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



More information about the Beginners mailing list