State Transformer

2002-01-07 Thread Jorge Adriano

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 typesomething -> (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 )

-- 

Re: State Transformer

2002-01-07 Thread Albert Lai

I will just translate your example from Norvell's DIY state monad to
GHC's ST monad.  As you noticed, GHC's ST monad begins with an "empty"
state and you use some commands to add state variables as you go.
This means the translation is not straightforward.  I hope you still
get the gist of it.

Your hunch is correct: Norvell's applyST becomes GHC's runST.

Your example uses two state variables: a Char and an Int, paired up as
a tuple.  Below, I use one state variable of type (Char,Int) for that,
as hinted by your first attempt at the translation.  foo and bar will
each need to take a parameter --- the reference to the state variable,
due to the reference business.

testfunc = do
   r <- newSTRef ('x',0)
   foo r
   bar r
   (c,n) <- readSTRef r
   return n

foo r = do
(c,n) <- readSTRef r
writeSTRef r ('a', n+1)

bar r = do
(c,n) <- readSTRef r
writeSTRef r (c,n+2)

tryTestFunc = runST testfunc


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-07 Thread Ketil Z Malde

Jorge Adriano <[EMAIL PROTECTED]> writes:

> 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 

[...]

> Monads! (right?)

Well, I suppose so.  Generally speaking.

But, you might want to consider using the standard random generation
routines from the (IO) top level of your program, and just split the
random generator for each function that uses it.  IOW, passing each
function its own random generator, instead of worrying about returning
the "rest" of a global random sequence.

(I don't have any good example code, I'm afraid, but at leat have a
look at the chapter on Random in the library report on http://haskell.org)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Jorge Adriano


> Your example uses two state variables: a Char and an Int, paired up as
> a tuple.  Below, I use one state variable of type (Char,Int) for that,
> as hinted by your first attempt at the translation.  foo and bar will
> each need to take a parameter --- the reference to the state variable,
> due to the reference business.
>
> testfunc = do
>r <- newSTRef ('x',0)
>foo r
>bar r
>(c,n) <- readSTRef r
>return n

Yeap, I could do it like this myself :)
The whole problem is with passing the 'r' as a parameter, which is precisly 
what I'm trying to avoid. I think I already understood how to use this monad. 
Its pretty different from the monad state I was expecting, and as far as I 
can see, to be used in distinct situations. 

Thanks
J.A.

>
> foo r = do
> (c,n) <- readSTRef r
> writeSTRef r ('a', n+1)
>
> bar r = do
> (c,n) <- readSTRef r
> writeSTRef r (c,n+2)
>
> tryTestFunc = runST testfunc
>


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Theodore Norvell


Jorge's question raised a question in my mind.  The IOExts
module has many of the same features as the ST module, why
are there two ways to do the same thing?  Is the ST module
only there for legacy purposes?

Cheers,
Theo Norvell


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Jan-Willem Maessen

Theodore Norvell <[EMAIL PROTECTED]> asks:
> Jorge's question raised a question in my mind.  The IOExts
> module has many of the same features as the ST module, why
> are there two ways to do the same thing?  Is the ST module
> only there for legacy purposes?

The ST monad provides safer encapsulation of mutable references.  We
can prove that references which escape a particular instance of ST are
never side effected.  See the paper "Lazy Functional State Threads":

  http://www.cse.ogi.edu/~jl/Papers/stateThreads.ps

This allows us to construct functions which are certain to present a
functional face to the world, but use mutation internally.  In this
respect, ST is actually "better" than IO, albeit less well-supported.

-Jan-Willem Maessen

[Note that the above paper presents the version of ST contained in the
LazyST library these days (if my memory serves me right).  The
arguments about encapsulation apply in either case.]

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Jan de Wit

Hi,

