{- Read from /dev/random Copyright (C) 2001 Remi Turk This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. -} module DevRandom(randomContents, randomIntegers) where import IO import Posix import Char import IOExts import System -- Read a string from a Posix filedescriptor fdGetContents :: Fd -> IO String fdGetContents fd = do byte <- readByte fd string <- unsafeInterleaveIO $ fdGetContents fd return $ byte : string where readByte :: Fd -> IO Char readByte fd = fdRead fd 1 >>= \(str,count) -> return $ head str -- Read a string from /dev/random (Basically getContents "/dev/random") randomContents :: IO String randomContents = fdIO >>= fdGetContents where fdIO :: IO Fd fdIO = openFd "/dev/random" ReadOnly Nothing (OpenFileFlags False False False False False) -- Read random Integers below a certain maximum randomIntegers :: Integer -> IO [Integer] randomIntegers max = randomContents >>= return . map (`rem`(max+1)) . map strToNum . groupByLen (bytesPerInteger max) where strToNum :: String -> Integer strToNum xs = let strToNum' :: Integer -> [Integer] -> Integer strToNum' cur [] = cur strToNum' cur (x:xs)= strToNum' (cur * 256 + x) xs strOrds :: String -> [Integer] strOrds = map (toInteger . ord) in strToNum' 0 (strOrds xs) groupByLen :: Int -> String -> [String] groupByLen len xs = let next (start,others) = splitAt len others in map fst $ tail $ iterate next ("", xs) bytesPerInteger :: Integer -> Int bytesPerInteger x = let pows2 = [(n, 2 ^ n - 1) | n <- [8,16..]] firstGT x = head . filter ((>=x) . snd) in (fst $ firstGT x pows2) `quot` 8