Re: [GHC] #1283: thread-safe getStdRandom and newStdGen

2007-08-30 Thread GHC
#1283: thread-safe getStdRandom and newStdGen
--+-
Reporter:  [EMAIL PROTECTED]  |Owner:  simonmar   
Type:  bug|   Status:  new
Priority:  normal |Milestone:  6.6.2  
   Component:  libraries/base |  Version:  6.6
Severity:  normal |   Resolution: 
Keywords: |   Difficulty:  Easy (1 hr)
  Os:  Multiple   | Testcase: 
Architecture:  Multiple   |  
--+-
Changes (by simonmar):

  * owner:  = simonmar

Comment:

 I'm testing this one

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1283
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1283: thread-safe getStdRandom and newStdGen

2007-08-30 Thread GHC
#1283: thread-safe getStdRandom and newStdGen
--+-
Reporter:  [EMAIL PROTECTED]  |Owner:  simonmar   
Type:  bug|   Status:  closed 
Priority:  normal |Milestone:  6.6.2  
   Component:  libraries/base |  Version:  6.6
Severity:  normal |   Resolution:  fixed  
Keywords: |   Difficulty:  Easy (1 hr)
  Os:  Multiple   | Testcase: 
Architecture:  Multiple   |  
--+-
Changes (by simonmar):

  * resolution:  = fixed
  * status:  new = closed

Comment:

 patch pushed and test added, thanks!

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1283
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #1283: thread-safe getStdRandom and newStdGen

2007-04-17 Thread GHC
#1283: thread-safe getStdRandom and newStdGen
--+-
Reporter:  [EMAIL PROTECTED]  |   Owner:  
Type:  bug|  Status:  new 
Priority:  normal |   Milestone:  6.6.2   
   Component:  libraries/base | Version:  6.6 
Severity:  normal |Keywords:  
  Difficulty:  Easy (1 hr)|Testcase:  
Architecture:  Multiple   |  Os:  Multiple
--+-
Implementations of getStdRandom and newStdGen use unsynchronised calls to
 getStdGen and setStdGen, allowing a race condition in which duplicate
 random numbers can be returned in multiple threads.

 Patch attached. Tested against GHC 6.6, on Linux amd64.

 The following code used with +RTS -N2 demonstrates the race condition.

 {{{
 import Control.Concurrent
 import Control.Monad
 import Data.Sequence hiding (take)
 import System.Random

 threads = 4
 samples = 5000

 main = loopTest threads samples

 loopTest t s = do
   isClean - testRace t s
   putStrLn $ if isClean
 then no race condition found
 else race condition found
   loopTest t s

 testRace t s = do
   ref - liftM (take (t*s) . randoms) getStdGen
   iss - threadRandoms t s
   return (isInterleavingOf (ref::[Int]) iss)

 threadRandoms t s = do
   vs - sequence $ replicate t $ do
 v - newEmptyMVar
 forkIO (sequence (replicate s randomIO) = putMVar v)
 return v
   mapM takeMVar vs

 isInterleavingOf xs yss = iio xs (viewl $ fromList yss) EmptyL where
   iio (x:xs) ((y:ys) : yss) zss
 | x /= y = iio (x:xs) (viewl yss) (viewl (fromViewL zss | (y:ys)))
 | x == y = iio xs (viewl ((ys | yss)  fromViewL zss)) EmptyL
   iio xs ([] : yss) zss = iio xs (viewl yss) zss
   iio [] EmptyL EmptyL = True
   iio _ _ _ = False

 fromViewL (EmptyL) = empty
 fromViewL (x : xs) = x | xs
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1283
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs