
Does haskell have a way of using /dev/random to generate random *things*? Currently I'm just reading the data into a byte string, converting it into bits, and keeping track of it in the state monad. -- Alex R

What's wrong with the System.Random.StdGen implementation of RandomGen?[1]
(I'm not sure if it's cryptographically safe)
Someone (Cale IIRC) has already implemented a Rand monad[2] which is like a
state monad but it keeps a RandomGen instead.
As an aside, there is no such Arrow or ArrowTransormer, but I intend to make
one as soon as I am able. Useful for Arrowised FRP.
[1] http://hackage.haskell.org/package/random-1.0.0.2
[2] http://hackage.haskell.org/package/MonadRandom
On 3 April 2010 09:11, Alex Rozenshteyn
Does haskell have a way of using /dev/random to generate random *things*? Currently I'm just reading the data into a byte string, converting it into bits, and keeping track of it in the state monad.
-- Alex R
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Matthew Hayden
What's wrong with the System.Random.StdGen implementation of RandomGen?[1] (I'm not sure if it's cryptographically safe)
It's a poor PRNG. And no, it's not anywhere near suitable for cryptographic applications.
Someone (Cale IIRC) has already implemented a Rand monad[2] which is like a state monad but it keeps a RandomGen instead.
http://hackage.haskell.org/package/MonadRandom by "Cale Gibbard and others" Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

The Rand monad you linked seems to be a step in the right direction for what
I want, but it uses getStdGen, which appears to end up using cpu time to
seed the generator.
On Sat, Apr 3, 2010 at 9:21 AM, Ertugrul Soeylemez
Matthew Hayden
wrote: What's wrong with the System.Random.StdGen implementation of RandomGen?[1] (I'm not sure if it's cryptographically safe)
It's a poor PRNG. And no, it's not anywhere near suitable for cryptographic applications.
Someone (Cale IIRC) has already implemented a Rand monad[2] which is like a state monad but it keeps a RandomGen instead.
http://hackage.haskell.org/package/MonadRandom
by "Cale Gibbard and others"
Greets, Ertugrul
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alex R

Alex Rozenshteyn
The Rand monad you linked seems to be a step in the right direction for what I want, but it uses getStdGen, which appears to end up using cpu time to seed the generator.
There's the random-stream package but looks like it's subject to code rot. Its RandomGen instance lacks the split functionality but I guess it could be used with MonadRandom. -- Gökhan San

Looking over the random-fu package, I think it might have what I'm looking
for (and a lot that I'm not).
On Sat, Apr 3, 2010 at 6:27 PM, Gökhan San
Alex Rozenshteyn
writes: The Rand monad you linked seems to be a step in the right direction for what I want, but it uses getStdGen, which appears to end up using cpu time to seed the generator.
There's the random-stream package but looks like it's subject to code rot. Its RandomGen instance lacks the split functionality but I guess it could be used with MonadRandom.
--
Gökhan San _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alex R

As the maintainer of random-fu, I'd be interested to know whether you find it useful after further inspection. It does, in fact, support using /dev/random as its entropy source. I don't know what exact sort of things you're wanting to do, but very basic usage (random Int in IO from DevRandom, etc.) is along these lines:
sampleFrom DevRandom (uniform 1 100) :: IO Int sampleFrom DevRandom stdNormal :: IO Double
If the haddock docs are insufficient, feel free to drop me an email for clarification - I know they're a bit spotty at the moment. Minor warning: I'm getting ready to release a fairly major overhaul of the library's innards (the latest is in the darcs repo). The public interface will probably not change much, but if you happen to end up using any of the low-level interfaces (such as to define your own new random source) just be aware that those are changing soon. It's nearing release, I'm mostly just trying to knock off rough edges and trying to decide whether to "take the plunge" and make some interface changes (mostly whether I want to hide some data constructors in order to better enforce some invariants). -- James Cook On Apr 3, 2010, at 1940, Alex Rozenshteyn wrote:
Looking over the random-fu package, I think it might have what I'm looking for (and a lot that I'm not).
On Sat, Apr 3, 2010 at 6:27 PM, Gökhan San
wrote: Alex Rozenshteyn writes: The Rand monad you linked seems to be a step in the right direction for what I want, but it uses getStdGen, which appears to end up using cpu time to seed the generator.
There's the random-stream package but looks like it's subject to code rot. Its RandomGen instance lacks the split functionality but I guess it could be used with MonadRandom.
--
Gökhan San _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alex R _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

James Cook
As the maintainer of random-fu, I'd be interested to know whether you find it useful after further inspection.
Is there a way to get multiple random numbers without having to replicateM? While comparing the random-fu interface with Control.Monad.Random (both using StdGen), I noticed that while performance is comparable, using getRandomRs to get a list of random numbers is a lot faster than replicating uniform (or getRandomR for that matter). I don't know if this kind of speed gain makes sense for random-fu though. -- Gökhan San

