How about integrating psuedoconstants along the lines of the existing `main'
mechanism. Each `Main' module would come with a `main' and `setup' function,
> main:: IO ()
> setup:: IO t
where `t' represents an arbitrary monotype. These definitions would
induce a binding:
> environment:: t
With this arrangement, a program is run by running `setup' then
running `main', binding `environment' to the result returned by
`setup'; any attempt to access `environment' in setup would result in
divergence.
If `setup' is not provided by the programmer then a default one could
be substituted:
> setup:: IO Setup.Environment
> setup = Setup.default_setup
using a new library module,
> module Setup where
>
> import System
>
> data Environment = Env { progName:: String, args::[String] }
>
> default_setup:: IO Environment
> default_setup = do
> pn <- getProgName
> as <- getArgs
> return (Env pn as)
(Perhaps the definitions could eventually make their way into the
`System' library module.)
The following example program would print the program name and arguments in a
tuple.
> main:: IO ()
> main = print (progName environment,args environment)
While this program would make a mutable integer variable globally
available in addition to the command-line arguments (using a
GHC-esque mutable-variable package):
> import MutVar( MutVar, newVar )
> data Ev = Ev { global:: MutVar Int,
> progName:: String,
> args::[String] }
>
> setup:: IO Ev
> setup = do
> v <- newVar 42
> pn <- getProgName
> as <- getArgs
> return (Ev v pn as)
>
> main:: IO ()
> main = ...
(I seem to remember global variables being used to implement the standard
I/O streams in one of the I/O libraries.)
Chris Dornan [EMAIL PROTECTED]
University College Cork +353 21 902837