[Haskell-cafe] Password hashing

roger peppe rogpeppe at gmail.com
Thu Oct 30 04:49:03 EDT 2008


if you're prepared to expend a few cpu cycles, you can always
use something like the following "beating clocks" algorithm, which
should generate
at least some genuine randomness, as long as you've got preemptive
scheduling, and a few hardware interrupts around the place.

>module Clockbeat where
>import Control.Concurrent
>import Control.Monad
>import Data.IORef
>
>random :: IO Int
>random = do
>	m <- newEmptyMVar
>	v <- newIORef (0 :: Int)
>
>	fast <- forkIO $ forever $ do
>		v' <- readIORef v
>		let v'' = v' + 1 in
>			v'' `seq` writeIORef v v''
>	slow <- forkIO $ forever $
>		do
>			threadDelay 500000
>			val <- readIORef v
>			putMVar m (val `mod` 2)
>	r <- replicateM 31 $ takeMVar m
>	killThread fast
>	killThread slow
>	return $ sum $ zipWith (*) (map (2 ^) [0..]) r


More information about the Haskell-Cafe mailing list