[Haskell-cafe] MonadGL - Partitioning effects without giving up type inference

Jules Bean jules at jellybean.co.uk
Thu Sep 13 14:34:49 EDT 2007


The OpenGL bindings which come bundled with ghc are a really great
example of how even an "almost-literal" port of a C API can still
be easier to work with in haskell than it is in C, because of the
benefits of type inference and powerful abstractions. Even the
ability to mapM_ is a tool to make C programmers envious, and there
are useful combinators like preservingMatrix to guarantee pairing of
pushes and pops.

Because the bindings are ported over using the FFI, all the GL calls
are in the IO monad. GL is build around state machines, so it's not at
all surprising to end up in some kind of state monad. However, we find
that the type system is not powerful enough to distinguish between

myActionWhichOnlyMakesGLCalls :: IO ()

and

myActionWhichMixesGLAndIO :: IO ()

It would be much nicer if the type-system could distinguish the two.
One case in point is that an arbitrary IO action can modify IORefs,
and it would be nice to have actions whose type guaranteed that they
didn't do that.

It's fairly simple to imagine something like the following:


 > {-# OPTIONS -fglasgow-exts #-}

(extensions are only for deriving (Monad), it's not important)

 >
 > newtype GL a = GL { runGL :: IO a } deriving (Monad)
 >
 > unsafeIOToGL :: IO a -> GL a
 > unsafeIOToGL = GL

The intention here of course is that we export 'runGL' which is safe,
having type GL a -> IO a, but don't export unsafeIOToGL.

Then we have lots of functions which are imported via the FFI and
end up with IO types, here is a trival example:

 > _foo :: IO ()
 > _foo = putStrLn "OpenGL!"

And we embed them into the GL monad. No other module can corrupt our
GL monad because we don't export unsafeIOToGL.

 > foo :: GL ()
 > foo = unsafeIOToGL _foo

As far as it goes, this technique is absolutely fine. We end up being
able to write actions entirely in the GL monad:

*Main> :t do { foo ; foo ; foo }
do { foo ; foo ; foo } :: GL ()

...as well as actions which mix general IO and GL calls :

*Main> :t do { runGL foo ; putStrLn "Not a GL call" ; runGL foo }
do { runGL foo ; putStrLn "Not a GL call" ; runGL foo } :: IO ()

The point of this message is actually to get rid of those annoying
'runGL' calls. When writing an IO action I want to be able to freely
intermix IO and GL calls. When writing a GL-only action, I want to
only use GL calls. And I want the type system to enforce that; and
ideally, infer it too.

So we define a type-class for "monad which can perform GL" :

 > class Monad m => MonadGL m where
 >     runMonadGL :: m a -> IO a
 >     embedGL    :: GL a -> m a

And we write an instance for IO:

 > instance MonadGL IO where
 >     runMonadGL = id
 >     embedGL    = runGL

Now we are able to bind our FFI call _foo slightly differently:

 > foo' :: MonadGL m => m ()
 > foo' = embedGL foo

This is interesting because, although we know that IO is in fact
the only instance of MonadGL, there might in principle be others.
(For example, GL is itself an instance of MonadGL if you put
runMonadGL = runGL and embedGL = id). The type signature for foo'
guarantees that it will run in *any* MonadGL, and therefore can't
use any IO-specific effects, only the GL ones.

Now we get the automatic type inference we want:

*Main> :t do { foo' ; foo' ; foo' }
do { foo' ; foo' ; foo' } :: (MonadGL t) => t ()

This only performs GL actions, no IO.

*Main> :t do { foo' ; putStrLn "Normal" ; foo' }
do { foo' ; putStrLn "Normal" ; foo' } :: IO ()

The single IO call here forces the type to IO, but we are not
required to put noisy 'runGL's in front of every GL call.

This technique is quite scalable in that you can have any number
of MonadFoos representing different librarys with different kinds
of state, and (as long as you don't mind the modest blow-up
in type signature size) you get, for an arbitrary action, a
type signature which pins down precisely what kinds of side-effect
the action can have.

It would, however, be a real pain to run through all the 'foreign'
calls in the rather large GL library and add appropriate wrappers
of the form 'embedGL . unsafeIOToGL'. Definitely a job for
an automated tool.

Incidentally, I don't believe this technique has any performance
implication at all. The newtypes are all erased at compile time.

Any comments? I'm sure this has been shown before but I don't
remember where.

Jules


More information about the Haskell-Cafe mailing list