
I finally understood that George Russell's Library is not really about global variables. Rather it is about what I want to call 'execution contexts', which are -- as Marcin Kowalczyk observed -- a restricted form of dynamically scoped variables. [NB: Another (maybe better) name would have been 'execution environment' but the name "environment" is too heavily associated with the related concept of process environment (the string to string map given to user processes as an implicit argument).] An execution context is a mutable finite map from types to (monomorphic) values. Each IO action implicitly carries exactly one such map and by default passes it on to the actions that follow. A function is provided to (implicitly) create a new mapping and run a given IO action with the new mapping as its execution context, instead of the default one. [NB: I also understand now why the library uses ThreadIds. This was obscure to me at first because in principle all this has nothing to do with concurrency (beside the requirement that accessing the context should be thread safe). ThreadIds are used simply because they are available as an index and nothing else is. Its just a hack.] Seen this way, the whole thing smells very much of monads. Indeed, the monadic implementation is trivial. I attached a proof-of concept implementation, using George Russel's 'Dict' as an abstract data type in a separate module (copied verbatim from GlobalVariables.hs, see attached file Dict.hs). The idea: we define type Context = MVar Dict and introduce an eXtended version of the IO monad type XIO a = StateT Context IO a together with a small number of simple functions that implement the same interface as the original GlobalVariables.hs; no unsafe operations are used, everything is Haskell98 + Dynamics. Also ThreadIds do not appear and it is not necessary to change forkIO (apart from lifting it, of course). (code is in ExecutionContext.hs) I modified George's test program so that it works with ExecutionContexts. The program is completely isomorphic to the original (and does the same, too ;). The only major difference is that all IO operations are lifted into the XIO monad. Again, almost everything is Haskell98, -fglasgow-exts is only needed to derive Typeable (which can also be done manually). (Code is in TestExecutionContext.hs) The only task that remains to support this programming style so that it can be used practically, is to redefine IO as XIO in the kernel libraries. The annoying liftIOs everywhere (and the necessity to invent higher order lifts along the way) would be gone. I am almost sure that even the trick of indexing the dictionary via types (and thus the dependency on Data.Typeable and ghc extensions) can be avoided with a little more effort. Ben

On 27 Nov 2004, at 00:59, Benjamin Franksen wrote:
I finally understood that George Russell's Library is not really about global variables. Rather it is about what I want to call 'execution contexts', which are -- as Marcin Kowalczyk observed -- a restricted form of dynamically scoped variables.
yes. [snip]
type XIO a = StateT Context IO a
...which, amusingly, brings us almost full circle to the message which sparked off this particular iteration of the Great Global Variables Debate: http://groups.google.com/groups?selm=fa.hvrd8p7.nmg2r7%40ifi.uio.no ..which uses StateT Env IO Although your work is rather more complete than what I sketch in that message. A problem is the ability to pass callbacks to external libraries... Jules