> > testfunc = do
> >r <- newSTRef ('x',0)
> >foo r
> >bar r
> >(c,n) <- readSTRef r
> >return n
>
> Yeap, I could do it like this myself :)
> The whole problem is with passing the 'r' as a parameter, which is
precisly
> what I'm trying to avoid. I think I already understood how to use this
monad.
> Its pretty different from the monad state I was expecting, and as far as I
> can see, to be used in distinct situations.
If I understand you correctly, you want global mutable variables, right?
This is, I believe, only possible using IORef's and unsafePerformIO.
Something like this:
| xRef :: IORef Int
| xRef = unsafePerformIO $
|  newIORef 0
| update_x :: IO ()
| update_x = do
|x <- readIORef xRef
|writeIORef xRef (x+1)
(Sorry for formatting, I'm using Outlook now :-)

Of course this is not very functional, nice, safe or robust under compiler
transformations (there probably should be a NOINLINE pragma there somewhere)

Another option is to use implicit variables here. I haven't tested this
approach yet, maybe somebody else on the list has? You don't need to pass
the reference around, but if you're fond of explicitly giving types for
top-level entities (as I am) you're stuck putting it in all type signatures
affected (context-ellipsis would come in handy here!!)

Cheers, Jan


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Albert Lai

> > testfunc = do
> >r <- newSTRef ('x',0)
> >foo r
> >bar r
> >(c,n) <- readSTRef r
> >return n

Jorge Adriano <[EMAIL PROTECTED]> writes:

> Yeap, I could do it like this myself :)
> The whole problem is with passing the 'r' as a parameter, which is precisly 
> what I'm trying to avoid.

I agree with you.  My work-around is then to define foo and bar locally
to testfunc, in the scope of r:

testfunc = do
   r <- newSTRef ('x',0)
   let foo = do
 (c,n) <- readSTRef r
 writeSTRef r ('a', n+1)
   bar = do
 (c,n) <- readSTRef r
 writeSTRef r (c,n+2)
   foo
   bar
   (c,n) <- readSTRef r
   return n

But if this looks like unsatisfactory (it does to me, too), perhaps
you have to go back to DIY monads.

DIY monads are good when: you fix the state variables, you don't want
to mention them in subprogram parameters.

The ST monad is good when: you create more state variables on the fly,
you use mutable arrays, you don't want to write your own monad and
put/get commands.


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Albert Lai

Theodore Norvell <[EMAIL PROTECTED]> writes:

> Jorge's question raised a question in my mind.  The IOExts
> module has many of the same features as the ST module, why
> are there two ways to do the same thing?  Is the ST module
> only there for legacy purposes?

My user view is that I appreciate the presence of both.

When I write a pure function that can be implemented efficiently in
imperative programming, I want the ST monad to support mutable
variables.  E.g., to implement "f n returns a list of all primes
between 2 and n", I want to use a mutable array and hide it.

When I write an I/O-bound routine that can be implemented conveniently
with state variables, I want the IO monad to support mutable
variables.

Now my grief is that I cannot write a subprogram with state variables
and have it reused in ST and IO.  Fortunately I can write a subprogram
with mutable arrays and have it reused in ST and IO, so I can write
"sort a given array"; but I cannot write "increment a given integer
variable".

Of course, you can tell me to use mutable arrays of length 1 to
simulate mutable variables.  Fine!

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Jorge Adriano

> If I understand you correctly, you want global mutable variables, right?
> This is, I believe, only possible using IORef's and unsafePerformIO.

Kind of, I'm searching for the best approach to keep track of data in my 
algorithms without constantly changing signatures.
State monad as defined in the paper I mentioned "monads for the working 
haskell progarmmer" seemed the most elegant way. I saw ST in the Ghc and 
thought it was supposed to do the same... 
I never used mutable variables, but seems like it would prabably be the most 
efficient way to do it, as for more elegant, I don't know... I'm thinking 
about going for a simple State monad, no mutable variables... probably will 
face some efficiency problems though...

>
> Something like this:
> | xRef :: IORef Int
> | xRef = unsafePerformIO $
> |  newIORef 0
> | update_x :: IO ()
> | update_x = do
> |x <- readIORef xRef
> |writeIORef xRef (x+1)
>
> (Sorry for formatting, I'm using Outlook now :-)
>
> Of course this is not very functional, nice, safe or robust under compiler
> transformations (there probably should be a NOINLINE pragma there
> somewhere)

And I was trying to get away from unsafePerformIO... :-)


J.A.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Jorge Adriano


> I agree with you.  My work-around is then to define foo and bar locally
> to testfunc, in the scope of r:
>
> testfunc = do
>r <- newSTRef ('x',0)
>let foo = do
>  (c,n) <- readSTRef r
>  writeSTRef r ('a', n+1)
>bar = do
>  (c,n) <- readSTRef r
>  writeSTRef r (c,n+2)
>foo
>bar
>(c,n) <- readSTRef r
>return n


