State Transformer

Remi Turk remi@abcweb.nl
Mon, 7 Jan 2002 22:50:55 +0100


--E7i4zwmWs5DOuDSH
Content-Type: multipart/mixed; boundary="gDGSpKKIBgtShtf+"
Content-Disposition: inline


--gDGSpKKIBgtShtf+
Content-Type: text/plain; charset=us-ascii
Content-Disposition: inline
Content-Transfer-Encoding: quoted-printable

Hi,
I'm still learning Haskell too, but I recently wrote a small
module which implements an infinite list of random Integers
(it gets its random seed from /dev/random :)

Using it means nothing more than:

import DevRandom

main    =3D randomIntegers 100 >>=3D mapM_ print . take 10


Happy Hacking

	Remi

--=20
I have so much
I want to say
but it doesen't matter
anyway

Key fingerprint =3D CC90 A1BA CF6D 891C 5B88  C543 6C5F C469 8F20 70F4

--gDGSpKKIBgtShtf+
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="DevRandom.hs"
Content-Transfer-Encoding: quoted-printable

{-
	Read from /dev/random
	Copyright (C) 2001 Remi Turk <remi@abcweb.nl>

	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	=3D do
						byte <- readByte fd
						string <- unsafeInterleaveIO $ fdGetContents fd
						return $ byte : string
	where
		readByte	:: Fd -> IO Char
		readByte fd	=3D fdRead fd 1 >>=3D \(str,count) -> return $ head str

-- Read a string from /dev/random (Basically getContents "/dev/random")
randomContents		:: IO String
randomContents		=3D fdIO >>=3D fdGetContents
	where
		fdIO		:: IO Fd
		fdIO		=3D openFd "/dev/random" ReadOnly Nothing
						(OpenFileFlags False False False False False)

-- Read random Integers below a certain maximum
randomIntegers		:: Integer -> IO [Integer]
randomIntegers max	=3D randomContents >>=3D
							return .
								map (`rem`(max+1)) .
								map strToNum .
								groupByLen (bytesPerInteger max)
	where
		strToNum		:: String -> Integer
		strToNum xs	=3D
						let
							strToNum'		:: Integer -> [Integer] -> Integer
							strToNum' cur []	=3D cur
							strToNum' cur (x:xs)=3D strToNum' (cur * 256 + x) xs
							strOrds				:: String -> [Integer]
							strOrds				=3D map (toInteger . ord)
						in
							strToNum' 0 (strOrds xs)

		groupByLen		:: Int -> String -> [String]
		groupByLen len xs =3D
						let
							next (start,others)	=3D splitAt len others
						in
							map fst $ tail $ iterate next ("", xs)

		bytesPerInteger	:: Integer -> Int
		bytesPerInteger x =3D
						let
							pows2		=3D [(n, 2 ^ n - 1) | n <- [8,16..]]
							firstGT x	=3D head . filter ((>=3Dx) . snd)
						in=09
							(fst $ firstGT x pows2) `quot` 8

--gDGSpKKIBgtShtf+--

--E7i4zwmWs5DOuDSH
Content-Type: application/pgp-signature
Content-Disposition: inline

-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.0.6 (GNU/Linux)
Comment: For info see http://www.gnupg.org

iD8DBQE8Ohg/bF/EaY8gcPQRAiQjAJ9RTmKYhKOWgu73mNgh62YGSKNyxwCeL8Tz
xtBoXs9A7Ko3L2/upg2SpNI=
=Uo4n
-----END PGP SIGNATURE-----

--E7i4zwmWs5DOuDSH--