-- Module : System.Random.TF.Init -- Copyright : (c) 2013 Michał Pałka -- License : BSD3 -- -- Maintainer : michal.palka@chalmers.se -- Stability : experimental -- Portability : portable -- module System.Random.TF.Init where import Control.Monad (when) --import Data.Int import Data.Word import Foreign import Data.Ratio (numerator, denominator) import Data.Time import System.CPUTime import System.IO -- | Use system time create the random seed. -- This method of seeding may not be relible. mkSeedTime :: IO (Word64, Word64, Word64, Word64) mkSeedTime = do utcTm <- getCurrentTime cpu <- getCPUTime let daytime = toRational $ utctDayTime utcTm t1, t2 :: Word64 t1 = fromIntegral $ numerator daytime t2 = fromIntegral $ denominator daytime day = toModifiedJulianDay $ utctDay utcTm d1 :: Word64 d1 = fromIntegral day c1 :: Word64 c1 = fromIntegral cpu return (t1, t2, d1, c1) -- | Use the UNIX special file @\/dev\/urandom@ to create the seed. -- Inspired by @random-mwc@. mkSeedUnix :: IO (Word64, Word64, Word64, Word64) mkSeedUnix = do let bytes = 32 rfile = "/dev/urandom" l <- allocaBytes bytes $ \buf -> do nread <- withBinaryFile rfile ReadMode $ \h -> hGetBuf h buf bytes when (nread /= bytes) $ fail $ "mkSeedUnix: Failed to read " ++ show bytes ++ " from " ++ rfile peekArray 4 buf let [x1, x2, x3, x4] = l return (x1, x2, x3, x4)