Thought about that to... but it looks kind of... terribly ugly (sorry :)

> But if this looks like unsatisfactory (it does to me, too), perhaps
> you have to go back to DIY monads.
DIY? what does that means?


> DIY monads are good when: you fix the state variables, you don't want
> to mention them in subprogram parameters.
Yeap!

> The ST monad is good when: you create more state variables on the fly,
> you use mutable arrays, you don't want to write your own monad and
> put/get commands.

What if you want both and keep nice clean(*) programming style... :-)
J.A.

(*) Clean as in "not dirty", not Clean the FL.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Theodore Norvell

> DIY monads are good when: you fix the state variables, you don't want
> to mention them in subprogram parameters.

I've taken this solution for a fairly large piece of software.
One word of warning about DIY state monads, you have to be very carefull
about strictness and lazyness.  If your monad or state are at all lazy,
you can end up dragging a lot of old states around.  When you construct a new
state, you want to be sure that it contains no unevaluated references to
a previous state!

Cheers,
Theodore Norvell


Dr. Theodore Norvell   [EMAIL PROTECTED]
Electrical and Computer Engineeringhttp://www.engr.mun.ca/~theo
Engineering and Applied Science
Memorial University of Newfoundland
St. John's, NF, Canada, A1B 3X5

Currently visiting the Department of Computer Science and ICICS at the
University of British Columbia. See my webpage for contact details.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Eray Ozkural (exa)

On Friday 11 January 2002 19:39, Jan-Willem Maessen wrote:
> The ST monad provides safer encapsulation of mutable references.  We
> can prove that references which escape a particular instance of ST are
> never side effected.  See the paper "Lazy Functional State Threads":
>
>   http://www.cse.ogi.edu/~jl/Papers/stateThreads.ps
>
> This allows us to construct functions which are certain to present a
> functional face to the world, but use mutation internally.  In this
> respect, ST is actually "better" than IO, albeit less well-supported.

So would writing for instance a GUI library, with abstract interfaces using 
ST be a good idea?

Thanks,

-- 
Eray Ozkural (exa) <[EMAIL PROTECTED]>
Comp. Sci. Dept., Bilkent University, Ankara
www: http://www.cs.bilkent.edu.tr/~erayo
GPG public key fingerprint: 360C 852F 88B0 A745 F31B  EA0F 7C07 AE16 874D 539C

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Ashley Yakeley

At 2002-01-11 06:18, Jorge Adriano wrote:

>The whole problem is with passing the 'r' as a parameter, which is precisly 
>what I'm trying to avoid.

You could always pass it implicitly (using -fglasgow-exts):

--
testfunc = do
   r <- newSTRef ('x',0)
   (do
  foo
  bar
with ?ref = r)
   (c,n) <- readSTRef r
   return n

foo :: (Num a,?ref :: STRef s (Char,a)) => ST s ()
foo = do
(c,n) <- readSTRef ?ref
writeSTRef ?ref ('a', n+1)

bar :: (Num a,?ref :: STRef s (t,a)) => ST s ()
bar = do
(c,n) <- readSTRef ?ref
writeSTRef ?ref (c,n+2)

tryTestFunc = runST testfunc
--

Curiously, GHC isn't smart enough to infer the types of foo and bar by 
itself.

-- 
Ashley Yakeley, Seattle WA


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-11 Thread Theodore Norvell

> DIY? what does that means?

Do It Yourself. I.e. as in my tutorial.

> What if you want both and keep nice clean(*) programming style... :-)

You can compose monads.  I've done something like the following in
the past (only with IO):
data StateTrans s a = StateTrans (s -> ST (s,a))
Here s is the global state.  A function that changes
the global state
   f :: s -> s
can be lifted into the monad by
listGlobalMutator :: (s -> s) -> StateTrans s a
liftGlobalMutator f = StateTrans (\s -> return (f s, ()))
similarly
liftGlobalAccessor :: (s -> a) -> StateTrans s a
liftGlobalAccessor g = StateTrans (\s -> return (s, g s))
and
liftST :: ST a -> StateTrans s a
liftST st = StateTrans (\s -> do { a<- st ; return (s, a)})

