Reference types

Simon Peyton-Jones simonpj@microsoft.com
Tue, 5 Feb 2002 07:50:41 -0800


For some time now, GHC and Hugs have had the following=20
families of types and operations:

	data IO a
	data IORef a
	newIORef   :: a -> IO (IORef a)
	readIORef  :: IORef a -> IO a
	writeIORef :: IORef a -> a -> IO ()


	data ST s a
	data STRef s a
	newSTRef   :: a -> ST s (STRef s a)
	readSTRef  :: STRef s a -> ST s a
	writeSTRef :: STRef s a -> a -> ST s ()

The basic bind operations etc are overloaded for IO and ST,
but to overload the Ref operations one needs to add=20

	class RefMonad r m | r -> m, m -> r where
	  newRef   :: a -> m (r a)
	  readRef  :: r a -> m a
	  writeRef :: r a -> a -> m ()

	instance RefMonad IORef     IO     where ...
	instance RefMonad (STRef s) (IO s) where ...

A multi-paramter type class is needed.  Notice particularly the
bidirectional functional dependencies.  This is the only convincing
example I know with functional dependencies going both ways.

Or at least it was.  But in a recent conversation with Peter Thiemann
I realised that this is all baloney.  There's a much easier type
structure:

	data Ref m a	-- References in monad m, values of type a

	newIORef :: a -> IO (Ref IO a)
	readIORef  :: Ref IO a -> IO a
	writeIORef :: Ref IO a -> a -> IO ()

	newSTRef   :: a -> ST s (Ref (ST  s) a)
	readSTRef  :: Ref (ST  s) a -> ST s a
	writeSTRef :: Ref (ST  s) a -> a -> ST s ()

	class RefMonad m where
	  newRef   :: a -> m (Ref m a)
	  readRef  :: Ref m a -> m a
	  writeRef :: Ref m a -> a -> m ()

	instance RefMonad IO     where ...
	instance RefMonad (ST s) where ...


No functional dependencies.  No multi-parameter classes.  Pure Haskell
98.  All of this works for mutable arrays too, of course.

I'm sending this to the Haskell list for several reasons.

1.  It's a good lesson in "don't use a sledgehammer just becaues
    it happens to be to hand".

2.  I'd be interested to know of any other examples you have of
    *bi-directional* functional depenencies.  The above simplification
    nukes my only convincing example.  (Usually one set of
    type variables determines another, but not vice versa.)

Unless there's some technical flaw, this simpler type structure will
be in the new hierarchical Haskell library structure.

Simon