[Haskell] ANN: global-variables-1.0

2011-10-12 Thread Jean-Marie Gaillourdet
Hi, I am pleased to announce the first public release of global-variables. A package providing a global namespace for IORefs, MVars, and TVars. Hackage URL: http://hackage.haskell.org/package/global-variables-1.0 Source: http://bitbucket.org/jmg/global-variables/ Description

[Haskell] Re: Global Variables and IO initializers

2004-11-24 Thread George Russell
t unexpected places. I think with the functions implemented by my proposal and without unsafePerformIO you can have all the guarantees, but still have global variables. In particular you can implement most of John Meacham's examples (the Random module)

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

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

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 ad

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. :) B

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

Re: [Haskell] Global Variables and IO initializers

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

Re: [Haskell] Global Variables and IO initializers

2004-11-23 Thread Lennart Augustsson
George Russell wrote: (3) It needs no extensions to the Haskell language, and only fairly standard hierarchical libraries like Data.IORef. It uses unsafePerformIO which is very much an extension to Haskell. :) -- Lennart ___ Haskell mailing list [

[Haskell] Global Variables and IO initializers

2004-11-23 Thread George Russell
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. http://www.haskell.org

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 ha

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

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

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 s

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 a

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 concre

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 t

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

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

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 to

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 t

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 sta

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

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 doe

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 > n

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

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

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 o

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 ref

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

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

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

2004-11-07 Thread Adrian Hey
On Sunday 07 Nov 2004 3:18 pm, Keean Schupke wrote: > The way I would do it would be to have an init function that > initialises an abstract data structure. Because the results of > the init function are stateless and not in a global variable it > does not matter if the user calls it twice. I don'

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 > > cre

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

2004-11-07 Thread Benjamin Franksen
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. > Maybe I'm missing something, but this doesn't seem very attractive to me > as a library writer (it m

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 a

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

2004-11-07 Thread Adrian Hey
7;t argue that :-) > Surely this is just one example, and not a very complex one. Nevertheless, > I am now less convinced that using global variables is in fact a good idea, > however convenient it may seem at first. I'm not at all convinced, having not seen or groked either the "

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

2004-11-06 Thread Benjamin Franksen
As an experiment, I just finished to change the Haskell Web Server with Plugins such that all global variables (unsafePerformIO-style) are replaced by standard argument passing. It wasn't difficult. The main work was (1) get it to compile with ghc-6.2.2 (2) understand how the code is orga

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

2004-11-06 Thread Adrian Hey
On Saturday 06 Nov 2004 1:07 pm, 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 ::

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

2004-11-06 Thread Adrian Hey
On Saturday 06 Nov 2004 12:27 pm, Keean Schupke wrote: > 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 - I don't agree. All top level bindings currently have the property that their value is indepe

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 u

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 transpar

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 S

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 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 be

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 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
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 Hask

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

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

2004-11-05 Thread Adrian Hey
On Friday 05 Nov 2004 7:03 pm, MR K P SCHUPKE wrote: > Could someone give an example of what these things are that need to be > initialised and that are safe. Here's a utility I've concocted for dealing with partial ordering constraints on initialisation of foreign libraries.. oneShot :: IO a ->

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

2004-11-05 Thread Benjamin Franksen
On Friday 05 November 2004 22:07, Keean Schupke wrote: > So what > we need is a way in the type system to tell the compiler the function > must have > a single unique definition... Something like: > > myRef :: Unique (IORef Int) > myRef = uniquePerformIO $ newIORef 0 > > and then have: > > runUniqu

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

2004-11-05 Thread Keean Schupke
Okay, now for the purposes of my understanding, let me explore this: 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 f

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

2004-11-05 Thread Jules Bean
On 5 Nov 2004, at 19:03, MR K P SCHUPKE wrote: You don't want stdin/stdout/stderr? Also these are only available in the IO monad... without breaking referential transparency by use of unsafePerformIO hack. I don't understand this still... how can it not break referntial transparancy. For example c

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

2004-11-05 Thread MR K P SCHUPKE
>Eiffel can dispense with global variables not least because objects contain >mutable state. And the methods cann access this state inside their object >without taking it as an argument. All of which you can do in Haskell (including the objects) with no additional extensions, s

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

2004-11-05 Thread MR K P SCHUPKE
>You don't want stdin/stdout/stderr? Also these are only available in the IO monad... >without breaking referential transparency >by use of unsafePerformIO hack. I don't understand this still... how can it not break referntial transparancy. For example consider if stdin were available outside th

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

2004-11-05 Thread Benjamin Franksen
erformIO-newIORef-style you still need to be in the IO Monad. Eiffel can dispense with global variables not least because objects contain mutable state. And the methods cann access this state inside their object without taking it as an argument. Ben __

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

2004-11-05 Thread Adrian Hey
On Friday 05 Nov 2004 1:23 pm, Marcin 'Qrczak' Kowalczyk wrote: > Keean Schupke <[EMAIL PROTECTED]> writes: > > Why do want global variables? > > Because they are more convenient than passing a state by hand. > They increase modularity by avoiding putting the f

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

2004-11-05 Thread MR K P SCHUPKE
>The point is to avoid threading global state to IO actions manually. >Programming langages exist in order to conveniently write programs in, >not only to admire their beauty. So if you are not interested in beauty, why not use the IO monad! If something is IO then declare it. You should not lie

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

2004-11-05 Thread Marcin 'Qrczak' Kowalczyk
Keean Schupke <[EMAIL PROTECTED]> writes: > Why do want global variables? Because they are more convenient than passing a state by hand. They increase modularity by avoiding putting the fact that a computation uses some global state in its type. You don't want stdin/stdou

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

2004-11-05 Thread Koen Claessen
Benjamin Franksen wrote: | > I think hiding the fact that certain objects are not | > constants but functions is a bad idea, because it will break | > sharing in a lazy implementation. | | You probably mean the case where the implicit parameter | is the only one. I don't see why that would "

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

2004-11-05 Thread Keean Schupke
dding stateful global variables is a bad thing and these are some reasons that spring to mind: Why do want global variables? They are like goto's the source of many programming errors... global constants maybe. To me global variables seems like a step backwards to languages like visual basic.

[Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread oleg
Koen Claessen wrote: > Imagine a commutative monad, CIO. Commutative monads have > the property that it does not matter in what order actions > are performed, they will have the same effect. In other > words, for all m1 :: CIO A, m2 :: CIO B, k :: A -> B -> CIO > C, it should hold that: > > do a

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

2004-11-04 Thread oleg
rted at Haskell Workshop 2004) is a far more advanced development and a practical realization of the similar idea. Incidentally, the above approach along with _many_ other approaches to global variables are surveyed at http://www.eecs.harvard.edu/~ccshan/prepose/prepose.pdf

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

2004-11-04 Thread Keith Wansbrough
> But I just realized that it will probably be necessary to declare (not > bind!) implicit parameters at the top level to avoid capture problems. Yep, this is the way it would have to go. --KW 8-) ___ Haskell mailing list [EMAIL PROTECTED] http://www.

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