This gives you a fixed global state (which could be a tuple
of global variables) and as many dynamic variables (accessed via
references) as you want.

Probably I should have used a strict pair type above instead
of (,).

Cheers,
Theo Norvell


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-19 Thread Marcin 'Qrczak' Kowalczyk

11 Jan 2002 17:10:16 -0500, Albert Lai <[EMAIL PROTECTED]> pisze:

> Now my grief is that I cannot write a subprogram with state
> variables and have it reused in ST and IO.  Fortunately I can write
> a subprogram with mutable arrays and have it reused in ST and IO,
> so I can write "sort a given array"; but I cannot write "increment
> a given integer variable".

You can if you write your own class describing the common interface.

Here is mine. The same code can work with MVars too, as long as the
order of operations is consistent with the empty/full state. The
empty/full state is real for MVars and imagined for IORef/STRef.

module UnifiedRef (Ref(..), STRef, IORef, MVar) where

import ST
import IOExts
import Concurrent

class Monad m => Ref m c | c -> m where
-- Minimal definition:
-- 'newRef' or 'newEmptyRef',
-- 'getRef' or 'cutRef',
-- 'setRef' or 'insertRef'.
newRef  :: a -> m (c a)
newEmptyRef :: m (c a)
copyRef :: c a -> m (c a)
getRef  :: c a -> m a
setRef  :: c a -> a -> m ()
cutRef  :: c a -> m a
insertRef   :: c a -> a -> m ()
modifyRef   :: c a -> (a -> m a) -> m ()
withRef :: c a -> (a -> m b) -> m b
changeRef   :: c a -> (a -> m (b, a)) -> m b

newRef  a   = do c <- newEmptyRef; insertRef c a; return c
newEmptyRef = newRef (error "Empty reference")
copyRef c   = newRef =<< getRef c
getRef  c   = do a <- cutRef c; insertRef c a; return a
setRef  c a = do cutRef c; insertRef c a
cutRef  = getRef
insertRef   = setRef
modifyRef   c f = insertRef c =<< f =<< cutRef c
withRef c f = do a <- cutRef c; b <- f a; insertRef c a; return b
changeRef   c f = do a <- cutRef c; (b, a') <- f a; insertRef c a'; return b

instance Ref (ST s) (STRef s) where
newRef = newSTRef
getRef = readSTRef
setRef = writeSTRef

instance Ref IO IORef where
newRef = newIORef
getRef = readIORef
setRef = writeIORef

instance Ref IO MVar where
newRef= newMVar
newEmptyRef   = newEmptyMVar
getRef= readMVar
cutRef= takeMVar
insertRef = putMVar
modifyRef = modifyMVar_
withRef   = withMVar
changeRef r f = modifyMVar r (\a -> do (b, a') <- f a; return (a', b))

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^
QRCZAK


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-19 Thread Ashley Yakeley

At 2002-01-19 08:16, Marcin 'Qrczak' Kowalczyk wrote:

>Here is mine. The same code can work with MVars too, as long as the
>order of operations is consistent with the empty/full state. The
>empty/full state is real for MVars and imagined for IORef/STRef.

Could you simply the interface if you consider (MVar a) to hold a (Maybe 
a)?

class Monad m => Ref m a r | r -> m a where
newRef  :: a -> m r
getRef  :: r -> m a
setRef  :: r -> a -> m ()
modifyRef   :: r -> (a -> m a) -> m ()

instance Ref (ST s) a (STRef s a) where
...

instance Ref IO a (IORef a) where
...

instance Ref IO (Maybe a) (MVar a) where
...


-- 
Ashley Yakeley, Seattle WA


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: State Transformer

2002-01-28 Thread Jorge Adriano

On Saturday 12 January 2002 07:31, Ashley Yakeley wrote:
> At 2002-01-11 06:18, Jorge Adriano wrote:
> >The whole problem is with passing the 'r' as a parameter, which is
> > precisly what I'm trying to avoid.
>
> You could always pass it implicitly (using -fglasgow-exts):

Thanks, at first it seemed to me it wouldn't be that usefull because it 
reflects on the type signature, but it does makes a diference.
I'm using it implicit parameters now.

J.A.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users