z_axis <z_a...@163.com> wrote: > 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/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe