> Phil writes:
> > I support those who argue AGAINST making argv a constant.
> > If it's a problem, let's find a general solution.
> >
> > One possible solution is a new declaration, of the form:
> >
> > pseudoconstant <name> <expr>
> >
> > where <expr> has type (IO t), and <name> is declared with type t.
> > (Pick a different keyword if you prefer.) The only tricky issue is
> > the order in which the commands of type (IO t) are executed. They
> > should clearly precede main, but how should they relate to each other?
> > It seems reasonable to restrict this declaration to appear in the same
> > module as main, in which case the textual order is sufficient.
There's a second problem with "pseudoconstant" that no-one's mentioned
yet - it breaks the Haskell type system (when used in conjunction with
mutable variables).
Here's an example inspired by similar problems (avoided) in the ML
type system. Note that "put" writes a Float into "var" and "get"
reads an Int out.
> module Main( main ) where
>
> import MutVar( MutVar, newVar, readVar, writeVar )
>
> pseudoconstant var = newVar undefined :: MutVar a
>
> put :: Float -> IO ()
> put x = writeVar var x
>
> get :: IO Int
> get = readVar var
>
> main :: IO ()
> main = put 1.0 >> (get >>= print)
Pedants may argue that this isn't a problem since MutVars aren't in
the language yet - but given the choice of adding pseudoconstant or
adding mutable variables, I know which I'd choose.
The simplest fix is to disallow polymorphic expressions in
pseudoconstant - but maybe this is too restrictive.
In the meantime, providing argv as a constant seems perfectly ok to me.
o Details about whether it's implemented with pseudoconstant or with
unsafePerformIO, etc can surely be left to whoever's implementing the
library.
o I don't believe that making argv constant would mess up interpreters.
If the interpreter provided a user-level command to change the current
setting of argv, it would be easy to reset the values of all CAFs that
might depend on argv (eg all modules that import the System module would
be a good approximation). (I've added this kind of thing to Hugs - 20
lines of code.)
Any such problem would, of course, also be shared with pseudoconstant.
--
Alastair Reid Yale Haskell Project Hacker
[EMAIL PROTECTED] http://WWW.CS.Yale.EDU/homes/reid-alastair.html