2004-11-04 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: >On Thursday 04 November 2004 17:20, Ben Rudiak-Gould wrote: > >>This is one of the several ways in which the current implementation of >>implicit parameters is broken. Clearly they *should* belong to the >>module namespace, and if we modify the implementation so that they

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

2004-11-04 Thread Ben Rudiak-Gould
ntation as completely > | as if you had used unexported global variables. > >Are you suggesting to always add the context >(?MyModule.globals :: MyModule.Globals) to every function in >every module you implement? (My example concerned a module >that was previously implemented with

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

2004-11-04 Thread Adrian Hey
On Thursday 04 Nov 2004 5:54 pm, George Russell wrote: > However virtually everyone seems to have their own patent solution, > and we are no closer to agreement. FWIW, what Koen describes is exactly what I want (I think :-). So there's at least 2 votes for the "non-IO" monad approach, provided the

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

2004-11-04 Thread Benjamin Franksen
On Thursday 04 November 2004 18:54, George Russell wrote: > John Peterson wrote (snipped): > > The implementer of these functions has to guarantee that the > > actions do not destroy the commutativity of the CIO monad. > > Sorry, but several of my variable initialisation actions involve > things

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

2004-11-04 Thread Benjamin Franksen
On Thursday 04 November 2004 18:28, Koen Claessen wrote: > Ben Rudiak-Gould wrote: > | I think the OP is proposing the same thing, except > | without the ellipsis: i.e. we just write > | > | pretty :: Doc -> String > | > | and the compiler infers pretty :: (?width :: Int) => Doc > | -> S

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

2004-11-04 Thread Benjamin Franksen
On Thursday 04 November 2004 17:20, Ben Rudiak-Gould wrote: > Koen Claessen wrote: > >(1) Whenever a module uses an implicit parameter like that, > >it has to have a name that is different from all implicit > >parameters used by any other (future) module. (Yes, implicit > >paramers cannot be qu

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

2004-11-04 Thread George Russell
John Peterson wrote (snipped): > The implementer of these functions has to guarantee that the > actions do not destroy the commutativity of the CIO monad. Sorry, but several of my variable initialisation actions involve things like starting up child processes or rapid exits from the program if unsu

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

2004-11-04 Thread Koen Claessen
unexported global variables. Are you suggesting to always add the context (?MyModule.globals :: MyModule.Globals) to every function in every module you implement? (My example concerned a module that was previously implemented without global variables, and now was going to be implemented with global

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

2004-11-04 Thread Benjamin Franksen
quantified by a module name" (whatever that may mean exactly). > (2) Having the implicit parameter breaks the abstraction > barrier. I might want to re-implement a module that does not > make use of global variables, into one that uses a cache or > hash-table or whatever (t

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

2004-11-04 Thread Jon Fairbairn
On 2004-11-04 at 16:16+0100 Koen Claessen wrote: > Benjamin Franksen wrote: > > | 1) I strongly disagree with ideas to execute IO actions > | implicitly in whatever defined or undefined sequence > | before or during main for whatever reasons. > > I agree with the objections you make. Having fu

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

2004-11-04 Thread John Peterson
I've been meaning to get into this debate ... Koen proposes: Imagine a commutative monad, CIO. Commutative monads have the property that it does not matter in what order actions are performed, they will have the same effect. In other words, for all m1 :: CIO A, m2 :: CIO B, k :: A -> B ->

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

2004-11-04 Thread Ben Rudiak-Gould
is almost exactly what the so called > | 'implicit parameters' extension to Haskell is all about, > | and that using them as a replacement for global variables > | has already been proposed by John Hughes. > >The problem with John's approach is that it breaks >m

[Haskell] Re: Global Variables and IO initializers

2004-11-04 Thread Koen Claessen
all about, | and that using them as a replacement for global variables | has already been proposed by John Hughes. The problem with John's approach is that it breaks modularity. It does this in two ways: (1) Whenever a module uses an implicit parameter like that, it has to have a name that is

Re: [Haskell] Global Variables and IO initializers

2004-11-01 Thread Benjamin Franksen
Let me add a few thoughts on the global variables problem and the proposed solutions. 1) I strongly disagree with ideas to execute IO actions implicitly in whatever defined or undefined sequence before or during main for whatever reasons. If initialization actions are necessary, they should

RE: [Haskell] Global Variables and IO initializers: A proposal andsemantics

2004-10-18 Thread Erkok, Levent
>> I wondered if something like that could work, but I wasn't sure that >> mdo allowed recursion in its let-bindings... > >The mdo implementation in ghc does not actually... I think there's a misunderstanding there. let expressions inside an mdo can of course be recursive; both Hugs and ghc suppor

Re: [Haskell] Global Variables and IO initializers: A proposal andsemantics

2004-10-15 Thread John Meacham
On Fri, Oct 15, 2004 at 04:40:09PM -0700, Erkok, Levent wrote: > >> I wondered if something like that could work, but I wasn't sure that > >> mdo allowed recursion in its let-bindings... > > > >The mdo implementation in ghc does not actually... > > I think there's a misunderstanding there. let exp

Re: [Haskell] Global Variables and IO initializers: A proposal and semantics

2004-10-13 Thread Andy Moran
ng of global variables (which the unsafePerformIO technique does not). Cheers, Andy -- Andy Moran Ph. (503) 626 6616, x113 Galois Connections Inc. Fax. (503) 350 0833 12725 SW Millikan Way, Suite #290

Re: [Haskell] Global Variables and IO initializers: A proposal and semantics

2004-10-13 Thread Jules Bean
On 13 Oct 2004, at 00:04, Greg Buchholz wrote: John Meacham wrote: I have put some thought, some time ago, into the 'global initializers' problem in haskell but for various reasons never wrote up my conclusions. I'm not really qualified to answer, but does anyone think that this paper might ha

Re: [Haskell] Global Variables and IO initializers: A proposal and semantics

2004-10-13 Thread John Meacham
ich > >allocates the space in the bss for global_var, the fact we can access > >and work with such space from haskell, but have no way to allocate it > >is quite telling that there is something missing in the language. > > > > Yes, that's weird, isn't it? Yeah,

Re: [Haskell] Global Variables and IO initializers: A proposal and semantics

2004-10-12 Thread Jules Bean
On 12 Oct 2004, at 23:33, John Meacham wrote: and via the FFI just a foreign import "&global_var" :: Ptr Int note that we do not need any foregin code, just an object which allocates the space in the bss for global_var, the fact we can access and work with such space from haskell, but have no

Re: [Haskell] Global Variables and IO initializers: A proposal and semantics

2004-10-12 Thread Greg Buchholz
John Meacham wrote: > > I have put some thought, some time ago, into the 'global > initializers' problem in haskell but for various reasons never wrote > up my conclusions. I'm not really qualified to answer, but does anyone think that this paper might have a solution? http://www.eecs.

[Haskell] Global Variables and IO initializers: A proposal and semantics

2004-10-12 Thread John Meacham
d unsafely already and the world has not collapsed: via getting and setting strings in the evironment we can create global variables holding read/showable values. via writing and reading temporary files and via the FFI just a foreign import "&global_var" :: Ptr Int note

Re: [Haskell] "global variables" and code optimization

2004-09-10 Thread Jan-Willem Maessen - Sun Labs East
Keith Wansbrough wrote: ... [Bernd discusses his problems using unsafeperformIO to generate unique names, and Keith responds] Why not just thread (newLabelNr :: Int) through your code to the places that need it? If you do this with other things too, then put them in a record. This is a kind of "

Re: [Haskell] "global variables" and code optimization

2004-09-10 Thread Keith Wansbrough
> > The problem is, that with optimizations turned on (using ghc V6.2.1) the > label number is calulated only once, so each call to makeBlockName yields > the same value. I tried a) adding a dummy parameter to makeBlockName and b) > specifying an INLINE pragma to both getAndUpdateVar and makeBlock

