[Haskell-cafe] 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:


'Data.Global' provides a global namespace of 'IORef's, 'MVar's and
'TVar's. This namespace may be accessed in pure code. Yet reading and
writing to those 'IORef's, 'MVar's and 'TVar's happens still in their
respective monads.
  
'Data.Global' is designed to meet the following use cases:

 * Simplify the declaration of top-level mutable variables, by
   avoiding any pragmas as well as 'unsafePerformIO'.
 
 * Avoid having to pass references explicitly throughout the program
   in order to let distant parts communicate.
 
 * Enable a communication by convention scheme, where e.g. different
   libraries may communicate without code dependencies.
 
 * Simplify the configuration problem - at least for code in the
   IO monad.

Note, that this library does not encourage sloppy software design by
re-introducing all bad effects of global variables. Nevertheless,
sometimes global variables are a suitable solution to a problem. In
that case Data.Global simplifies and extends their handling
significantly.

Example:
-

 module Main where
 
 import Data.Global
 import Data.IORef

 counter :: IORef Int
 counter = declareIORef Main.counter 0

 main :: IO ()
 main = do
   counter `writeIORef` 1
   readIORef counter = print 

Note absence of pragmas and of unsafePerformIO!

Future Plans:
--

* Support discovery/traversal of existing variables

* TemplateHaskell support to generate private and unique variable names.

Regards,
  Jean



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


Re: [Haskell-cafe] [Haskell] ANN: global-variables-1.0

2011-10-12 Thread Henning Thielemann


On Wed, 12 Oct 2011, Jean-Marie Gaillourdet wrote:


* Simplify the configuration problem - at least for code in the
  IO monad.

Note, that this library does not encourage sloppy software design by
re-introducing all bad effects of global variables.


But isn't this kind of solution for the configuration problem an example 
for sloppy software design? If a global configuration would be passed 
around, then you could easily use the program functions with different 
configurations simultaneously. In contrast to that, with the global IORef 
this is not possible.


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


[Haskell-cafe] Fwd: [Haskell] ANN: global-variables-1.0

2011-10-12 Thread Jean-Marie Gaillourdet

Begin forwarded message:

 From: Jean-Marie Gaillourdet j...@gaillourdet.net
 Subject: Re: [Haskell] ANN: global-variables-1.0
 Date: 12. Oktober 2011 20:27:16 MESZ
 To: Henning Thielemann lemm...@henning-thielemann.de
 
 Hi,
 
 On 12.10.2011, at 20:20, Henning Thielemann wrote:
 
 
 On Wed, 12 Oct 2011, Jean-Marie Gaillourdet wrote:
 
 * Simplify the configuration problem - at least for code in the
 IO monad.
 
 Note, that this library does not encourage sloppy software design by
 re-introducing all bad effects of global variables.
 
 But isn't this kind of solution for the configuration problem an example 
 for sloppy software design? If a global configuration would be passed 
 around, then you could easily use the program functions with different 
 configurations simultaneously. In contrast to that, with the global IORef 
 this is not possible.
 
 Well, the question whether using a  carefully documented set of global 
 configuration variables which, e.g. only affect the verbosity of logging, is 
 sloppy or not is a question I don't want to answer. But I am convinced there 
 are good reasons to use global-variables *sometimes*. If only for a temporary 
 debugging aid. In any case, an additional possibility to express design 
 intents never hurts. 
 
 Note, that I wrote simplify not solve the configuration problem  :-)
 
 Cheers,
   Jean


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


Re: [Haskell-cafe] global variables for foreign C functions

2008-12-02 Thread Andrea Rossato
On Mon, Dec 01, 2008 at 05:30:33PM -0800, Judah Jacobson wrote:
 You can limit the size of that stub file using:
 
 foreign import ccall progname progname :: Ptr (Ptr CChar)
 
 which lets you access that global variable and write the
 getters/setters in Haskell rather than C.

this solves my problems quite nicely indeed, but I still cannot figure
how to write a setter function that actually works.

That is to say, after:
newCString new_name = poke progname

this:
putStrLn . show = peekCString = peek progname

would return new_name, but the library, which is using progname to
produce some debugging messages, doesn't seem to get it correctly: the
original bits are gone, but instead of new_name I get some garbage.

Thanks to everyone for the interesting and useful hints.

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


[Haskell-cafe] global variables for foreign C functions

2008-12-01 Thread Andrea Rossato
Hello,

I'm writing the bindings to a C library which uses, in some functions,
global variables.

To make it clearer, those functions need a global variable to be
defined. A C program using my_function, one of the library functions,
would look like:

char progname[] = a_program_name;

int
main( int argc, char *argv[] )
{
param p;
my_function ( p )
etc.

I've been searching the ML, the wiki, the net, etc. without finding
some examples on how such things are dealt with in Haskell - is it
possible, BTW?

If I import those functions without defining the global variable I get
a linker error:

/usr/lib/mylib.a(cfile.o): In function `my_function':
cfile.c:(.text+0x510): undefined reference to `progname'

I hope the issue is clear. Any help would be greatly appreciated.

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


Re: [Haskell-cafe] global variables for foreign C functions

2008-12-01 Thread Evan Laforge
On Mon, Dec 1, 2008 at 4:39 PM, Andrea Rossato
[EMAIL PROTECTED] wrote:
 Hello,

 I'm writing the bindings to a C library which uses, in some functions,
 global variables.

 To make it clearer, those functions need a global variable to be
 defined. A C program using my_function, one of the library functions,
 would look like:

I don't think you can use the FFI to declare symbols for C.  One
not-so-pretty but effective way to do it is create a stub.c with the
variables declared along with setting functions, then bind those
functions like any other.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] global variables for foreign C functions

2008-12-01 Thread Judah Jacobson
On Mon, Dec 1, 2008 at 4:55 PM, Evan Laforge [EMAIL PROTECTED] wrote:
 On Mon, Dec 1, 2008 at 4:39 PM, Andrea Rossato
 [EMAIL PROTECTED] wrote:
 Hello,

 I'm writing the bindings to a C library which uses, in some functions,
 global variables.

 To make it clearer, those functions need a global variable to be
 defined. A C program using my_function, one of the library functions,
 would look like:

 I don't think you can use the FFI to declare symbols for C.  One
 not-so-pretty but effective way to do it is create a stub.c with the
 variables declared along with setting functions, then bind those
 functions like any other.

You can limit the size of that stub file using:

foreign import ccall progname progname :: Ptr (Ptr CChar)

which lets you access that global variable and write the
getters/setters in Haskell rather than C.

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


Re: [Haskell-cafe] global variables for foreign C functions

2008-12-01 Thread John Meacham
On Mon, Dec 01, 2008 at 04:55:14PM -0800, Evan Laforge wrote:
 On Mon, Dec 1, 2008 at 4:39 PM, Andrea Rossato
 [EMAIL PROTECTED] wrote:
  Hello,
 
  I'm writing the bindings to a C library which uses, in some functions,
  global variables.
 
  To make it clearer, those functions need a global variable to be
  defined. A C program using my_function, one of the library functions,
  would look like:
 
 I don't think you can use the FFI to declare symbols for C.  One
 not-so-pretty but effective way to do it is create a stub.c with the
 variables declared along with setting functions, then bind those
 functions like any other.

Yes, it is unfortunate this is the case. my ForeignData proposal was
meant to address this:

http://hackage.haskell.org/trac/haskell-prime/wiki/ForeignData

I am not entirely sure about the proposal as described, but I think
something like it should be done.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] global variables for foreign C functions

2008-12-01 Thread John Van Enk
I would find a ForeignData extension incredibly helpful. This will be
crucial if Haskell ever wants to target out of the ordinary systems.

/jve


On Mon, Dec 1, 2008 at 8:38 PM, John Meacham [EMAIL PROTECTED] wrote:

 On Mon, Dec 01, 2008 at 04:55:14PM -0800, Evan Laforge wrote:
  On Mon, Dec 1, 2008 at 4:39 PM, Andrea Rossato
  [EMAIL PROTECTED] wrote:
   Hello,
  
   I'm writing the bindings to a C library which uses, in some functions,
   global variables.
  
   To make it clearer, those functions need a global variable to be
   defined. A C program using my_function, one of the library functions,
   would look like:
 
  I don't think you can use the FFI to declare symbols for C.  One
  not-so-pretty but effective way to do it is create a stub.c with the
  variables declared along with setting functions, then bind those
  functions like any other.

 Yes, it is unfortunate this is the case. my ForeignData proposal was
 meant to address this:

 http://hackage.haskell.org/trac/haskell-prime/wiki/ForeignData

 I am not entirely sure about the proposal as described, but I think
 something like it should be done.

John

 --
 John Meacham - ⑆repetae.net⑆john⑈
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] global variables

2007-05-24 Thread Adrian Hey

Taral wrote:

On 5/23/07, Adrian Hey [EMAIL PROTECTED] wrote:

I think I still prefer..

var :: IORef Int
var - newIORef 3


So do I. For one very good reason: this syntax could be defined as a
constructor syntax and guaranteed to run before main.


Or even at compile time (which is why I think it's reasonable to
regard operations like newIORef etc.. as not really being IO
operations at all). But anyway, the constraints of the ACIO monad
allow creation to occur at any time before the first attempt to
read or write the IORef.


The other syntaxes proposed don't strike me as sufficiently rigorous.


Me neither. It's always been a great source of puzzlement to me why this
very simple and IMO conservative proposal should be so controversial.
Unless someone can point out some severe semantic difficulty or suggest
something better it seems like a no-brainer to me.

Regards
--
Adrian Hey



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


Re: [Haskell-cafe] global variables

2007-05-24 Thread Taral

On 5/24/07, Adrian Hey [EMAIL PROTECTED] wrote:

Taral wrote:
 The other syntaxes proposed don't strike me as sufficiently rigorous.

Me neither. It's always been a great source of puzzlement to me why this
very simple and IMO conservative proposal should be so controversial.
Unless someone can point out some severe semantic difficulty or suggest
something better it seems like a no-brainer to me.


I think it lacks implementation. I don't have time, or I'd look into
hacking this into GHC.

--
Taral [EMAIL PROTECTED]
Please let me know if there's any further trouble I can give you.
   -- Unknown
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] global variables

2007-05-24 Thread Simon Marlow

Adrian Hey wrote:

Taral wrote:

On 5/23/07, Adrian Hey [EMAIL PROTECTED] wrote:

I think I still prefer..

var :: IORef Int
var - newIORef 3


So do I. For one very good reason: this syntax could be defined as a
constructor syntax and guaranteed to run before main.


Or even at compile time (which is why I think it's reasonable to
regard operations like newIORef etc.. as not really being IO
operations at all). But anyway, the constraints of the ACIO monad
allow creation to occur at any time before the first attempt to
read or write the IORef.


The other syntaxes proposed don't strike me as sufficiently rigorous.


Me neither. It's always been a great source of puzzlement to me why this
very simple and IMO conservative proposal should be so controversial.
Unless someone can point out some severe semantic difficulty or suggest
something better it seems like a no-brainer to me.


This is going to be highly subjective, but to me it still doesn't feel like it 
falls under the bar for implementation cost given its usefulness.


The new syntax requires additions all the way through the front end of the 
compiler: parser, abstract syntax, renamer, type checker, desugarer, for 
something that is rarely used.  It's a first-class language construct (a new 
top-level binding form, no less), and it has to pay its way.  Also you want to 
add the ACIO monad as a built-in to the language.


Not that my gut feeling should in any way be considered the final word on the 
subject, but I thought I should say something about why we're not running to 
implement this right now.  To me it seems like we should let it simmer some more.


Cheers,
Simon

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


Re: [Haskell-cafe] global variables

2007-05-24 Thread David House

On 24/05/07, Adrian Hey [EMAIL PROTECTED] wrote:

Or even at compile time (which is why I think it's reasonable to
regard operations like newIORef etc.. as not really being IO
operations at all).


