[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

[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

Re: Global variables

2007-02-01 Thread Yitzchak Gale
Hi Bulat, You wrote: there is common proposal that i support. example of its use: i :: IORef Int i - newIORef 1 with a semantics equivalent to current use of usafePerformIO+INLINE in GHC Are the details of this posted anywhere? Is there a ticket for this? I assume you mean that this will

Re: Global variables

2007-02-01 Thread David House
On 01/02/07, Bulat Ziganshin [EMAIL PROTECTED] wrote: there is common proposal that i support. example of its use: i :: IORef Int i - newIORef 1 with a semantics equivalent to current use of usafePerformIO+INLINE in GHC I think that's too safe-looking. Anything that translates to something

Re: Global variables

2007-02-01 Thread Philippa Cowderoy
On Thu, 1 Feb 2007, David House wrote: I think that's too safe-looking. Anything that translates to something involving unsafe* should be tagged with 'unsafe' somewhere as well. Also, as unsafe* is still compiler specific, I think a pragma is probably most appropriate: {-# GLOBAL-MUTVAR

Re: Global variables

2007-02-01 Thread Douglas Philips
On 2007 Feb 1, at 11:51 AM, David House indited: On 01/02/07, Bulat Ziganshin [EMAIL PROTECTED] wrote: there is common proposal that i support. example of its use: i :: IORef Int i - newIORef 1 with a semantics equivalent to current use of usafePerformIO +INLINE in GHC I think that's too

Re: Global variables

2007-02-01 Thread David House
(CCing the list as this is of general concern.) On 01/02/07, Yitzchak Gale [EMAIL PROTECTED] wrote: Why is this unsafe? What could go wrong? It could segfault due to the type safety properties that unsafePerformIO breaks: import System.IO.Unsafe import Data.IORef ref :: IORef [a] ref -

Re: Global variables

2007-02-01 Thread John Meacham
On Thu, Feb 01, 2007 at 04:51:39PM +, David House wrote: I think that's too safe-looking. Anything that translates to something involving unsafe* should be tagged with 'unsafe' somewhere as well. Also, as unsafe* is still compiler specific, I think a pragma is probably most appropriate:

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)

[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

[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

[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

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

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

[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

[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

[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 ...

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

[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

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

[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 ()

[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

[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,

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

2004-11-24 Thread Tomasz Zielonka
On Wed, Nov 24, 2004 at 08:53:47AM +0100, Lennart Augustsson wrote: Well, I don't. unsafePerformIO is an extension that is very much against the spirit of Haskell. Haskell with it does not have the properties I want. So I don't use it. :) I hope 'it' means unsafePerformIO, not Haskell :) I

[Haskell] Re: Global Variables and IO initializers

2004-11-24 Thread George Russell
Tomasz wrote: Without unsafePerformIO Haskell gives me many guarantees for free. With unsafePerformIO, they are no longer for free, I have to think, prove, etc. When I mistakenly give a pure function interface to an unpure function, it can affect my program in most unexpected places. I think

[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

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

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

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

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:

[Haskell] Re: Global Variables and IO initializers

2004-11-23 Thread George Russell
I wrote (snipped): 3) It needs no extensions to the Haskell language, and only fairly standard hierarchical libraries like Data.IORef. Lennart Augustsson wrote (snipped): It uses unsafePerformIO which is very much an extension to Haskell. :) Ben Rudiak-Gould wrote (snipped): I think by Haskell

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

2004-11-23 Thread Jules Bean
On 23 Nov 2004, at 11:53, George Russell wrote: I wrote (snipped): 3) It needs no extensions to the Haskell language, and only fairly standard hierarchical libraries like Data.IORef. Lennart Augustsson wrote (snipped): It uses unsafePerformIO which is very much an extension to Haskell. :) Ben

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

2004-11-23 Thread ajb
G'day all. Quoting George Russell [EMAIL PROTECTED]: No. I mean by the Haskell language what is described in the Haskell 98 Report. unsafePerformIO is not part of the language, it is a value defined by one of the standard hierarchical libraries. unsafePerformIO is part of the FFI addendum

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

2004-11-23 Thread Lennart Augustsson
[EMAIL PROTECTED] wrote: No. I mean by the Haskell language what is described in the Haskell 98 Report. unsafePerformIO is not part of the language, it is a value defined by one of the standard hierarchical libraries. unsafePerformIO is part of the FFI addendum to the H98 report. So I think

[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

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

[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

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

[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

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

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

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

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

2004-11-08 Thread Krasimir Angelov
--- 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 newRef :: a - ST s (Ref s a) -- replaces newIORef and

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

2004-11-08 Thread Keean Schupke
However, turning Haskell into O'Haskell seems like a far more radical suggestion than the (IMO) conservative language extension under discussion. So I don't expect it to happen anytime soon. Maybe if Haskell ever gets a better records/modules system things might look a bit different. But there

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

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

2004-11-08 Thread Keean Schupke
Krasimir Angelov wrote: Note that 2-rank type of runSTInit doesn't allow to execute regular IO actions. Even that (ST s a) allows actions like readRef and writeRef. This allows to initialise local references but doesn't allow to access other toplevel reverences since they are bound to RealWorld

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

2004-11-08 Thread Keean Schupke
Note that 2-rank type of runSTInit doesn't allow to execute regular IO actions. Even that (ST s a) allows actions like readRef and writeRef. This allows to initialise local references but doesn't allow to access other toplevel reverences since they are bound to RealWorld state. Thinking about

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

2004-11-08 Thread Krasimir Angelov
--- Keean Schupke [EMAIL PROTECTED] wrote: Note that 2-rank type of runSTInit doesn't allow to execute regular IO actions. Even that (ST s a) allows actions like readRef and writeRef. This allows to initialise local references but doesn't allow to access other toplevel reverences

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

2004-11-08 Thread Keean Schupke
Krasimir Angelov wrote: ered on top of ST and the stToIO is the lifting function. What does 'automatically be lifted' mean? Krasimir For example with the state monad you can define: instance (MonadState st m,MonadT t m) = MonadState st (t m) where update = up . update setState = up .

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

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.

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

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

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

2004-11-08 Thread Krasimir Angelov
As I know the ST monad doesn't provide getState/setState functions. In order to get this kind of overloading we need to put all functions that deal with references in type class: class MonadRef m r where readRef :: r a - m a writeRef :: a - r a - m () I guess that this is an overkill

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

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

2004-11-08 Thread Simon Peyton-Jones
| 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). Actually, I'd like to suggest that it move to Haskell-café. It's certainly an

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

2004-11-08 Thread Marcin 'Qrczak' Kowalczyk
Krasimir Angelov [EMAIL PROTECTED] writes: I guess that this is an overkill since we can just define IO as type IO a = ST RealWorld a 'instance MonadIO IO' would start to need some type system extensions. -- __( Marcin Kowalczyk \__/ [EMAIL PROTECTED] ^^

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

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 10:52 am, Keean Schupke wrote: Krasimir Angelov wrote: Note that 2-rank type of runSTInit doesn't allow to execute regular IO actions. Even that (ST s a) allows actions like readRef and writeRef. This allows to initialise local references but doesn't allow to access

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

2004-11-08 Thread Adrian Hey
On Monday 08 Nov 2004 12:23 pm, 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. Isn't an IORef just a handle for a

[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

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.

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

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

[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

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

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

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

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

[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:

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

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

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.

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

[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

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

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

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

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

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

2004-11-07 Thread Adrian Hey
On Sunday 07 Nov 2004 3:16 am, Benjamin Franksen wrote: Of course, the downside is that some of the functions (not many) now have one or two additional arguments. OTOH one could argue that this is in fact an advantage, as it makes all the dependencies crystal clear. I wouldn't argue that :-)

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

2004-11-07 Thread Keean Schupke
Adrian Hey wrote: I'm not at all convinced, having not seen or groked either the before or after code. Perhaps you could show how this would work with an even simpler example, the one that I posted concerning the use of oneShot to create a top level (I.E. exportable) userInit. AFAICS the only

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

2004-11-07 Thread Benjamin Franksen
On Sunday 07 November 2004 13:36, you wrote: AFAICS the only alternative to.. userInit - oneShot realInit is to export realInit, have users create their own userInit, and then pass that around as an argument to everything that might make use of userInit. Yes. For instance, user code

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

2004-11-07 Thread Benjamin Franksen
On Sunday 07 November 2004 16:18, you wrote: Adrian Hey wrote: I'm not at all convinced, having not seen or groked either the before or after code. Perhaps you could show how this would work with an even simpler example, the one that I posted concerning the use of oneShot to create a top

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

2004-11-07 Thread Adrian Hey
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

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

2004-11-07 Thread Tomasz Zielonka
On Fri, Nov 05, 2004 at 07:03:06PM +, MR K P SCHUPKE wrote: You don't want stdin/stdout/stderr? Also these are only available in the IO monad... No, they are available outside the IO monad, only you can't do anything useful with them. Well, you can show them! without breaking

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

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

2004-11-07 Thread Adrian Hey
On Monday 08 Nov 2004 1:55 am, Benjamin Franksen wrote: [moving to haskell-cafe] Sorry for the long post. [moving back to haskell] Hope you'll exuse me if I don't respond to everything here, just don't have the stamina. But maybe this.. Timber doesn't even have top-level IO actions, instead

[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.

[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

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

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

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

2004-11-06 Thread Vincenzo Ciancia
On Friday 05 November 2004 22:07, Keean Schupke wrote: myRef :: IORef Int myRef = unsafePerformIO $ newIORef 0 This should always return the same reference, whereas: myIORef :: IO (IORef Int) myIORef = newIORef 0 Will return a new reference every time. I agree it would seem that the

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

2004-11-06 Thread Keean Schupke
The problem I see here is how to proove the IO in safeIO is indeed safe. Perhaps UnsafeIO is a better name, as infact the IO is still unsafe - the compiler has to take special notice of this type and not inline its definitions. Your oneShot function has the same problem - if the compiler inlines

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

2004-11-06 Thread Keean Schupke
Vincenzo Ciancia wrote: Yes, but I guess everybody would like a solution where myRef1 = unsafePerformIO $ newIORef 0 myRef2 = unsafePerformIO $ newIORef 0 are different variables. Also, it's not true that it's perfectly safe, I don't understant this - they would be different variables with

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

2004-11-06 Thread David Sabel
Inling isn't the only optimization, which can lead to a wrong behavior, let floating out and common subexpression elimination can also change the behavior of programs using unsafePerformIO. Our research group has developed the calculus FUNDIO as a semantic basis: It's a non-deterministic

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

2004-11-06 Thread Keean Schupke
Just been reading arround. According to ghc docs, the noinline pragma is in the Haskell98 report. On that basis what is wrong with using the following to initialise these top-level constants? {-# NOINLINE newref #-} newref :: IORef Int newref = unsafePerformIO $ newIORef 0 Keean.

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

2004-11-06 Thread Keean Schupke
I hope this is not a stupid idea - but why not contribute the changes as patches back to the main GHC development? Keean. David Sabel wrote: Inling isn't the only optimization, which can lead to a wrong behavior, let floating out and common subexpression elimination can also change the

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

2004-11-06 Thread Jules Bean
On 6 Nov 2004, at 13:07, Keean Schupke wrote: Just been reading arround. According to ghc docs, the noinline pragma is in the Haskell98 report. On that basis what is wrong with using the following to initialise these top-level constants? {-# NOINLINE newref #-} newref :: IORef Int newref

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

2004-11-06 Thread David Sabel
The main reason is: Nobody asks for it. I conjecture, a problem is: if you use FUNDIO as a semantics for Haskell, you have to give up referential transparency in the strong sense. FUNDIO-programs are only referential transparent with respect to the defined contextual equivalence. David Keean

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

2004-11-06 Thread Keean Schupke
David Sabel wrote: The main reason is: Nobody asks for it. Actually I think Simon Marlow has talked in the past about wanting to make GHC only do safe optimisations on unsafePerformIO. I conjecture, a problem is: if you use FUNDIO as a semantics for Haskell, you have to give up referential

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

2004-11-06 Thread David Sabel
Keean Schupke wrote: David Sabel wrote: The main reason is: Nobody asks for it. Actually I think Simon Marlow has talked in the past about wanting to make GHC only do safe optimisations on unsafePerformIO. I conjecture, a problem is: if you use FUNDIO as a semantics for Haskell, you have to give

  1   2   >