How to write such a code elegantly ?

betterStdGen :: IO StdGen betterStdGen = alloca $ \p -> do h <- openBinaryFile "/dev/urandom" ReadMode hGetBuf h p $ sizeOf (undefined :: Int) hClose h mkStdGen <$> peek p picoSec :: IO Integer picoSec = do t <- ctPicosec `liftM` (getClockTime >>= toCalendarTime) return t The pseudo-code is : if doesFileExist "/dev/urandom" then myGen = betterStdGen else myGen = (mkStdGen . fromTnteger) <$> picoSec How to write these pseudo-code elegantly ? Sincerely! ----- e^(π.i) + 1 = 0 -- View this message in context: http://haskell.1045720.n5.nabble.com/How-to-write-such-a-code-elegantly-tp33... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 10 January 2011 10:44, z_axis
betterStdGen :: IO StdGen betterStdGen = alloca $ \p -> do h <- openBinaryFile "/dev/urandom" ReadMode hGetBuf h p $ sizeOf (undefined :: Int) hClose h mkStdGen <$> peek p
Maybe use a catch or something here and have it return "IO (Maybe StdGen)", with Nothing denoting that file not existing? -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

z_axis
betterStdGen :: IO StdGen betterStdGen = alloca $ \p -> do h <- openBinaryFile "/dev/urandom" ReadMode hGetBuf h p $ sizeOf (undefined :: Int) hClose h mkStdGen <$> peek p
picoSec :: IO Integer picoSec = do t <- ctPicosec `liftM` (getClockTime >>= toCalendarTime) return t
The pseudo-code is :
if doesFileExist "/dev/urandom" then myGen = betterStdGen else myGen = (mkStdGen . fromTnteger) <$> picoSec
How to write these pseudo-code elegantly ?
I would do this: {-# LANGUAGE ScopedTypeVariables #-} readFrom :: forall a. Storable a => Handle -> IO a readFrom h = alloca $ \ptr -> hGetBuf h ptr (sizeOf (undefined :: a)) >> peek ptr newStdGen' :: IO StdGen newStdGen' = do mh <- try $ openBinaryFile "/dev/urandom" ReadMode case mh of Left err -> ctPicosec <$> (getClockTime >>= toCalendarTime) Right h -> mkStdGen <$> readFrom h `finally` hClose h Warning: Untested code, but it should work and have a safer file handling. Also note that the current implementation (base >= 4) does this already. You should probably try one of the more sophisticated PRNG libraries out there. Check out mersenne-random and mwc-random. If you want a pure generator, there is also mersenne-random-pure64 and some other libraries. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

thanks for all of your replies. I will test your code later. Another newbie question is why has the following code indentation problem ? rollDice n = do let myGen = if doesFileExist "/dev/urandom" then betterStdGen else (mkStdGen . fromInteger) <$> picoSec return $ (take 1 $ randomRs (1,n) myGen) !! 0 Sincerely! ----- e^(π.i) + 1 = 0 -- View this message in context: http://haskell.1045720.n5.nabble.com/How-to-write-such-a-code-elegantly-tp33... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On 10 January 2011 12:25, z_axis
thanks for all of your replies. I will test your code later. Another newbie question is why has the following code indentation problem ?
rollDice n = do let myGen = if doesFileExist "/dev/urandom" then betterStdGen else (mkStdGen . fromInteger) <$> picoSec return $ (take 1 $ randomRs (1,n) myGen) !! 0
I don't see an indentation problem, but I _do_ see a type problem: doesFileExist presumably uses IO, and as such can't be used as a Bool for the if statement. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

rollDice n = do tmp <- doesFileExist "/dev/urandom" myGen <- if tmp then betterStdGen else (mkStdGen . fromInteger) <$> picoSec return $ (take 1 $ randomRs (1,n) myGen) !! 0 works but not so elegant? ----- e^(π.i) + 1 = 0 -- View this message in context: http://haskell.1045720.n5.nabble.com/How-to-write-such-a-code-elegantly-tp33... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

why has the following code indentation problem ?
rollDice n = do let myGen = if doesFileExist "/dev/urandom" then betterStdGen else (mkStdGen . fromInteger) <$> picoSec
because "if" starts in the same column as "myGen", so the parser inserts a ";" before the "if". J.W.

On Mon, 10 Jan 2011 01:44:26 +0100, z_axis
picoSec :: IO Integer picoSec = do t <- ctPicosec `liftM` (getClockTime >>= toCalendarTime) return t : How to write these pseudo-code elegantly ?
picoSec can be simplified to: picoSec = ctPicosec `liftM` (getClockTime >>= toCalendarTime) or: picoSec = ctPicosec <$> (getClockTime >>= toCalendarTime) Regards, Henk-Jan van Tuyl -- http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html --
participants (5)
-
Ertugrul Soeylemez
-
Henk-Jan van Tuyl
-
Ivan Lazar Miljenovic
-
J. Waldmann
-
z_axis