You can allocate heap space at compile time? (Well, I guess you could,
but that wouldn't still be usable at run time...) I imagine newIORef
as mallocing() some room, then returning a pointer to that memory.
That doesn't seem like something that could be done at compile time.

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


Re: [Haskell-cafe] global variables

2007-05-24 Thread Adrian Hey

David House wrote:

On 24/05/07, Adrian Hey [EMAIL PROTECTED] wrote:

Or even at compile time (which is why I think it's reasonable to
regard operations like newIORef etc.. as not really being IO
operations at all).


You can allocate heap space at compile time? (Well, I guess you could,
but that wouldn't still be usable at run time...) I imagine newIORef
as mallocing() some room, then returning a pointer to that memory.
That doesn't seem like something that could be done at compile time.


There seems to be quite a few implicit (and incorrect) assumptions in
your argument, which is fallacious IMO. The logic of your argument
would imply that *no* top level expression can be evaluated at compile
time. This might be the case with ghc, though I doubt it (and even if
it was this would just be a ghc problem).

BTW, the Haskell standard says nothing about any kind of heap, let
alone a C style malloc.

Regards
--
Adrian Hey




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


Re: [Haskell-cafe] global variables

2007-05-24 Thread Aaron Denney
On 2007-05-24, David House wrote:
 On 24/05/07, Adrian Hey [EMAIL PROTECTED] wrote:
 Or even at compile time (which is why I think it's reasonable to
 regard operations like newIORef etc.. as not really being IO
 operations at all).

 You can allocate heap space at compile time? (Well, I guess you could,
 but that wouldn't still be usable at run time...) I imagine newIORef
 as mallocing() some room, then returning a pointer to that memory.
 That doesn't seem like something that could be done at compile time.

You can allocate bss or data space at compile time for the executable
you are compiling.  (Well, if you read compile as compile and link.
It's a bit fuzzy.)

-- 
Aaron Denney
--

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


Re: [Haskell-cafe] global variables

2007-05-24 Thread Adrian Hey

Aaron Denney wrote:

On 2007-05-24, David House wrote:

On 24/05/07, Adrian Hey [EMAIL PROTECTED] wrote:

Or even at compile time (which is why I think it's reasonable to
regard operations like newIORef etc.. as not really being IO
operations at all).

You can allocate heap space at compile time? (Well, I guess you could,
but that wouldn't still be usable at run time...) I imagine newIORef
as mallocing() some room, then returning a pointer to that memory.
That doesn't seem like something that could be done at compile time.


You can allocate bss or data space at compile time for the executable
you are compiling.  (Well, if you read compile as compile and link.
It's a bit fuzzy.)


Well we don't need to get too bogged down with the details of how
any particular compiler/linker/rts might work. The point being that
with any..

myIORef - newIORef initialExpression

whether or not it's at the top level, the only information needed
to create the IORef is the initialExpression, and if it's at the
top level then this is available at compile time (it doesn't even
have to be evaluated at compile time in order to create the IORef).

But it doesn't require any information from, nor should it have
any effect on, the outside world that an executing program is
interacting with. It is conceivable that for some newIORef
implementations this would not be true, but in that case it's
difficult to see how such implementations could safely put
their newIORef in the ACIO monad anyway.

Regards
--
Adrian Hey





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


Re: [Haskell-cafe] global variables

2007-05-23 Thread Adrian Hey

Isaac Dupree wrote:


var :: IORef Int
var = {-# EVALUATE_THIS_TEXT_ONLY_ONCE #-} (unsafePerformIO (newIORef 3))


I think I still prefer..

var :: IORef Int
var - newIORef 3

or, more likely..

var :: IORef Int
var - ACIO.newIORef 3

The - syntax should make the intended semantics clear and unambiguous,
so it becomes the problem of individual implementors (not standards
writers) to make sure that whatever optimisations or transformations
that may be appropriate for their implementation preserve those
semantics. (IOW there's no need to worry about what a pragma really
means in operational terms, AFAICS).

The ACIO monad also restricts what programmers may use on the rhs of
the -.

But if you want a good name for the pragma how about this..


var :: IORef Int
var = {-# - #-} (unsafePerformIO (newIORef 3))


:-)

Regards
--
Adrian Hey








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


Re: [Haskell-cafe] global variables

2007-05-23 Thread Taral

On 5/23/07, Adrian Hey [EMAIL PROTECTED] wrote:

I think I still prefer..

var :: IORef Int
var - newIORef 3


So do I. For one very good reason: this syntax could be defined as a
constructor syntax and guaranteed to run before main.

The other syntaxes proposed don't strike me as sufficiently rigorous.

--
Taral [EMAIL PROTECTED]
Please let me know if there's any further trouble I can give you.
   -- Unknown
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] global variables

2007-05-22 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Isaac Dupree wrote:
 Maybe some sort of ISOLATE, DON'T_OPTIMIZE (but CAF), or
 USED_AS_GLOBAL_VARIABLE pragma instead of just the insufficient NOINLINE
 would be a good first step... if successful it would remove the
 occasional need for -fno-cse for a whole module in GHC, at least.

ISOLATE, DON'T_OPTIMIZE are actually bad names for the whole effect,
which requires persistent CAF semantics.  An implementation that doesn't
make top-level definitions be CAFs, or even one that is willing to
garbage-collect them when memory is tight such that they need
recalculation later, would need a special case for global variables to
make them work.

i.e. I'm not sure if there exists a reasonable pragma while the code
still uses unsafePerformIO.

Hmm

How about

so,
{-# NOINLINE var #-}
var :: IORef Int
var = unsafePerformIO (newIORef 3)

- --

var :: IORef Int
var = {-# EVALUATE_THIS_TEXT_ONLY_ONCE #-} (unsafePerformIO (newIORef 3))

to capture the desired semantics: text-based uniqueness, no duplication,
no sharing of the IORefs (sharing the pure contents is fine), and no
need to actually evaluate it any times at all. {-#
EVALUATE_THIS_TEXT_ONLY_ONCE #-} is syntactically like a (special)
function.  Clearly it is an impossible demand for polymorphic things, so
the compiler could complain (at least a warning) if the (var :: IORef
Int) line was left off, for example. I guess it would also complain
about non-type(class) argument dependencies too such as (f x =
(unsafePerformIO (newIORef (x::Int))) )...

Food for thought :-)


Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGU02YHgcxvIWYTTURAoCaAKCkDH7Pd7JbNt0TmNig9j7ujiUV9ACZAevI
QOjdmMbrPfVrKBafZshCh7c=
=9/5v
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] global variables

2007-05-21 Thread Simon Peyton-Jones

| I see no need two answer this again I believe I have already made my
| views perfectly clear already and provided ample evidence to justify
| them. Surely I don't need to do it again?

Is there a Wiki page about this somewhere?  Often email gets into a loop 
because not everyone reads everything on Haskell Cafe. (There's just too much 
of it.)  When that happens, a good thing do to is to summarise the various 
positions on a Wiki page, so the debate can progress by refining text rather 
than by repeating it.  There is the additional advantage that someone coming 
along later can still make sense of the debate.

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


Re: [Haskell-cafe] global variables

2007-05-21 Thread Arthur van Leeuwen


On 21-mei-2007, at 9:31, Simon Peyton-Jones wrote:



| I see no need two answer this again I believe I have already made my
| views perfectly clear already and provided ample evidence to justify
| them. Surely I don't need to do it again?

Is there a Wiki page about this somewhere?  Often email gets into a  
loop because not everyone reads everything on Haskell Cafe.  
(There's just too much of it.)  When that happens, a good thing do  
to is to summarise the various positions on a Wiki page, so the  
debate can progress by refining text rather than by repeating it.   
There is the additional advantage that someone coming along later  
can still make sense of the debate.


As I am sure Adrian would tell you were he awake:

http://www.haskell.org/haskellwiki/Top_level_mutable_state

With regards, Arthur van Leeuwen

--

  /\/ |   [EMAIL PROTECTED]   | Work like you don't need  
the money
/__\  /  | A friend is someone with whom | Love like you have never  
been hurt
/\/__ | you can dare to be yourself   | Dance like there's nobody  
watching




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


Re: [Haskell-cafe] global variables

2007-05-20 Thread Adrian Hey

Jules Bean wrote:

I've pretty much convinced it's wrong. There should be one and only
one main from which all subsequent IO activity derives. But creating
internal state in the form of mutable data structures is not an IO
activity. It just so happens that at the moment the only way to do this
is newIORef :: a - IO(IORef a), but this need not be so (readIORef and
writeIORef are IO activities, but newIORef isn't).



I find this point rather slippery. 'newIORef' is a unique-name-provider, 
but 'unique over what'? When a module is imported twice, should it not 
create new unique names?


No, it's just binding a name to a value, same as any other binding.
The difference is unlike normal top level bindings, that name is not
equal to any other expression. It just is, if you get what I mean
(I'm sure you do). That's why the proposed syntax borrows the - from
do expressions.


If it's necessary that there is only one libWhateverState to preserve
safety properties (because the state must be kept in sync with what's
really being done to the world, of which there is also only one) then
what's the point of making it a parameter (the lib is not truly
parameterisable by that state).


A slightly irrational point of concern in my mind is that by encouraging 
this practice, we encourage lazy library design.


Yes, this is slightly irrational :-)


A large proportion of
libraries in fact *can* be written as reentrant in this sense, and
truly are parameterisable by their state.


I can't help being sceptical about this. AFAICS it doesn't matter how
many explicit state handles you tack on to the left of the
- IO Whatever, the fact that the whole lot ends in - IO Whatever
means there's almost certainly some state left unaccounted for and
unparameterised (calls the OS are missing an OS state handle for
example).

Also, I don't really understand what you mean by reentrant in this
context. Are you talking about thread safety? (I guess not) Are you
implying that APIs of IO libs that mutate Haskell global state are
some how different from other IO APIs which mutate other global state
(such as OS state or world state)? Are they deficient in some way?
If so, how can you tell the difference?

Regards
--
Adrian Hey







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


Re: [Haskell-cafe] global variables

2007-05-20 Thread Jules Bean

Adrian Hey wrote:

Jules Bean wrote:

I've pretty much convinced it's wrong. There should be one and only
one main from which all subsequent IO activity derives. But creating
internal state in the form of mutable data structures is not an IO
activity. It just so happens that at the moment the only way to do this
is newIORef :: a - IO(IORef a), but this need not be so (readIORef and
writeIORef are IO activities, but newIORef isn't).



I find this point rather slippery. 'newIORef' is a 
unique-name-provider, but 'unique over what'? When a module is 
imported twice, should it not create new unique names?


No, it's just binding a name to a value, same as any other binding.
The difference is unlike normal top level bindings, that name is not
equal to any other expression. It just is, if you get what I mean
(I'm sure you do). That's why the proposed syntax borrows the - from
do expressions.



That's not my point. newIORef creates unique names (references). The 
whole job of newIORef is to create unique names; unique names which 
refer to little tiny bits of state parcelled up somewhere in that 
mysterious IO monad. It is the scope of this uniqueness I'm talking 
about: do libraries need these unique names to be unique over each 
importer, over each thread, over each subprocess: consider a haskell 
application server or a haskell OS... what is the correct domain of 
uniqueness?




A large proportion of
libraries in fact *can* be written as reentrant in this sense, and
truly are parameterisable by their state.


I can't help being sceptical about this. AFAICS it doesn't matter how
many explicit state handles you tack on to the left of the
- IO Whatever, the fact that the whole lot ends in - IO Whatever
means there's almost certainly some state left unaccounted for and
unparameterised (calls the OS are missing an OS state handle for
example).

Also, I don't really understand what you mean by reentrant in this
context. Are you talking about thread safety? (I guess not) Are you
implying that APIs of IO libs that mutate Haskell global state are
some how different from other IO APIs which mutate other global state
(such as OS state or world state)? Are they deficient in some way?
If so, how can you tell the difference?



'reentrant' is not the right word, although it's a related notion. I was 
talking about libraries which can safely be initialised more than once, 
for multiple clients, and they keep around 'separate' state for each 
client/each time they are initialised. This kind of design is often a 
precondition for being thread-safe; and it's often plain good design, 
unless some external 'real world' uniqueness makes it impossible.


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


Re: [Haskell-cafe] global variables

2007-05-20 Thread Adrian Hey

[cc'ing HPrime]

Isaac Dupree wrote:

The unsafePerformIO hack being used is not very satisfactory given how
many optimizations make it difficult to use safely in practice.  This
hack is also used many places.  I would be happier if that situation
were not true, and I suspect there's something like a consensus on
_that_. (maybe not as strong as _needs_ a solution in the short-to-mid
term future)


Considering the value that the Haskell community normally places on
sound semantics, reliance on such an appalling hack seems pretty bad to
me. If a solution doesn't find it's way into H' then how many more years
is it going to be with us? It's just embarrassing :-)

Also, I don't know if the OP was a noob, but telling people (especially
noobs) that if they can't figure out how to solve a problem without
using a global variable then that must be down to inexperience and
general cluelessness on their part just seems wrong to me. It simply
isn't true.

(Anyone who disagrees with this should feel free to submit the patches
needed to fix up the base package :-)

Regards
--
Adrian Hey

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


Re: [Haskell-cafe] global variables

2007-05-20 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Adrian Hey wrote:
 [cc'ing HPrime]
 
 Isaac Dupree wrote:
 The unsafePerformIO hack being used is not very satisfactory given how
 many optimizations make it difficult to use safely in practice.  This
 hack is also used many places.  I would be happier if that situation
 were not true, and I suspect there's something like a consensus on
 _that_. (maybe not as strong as _needs_ a solution in the short-to-mid
 term future)
 
 Considering the value that the Haskell community normally places on
 sound semantics, reliance on such an appalling hack seems pretty bad to
 me. If a solution doesn't find it's way into H' then how many more years
 is it going to be with us? It's just embarrassing :-)

Yes, also it places value on REALLY EXTREMELY (excessively?) SOUND
semantics, and on the modularity of the language even more than the
modularity of its uses (or something like that :-)

Maybe some sort of ISOLATE, DON'T_OPTIMIZE (but CAF), or
USED_AS_GLOBAL_VARIABLE pragma instead of just the insufficient NOINLINE
would be a good first step... if successful it would remove the
occasional need for -fno-cse for a whole module in GHC, at least.

Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGUF4yHgcxvIWYTTURAvqWAJ46eFRt5LK1lUwqr2BmHVSrHljxzwCfYGJB
x5ivAFEw5vYKbxTPIg+PrIU=
=0xVK
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] global variables

2007-05-20 Thread Adrian Hey

Isaac Dupree wrote:

Maybe some sort of ISOLATE, DON'T_OPTIMIZE (but CAF), or
USED_AS_GLOBAL_VARIABLE pragma instead of just the insufficient NOINLINE
would be a good first step... if successful it would remove the
occasional need for -fno-cse for a whole module in GHC, at least.


I have a hard time trying to understand why anyone would prefer
this to the simple and clear - syntax that's been proposed. As
for the ACIO monad itself, this is utterly trivial and requires
no language change. It's just a library.

Maybe the first pragma you propose might have other uses to control
optimisations, so I'm not totally anti this. But generally I
dislike pragmas (I always find myself wondering what's wrong
with the language design that makes the pragma necessary).

So pragmas that influence optimisation are something I can
live with. But using pragmas to influence *semantics* really
is an evil practice IMO and is something that should be
discouraged, not made an unavoidable necessity.

But yes, if this problem isn't going to be properly addressed
then at the very least the -fno-cse flag or something similar
needs standardising (NOINLINE already is I think). Or we port
all existing unsafePerfomIO hacked code to use Johm Meachams
variant of the hack (uses types to ensure the compiler doesn't
see common sub-expressions).

Regards
--
Adrian Hey



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


Re: [Haskell-cafe] global variables

2007-05-20 Thread Albert Y. C. Lai

Adrian Hey wrote:

Also, I don't know if the OP was a noob, but telling people (especially
noobs) that if they can't figure out how to solve a problem without
using a global variable then that must be down to inexperience and
general cluelessness on their part just seems wrong to me. It simply
isn't true.


Then what is right and what is true?

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


Re: [Haskell-cafe] global variables

2007-05-20 Thread Adrian Hey

Jules Bean wrote:
That's not my point. newIORef creates unique names (references). The 
whole job of newIORef is to create unique names; unique names which 
refer to little tiny bits of state parcelled up somewhere in that 
mysterious IO monad. It is the scope of this uniqueness I'm talking 
about: do libraries need these unique names to be unique over each 
importer, over each thread, over each subprocess: consider a haskell 
application server or a haskell OS... what is the correct domain of 
uniqueness?


The scoping rules are exactly the same as for any other top level
identifier, whether or not exported or imported. There's no reason why
an importing module should know or care that one or more of the
identifiers it's importing is the result of a - binding.

Should every module that imports the prelude get a different stdout?
(they currently don't of course)

'reentrant' is not the right word, although it's a related notion. I was 
talking about libraries which can safely be initialised more than once, 
for multiple clients, and they keep around 'separate' state for each 
client/each time they are initialised. This kind of design is often a 
precondition for being thread-safe; and it's often plain good design, 
unless some external 'real world' uniqueness makes it impossible.


I don't see a problem here. The fact that an IO lib presents some
controlled interface one or more to real world resources (I.E.
resources where you can't simply conjour up a new ones by using
a newResource constructor) should not stop it being able to service
multiple clients or sessions. The socket API and indeed the OS itself
seem to be obvious examples of this (or even something really simple
like Data.Unique).

Or take a look at the hypothetical embedded device driver API I put
on the wiki. This makes a clear distinction between DeviceHandles and
DeviceSessionHandles (which will wrap the correspnding DeviceHandle).
Users cannot create new DeviceHandles but are free to create as many
DeviceSessionHandles with a particular device as they like.

Regards
--
Adrian Hey




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


Re: [Haskell-cafe] global variables

2007-05-20 Thread Adrian Hey

Albert Y. C. Lai wrote:

Adrian Hey wrote:

Also, I don't know if the OP was a noob, but telling people (especially
noobs) that if they can't figure out how to solve a problem without
using a global variable then that must be down to inexperience and
general cluelessness on their part just seems wrong to me. It simply
isn't true.


Then what is right and what is true?


I see no need two answer this again I believe I have already made my
views perfectly clear already and provided ample evidence to justify
them. Surely I don't need to do it again?

If you disagree with any of them then feel free to explain why.

Regards
--
Adrian Hey

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


Re[2]: [Haskell-cafe] global variables

2007-05-20 Thread Bulat Ziganshin
Hello Isaac,

Sunday, May 20, 2007, 6:41:54 PM, you wrote:
 Maybe some sort of ISOLATE, DON'T_OPTIMIZE (but CAF), or
 USED_AS_GLOBAL_VARIABLE pragma instead of just the insufficient NOINLINE
 would be a good first step...

or LOOK_BUT_DON'T_TOUCH :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: [Haskell-cafe] global variables

2007-05-18 Thread Simon Peyton-Jones
|  and (at worst) are evil. These people are quite simply wrong and
|  should be ignored :-)
| 
|  Adrian Hey is not only wrong, but actually evil. He should be ignored. :-)
|
| I am right, I might well be evil, and if past experience is anything to
| go by I already know that I will be ignored. We've been talking about
| this problem for years, but nothing is ever done about it

I know that Jules preceded his remarks by saying that they were lighthearted, 
but I'd like to urge moderation in language.  One of the best things about the 
Haskell community is that politeness is pretty much universal.  Email is too 
fragile a medium to sustain the wry smile that can accompany an in-person 
conversation.

Also Adrian, you may feel ignored, but I don't think that's really so.  For 
example, I was looking back at your ACIO mail a couple of months ago, when I 
was thinking about concurrency.

Not immediately achieving a critical mass behind a language change is not the 
same as being ignored.  One of the good things about Haskell is that we put up 
with woefully inadequate situations (such as the total lack of sensible I/O in 
early lazy languages) because we can't yet find a solution that feels 
satisfying.  To say that nothing is ever done about it implies that there are 
clear things that could be done, but I don't think that is so (yet).  And 
sometimes people don't reply because they are just busy, or because they don't 
have anything useful to say.

In short, don't be discouraged.  Keep identifying problems, suggesting 
solutions, maintaining Wiki pages that summarise both, and so on.  There are 
lots of bright people on this mailing list, and sooner or later an aha moment 
will happen.

Simon

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


Re: [Haskell-cafe] global variables

2007-05-18 Thread Henning Thielemann

On Thu, 17 May 2007, Jules Bean wrote:

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

 (Perhaps annoyingly) the answer to this question, like so many other
 questions on this list, is a question. What are you trying to do?.

I've put your answer to the FAQ category on Haskell-Wiki:
 http://haskell.org/haskellwiki/Global_variables
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] global variables

2007-05-18 Thread Jules Bean

[I agree with your points, but...]

Adrian Hey wrote:


I've pretty much convinced it's wrong. There should be one and only
one main from which all subsequent IO activity derives. But creating
internal state in the form of mutable data structures is not an IO
activity. It just so happens that at the moment the only way to do this
is newIORef :: a - IO(IORef a), but this need not be so (readIORef and
writeIORef are IO activities, but newIORef isn't).



I find this point rather slippery. 'newIORef' is a unique-name-provider, 
but 'unique over what'? When a module is imported twice, should it not 
create new unique names?




Indeed they do, unfortunately. In fact it was this very problem that
lead me to conclude the top level mutable state is not only not evil,
but is a necessity. Having to call explicit initialisation code is
a big problem in complex systems. Exactly who is responsible for
initialising what? and in what order?


Maybe I'm being old-fashioned here, but isn't that a *fundamental* 
problem, that can't be automatically solved? Isn't it just a fact that 
in a complex system you, the programmer, have to make some decisions 
about who is responsible for acquiring resources?



If it's necessary that there is only one libWhateverState to preserve
safety properties (because the state must be kept in sync with what's
really being done to the world, of which there is also only one) then
what's the point of making it a parameter (the lib is not truly
parameterisable by that state).


A slightly irrational point of concern in my mind is that by encouraging 
this practice, we encourage lazy library design. A large proportion of 
libraries in fact *can* be written as reentrant in this sense, and 
truly are parameterisable by their state.


Only a few are not: those which actually manage connections to some 
real entity which is in fact unique.


Of course that doesn't mean the problem doesn't exist.

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


Re: [Haskell-cafe] global variables

2007-05-18 Thread Adrian Hey

Jules Bean wrote:

main = do
  sockstate - initSocks
  graphstate - initGraphics
  ...
  disposeGraphics graphstate
  disposeSocks sockstate
  exit


Voila. Mutable state which persists for our entire program.

Arguably it's a pain passing around the state explicitly. Alternatively, 
you can argue that passing this stuff around explicitly makes code much 
easier to reason about. And we know a dozen tricks to hide this stuff 
(reader monads, state monads, withSocketsDo-style bracket constructs).


So I don't think this is really the issue, is it?


Have you ever wondered why our IO API's don't look like this? I think
there are many problems with this approach. What are the consequences
of this philosophy for issues such safety, platform independence,
maintainance of stable APIs?

As I understood it, the issue was more about whether or not *library* 
modules should be allowed to some 'set up' initialisation code to run at 
the beginning of 'main' to start up their own global state. I was never 
convinced this was a nice idea (I don't like the thought than an 
'import' alone can add hidden IO actions to main).


I agree, which is why I'm not keen on the top level mdo proposal.
But addressing this issue is the point of the ACIO monad proposal.

Mind you, I'm not 
convinced it's wrong, either. I think it's a hard one.


I've pretty much convinced it's wrong. There should be one and only
one main from which all subsequent IO activity derives. But creating
internal state in the form of mutable data structures is not an IO
activity. It just so happens that at the moment the only way to do this
is newIORef :: a - IO(IORef a), but this need not be so (readIORef and
writeIORef are IO activities, but newIORef isn't).


I wouldn't dispute the assertion that at the level of complete programs
or processes, implementations that don't use global variables are
possible. But this does not hold at the level of individual IO library
API's. If we want to keep our software *modular* (I take we do), then
we need top level mutable state.


That's assuming you feel having an explicit 'init' command and a 
'withLibXYZDo' construct breaks modularity. It doesn't feel like a 
terrible modularity break to me. (Plenty of C libraries I've used 
require explicit init calls).


Indeed they do, unfortunately. In fact it was this very problem that
lead me to conclude the top level mutable state is not only not evil,
but is a necessity. Having to call explicit initialisation code is
a big problem in complex systems. Exactly who is responsible for
initialising what? and in what order?

You could make it the users responsibility to do it right at the
begining of main. But this places a heavy burden on the user to
fully understand the dependencies of their hardware and the
software that controls it.

Or you could make it the users responsibility to initialise whatever
APIs they actually make use of, in no particular order. Those APIs
then initialise whatever sub-systems they actually use as part of
their own initialisation. But what happens if the same sub-system is
used (and initialised) by two different higher level IO libs?
(The second will initialisation will destroy any state that the first
may have set up.)

Of course it's perfectly straight forward to avoid accidental
re-initialisation, but only by making use of..you know what.


Is it the use of global variables?
Or is it the use of the unsafePerformIO hack to create them?



The latter is definitely a problem.


Yes.


The former, I'm not sure. My gut feeling is that it is, too.


If it's necessary that there is only one libWhateverState to preserve
safety properties (because the state must be kept in sync with what's
really being done to the world, of which there is also only one) then
what's the point of making it a parameter (the lib is not truly
parameterisable by that state).

Furthermore, if it is going to take this state handle as an explicit
argument then you need to provide some way for users to get this
state handle. This could be by..
 1 - Making it an argument of main.
 2 - Exposing a newLibWhateverState constructor
 3 - Exposing a getLibWhateverState getter.

Problems..
 1 Requires the type of main to depend on what IO libs are used.
   Also the Boot code that invokes main must get this state handle
   from somewhere.
 2 Potentially permits 2 or more libWhateverStates to be created
   (in which case all bets are off re. the safety proprties I was
talking about).
 3 Can't be implemented without making use of..you know what.

Regards
--
Adrian Hey


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


Re: [Haskell-cafe] global variables

2007-05-18 Thread Adrian Hey

Simon Peyton-Jones wrote:

For example, I was looking back at your ACIO mail a couple of months ago,

 when I was thinking about concurrency.

Actually, this is Ian Starks proposal..

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

..but is one with which I agree. I just wrote some stuff on the wiki
about this actually solved some currently insoluble problems.


Not immediately achieving a critical mass behind a language change is not the

 same as being ignored.

Unfortunately the situation seems worse than this. AFAICT we haven't
even got a consensus that that there is a real problem here that needs
any kind of solution :-)

Regards
--
Adrian Hey


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


Re: [Haskell-cafe] global variables

2007-05-18 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Adrian Hey wrote:
 Furthermore, if it is going to take this state handle as an explicit
 argument then you need to provide some way for users to get this
 state handle. This could be by..
  1 - Making it an argument of main.
  2 - Exposing a newLibWhateverState constructor
  3 - Exposing a getLibWhateverState getter.
 
 Problems..
  1 Requires the type of main to depend on what IO libs are used.
Also the Boot code that invokes main must get this state handle
from somewhere.
  2 Potentially permits 2 or more libWhateverStates to be created
(in which case all bets are off re. the safety proprties I was
 talking about).
  3 Can't be implemented without making use of..you know what.

Making it an argument of main (1) is somewhat the same as doing (3) -
consider getArgs.  What bothers me is the IO-state in the Haskell
standard (arguments, random state...) which is a set not extensible
without the hack.  (It bothers me that there _are_ so many things in
that set, somewhat ad-hoc-ly it seems :)


 Unfortunately the situation seems worse than this. AFAICT we haven't
 even got a consensus that that there is a real problem here that needs
 any kind of solution :-)

The unsafePerformIO hack being used is not very satisfactory given how
many optimizations make it difficult to use safely in practice.  This
hack is also used many places.  I would be happier if that situation
were not true, and I suspect there's something like a consensus on
_that_. (maybe not as strong as _needs_ a solution in the short-to-mid
term future)

Isaac


-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGTg2+HgcxvIWYTTURAvWfAKC36q24IKTX5YQOVi+A4gNYLzBMMACePwkL
dwnAlZh++e2EqiFKvJEmn1M=
=NBHG
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] global variables

2007-05-18 Thread John Meacham
On Thu, May 17, 2007 at 07:25:03PM +0100, Adrian Hey wrote:
 The above hack is not actually Haskell. It's a hack, and it depends on 
 the particular implementation characteristics of GHC. It is not 
 unreasonable to imagine that a future GHC might contain different 
 compilation techniques (I hesitate to use the word 'optimisations' 
 because that sounds like something easy to turn off) which invalidate 
 the technique in other ways or make it dangerous.
 
 Well of course, that's why something needs to be done about this. Just
 being in a state of complete denial regarding the reality of this
 problem won't make it go away.

Indeed, I made a proposal a while ago to allow top level IO actions,

foo - newIORef foo

which are quite straigtforward, and would not even be inconsistant in
the view of the type system, as - bindings are always monomorphic
anyway.

Others pointed out that if we allow arbitrary IO actions, it could cause
undesirable things like causing importing a mobule to change program
behavior, or expose implementatino details, like when these are
executed, right away or lazily.

The solution was to have a special restricted version of IO containing
only those actions that are safe. like newMVar etc.. where safe means
more or less commutative and omittable.

this doesn't require any special support, just a

newtype ACIO a = ACIO (IO a)
deriving(Monad,Functor)

and then have a module only export the trusted things in the ACIO monad.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] global variables

2007-05-18 Thread John Meacham
On Thu, May 17, 2007 at 11:00:18PM +0100, Jules Bean wrote:
 I'm not sure that's quite to the point. Clearly we can set up state at 
 the top of our main action:
 
 main = do
   sockstate - initSocks
   graphstate - initGraphics
   ...
   disposeGraphics graphstate
   disposeSocks sockstate
   exit
 
 
 Voila. Mutable state which persists for our entire program.
 
 Arguably it's a pain passing around the state explicitly. Alternatively, 
 you can argue that passing this stuff around explicitly makes code much 
 easier to reason about. And we know a dozen tricks to hide this stuff 
 (reader monads, state monads, withSocketsDo-style bracket constructs).
 
 So I don't think this is really the issue, is it?
 
 As I understood it, the issue was more about whether or not *library* 
 modules should be allowed to some 'set up' initialisation code to run at 
 the beginning of 'main' to start up their own global state. I was never 
 convinced this was a nice idea (I don't like the thought than an 
 'import' alone can add hidden IO actions to main). Mind you, I'm not 
 convinced it's wrong, either. I think it's a hard one.

indeed. the whole issue is libraries. global state need not be visible
to users, but is certainly useful when hidden inside librarys to provide
efficient purely functional veneers for internal algorithms. 

I think restricting the actions to ones that don't have externally
visible effects is the way to go here for a couple reasons. 

 * I would very much hate for 'import' to have effects in and of itself.
 * it would disallow (or expose) the obvious 'lazy' approach to
   top-level IO, where you don't actually perform the IO until the first
   time the value is needed, then memoize it.

so, some sort of restricted ACIO monad is in order.

Also, there is the somewhat related 'ForeignData' proposal of mine, the
syntax is pretty much off the top of my head, but I think something like
this needs to go into the haskell FFI, 

http://hackage.haskell.org/trac/haskell-prime/wiki/ForeignData

especially since it will sever the last need for C, allowing fully native
haskellp programs with the full power of C code. (plus, lots of
optimizatuons are available to the compiler when it sees the definitions
like this and it is really easy to implement)

John

 

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] global variables

2007-05-17 Thread Eric

H|i,

Does anyone know of a simple and straightforward way to use global 
variables in Haskell?


E.


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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Donald Bruce Stewart
eeoam:
 H|i,
 
 Does anyone know of a simple and straightforward way to use global 
 variables in Haskell?
 
 E.

The usual way is to run the code that needs a global variable in a State monad.

The next answer is: you don't really need global variables, since you
don't have mutable variables anyway :-)

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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Dougal Stanton

On 17/05/07, Eric [EMAIL PROTECTED] wrote:

H|i,

Does anyone know of a simple and straightforward way to use global
variables in Haskell?



You can pass around an environment with the State or Reader monads
(read/write and read-only respectively). If you want to do IO with the
data you'll probably need the transformer equivalents: StateT or
ReaderT.

I think there are some hackish ways of making IO variables but I don't
know how that's done. I'd imagine it's frowned on from a stylistic
point of view, too...

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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Tom Harper

You can also use mutable variables (MVars) found in Control.Concurrent.MVar

http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurrent-MVar.html

They might work depending on your implementation.  The reading and
writing of MVars returns IO actions.

On 5/17/07, Dougal Stanton [EMAIL PROTECTED] wrote:

On 17/05/07, Eric [EMAIL PROTECTED] wrote:
 H|i,

 Does anyone know of a simple and straightforward way to use global
 variables in Haskell?


You can pass around an environment with the State or Reader monads
(read/write and read-only respectively). If you want to do IO with the
data you'll probably need the transformer equivalents: StateT or
ReaderT.

I think there are some hackish ways of making IO variables but I don't
know how that's done. I'd imagine it's frowned on from a stylistic
point of view, too...

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




--
Tom Harper
Computer Science Major '07
Syracuse University
+1 949 235 0185
Public Key: http://aftereternity.co.uk/rth.asc
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] global variables