Jules Bean wrote:
A problem is the ability to pass callbacks to external libraries...
Why not just put all the state in a record, then there's only one thing to pass around... you can use the state monad to hide this (or the state monad transformer if you need to layer over IO) then use partial function application to pass the necessary state to the callback on creation? Also another take on the TWI question... Doesn't this equate to the same thing as first class modules... then a module can be defined within the scope of a function? printablePoint x_init = do x <- newIORef x_init return $ module PrintablePoint where getX = readIORef x ... And the above can be seen as a model of an object... So using the HList library you can write this: class_printable_point x_init self = do x <- newIORef x_init returnIO $ mutableX .=. x .*. getX .=. readIORef x .*. moveD .=. (\d -> modifyIORef x ((+) d)) .*. ooprint .=. ((self # getX ) >>= print) .*. emptyRecord Of course true top-level TWIs behave like static objects... But with dynamic objects you can guarantee that each object is only initialised once, but cannot guarantee that only one object of a given type exists (and I think encapsulation is a more important property than uniqueness). Keean.

On Sat, 27 Nov 2004, Benjamin Franksen wrote:
An execution context is a mutable finite map from types to (monomorphic) values. Each IO action implicitly carries exactly one such map and by default passes it on to the actions that follow.
Execution contexts sound a good description of them. Building on your recoding of this, if you have top-level declarations of newMVar / newIORef then how much of this can you do by just keeping a dictionary in a global variable? This should certainly save some of the StateT plumbing; and such declarations are safe, becuase they are affine central (see http://groups.google.com/groups?selm=fa.doh68b9.96sgjd%40ifi.uio.no )
A function is provided to (implicitly) create a new mapping and run a given IO action with the new mapping as its execution context, instead of the default one.
Update the global MVar, do the IO, then reset it?
I am almost sure that even the trick of indexing the dictionary via types (and thus the dependency on Data.Typeable and ghc extensions) can be avoided with a little more effort.
Another global MVar to issue a sequence of unique index keys? Ian -- Ian Stark http://www.ed.ac.uk/~stark LFCS, School of Informatics, The University of Edinburgh, Scotland

A general point on top-level TWIs. It occurs to me that all variables are local to something (function, object, thread, process, machine, network, world...). I think it is an error to limit Haskells domain. If we allow unique per process variables (top-level TWI's) we limit our level of abstraction to a process - haskell cannot dispatch processes beacuse it cannot handle the multiple process contexts required. All the attempts at modelling execution contexts therefore seem a better solution than top-level TWIs which limit us to a single process world model. It seems the real world is an infinitely deep nesting of abstractions, so uniqueness is always relative to its context. Using the object model, we can have a process object, this object can ensure uniqueness of values within the context of a process - which is what Adrian wants. However if we want uniqueness at the next level, say the per CPU level, then a CPU object is the relavent context. It seems to me the object model fits perfectly, and what people are trying to do is turn modules into primitive objects complete with data-hiding and constructors (top-level TWIs)... However modules cannot be nested so the model breaks down, and we end up needing first-class modules anyway. Of course objects can be modeled another way (see http://www.cwi.nl/~ralf/OOHaskell) using the HList library... The syntax is simple enough, but would still benefit from a little sytactic sugar (hopefully to be providied by template-haskell, but this part is a work in progress). So in conclusion, it seems to me that that objects in Haskell solve all the problems that top-level TWIs solve, and still allow encapsulation and multiple 'process' contexts to be handled by the RTS. So use them! Sorry for the rambling explanation and shameless promotion of HLists... Keean.

On Saturday 27 November 2004 17:55, you wrote:
A general point on top-level TWIs. It occurs to me that all variables are local to something (function, object, thread, process, machine, network, world...). [...] It seems to me the object model fits perfectly, and what people are trying to do is turn modules into primitive objects complete with data-hiding and constructors (top-level TWIs)... However modules cannot be nested so the model breaks down, and we end up needing first-class modules anyway. [...] So in conclusion, it seems to me that that objects in Haskell solve all the problems that top-level TWIs solve, and still allow encapsulation and multiple 'process' contexts to be handled by the RTS. So use them!
Timber (formerly O'Haskell) has gone this way. Its object model is defined (and in fact was implemented) by a straight-forward translation into a (state) reader monad transformer over the IO monad. It is noteworthy that in this translation the (local) state of a Timber object is not a record but just an (IORef to an) anonymous tuple. [It is true that they added 'real' records and subtyping to the language but these additions are completely orthogonal to the object model. Records are merely used to group the monadic actions that define the interface of an object into a suitable type hierarchy (in order to model a weak form of interface inheritance).] So, one of the things I learned when studying Timber's object model is that records (or modules) with mutable fields (and inheritance and so on) are *not* the whole story. The most interesting aspect is how objects react to external stimulus, i.e. their representation as monadic effects. One *can* program in such a way in Haskell. What's missing is not so much records or first class modules, nor top-level IO actions (safe or not), but suitable syntactic sugar to alleviate the burden of having to lift (sic!) all IO actions to a suitable object/context monad. Ben

Benjamin Franksen wrote:
Timber (formerly O'Haskell) has gone this way. Its object model is defined (and in fact was implemented) by a straight-forward translation into a (state) reader monad transformer over the IO monad. It is noteworthy that in this translation the (local) state of a Timber object is not a record but just an (IORef to an) anonymous tuple. [It is true that they added 'real' records and subtyping to the language but these additions are completely orthogonal to the object model. Records are merely used to group the monadic actions that define the interface of an object into a suitable type hierarchy (in order to model a weak form of interface inheritance).]
Well without propper records you cannot do inheritance and other things relavent to the object model - so it is not orthogonal - but it is certainly true that you can define the state of an object using an IORef, and local scoping can provide the data-hiding necessary. We are using HLists to provide records and sub-typing, which are implemented using ghc's existing extensions to the class system (multi-parameter type and fundeps) - so no language extensions are necessary for these features - Haskell already has them, and they can be used quite reasonably from a library without syntax extensions.
So, one of the things I learned when studying Timber's object model is that records (or modules) with mutable fields (and inheritance and so on) are *not* the whole story. The most interesting aspect is how objects react to external stimulus, i.e. their representation as monadic effects.
Well the records implement method dictionaries, so they determine which inheritance and interface methods are possible.
One *can* program in such a way in Haskell. What's missing is not so much records or first class modules, nor top-level IO actions (safe or not), but suitable syntactic sugar to alleviate the burden of having to lift (sic!) all IO actions to a suitable object/context monad.
Erm no, all the objects can be implemented directly in the IO monad if you so wish, so no lifting is necessary... here is an example object in actuall Haskell code using the HList library...
point = do x <- newIORef 0 returnIO $ mutableX .=. x .*. getX .=. readIORef x .*. moveD .=. (\d -> modifyIORef x ((+) d)) .*. emptyRecord
And here's the object in use:
myFirstOOP = do p <- point p # getX >>= print p # moveD $ 3 p # getX >>= print
As you can see no lifting or awkwardness involved... the syntax looks very much like the OCaml example it was ported from. Admittedly a little syntactic sugar may make it more palatable to OO programers. (But notice how all the types for the objects methods are inferred by the compiler...) Keean.

On Sunday 28 November 2004 13:53, Keean Schupke wrote:
... here is an example object in actuall Haskell code using the HList library...
point = do x <- newIORef 0 returnIO $ mutableX .=. x .*. getX .=. readIORef x .*. moveD .=. (\d -> modifyIORef x ((+) d)) .*. emptyRecord
And here's the object in use:
myFirstOOP = do p <- point p # getX >>= print p # moveD $ 3 p # getX >>= print
As you can see no lifting or awkwardness involved... the syntax looks very much like the OCaml example it was ported from.
Very nice. This would be enough for single threaded programs and as long as the local state is simple. I think it would get quite awkward as soon as you want to provide - more mutable members - synchronized access + asynchronous methods (i.e. _reactive_ objects) I am ready to be proved wrong, though. Ben

[this has drifted off-topic quite a bit, so new subject] On Sunday 28 November 2004 17:29, Benjamin Franksen wrote:
I think it would get quite awkward as soon as you want to provide
- more mutable members - synchronized access + asynchronous methods
(i.e. _reactive_ objects)
I am ready to be proved wrong, though.
The view of indefinite blocking as a transparent operational property dates back to the era of batch-oriented computing, when interactivity was a term yet unheard of, and buffering operating systems had just become widely employed to relieve the programmer from the intricacies of synchronization with card-readers and line-printers. Procedure-oriented languages have followed this course ever since, by maintaining the abstraction that a
I couldn't wait so I proved myself wrong myself ;) Since I didn't get the extensible records example to compile, I translated it to normal Haskell records. The state is still only one mutable Int but the object is fully reactive. The code is attached and I do not find it awkward (although the generic object API could still be improved). One problem remains: to preserve reactivity, the programmer must make sure that methods don't execute IO actions that may block indefinitely. Unfortunately there is no way in Haskell to enforce this, because (indefinitely) blocking IO actions have the same type as non-blocking ones. Too late to change that, I guess... Btw, here is one of my all-time favourite quotes: program environment is essentially just a subroutine that can be expected to return a result whenever the program so demands. Selective method filtering is the object-oriented continuation of this tradition, now interpreted as ``programmers are more interested in hiding the intricacies of method-call synchronization, than preserving the intuitive responsiveness of the object model''. Some tasks, like the standard bounded buffer, are arguably easier to implement using selective disabling and queuing of method invocations. But this help is deceptive. For many clients that are themselves servers, the risk of becoming blocked on a request may be just as bad as being forced into using polling for synchronization, especially in a distributed setting that must take partial failures into account. Moreover, what to the naive object implementor might look like a protocol for imposing an order on method invocations, is really a mechanism for reordering the invocation-sequences that have actually occurred. In other words, servers for complicated interaction protocols become disproportionately easy to write using selective filtering, at the price of making the clients extremely sensitive to temporal restrictions that may be hard to express, and virtually impossible to enforce. <<< (see http://www.cs.chalmers.se/~nordland/ohaskell/rationale.html) Cheers, Ben

At 00:39 29/11/04 +0100, Benjamin Franksen wrote:
One problem remains: to preserve reactivity, the programmer must make sure that methods don't execute IO actions that may block indefinitely. Unfortunately there is no way in Haskell to enforce this, because (indefinitely) blocking IO actions have the same type as non-blocking ones. Too late to change that, I guess...
I was somewhat intrigued by this comment. Maybe I'm missing the point or simply too detached from the thrust of this thread to make any sense here, but wondered if anything really needs to be changed to be able to express this idea of non-blocking IO. Suppose we define a new type, say NBIO, which, like IO, allows any interaction with the external world, but with the proviso that it never blocks (I shalln't attempt to try and define exactly what this means, but hope that the intent is clear). A key function associated with this type would have type: forall a. NBIO a -> IO a Thus any non-blocking I/O activity can be implemented in NBIO, and its IO-equivalent is always available. But not the converse, of course. ... I think I now see the problem: while functions can be implemented in NBIO, and thereby convey an intended guarantee to the caller, there's no way I can see for the Haskell type system to stop a programmer to write a function of this type that actually uses (but does not return a value from) an IO value. Without this, how can facilities like Debug.Trace be provided? But then again, if no value from an IO is ever actually used or referenced outside the IO code, doesn't lazy evaluation mean that there's never any need to evaluate the value within IO? Now getting hopelessly out of my depth, but interested in any comments you may have... #g --
Btw, here is one of my all-time favourite quotes:
The view of indefinite blocking as a transparent operational property dates back to the era of batch-oriented computing, when interactivity was a term yet unheard of, and buffering operating systems had just become widely employed to relieve the programmer from the intricacies of synchronization with card-readers and line-printers. Procedure-oriented languages have followed this course ever since, by maintaining the abstraction that a program environment is essentially just a subroutine that can be expected to return a result whenever the program so demands. Selective method filtering is the object-oriented continuation of this tradition, now interpreted as ``programmers are more interested in hiding the intricacies of method-call synchronization, than preserving the intuitive responsiveness of the object model''.
Some tasks, like the standard bounded buffer, are arguably easier to implement using selective disabling and queuing of method invocations. But this help is deceptive. For many clients that are themselves servers, the risk of becoming blocked on a request may be just as bad as being forced into using polling for synchronization, especially in a distributed setting that must take partial failures into account. Moreover, what to the naive object implementor might look like a protocol for imposing an order on method invocations, is really a mechanism for reordering the invocation-sequences that have actually occurred. In other words, servers for complicated interaction protocols become disproportionately easy to write using selective filtering, at the price of making the clients extremely sensitive to temporal restrictions that may be hard to express, and virtually impossible to enforce. <<<
(see http://www.cs.chalmers.se/~nordland/ohaskell/rationale.html)
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

On Saturday 27 November 2004 17:10, you wrote:
On Sat, 27 Nov 2004, Benjamin Franksen wrote:
An execution context is a mutable finite map from types to (monomorphic) values. Each IO action implicitly carries exactly one such map and by default passes it on to the actions that follow.
Execution contexts sound a good description of them. Building on your recoding of this, if you have top-level declarations of newMVar / newIORef then how much of this can you do by just keeping a dictionary in a global variable?
This should certainly save some of the StateT plumbing; and such declarations are safe, becuase they are affine central (see http://groups.google.com/groups?selm=fa.doh68b9.96sgjd%40ifi.uio.no )
I like your definition of ACIO and I think it is sound (I have also suggested centrality, see http://www.haskell.org//pipermail/haskell/2004-November/014743.html). I would think that with ACIO we have a nice mathematical characterization for the IO actions that would be "safe" even at the top-level. ("Safe" meaning mainly that we do not open a can-of-worms with regard to execution order.) I don't know how easy or hard it is to prove of a certain IO action that is in fact in ACIO. However, monadic execution contexts don't need any safety proofs, because they are purely functional. With modest support from the compiler they could be implemented quite efficiently. And they would solve almost all problems for which global variables have been used or proposed as a solution. To be more precise, they would solve all those problems, provided you replace any reference to "the whole program" by "a certain execution context". I think this would be good enough for almost all applications.
A function is provided to (implicitly) create a new mapping and run a given IO action with the new mapping as its execution context, instead of the default one.
Update the global MVar, do the IO, then reset it?
This breaks down as soon as the IO action does a forkIO. This breakdown is one of the reasons I dislike global variables so much. Sure, you can find a way to code around this special probem.(*) But the fact that you have to (explicitly take concurrency into consideration) doesn't bode well for global variables. One of the nice features of (monadic) execution contexts is that they are automatically protected from such problems, without taking any special precaution.
I am almost sure that even the trick of indexing the dictionary via types (and thus the dependency on Data.Typeable and ghc extensions) can be avoided with a little more effort.
Another global MVar to issue a sequence of unique index keys?
Maybe this is possible. But I'd rather have a library that depends on Dynamics (plus some compiler support) than a highly controversial new language feature. Ben (*) You'd probably need a hack like using ThreadIds to identify the IO action being run under the new context, see George Russel's implementation.

On Sat, 27 Nov 2004, Benjamin Franksen wrote:
I would think that with ACIO we have a nice mathematical characterization for the IO actions that would be "safe" even at the top-level. ("Safe" meaning mainly that we do not open a can-of-worms with regard to execution order.) I don't know how easy or hard it is to prove of a certain IO action that is in fact in ACIO.
Hard, because it depends on observational equivalence of IO effects, and for that you need a semantics for the RealWorld. Maybe a better way to treat it is that whereas doing an IO action puts it in an execution trace at a specific point, doing an ACIO action is simply "perform this some time, maybe, if required". Giving something like newUnique an ACIO type indicates that semantics is sufficient; whereas for readIORef it typically isn't, and you want the stronger guarantee of an IO type.
This breaks down as soon as the IO action does a forkIO.
Isn't sharing global variables the correct semantics for forkIO ? That explicitly creates a 'lightweight' thread, which shares execution context with its invoker. I agree that forkOS, with its own local context, is harder. I suspect that, yes, as soon as you want to have more than one execution context simultaneously, then you need to manage them. For which XIO seems to do the job. Ian -- Ian Stark http://www.ed.ac.uk/~stark LFCS, School of Informatics, The University of Edinburgh, Scotland

Ben, On Sat, 27 Nov 2004, Benjamin Franksen wrote (apropos ACIO topdecls):
... a highly controversial new language feature.
The language feature is easily done, and just what has been happening all along: type ACIO = IO declare :: ACIO a -> a {-# NOINLINE declare #-} declare e = unsafePerformIO e All 'affine central' does is give a label to one particular idiomatic use of IO. The controversial part would be wading through libraries arguing over what things were ACIO. OK, I admit it would be nice if the compiler would manage everything, use <- syntax, and take advantage of affine central actions being well-behaved. But not vital. Ian
participants (5)
-
Benjamin Franksen
-
Graham Klyne
-
Ian.Stark@ed.ac.uk
-
Jules Bean
-
Keean Schupke