[Haskell-cafe] Re: global variables

2007-05-17 Thread Big Chris


On Thu, 17 May 2007, Jason Dagit wrote:


Well, it seems to me that Haskell modules are actually very similar to
singletons. Perhaps all these problems with modules having top level
mutable state could be solved if Haskell modules were parameterizable
at "instantiation"?  I'm not saying we should turn the Haskell module
system into an OO system, just that maybe it would be wise to borrow
some ideas from that paradigm.


Well, I'm a little unclear as to how the discussion shifted from
global variables to modules, but as long as we're here: Rather than
looking at OO languages, why not take a lesson from more powerful
module systems already in functional programming languages.  In
particular, the ML module system supports "parameterization at
instantiation" with functors.  Of course, there is considerable
evidence that ML modules and Haskell type classes really do the same
thing, but they do seem to be useful in very different situations.

--Chris
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: global variables

2007-05-17 Thread Jón Fairbairn
Eric <[EMAIL PROTECTED]> writes:

> H|i,
> 
> Does anyone know of a simple and straightforward way to use
> global variables in Haskell?

No, no-one does. Global variables are neither simple nor
straightforward. :-P

In addition to what others have said (assuming you don't
just mean providing a name for a constant¹), to avoid the
problems caused by global variables is one of the reasons
for using a functional language.


[1] as in

> e = exp 1
-- 
Jón Fairbairn [EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IOinitializers

2004-11-30 Thread Ian . Stark
On Mon, 29 Nov 2004, Simon Peyton-Jones wrote:
This unfortunate observabilty of an ordering (or hash value) that is
needed only for efficient finite maps, is very annoying.  I wish I knew
a way round it.  As it is we can pick
a) expose Ord/Hash, but have unpredictable results
b) not have Ord/Hash, but have inefficient maps
I was going to ask what was wrong with doing the tedious:
  class FiniteMappable key where
listToFM :: [(key,elt)] -> FiniteMap key elt
addToFM :: FiniteMap key elt -> key -> elt -> FiniteMap key elt
...etc etc...
with the possibility of:
  instance Ord key => FiniteMappable key where
listToFM = listToFMoriginal
...etc etc...
where one would only export the fact that a particular type is 
FiniteMappable, not Ord.

But then I remembered that modules can't hide instance declarations, so 
that's no good. :-(

Is there some way to insert a newtype, so that just one instance becomes 
visible?

--
Ian Stark   http://www.ed.ac.uk/~stark
LFCS, School of Informatics, The University of Edinburgh, Scotland
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IOinitializers

2004-11-30 Thread Graham Klyne
At 13:43 29/11/04 -0800, John Meacham wrote:
On Mon, Nov 29, 2004 at 03:09:53PM -, Simon Peyton-Jones wrote:
> | > In fact GHC at least *already* generates a unique integer for each
> | > TypeRep. A good idea, since it means comparisons can be done in unit
> | > time. Thus indexing can be done trivially using this integer as a
> | > hash function.
> |
> | Yes, I have seen this in the code, too. The Ord and Typeable instances
> | should be trivial.
>
> Take care here.  There is no guarantee that the unique number generated
> will be the same in each run.  So if you have Ord Typeable, this program
> may give unpredictable results:
>
> main = print (typeOf True < typeOf 'x')
>
> This unfortunate observabilty of an ordering (or hash value) that is
> needed only for efficient finite maps, is very annoying.  I wish I knew
> a way round it.  As it is we can pick
>   a) expose Ord/Hash, but have unpredictable results
>   b) not have Ord/Hash, but have inefficient maps
I thought it would be good to have two Ord classes, one to give the
natural ordering (Ord) if one exists, and one to give the most efficient
one for implementing maps/sets which has the side constraint that
nothing may observably depend on what the actual order is, just that it
is a valid total ordering. I have come across a few types where such a
distinction would have been nice to have. either because the ordering
was arbitrary so exposing it via 'Ord' seemed like a white lie to the
user or a much more efficient yet non-intuitive ordering was possible..
of course, the side condition here is pretty vauge. I don't know how to
enforce it within the type system, but it is a pretty straightforward
condition which I don't think would cause too much trouble in practice
to maintain.
This reminds me of recent discussion about multiple flavours of Show.  Is 
there a pattern here?

#g

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-29 Thread John Meacham
On Mon, Nov 29, 2004 at 11:57:31AM +0100, Benjamin Franksen wrote:
> Can anyone think of a situation where adding a derived instance to an 
> abstract data type breaks one of its invariants?

Yes, I was thinking of this the other day, 

newtype LessThan5 = LessThen5 Int 

new x | x < 5 = LessThen5 x
  | otherwise = error "not less than five"


if someone were allowed to do a 

derive (Enum LessThan5)


in another module, then they could break the invarient with toEnum 6 for
instance.


For safety, one should only be able to remotely derive if all the
constructors of the type are in scope as well as the type. However, this
is too strong of a constraint for deriving Typeable which does not care
about the constructors. It is not clear
what the correct thing to do is, perhaps have 2 types of derivable
classes, ones which need the constructors and ones which don't? Hmm.. 

I am sort of of the practically motivated opinion that Typable should be
a built-in that everything is automatically an instance of, but I don't
know if that is really the right thing to do or just a convinient hack. 

John

-- 
John Meacham - ârepetae.netâjohnâ 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IOinitializers

2004-11-29 Thread John Meacham
On Mon, Nov 29, 2004 at 03:09:53PM -, Simon Peyton-Jones wrote:
> | > In fact GHC at least *already* generates a unique integer for each
> | > TypeRep. A good idea, since it means comparisons can be done in unit
> | > time. Thus indexing can be done trivially using this integer as a
> | > hash function.
> | 
> | Yes, I have seen this in the code, too. The Ord and Typeable instances
> | should be trivial.
> 
> Take care here.  There is no guarantee that the unique number generated
> will be the same in each run.  So if you have Ord Typeable, this program
> may give unpredictable results:
> 
> main = print (typeOf True < typeOf 'x')
> 
> This unfortunate observabilty of an ordering (or hash value) that is
> needed only for efficient finite maps, is very annoying.  I wish I knew
> a way round it.  As it is we can pick
>   a) expose Ord/Hash, but have unpredictable results
>   b) not have Ord/Hash, but have inefficient maps

I thought it would be good to have two Ord classes, one to give the
natural ordering (Ord) if one exists, and one to give the most efficient
one for implementing maps/sets which has the side constraint that
nothing may observably depend on what the actual order is, just that it
is a valid total ordering. I have come across a few types where such a
distinction would have been nice to have. either because the ordering
was arbitrary so exposing it via 'Ord' seemed like a white lie to the
user or a much more efficient yet non-intuitive ordering was possible..

of course, the side condition here is pretty vauge. I don't know how to
enforce it within the type system, but it is a pretty straightforward
condition which I don't think would cause too much trouble in practice
to maintain.

John

-- 
John Meacham - ârepetae.netâjohnâ 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IOinitializers

2004-11-29 Thread Simon Peyton-Jones
| > In fact GHC at least *already* generates a unique integer for each
| > TypeRep. A good idea, since it means comparisons can be done in unit
| > time. Thus indexing can be done trivially using this integer as a
| > hash function.
| 
| Yes, I have seen this in the code, too. The Ord and Typeable instances
| should be trivial.

Take care here.  There is no guarantee that the unique number generated
will be the same in each run.  So if you have Ord Typeable, this program
may give unpredictable results:

main = print (typeOf True < typeOf 'x')

This unfortunate observabilty of an ordering (or hash value) that is
needed only for efficient finite maps, is very annoying.  I wish I knew
a way round it.  As it is we can pick
a) expose Ord/Hash, but have unpredictable results
b) not have Ord/Hash, but have inefficient maps

Simon

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Global Variables and IO initializers

2004-11-29 Thread George Russell
Benjamin wrote (snipped):
> Typeable would be completely safe if the only way to declare instances
> would be to derive them, but this is only practical if it can be done
> from anywhere outside the data type definition.
Unfortunately this would also outlaw some legitimate uses of Typeable.
In particular, I think you can only derive Typeable for a type
constructor of type (*).  GHC has recently added Typeable1,Typeable2,...
which are classes of type constructors of kind *->*, *->*->* and so on, up
to 6 arguments I think, and these can be derived, which is a great help.
But there are still kinds this does not include; for example (*->*)->*,
which is an example of a type constructor I actually used where I wanted
an instance of Typeable.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-29 Thread Benjamin Franksen
On Monday 29 November 2004 11:35, George Russell wrote:
> (indexing with TypeRep)
>
>  > This is yet another incidence where Robert Will's ByMaps would be
>  > very useful
>
> In fact GHC at least *already* generates a unique integer for each
> TypeRep. A good idea, since it means comparisons can be done in unit
> time. Thus indexing can be done trivially using this integer as a
> hash function.

Yes, I have seen this in the code, too. The Ord and Typeable instances 
should be trivial.

[off topic:]

There was a recent discussion about allowing to derive an instance from 
anywhere at the top-level, and not only in the type definition. This is 
one more example where such a feature would be very useful.

Another related example is the class Typeable itself. It has been noted 
by others that the current interface is not type safe, since mkTyCon 
gets an arbitrary string as argument. (Unfortunately this means that 
GlobalVariables.hs and ExecutionContext.hs aren't really type safe 
either).

Typeable would be completely safe if the only way to declare instances 
would be to derive them, but this is only practical if it can be done 
from anywhere outside the data type definition.