2007-05-17 Thread Robin Green
On Thu, 17 May 2007 14:41:33 +0100
Eric [EMAIL PROTECTED] wrote:

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

Another alternative, for write-once variables, is implicit parameters.

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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Stefan O'Rear
On Thu, May 17, 2007 at 02:41:33PM +0100, Eric wrote:
 Does anyone know of a simple and straightforward way to use global 
 variables in Haskell?

Just declare them at the top level, as a function but without
arguments:

===

x = 2

main = print x

===

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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Jules Bean

Eric wrote:

H|i,

Does anyone know of a simple and straightforward way to use global 
variables in Haskell?


(Perhaps annoyingly) the answer to this question, like so many other 
questions on this list, is a question. What are you trying to do?.


The reason for this is that haskell's abstractions are different from 
those of the mainstream imperative languages, and the mapping isn't 1-1. 
So for a particular 'C' feature, there may be 3 or 4 haskell features 
which achieve similar effects, and the correct choice depends on the 
detailed context.


So, in particular, all those tasks which you use global variables for in 
C, can be achieved in haskell, but which solution depends what you are 
trying to do:


1. If you have some globals which are constant, then just define them at 
the top level. No problem.  pi = 3.14; progname = MyCoolApp.


2. If you have a global environment, which various functions read from 
(and you might, for example, initialise from a configuration file) then 
you should thread that as a parameter to your functions (after having, 
very likely, set it up in your 'main' action). If the explicit parameter 
passing annoys you, then you can 'hide' it with a monad.


