[Haskell-cafe] Functions with side-effects?

Glynn Clements glynn at gclements.plus.com
Fri Dec 23 06:12:01 EST 2005


Daniel Carrera wrote:

> I'm a Haskell newbie and I don't really understand how Haskell deals 
> with functions that really must have side-effects. Like a rand() 
> function or getLine().

Those aren't functions.

A function is a single-valued relation, i.e. a (possibly infinite) set
of ordered pairs <x,y> such that the set doesn't contains two pairs
<a,b> and <c,d> where a == c and b =/= d. IOW, a static mapping from
argument to result.

Haskell uses the term "function" to mean a function in the strict
mathematical sense, and not (like most other languages) to mean a
procedure which returns a value as well as reading and writing some
implicit state.

> I know this has something to do with monads, but I don't really 
> understand monads yet. Is there someone who might explain this in newbie 
> terms? I don't need to understand the whole thing, I don't need a rand() 
> function right this minute. I just want to understand how Haskell 
> separates purely functional code from non-functional code (I understand 
> that a rand() function is inevitably not functional code, right?)

All Haskell code is functional (discounting certain low-level details
such as unsafePerformIO).

Side effects are implemented by making the prior state an argument and
the new state a component of the result, i.e. a C procedure of type:

	res_t foo(arg_t);

becomes a Haskell function with type:

	ArgType -> State -> (State, ResType)

To simplify coding (particularly, making sure that you use the correct
iteration of the state at any given point), all of this is usually
wrapped up in an instance of the Monad class. But there isn't anything
special about Monad instances. The class itself and many of its
instances are written in standard Haskell.

To provide a concrete example, here's a monadic random number
generator:

	type Seed = Int
	
	data Rand a = R { app :: Seed -> (Seed, a) }
	
	myRand :: Rand Int
	myRand = R $ \seed -> let
			result = (seed' `div` 65536) `mod` 32768
			seed' = seed * 1103515245 + 12345
			in (seed', result)
	
	instance Monad Rand where
		f >>= g = R $ \seed -> let (seed', x) = app f seed
					 in app (g x) seed'
		return x = R $ \seed -> (seed, x)
	
	runR :: Seed -> Rand a -> a
	runR seed f = snd $ app f seed

Example usage:

	randomPair :: Rand (Int, Int)
	randomPair = do
		myRand >>= \x ->
		myRand >>= \y ->
		return (x, y)

or, using "do" notation (which is simply syntactic sugar):

	randomPair :: Rand (Int, Int)
	randomPair = do
		x <- myRand
		y <- myRand
		return (x, y)

	main = print $ runR 99 randomPair

The main difference between the built-in IO monad and the Rand monad
above is that where the Rand monad has a Seed for its state, the IO
monad has the (conceptual) World type.

As the World type has to represent the entire observable state of the
universe, you can't actually obtain instances of it within a Haskell
program, and thus there is no equivalent to runR.

Instead, you provide an IO instance (main) to the runtime, which
(conceptually) applies it to the World value representing the state of
the universe at program start, and updates the universe to match the
World value returned from main at program end.

-- 
Glynn Clements <glynn at gclements.plus.com>


More information about the Haskell-Cafe mailing list