[Haskell] "global variables" and code optimization

2004-09-10 Thread Holzmüller, Bernd
Hi all, in a compiler project I am using "global variables" of the form: gNewLabelNr :: IORef Int gNewLabelNr = unsafePerformIO $ newIORef 1 getAndUpdateVar var f = unsafePerformIO $ do oldVal <- readIORef var writeIORef var (f oldVal) return oldVal makeBlockName = &qu

Re: Global variables

2001-11-29 Thread Ashley Yakeley
At 2001-11-29 11:13, Ashley Yakeley wrote: >Lifted monads look something like this: > > data MyAction a = MkMyAction ((consts,vars) -> (vars,a)); > instance Monad MyAction where etc. Whoops, should be data MyAction a = MkMyAction ((consts,vars) -> IO (vars,a)); -- Ashley Yakeley

Re: Global variables

2001-11-29 Thread Ashley Yakeley
At 2001-11-29 05:31, Juan Ignacio García García wrote: >I am interested in using global variables (in GHC). In JVM-Bridge (nearly there!) I use lifted monads to store global constants, though variables are not hard either. This does mean an extra function needed to call IO functions, but in

Re: Global variables

2001-11-29 Thread C.Reinke
> Hello, I am interested in using global variables (in GHC). I need a > variable to store list of Integers to store temporary results. I > have been reading the module MVar, but I wonder if there is an > alternative way of doing it. I have already implemented my function > us

Re: Global variables

2001-11-29 Thread Alastair David Reid
> Hello, I am interested in using global variables (in GHC). I need a > variable to store list of Integers to store temporary results. I > have been reading the module MVar, but I wonder if there is an > alternative way of doing it. I have already implemented my function > us

Re: Global variables

2001-11-29 Thread Dmitry Astapov
JIGG> alternative way of doing it. I have already implemented my function JIGG> using an auxiliar argument where I put my lists of Integers. Will JIGG> the use of a global variable improve my function? There is no such thing as mutable variable (as in imperative languages) in Haskell (and m

Global variables

2001-11-29 Thread Juan Ignacio García García
Hello, I am interested in using global variables (in GHC). I need a variable to store list of Integers to store temporary results. I have been reading the module MVar, but I wonder if there is an alternative way of doing it. I have already implemented my function using an auxiliar argument