3. If you have a need to store some global state which various of your 
functions modify, then you have a design issue. This style of design is 
frowned upon in C as well! The correct solution in C is to pass a 
'bundle' of appropriate parameters (you might call it an environment) to 
those functions which need it. In C++, perl or python you'd very likely 
make this bundle an object. In haskell this bundle will be a data value 
in some custom type; and using Monads you can 'hide the details' of 
passing it around, if you wish.


Hope that helps a bit,


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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Adrian Hey

Eric wrote:

H|i,

Does anyone know of a simple and straightforward way to use global 
variables in Haskell?


I assume what you're looking for is to be able to have IORefs,MVars
Chans etc at the top level. The standard (for want of a better word)
way to do this is known commonly known as the unsafePerformIO hack.

myTopLevelFlag :: IORef Bool
{-# NOINLINE myTopLevelFlag #-}
myTopLevelFlag = unsafePerformIO (newIORef False)

With ghc you should also compile which make use of the unsafePerformIO
hack using the -fno-cse flag (to inhibit common sub-expression elemination).

Use something like this at the top of the module..
{-# OPTIONS_GHC -fno-cse #-}

BTW, this is the commonly the subject of flame wars on the Haskell
mailing lists because there appear to be many who passionately believe
and assert that so called global variables are (at best) unnecessary
and (at worst) are evil. These people are quite simply wrong and
should be ignored :-)

They are necessary because they are the only way to ensure important
safety properties of many IO APIs.

I ported the old wiki page about this to the new wiki..
  http://www.haskell.org/haskellwiki/Top_level_mutable_state

If you want to see more examples of the use of the unsafePerformIO
hack you need only look at the source code of the current base
package (you'll find a dozen or so uses of this hack to create
top level mutable state).

Regards
--
Adrian Hey

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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Jules Bean
Please take this message in the fashion that is intended. My criticism 
is light hearted, as I believe yours is.


Adrian Hey wrote:

[hack snipped]


BTW, this is the commonly the subject of flame wars on the Haskell
mailing lists because there appear to be many who passionately believe
and assert that so called global variables are (at best) unnecessary
and (at worst) are evil. These people are quite simply wrong and
should be ignored :-)


