Re: [Haskell-cafe] True Random Numbers

2010-04-15 Thread Yitzchak Gale
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- hGetBufh 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)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] True Random Numbers

2010-04-03 Thread 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


Re: [Haskell-cafe] True Random Numbers

2010-04-03 Thread Matthew Hayden
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 rpglove...@gmail.com wrote:

 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


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


Re: [Haskell-cafe] True Random Numbers

2010-04-03 Thread 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe