Re: [Haskell-cafe] STM and random numbers

2007-01-13 Thread Tomasz Zielonka
On Sat, Jan 13, 2007 at 01:49:36PM +1000, Matthew Brecknell wrote:
> > Rather than having a separate thread computing the random numbers
> > using IO, why not just stick an StdGen in a TVar and write a function
> > like:
> > 
> > type RandomVar = TVar StdGen
> > 
> > rnd :: RandomVar -> STM a
> > rnd var = do
> >  g <- readTVar var
> >  let (r,g') = random g
> >  writeTVar var g'
> >  return r
> 
> The user of this approach should be aware that it may lead to
> non-determinism. That is, the sequence of psuedo-random numbers
> extracted by any one thread will depend on those extracted by other
> threads, which may in turn depend on the scheduling of those threads.
> 
> The TVar approach might also lead to excessive STM transaction
> abort-retry cycles, if multiple threads are retrieving many
> pseudo-random numbers via a single TVar.

As a workaround for these problems you can create a separate RandomVar
for each "atomically" block.

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM and random numbers

2007-01-12 Thread Matthew Brecknell
> Rather than having a separate thread computing the random numbers
> using IO, why not just stick an StdGen in a TVar and write a function
> like:
> 
> type RandomVar = TVar StdGen
> 
> rnd :: RandomVar -> STM a
> rnd var = do
>  g <- readTVar var
>  let (r,g') = random g
>  writeTVar var g'
>  return r

The user of this approach should be aware that it may lead to
non-determinism. That is, the sequence of psuedo-random numbers
extracted by any one thread will depend on those extracted by other
threads, which may in turn depend on the scheduling of those threads.

While non-determinism might be ideal for some applications of
psuedo-random numbers, there are other applications (simulation, in
particular) where it is useful to be able to reproduce an exact sequence
of psuedo-random events by just reapplying the same initial seed. To do
that, you would need (among other things) to thread a separate
pseudo-random generator through each thread (using the approach
described by Robert and Henning), and split the psuedo-random generator
whenever forking a new thread.

The TVar approach might also lead to excessive STM transaction
abort-retry cycles, if multiple threads are retrieving many
pseudo-random numbers via a single TVar.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM and random numbers

2007-01-12 Thread Sebastian Sylvan

On 1/12/07, Rich Neswold <[EMAIL PROTECTED]> wrote:

On 1/12/07, Chad Scherrer <[EMAIL PROTECTED]> wrote:
> Even if I use randomIO outside the STM code, I don't know of a (safe)
> way to bring it in.

Define your STM action to be (Int -> STM s). Generate the random
number and then pass it in:

mySTM :: Int -> STM a
mySTM n = do { ... }

To use it:

do { n <- getStdRandom (...)
; atomically (mySTM n) }

> Anyway, the number of random values needed depends
> on other stuff going on within the STM part.

Ah. This detail removes my suggestion. But how about this?

randomizer :: TMVar Int -> IO ()
randomizer v = do { n <- getStdRandom (...)
   ; atomically (putTMVar v n)
   ; randomizer v }

Start the randomizer action using forkIO. This gives you a steady
supply of random numbers in the STM monad just by reading the TMVar
(via takeTMVar).


Rather than having a separate thread computing the random numbers
using IO, why not just stick an StdGen in a TVar and write a function
like:

type RandomVar = TVar StdGen

rnd :: RandomVar -> STM a
rnd var = do
g <- readTVar var
let (r,g') = random g
writeTVar var g'
return r

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM and random numbers

2007-01-12 Thread Rich Neswold

On 1/12/07, Chad Scherrer <[EMAIL PROTECTED]> wrote:

Even if I use randomIO outside the STM code, I don't know of a (safe)
way to bring it in.


Define your STM action to be (Int -> STM s). Generate the random
number and then pass it in:

mySTM :: Int -> STM a
mySTM n = do { ... }

To use it:

do { n <- getStdRandom (...)
   ; atomically (mySTM n) }


Anyway, the number of random values needed depends
on other stuff going on within the STM part.


Ah. This detail removes my suggestion. But how about this?

randomizer :: TMVar Int -> IO ()
randomizer v = do { n <- getStdRandom (...)
  ; atomically (putTMVar v n)
  ; randomizer v }

Start the randomizer action using forkIO. This gives you a steady
supply of random numbers in the STM monad just by reading the TMVar
(via takeTMVar).

--
Rich

AIM : rnezzy
ICQ : 174908475
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM and random numbers

2007-01-12 Thread Chad Scherrer

Wow, lots of great ideas. Thanks, guys.

Lemmih,
I worry about the uncertainty in the semantics that seems to be
introduced by the unsafe stuff. But I actually hadn't noticed
GHC.Conc.unsafeIOToSTM before, so it's good to know it's there.

Rich,
Even if I use randomIO outside the STM code, I don't know of a (safe)
way to bring it in. Anyway, the number of random values needed depends
on other stuff going on within the STM part.

Christian,
I think setStdGen has the same problem as just using randomIO and
ignoring the initial seed - there's no nice way of moving the (IO a)
value generated into the STM monad.

Rob, Henning,
I think I'll take this approach, or something similar. Thanks for the pointers.

-Chad
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM and random numbers

2007-01-12 Thread Henning Thielemann

On Fri, 12 Jan 2007, Robert Dockins wrote:

> Humm... I'd actually suggest you stop trying to break the rules, and use the
> portion of the random interface that doesn't require IO.  You can pretty
> easily wrap a StdGen using StateT, and write your stuff in the monad (StateT
> StdGen STM).
> 
> Or, (and I'm amazed this hasn't been done before), you can create a custom
> random monad that wraps up this behavior.

http://haskell.org/haskellwiki/New_monads/MonadRandom
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM and random numbers

2007-01-12 Thread Robert Dockins


On Jan 12, 2007, at 10:58 AM, Chad Scherrer wrote:


Hi,

I'd like to be able to use randomIO, but I'm working within the
context of STM. Is there a way to get these working together happily?

For now, I guess I could kludgingly use unsafePerformIO inside STM
(it's the other way around that's not allowed, right?), but I would
need to be sure it doesn't get inlined.


Humm... I'd actually suggest you stop trying to break the rules, and  
use the portion of the random interface that doesn't require IO.  You  
can pretty easily wrap a StdGen using StateT, and write your stuff in  
the monad (StateT StdGen STM).


Or, (and I'm amazed this hasn't been done before), you can create a  
custom random monad that wraps up this behavior.  Prototype  
attached.  Now you can write in (RandT StdGen STM), and use the  
convenient getRandom method.


Invoke like:

dostuff :: IO ()
dostuff = do
gen <- newStdGen
x <- atomically (evalRandT stuff gen)
process x

stuff :: RandT StdGen STM Int
stuff = do
 r <- getRandom
 lift (someSTMaction r)




Thanks,

Chad



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG




Random.hs
Description: Binary data


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM and random numbers

2007-01-12 Thread Lemmih

On 1/12/07, Chad Scherrer <[EMAIL PROTECTED]> wrote:

Hi,

I'd like to be able to use randomIO, but I'm working within the
context of STM. Is there a way to get these working together happily?

For now, I guess I could kludgingly use unsafePerformIO inside STM
(it's the other way around that's not allowed, right?), but I would
need to be sure it doesn't get inlined.


You could use GHC.Conc.unsafeIOToSTM. Just be aware that your
transaction may be re-executed an arbitrary number of times.

--
Cheers,
 Lemmih
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] STM and random numbers

2007-01-12 Thread Chad Scherrer

Hi,

I'd like to be able to use randomIO, but I'm working within the
context of STM. Is there a way to get these working together happily?

For now, I guess I could kludgingly use unsafePerformIO inside STM
(it's the other way around that's not allowed, right?), but I would
need to be sure it doesn't get inlined.

Thanks,

Chad
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe