[Haskell] Re: Global Variables and IO initializers

John Peterson peterson-john at cs.yale.edu
Thu Nov 4 11:51:12 EST 2004


I've been meaning to get into this debate ...

Koen proposes:
  Imagine a commutative monad, CIO. Commutative monads have
  the property that it does not matter in what order actions
  are performed, they will have the same effect. In other
  words, for all m1 :: CIO A, m2 :: CIO B, k :: A -> B -> CIO
  C, it should hold that:

    do a <- m1             do b <- m2
       b <- m2     ===        a <- m1
       k a b                  k a b

  Now, one could imagine an extension X of Haskell98, in which
  modules are allowed to contain definitions of the form:

    p <- m

  Here, p is a (monomorphic) pattern, and m is of type CIO A,
  for some type A. CIO is an (abstract) monad provided in a
  library module, just like IO is today.

  One could wonder where the primitive actions in the monad
  CIO come from? Well, library providers (compilers) could
  provide these. For example:

    newIORefCIO     :: a -> CIO (IORef a)
    newEmptyMVarCIO :: CIO (MVar a)

  And so on.

  The implementer of these functions has to guarantee that the
  actions do not destroy the commutativity of the CIO monad.
  This is done in the same way as today, compiler writers and
  users of the FFI guarantee that certain primitive operations
  such as + on Ints are pure.

  The FFI could even adapt CIO as a possible result type
  (instead of having just pure functions or IO functions in
  the FFI).

This is definitely a step in the right direction.  I am using this
syntax already in Pan# and it's definitely the right thing to do.  I
would be hesitant to have any direct connection between this syntax
and a specific monad (like CIO) - I want the same syntax in inner let
statements and would like a context such as CMonad => to pop out when
I see <- in a let, where CMonad is any commutative monad.

The monads I use are a name supply and writer (which writes into a set
rather than a list to preserve commutativity).  As long as "CIO" had
these I could use it but it would ne more interesting to avoid placing
the initializations in a specific monad.

Ultimately, I want the main program to see the initializing action:

main :: CMonad m => m () -> IO ()

or if you have a specific monad in mind:

main :: CIO () -> IO ()

The use of the CMonad type class is probably tough since you might want to
blend modules with different initialization monads.  You can address
this with yet more type classes or just give up and use a single CIO
type.  But the main thing I want is a feedback path from the
initializers to the main program.  You could hack this by allowing CIO
computations to get at a name supply and write into some kind of
output for the main program but that seems a bit hacky to me.  Much
better to allow the main program to "run" the initialization code.

All of this rambling non-withstanding, the idea of top level <- and a 
commutative monad are the really import ones.  I think this would be
an excellent way to address this issue in the real spirit of
functional programming rather than just hacking things on and hoping
they don't have any unintended consequences.

   John





More information about the Haskell mailing list