[Haskell] Re: Global Variables and IO initializers

Keean Schupke k.schupke at imperial.ac.uk
Fri Nov 5 04:15:06 EST 2004


I don't quite understand this thread - There are already the equivalent of
IOrefs in the ST monad called STrefs. You can do newSTRef etc... you can use
stToIO to embed an ST operation in the IO monad and this is safe. You 
can also
use the unsafe ioToST, provided you are careful. To me adding stateful 
global variables
is a bad thing and these are some reasons that spring to mind:

Why do want global variables? They are like goto's the source of many 
programming
errors... global constants maybe. To me global variables seems like a 
step backwards
to languages like visual basic. One of the advantages of a functional 
language is that
a function only depends on it's arguments, not some 'hidden' state which 
makes
debugging hard.

As for top level init functions - there already is one, its called 
'main'. If you want to initialise
some state, call it from main, and return the state from the 
initialisation function.

Finally if something does IO (that is communicates with something 
stateful) that is not
a state thread (due to the documented properties of the ST monad) it 
should be in the
IO monad - thats what its there for.

    Keean.

Ben Rudiak-Gould wrote:

> Koen Claessen wrote:
>
> >Ben Rudiak-Gould wrote:
> >
> > | I'm not convinced this is a problem either. All you have
> > | to do is use a single parameter (?MyModule.globals ::
> > | MyModule.Globals), where MyModule.Globals is an abstract
> > | type, and you've hidden your implementation as completely
> > | as if you had used unexported global variables.
> >
> >Are you suggesting to always add the context
> >(?MyModule.globals :: MyModule.Globals) to every function in
> >every module you implement? (My example concerned a module
> >that was previously implemented without global variables,
> >and now was going to be implemented with global variables.)
>
> Okay, I see. The implicit parameter approach gives you more 
> flexibility than the global variable approach, since you can create 
> and use more than one set of "globals", and supply arguments to the 
> factory function. If you need that flexibility, obviously you can't 
> avoid changing the public interface. If you don't need that 
> flexibility, I think real global variables are fine. I have my own pet 
> proposal for those, after all. :-)
>
> >I think hiding the fact that certain objects are not
> >constants but functions is a bad idea, because it will break
> >sharing in a lazy implementation.
>
> Okay, this is a problem. We'd have to tweak the monomorphism 
> restriction a bit.
>
> > | Adrian Hey proposed a "SafeIO" monad with similar
> > | properties to yours. I have the same objection to both of
> > | them: a whole new monad and a bunch of interconversion
> > | functions seems like overkill for such a minor new
> > | language feature.
> >
> >I was not aware of his proposal. I don't think it is that
> >bad:
> >
> >  * 1 new monad
> >
> >  * for each current safe IO operation, 1 new operation
> >    (read: newIORef. What else?)
>
> At least newMVar, newEmptyMVar, newArray, newArray_, and newListArray. 
> I'm not sure how you'd handle the last three, since they're overloaded 
> and I don't think that all of the instances of MArray are safe to 
> create in CIO.
>
> > | And I have the same counter-proposal: why not use (forall
> > | s. ST s)? It's not commutative, but I think it has all of
> > | the properties we need.
> >
> >Interesting idea. However, when I then provide a function
> >for creating an IORef (which is what this extension would be
> >used for mostly), I get this:
> >
> >  newIORefST :: a -> ST s (IORef a)
> >
> >Which is probably not what you want.
>
> This is solved by merging the IO and ST monads, something that ought 
> to be done anyway:
>
>    type IO = ST RealWorld
>    type IORef a = Ref RealWorld a
>    type STRef s a = Ref s a
>
>    newRef :: a -> ST s (Ref s a)   -- replaces newIORef and newSTRef
>    readRef :: Ref s a -> ST s a
>    writeRef :: Ref s a -> a -> ST s ()
>    ...
>
> A top-level init action would look like
>
>    r <- newRef 'x'
>
> The RHS has type (forall s. ST s (Ref s Char)). The runtime system 
> runs it through (id :: forall a. (forall s. ST s a) -> ST RealWorld 
> a), with a resulting type of ST RealWorld (Ref RealWorld Char), which 
> is the same as IO (IORef Char). So r ends up with the type IORef Char.
>
> The same newRef function works in ST monad and IO monad computations. 
> You don't have to decide ahead of time whether you want the 
> versatility of ST or the convenience of IO. The compiler will 
> automatically infer a type of IO x for any function which actually 
> does I/O, and (forall s. ST s x) for a function which just mucks 
> around with Refs and MArrays. This is one small step towards getting 
> rid of the current status of IO as a dumping ground for everything 
> that might need to be used alongside genuine I/O.
>
> I don't think this even breaks existing code -- though I'm prepared to 
> be presented with counterexamples.
>
> A slight wart is that we have to move MVars into ST as well if we want 
> to create them in init actions. This doesn't break anything, but it's 
> a bit silly because they're basically useless outside IO.
>
> > | So importing a module doesn't have side effects, and init
> > | actions can be implemented easily using unsafePerformIO
> > | without affecting the semantics.
> >
> >I don't understand this remark.
>
> This isn't specific to my proposal. I just meant that if we allow 
> unrestricted IO actions then we have to worry about which ones get run 
> and when they get run. If we run all actions at the beginning, then 
> importing a module into your program has side effects (versus not 
> mentioning it at all). On the other hand if those actions are 
> appropriately restricted, then the program can't tell whether they've 
> been run or not, and so importing a module doesn't have side effects, 
> and also we don't have to worry about the (difficult, inefficient) 
> engineering problem of making all the actions run before main; we can 
> run them on demand, as though they were individually wrapped in 
> unsafePerformIO.
>
> > | Note that the ST monad does not require higher-order
> > | polymorphism -- only the runST function requires that. ST
> > | is still useful without runST, as this example
> > | demonstrates.
> >
> >So, if I get it right, you want to use (forall s . ST s)
> >because it avoids adding yet another monad to Haskell?
>
> Better than that, it reduces the number of monads in Haskell. :-)
>
> John Peterson's post intrigues me, though: maybe there is good reason 
> to add a CIO monad if we get other benefits from it as well. But I 
> don't (yet) understand what those benefits are. I'd like to see an 
> example of what CIO can do that (forall s. ST s) can't. (There are 
> definitely things that ST can do that CIO can't -- write values into 
> those mutable arrays before returning them, for example.)
>
> -- Ben
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell




More information about the Haskell mailing list