Is there a way to get multiple random numbers without having to replicateM?
While comparing the random-fu interface with Control.Monad.Random (both using StdGen), I noticed that while performance is comparable, using getRandomRs to get a list of random numbers is a lot faster than replicating uniform (or getRandomR for that matter). I don't know if this kind of speed gain makes sense for random-fu though.
I have been attempting to replicate this. What sort of a performance difference are you seeing, and are you using the hackage-released version of random-fu or the darcs one? The darcs release is, overall, a fair bit faster than the current hackage release. Depending on the particular way that I sample my RVars (eg, replicateM n (sample ...) vs sample (replicateM n ...)), I am seeing the random-fu version of my little benchmark run anywhere from 30% faster to 25% slower than Control.Monad.Random.getRandomRs (for 64000 uniform Double samples). The same benchmark using random-fu-0.0.3.2 shows it consistently about 33% slower than getRandomRs. In case you're interested, this is the (criterion) benchmark I used (with count = 64000, and in the first bgroup 'src' is an "IORef StdGen"):
[ bgroup "replicateM" [ bench "randomRIO" $ do xs <- replicateM count (randomRIO (10,50) :: IO Double) sum xs `seq` return ()
, bench "uniform A" $ do xs <- replicateM count (sampleFrom src (uniform 10 50) :: IO Double) sum xs `seq` return () , bench "uniform B" $ do xs <- sampleFrom src (replicateM count (uniform 10 50)) :: IO [Double] sum xs `seq` return () ]
, bgroup "pure StdGen" [ bench "getRandomRs" $ do src <- newStdGen let (xs, _) = CMR.runRand (CMR.getRandomRs (10,50)) src sum (take count xs :: [Double]) `seq` return () , bench "RVarT, State - sample replicateM" $ do src <- newStdGen let (xs, _) = runState (sample (replicateM count (uniform 10 50))) src sum (xs :: [Double]) `seq` return () , bench "RVarT, State - replicateM sample" $ do src <- newStdGen let (xs, _) = runState (replicateM count (sample (uniform 10 50))) src sum (xs :: [Double]) `seq` return () ]
If the problem is worse than this benchmark indicates, or if this benchmark shows radically different results on a different platform (I'm running on Mac OS 10.6 with GHC 6.12.1), I'd love to hear about it. I could certainly imagine cases where the choice of monad in which to sample makes things quite slow. In the above case, I was using IO in the first bgroup and State StdGen in the second. As for whether an optimization like getRandomRs would benefit the random-fu library: I have tried a few different times to implement list or vector primitives and the corresponding high-level interfaces for sampling many variables at once, but have not yet come up with a version that actually made anything faster. I'm more than happy to accept patches if someone comes up with one, though! ;) -- James

mokus@deepbondi.net writes:
are you using the hackage-released version of random-fu or the darcs one?
I was using the hackage version, but since then I switched to the darcs version. (Btw, began using it in some of my projects and I'm really happy about it.)
In the above case, I was using IO in the first bgroup and State StdGen in the second.
I'm running it on a x86_64 Gentoo Linux box with GHC 6.10.4 and was unable to install Criterion (apparently, impossible is happening while compiling vector-algorithms) so I used 'time' to come up with some results. Below doesn't include IO tests (randomRIO, etc.), since they turned out to be spectacularly slow anyway. Results using ghc -O2.
module Main (main) where
import Data.Random import Data.List import Control.Monad.State import Control.Monad.Random import System.Random
test = p1 `fmap` getStdGen type RType = Double
/usr/bin/time results for (test, RType): (p1, Double) : ~3.3 secs (p2, Double) : ~1.7 secs (p3, Double) : ~1.0 sec (p1, Int) : ~1.9 secs (p2, Int) : ~1.0 sec (p3, Int) : ~0.5 sec
count = 10 ^ 6 range = (-10, 10) type P = StdGen -> [RType]
p1 = evalState (sample (replicateM count (uncurry uniform range))) :: P
p2 = evalRand (replicateM count (getRandomR range)) :: P
p3 = take count . evalRand (getRandomRs range) :: P
main = test >>= (print . foldl' (+) 0)
Using 'sum' turned to be rather misleading (took up to a minute to sum up 'Double's; this problem was less apparent for p1), so I had to use foldl' here to get consistent results between 'Int's and 'Double's. '`using` rnf' produced similar results. Also, using DevURandom for random-fu produces almost the same results. -- Gökhan San

Thanks for the clues, I'll try and make some time this weekend to track it down. I do have some gentoo x64 systems to play with. My first impulse is actually that it is likely due to differences in inlining and/or rewrite rule processing between the GHC versions, but we'll see what turns up. -- James On Apr 9, 2010, at 6:51 AM, Gökhan San wrote:
mokus@deepbondi.net writes:
are you using the hackage-released version of random-fu or the darcs one?
I was using the hackage version, but since then I switched to the darcs version. (Btw, began using it in some of my projects and I'm really happy about it.)
In the above case, I was using IO in the first bgroup and State StdGen in the second.
I'm running it on a x86_64 Gentoo Linux box with GHC 6.10.4 and was unable to install Criterion (apparently, impossible is happening while compiling vector-algorithms) so I used 'time' to come up with some results.
Below doesn't include IO tests (randomRIO, etc.), since they turned out to be spectacularly slow anyway. Results using ghc -O2.
module Main (main) where
import Data.Random import Data.List import Control.Monad.State import Control.Monad.Random import System.Random
test = p1 `fmap` getStdGen type RType = Double
/usr/bin/time results for (test, RType):
(p1, Double) : ~3.3 secs (p2, Double) : ~1.7 secs (p3, Double) : ~1.0 sec (p1, Int) : ~1.9 secs (p2, Int) : ~1.0 sec (p3, Int) : ~0.5 sec
count = 10 ^ 6 range = (-10, 10) type P = StdGen -> [RType]
p1 = evalState (sample (replicateM count (uncurry uniform range))) :: P
p2 = evalRand (replicateM count (getRandomR range)) :: P
p3 = take count . evalRand (getRandomRs range) :: P
main = test >>= (print . foldl' (+) 0)
Using 'sum' turned to be rather misleading (took up to a minute to sum up 'Double's; this problem was less apparent for p1), so I had to use foldl' here to get consistent results between 'Int's and 'Double's. '`using` rnf' produced similar results.
Also, using DevURandom for random-fu produces almost the same results.
--
Gökhan San

I have now had a chance to experiment with these a bit, and have come up with some changes that bring random-fu's speed in these tests into line with Control.Monad.Random's when compiled with ghc-6.12.1, although it is still a bit slower when using GHC 6.10.4. This is partially because one of the optimization flags I enabled does not work with ghc-6.10.4 (strict dictionaries - the flag exists on the older ghc but causes it to panic on several of the source files). Actually, I'm a bit surprised I was able to get comparable performance out of it on either platform, because it's doing a bit more with the StdGen than System.Random's "Random" class in the first place. In the Double case, it's using more entropy (System.Random converts a uniform Int32 to a Double, random-fu expects at least 52 bits of entropy in a Double) and in the Int case it's doing an extra 'mod' and a rejection test to make the results uniform. In any case, it is still far from perfect (in particular, these exact same tests are still a bit slower for Integer even on ghc-6.12.1), but I believe it is better. If anyone has any further suggestions, either about how to speed things up or about other places to focus effort on improving, please pass them on to me. BTW, I was able to get vector-algorithms to build on GHC 6.10.4 by commenting out an internal type signature (I don't have the system I did this on in front of me but I seem to recall it was a function called "partitionBy" or similar, towards the bottom of Intro.hs), and after that I had no further trouble building criterion. -- James On Apr 9, 2010, at 6:51 AM, Gökhan San wrote:
mokus@deepbondi.net writes:
are you using the hackage-released version of random-fu or the darcs one?
I was using the hackage version, but since then I switched to the darcs version. (Btw, began using it in some of my projects and I'm really happy about it.)
In the above case, I was using IO in the first bgroup and State StdGen in the second.
I'm running it on a x86_64 Gentoo Linux box with GHC 6.10.4 and was unable to install Criterion (apparently, impossible is happening while compiling vector-algorithms) so I used 'time' to come up with some results.
Below doesn't include IO tests (randomRIO, etc.), since they turned out to be spectacularly slow anyway. Results using ghc -O2.
module Main (main) where
import Data.Random import Data.List import Control.Monad.State import Control.Monad.Random import System.Random
test = p1 `fmap` getStdGen type RType = Double
/usr/bin/time results for (test, RType):
(p1, Double) : ~3.3 secs (p2, Double) : ~1.7 secs (p3, Double) : ~1.0 sec (p1, Int) : ~1.9 secs (p2, Int) : ~1.0 sec (p3, Int) : ~0.5 sec
count = 10 ^ 6 range = (-10, 10) type P = StdGen -> [RType]
p1 = evalState (sample (replicateM count (uncurry uniform range))) :: P
p2 = evalRand (replicateM count (getRandomR range)) :: P
p3 = take count . evalRand (getRandomRs range) :: P
main = test >>= (print . foldl' (+) 0)
Using 'sum' turned to be rather misleading (took up to a minute to sum up 'Double's; this problem was less apparent for p1), so I had to use foldl' here to get consistent results between 'Int's and 'Double's. '`using` rnf' produced similar results.
Also, using DevURandom for random-fu produces almost the same results.
--
Gökhan San

Since they weren't mentioned in this thread, I'll point out that there are better sources of entropy than /dev/random, /dev/urandom, and the Windows API. For example, the two sites https://random.org/integers https://www.fourmilab.ch/hotbits/secure_generate.html both offer free random bits via a secure REST interface. Random.org is run by Mads Haahr of the School of Computer Science and Statistics at Trinity College, Dublin. They use background atmospheric radio noise to generate the entropy. Fourmilab is run by John Walker. He uses a source of radioactive decay (Ce 137) and a geiger counter to generate the entropy. Both sites have gone to some trouble in design and testing to ensure that their entropy is truly random. There are quotas on the number of bits you can retrieve per day for free at each of the sites. At random.org, you can purchase additional entropy at low cost. Regards, Yitz

Yitzchak Gale
Since they weren't mentioned in this thread, I'll point out that there are better sources of entropy than /dev/random, /dev/urandom, and the Windows API.
For example, the two sites
https://random.org/integers https://www.fourmilab.ch/hotbits/secure_generate.html
both offer free random bits via a secure REST interface.
I would prefer /dev/random, /dev/urandom and the Windows API over those sources. Firstly receiving random strings through the internet is slow -- too slow for many applications. Also it can fail. But more importantly you have no control over who generates, watches and perhaps even intercepts the stream. In many applications randomness is worth nothing if other people have access to the random data. The random streams from the two services you mentioned are hardly any better for any practical purpose than what /dev/*random can provide, especially if you use an entropyd. If cryptographic strength is required you can just use the random stream from /dev/*random. Otherwise I recommend seeding mersenne-random or mwc-random from /dev/*random and using the PRNG. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

I've used this one before: betterStdGen :: IO StdGen betterStdGen = alloca $ \p -> do h <- openBinaryFile "/dev/random" ReadMode hGetBuf h p $ sizeOf (undefined :: Int) hClose h mkStdGen <$> peek p

Hello Christopher,
unfortunately this is not a "better StdGen", because it still uses the
poor PRNG algorithm of StdGen. You can get better statistic properties
by using a package like mwc-random or mersenne-random.
However, if you want (an approximation of) truely random numbers, you
need to read from /dev/random. If you prefer pseudo-random numbers, but
need cryptographic strength, you can use the "OpenSSL.Random" module
from the HsOpenSSL package.
Greets,
Ertugrul
Christopher Done
I've used this one before:
betterStdGen :: IO StdGen betterStdGen = alloca $ \p -> do h <- openBinaryFile "/dev/random" ReadMode hGetBuf h p $ sizeOf (undefined :: Int) hClose h mkStdGen <$> peek p
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

Christopher Done wrote:
betterStdGen :: IO StdGen
Here's what I have been using. It's a bit more complete. Of course, you can always use mkStdGen with it to get one of those if you want. (Yes, I often do that. StdGen is much maligned, but it's pretty good at what it's designed for.) Regards, Yitz module DevRandom where import System.IO import System.IO.Error import Foreign.Marshal.Alloc import Foreign.Storable import Foreign.Ptr data BlockingMode = Blocking | NonBlocking deriving (Eq, Show) -- Read data from the system random device. -- Return Nothing if there is currently not -- enough entropy in the system random device. devRandom :: Storable a => IO (Maybe a) devRandom = readDev "/dev/random" NonBlocking -- Read data from the system random device. -- If necessary, wait until there is -- enough entropy in the system random device. devRandomWait :: Storable a => IO a devRandomWait = readDev dev Blocking >>= maybe (devRandomError dev) return where dev = "/dev/random" -- Read data from the system random device. -- If there is currently not enough entropy -- in the system random device, use a lower -- quality source of randomness instead. devURandom :: Storable a => IO a devURandom = readDev dev NonBlocking >>= maybe (devRandomError dev) return where dev = "/dev/urandom" readDev :: Storable a => FilePath -> BlockingMode -> IO (Maybe a) readDev dev mode = do h <- openFile dev ReadMode hSetBuffering h NoBuffering alloca $ getMaybe h undefined where getMaybe :: Storable a => Handle -> a -> Ptr a -> IO (Maybe a) getMaybe h undef ptr = do let size = sizeOf undef n <- case mode of Blocking -> hGetBuf h ptr size NonBlocking -> hGetBufNonBlocking h ptr size if n < size then return Nothing else fmap Just $ peek ptr devRandomError :: FilePath -> IO a devRandomError p = ioError $ mkIOError illegalOperationErrorType "Unable to read from the system random device" Nothing (Just p)
participants (9)
-
Alex Rozenshteyn
-
Christopher Done
-
Ertugrul Soeylemez
-
gsan@stillpsycho.net
-
James Andrew Cook
-
James Cook
-
Matthew Hayden
-
mokus@deepbondi.net
-
Yitzchak Gale