Adrian Hey is not only wrong, but actually evil. He should be ignored. :-)

The above hack is not actually Haskell. It's a hack, and it depends on 
the particular implementation characteristics of GHC. It is not 
unreasonable to imagine that a future GHC might contain different 
compilation techniques (I hesitate to use the word 'optimisations' 
because that sounds like something easy to turn off) which invalidate 
the technique in other ways or make it dangerous.



They are necessary because they are the only way to ensure important
safety properties of many IO APIs.


That's a bold claim. It's very hard to prove that things don't exist. 
(That is, that other ways to ensure these safety properties don't 
exist). In snipped text you comment that the problems are often in 
low-level FFI library code: this makes me wonder if the real culprit 
doesn't lie at the FFI-haskell boundary. Perhaps there are good ways to 
specify this kind of invariant there.



If you want to see more examples of the use of the unsafePerformIO
hack you need only look at the source code of the current base
package (you'll find a dozen or so uses of this hack to create
top level mutable state).


All of these are, in a sense, failings. Because unsafePerformIO is not 
haskell, and we'd like base to be a haskell library. Not a GHC library.


I'd be willing to take a sportsman's bet that the original poster
does not actually need to use this hack; I doubt his application falls 
into the categories you have outlined. I would discourage people from 
using this hack unless it is, in fact, the only feasible approach.


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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Dougal Stanton

On 17/05/07, Jules Bean [EMAIL PROTECTED] wrote:


I'd be willing to take a sportsman's bet that the original poster
does not actually need to use this hack; I doubt his application falls
into the categories you have outlined. I would discourage people from
using this hack unless it is, in fact, the only feasible approach.


I find it amusing that questions like these elicit such a wide variety
of responses. The original poster probably thought they were asking a
fairly straightforward question and then... woosh :-) Everyone
responds to the question at the level that suits their own proficiency
in the subject, I suppose.

D.
___
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] global variables

2007-05-17 Thread Adrian Hey

Jules Bean wrote:

BTW, this is the commonly the subject of flame wars on the Haskell
mailing lists because there appear to be many who passionately believe
and assert that so called global variables are (at best) unnecessary
and (at worst) are evil. These people are quite simply wrong and
should be ignored :-)


Adrian Hey is not only wrong, but actually evil. He should be ignored. :-)


I am right, I might well be evil, and if past experience is anything to
go by I already know that I will be ignored. We've been talking about
this problem for years, but nothing is ever done about it (a solution to
this problem isn't even on the agenda for Haskell' AFIAK).

The above hack is not actually Haskell. It's a hack, and it depends on 
the particular implementation characteristics of GHC. It is not 
unreasonable to imagine that a future GHC might contain different 
compilation techniques (I hesitate to use the word 'optimisations' 
because that sounds like something easy to turn off) which invalidate 
the technique in other ways or make it dangerous.


Well of course, that's why something needs to be done about this. Just
being in a state of complete denial regarding the reality of this
problem won't make it go away.


They are necessary because they are the only way to ensure important
safety properties of many IO APIs.


That's a bold claim. It's very hard to prove that things don't exist. 
(That is, that other ways to ensure these safety properties don't 
exist). In snipped text you comment that the problems are often in 
low-level FFI library code: this makes me wonder if the real culprit 
doesn't lie at the FFI-haskell boundary. Perhaps there are good ways to 
specify this kind of invariant there.


No. Even if we stripped away all other code apart from the Haskell rts
itself (OS, device drivers etc) and performed your IO entirely in
Haskell (just using peek and poke on bare hardware), you'd still need
top level mutable state to implement common IO API's (e.g. The socket
API, does anybody really believe this is entirely stateless?).

I wouldn't dispute the assertion that at the level of complete programs
or processes, implementations that don't use global variables are
possible. But this does not hold at the level of individual IO library
API's. If we want to keep our software *modular* (I take we do), then
we need top level mutable state.


If you want to see more examples of the use of the unsafePerformIO
hack you need only look at the source code of the current base
package (you'll find a dozen or so uses of this hack to create
top level mutable state).


All of these are, in a sense, failings. Because unsafePerformIO is not 
haskell, and we'd like base to be a haskell library. Not a GHC library.


But what's the problem?
Is it the use of global variables?
Or is it the use of the unsafePerformIO hack to create them?

Regards
--
Adrian Hey

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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Adrian Hey wrote:
 They are necessary because they are the only way to ensure important
 safety properties of many IO APIs.

 That's a bold claim. It's very hard to prove that things don't exist.
 (That is, that other ways to ensure these safety properties don't
 exist). In snipped text you comment that the problems are often in
 low-level FFI library code: this makes me wonder if the real culprit
 doesn't lie at the FFI-haskell boundary. Perhaps there are good ways
 to specify this kind of invariant there.
 
 No. Even if we stripped away all other code apart from the Haskell rts
 itself (OS, device drivers etc) and performed your IO entirely in
 Haskell (just using peek and poke on bare hardware), you'd still need
 top level mutable state to implement common IO API's (e.g. The socket
 API, does anybody really believe this is entirely stateless?).
 
 I wouldn't dispute the assertion that at the level of complete programs
 or processes, implementations that don't use global variables are
 possible. But this does not hold at the level of individual IO library
 API's. If we want to keep our software *modular* (I take we do), then
 we need top level mutable state.
 
 If you want to see more examples of the use of the unsafePerformIO
 hack you need only look at the source code of the current base
 package (you'll find a dozen or so uses of this hack to create
 top level mutable state).

 All of these are, in a sense, failings. Because unsafePerformIO is not
 haskell, and we'd like base to be a haskell library. Not a GHC library.
 
 But what's the problem?
 Is it the use of global variables?
 Or is it the use of the unsafePerformIO hack to create them?

It's only slightly the unsafePerformIO hack, IMHO - if that were all,
a mechanism not requiring it would have been implemented long ago.

Now I launch into a long discussion:

The difficult question is how global?. GHCi already has problems with
this (varying persistence of those global variables, and they never last
between separate invocations of ghci).  Obviously global variables to
truly be global should be shared with one persistent state across the
whole wide world forever :P - but then we get identity problems, e.g.
fancy-package:GlobalVariable.Fancy.nuclearMissilesLaunched :: IORef/MVar
MannerOfNuclearMissileLaunch
where one day or on one hacker's computer there is
type MannerOfNuclearMissileLaunch = Int --number launched already
and another,
data MannerOfNuclearMissileLaunch = NoMissilesLaunched | WorldDestroyed
| Unknown

The usual meaning relies on the size of a program invocation.  This is a
link to main:Main.main .  As you observe, this is like inserting a
wrapper over everywhere the IO monad is used.  Clearly this adds
modularity by not requiring main's code to be modified, and also
destroys modularity by forcing main's semantics to be modified.  A
Haskell program is notionally executed by running Main.main.  Consider:

 global foo (initial value: False)
 main1 = setGlobal foo True
 main2 = getGlobal foo = print

Compile with -main-is main1 to the binary 'main1' and with -main-is
main2 to the binary 'main2'.  Now consider two possible overall
definitions of main:

 main = main1  main2
or
 main = executeBinary main1  executeBinary main2

Basically, all existing operating systems require executing a binary to
be more than just running its IO monad; they set up a global
(process-specific) environment for the process, which is why the two
hypothetical example defintions of main give different results.

Note that operating systems also serve the root of filesystems / in
unix, and variables global to the root filesystem's sharedness can be
simulated in this way.  Operating systems could serve process-specific
spaces this way, as long as it is possible for them to define something
like getProcessID :: IO ProcessID.  Note that Haskell has ThreadID which
is usefully Eq-comparable in GHC, whereas Hugs chooses not to
distinguish the identity of threads.  It is a similar design tradeoff.


Hardware:
readHardware, writeHardware are IO specific to the hardware.
Kernels generally rely on storing information in RAM about the state of
the hardware, and they presume to have global variables whose scope is
the present run of the computer.  This is straightforward for monolithic
kernel designs.  Although, if you want persistent settings it is more
difficult, the system explicitly saving ALSA state to disk or whatever.

Operating systems:
I don't know sockets in particular, but indeed operating systems are
expected to provide some IO operations that don't do exactly the same
thing depending on which computer in the world the program is running on.

Kernel/OS design variation is certainly one area to look into for
further consideration of these issues.  There are non-monolithic kernels
(GNU Hurd...), systems that can run on multiple hardware-computers as a
cluster...

There is usually expected to be one name resolver (e.g

Re: [Haskell-cafe] global variables

2007-05-17 Thread Jules Bean

Adrian Hey wrote:

We've been talking about
this problem for years, but nothing is ever done about it (a solution to
this problem isn't even on the agenda for Haskell' AFIAK).


The problem needs talking about, it's important.

My objection was the implication that top-level mutable state was the 
right answer to the OP's question, which my strong hunch is it isn't. I 
don't deny the existence of a problem here.



No. Even if we stripped away all other code apart from the Haskell rts
itself (OS, device drivers etc) and performed your IO entirely in
Haskell (just using peek and poke on bare hardware), you'd still need
top level mutable state to implement common IO API's (e.g. The socket
API, does anybody really believe this is entirely stateless?).


I'm not sure that's quite to the point. Clearly we can set up state at 
the top of our main action:


main = do
  sockstate - initSocks
  graphstate - initGraphics
  ...
  disposeGraphics graphstate
  disposeSocks sockstate
  exit


Voila. Mutable state which persists for our entire program.

Arguably it's a pain passing around the state explicitly. Alternatively, 
you can argue that passing this stuff around explicitly makes code much 
easier to reason about. And we know a dozen tricks to hide this stuff 
(reader monads, state monads, withSocketsDo-style bracket constructs).


So I don't think this is really the issue, is it?

As I understood it, the issue was more about whether or not *library* 
modules should be allowed to some 'set up' initialisation code to run at 
the beginning of 'main' to start up their own global state. I was never 
convinced this was a nice idea (I don't like the thought than an 
'import' alone can add hidden IO actions to main). Mind you, I'm not 
convinced it's wrong, either. I think it's a hard one.



I wouldn't dispute the assertion that at the level of complete programs
or processes, implementations that don't use global variables are
possible. But this does not hold at the level of individual IO library
API's. If we want to keep our software *modular* (I take we do), then
we need top level mutable state.


That's assuming you feel having an explicit 'init' command and a 
'withLibXYZDo' construct breaks modularity. It doesn't feel like a 
terrible modularity break to me. (Plenty of C libraries I've used 
require explicit init calls).



Is it the use of global variables?
Or is it the use of the unsafePerformIO hack to create them?



The latter is definitely a problem.

The former, I'm not sure. My gut feeling is that it is, too.

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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Adrian Hey

