State Transformer

Jorge Adriano jadrian@mat.uc.pt
Mon, 7 Jan 2002 15:41:57 +0000


Hi,
I'm studying, among other things, Genetic Algorithms and Neural Networks and 
I decided I'd use haskell to code some simple GAs and NNs along with my study.
Well, maybe it was not such a good idea after all, because I've been spending 
way more time learning more Haskell then GAs and NNs :(

Anyway, I was coding some simple GA, and as you probably know I need to use 
random values. The most elegant way I could think of was to generate some 
infinite list of random values and pass them around as arguments to the 
functions that need those values. I called data which wraped this list 
Environment, and at first it seemed a nice way to solve the problem.
Well, now I think it gets kind of weird because some functions will end up to 
have type    something -> (otherthing, Environment), to update those lists... 
it's just ugly. 
Beside those lists I'd also like to control some statistics like the number 
of mutations, n. of crossovers, best fitness value in each generation, etc... 
I figured out that there should be a better way to do this then just chaging 
all the signatures and passing all this values around.

Monads! (right?)
Till then I had just read what I needed to be able to use the IO Monad. 
Seems to me like having a State Transformer monad its the best way to do it.
Now I've read a great deal of Richard Birds Book chap 10 (Monads), as well as 
the "Monads for the Haskell Working Programmer"[1] by Theodore Norvell.

I was going to try to make my own simple examples using a ST.
A State Monad seemed something like would most probably be in some Standard 
Library, or at least in some GHC library.
And it was (section 4.31.ST in the hslibs documentation)
I wanted to use this ST, but then I noticed it was different from the one 
described in tutorial[1].

I was expecting the ST Monad ghc module to provide an apply function, 
analogue to the 
> applyST :: StateTrans s a -> s -> (s, a)
> applyST (ST p) s = p s
in the tutorial.
I also expected to have general functions to access and change State. I can't 
implement them myself since the ST constructor is (obviously) not exported.
But this ST module seems to work in a completely diferent way.
From what I can tell it is not suposed to be applyed to an initial state, 
instead it starts with an 'empty' state...
State is controled with Referencies (mutable variables).

Ok, now my problem, how do I use this?
I can't really see how to change this referencies from within some function. 
(Got an example in the end to explain better waht I mean with that [Example1])

I'd also appreciate  some coments on:
Using a ST monad (good idea, bad?)
Using the Ghc ST monad?
Chromosomes defined as arrays? - either IArray or Diff array got to give it 
some more thought... (don't want Ints + bitwise operations right now...)

Well, any other comments or hints that you think that might be usefully are 
welcome. I've already checked out the paper from the TAIGA project[2], it's 
not exactly done the way I'm thinking about doing it, but I got some usefull 
tips from there, like the use of a Monad to control statistics.
One of my main problems so far as been *knowing what do I need to know*!
I don't know anyone that codes in haskell, not having anyone to talk to and 
share ideas doesn't helps much either.
Things get complicated where you (you - the guy that comes from the 
imperative paradigm) less expects it too... the space leaks, using monads to 
control state... if you still have not read about this stuff, IMO, it is easy 
to feel like you already know enough to do some solve some kind of problems 
when you actually don't. 
Any newbie to C or Pascal can make a few randoms here and there, and keep 
track of statistics... when you already spent some time with haskell you 
don't even question whether you already know enough to do something like 
*that*. Only when you start to work, and thing start to get messy, you begin 
to think that *maybe you need something you still don't know about*, and then 
you got to find out what it is...
Documentation, I also feel like it could be more and better... the ST module 
in ghc for instance... would it be that hard to put at least some simple 
example there? No, just the type signatures...
Well, this is just my opinion anyway.

Thanks for your atention, and happy 2002 ;-)
J.A.


[Example1]
How can I do this for instance, with the Ghc ST Monad:
------------------------------------------------------------------------

-- the State Trans defined as in the tutorial
newtype StateTrans s a = ST( s -> (s, a) )

instance Monad (StateTrans s)
  where
    -- (>>=) :: StateTrans s a -> (a -> StateTrans s b) -> StateTrans s b
    (ST p) >>= k  =  ST( \s0 -> let (s1, a) = p s0
                                    (ST q) = k a
                                in q s1 )
                                
    -- return :: a -> StateTrans s a
    return a = ST( \s -> (s, a) )

applyST :: StateTrans s a -> s -> (s, a)
applyST (ST p) s = p s


-- just change the state
putST         :: (Char,Int) -> StateTrans (Char,Int) ()
putST (c',n') = ST(\(c,n)->((c',n'),()))

-- get the state
getST :: StateTrans (Char,Int) (Char,Int)
getST = ST(\(x,y)-> ((x,y), (x,y)))

testfunc :: StateTrans (Char,Int) Int
testfunc = do
	   foo
	   bar
	   (c,n)<-getST
	   return n


foo = do 
      (c,n)<-getST   
      putST ('a',n+1)   

bar = do 
      (c,n)<-getST
      putST (c,n+2)

tryTestFunc = applyST testfunc ('x',0)
------------------------------------------------------------------------

I is something like this?

----------------------------------------
stupidFunc 
    runST (
     do {
      initstate <- newSTRef ('x',0)
      -- and now what?
	})
-----------------------------------------



[1] http://www.engr.mun.ca/~theo/Misc/haskell_and_monads.htm
[2] http://www.scms.rgu.ac.uk/staff/db/Taiga/
http://www.scms.rgu.ac.uk/staff/db/Taiga/APGA2000.ps.gz