Can anyone think of a situation where adding a derived instance to an 
abstract data type breaks one of its invariants?

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-29 Thread George Russell
(indexing with TypeRep)
> This is yet another incidence where Robert Will's ByMaps would be very useful
In fact GHC at least *already* generates a unique integer for each TypeRep.
A good idea, since it means comparisons can be done in unit time.
Thus indexing can be done trivially using this integer as a hash function.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-27 Thread Benjamin Franksen
On Friday 26 November 2004 08:39, you wrote:
> Benjamin Franksen wrote (snipped):
>  > What non-standard libraries have I used (that you don't)?
>
> OK, but you have to test every element of the dictionary with fromDynamic
> until you find one with the type you want, which is not a good idea if the
> dictionary is big.  My implementation is equally inefficient now (because
> TypeRep's have no Ord), but if TypeRep's had Ord or a hashing function
> (both would be very easy to provide from GHC's implementation) I could make
> my implementation efficient very easily, while you'd have to completely
> rewrite yours to get the same effect.

[completely off-topic but anyway:]

This is yet another incidence where Robert Will's ByMaps would be very useful:

http://www.stud.tu-ilmenau.de/~robertw/dessy/fun/principles.html#bymap

I am quite astonished that apparently none of the data structure library 
projects have taken up the idea.

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-27 Thread Benjamin Franksen
On Friday 26 November 2004 08:39, George Russell wrote:
> Benjamin Franksen wrote (snipped):
>  > What non-standard libraries have I used (that you don't)?
>
> OK, but you have to test every element of the dictionary with fromDynamic
> until you find one with the type you want, which is not a good idea if the
> dictionary is big.  My implementation is equally inefficient now (because
> TypeRep's have no Ord), but if TypeRep's had Ord or a hashing function
> (both would be very easy to provide from GHC's implementation) I could make
> my implementation efficient very easily, while you'd have to completely
> rewrite yours to get the same effect.

[completely off-topic but anyway:]

This is yet another incidence where Robert Will's ByMaps would be very useful:

http://www.stud.tu-ilmenau.de/~robertw/dessy/fun/principles.html#bymap

I am quite astonished that apparently none of the data structure library 
projects have taken up the idea.

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-26 Thread Benjamin Franksen
On Friday 26 November 2004 14:12, Benjamin Franksen wrote:
> I still can't see any reason why each single Haskell thread should have its
> own searate dictionary. Contrary, since it is common to use forkIO quite
> casually, and you expect your actions to do the same thing regardless of
> which thread calls them, this would be disastrous. IMO GlobalVariables.hs
> shouldn't be aware of threadIds at all.

I think I misunderstood your proposal (GlobalVariables.hs). It seems to do 
what I would expect, if your version of forkIO is used. I thought by 
inheriting the dictionary you meant working on a new copy, but it does in 
fact mean using the same dictionary.

Sorry for the confusion.

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-26 Thread Benjamin Franksen
[for the 4th time moving this discussion to cafe]

On Friday 26 November 2004 08:39, you wrote:
> Benjamin Franksen wrote (snipped):
>  > Doesn't that run contrary to Adrian Hey's "oneShot" example/requirement?
>
> Remind me again what Adrian Hey's "oneShot" example/requirement is ...

http://www.haskell.org//pipermail/haskell/2004-November/014766.html

> [...]
>  > Furthermore, I have great difficulty in understanding why different
>  > threads need different dictionaries. Could you explain why this is
>  > useful, or rather, more useful than a global single dictionary?
>
> Consider Data.Unique implemented over lots of processors.  If you had a
> single IORef managed by a single processor used to generate new unique
> identifiers, there is the danger that that processor will become a
> bottleneck for the whole system.  Much better to have a thread-local or
> processor-local IORef which generates new identifiers, which you then
> prepend with a processor tag.

I see. Note that currently there exists no Haskell implementation that is able 
to make use of multiple processors. See

http://research.microsoft.com/Users/simonpj/papers/conc-ffi/conc-ffi.ps

Having read

http://www.haskell.org//pipermail/haskell-cafe/2004-November/007666.html

again, as well as your comments above, I tend to agree that withEmptyDict may 
indeed be useful. However, the situations you describe are somewhat special. 
They can and should be handled by explicitly calling withEmptyDict.

I still can't see any reason why each single Haskell thread should have its 
own searate dictionary. Contrary, since it is common to use forkIO quite 
casually, and you expect your actions to do the same thing regardless of 
which thread calls them, this would be disastrous. IMO GlobalVariables.hs 
shouldn't be aware of threadIds at all.

>  > What non-standard libraries have I used (that you don't)?
>
> [...explanation...]

I see. Thanks for the explanation.

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-25 Thread George Russell
Benjamin Franksen wrote (snipped):
> Doesn't that run contrary to Adrian Hey's "oneShot" example/requirement?
Remind me again what Adrian Hey's "oneShot" example/requirement is ...
> Well, that's indeed one major problems with global variables. Sure, you can
> try to solve it with multiple dictionaries, but that makes understanding what
> a certain part of the program does even harder. How do I find out what
> dictionary a write or read to a (no longer global) variable refers to?
This seems to me as unnecessary as asking for which memory location it has.
Provided the no-longer-global variables act as if they were global within
their own universe, there is no problem.   The withEmptyDict operator
I provide gives you a new universe where everything starts from scratch.
It seems to me you have a much bigger problem when you force everything to
have global variables, and then want to run multiple copies of a program,
only to have them clobber each other's variables.
> Furthermore, I have great difficulty in understanding why different threads
> need different dictionaries. Could you explain why this is useful, or rather,
> more useful than a global single dictionary?
Consider Data.Unique implemented over lots of processors.  If you had a single
IORef managed by a single processor used to generate new unique identifiers,
there is the danger that that processor will become a bottleneck for the whole
system.  Much better to have a thread-local or processor-local IORef which 
generates
new identifiers, which you then prepend with a processor tag.
Me (snipped):
> It is, but I'm not sure if it can be avoided without using stuff not in
> the standard libraries.
Ben:
> What non-standard libraries have I used (that you don't)?
OK, but you have to test every element of the dictionary with fromDynamic until
you find one with the type you want, which is not a good idea if the dictionary
is big.  My implementation is equally inefficient now (because TypeRep's have
no Ord), but if TypeRep's had Ord or a hashing function (both would be very
easy to provide from GHC's implementation) I could make my implementation
efficient very easily, while you'd have to completely rewrite yours to get
the same effect.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Global Variables and IO initializers

2004-11-25 Thread George Russell
Marcin wrote (snipped):
> I think global variables are a lot less evil if they behave as if they
> were dynamically scoped, like Lisp special variables.
>
> That is, there is a construct which gives the variable a new mutable
> binding visible in the given IO action. It's used more often than
> assignment. Assignment is still available though.
I agree entirely.  The fact that declaring global variables using 
unsafePerformIO
introduces an artificial notion of "global" and forces it on every part of the
program is a major disadvantage which we haven't heard enough about in this
discussion.  It prevents you doing all sorts of things.  It's bad for 
parallelism.
It prevents you running two independent copies of a (main) action.  It prevents
you writing a Haskell controller which runs over Haskell actions as subprograms.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-25 Thread Benjamin Franksen
On Thursday 25 November 2004 10:02, you wrote:
>  > This is funny. When I got no immediate reaction from you, I started
>  > implementing it myself. I ended up with something similar. It has less
>  > features but is also a lot simpler. This is the interface:
>  >
>  > initGlobal :: Typeable a => a -> IO ()
>  > getGlobal :: Typeable a => IO a
>
> Your implementation is probably much simpler than mine because you don't
> implement withEmptyDict.  I'm really quite keen about withEmptyDict,
> because one of the MAJOR conceptual problems I have with unsafePerformIO
> global variables is that you only get one universe, corresponding to the
> Haskell program. There shouldn't really be a single "the Haskell program" 
> anyway;

Doesn't that run contrary to Adrian Hey's "oneShot" example/requirement?

> imagine something like GHC or an operating system written in 
> Haskell which run sub-systems which require their own global variables.

Well, that's indeed one major problems with global variables. Sure, you can 
try to solve it with multiple dictionaries, but that makes understanding what 
a certain part of the program does even harder. How do I find out what 
dictionary a write or read to a (no longer global) variable refers to?

Furthermore, I have great difficulty in understanding why different threads 
need different dictionaries. Could you explain why this is useful, or rather, 
more useful than a global single dictionary?

It reminds me of the usual "thread-local" variables that are offered by most 
systemlevel thread libraries. I think they put them in there so that they can 
easily port non-reentrant libraries (i.e. ones that use global variables 
internally) to a multi-threaded setting without changing their APIs. This 
approach leads to libraries that are extremely inconvenient and dangerous to 
use. Their existence is one of the reasons why I have been arguing so much 
against global variables.

>  > Storing (TypeRep,Dynamic) pairs is redundant, since Dynamics already
>  > contain their own TypeRep (that is how they are made to work).
>
> It is, but I'm not sure if it can be avoided without using stuff not in
> the standard libraries.

What non-standard libraries have I used (that you don't)?

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] Re: Global Variables and IO initializers

2004-11-25 Thread Marcin 'Qrczak' Kowalczyk
George Russell <[EMAIL PROTECTED]> writes:

> Your implementation is probably much simpler than mine because
> you don't implement withEmptyDict. I'm really quite keen about
> withEmptyDict, because one of the MAJOR conceptual problems I have
> with unsafePerformIO global variables is that you only get one
> universe, corresponding to the Haskell program.

I think global variables are a lot less evil if they behave as if they
were dynamically scoped, like Lisp special variables.

That is, there is a construct which gives the variable a new mutable
binding visible in the given IO action. It's used more often than
assignment. Assignment is still available though.

In Common Lisp implementations these variables are not inherited
by threads: each thread starts with toplevel bindings of dynamic
variables. I think this is wrong and they should be inherited.
In my language Kogut they are inherited.

With threads it makes a difference that the variable gets a new
binding, not just a new value. The old binding is still mutable by
threads which have not shadowed it. When the scope of the new binding
finishes, the value restored in this thread might be different than
the value from the time the scope was entered, if other threads have
changed it in the meantime.

In Haskell it would be a new kind of reference, parallel to IORef
and MVar.

In principle dynamic variables need not to be defined at the toplevel.
In Lisp they are effectively always toplevel variables (even if
declared locally); in my language they can be created in arbitrary
places, e.g. as fields of objects. But usually they are toplevel.
It would be pointless to *not* have toplevel dynamic variables,
because their purpose is to avoid manually threading them through
all actions which need them.

This is an alternative design to Haskell's implicit parameters. It's
different in that it applies to the IO monad only (dynamic variables
obviously can't be read from pure code) and that the fact that an
action uses a particular variable is not reflected in its type.

Their primary use is to provide a default setting used in deep places
in a computation, with the assumption that usually a single setting
applies to the whole computation started from a given place. Like the
random number generator, the default output handle (not the *internals*
of stdOut as a statefulobject, but binding the stdOut variable to
different handles, not possible in Haskell), the current locale or
individual settings implied by the locale (I don't know yet how
"inheritable" settings should be designed, like the locale as a whole
and its parts).

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [Haskell] Re: Global Variables and IO initializers

2004-11-25 Thread George Russell
> This is funny. When I got no immediate reaction from you, I started
> implementing it myself. I ended up with something similar. It has less
> features but is also a lot simpler. This is the interface:
>
> initGlobal :: Typeable a => a -> IO ()
> getGlobal :: Typeable a => IO a
Your implementation is probably much simpler than mine because you don't
implement withEmptyDict.  I'm really quite keen about withEmptyDict, because
one of the MAJOR conceptual problems I have with unsafePerformIO global 
variables
is that you only get one universe, corresponding to the Haskell program.
There shouldn't really be a single "the Haskell program" anyway; imagine 
something
like GHC or an operating system written in Haskell which run sub-systems which
require their own global variables.  Or imagine a program split between lots of
processors where, for efficiency reasons, you don't want everyone to have to 
refer
to the same set of global variables.o
> Storing (TypeRep,Dynamic) pairs is redundant, since Dynamics already
> contain their own TypeRep (that is how they are made to work).
It is, but I'm not sure if it can be avoided without using stuff not in
the standard libraries.
> I also use a list for the dictionary; and I share your view about
> TypeRep badly needing an Ord instance (probably trivial to provide
> but I could be wrong).
Even better would be a hashable integer.  TypeRep actually is implemented
internally on GHC using a hashcons'd unique integer, so exposing it should be
trivial ...
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Global Variables and IO initializers

2004-11-24 Thread Judah Jacobson
On Thu, 25 Nov 2004 01:46:03 +, Ben Rudiak-Gould
<[EMAIL PROTECTED]> wrote:
> Benjamin Franksen wrote:
> 
> > My god, what a stupid mistake. I should just give it up... :-(
> 
> Funny you should say that, because I made the same mistake two weeks ago
> and felt the same way:
> 
> http://www.haskell.org/pipermail/haskell-cafe/2004-November/007556.html
> 
> Live and learn...
> 
> -- Ben
> 

And I (as the poster of the message correcting Ben) had made a related
but even more severe mistake several days earlier:

http://www.haskell.org//pipermail/haskell-cafe/2004-November/007527.html

Strength in numbers?

Best,
-Judah
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Global Variables and IO initializers

2004-11-24 Thread Ben Rudiak-Gould
Benjamin Franksen wrote:
My god, what a stupid mistake. I should just give it up... :-(
Funny you should say that, because I made the same mistake two weeks ago 
and felt the same way:

   http://www.haskell.org/pipermail/haskell-cafe/2004-November/007556.html
Live and learn...
-- Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Global Variables and IO initializers

2004-11-24 Thread Benjamin Franksen
On Thursday 25 November 2004 01:14, Ben Rudiak-Gould wrote:
> Benjamin Franksen wrote:
>  >label1 = unique Uniq1
>  >label2 = unique Uniq2
>  >global1 = functionalNewMVar label1 True
>  >global2 = functionalNewMVar label1 (117::Int)
>
> No dice. Your example inadvertently shows why: you used label1 when
> creating both global1 and global2, and now I can write
>
> coerce :: Bool -> Int
> coerce x = putMVar global1 x >> takeMVar global2
>
> (provided I've emptied them first).

My god, what a stupid mistake. I should just give it up... :-(

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Global Variables and IO initializers

2004-11-24 Thread Ben Rudiak-Gould
Benjamin Franksen wrote:
>label1 = unique Uniq1
>label2 = unique Uniq2
>global1 = functionalNewMVar label1 True
>global2 = functionalNewMVar label1 (117::Int)
No dice. Your example inadvertently shows why: you used label1 when 
creating both global1 and global2, and now I can write

   coerce :: Bool -> Int
   coerce x = putMVar global1 x >> takeMVar global2
(provided I've emptied them first).
-- Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Global Variables and IO initializers

2004-11-24 Thread Benjamin Franksen
[encouraging everybody to reply on haskell-cafe]

On Tuesday 23 November 2004 12:02, you wrote:
> Thanks to the encouraging post
>
> http://www.haskell.org//pipermail/haskell/2004-November/014748.html
>
> from Benjamin Franksen, I have implemented
> my proposal which allows the user to define new global variables without
> unsafePerformIO, NOINLINE and other such horrors.

This is funny. When I got no immediate reaction from you, I started 
implementing it myself. I ended up with something similar. It has less 
features but is also a lot simpler. This is the interface:

initGlobal :: Typeable a => a -> IO ()
getGlobal :: Typeable a => IO a

Some remarks:

 o The separation into two modules is only historical.
 o I use an MVar internally, not an IORef; since it is not exposed,
   no indefinite blocking can occur. It's just a mutex around the
   dictionary.
 o Storing (TypeRep,Dynamic) pairs is redundant, since Dynamics already
   contain their own TypeRep (that is how they are made to work).
 o Both our implementations use unsafePerformIO in an unsafe manner,
   which is why the NOINLINE flag is used.
 o I also use a list for the dictionary; and I share your view about
   TypeRep badly needing an Ord instance (probably trivial to provide
   but I could be wrong).

  ***

On a related note, there was some discussion recently about which IO actions 
should be considered as 'harmless' so that they are allowed for the proposed 
top-level '<-' bindings, and how to characterize them in an elegant way.

Here is yet another solution:

The only things allowed at top-level (other than pure values) will be unique 
labels (such as provided by Data.Unique). Then we take all the newXXX actions 
out of whatever monad they live in and provide them as pure functions that 
take a Unique as additional argument:

newXXX :: Unique -> a -> XXX a

This might be a bit tricky to do efficiently. Anyway, a Haskell program could 
then create top-level Unique labels instead of top-level XXX vars:

myGlobalVarLabel <- unique

myGlobalMVar = newMVar myGlobalVarLabel "initial content"

The concrete syntax could be made even simpler (and clearer), i.e. without the 
'<-' operator:

unique myGlobalVarLabel

Advantages:

 o No question of what is in SafeIO and what is not.
 o No question of when top-level IO actions are performed.

  ***

Now what about combining the two aproaches? The point here is that in Haskell 
we can easily create new unique labels at the top-level without resorting to 
any kind of unsafe operations:

data Uniq1 = Uniq1
data Uniq2 = Uniq2
...

Only these have not the same but different types. So we need a way to map them 
to a single type in such a way that their uniqueness is preserved. We already 
have such a tool and it is called "deriving Typeable":

unique = typeOf
type Unique = TypeRep

data Uniq1 = Uniq1 deriving Typeable
data Uniq2 = Uniq2 deriving Typeable

Our unique labels can now simply be defined as

label1 = unique Uniq1
label2 = unique Uniq2

and our global variables as

global1 = functionalNewMVar label1 True
global2 = functionalNewMVar label1 (117::Int)

I think this is most elegant, although there remains the questions of an 
efficient implementation of functionalNewXXX.

Ben
{-# OPTIONS -fglasgow-exts -fno-cse #-}
module Data.IO.Dict (
  register,
  standard,
  lookup
  ) where

import Prelude hiding (lookup)
import Foreign
import Data.Dynamic
import Data.Maybe
import Control.Concurrent
import Control.Exception

-- a collection of initialised data.
type Dict = MVar [Dynamic]

thedict :: Dict
{-# NOINLINE thedict #-}
thedict = unsafePerformIO $ newMVar []

-- Each Haskell "main" program will have one of these.
standard :: IO Dict
standard = do
  return thedict

-- register a value of type (a) in the dictionary.  Only one value of each
-- type is allowed in the dictionary; registering the same type twice will
-- cause an exception.
register :: Typeable a => Dict -> a -> IO ()
register dict_var val = modifyMVar_ dict_var register'
  where
register' :: [Dynamic] -> IO [Dynamic]
register' d = do
  x <- tryJust errorCalls (lookup' d `asTypeOf` (return val))
  case x of
Left _ -> return $ (toDyn val):d
Right val' -> error $ "Dict.register: a value of type (" ++ (show $ 
typeOf val) ++ ") has already been registered"

-- Get the value of (a) registered in the Dict, or raise an exception if it
-- isn't.
lookup :: Typeable a => Dict -> IO a
lookup dict_var = withMVar dict_var lookup'

lookup' :: Typeable a => [Dynamic] -> IO a
lookup' [] = error "Dict.lookup: not found"
lookup' (dyn:dyns) =
  case fromDynamic dyn of
Just val -> return val
Nothing -> lookup' dyns

-- thisThreadDict :: IO Dict

-- newEmptyDict :: IO Dict

-- runWithDifferentDefaultDict :: Dict -> IO a -> IO a
module Data.IO.Global

[Haskell-cafe] Re: Global variables again

2004-11-23 Thread Benjamin Franksen
[we should really keep this on haskell-cafe because such lengthy discussions 
are what the cafe is for]

On Tuesday 23 November 2004 10:26, Adrian Hey wrote:
> On Monday 22 Nov 2004 4:03 pm, Benjamin Franksen wrote:
> > This is getting ridiculous. At least two workable alternatives have been
> > presented:
> >
> > - C wrapper (especially if your library is doing FFI anyway)
> > - OS named semaphores
>
> Neither of these alternatives is a workable general solution.

Since the problem only appears in special situations, a general solution is 
not required, nor is it desirable (because of the danger of infection with 
the "global variable disease".)

> There are several significant problems with both, but by far
> the most significant problem (at least if you believe that top
> level mutable state is evil) is that they both rely on the use
> of top level mutable state. If this is evil it is surely just as
> evil in C or OS supplied resources as it is in Haskell.

The evil is in the world in the form of C libraries with hidden global 
variables and hardware with non-readable registers.

What I am arguing for is to *contain* this disease by forcing a solution to 
happen outside of Haskell.

What you are arguing for (i.e. a general solution *in* Haskell) amounts to 
(deliberately) *spreading* the disease.

> The fact that one solution requires the use of a completely different
> programming language 

And that is exactly the point: In order to do evil you have to go somewhere 
else, preferably to where the problem originally came from. If it originated 
in C, go fix it on the C level. If originates in the OS, go fix it on the OS 
level. As for broken hardware, you should use a OS level mechanism, so that 
multiple initialization is prevented OS wide and not only per program run.

> and the other requires the use of a library which 
> could not be implemented in Haskell (not without using unsafePerformIO
> anyway) must be telling us that there something that's just plain missing
> from Haskell. 

Yes it's plain missing and for good reasons. There are many things plainly 
missing from Haskell besides global variables.

> IMO this is not a very satisfactory situation for a language 
> that's advertised as "general purpose".

"General purpose" doesn't mean that any programming idiom is supported.

> > Further, as for "evidence or credible justification" for the my claim,
> > you can gather it from the numerous real-life examples I gave, and which
> > you chose to ignore or at least found not worthy of any comment.
>
> I have no idea what examples you're talking about. Did you post any code?

No, I didn't post code. I already said it's annecdotal evidence. For instance, 
I was talking about using the ONC/RPC implementation on VxWorks, which is 
broken because they internally use thread-local mutual state.

> If so, I must have missed it for some reason. Perhaps your're refering
> to your elimination of unsafePerformIO from a library you were writing.

I wasn't.

> > Of course,
> > these examples are only annecdotal but I think this is better than a
> > completely artificial requirement (like your "oneShot").
>
> Being able to avoid the use of top level mutable state sometimes (or even
> quite often) is not proof that it's unnecessary, 

True. I have never claimed that, though. What I claimed is that in the cases 
where they are necessary, FFI is probably used anyway, so it *is* workable to 
use a foreign language wrapper.

In order to convince me that this is wrong you could present a (real-world, no 
artificial requirements) example that does not require the use of FFI anyway. 
If you can do so (which I doubt) I might be willing to accept a 
compiler-supported standard library routine with a very long and very ugly 
name like

warningBadStyleUseOnlyIfAbolutelyNecessary_performOnlyOnce: IO a -> IO a

;-)

> especially when nobody 
> (other than yourself presumably) knows why you were using it in the first
> place. 

Not I. And it was for convenience only, as I proved by completely eliminating 
them without making the code any more complicated. I never claimed that this 
proves anything, it was just a personal experience.

BTW, the main reason they use global variable in C all the time is because 
it's just so damn convenient (at first) and *not* because there are problems 
otherwise unsolvable. (There are *very* few exceptions.)

> However, the existance of just one real world example where it does 
> appear unavoidable is pretty convincing evidence to the contrary IMO.

I agree that the alternatives are not a good *general* solution. I have been 
arguing that a general solution is not desirable.

> > You have been asked more than once to present a *real-life* example to
> > illustrate that
> >
> > (a) global variables are necessary (and not just convenient),
> > (b) both above mentioned alternatives are indeed unworkable.
>
> I knew this would happen. I was asked to provide an example and I *did*.
> I gave the simpl

Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables andIO initializers

2004-11-09 Thread Claus Reinke
> > >The problem is simple enough to restate for anyone who's interested.
> > >"Provide a simple reliable mechanism to ensure that in a given
> > > program run one particular top level IO operation cannot be executed
> > > more than once."
> > No language can guarantee this -  all I have to do is run 2 copies of
> > the executable at once... or wven sequentially!
> Read what I wrote :-)

oh well, if you insist on overspecification:

Loading package base ... linking ... done.
Prelude> let once io = getContents >> io
Prelude> let init = once $ putStrLn "okay"
Prelude> init
okay
Prelude> init
*** Exception: : hGetContents: illegal operation (handle is closed
Prelude> init
*** Exception: : hGetContents: illegal operation (handle is closed
Prelude>

this method may have some unexpected side-effects, but you don't mind
that, do you?-)

unsafePerformIO is a wonderful extension hook for making Haskell implementations
do things they wouldn't normally do without having to write such an 
implementation
from scratch. the problem is that those extended Haskell implementations may 
then
do things they wouldn't normally do..

for instance, you shouldn't bet your life on your method working with all 
future 
Haskell implementations - you'll have to check with every new release whether
your use of the extension hook is still compatible with whatever other progress
has been made (e.g., a distributed implementation may decide to start with 
copies
of the code on each node, etc.).

today you can say {-# please don't mess with this #-}, or if your compiler is a 
bit
more eager, you may have to say {-# please, please don't mess with this #-}, and
it may just work most of the time as long as everybody remembers that there are
these user-defined extensions hanging around that will break in horrible ways 
if we
forget that we've left the domain of pure functional programming.

i thought the point of this thread was to look for a way to take one particular 
use
pattern of unsafePerformIO that is deemed to be safe, and to devise a proper
language extension that captures exactly this use pattern in such a way that no 
unsafe constructs need be involved anymore.

iirc, this use pattern started out as being global variables, then became IO 
initialisers, then IO initialisers per module, then commutative monads, then
merging of  IO and ST, then run-once code, ..

you won't be able to capture all uses of unsafePerformIO unless you recreate 
it, which is exactly what you don't want - it is there already, and you want to
find ways not having to use it.

your example is still useful because it describes a situation at the borderline 
between the functional and IO worlds where one is tempted to use global
variables. as has been pointed out, the reason in this particular case is that 
one might want to do something in Haskell-land that should perhaps be done 
in the outside world, because the whole point of the exercise is to make 
something behave as a functional object when it is not. 

now one could argue that things should be converted to a functional point 
of view before importing them into Haskell, or one could argue that as much
as possible should be done on the Haskell side, even if that means 
compromising the language a little or balancing the library author over 
an abyss.both arguments have their merit.

afaik, the main problem that people try to solve with global variable tricks
is not executing code (you could call an init action in main), but having to
distribute the results of running that code. as others have pointed out, that
is similar to the situation with stdin/etc - you want to open the channels
*and* make the resulting handles available everywhere.

now, if every module by default had a stdinitMVar, you could do your
initialisation in main and put the results into Main.stdinitMVar. and if you
wanted to forward the information to an imported module, you could
put the info into Module.stdinitMVar. and if you wanted per-module
initialisation, you'd use Main.init to call Module.init (name init just a 
convention), which would put its results into its very own 
Module.stdinitMVar. problem solved. 

problem solved? i'm not so sure about that, for the same reasons
global variables/registers/etc. have been considered evil by many of
who reinvented them.and shouldn't multiple instances of modules be
possible, each with its own stdinitMVar? but some of the proposals 
that have been circulating in this thread are even worse, as they 
include an arbitrary number of user-defined and -named initialisation 
variables, and arbitrary numbers of initilisation actions, to be called 
in some underspecified form and sequence, making them hard to 
predict and find for those having to maintain such code.

there are actually at least *two* problems you need to solve: one
is providing for those few cases where global-variable-like things
are too convenient to consider anything else. that's actually fairl

Re: [Haskell-cafe] Re: Global Variables and IO initializers

2004-11-09 Thread Henning Thielemann

On Tue, 9 Nov 2004, Ferenc Wagner wrote:

> Henning Thielemann <[EMAIL PROTECTED]> writes:
> 
> > On Mon, 8 Nov 2004, Keean Schupke wrote:
> >
> >> If you tell me the library you wish to use I may be able
> >> to suggest a better alternative.
> >
> > I'm using FFTW and PLPlot (but not with Haskell), both
> > uses internal states and thus must be considered as ill
> > designed. Do you know of better alternatives?
> 
> I'm no expert on this, being exposed to FFTW for a couple of
> hours, but isn't its internal state encapsulated into the
> 'plan', which is suitable as a handle?

Additional to plans it stores some "wisdom" which is handled globally. 
 http://www.fftw.org/fftw3_doc/Thread-safety.html#Thread-safety

:-(

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and whatever

2004-11-09 Thread Keean Schupke

as i said in my other post (waiting for moderator approval), there
are many people on this thread, and i'm not sure they are all talking
about the same thing. perhaps a good step forward would be for 
each concrete proposal to go into a separate thread (beginning 
with a summary of the use pattern to be covered and the concrete 
extension proposal claiming to do the job), and then to see whether 
there is any consensus for any of them.
 

Well, my suggestion for one-shot routines would be to implement
a simple Haskell library supporting named semaphores, and named
channels. These resources need to be managed by the OS, so on
unix the obvious way to implement them is to use unix-domain
sockets for the channels, but their might be a more efficient way.
   oneTimeInit = do
  s <- testAndSetSemaphore "myUniqueString"
  if s
 then -- already run
 else -- not run yet
   Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Global Variables and IO initializers

2004-11-09 Thread Ferenc Wagner
Henning Thielemann <[EMAIL PROTECTED]> writes:

> On Mon, 8 Nov 2004, Keean Schupke wrote:
>
>> If you tell me the library you wish to use I may be able
>> to suggest a better alternative.
>
> I'm using FFTW and PLPlot (but not with Haskell), both
> uses internal states and thus must be considered as ill
> designed. Do you know of better alternatives?

I'm no expert on this, being exposed to FFTW for a couple of
hours, but isn't its internal state encapsulated into the
'plan', which is suitable as a handle?
-- 
Feri.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO and State (was Re: [Haskell] Re: Global Variables and IO initializers)

2004-11-09 Thread Graham Klyne
At 10:38 08/11/04 -0800, Iavor S. Diatchki wrote:
It is not (should not be?) the case that IO = ST RealWord, as IO is not a 
state monad as we understand it.
In a state monad, the changes to the state are all in the program, i.e. 
one can always
point to the part of the program that modified the state.
On the other hand, the "state" of the RealWorld can change on its own,
without anything in the program affecting it.
I guess this is similar to "volatile" state in C.
For example, one might expect the following rule in a state monad:

do x <- readSTRef r
y <- readSTRef r
f x y
=
do x <- readSTRef r
f x x
But this is not true for the IO monad, as for example reading a file twice 
does not guarantee
that you will get the same result, even if no part of the program ever 
wrote to the file.

Now the above law already doesn't hold when all GHC extensions are used,
as when concurrency is present we cannot assume that nobody modified the 
state concurrently.
As a result all pointers in GHC probably behave as if they were 
"volatile", which is not very nice.
Eek!  I find this most worrisome.  And I'm not sure that I agree.
I thought that part of the reason for having a monad that it was threaded 
in a useful way through the path of a *single* computation (expression 
evaluation).  If concurrent activities can change that, then I sense that 
they're breaking something quite fundamental in the way Haskell should work.

e.g. in a sequence like:
  v :: SomeMonad
  v = do { e1 ; e2 ; e3 }
Then I think that exactly the monad created by e1 is passed to e2, and the 
result of e2 passed to e3, without any visible external interference under 
any circumstance.  Concurrency, as I understand it should apply to Haskell, 
would allow different elements of that computation to be performed in 
different threads/processes, but the overall result of the computation 
should not be changeable.  Put another way, the graph reduction model for 
evaluating a Haskell program should not change, just the mechanics actual 
processes (or processors) actually perform the reduction steps.

Or am I really overlooking something here?
#g

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Global Variables and IO initializers

2004-11-09 Thread Henning Thielemann

On Mon, 8 Nov 2004, Keean Schupke wrote:

> For 'broken' libraries that cannot support multiple simultaneous
> contexts, it would be better to use the 'C' FFI based solution
> suggested by another poster. Ideally you would want to find
> a library with a better interface - If you tell me the library you
> wish to use I may be able to suggest a better alternative.

Really? That also interests me. I'm using FFTW and PLPlot (but not with
Haskell), both uses internal states and thus must be considered as ill
designed. Do you know of better alternatives? 


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and whatever

2004-11-09 Thread Claus Reinke
> I take it the position of those who object to such things is not..
>  "Top level mutable variables are a very very bad thing and
>   should never ever be used (Errm..well unless they're really
>   necessary, in which case you should use C)."

more like: if you have two parts of your codebase, one of which
easily accomodates such variables and is already flooded with 
them, the other not, then it may be a good idea to put such 
variables in the first part.

but that doesn't mean that there aren't common programming
problems that are currently inconvenient in Haskell and could
be supported better, without the need for unsafePerformIO.

> As I have observed in an earlier post, the thread title
> chosen by the OP is a rather unfortunate choice of words IMO.
> I wish people stop talking about "global variables". Nobody is
> advocating the use of global mutable variables. 

perhaps you aren't, and some other posters in this thread aren't,
but it is one of the most common uses of unsafePerformIO, and
it is one of the subjects of this thread (and the ones before). then 
again, perhaps you're only thinking you're not talking about 
global mutable variables (the emphasis being more on mutable 
than on global).

if you look back at your own oneShot example, you might find
that the local MVar putting and taking isn't doing much at all, 
and the magic lies in the use of unsafePerformIO to share the
result of the IO action. so you could move the unsafePerformIO 
into your oneShot (if you're certain to inspect the result of
initialisation, you could avoid the strict application $!):

Prelude System.IO.Unsafe> let realInit = putStrLn "okay"
Prelude System.IO.Unsafe> let {oneShot :: IO a -> IO a; 
  oneShot io = return $! 
unsafePerformIO io}
Prelude System.IO.Unsafe> let userInit = oneShot realInit
Prelude System.IO.Unsafe> userInit >>= print
okay
()
Prelude System.IO.Unsafe> userInit >>= print
()
Prelude System.IO.Unsafe> userInit >>= print
()
Prelude System.IO.Unsafe>

in other words, the core of your example is the variable userInit 
that is modified exactly once. but modified it is, even though userInit
is a Haskell variable, no MVar or other inherently modifiable thing.
depending on what realInit does (and being in IO a, that could be 
a lot), that may or may not be observable.

and as others pointed out, reasoning about programs involving 
unsafePerformIO involves contextual equivalences, no longer 
replacing equals in all contexts, so hoping for referential 
transparency in the general case might be a bit optimistic 
(that's why one has to disable compiler optimisations based 
on this property, after all). 

your specific case seems slightly less problematic since userInit 
is itself of type IO (), but in combination with the monad laws, 
one might still run into trouble -- every use of unsafePerformIO 
indicates a proof obligation that such trouble will not arise (or 
rather: under what constraints it won't).

> Actually, I know I'm not going to have to repeat this yet again
> because I'm going to make this is my last post on this thread.

as i said in my other post (waiting for moderator approval), there
are many people on this thread, and i'm not sure they are all talking
about the same thing. perhaps a good step forward would be for 
each concrete proposal to go into a separate thread (beginning 
with a summary of the use pattern to be covered and the concrete 
extension proposal claiming to do the job), and then to see whether 
there is any consensus for any of them.

cheers,
claus



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and whatever

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 9:53 pm, Keean Schupke wrote:
> What did you think of the code example given where the one-shot nature is
> provided by a 'C' wrapper around the FFI function. I think this is the best
> solution...

As a pragmatic solution to this (and only this) particular problem it's OK.

But let's not pretend the real problem has gone way (or just doesn't exist)
as a result of this. There are many reasons why people might need top-level
TWIs. You asked for a simple example and I provided one, that's all.

Also note that Roberts solution still requires the use of a top level
mutable variable. I take it the position of those who object to such
things is not..

 "Top level mutable variables are a very very bad thing and
  should never ever be used (Errm..well unless they're really
  necessary, in which case you should use C)."

Now that would be strange. I would call that "militant denial".

As a side note (not specifically directed at you) I would also
like folk to take note that the mutable variable used in Roberts
solution is top level, but is NOT global.

As I have observed in an earlier post, the thread title
chosen by the OP is a rather unfortunate choice of words IMO.
I wish people stop talking about "global variables". Nobody is
advocating the use of global mutable variables. I sure hope I'm
not going to have to repeat this (yet again!).

Actually, I know I'm not going to have to repeat this yet again
because I'm going to make this is my last post on this thread.

Regards
--
Adrian Hey

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Global Variables and IO initializers

2004-11-08 Thread jeff
Quoting Peter Simons <[EMAIL PROTECTED]>:

> jeff  writes:
>
>  >> Just ask the C++ folks about the wonders of global
>  >> variables that are actually complex classes with a
>  >> constructor and a destructor.
>
>  > You can't use that as an argument against global
>  > variables in other languages.
>
> Why not?

So what if there are problems with globals that are actually
complex classes etc in C++?

Why should that matter to anyone using any other language?

> Does the creation of global variables never fail in
> Haskell?

That's a different argument, not based on C++.

> Besides, my main point is that they are
> _unnecessary_ in my experience,

Ok, but that's again not the C++ argument (which was all that
I was addressing).

-- Jeff
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Global Variables and IO initializers

2004-11-08 Thread Peter Simons
jeff  writes:

 >> Just ask the C++ folks about the wonders of global
 >> variables that are actually complex classes with a
 >> constructor and a destructor.

 > You can't use that as an argument against global
 > variables in other languages.

Why not? Does the creation of global variables never fail in
Haskell? Besides, my main point is that they are
_unnecessary_ in my experience, not that it were impossible
to implement them.

Peter

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and =?utf-8?q?IO initializers?=

2004-11-08 Thread Keean Schupke
Yes I didn't read your specification accurately... However I would argue
such a constraint on the problem domain is artificial as operating 
systems exist.
At the end of the day it is the job of the OS to manage such one-shot 
hardware
inits, not application code. (As the OS is the only thing that can 
manage resources
accross multiple programs)...

What did you think of the code example given where the one-shot nature is
provided by a 'C' wrapper around the FFI function. I think this is the best
solution...
   Keean.
Adrian Hey wrote:
On Monday 08 Nov 2004 6:48 pm, Keean Schupke wrote:
 

Adrian Hey wrote:
   

The problem is simple enough to restate for anyone who's interested.
"Provide a simple reliable mechanism to ensure that in a given
program run one particular top level IO operation cannot be executed
more than once."
 

No language can guarantee this -  all I have to do is run 2 copies of
the executable at once... or wven sequentially!
   

Read what I wrote :-)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and =?utf-8?q?IO initializers?=

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 6:48 pm, Keean Schupke wrote:
> Adrian Hey wrote:
> >The problem is simple enough to restate for anyone who's interested.
> >"Provide a simple reliable mechanism to ensure that in a given
> > program run one particular top level IO operation cannot be executed
> > more than once."
>
> No language can guarantee this -  all I have to do is run 2 copies of
> the executable at once... or wven sequentially!

Read what I wrote :-)

Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Global Variables and IO initializers

2004-11-08 Thread jeff
Quoting Peter Simons <[EMAIL PROTECTED]>:

> Just ask the C++ folks about the
> wonders of global variables that are actually complex
> classes with a constructor and a destructor.

You can't use that as an argument against global variables
in other languages.

-- Jeff
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Global Variables and IO initializers

2004-11-08 Thread Peter Simons
Adrian Hey writes:

 >> I don't see any value in problems that are
 >> specifically designed so that they can be solved
 >> only with a global entity.

 > Even if it was true that I had "specifically
 > designed" this problem, it's existance is of some
 > interest I think.

Perhaps my choice of words wasn't really good. I am
sorry. What I meant to say is that I have never once
_needed_ a global variable yet. Never. On the other
hand, there were plenty of occasions where I had
trouble with global variables in other people's code.
I'll readily admit that a safe way to implement them in
Haskell is probably an interesting research subject,
but I honestly don't expect to be using that feature
any time soon. It's a completely abstract concept for
me; I associate no practical value with it.


 > [Creating top level "things with identity" is] what
 > many in this thread assert is bad code, yourself
 > included it seems. Yet this is widely used in many
 > programs and libraries, even in ghc itself I
 > believe. Not to mention stdin etc.. (again).

Right, but it is by no means _necessary_ to have a
global 'stdin'. It could equally well be defined as

  stdin :: IO Handle

and it would work just the same. The fact that it isn't
implemented this way is for historical reasons, IMHO,
not because it's a good idea.


 >> Because code like that is very hard to get right
 >> and very hard to maintain, and I don't want to use
 >> library code that uses this technique if I can
 >> avoid it.

 > This is dogma I think.

Yes, you are right. Nonetheless, it is a dogma that's
not just arbitrary; it is motivated by experience with
real-life code. Just ask the C++ folks about the
wonders of global variables that are actually complex
classes with a constructor and a destructor. You
wouldn't believe through what kind of hoops you have to
jump if you want to write reliable code that has to
deal with this. For instance: Where do you catch
exceptions a constructor throws that is executed before
your main() routine is? How do you deal with exceptions
that are thrown after your main routine has _ended_?

The effect is that the language is full of strange and
very counter-intuitive mechanisms, just so that they
can implement something which -- in _my_ opinion -- is
completely useless to begin with!


 > There are many libraries you will need to try to
 > avoid using if this is really your position.

Let's say ... I try to compromise rarely, but I do have
to compromise, unfortunately. In fact, I have to admit
that my own Haskell code contains unsafePerformIO at
the occasion, too. Not that I'd need it, but I am too
damn lazy as well. :-)

Peter

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables =?iso-8859-1?q?and IO initializers?=

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 12:26 pm, Lennart Augustsson wrote:
> Keean Schupke wrote:
> > Adrian Hey wrote:
> >> The first step to solving a problem is to at least recognise
> >> that it exists. What is "bizarre" is that so many folk seem
> >> to be in denial over this. Perhaps you would like to show
> >> me your solution to the "oneShot" problem.
> >
> > Why are you unable to give a concrete real world
> > example of why this is necessary then. Even your
> > example of real world hardware that must be
> > initialised once fails! (What if I start two copies
> > of the program?)
>
> Indeed.  With hardware the solution is to do
>   hdl <- openDevice
> which will succeed the first time and then return
> "busy" until closed.

How will it know it's "busy"? Please show me the
code for your hypothetical openDevice.

Regards
--
Adrian Hey

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and =?iso-8859-1?q?IO initializers?=

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 10:37 am, Keean Schupke wrote:
> Adrian Hey wrote:
> >The first step to solving a problem is to at least recognise
> >that it exists. What is "bizarre" is that so many folk seem
> >to be in denial over this. Perhaps you would like to show
> >me your solution to the "oneShot" problem.
>
> Why are you unable to give a concrete real world
> example of why this is necessary then.

Because it is irrelevant, unless you think I'm lying.
It is suffices merely to state the problem.

If you want an answer see my reply to Keith.

Regards
--
Adrian Hey


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 12:14 pm, Lennart Augustsson wrote:
> Adrian Hey wrote:
> > Why are top level IORefs any worse than other IORefs (for
> > example)?
>
> Because global variables are just BAD.

Who said anything about global? 

> If you really grok the functional way of doing things there should
> be *very*, *very* few times you need a global variable.

"*very*, *very* few times" is not the same as never.

Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Keean Schupke
Just to add a small point... you can see how the 'bad' single context
design affects the code that uses it. Because C allows global variables
it is possible to write libraries that require once-and-only-once 
initialisation.
In Haskell (without global variables) it is impossible (or at least 
extreemly
hard) to write such librarys. Haskell libraries tend to allow multiple
concurrent independent threads of access. Allowing global vars into
Haskell would make it easy for coders moving to Haskell from C to carry
on coding in a bad style. It seems correcting the problem outside of
Haskell and in C is the right approach - as it does not involve making
these 'bad' things easier to do in Haskell.

Keean.
Keean Schupke wrote:

Any C library which requires an explicit initialisation call before 
anything
in that library can be used (common enough IME). Accidental 
re-initialisation
(e.g. by two independent modules/libraries) will destroy any state 
currently
be used by the libraries existing "clients".

The need to do this may or may not indicate "bad design" on the part 
of the
library author. But so what? It just happens to be a fact that must 
be dealt
with from Haskell (in a safe manner preferably).
 

You are right, the C library that works like this is "bad design"...
any library should really be reentrant, an preferably state free.
An example of a well designed C library is the ODBC database
connection library, where all the state is stored in opaque
handles returned to the user.
For 'broken' libraries that cannot support multiple simultaneous
contexts, it would be better to use the 'C' FFI based solution
suggested by another poster. Ideally you would want to find
a library with a better interface - If you tell me the library you
wish to use I may be able to suggest a better alternative.
   Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and =?iso-8859-1?q?IO initializers?=

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 11:58 am, Peter Simons wrote:
> Adrian Hey writes:
>  > Perhaps you would like to show me your solution to the
>  > "oneShot" problem.
>
> I don't see any value in problems that are specifically
> designed so that they can be solved only with a global
> entity. 

Why not? Even if it was true that I had "specifically designed"
this problem, it's existance is of some interest I think.

> What is the real-world application for oneShot?

See my response to Keith.

>  > I gather it's even used within ghc. If the two Simons
>  > don't know how to write "proper" Haskell, what hope is
>  > there for the rest of us.
>
> Nobody said that. Use of unsafePerformIO does not equal bad
> code.

Nor did I accuse anyone of this. In this thread we're talking
one specific use of unsafePerformIO to create top level
"things with identity" (I think I'll call them TWI's from
now on).

This is what many in this thread assert is bad code, yourself
included it seems. Yet this is widely used in many programs and
libraries, even in ghc itself I believe. Not to mention stdin
etc.. (again).

>  > But why would it be a problem if it was not?
>
> Because code like that is very hard to get right and very
> hard to maintain, and I don't want to use library code that
> uses this technique if I can avoid it.

This is dogma I think. There are many libraries you will need
to try to avoid using if this is really your position.

Regards
--
Adrian Hey

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Keean Schupke

Any C library which requires an explicit initialisation call before anything
in that library can be used (common enough IME). Accidental re-initialisation
(e.g. by two independent modules/libraries) will destroy any state currently
be used by the libraries existing "clients".
The need to do this may or may not indicate "bad design" on the part of the
library author. But so what? It just happens to be a fact that must be dealt
with from Haskell (in a safe manner preferably).
 

You are right, the C library that works like this is "bad design"...
any library should really be reentrant, an preferably state free.
An example of a well designed C library is the ODBC database
connection library, where all the state is stored in opaque
handles returned to the user.
For 'broken' libraries that cannot support multiple simultaneous
contexts, it would be better to use the 'C' FFI based solution
suggested by another poster. Ideally you would want to find
a library with a better interface - If you tell me the library you
wish to use I may be able to suggest a better alternative.
   Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] IO and State (was Re: [Haskell] Re: Global Variables and IO initializers)

2004-11-08 Thread Iavor S. Diatchki
Hello,
Just wanted to point out that the suggested idea is not quite correct.
(well that has to be quantiifed a bit, see bellow)
Krasimir Angelov wrote:
--- Ben Rudiak-Gould
<[EMAIL PROTECTED]> wrote:
 

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
   


It is not (should not be?) the case that IO = ST RealWord, as IO is not 
a state monad as we understand it.
In a state monad, the changes to the state are all in the program, i.e. 
one can always
point to the part of the program that modified the state.
On the other hand, the "state" of the RealWorld can change on its own,
without anything in the program affecting it.
I guess this is similar to "volatile" state in C.
For example, one might expect the following rule in a state monad:

do x <- readSTRef r
y <- readSTRef r
f x y
=
do x <- readSTRef r
f x x
But this is not true for the IO monad, as for example reading a file 
twice does not guarantee
that you will get the same result, even if no part of the program ever 
wrote to the file.

Now the above law already doesn't hold when all GHC extensions are used,
as when concurrency is present we cannot assume that nobody modified the 
state concurrently.
As a result all pointers in GHC probably behave as if they were 
"volatile", which is not very nice.

I think that inherently there are two concepts here, and I see no point 
in mixing them
(even though they are already a bit mixed up, because of stToIO).
The one is the usual sequential state that we know and love (and I think 
we use that a lot of the time).
In the sequential state the above optimization is one of the laws 
specifying the monad.
The other concept is that of "volatile" or concurrent state, and then 
the law doesn't hold.

The two monads have a very similar inetrafce (reading and wrinting 
pointers, and creating new pointers)
but the laws that the operations satisfy are different.

-Iavor




___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Robert Dockins
As a purely practical matter, it seems like the easiest solution (to 
this particular use case) is to write a small wrapper initializer in C 
which is idempotent, then use FFI to call the wrapper, rather than 
calling the initialization directly.  This is easy enough to do with a 
static local variable:

void doInit()
{
static int doneInit = 0;
if( !doneInit ) {
   reallyInit();
   doneInit = 1;
}
}
Then your haskell libs can call doInit any number of times, and
reallyInit will be called at most once.
Since your committed to FFI anyway (calling a C lib is the premise), the 
wrapper seems a small price to pay.  For Haskell-only code, something 
else would be nice.

Keith Wansbrough wrote:
Adrian Hey writes:

The problem is simple enough to restate for anyone who's interested.
"Provide a simple reliable mechanism to ensure that in a given
program run one particular top level IO operation cannot be executed
more than once."

Can you give one concrete example of an "intended application
of oneShot", so that we can either propose a concrete Haskell
implementation of it, or agree that global variables really are necessary.
Any C library which requires an explicit initialisation call before anything
in that library can be used (common enough IME). Accidental re-initialisation
(e.g. by two independent modules/libraries) will destroy any state currently
be used by the libraries existing "clients".

Great, thanks, that's just what I was hoping for - I now see the
problem you're trying to address.
--KW 8-)
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Keith Wansbrough
Adrian Hey writes:

> The problem is simple enough to restate for anyone who's interested.
> "Provide a simple reliable mechanism to ensure that in a given
>  program run one particular top level IO operation cannot be executed
>  more than once."
> 
> > Can you give one concrete example of an "intended application
> > of oneShot", so that we can either propose a concrete Haskell
> > implementation of it, or agree that global variables really are necessary.
> 
> Any C library which requires an explicit initialisation call before anything
> in that library can be used (common enough IME). Accidental re-initialisation
> (e.g. by two independent modules/libraries) will destroy any state currently
> be used by the libraries existing "clients".

Great, thanks, that's just what I was hoping for - I now see the
problem you're trying to address.

--KW 8-)

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Keean Schupke
Adrian Hey wrote:
The problem is simple enough to restate for anyone who's interested.
"Provide a simple reliable mechanism to ensure that in a given
program run one particular top level IO operation cannot be executed
more than once."
 

No language can guarantee this -  all I have to do is run 2 copies of
the executable at once... or wven sequentially!
Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 3:57 pm, Keith Wansbrough wrote:
> [posted to haskell-cafe per SLPJ's request]
>
> Hi Adrian,
>
> > I can assure you that for the intended applications of oneShot it
> > is vital that realInit is executed once at most, but the user must
>
> [..]
>
> > So please, no more handwaving arguments about this kind of thing
> > being unnecessary, bad programming style, or whatever..
> >
> > Please show me a concrete alternative in real Haskell code, other
>
> I'm mystified as to why you are insisting others provide real examples when
> you are not.

Maybe you should read the whole thread. AFAIK I am the only person who
has provided a concrete example of anything, and I did so in direct response
to a request to do so from Keaan IIRC.

Unfortunately my own requests for counter examples showing that there are
safer (easier, more elegant or whatever) solutions have been ignored (not
that I'm in the least bit surprised by this). Instead all I get is repeated 
denial of the reality of this problem.

The problem is simple enough to restate for anyone who's interested.
"Provide a simple reliable mechanism to ensure that in a given
 program run one particular top level IO operation cannot be executed
 more than once."

> Can you give one concrete example of an "intended application
> of oneShot", so that we can either propose a concrete Haskell
> implementation of it, or agree that global variables really are necessary.

Any C library which requires an explicit initialisation call before anything
in that library can be used (common enough IME). Accidental re-initialisation
(e.g. by two independent modules/libraries) will destroy any state currently
be used by the libraries existing "clients".

The need to do this may or may not indicate "bad design" on the part of the
library author. But so what? It just happens to be a fact that must be dealt
with from Haskell (in a safe manner preferably).

Regards
--
Adrian Hey

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Keith Wansbrough
[posted to haskell-cafe per SLPJ's request]

Hi Adrian,

> I can assure you that for the intended applications of oneShot it
> is vital that realInit is executed once at most, but the user must
[..]
> So please, no more handwaving arguments about this kind of thing
> being unnecessary, bad programming style, or whatever..
> 
> Please show me a concrete alternative in real Haskell code, other

I'm mystified as to why you are insisting others provide real examples when you 
are not.  Can you give one concrete example of an "intended application of 
oneShot", so that we can either propose a concrete Haskell implementation of 
it, or agree that global variables really are necessary.

Hoping to increase the light / heat ratio in this discussion...

Cheers,

--KW 8-)

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Jules Bean
On 8 Nov 2004, at 12:23, Lennart Augustsson wrote:
Adrian Hey wrote:
4- They already exist (stdin,stout,stderr) and I don't
   recall anybody ever complaining about this.
stdin, stdout, and stderr are not global variables.
They are just handles.  One possible implementation
of handles is as an Int.  So stdin is no more a global
variable than 0.  Of course you need some state
associated with the handle, but that state does not
have to be a unique global things.  You are passing
that state around via the IO monad, and there could
be multiple versions of it.  GHC chooses to implement
it differently, but that's a choice.
Yes... a lot of the example we have seen here are 'just' handles. 
newIORef creates handles.  Something many programmers would like is the 
ability to create fresh handles at the toplevel...

Jules
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Jules Bean wrote:
Yes... a lot of the example we have seen here are 'just' handles. 
newIORef creates handles.  Something many programmers would like is the 
ability to create fresh handles at the toplevel...
Yes, I hear what they want.  That doesn't mean I think it's
a good idea.  Top level things with identity are evil. :)
-- Lennart
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Keean Schupke wrote:
Adrian Hey wrote:
The first step to solving a problem is to at least recognise
that it exists. What is "bizarre" is that so many folk seem
to be in denial over this. Perhaps you would like to show
me your solution to the "oneShot" problem.
 

Why are you unable to give a concrete real world
example of why this is necessary then. Even your
example of real world hardware that must be
initialised once fails! (What if I start two copies
of the program?)
Indeed.  With hardware the solution is to do
hdl <- openDevice
which will succeed the first time and then return
"busy" until closed.  Any access to the device must
use the hdl.  Trying to do without the handle is just
shooting yourself in the foot.  It might look good at
first, but it doesn't scale.
-- Lennart
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Adrian Hey wrote:
4- They already exist (stdin,stout,stderr) and I don't
   recall anybody ever complaining about this.
stdin, stdout, and stderr are not global variables.
They are just handles.  One possible implementation
of handles is as an Int.  So stdin is no more a global
variable than 0.  Of course you need some state
associated with the handle, but that state does not
have to be a unique global things.  You are passing
that state around via the IO monad, and there could
be multiple versions of it.  GHC chooses to implement
it differently, but that's a choice.
-- Lennart
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Adrian Hey wrote:
Why are top level IORefs any worse than other IORefs (for
example)?
Because global variables are just BAD.  They have been considered
bad a long time, it's not a Haskell thing.
If you really grok the functional way of doing things there should
be *very*, *very* few times you need a global variable.
I incredibly suspicious about code that "needs" it.  Having a global
variable almost always you have a single copy of some data structure;
there is no way to create two of them.  I claim that the right way
is to have a handle to your "object" and pass that around.  (But I
can also be persuaded that there might be exceptions.  (I've written
a few lines of Haskell and I have used a global variable once, I
think.))
-- Lennart
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Peter Simons
Adrian Hey writes:

 > Perhaps you would like to show me your solution to the
 > "oneShot" problem.

I don't see any value in problems that are specifically
designed so that they can be solved only with a global
entity. What is the real-world application for oneShot?


 > If this is such a wacky idea then why is the use of the
 > unsafePerformIO hack to do precisely this so common place?

Because programmers tend to be lazy. I like Haskell because
it doesn't _allow_ me to be lazy.


 > I gather it's even used within ghc. If the two Simons
 > don't know how to write "proper" Haskell, what hope is
 > there for the rest of us.

Nobody said that. Use of unsafePerformIO does not equal bad
code.


 > But why would it be a problem if it was not?

Because code like that is very hard to get right and very
hard to maintain, and I don't want to use library code that
uses this technique if I can avoid it.

I'll be readily convinced of the opposite once I see code
that makes good use of this.

Peter

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Keean Schupke
Adrian Hey wrote:
The first step to solving a problem is to at least recognise
that it exists. What is "bizarre" is that so many folk seem
to be in denial over this. Perhaps you would like to show
me your solution to the "oneShot" problem.
 

Why are you unable to give a concrete real world
example of why this is necessary then. Even your
example of real world hardware that must be
initialised once fails! (What if I start two copies
of the program?) With this example the only
satesfactory solution if for the hardware itself
to keep track of when it is initialised. If the hardware
has a "I have been inititalsed" flag, the init
routine would check this flag as its first action and
exit should initialisation already have taken place.
Any other solution is broken in a multi-threaded
environment (or  even a single-threaded one in which
multiple exexutions of the same program are possible
like DOS).
   Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 6:00 am, Peter Simons wrote:
> Frankly, the idea that anyone would want to jump through
> hoops to add them to a purely functional language sounds
> bizarre to me. 

The first step to solving a problem is to at least recognise
that it exists. What is "bizarre" is that so many folk seem
to be in denial over this. Perhaps you would like to show
me your solution to the "oneShot" problem.

If this is such a wacky idea then why is the use of the
unsafePerformIO hack to do precisely this so common place?

I gather it's even used within ghc. If the two Simons
don't know how to write "proper" Haskell, what hope is
there for the rest of us.

Also a few more points that seem to need repeating..
1- We're talking about the general problem of creating
   top level "things with identity" (does anyone have
   a less cumbersome term?)
2- Creating top-level mutable variables (IORefs) is
   just one utterly trivial use of this capability.
3- Top-level does not imply global.
4- They already exist (stdin,stout,stderr) and I don't
   recall anybody ever complaining about this.
5- The above are already *implicitly* referenced by many
   other commonly used top level IO related functions.

> But by all means, as long as the compiler
> extension is disabled per default I won't mind. :-)

No doubt it would be, like all non-standard extensions.
But why would it be a problem if it was not?
If you don't want to use <- bindings then don't.
Nothing else has changed.

Regards
--
Adrian Hey

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Ben Lippmeier
Peter Simons wrote:
> [Global variables]
Well, to be fair one has to say that they are still quite
popular although people call them "singletons" and other
cute things these days.
 > Frankly, the idea that anyone would want to jump through
hoops to add them to a purely functional language sounds
bizarre to me. But by all means, as long as the compiler
extension is disabled per default I won't mind. :-)
A singleton doesn't nessesarally have to be "mutable". The idea is that 
the first time you use a singleton the object tied to that variable gets 
created, then all subsequent calls to it share the same object.

A Constant Applicative Form (CAF) (an expression defined at top level 
which has zero airity) in a pure functional language can be implemented 
in the same way. If you implement it as a singleton, it doesn't have to 
be created when its not needed.

All your top level library functions are also "global", you don't pass 
them into every function that uses them do you?

"Mutable" global state is another matter. It's sometimes well used and 
sometimes not. Just because you go and wrap a monad around it doesn't 
make it less mutable.

Ben.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Peter Simons
Benjamin Franksen writes:

 > Even in C++ using global variables is nowadays generally
 > regarded as bad design, especially for libraries.

Well, to be fair one has to say that they are still quite
popular although people call them "singletons" and other
cute things these days. I distinctly remember reading
hundreds and hundreds of articles which explained in great
detail how to create and use them in slightly less than 200
lines of template meta-programming code without making the
compiler explode and still getting the result you expected
almost half of the time. Of course, if you used
multi-threading it all exploded nonetheless then.

So the discussion about global IO initializers in Haskell is
slightly reminiscent of that for me.

The argument in favor of global variables usually was that
it was "more comfortable", which means that using them saved
you a total of 20 seconds per-module because you had a
parameter less to type every now and then, at the small cost
of making your code almost unmaintainable in the long run.

Frankly, the idea that anyone would want to jump through
hoops to add them to a purely functional language sounds
bizarre to me. But by all means, as long as the compiler
extension is disabled per default I won't mind. :-)

Peter

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Adrian Hey
Please, can we confine this discussion to just one mailing list:-)

It started out on [EMAIL PROTECTED] so that's where I'd like
to keep it (at least that's where I will be posting my responses
from now on).

On Sunday 07 Nov 2004 10:38 pm, Keean Schupke wrote:
> >I don't understand the relevance of this. In the example I gave
> >we're not talking about an abstract data structure and the init
> >function is not stateless.
>
> Well, it works like this, to call any function in your library
> you must present a state-type. The only way to get a
> state-type would be to call the init function. Therefore the
> type system enforces that initialisation has occured
> before a function is called. The user would not need to
> call the initialiser again as you would pass the state-type
> between functions. The neatest way to do this would be
> to make functions in your interface instances of a
> state-monad-transformer that could be layered over the
> IO monad.

So how does this _prevent_ the user calling realInit twice?

Also, you seem to be assuming that the parameter returned by
realInit is a some kind of state reference that must be passed
as an argument to every function that is dependent on that state.
There may be something to be said for that approach (for the reasons
you give), but it's also rather tiresome to do this.
(Almost as awkward as Cleans unique environment passing.)

But maybe realInit simply returns a Bool to indicate whether or
not initialisation is successful (as is typical with C). Or maybe
it just returns () if there's no possibility of failure.

I certainly could design the realInit binding so that it returns
an abstract state reference, and I could insist that every function
in the library takes that state reference as an argument. But why
should I make life so awkward for both myself and library users,
especially as AFAICS it does not stop realInit being used twice
or more.

> >I can assure you that for the intended applications of oneShot it
> >is vital that realInit is executed once at most, but the user must
> >have the freedom to execute userInit as many times as they need
> >(I.E. without the burden of having to keep track of whether or not
> >they've used it before).
>
> I don't understand this - If you pass the state type you
> do not need to call init again.

Please just take my word for it that that realInit can never
be used more than once. That is the basic premise of this problem.
The user may not need to use it more than once, but that doesn't mean
they won't, and in fact it may be rather awkward for them to ensure
they don't (other than by using oneShot or similar mechanism themselves
at the top level).

> It would work like openFile,
> which seems easy enough for users to understand is
> called only once on a file to get the filehandle that is used
> with the IO functions. You can call the state-type returned
> from your library an opaque-handle, and treat it like a file
> handle.

No it wouldn't. realInit is not an "act of creation" which
may be used again and again to create more and more things.
It is an act of initialisation of a unique external resource.

> I am only trying to understand the need for this. As it
> appears the cost of using the unsafePerformIO style is that
> certain optimisations need to be switched off.

They only need to be switched off for an entire module because of
the use of unsafePerformIO. This is the problem, not the use of
top level <- bindings (if they existed).

So why not fix the language to make the use of unsafePerformIO
unnecessary?

> it seems it would be better to find an alternative.

Sure there are alternatives, darned awkward ones AFAICS.

Why should this awkwardness be forced upon us because of (what appears
to me) a dogmatic belief that top level "things with identity" are a bad 
thing?

Why are they a bad thing?

Why are top level IORefs any worse than other IORefs (for
example)?

[I hope nobody is going to bring up the old type security chestnut
in response to this question. We've already been over that ground.]

> If you could give
> more details of the application someone may be able to
> suggest a resonable way of refactoring.

The problem is to ensure that a top level IO action cannot be
executed more than once. 

Regards
--
Adrian Hey

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Benjamin Franksen
[moving to haskell-cafe]

Sorry for the long post.

On Sunday 07 November 2004 22:55, Adrian Hey wrote:
> On Sunday 07 Nov 2004 1:45 pm, Benjamin Franksen wrote:
> > It's a similar advantage as using the IO monad has over allowing
> > arbitrary side-effects in functions: The IO monad gives you a clear
> > separation between stuff that has (side-) effects (i.e. depends on the
> > real word) and pure functions (which don't). Abandoning global variables
> > gives you a clear separation of stuff that depends on initialized state
> > and other stuff that does not depend on it.
>
> I don't agree. Hidden dependencies are a fact of life with stateful
> programming in general and IO monad in particular. Making some
> references explicit arguments (as you seem to be suggesting) does
> not eliminate the problem, it merely complicates an api for no good
> reason.

You have point here: hidden dependencies are something that is inherently 
possible in the IO monad. You can for instance easily create global variables 
using the FFI without resorting to unsafePerformIO. I'll take back what I 
said above. But I maintain that it is a good idea to avoid hiding 
dependencies if possible.

> Hiding internal state dependencies is a *good thing*. The trick is
> organise the dependencies and provide a robust "idiot proof" api so
> that users don't have to know about the internal organisation and any
> dependencies.

Oh, but the user *has* to know about them. The user must call the init routine 
before using otehr routines of the library, remember? Why are you against the 
type checker reminding her?

I know a lot of those "idiot proof" libraries: "You need to call X then call Y 
but not if Z was called before..." One of the ideas behind using functions 
with arguments and a static type system is to encode dependencies so that the 
compiler can enforce them.

And BTW what if your idiot proof initialization routine needs arguments to 
configure the library? Is the user still allowed to call it from several 
places in his code, now with possibly different arguments? And with what 
effect?

> I don't believe this is a new (or controversial) idea.
> Its the basic idea behind stateful modular or OO programming.
> All the user sees is a set of actions which collectively deliver on
> a promise (by unknown means).

OO is the best argument *against* global variables. Pure OO languages have 
*no* hidden global state. In every real OO programm you have the dependency 
explicit, since you always need a "target" object on which to invoke methods. 
It doesn't matter that you write "object.f" instead of "f object" as you 
would in Haskell. I have never heard anyone using an OO language complain 
about that.

The two best OO languages I know of are Eiffel and O'Haskell/Timber. Both do 
not have global variables. Eiffel has 'once' routines which seem similar to 
be what you are after. Timber doesn't even have top-level IO actions, instead 
everything you need from the environment is given as an argument to main. 
Mark that Timber is used for real-time control, an inherently stateful and IO 
intensive field.

Your opinion that it automatically leads to a horrible API if you have to pass 
the initialized state around amounts to saying that in an OO language like 
Eiffel only libraries with horribly inconvenient APIs can be written. This is 
ridiculous.

Even in C++ using global variables is nowadays generally regarded as bad 
design, especially for libraries.

> > [...] You know that IO actions have (side-) effects, so you
> > would take care that the actions get executed as many times as is
> > apropriate. If the library docs indicate that it makes no sense to call
> > it twice, why would you do so?
>
> Given such a statement about realInit you wouldn't (or to be more precise,
> given a statement that calling it twice or more will really screw things
> up).

I would be really interested to know what kind of init action you are talking 
about, that so badly screws everything up if called twice. This is not 
rethoric, I mean it.

> But the question is *how* is the user to ensure that it is only called
> once. I see no other way than the darned awkward alternative I gave.

We have an interesting patt situation here: You argue that you want a feature 
so that you can enforce that a routine is called *at most* once. I argue that 
if you do this by hiding state dependencies, you are loosing the ability to 
enforce that it is called *at least* once.

You argue that it might be catastrophic if the library initialized more than 
once. I argue that it is usually catastrophic (with this I mean core dump or 
at least exception if it is programmed defensively) if you don't initialize 
it at all.

> I 
> suppose the other alternative is the noddy realInit is only used once in an
> action which is only used once, in an action .. from main (which is only
> used once hopefully). Is this what you have in mind?

It's the same patt as above: If you do it your way, you

Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Keean Schupke
Adrian Hey wrote:
Oh and while we're at it, perhaps one of you could explain what it is
you think is unsafe about the hypothetical top level <- bindings we're
discussing (I've asked this before too, but no answer has been provided).
Are your objections dogmatic, aesthetic, or rational?
Do either of you object to the existance of such things as stdout?
Or are you happy with their existance and it's just their safe creation
you object to? If so, this seems like a strange contradiction to me.
 

Just because something is possible does not make it desireable.
There may be certain extreme examples that really do require
this kind of thing - but I would have thought that if the code could
be refactored not to require it then that would be better.
Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Adrian Hey
On Sunday 07 Nov 2004 6:19 pm, Benjamin Franksen wrote:
> On Sunday 07 November 2004 17:41, Keean wrote:
> > I might really want to call the initialisation twice. If you use global
> > variables, the library can only be initialised once... but what if I
> > really want to use the library twice? With the state in a type passed
> > between functions, you can have multiple different states active
> > at once.
>
> Yes, exactly. Just as you might, in fact, *want* to call putString twice...

Exactly wrong. I have stated several times that realInit cannot be used
more than once, and this fact is the reason for the existance of oneShot.

I don't want to get to hung up on this one simple example (heaven knows
there are plenty of other possible examples), but I'm still waiting for
yourself or Keean to demonstrate a simpler and safer way of ensuring this,
not waffle your way out by saying it's unnecessary. I can assure you it
is necessary.

Oh and while we're at it, perhaps one of you could explain what it is
you think is unsafe about the hypothetical top level <- bindings we're
discussing (I've asked this before too, but no answer has been provided).

Are your objections dogmatic, aesthetic, or rational?

Do either of you object to the existance of such things as stdout?

Or are you happy with their existance and it's just their safe creation
you object to? If so, this seems like a strange contradiction to me.

Regards
--
Adrian Hey

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Keean Schupke

I don't understand the relevance of this. In the example I gave
we're not talking about an abstract data structure and the init
function is not stateless.
 

Well, it works like this, to call any function in your library
you must present a state-type. The only way to get a
state-type would be to call the init function. Therefore the
type system enforces that initialisation has occured
before a function is called. The user would not need to
call the initialiser again as you would pass the state-type
between functions. The neatest way to do this would be
to make functions in your interface instances of a
state-monad-transformer that could be layered over the
IO monad.
I can assure you that for the intended applications of oneShot it
is vital that realInit is executed once at most, but the user must
have the freedom to execute userInit as many times as they need
(I.E. without the burden of having to keep track of whether or not
they've used it before).
 

I don't understand this - If you pass the state type you
do not need to call init again. It would work like openFile,
which seems easy enough for users to understand is
called only once on a file to get the filehandle that is used
with the IO functions. You can call the state-type returned
from your library an opaque-handle, and treat it like a file
handle.
So please, no more handwaving arguments about this kind of thing
being unnecessary, bad programming style, or whatever...
 

I am only trying to understand the need for this. As it
appears the cost of using the unsafePerformIO style is that
certain optimisations need to be switched off, it seems it
would be better to find an alternative. If you could give
more details of the application someone may be able to
suggest a resonable way of refactoring.
   Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Benjamin Franksen
On Sunday 07 November 2004 17:41, Keean wrote:
> I might really want to call the initialisation twice. If you use global
> variables, the library can only be initialised once... but what if I
> really want to use the library twice? With the state in a type passed
> between functions, you can have multiple different states active
> at once.

Yes, exactly. Just as you might, in fact, *want* to call putString twice... ;)

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-07 Thread Keean Schupke
I might really want to call the initialisation twice. If you use global
variables, the library can only be initialised once... but what if I
really want to use the library twice? With the state in a type passed
between functions, you can have multiple different states active
at once.
   Keean.
Benjamin Franksen wrote:
Yes, whenever possible I would use this approach. Unfortunately, there are 
libraries (or just modules) that need to do some IO action in order to 
produce the (A)DT. In this case it _will_ make a difference how often you 
call it. But then this is just how IO actions are by nature, isn't it?

Ben
 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Global variables?

2003-02-16 Thread Richard Uhtenwoldt
Jon Cast writes

>I, personally, haven't written a program whose bulk will fit in a single
>file in several years, and I doubt I ever will again.  So, support for
>separate compilation is a necessity.  How do you intend to handle this?

Hmm; good point.


I see I have been guilty of a careless, uncharitable reading of Hughes's
paper!

the first three pages of Hughes's paper refer to "module" and the
equivalent word "package", but I skipped over those references on first
reading.

Moreover, when at the top of page 4 Hughes writes, "but such a
variable is bound by a \-expression, and not at top level," I missed the
relevance of the fact that only top-level binding are eligible for
export from a module.  

So, my previous post was unfair to Hughes because Hughes's four
solutions to the "global-mutables" problem seem to be able to span
module boundaries, whereas my solution does not.


Specifically, my "lexical-scope" solution allocates a global variable
via the code fragment

>newIORef 0 >>= \globalVariable-> lala

but there is no way in Haskell to export a lambda-bound variable, which
is what globalVariable is.


There's more bad news for my solution.

It is a very common pattern in the imperative world for a module to
contain a piece of "hidden" (not exported) state.  In fact, this is
one of the defining characteristics of the OOP paradigm.

And the addG, removeG, frontG, isEmptyG that figure so large in Hughes's
paper constitute and interface to a piece of hidden state, so it has
module-like characteristics, even though Hughes does not identify
it as a module.

If we try to use my lexical-scope solution to implement this very common
pattern, as follows, we run into trouble if we try to put it in its own
module because the variables addG, removeG, frontG and isEmptyG are not
bound at the top level and thus not eligible for export.

>main=do 
>ioref<-newIORef ...
>let
>addG = ...
>removeG = ...
>frontG = ...
>isEmptyG = ...
>in
>--code that refers to addG, removeG, etc, goes here.


In summary, my lexical-scope solution works only when 
the solution does not need to cross module boundaries.

We could change Haskell's module system so that it 
allows the export of lambda-bound and let-bound variables.

Or we could use the implicit-variables solution reccommended
in Hughes's paper.

I'm not going to try to make a decisive argument for either one, but in
the rest of this post I want to put in a few good words for the
alternative of changing Haskell's module system.  


What incited me to write the rest of this post is not module systems per
se.  Rather, I wish to use modules systems and Hughes's global-variables
paper as examples with which to express my scepticism or concern over
the design decisions behind extensions to Haskell whose purpose is to
support imperative programming.

The rest of this post (61 lines long) is not terribly important or
penetrating, so stop reading now if you value your time!  Maybe I should
have just deleted it rather than posting.


Haskell's module system was probably not designed with imperative
programming in mind.

In other words, it was designed before we had ambitions for Haskell to
be an imperative programing language as well as a declarative
programming language.  (Of course, not everyone in the Haskell community
has such ambitions.)

maybe it is time to re-examining the design decisions behind the module
system.

The imperative world has 27 years of experience with module systems,
starting with Modula in 1975.  It is likely that some of the design
decisions that have stood the test of time in the imperative world can
be applied directly to Haskell.

We probably do not want slavishly to copy into Haskell a module system
from the imperative world because no imperative language has Haskell's
type classes, nor AFAIK its algebraic datatypes and pattern matching.

Both of these features probably overlap in functionality
with module systems popular in the imperative world.

A good language designer will want to understand the areas of overlap
before designing a new module system for Haskell.


There is an analog in the imperative world to Haskell's notion of
a variable that receives the "result" of a monadic computation:
it is the assignment statement.

If the module systems that have withstood the test of time in the
imperative world can export entities that have been give a value by an
assignment statement, I am perfectly happy for Haskell's module system
to change so that it can do the same thing.

I see nothing wrong with looking toward the imperative world for ways of
implementing intrinsically imperative things (like global mutables).

And if the result of importing (pun not intended) from the imperative
all have types in the IO monad, that's okay with me: I see nothing toxic
or evil about the IO monad.


One might raise the objection that if Haskell simply copies the design
decisions of the imperative world, then there is no 

Re: separate compilation [was Re: Global variables?]

2003-02-05 Thread Andrew J Bromage
G'day all.

On Wed, Feb 05, 2003 at 09:28:05PM -0600, Jon Cast wrote:

> I think I see what you're saying.  I still maintain, however, that,
> since you've changed the type of B.b (admittedly implicitly), and B.b is
> exported from B, that you've changed B's interface.
> 
> There is a reason make is designed to re-build B /and/ (potentially) A
> when C changes, after all.

In principle, it shouldn't.  If module D imports module E, changing
E's implementation should not force a recompilation of module D
(assuming no intermodule optimisation, of course).  In GHC terms,
D.o should only depend on D.hs and E.hi.

However, this isn't my main problem.  This is at best a big pain,
and at worst a potential waste of an expensive software engineer's
time.  Software engineers like it when they can predict how long a
compilation will take.  The unknowns are an acceptible risk when
intermodule optimisation is turned on, but if I'm being paid by the
hour to hack Haskell code, I want a way to turn that off in order to
better schedule my day.  I digress.

My main problem is that under H98, it's not possible, in general, to
determine what the public interface of a module actually _is_ without
intermodule analysis.  This, IMO, breaks pretty much every sensible
meaning that you could assign to the term "separate compilation".

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: separate compilation [was Re: Global variables?]

2003-02-05 Thread Jon Cast
Andrew J Bromage <[EMAIL PROTECTED]> wrote:
> G'day all.

> On Wed, Feb 05, 2003 at 08:05:56PM -0600, Jon Cast wrote:

> > I'm not sure I follow this.  If you change the type of a value exported
> > from a given module, that's a public change, no?  And if you don't, why
> > should re-compilation be needed?

> Consider this:

> <<
> module A where

> import B

> {- use B.b -}
> >>

> <<
> module B (b) where

> import C

> b = C.c
> >>

> <<
> module C (c) where

> c :: Int
> >>

> Changing the type of c requires recompiling module A.

> You would expect that changing c's type forces a recompilation of B,
> since you changed C's public interface.  However, this also changes
> B's public interface even though you did not touch the text of module
> B.  The reason is that B's public interface is partly based on modules
> which it _privately_ imports, even if it does not re-export any
> symbols from those modules.

I think I see what you're saying.  I still maintain, however, that,
since you've changed the type of B.b (admittedly implicitly), and B.b is
exported from B, that you've changed B's interface.

There is a reason make is designed to re-build B /and/ (potentially) A
when C changes, after all.

> One fix is to require all exported symbols to have explicit type
> declarations.  Since this is good practice anyway, I would be in
> favour of making it a language requirement in Haskell 2.

> Cheers,
> Andrew Bromage

Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: separate compilation [was Re: Global variables?]

2003-02-05 Thread Andrew J Bromage
G'day all.

On Wed, Feb 05, 2003 at 08:05:56PM -0600, Jon Cast wrote:

> I'm not sure I follow this.  If you change the type of a value exported
> from a given module, that's a public change, no?  And if you don't, why
> should re-compilation be needed?

Consider this:

<<
module A where

import B

{- use B.b -}
>>

<<
module B (b) where

import C

b = C.c
>>

<<
module C (c) where

c :: Int
>>

Changing the type of c requires recompiling module A.

You would expect that changing c's type forces a recompilation of B,
since you changed C's public interface.  However, this also changes B's
public interface even though you did not touch the text of module B.
The reason is that B's public interface is partly based on modules
which it _privately_ imports, even if it does not re-export any symbols
from those modules.

One fix is to require all exported symbols to have explicit type
declarations.  Since this is good practice anyway, I would be in
favour of making it a language requirement in Haskell 2.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: separate compilation [was Re: Global variables?]

2003-02-05 Thread Jon Cast
Andrew J Bromage <[EMAIL PROTECTED]> wrote:
> G'day all.

> On Wed, Feb 05, 2003 at 04:16:33PM -0800, Iavor S. Diatchki wrote:

> > why do you think separate compilation is difficult to achieve in
> > Haskell 98?

> Because of type inference over recursive module imports.  Determining
> the type of a function may, in general, require inferring types from an
> arbitrary number of other modules, and may require inference to occur
> at the level of granularity of a clique in the import graph, rather than
> at the level of a single module.

> Requiring an implementation to perform static analysis a clique at a
> time is not "separate compilation", because changing something which
> is private to one module may in general require an unbounded number of
> other modules to be recompiled, even if inter-module optimisation is
> turned off.

I'm not sure I follow this.  If you change the type of a value exported
from a given module, that's a public change, no?  And if you don't, why
should re-compilation be needed?



> Cheers,
> Andrew Bromage

Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: separate compilation [was Re: Global variables?]

2003-02-05 Thread Andrew J Bromage
G'day all.

I noticed a mistake.

On Thu, Feb 06, 2003 at 11:42:21AM +1100, Andrew J Bromage wrote:

> Because of type inference over recursive module imports.

I meant to say _transitive_ module imports, which includes recursive
module imports.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: separate compilation [was Re: Global variables?]

2003-02-05 Thread Andrew J Bromage
G'day all.

On Wed, Feb 05, 2003 at 04:16:33PM -0800, Iavor S. Diatchki wrote:

> why do you think separate compilation is difficult to achieve in Haskell 
> 98?

Because of type inference over recursive module imports.  Determining
the type of a function may, in general, require inferring types from an
arbitrary number of other modules, and may require inference to occur
at the level of granularity of a clique in the import graph, rather than
at the level of a single module.

Requiring an implementation to perform static analysis a clique at a
time is not "separate compilation", because changing something which is
private to one module may in general require an unbounded number of
other modules to be recompiled, even if inter-module optimisation is
turned off.

> as simon pointed out, GHC does it and has been doing it for a long 
> time.

GHC does separate compilation by requiring the programmer to step
outside H98, by writing GHC-specific hi-boot files.  I agree that
GHC therefore supports separate compilation, but, as Fergus pointed
out, it does not support separate compilation within H98.

> dealing with mutually recusrive modules is i think a separate 
> issue.

Why is it a separate issue?

> even though GHC doesn't quite do it, it is certainly possible, 
> and not very difficult to do.  in fact we have it implemented in one of 
> the projects i am currently working on. hopefully one day GHC will also 
> dispense with the hi-boot files.

I would certainly like to see this, but it doesn't fix the concern
noted above, that changing something private to one module may cause
an arbitrary number of other modules to be recompiled.  That is not
"separate compilation" by any definition of the word "separate" that
I am aware of.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



separate compilation [was Re: Global variables?]

2003-02-05 Thread Iavor S. Diatchki
hello,

Andrew J Bromage wrote:

...
What H98 does is it defines a language for which separate compilation
is at best extremely difficult and at worst virtually impossible
without extra information which is not part of H98 (such as GHC's
hi-boot files).

> ...

why do you think separate compilation is difficult to achieve in Haskell 
98?  as simon pointed out, GHC does it and has been doing it for a long 
time.  dealing with mutually recusrive modules is i think a separate 
issue.  even though GHC doesn't quite do it, it is certainly possible, 
and not very difficult to do.  in fact we have it implemented in one of 
the projects i am currently working on. hopefully one day GHC will also 
dispense with the hi-boot files.

bye
iavor
--
==
| Iavor S. Diatchki, Ph.D. student   |
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Global variables?

2003-02-05 Thread Andrew J Bromage
G'day.

On 05-Feb-2003, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:

> > H98 has nothing to say about the separate compilation; it's an issue for
> > the implementation.

H98 indeed says nothing about separate compilation, and it is indeed
an issue for the implementation.

What H98 does is it defines a language for which separate compilation
is at best extremely difficult and at worst virtually impossible
without extra information which is not part of H98 (such as GHC's
hi-boot files).

On Wed, Feb 05, 2003 at 07:41:52PM +1100, Fergus Henderson wrote:

> In other words, GHC doesn't support separate compilation of
> Haskell 98 -- it supports separate compilation of a closely related
> but distinct language which we can call "Haskell 98 + GHC hi-boot files".

Exactly.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-05 Thread Fergus Henderson
On 05-Feb-2003, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:
> 
> | Haskell 98 has never supported separate compilation.  That's why we
> | have hi-boot files (or something similar).
> | 
> | So, yes, I'd like to know how the language designers intend to support
> | separate compilation in the next version.
> 
> H98 has nothing to say about the separate compilation; it's an issue for
> the implementation.  GHC does separate compilation for Haskell, and
> always has done.  It requires the programmer to supply an auxiliary
> hi-boot file for one module in each mutually recursive group (and, of
> course, none if there is no recursion between modules).

In other words, GHC doesn't support separate compilation of
Haskell 98 -- it supports separate compilation of a closely related
but distinct language which we can call "Haskell 98 + GHC hi-boot files".

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: Global variables?

2003-02-05 Thread Simon Peyton-Jones

| Haskell 98 has never supported separate compilation.  That's why we
| have hi-boot files (or something similar).
| 
| So, yes, I'd like to know how the language designers intend to support
| separate compilation in the next version.

H98 has nothing to say about the separate compilation; it's an issue for
the implementation.  GHC does separate compilation for Haskell, and
always has done.  It requires the programmer to supply an auxiliary
hi-boot file for one module in each mutually recursive group (and, of
course, none if there is no recursion between modules).

Simon
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-04 Thread Andrew J Bromage
G'day all.

On Mon, Feb 03, 2003 at 03:24:49PM -0600, Jon Cast wrote:

> I, personally, haven't written a program whose bulk will fit in a single
> file in several years, and I doubt I ever will again.  So, support for
> separate compilation is a necessity.  How do you intend to handle this?

Haskell 98 has never supported separate compilation.  That's why we
have hi-boot files (or something similar).

So, yes, I'd like to know how the language designers intend to support
separate compilation in the next version.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-03 Thread oleg

Richard Uhtenwoldt wrote:
> (2) the global variable has a lexical scope that extends over
> the bulk of the program.

> It strikes me as a simple and obvious application of lexical
> scope, and I am surprised that it received no mention in the
> discussions on this list and in Hughes's paper.

Something like that has been mentioned before:
  http://www.haskell.org/pipermail/haskell-cafe/2002-September/003423.html

If the global variables are used to store parameters that are read
from configuration files at the beginning and are not changed since,
it's possible to make such "global variables" _ordinary_ top-level
variables scoped through the entire program. No unsafe operations, no
pragmas, no implicit variables, and no reliance on the IO monad for
variable access are needed.

The previous article said the approach was ugly. I'd like to take it
back. The approach relies on an ability to dynamically compile and
link in a program -- something that we all do and something that is
specifically emphasized in the GHCi documentation.


The following code is snipped from the previous article and adjusted
for GHC. The latter is used as a meta-evaluator/dynamic linker of
sorts.

Suppose file '/tmp/a.hs' contains the following user program. Suppose
the program needs a global, configurational variable named 
Config.config_item. 

>>> File "/tmp/a.hs"

> import Config (config_item)
>
> foo = "foo shows: " ++ (show config_item)
>
> bar = "bar shows: " ++ (show config_item)
>
> main = do
>   print foo
>   print bar
>   print foo

Realistically a user program would do something more with the global
variables than just showing them. We specifically illustrate multiple
access to the global variable, to indicate that such access poses no
trouble (in contrast to the unsafePerformIO approach). We also note
that user computations 'foo' and 'bar' do not have to be annotated
with the type and the name of the global variable -- in contrast to
the implicit variable approach. Furthermore, foo and bar are pure
functions rather than IO actions. 

The value of the global variable Config.config_item is computed by
reading it from the configuration file. The computation occurs before
running of the main function of the user program. The following code
accomplishes the trick

*>>> File "/tmp/b.lhs"
*>>> To run this code, do 
*>>>   ghci -package posix b.lhs
*>>> Be sure /tmp/config exists and contains an integer value

> import System (system, ExitCode(ExitSuccess))
> import Posix(executeFile)
>
> myconfig_file = "/tmp/config"
>
> phaseII_var = "/tmp/Config.hs"
> phaseII_const = "/tmp/a.hs"
> phaseII_eval = "ghc --make "
> phaseII_result = "/tmp/a.out"
>
> nl = "\n"
>
> writeConfig :: Int -> IO ()
> writeConfig num =
>   do
>writeFile phaseII_var $
> concat
>  ["module Config (config_item) where", nl,
>   "config_item =", show num, nl]
>  
>
> runSuperIO () = system (phaseII_eval ++ 
> phaseII_const ++ " -o " ++ phaseII_result)
> >>= \ExitSuccess -> 
>  executeFile phaseII_result False [] Nothing
>
> main = readFile myconfig_file >>= writeConfig . read >>= runSuperIO

We can indeed be sure that the configurational variable is set before
the first attempt to access it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-03 Thread Jon Cast
Richard Uhtenwoldt <[EMAIL PROTECTED]> wrote:


> I do not think it is nice: I do not like any of the solutions Hughes
> considers in that paper because this problem can be handled much more
> simply with lexical scope and the IO monad.

can be /= should be

> Just to get our bearings, let us first consider the solution that uses
> unsafePerformIO, which neither Hughes nor I prefer:

> >globalVar :: IORef Int 
> >globalVar = unsafePerformIO $ newIORef 0 
> >foo = fff aaa bbb ccc 
> >bar = ggg xxx yyy zzz 
> >main = mmm >> nnn >> ooo

> where the lines 

> >foo = fff aaa bbb ccc
> >bar = ggg xxx yyy zzz

> stand in for a typically much larger chunk of code --the bulk of the
> program, let us call it.

I, personally, haven't written a program whose bulk will fit in a single
file in several years, and I doubt I ever will again.  So, support for
separate compilation is a necessity.  How do you intend to handle this?



Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-03 Thread Tom Pledger
Richard Uhtenwoldt writes:
 :
 | The solution I prefer replaces that last with
 | 
 | >main=do
 | >globalVar<-newIORef 0
 | >let 
 | >foo = fff aaa bbb ccc
 | >bar = ggg xxx yyy zzz
 | >mmm >> nnn >> ooo
 :
 | Am I the only one who prefers the above "lexical scope" solution
 | to all the solutions in Hughes's paper and given previously on
 | this list?

No, I prefer it too.  It would be even nicer with parameterised
modules, so that we could do something like

main = do
globalVar <- newIORef 0
let import (EvenBulkierThanFooAndBar globalVar)
foo = fff aaa bbb ccc
bar = ggg xxx yyy zzz
mmm >> nnn >> ooo

instead of passing globalVar to several of EvenBulkierThanFooAndBar's
exported functions separately.

- Tom

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Richard Uhtenwoldt
Andrew J Bromage writes:

>> John Hughes wrote a nice pearl on the subject, see
>> 
>>  http://www.math.chalmers.se/~rjmh/Globals.ps
>
>Nice!

I do not think it is nice: I do not like any of the
solutions Hughes considers in that paper because this 
problem can be handled much more simply with lexical
scope and the IO monad.

Just to get our bearings, let us first consider the solution that
uses unsafePerformIO, which neither Hughes nor I prefer:

>globalVar :: IORef Int 
>globalVar = unsafePerformIO $ newIORef 0 
>foo = fff aaa bbb ccc 
>bar = ggg xxx yyy zzz 
>main = mmm >> nnn >> ooo

where the lines 

>foo = fff aaa bbb ccc
>bar = ggg xxx yyy zzz

stand in for a typically much larger chunk of code --the bulk
of the program, let us call it.

The solution I prefer replaces that last with

>main=do
>globalVar<-newIORef 0
>let 
>foo = fff aaa bbb ccc
>bar = ggg xxx yyy zzz
>mmm >> nnn >> ooo

In other words, to be painfully explicit, the solution I prefer
arranges the program so that

(1) the global variable is the result of an IO computation just
like every other IO computation; and

(2) the global variable has a lexical scope that extends over
the bulk of the program.

It strikes me as a simple and obvious application of lexical
scope, and I am surprised that it received no mention in the
discussions on this list and in Hughes's paper.

Of course, whenever you want to read or to write my global
variable, you must be in the IO monad, but Hughes's solution
requires being in a state monad.  I do not consider the IO monad
any worse than any other state monad.

Am I the only one who prefers the above "lexical scope" solution
to all the solutions in Hughes's paper and given previously on
this list?


Indentation

One may raise the following objection to the "lexical scope"
solution: levels of indentation are a scarce resource and a
solution that consumes two of those levels before the program
proper even starts is wasteful.

I do not disagree with that objection; but I believe that the
best response to the objection is not to abandon the the
"lexical scope" solution but rather to adjust the syntactical
definition of Haskell and of the do notation.  E.g., we can
eliminate one level of indentation by doing what GHCi does and
eliminate the requirement for the "main=do" in programs.

(This has the added benefit of shortening the Haskell version of
"hello, world" to putStrLn "hello, world."

Do not underestimate the attractiveness of a language with a
short "hello, world" to the more practically-inclined
programmers of the world.)


>Why isn't RefMonad in hslibs?

>It makes perfect sense for there to be more than one kind of "ref"
>for a given monad.  Indeed, sometimes it's important.  Quite often, I
>use a custom ref built on top of IORef which supports Ord, as this is
>needed for hash consing.

I think it is cleaner and simpler to ask the compiler
maintainers to add an IORef instance to Ord.  They know
better how to implement it so it is fast.  And it is
the solution that puts the least cognitive demmand on
readers of your program.  (It's the easiest to learn,
I mean.)


I am not unalterably opposed to class RefMonad or to implicit
variables.  If someone makes a convincing argument that they are
the best solution to an issue or problem, I will use them.
But Hughes's paper does not convince me.

Note that the global-variable solution I prefer will be more
familiar to non-Haskell programmers.  (To appreciate it, they
have to "grok" monads, which can be a high hurdle, but they have
to "grok" monads to appreciate Hughes's solution, too.)

I wonder if Hughes's solution was motivated by a desire to avoid
having to stay in the IO monad during all access to global
variables.

Several on this list have stated or implied that the IO monad is
something to be resisted when possible.  I do not agree with
that position.  But a general defense of the IO monad will take
much more time than I have today.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Jon Cast
Fergus Henderson <[EMAIL PROTECTED]> wrote:
> On 02-Feb-2003, Jon Cast <[EMAIL PROTECTED]> wrote:
> > Claus Reinke <[EMAIL PROTECTED]> wrote:

> > > It is the programmer's responsibility to verify that none of these
> > > problems matter in the particular case of usage. Since many
> > > advances in compiler technology tend to invalidate those
> > > verifications, it is almost impossible to guarantee safety in such
> > > cases

> > Even with sufficiently liberal use of {-# NOINLINE #-}?

> Haskell Report, Appendix E (Compiler Pragmas): "An implementation is
> not required to respect any pragma".

Right.  So perhaps the Haskell Report should take more notice of global
variables.  But considering that it doesn't, and there is no completely
portable mechanism for getting global mutables, it seems to me that
bashing any alternative as non-portable is missing the point :)

> > > There you went.. into one of the many available traps in this
> > > mine-field:

> > > You argue that unallocated IORefs don't matter as long as "the"
> > > IORef is allocated before it is dereferenced. But that's just part
> > > of the problem - what about inlining globalVar, creating multiple
> > > IORefs?

> > {-# NOINLINE globalVar #-} :)

> What about creating two copies of globalVar, neither of them inlined?
> A compiler could do that to improve performance on some architectures,
> e.g. by allowing the function to be called via a short jump
> instruction rather than a long jump instruction.

See above.

> -- 
> Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
> The University of Melbourne |  of excellence is a lethal habit"
> WWW:   | -- the last words of T. S. Garp.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Fergus Henderson
On 02-Feb-2003, Jon Cast <[EMAIL PROTECTED]> wrote:
> Claus Reinke <[EMAIL PROTECTED]> wrote:
> > It is the programmer's responsibility to verify that none of these
> > problems matter in the particular case of usage. Since many advances
> > in compiler technology tend to invalidate those verifications, it is
> > almost impossible to guarantee safety in such cases
> 
> Even with sufficiently liberal use of {-# NOINLINE #-}?

Haskell Report, Appendix E (Compiler Pragmas):
"An implementation is not required to respect any pragma".

> > There you went.. into one of the many available traps in this
> > mine-field:
> 
> > You argue that unallocated IORefs don't matter as long as "the" IORef
> > is allocated before it is dereferenced. But that's just part of the
> > problem - what about inlining globalVar, creating multiple IORefs?
> 
> {-# NOINLINE globalVar #-} :)

What about creating two copies of globalVar, neither of them inlined?
A compiler could do that to improve performance on some architectures,
e.g. by allowing the function to be called via a short jump instruction
rather than a long jump instruction.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Jon Cast
Claus Reinke <[EMAIL PROTECTED]> wrote:
> > > > import IORef
> > > > import IOExts
> > > >
> > > > globalVar :: IORef Int
> > > > globalVar = unsafePerformIO $ newIORef 0

> > > John Hughes wrote a nice pearl on the subject, see

> > > http://www.math.chalmers.se/~rjmh/Globals.ps

> > This paper claims ``unsafePerformIO is unsafe''.  That's not
> > actually true in the sense meant; unsafePerformIO merely has safety
> > pre-conditions that the compiler can't check.

> Which is the main sense in which the 'unsafe' prefix is usually meant
> to be interpreted, and that is bad enough (see below, then re-read
> John's quote of Simon PJ's description of unsafePerformIO;-). In
> particular, the 'unsafe'-prefix is not a hint for the implementation
> to treat something with extra care, but a hint for the programmer that
> the implementation may shake unsafe expressions around like any other
> ones (inlining, cse, ..), even though that is bound to lead to
> problems with the hidden side-effects.

So you have to be careful.  If that weren't what I said, I'd disagree
with you :)

> It is the programmer's responsibility to verify that none of these
> problems matter in the particular case of usage. Since many advances
> in compiler technology tend to invalidate those verifications, it is
> almost impossible to guarantee safety in such cases

Even with sufficiently liberal use of {-# NOINLINE #-}?

> - about the best one can hope for is to identify and document
> precisely which assumptions need to be made to "guarantee"
> safety. Unfortunately, this leaves it to users to figure out whether
> the assumptions made by 'unsafe' authors (e.g., no inlining) are still
> valid at the point of use..

> Btw, when talking about unsafety in that paper, John also happens to
> point out the other little problem with unsafePerformIO: it permits to
> break type safety (many a good spirit has stumbled over that
> "polymorphic references" problem in other functional languages).

> > The precondition (proof obligation) of unsafePerformIO is that the
> > order in which unsafePerformIOs are performed cannot affect the
> > outcome of the program.  However, in this case, ordering doesn't
> > matter: the only side effect is allocation of a new IORef, and
> > IORefs are sufficiently opaque we don't care (or really know) about
> > un-allocated IORefs while the only case we care about the
> > now-allocated IORef is when we de-reference it.  But, that forces
> > the IORef, which executes the unsafePerformIO.  So, whenever we
> > access the variable, it is allocated.  Therefore, the outcome of the
> > program (regardless of the order of evaluation) is the same as if
> > all such global variable declarations are executed before main
> > begins executing.  So, the outcome is independent of the order of
> > evaluation.

> > There you go: the precondition of unsafePerformIO is satisfied, so
> > the usage is safe.

> There you went.. into one of the many available traps in this
> mine-field:

> You argue that unallocated IORefs don't matter as long as "the" IORef
> is allocated before it is dereferenced. But that's just part of the
> problem - what about inlining globalVar, creating multiple IORefs?

{-# NOINLINE globalVar #-} :)

> Remember that, by using unsafePerformIO, you've given the compiler the
> license to treat globalVar as an expression without side-effects, and
> for those inlining is a common first step to enable further
> optimisations (last time I checked, the language report didn't even
> guarantee the sharing on which the globalVar trick depends)! Now there
> are multiple side-effects instead of a single one, and read-and
> write-accesses are spread out over the multiple copies of your IORef,
> none of which is likely to hold the value you'd like it to have..

> Cheers,
> Claus

Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Jon Cast
Andrew J Bromage <[EMAIL PROTECTED]> wrote:
> G'day all.

> On Fri, Jan 31, 2003 at 01:54:26PM -0600, Jon Cast wrote:

> > Otherwise, though, see my other post on this subject:
> > unsafePerformIO will perform its action when the variable is
> > accessed, so you can't write a Haskell program which differentiates
> > between what any compiler actually does and running the variable
> > allocations before main.

> As has been pointed out, there is no language requirement for a
> Haskell implementation to be "fully lazy".  In particular, it is
> technically possible for an implementation to garbage collect
> globalVar and re-evaluate it on the next call.

So, the technique is implementation-dependent.  Since Hughes'
recommendation is equally non-portable, I don't see this as a serious
problem in this case.

> Haskell 2 should probably have a pragma controlling this.

IMO, that would be a good idea :)

> Cheers,
> Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Jon Cast
Patrik Jansson <[EMAIL PROTECTED]> wrote:
> On Fri, 31 Jan 2003, Jon Cast wrote:
> > Otherwise, though, see my other post on this subject:
> > unsafePerformIO will perform its action when the variable is
> > accessed, so you can't write a Haskell program which differentiates
> > between what any compiler actually does and running the variable
> > allocations before main.

> If you initialize this "global variable" with a value from a file
> which is changed by main (or over time) then order does matter.

1. Why would you do this?  In any case, the solution adopted in C
   (initialize the global statically with ``no value'' (0, NULL,
   Nothing, etc.) and overwrite it at a fixed point in main or
   elsewhere) should be good enough.

2. In any case, my claim is actually:

If a :: IO alpha, for monomorphic alpha, and a's only interaction with
the state consists of either creating new IORefs or accessing IORefs
created by a, then unsafePerformIO's result is unaffected by the order
of evaluation.

> I claim unsafePerformIO is very often unsafe

It's always potentially unsafe.  However, it is always possible to prove
that a particular application is safe (under sufficiently stringent
conditions, of course).

> - the question is more like if the "level of unsafety" is acceptable
> for a particular application.

There is no "level of unsafety".  There is only the level of trust you
put in your proof of satisfaction of unsafePerformIO's proof obligation
and your view of the acceptability of the portability restrictions of
your proof.

> /Patrik

Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Andrew J Bromage
G'day all.

On Fri, Jan 31, 2003 at 01:54:26PM -0600, Jon Cast wrote:

> Otherwise, though, see my other post on this subject: unsafePerformIO
> will perform its action when the variable is accessed, so you can't
> write a Haskell program which differentiates between what any compiler
> actually does and running the variable allocations before main.

As has been pointed out, there is no language requirement for a
Haskell implementation to be "fully lazy".  In particular, it is
technically possible for an implementation to garbage collect
globalVar and re-evaluate it on the next call.

Haskell 2 should probably have a pragma controlling this.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Andrew J Bromage
G'day all.

On Fri, Jan 31, 2003 at 09:08:22AM +0100, Ralf Hinze wrote:

> John Hughes wrote a nice pearl on the subject, see
> 
>   http://www.math.chalmers.se/~rjmh/Globals.ps

Nice!  Why isn't RefMonad in hslibs?

Possibly because of the class signature:

class Monad m => RefMonad m r | m -> r where
{- etc -}

It makes perfect sense for there to be more than one kind of "ref"
for a given monad.  Indeed, sometimes it's important.  Quite often, I
use a custom ref built on top of IORef which supports Ord, as this is
needed for hash consing.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Claus Reinke
> > > import IORef
> > > import IOExts
> > >
> > > globalVar :: IORef Int
> > > globalVar = unsafePerformIO $ newIORef 0
 
> > John Hughes wrote a nice pearl on the subject, see
> 
> > http://www.math.chalmers.se/~rjmh/Globals.ps
> 
> This paper claims ``unsafePerformIO is unsafe''.  That's not actually
> true in the sense meant; unsafePerformIO merely has safety
> pre-conditions that the compiler can't check.  

Which is the main sense in which the 'unsafe' prefix is usually meant 
to be interpreted, and that is bad enough (see below, then re-read John's
quote of Simon PJ's description of unsafePerformIO;-). In particular, the
'unsafe'-prefix is not a hint for the implementation to treat something with 
extra care, but a hint for the programmer that the implementation may shake
unsafe expressions around like any other ones (inlining, cse, ..), even though 
that is bound to lead to problems with the hidden side-effects. 

It is the programmer's responsibility to verify that none of these problems 
matter in the particular case of usage. Since many advances in compiler 
technology tend to invalidate those verifications, it is almost impossible to 
guarantee safety in such cases - about the best one can hope for is to identify
and document precisely which assumptions need to be made to "guarantee" 
safety. Unfortunately, this leaves it to users to figure out whether the assumptions
made by 'unsafe' authors (e.g., no inlining) are still valid at the point of use..

Btw, when talking about unsafety in that paper, John also happens to point 
out the other little problem with unsafePerformIO: it permits to break type 
safety (many a good spirit has stumbled over that "polymorphic references" 
problem in other functional languages).

> The precondition (proof obligation) of unsafePerformIO is that the order
> in which unsafePerformIOs are performed cannot affect the outcome of the
> program.  However, in this case, ordering doesn't matter: the only side
> effect is allocation of a new IORef, and IORefs are sufficiently opaque
> we don't care (or really know) about un-allocated IORefs while the only
> case we care about the now-allocated IORef is when we de-reference it.
> But, that forces the IORef, which executes the unsafePerformIO.  So,
> whenever we access the variable, it is allocated.  Therefore, the
> outcome of the program (regardless of the order of evaluation) is the
> same as if all such global variable declarations are executed before
> main begins executing.  So, the outcome is independent of the order of
> evaluation.
> 
> There you go: the precondition of unsafePerformIO is satisfied, so the
> usage is safe.

There you went.. into one of the many available traps in this mine-field:

You argue that unallocated IORefs don't matter as long as "the" IORef
is allocated before it is dereferenced. But that's just part of the problem
- what about inlining globalVar, creating multiple IORefs? Remember 
that, by using unsafePerformIO, you've given the compiler the license
to treat globalVar as an expression without side-effects, and for those
inlining is a common first step to enable further optimisations (last time
I checked, the language report didn't even guarantee the sharing on
which the globalVar trick depends)! Now there are multiple side-effects 
instead of a single one, and read-and write-accesses are spread out over 
the multiple copies of your IORef, none of which is likely to hold the 
value you'd like it to have..

Cheers,
Claus


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-02-02 Thread Patrik Jansson
On Fri, 31 Jan 2003, Jon Cast wrote:
> Otherwise, though, see my other post on this subject: unsafePerformIO
> will perform its action when the variable is accessed, so you can't
> write a Haskell program which differentiates between what any compiler
> actually does and running the variable allocations before main.

If you initialize this "global variable" with a value from a file which is
changed by main (or over time) then order does matter.

I claim unsafePerformIO is very often unsafe - the question is more like
if the "level of unsafety" is acceptable for a particular application.

/Patrik
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-01-31 Thread Jon Cast
Nick Name <[EMAIL PROTECTED]> wrote:
> On Fri, 31 Jan 2003 07:47:43 +
> Glynn Clements <[EMAIL PROTECTED]> wrote:

> >  The usual fudge is:

> > import IORef
> > import IOExts

> > globalVar :: IORef Int
> > globalVar = unsafePerformIO $ newIORef 0

> I see in the documentation of unsafePerformIO that no one makes
> guarantees about the order in wich unsafePerformIO arguments are
> performed (especially they don't have to be executed BEFORE main), so
> this trick should not be adviced as a general practice; it should be
> pointed out that it works in GHC but could not work in other
> compilers.

English nit: I think you mean ``could fail in other compilers'': it's
not really impossible for the trick to work in other compilers than
GHC.

Otherwise, though, see my other post on this subject: unsafePerformIO
will perform its action when the variable is accessed, so you can't
write a Haskell program which differentiates between what any compiler
actually does and running the variable allocations before main.

> Vincenzo

> --
> Fedeli alla linea, anche quando non c'š Quando l'imperatore š
> malato, quando muore,o š dubbioso, o š perplesso.  Fedeli alla linea
> la linea non c'š.  [CCCP]

Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-01-31 Thread Jon Cast
Ralf Hinze <[EMAIL PROTECTED]> wrote:
> > Pavel G. Zhbanov wrote:
> > > Is it even possible to make a "global variable" in Haskell?  If
> > > yes, how?

> > The usual fudge is:

> > import IORef
> > import IOExts
> >
> > globalVar :: IORef Int
> > globalVar = unsafePerformIO $ newIORef 0

> > However, beware of creating more than one "global variable" of the
> > same type. If you enable optimisation, common subexpression
> > elimination may result in both names referring to the same IORef.

> John Hughes wrote a nice pearl on the subject, see

>   http://www.math.chalmers.se/~rjmh/Globals.ps

This paper claims ``unsafePerformIO is unsafe''.  That's not actually
true in the sense meant; unsafePerformIO merely has safety
pre-conditions that the compiler can't check.  However, there's nothing
wrong with using it (or wrapping it) as long as the preconditions are
checked.  In fact, IMO, it's /better/ to use unsafePerformIO in a common
case like this, because exactly when the preconditions are satisfied
will be much better understood.

The precondition (proof obligation) of unsafePerformIO is that the order
in which unsafePerformIOs are performed cannot affect the outcome of the
program.  However, in this case, ordering doesn't matter: the only side
effect is allocation of a new IORef, and IORefs are sufficiently opaque
we don't care (or really know) about un-allocated IORefs while the only
case we care about the now-allocated IORef is when we de-reference it.
But, that forces the IORef, which executes the unsafePerformIO.  So,
whenever we access the variable, it is allocated.  Therefore, the
outcome of the program (regardless of the order of evaluation) is the
same as if all such global variable declarations are executed before
main begins executing.  So, the outcome is independent of the order of
evaluation.

There you go: the precondition of unsafePerformIO is satisfied, so the
usage is safe.

> Cheers, Ralf

Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-01-31 Thread Jon Cast
Glynn Clements <[EMAIL PROTECTED]> wrote:

> Pavel G. Zhbanov wrote:

> > Is it even possible to make a "global variable" in Haskell?  If yes,
> > how?

> The usual fudge is:

>   import IORef
>   import IOExts

>   globalVar :: IORef Int
>   globalVar = unsafePerformIO $ newIORef 0

> However, beware of creating more than one "global variable" of the
> same type. If you enable optimisation, common subexpression
> elimination may result in both names referring to the same IORef.

Is this true?  It seems wrong---I don't think expressions involving
unsafePerformIO should be combined, for precisely this reason.

Even if it is true, though, the following kludge should work:

> {-# NOINLINE mkGlobalVar #-}
> mkGlobalVar :: String -> alpha -> IORef alpha
> mkGlobalVar name value = usafePerformIO (newIORef value)

> globalVar = mkGlobalVar "globalVar" 0

This ensures that no common sub-expression elimination will be
performed.

> -- 
> Glynn Clements <[EMAIL PROTECTED]>

Jon Cast
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-01-31 Thread Nick Name
On Fri, 31 Jan 2003 07:47:43 +
Glynn Clements <[EMAIL PROTECTED]> wrote:

>  The usual fudge is:
> 
>   import IORef
>   import IOExts
>   
>   globalVar :: IORef Int
>   globalVar = unsafePerformIO $ newIORef 0

I see in the documentation of unsafePerformIO that no one makes
guarantees about the order in wich unsafePerformIO arguments are
performed (especially they don't have to be executed BEFORE main), so
this trick should not be adviced as a general practice; it should be
pointed out that it works in GHC but could not work in other compilers.

Vincenzo

-- 
Fedeli alla linea, anche quando non c'è Quando l'imperatore è
malato, quando muore,o è dubbioso, o è perplesso.  Fedeli alla linea
la linea non c'è.  [CCCP]

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-01-31 Thread Jorge Adriano

> Hello,
> Is it even possible to make a "global variable" in Haskell?
> If yes, how?
> Thanks.

(short answer, no time now...)
Look here:
http://www.haskell.org/pipermail/haskell-cafe/2002-January/002589.html

Hope it helps ;)

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-01-31 Thread Ralf Hinze
> Pavel G. Zhbanov wrote:
> > Is it even possible to make a "global variable" in Haskell?
> > If yes, how?
>
> The usual fudge is:
>
>   import IORef
>   import IOExts
>
>   globalVar :: IORef Int
>   globalVar = unsafePerformIO $ newIORef 0
>
> However, beware of creating more than one "global variable" of the
> same type. If you enable optimisation, common subexpression
> elimination may result in both names referring to the same IORef.

John Hughes wrote a nice pearl on the subject, see

http://www.math.chalmers.se/~rjmh/Globals.ps

Cheers, Ralf
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Global variables?

2003-01-30 Thread Glynn Clements

Pavel G. Zhbanov wrote:

> Is it even possible to make a "global variable" in Haskell? 
> If yes, how?

The usual fudge is:

import IORef
import IOExts

globalVar :: IORef Int
globalVar = unsafePerformIO $ newIORef 0

However, beware of creating more than one "global variable" of the
same type. If you enable optimisation, common subexpression
elimination may result in both names referring to the same IORef.

-- 
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



  1   2   >