Albert Y. C. Lai wrote:
There is no reality about global variables. Global variables are 
syntactic sugar for local variables. That is the reality we need to 
think through. This syntactic sugar streamlines many practical programs 
and is indeed valuable.


I agree that the use of the term global variable is both inaccurate
an highly emotive, which is why I don't like it. But even the term
I use (top level mutable state) is not entirely accurate. The
mutable state is not at the top level, the mutable state is already
part of the world before main starts running.

What is top level are references to that state (IORefs, MVars etc).
As these are perfectly ordinary (I.E. *immutable*) Haskell values
there doesn't seem to be any obvious reason why they should not
exist at the top level. All that's missing is a semantically sound
mechanism to achieve this (such as the ACIO monad proposal).

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


Re: [Haskell-cafe] global variables

2007-05-17 Thread Jason Dagit

On 5/17/07, Adrian Hey [EMAIL PROTECTED] wrote:

Jules Bean wrote:
 BTW, this is the commonly the subject of flame wars on the Haskell
 mailing lists because there appear to be many who passionately believe
 and assert that so called global variables are (at best) unnecessary
 and (at worst) are evil. These people are quite simply wrong and
 should be ignored :-)

 Adrian Hey is not only wrong, but actually evil. He should be ignored. :-)

I am right, I might well be evil, and if past experience is anything to
go by I already know that I will be ignored. We've been talking about
this problem for years, but nothing is ever done about it (a solution to
this problem isn't even on the agenda for Haskell' AFIAK).

 The above hack is not actually Haskell. It's a hack, and it depends on
 the particular implementation characteristics of GHC. It is not
 unreasonable to imagine that a future GHC might contain different
 compilation techniques (I hesitate to use the word 'optimisations'
 because that sounds like something easy to turn off) which invalidate
 the technique in other ways or make it dangerous.

Well of course, that's why something needs to be done about this. Just
being in a state of complete denial regarding the reality of this
problem won't make it go away.

 They are necessary because they are the only way to ensure important
 safety properties of many IO APIs.

 That's a bold claim. It's very hard to prove that things don't exist.
 (That is, that other ways to ensure these safety properties don't
 exist). In snipped text you comment that the problems are often in
 low-level FFI library code: this makes me wonder if the real culprit
 doesn't lie at the FFI-haskell boundary. Perhaps there are good ways to
 specify this kind of invariant there.

No. Even if we stripped away all other code apart from the Haskell rts
itself (OS, device drivers etc) and performed your IO entirely in
Haskell (just using peek and poke on bare hardware), you'd still need
top level mutable state to implement common IO API's (e.g. The socket
API, does anybody really believe this is entirely stateless?).


At this point in the discussion I always think Haskell could probably
take a lesson from the evolution of object oriented programming.  As I
was taught, people starting to see modules as an important abstraction
(yay, Haskell has those).  Then people started to also realize that
instead of just modules it would be useful to have abstract data types
which could be instantiated many times and sort of encapsulate the
things (state) you might store in a module (yay, Haskell has ADTs).
Eventually, people put the two together, data types that also
encapsulated functionality.  Around this time, it was sort of like
having modules that could be instantiated many times instead of once
per program and objects were essentially born.

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.

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


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


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


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.netjohn 
___
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.netjohn 
___
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


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


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


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

import qualified Data.IO.Dict

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


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


[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 simplest possible example I had of the more general problem,
 and now

Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-13 Thread Adrian Hey
On Friday 12 Nov 2004 5:42 pm, Judah Jacobson wrote:
 On Fri, 12 Nov 2004 14:53:33 +, Adrian Hey [EMAIL PROTECTED] wrote:
  On Thursday 11 Nov 2004 12:27 pm, Ben Rudiak-Gould wrote:
   On the other hand, these are perfectly safe:
  
   once' :: IO a - IO (IO a)
   oncePerString :: String - IO a - IO a
   oncePerType   :: Typeable a = IO a - IO a
  
   once' seems virtually useless unless you have top-level -, but the
   other two don't need it. I'm not sure which would be preferable. I lean
   toward oncePerString as more flexible and predictable, though it
   requires a certain discipline on the part of its users.
 
  Having taken a bit of time to look at this, I have to say that IMO
  saying they are perfectly safe is over stating things a bit :-)

 How is oncePerType in particular unsound?

Actually, I think I'd better retract that statement as looking at your
definition closely I can't see obvious transformation that a compiler
could do that would change the observable behaviour of a program.
Reliance on current dynamics (which is it self a cheap and cheerful
hack) worries me though.

It certainly seems reasonable to eliminate your use of unsafePerformIO
as the source of any unsoundness because this is exactly the sort of
thing you'd do with top level - bindings if they existed (and
if they can't be given sound semantics I guess we'd better forget
the whole idea :-).

To be honest, all the alternatives that have been put forward
have looked like extrordinarily complex hacks to me. I dislike
having to use unsafePerformIO, but for one reason or another all
the suggested alternatives come with so many strings attached (to
get them to work properly) that I dislike them even more. A case
of the cure(s) being worse than the disease :-(

The problem just doesn't seem to be solvable at the library level.
It's something that's just plain missing from the language.

Regards
--
Adrian Hey


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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-13 Thread Keean Schupke

I'm not sure I understand what problem you think there is. Are the inits
you're talking about module inits? If so, I don't think there's a problem,
for several reasons.
The idea under discussion is that a top level (x - newThing) should
be lazy, (no action at all occurs until value of x is demanded). IOW,
it's exactly the same as the current unsafePerformIO hack, but not unsafe
because the compiler knows the semantics. So there is no implied module 
initialisation

Okay - I can see that with lazy semantics this might not be a problem... 
What happens with
the second problem: That where module B uses A internally and C uses A 
internally, then
I write a new module that tries to use B  C together... This 
potentially breaks B  C. I think
you need the extra restriction that the top level '-' bindings must not 
be exported. So where
does that leave us.

Top level inits are safe (I think) iff:
   - They are lazy (the definition only happens when required)
   - They contain only a subset of IO actions - namely those concerned
 with name creation within Haskell that don't actually do any IO.
   - They are not exportable from the module that contains them.
I think that covers it... have I forgotten anything?
   Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-13 Thread Adrian Hey
On Saturday 13 Nov 2004 9:15 am, Keean Schupke wrote:
 I'm not sure I understand what problem you think there is. Are the inits
 you're talking about module inits? If so, I don't think there's a problem,
 for several reasons.
 
 The idea under discussion is that a top level (x - newThing) should
 be lazy, (no action at all occurs until value of x is demanded). IOW,
 it's exactly the same as the current unsafePerformIO hack, but not unsafe
 because the compiler knows the semantics. So there is no implied module
 initialisation

 Okay - I can see that with lazy semantics this might not be a problem...
 What happens with
 the second problem: That where module B uses A internally and C uses A
 internally, then
 I write a new module that tries to use B  C together... This
 potentially breaks B  C. I think
 you need the extra restriction that the top level '-' bindings must not
 be exported. So where
 does that leave us.

 Top level inits are safe (I think) iff:
 - They are lazy (the definition only happens when required)
 - They contain only a subset of IO actions - namely those concerned
   with name creation within Haskell that don't actually do any IO.
 - They are not exportable from the module that contains them.

 I think that covers it... have I forgotten anything?

One of us has :-) Not sure who though.

I thought I'd covered the second problem you're alluding to already.
But if you think there's still a problem you'd better elaborate a little
more. Certainly I see no reason why top level TWI's cannot be exported
from a module. We don't have this constraint with the unsafePerformIO
hack.

For instance, if I had

 userInit - oneShot realInit

is there any reason why userInit can't be safely exported and used
in many different modules? The whole idea was that it should be.

Regards
--
Adrian Hey








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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-13 Thread Keean Schupke
Well lets say:
userInit - oneShot realInit
where realInit defines an MVar used for state storage that is used in 
module A to implement
an accumulator. Now module B does some maths using the accumulator, and 
module C does
some maths using the accumulator. If Main uses functions defined in both 
B and C then they
will both be trying to use the _same_ MVar to store their state in - 
which will result in the wrong answer. The following is a contrived 
example, If arith and geom were in the same module, this would be an 
error on the programmers part. But consider if A were in the standard 
libraries, and B and C were two orthogonal extensions by different 
authors, do we really want the situation where they break each other. 
Note: this does not apply to declarations like (i=4) as this is true for 
all time.  The problem is essentially that the declaration in the 
example is mutable. If  mutable-declarations are not exportable, you can 
reasonably say it is the module authors job to make sure all uses of the 
MVar are consistent.

module A
   mVarA - newMVar 1
   acc :: Int - IO ()
   acc i = writeMVar mVarA (readMVar mVarA + i)
   val :: IO Int
   val = readMVar mVarA
module B
   import A
   arith :: IO [Int]
   arith = do
  i - val
  acc (7+val)
  j - arith
  return (i:j)
module C
   import A
   geom :: IO [Int]
   geom = do
  i - val
  acc (7*val)
  j - geom
  return (i:j)
module D
   import B
   import C
   main = do
  a - arith
  g - geom
  putStrLn $ show (take 100 a)
  putStrLn $ show (take 100 g)
Keean
Adrian Hey wrote:
On Saturday 13 Nov 2004 9:15 am, Keean Schupke wrote:
 

I'm not sure I understand what problem you think there is. Are the inits
you're talking about module inits? If so, I don't think there's a problem,
for several reasons.
The idea under discussion is that a top level (x - newThing) should
be lazy, (no action at all occurs until value of x is demanded). IOW,
it's exactly the same as the current unsafePerformIO hack, but not unsafe
because the compiler knows the semantics. So there is no implied module
initialisation
 

Okay - I can see that with lazy semantics this might not be a problem...
What happens with
the second problem: That where module B uses A internally and C uses A
internally, then
I write a new module that tries to use B  C together... This
potentially breaks B  C. I think
you need the extra restriction that the top level '-' bindings must not
be exported. So where
does that leave us.
Top level inits are safe (I think) iff:
   - They are lazy (the definition only happens when required)
   - They contain only a subset of IO actions - namely those concerned
 with name creation within Haskell that don't actually do any IO.
   - They are not exportable from the module that contains them.
I think that covers it... have I forgotten anything?
   

One of us has :-) Not sure who though.
I thought I'd covered the second problem you're alluding to already.
But if you think there's still a problem you'd better elaborate a little
more. Certainly I see no reason why top level TWI's cannot be exported
from a module. We don't have this constraint with the unsafePerformIO
hack.
For instance, if I had
userInit - oneShot realInit
is there any reason why userInit can't be safely exported and used
in many different modules? The whole idea was that it should be.
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] One-shot? (was: Global variables and stuff)

2004-11-13 Thread Adrian Hey
On Saturday 13 Nov 2004 10:39 am, Keean Schupke wrote:
 Actually, I Think I'm wrong - I think its not even safe if you cannot
 export the '-' def. If any functions which use it are exported you are
 in the same situation. I cannot say the kind of code in the example I
 gave is good, can you? Infact the availability of these top level IO
 actions seems to completely change the feel of the language...

I've looked at your example, and the behaviour you describe is exactly
what would be expected and what it is intended. That's the whole point
of things having identity. The reason they have identity is because
they are mutable and all users of a particular TWI are indeed mutating
the same thing, just as all users of stdout are writing to the same
file.

