import System.Random -- Two calls tow the program, generate different outputs main :: IO () main = do -- make an initial random number using getStdGen (system entropy, hence IO monad) initial_gen <- getStdGen let initial_rand_value = mkRandomValue (0 , 100) initial_gen :: RandomFloat putStrLn "Initial random value" print initial_rand_value -- This is your initial pseudo-random number -- Two calls to the same function generate the same result putStrLn "These two lines should be same, but still random-ish" print $ addRandom initial_rand_value print $ addRandom initial_rand_value putStrLn "This line should output something random" print $ subRandom initial_rand_value -- The advantage, is that functions compose well. putStrLn "We can compose!!" print $ subRandom . addRandom $ initial_rand_value -- This type allow you to get a (random) value -- And to generate a new one from it. I think the constructor -- should be private in order to guarantee randomness data RandomValue a = RandomValue { value :: a -- The value , new :: RandomValue a -- get a new random value } -- example type RandomFloat = RandomValue Float -- Smart constructor. Uses laziness to store the "next random value" ad infinitum. mkRandomValue :: UniformRange a => (a, a) -> StdGen -> RandomValue a mkRandomValue (low, high) initial_gen = RandomValue v (mkRandomValue (low, high) new_gen) where (v, new_gen) = uniformR (low, high) initial_gen -- Given a random number, add a random amount to it addRandom :: Num a => RandomValue a -> RandomValue a addRandom rand_float = let other = new rand_float in rand_float + other -- Given a random number, subtract a random amount to it subRandom :: Num a => RandomValue a -> RandomValue a subRandom rand_float = let other = new rand_float in rand_float - other -- Useful instances. Notice, you can't make an Applicative/Monad instance -- because is impossible (is it, right?) to define pure/return for RandomValue. -- Also notice the Num instance is incomplete... precissely, because you can't -- define fromInteger :: Int -> RandomValue a instance Show a => Show (RandomValue a) where show (RandomValue a _) = show a -- Be sure, you don't evaluate the inifite series of rand numbers!! instance Functor RandomValue where fmap f (RandomValue v n) = RandomValue (f v) (fmap f n) instance Num a => Num (RandomValue a) where (RandomValue v n) + (RandomValue v' _) = RandomValue (v + v') (new n) (RandomValue v n) - (RandomValue v' _) = RandomValue (v - v') (new n) (RandomValue v n) * (RandomValue v' _) = RandomValue (v * v') (new n) abs (RandomValue v n) = RandomValue (abs v) (new n) signum (RandomValue v n) = RandomValue (signum v) (new n)