The point is that if the shared TWI is something like an IORef this
is (of course) extremely dangerous because anybody can write anything
they like to it at any time. But that is not how this should be used.
The module exporting one or more TWIs typically will not be exporting
raw IORefs. It will be exporting a well designed stateful api which
access IORefs etc via closures. It's the responsibility of the author
of the exporting module to organise the code so that it delevers (on
whatever promisies it's making) to all clients, and clients should not
rely on anything that isn't being promised.

So it seems to me that the only thing that's wrong here is your
expectations (I.E. that a module should assume it has exclusive access
to whatever state the TWI's it imports mutate). This is not so.
If it wants it's own private TWI (a mutable queue say) it should not
be importing another modules queue (not that any good design should
be exporting such a thing anyway), it should be importing a newQueue
constructor and making it's own queue (either at the top level or
via normal IO monadic operations)..

 myQueue - newQueue

But there's no magic here. All IO actions have potentially unknown
state dependencies and mutating effects, that's why they're in the
IO monad. All the top level - extension does is enable the user to
extend the initial world state (as seen by main) with user defined
state, but it doesn't fundamentally change nature or hazards of
programming via the IO monad, for better or worse.

Regards
--
Adrian Hey





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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-12 Thread Graham Klyne
At 16:07 11/11/04 +, Keith Wansbrough wrote:
Graham Klyne wrote:
 At 12:27 11/11/04 +, Ben Rudiak-Gould wrote:
[..]
 going to be safe, because it's just not the case that
 
 x = once (newIORef ())
 y = x
 
 has the same intended meaning as
 
 x = once (newIORef ())
 y = once (newIORef ())
 
 No amount of compiler-specific magic is going to fix this.

 Ah, yes, I take the point now.

 Isn't this generally the case for any value in the IO monad?  (Brushing a
 murky area of equivalence;  the same IO computation used twice may yield
 different results, so I'm not clear to what extent it is meaningful to say
 that any IO value is the same as any other, including itself, in any
 observable sense.)
No.  getChar is always the IO operation that reads a character from
stdin.  You can always substitute one instance of getChar for
another; you can even say foo = getChar and substitute foo for
every occurrence of getChar.  A value of type IO a is a
*computation*; its result may change, but the computation itself
cannot.
So you say (and I do agree).  But how can I *observe* that they are the 
same?
#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] One-shot? (was: Global variables and stuff)

2004-11-12 Thread Keith Wansbrough
 So you say (and I do agree).  But how can I *observe* that they are the same?

Well, not with a single program run (obviously).  But it is the case
that for any program P and input sequence X (i.e., keys
pressed):

running P with X

and

running {foo = getChar; P'} with X  (where P' is P with all
occurrences of getChar replaced by foo)

will behave identically.

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-12 Thread Adrian Hey
On Thursday 11 Nov 2004 12:27 pm, Ben Rudiak-Gould wrote:
 On the other hand, these are perfectly safe:

 once' :: IO a - IO (IO a)
 oncePerString :: String - IO a - IO a
 oncePerType   :: Typeable a = IO a - IO a

 once' seems virtually useless unless you have top-level -, but the
 other two don't need it. I'm not sure which would be preferable. I lean
 toward oncePerString as more flexible and predictable, though it
 requires a certain discipline on the part of its users.

Having taken a bit of time to look at this, I have to say that IMO
saying they are perfectly safe is over stating things a bit :-)

The only one that is perfectly safe is the first, but as you say,
is useless (at least for the purposes under discussion) without
the top-level - extension. AFAICS the other two are unsound hacks.

So it seems to me that either the top-level - extension (in one form
or another) really is necessary, or that top level TWI's are unnecessary.

The latter is probably true, in a strict technical sense. But I can't
see a way to live without them and keep modularity. In any case,
I don't think there's any reason to force programmers wear the hair
shirt in this respect (other than dogma and superstitious fear about
the evils of global variables :-)

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-12 Thread Keean Schupke
Adrian Hey wrote:
The latter is probably true, in a strict technical sense. But I can't
see a way to live without them and keep modularity. In any case,
I don't think there's any reason to force programmers wear the hair
shirt in this respect (other than dogma and superstitious fear about
the evils of global variables :-)
 

I agree about not wearing a hair-shirt, but how do you propose to solve
the multiple import problem: B imports A, C imports A, D imports B  C.
Now the top level inits (a - computation) in A, do they happen once, 
defining
the same init A.a, do they happen twice, perhaps initialising B.A.a and 
C.A.a,
do they happen twice, meaning that 'a' may have different values depending
on whether it is accessed from B or C? for example:

module A where
   a - newChan 0
module B where
   import A
   b - do {writeChan A.a 7;return ()}
module C
   import A
   c - do {writeChan A.a 6;return ()}
module D
   import A
   import B
   d - readChan A.a
does this mean the same as:
module D'
   import B
   import A
   d - readChan A.a
Should values really depend on the order of includes? Even if you limit 
things to just
newChan in top level '-' you still don't know if A.a in B the same A.a 
in C. Perhaps it
is enough to say  A.a only exists once no matter how many times it is 
directly or
indirectly imported?

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-12 Thread Robert Dockins

Should values really depend on the order of includes? Even if you limit 
things to just
newChan in top level '-' you still don't know if A.a in B the same A.a 
in C. Perhaps it
is enough to say  A.a only exists once no matter how many times it is 
directly or
indirectly imported?
This strikes me as the only sane thing to do.  Are there any reasons you 
might want C.A.a to be different than B.A.a?

In addition, perhaps we should require that modules using TWIs not have 
cicular dependancies.  Then all init actions can be topo sorted by 
dependencies.

Would those restrictions solve the problems that have been floating aroud?
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-12 Thread Keean Schupke
This still has a problem. Lets say B implements some useful function that
relies on A. Now also C implements some different useful function and also
relies on A in its implementation. If there is only one A.a then using 
both B
and C features in the same code will potentally break both B and C. The only
thing that makes sense in this case is that the A imported by B is distinct
from the A imported by C.

The problem as far as I can see it is that you can create sensible 
examples that
require the behaviour to be one way or the other. Perhaps one solution 
is to allow
top level '-' but to not allow them to be exported?

   Keean.
Robert Dockins wrote:

Should values really depend on the order of includes? Even if you 
limit things to just
newChan in top level '-' you still don't know if A.a in B the same 
A.a in C. Perhaps it
is enough to say  A.a only exists once no matter how many times it is 
directly or
indirectly imported?

This strikes me as the only sane thing to do.  Are there any reasons 
you might want C.A.a to be different than B.A.a?

In addition, perhaps we should require that modules using TWIs not 
have cicular dependancies.  Then all init actions can be topo sorted 
by dependencies.

Would those restrictions solve the problems that have been floating 
aroud?

___
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] One-shot? (was: Global variables and stuff)

2004-11-12 Thread Judah Jacobson
On Fri, 12 Nov 2004 14:53:33 +, Adrian Hey [EMAIL PROTECTED] wrote:
 On Thursday 11 Nov 2004 12:27 pm, Ben Rudiak-Gould wrote:
 
 
  On the other hand, these are perfectly safe:
 
  once' :: IO a - IO (IO a)
  oncePerString :: String - IO a - IO a
  oncePerType   :: Typeable a = IO a - IO a
 
  once' seems virtually useless unless you have top-level -, but the
  other two don't need it. I'm not sure which would be preferable. I lean
  toward oncePerString as more flexible and predictable, though it
  requires a certain discipline on the part of its users.
 
 Having taken a bit of time to look at this, I have to say that IMO
 saying they are perfectly safe is over stating things a bit :-)
 

How is oncePerType in particular unsound?  I've given a quick example
implementation below.  It's a referentially transparent function (no
use of unsafePerformIO except to implement an internal global
hashtable), it's type-safe, and I imagine that the discipline involved
is no worse than that of dynamic exceptions, for example.

I'm not necessarily suggesting that this solves the discussion, but it
could be good enough to replace unsafePerformIO in many situations.

Incidentally, a similar idea was suggested by George Russell, but not
really followed up on:
http://www.haskell.org/pipermail/haskell/2004-June/014104.html
(This was perhaps the first message in the current months-long discussion?)

-Judah

---
module OnceType(oncePerType) where

import Data.Dynamic
import Data.Hashtable as HT
import Data.Int(Int32)
import GHC.IOBase (unsafePerformIO)

type Dict = HT.HashTable TypeRep Dynamic

oncePerType :: Typeable a = IO a - IO a
oncePerType (action :: IO a) = do
let rep = typeOf (undefined :: a)
l - HT.lookup globalDict rep
case l of
Nothing - do -- run the action
x - action
HT.insert globalDict (typeOf x) (toDyn x)
return x
Just dyn - case fromDynamic dyn of
-- since we store values according to their TypeRep,
-- fromDynamic should never fail.
Just x - return x

{-# NOINLINE globalDict #-}
globalDict :: Dict
globalDict = unsafePerformIO $ HT.new (==) hashTypeRep

-- this could be implemented better using the internals of Data.Typeable
hashTypeRep :: TypeRep - Int32
hashTypeRep = hashString . show
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-12 Thread Adrian Hey
On Friday 12 Nov 2004 3:20 pm, Keean Schupke wrote:
 Adrian Hey wrote:
 The latter is probably true, in a strict technical sense. But I can't
 see a way to live without them and keep modularity. In any case,
 I don't think there's any reason to force programmers wear the hair
 shirt in this respect (other than dogma and superstitious fear about
 the evils of global variables :-)

 I agree about not wearing a hair-shirt, but how do you propose to solve
 the multiple import problem: B imports A, C imports A, D imports B  C.
 Now the top level inits (a - computation) in A, do they happen once,
 defining
 the same init A.a, do they happen twice, perhaps initialising B.A.a and
 C.A.a,
 do they happen twice, meaning that 'a' may have different values depending
 on whether it is accessed from B or C? for example:

I'm not sure I understand what problem you think there is. Are the inits
you're talking about module inits? If so, I don't think there's a problem,
for several reasons.

The idea under discussion is that a top level (x - newThing) should
be lazy, (no action at all occurs until value of x is demanded). IOW,
it's exactly the same as the current unsafePerformIO hack, but not unsafe
because the compiler knows the semantics. So there is no implied module 
initialisation.

 module A where
 a - newChan 0

 module B where
 import A
 b - do {writeChan A.a 7;return ()}

 module C
 import A
 c - do {writeChan A.a 6;return ()}

 module D
 import A
 import B

 d - readChan A.a

 does this mean the same as:

 module D'
 import B
 import A

 d - readChan A.a


 Should values really depend on the order of includes?

No, and they don't.

Firstly, since the values of neither b or c are demanded, no
writes will occur.

Secondly, ordering is not dependent on import ordering,
it's depencency ordering only. Assuming laziness, actions
are performed as and when the corresponding TWI's
are required (perhaps never). 

Thirdly, ordering doesn't matter anyway. The point of the
restricted monad proposal (SafeIO or whatever), was to address
precisely this ordering issue. With SafeIO ordering doesn't
matter because you cannot perform any IO. All you can do is
create IORefs (MVars etc..). You can't read or write them,
nor can you do any other IO.

So assuming we're using this monad for - bindings, you
wouldn't be able to use readChan or writeChan in any case.

Regards
--
Adrian Hey

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Adrian Hey
On Thursday 11 Nov 2004 6:36 am, Judah Jacobson wrote:
 AFAIKS, the definition of once that I gave uses unsafePerformIO in a
 perfectly sound manner; namely, the creation of a top-level MVar.  It
 only becomes unsafe if certain optimizations are performed; but
 then, that's also true for the SafeIO proposal (as I understand it).

That's the trouble with unsafePerformIO. Haskell is supposed to be a
purely functional language and the compiler will assume all functions
are pure. As soon as you use unsafePerformIO to create something that
isn't a function you're in grave danger, even if it looks safe at
the local level, it still isn't a function and the damage can't be
contained at the local level. It's only really OK if it still is
a function despite the use of unsafePerformIO (which is possible,
but often hard to be sure about).

 Yeah, perhaps it hasn't been said so much before.  :-)   You noted
 several days ago that oneShot (a variant of my once) can be defined
 using top-level mutable variables.  I was just pointing out that the
 converse is true: top-level mutable variables can be emulated using

I'm not too sure about that. But I guess the devil's in the detail,
so until that's been thrashed out I'll reserve judgement.

 Again, I would assume that any translation of (x - someAction) needs
 to have a prohibition on CSE, inlining, etc on the RHS; there's
 nothing special to once here.

Yes, but the trouble is in Haskell if you have x = y that really means
any occurance of x can be replaced by y (and vice-versa) without changing
the meaning of the program (subject to scoping rules of course).

You're right that your once solution and the (x - someAction) both have
the same problem. But the difference is the compiler doesn't know that
with the once solution because you've told it that..
 myRef = once (newIORef 'a')
..and it will believe you.

 I disagree that this only works for newIORef.  Consider (in ghci):

Well no, of course newIORef isn't the *only* case where it works :-)

But I thought the point you were making was that the once guaranteed
that the resulting value was independent of when it got reduced
(presumably for any action). This isn't generally true, any more
than it would be true for the x - someAction solution if some
action can be *any* IO monadic operation.

That's why the proposal to use a restricted monad was put forward
I.E. an IO monad which was not capable of doing any real IO.
In principle at least, with the SafeIO/CIO monads the resulting
initial value could be determined at compile time, which is
exactly what we want I think (same intial value for every program
run). 

Regards
--
Adrian Hey

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Keean Schupke
Graham Klyne wrote:
Keean,
As far as I can tell, both your solutions to the one-shot problem 
require that:

(a) the expression to be one-shotted is in the IO monad.  That seems 
reasonable, since why else does one care (semantically speaking)?

(b) they depend on the host operating system platform (semaphores, 
process id, environment variables) rather than pure Haskell language 
features.

Wouldn't it be easier to simply define once as a common Haskell 
library function?

#g
--
Erm, it is a library function (I provided the NamedSem library as an 
attachment)... Are you suggesting it would be nice to be able to do this 
without talking to the OS?

Remember a process is an operating system level identity... The 
boundries of a process are controlled by the OS not the language - 
therefore I think it is entirely appropriate to use it for this.

Also see my proposal for NamedMVars, This would move the concept of this 
solution into a
purely Haskell space, and would not need to communicate with the OS. The 
NamedMVar library could be implemented with a bit of C and Haskell in a 
library module - without changes to
the language spec and the compiler. I guess I was relly looking for 
comments on the
general technique to detemine if it is worth my while writing this 
(NamedMVar) library...

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Graham Klyne
At 11:31 11/11/04 +, Keean Schupke wrote:
Wouldn't it be easier to simply define once as a common Haskell library 
function?
Erm, it is a library function (I provided the NamedSem library as an 
attachment)... Are you suggesting it would be nice to be able to do this 
without talking to the OS?
OK, I didn't sufficiently emphasize *common* library function.  Maybe I 
should have said standard.

I'm not suggesting that the calling program should not use the operating 
system, but that it should be insulated from the details of said OS.  Not 
all OSes have process IDs or named semaphores.  This discussion has shown 
many ways to implement once, and which is best may depend upon the 
underlying OS.

#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] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Ben Rudiak-Gould
Graham Klyne wrote:
Wouldn't it be easier to simply define once as a common Haskell 
library function?
Depends on the type and the expected semantics. As Adrian Hey already 
pointed out, (once :: IO a - IO a) with the obvious semantics is never 
going to be safe, because it's just not the case that

   x = once (newIORef ())
   y = x
has the same intended meaning as
   x = once (newIORef ())
   y = once (newIORef ())
No amount of compiler-specific magic is going to fix this.
On the other hand, these are perfectly safe:
   once' :: IO a - IO (IO a)
   oncePerString :: String - IO a - IO a
   oncePerType   :: Typeable a = IO a - IO a
once' seems virtually useless unless you have top-level -, but the 
other two don't need it. I'm not sure which would be preferable. I lean 
toward oncePerString as more flexible and predictable, though it 
requires a certain discipline on the part of its users.

In any case there would need to be support for different scopes:
   perProcess :: String - IO a - IO a
   perThread  :: String - IO a - IO a
   perMachine :: String - IO a - IO a
I suppose you could add
   perType :: Typeable a = IO a - IO a
with the stipulation that types in different processes are distinct 
(which seems like the only safe assumption).

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Graham Klyne
At 12:27 11/11/04 +, Ben Rudiak-Gould wrote:
Graham Klyne wrote:
Wouldn't it be easier to simply define once as a common Haskell library 
function?
Depends on the type and the expected semantics. As Adrian Hey already 
pointed out, (once :: IO a - IO a) with the obvious semantics is never 
going to be safe, because it's just not the case that

   x = once (newIORef ())
   y = x
has the same intended meaning as
   x = once (newIORef ())
   y = once (newIORef ())
No amount of compiler-specific magic is going to fix this.
Ah, yes, I take the point now.
Isn't this generally the case for any value in the IO monad?  (Brushing a 
murky area of equivalence;  the same IO computation used twice may yield 
different results, so I'm not clear to what extent it is meaningful to say 
that any IO value is the same as any other, including itself, in any 
observable sense.)

#g
--
On the other hand, these are perfectly safe:
   once' :: IO a - IO (IO a)
   oncePerString :: String - IO a - IO a
   oncePerType   :: Typeable a = IO a - IO a
once' seems virtually useless unless you have top-level -, but the other 
two don't need it. I'm not sure which would be preferable. I lean toward 
oncePerString as more flexible and predictable, though it requires a 
certain discipline on the part of its users.

In any case there would need to be support for different scopes:
   perProcess :: String - IO a - IO a
   perThread  :: String - IO a - IO a
   perMachine :: String - IO a - IO a
I suppose you could add
   perType :: Typeable a = IO a - IO a
with the stipulation that types in different processes are distinct (which 
seems like the only safe assumption).

-- Ben

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] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Judah Jacobson
On Thu, 11 Nov 2004 09:16:04 +, Adrian Hey [EMAIL PROTECTED] wrote:
 
 That's the trouble with unsafePerformIO. Haskell is supposed to be a
 purely functional language and the compiler will assume all functions
 are pure. As soon as you use unsafePerformIO to create something that
 isn't a function you're in grave danger, even if it looks safe at
 the local level, it still isn't a function and the damage can't be
 contained at the local level. It's only really OK if it still is
 a function despite the use of unsafePerformIO (which is possible,
 but often hard to be sure about).

Your first reply convinced me that supplying once as a function would
be bad.  I'm still not entirely convinced that hiding it in the
compiler implementation of (x - someAction) is infeasible, but as you
say the devil's in the details.  Even if it could be hacked to work,
the added complexity is probably not worth it.

 But I thought the point you were making was that the once guaranteed
 that the resulting value was independent of when it got reduced
 (presumably for any action). This isn't generally true, any more
 than it would be true for the x - someAction solution if some
 action can be *any* IO monadic operation.

Ok, I think that's where we diverged.  I was trying to be more
ambition and also consider actions such as reading in a configuration
file, which seems to be another common use of unsafePerformIO.  The
idea behind once is that although the return value does depend on
when it's reduced, this happens at a well-defined location (namely,
where it first appears in the sequence of IO actions that makes up the
program).

But in any event, the proposal for oncePerString/Process/Type seems
like a much a more robust solution than mine.

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Keith Wansbrough
Graham Klyne wrote:

 At 12:27 11/11/04 +, Ben Rudiak-Gould wrote:
[..]
 going to be safe, because it's just not the case that
 
 x = once (newIORef ())
 y = x
 
 has the same intended meaning as
 
 x = once (newIORef ())
 y = once (newIORef ())
 
 No amount of compiler-specific magic is going to fix this.
 
 Ah, yes, I take the point now.
 
 Isn't this generally the case for any value in the IO monad?  (Brushing a 
 murky area of equivalence;  the same IO computation used twice may yield 
 different results, so I'm not clear to what extent it is meaningful to say 
 that any IO value is the same as any other, including itself, in any 
 observable sense.)

No.  getChar is always the IO operation that reads a character from
stdin.  You can always substitute one instance of getChar for
another; you can even say foo = getChar and substitute foo for
every occurrence of getChar.  A value of type IO a is a
*computation*; its result may change, but the computation itself
cannot.

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Judah Jacobson
On Thu, 11 Nov 2004 12:27:17 +, Ben Rudiak-Gould
[EMAIL PROTECTED] wrote:
 
 On the other hand, these are perfectly safe:
 
 once' :: IO a - IO (IO a)
 oncePerString :: String - IO a - IO a
 oncePerType   :: Typeable a = IO a - IO a
 
 once' seems virtually useless unless you have top-level -, but the
 other two don't need it. I'm not sure which would be preferable. I lean
 toward oncePerString as more flexible and predictable, though it
 requires a certain discipline on the part of its users.
 

Reflecting on the matter, I don't think that oncePerString is
type-safe.  For example, it allows us to create the following:

ref :: IO (IORef a)
ref = oncePerString foo (newIORef undefined)

Here's an example in which we subvert the type system (and probably
crash the program) by writing a String and reading an Int from the
same IORef:

do 
ref = writeIORef (foo)
(x :: Int) - ref = readIORef 
print x

This is similar to the reason for ML's value monomorphism restriction.
 In contrast, oncePerType
preserves monomorphism nicely, since all instances of Typeable are monomorphic.

Thoughts?  Am I missing something?
-Judah
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Keean Schupke
I think you are right... The only safe operation I can see for a 
one-time init
is type IO (). All results have to be returned via side effects. Hence with
my named-MVar proposal the first execution of the init function initialises
certain named-MVars, and subsequent executions do nothing at all. The
functions in the library would use the names-MVars directly. Therefore the
once function in the NamedSem library is:

   once :: IO () - IO ()
   Keean.
Judah Jacobson wrote:
On Thu, 11 Nov 2004 12:27:17 +, Ben Rudiak-Gould
[EMAIL PROTECTED] wrote:
 

On the other hand, these are perfectly safe:
   once' :: IO a - IO (IO a)
   oncePerString :: String - IO a - IO a
   oncePerType   :: Typeable a = IO a - IO a
once' seems virtually useless unless you have top-level -, but the
other two don't need it. I'm not sure which would be preferable. I lean
toward oncePerString as more flexible and predictable, though it
requires a certain discipline on the part of its users.
   

Reflecting on the matter, I don't think that oncePerString is
type-safe.  For example, it allows us to create the following:
ref :: IO (IORef a)
ref = oncePerString foo (newIORef undefined)
Here's an example in which we subvert the type system (and probably
crash the program) by writing a String and reading an Int from the
same IORef:
do 
   ref = writeIORef (foo)
   (x :: Int) - ref = readIORef 
   print x

This is similar to the reason for ML's value monomorphism restriction.
In contrast, oncePerType
preserves monomorphism nicely, since all instances of Typeable are monomorphic.
Thoughts?  Am I missing something?
-Judah
___
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] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Judah Jacobson
On Thu, 11 Nov 2004 20:14:24 +, Keean Schupke
[EMAIL PROTECTED] wrote:
 I think you are right... The only safe operation I can see for a
 one-time init
 is type IO (). All results have to be returned via side effects. Hence with
 my named-MVar proposal the first execution of the init function initialises
 certain named-MVars, and subsequent executions do nothing at all. The
 functions in the library would use the names-MVars directly. Therefore the
 once function in the NamedSem library is:
 
 once :: IO () - IO ()
 
 Keean.
 

Actually, I don't see anything wrong on the face of it with
oncePerType :: Typeable a = IO a - IO a
since the only instances of Typeable are monomorphic.  Indeed, the
implementation seems pretty straightforward: store the results of
already-run computations as Dynamic values in a global dictionary,
keyed by TypeRep.

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


Re: [Haskell-cafe] One-shot? (was: Global variables and stuff)

2004-11-11 Thread Keean Schupke

Actually, I don't see anything wrong on the face of it with
oncePerType :: Typeable a = IO a - IO a
since the only instances of Typeable are monomorphic.  Indeed, the
implementation seems pretty straightforward: store the results of
already-run computations as Dynamic values in a global dictionary,
keyed by TypeRep.
 

What happens if more than one 'once' function returns the same type? I 
guess you could wrap the types in a unique constructor. Infact you could 
use the HList library to produce a type indexed list with a unqiue type 
constraint that can be enforced at compile time.

The version with the String key also seems interesting, as the key 
could  be the name of the function being memoised, which has to be 
unique. Template-Haskell could be used to generate the reified string 
from the function name, it would end up like (in the new TH syntax):

   a - $(once 'function) a b c
Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


  1   2   >