Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 01:53:22PM +0100, Ben Rudiak-Gould wrote:
[snip]
  Since a lot of the concerns expressed about this seem to centre
  around possible abuse of arbitrary IO operations in these top level
  constructions, maybe the problem could be addressed by insisting
  that a restricted monad was used, call it SafeIO say.
 
 How about (forall s. ST s)?
 
 We can require module init actions to have a type (forall s. ST s a) 
 instead of IO a. The compiler or RTS wraps the actions with stToIO 
 (which is a safe function) before executing them.
 
 Benefits:
 
* It's just as easy as before to allocate global refs (and global 
 mutable arrays).
* It's still possible to perform arbitrary IO actions (e.g. FFI 
 calls), but you have to wrap them in unsafeIOToST -- a good thing since 
 they really are unsafe. unsafeIOToST is much safer than unsafePerformIO 
 when used in this way.
 
 Problems:
 
* stToIO (newSTRef 'x') doesn't have type IO (IORef Char).
 
 This problem can be solved by adopting a reform that I've wanted for a 
 long time anyway: make IO, IORef, etc. aliases for (ST RealWorld), 
 (STRef RealWorld), etc. instead of completely different types. Then 
 stToIO is the identity function and we only need a single set of 
 state-thread functions instead of the parallel IO and ST equivalents 
 that we have currently.

It definitely sounds nice, but is it actually possible to
generalize e.g. MVar from RealWorld to forall s or are we
always going to have to say:

v - unsafeIOToST (newMVar / newChan ... )

GHC's definition:
data MVar a = MVar (MVar# RealWorld a)


-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Ben Rudiak-Gould
Remi Turk wrote:
It definitely sounds nice, but is it actually possible to generalize e.g. MVar from RealWorld 
to forall s or are we always going to have to say:
v - unsafeIOToST (newMVar / newChan ... )
 

I hadn't thought of that, but I don't think there's any problem with
   type MVar = STMVar RealWorld
   newMVar  :: a - ST s (STMVar s a)
   withMVar :: STMVar s a - (a - ST s b) - ST s b
   ...
For that matter it seems like we could (should?) have
   forkST :: ST s () - ST s (STThreadId s)
   forkIO = forkST
and so on.
-- Ben
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 05:11:02PM +0100, Ben Rudiak-Gould wrote:
 Remi Turk wrote:
 
 It definitely sounds nice, but is it actually possible to generalize e.g. 
 MVar from RealWorld to forall s or are we always going to have to say:
 
 v - unsafeIOToST (newMVar / newChan ... )
  
 
 I hadn't thought of that, but I don't think there's any problem with
 
type MVar = STMVar RealWorld
 
newMVar  :: a - ST s (STMVar s a)
withMVar :: STMVar s a - (a - ST s b) - ST s b
...
 
 For that matter it seems like we could (should?) have
 
forkST :: ST s () - ST s (STThreadId s)
forkIO = forkST
 
 and so on.
 
 -- Ben

But what semantics would they have?
It cannot be the normal concurrency as
AFAIK runST is supposed to be deterministic.

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Adrian Hey
On Sunday 17 Oct 2004 4:45 am, Wolfgang Thaller wrote:
 Adrian Hey wrote:
  I'm puzzled about this idea of module init action in a declarative
  language. Perhaps, if it's desirable to have some module initialisation
  applied to a module if anything from it is used, the way to do this
  would
  be to have a reserved identifier specially for the purpose, like
  main, but at the module level. (Though this idea still seems a
  bit strange to me).

 I don't see what's so strange about that.

What's strange about it IMHO is that at the moment the mere presence of
some definition in a module has no effect on actual programs. What counts
is whether or not defined thing is actually connected to the top
level main via some chain of explicit (I.E. named) dependency. This
is a property I would like to preserve. If I've understood the proposal
correctly, we'd lose this.

 At least, it's not any
 stranger than on-demand execution of IO actions in a pure functional
 language. And the toplevel - is definitely a natural syntax for
 that.

True, but maybe this isn't neccessary, and even if it is, performing the
IO creation acts only if the created thing is actually used by a
program still seems the lesser of two evils to me. Of course used
could mean one of at least two different things..
 1- The compiler does some kind of dependency analysis and mops up
all referenced things which must be created into some kind of
pre-main action.
 2- Things which must be created are just compiled into some kind of
thunk which gets reduced (post-main), if and when it is actually
required by a running program.

Option 1 seems like quite a difficult thing to implement, but does
have the advantage that well defined semantics could be given to
arbitrary IO operations. It also has the disadvantage that a some
of these may be redundant (just because something is referenced
doesn't imply that is will actually be used in any given program
run).

Option 2 seems easier to implement and is nice and lazy, but
suffers from semantic ambiguity if arbitrary IO operations
are allowed (encouraged). But do we need to do this? I'm
begining think maybe we don't. The only reason it seems like
we do is because currently the only way of creating IORefs
and wotnot is via the IO monad, but this need not be so IMO.

 You're taking away a feature I want to use.

Sorry, I didn't mean to deprive you of something you would find useful.
But maybe it should be considered as a separate issue. It's not clear to
me how the compiler (or Joe programmer for that matter) would determine
and/or control which modules initialisation actions would be executed or
not, if there's no obvious connection to the top level main.

 1) Initialising global IORefs is a good thing, no matter when it's
 actually done.

Yes, the hypothetical SafeIO monad allows you to do this (what you can't
do is read or write IORefs).

 2) Being able to initialize things at program startup is a good thing,
 even if they're not explicitly referred to.

Well here is where we disagree I think. Not that I think this is a bad
thing as such, but the rules that determine which modules init actions
do or don't get invoked seem quite unclear to me if there's no requirement
that they are referenced from main, directly or indirectly.

But maybe you could clarify what you have in mind?

Regards
--
Adrian Hey

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


Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Ben Rudiak-Gould
Remi Turk wrote:
 On Sun, Oct 17, 2004 at 05:11:02PM +0100, Ben Rudiak-Gould wrote:
 I don't think there's any problem with

 type MVar = STMVar RealWorld

 newMVar :: a - ST s (STMVar s a)
 withMVar :: STMVar s a - (a - ST s b) - ST s b ...

 For that matter it seems like we could (should?) have

 forkST :: ST s () - ST s (STThreadId s) forkIO = forkST
 But what semantics would they have? It cannot be the normal
 concurrency as AFAIK runST is supposed to be deterministic.
Okay, so I'm being silly. Forget forkST then. But STMVar is still okay, 
isn't it? The only MVars you could use in a state thread would be those 
you'd created in the same state thread, and without forkST they can't be 
accessed in a nondeterministic way. Their presence is pointless, true, 
but at least not unsafe.

It does seem a bit of a hack, but it still seems preferable to the other 
alternatives currently on the table (namely unrestricted IO, a new 
SafeIO, or unsafeIOToST.newMVar).

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


Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-17 Thread Remi Turk
On Sun, Oct 17, 2004 at 07:20:28PM +0100, Ben Rudiak-Gould wrote:
 Remi Turk wrote:
 
  On Sun, Oct 17, 2004 at 05:11:02PM +0100, Ben Rudiak-Gould wrote:
 
  I don't think there's any problem with
 
  type MVar = STMVar RealWorld
 
  newMVar :: a - ST s (STMVar s a)
  withMVar :: STMVar s a - (a - ST s b) - ST s b ...
 
  For that matter it seems like we could (should?) have
 
  forkST :: ST s () - ST s (STThreadId s) forkIO = forkST
 
  But what semantics would they have? It cannot be the normal
  concurrency as AFAIK runST is supposed to be deterministic.
 
 Okay, so I'm being silly. Forget forkST then. But STMVar is still okay, 
 isn't it? The only MVars you could use in a state thread would be those 

I won't ever remind you of your being silly if you tell me about
the current state of your implicit-(parameter|return)-IO story ;)

STMVar does indeed still seem okay, except that I have no idea if
it actually makes any sense outside of IO.
(That is: newSTMVar x = unsafeIOToST (newMVar x) seems a bit
pointless and might be the actual way it needs to be implemented.
Has a vague feeling of being silly too now...)

By the way, I'm still in favour of `type IO a = ST RealWorld a':
It just seems wrong to either let's just make it IO or having
to sprinkle stToIO's around...

 you'd created in the same state thread, and without forkST they can't be 
 accessed in a nondeterministic way. Their presence is pointless, true, 
 but at least not unsafe.
 
 It does seem a bit of a hack, but it still seems preferable to the other 
 alternatives currently on the table (namely unrestricted IO, a new 
 SafeIO, or unsafeIOToST.newMVar).
 
 -- Ben

I'm waiting to be convinced either way ;)

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-16 Thread Wolfgang Thaller
Adrian Hey wrote:
I'm puzzled about this idea of module init action in a declarative
language. Perhaps, if it's desirable to have some module initialisation
applied to a module if anything from it is used, the way to do this 
would
be to have a reserved identifier specially for the purpose, like
main, but at the module level. (Though this idea still seems a
bit strange to me).
I don't see what's so strange about that. At least, it's not any 
stranger than on-demand execution of IO actions in a pure functional 
language. And the toplevel - is definitely a natural syntax for 
that.

I've interpreted this correctly this means that someAction will always
get executed, whether or not foo (or anything dependent on foo) is used
elsewhere? This seems like a bad thing to me.
It's a feature. I'd actually _want_ to use that one independently.
It may be harmless enough
if all it does is create a few IORefs which are then promptly garbage
collected, but in some situations it could involve quite complex
and expensive initialisation operations on foreign libraries
(for example).
Well if you want those IO operations to be lazily interleaved with the 
rest of the program (or not executed at all), you can use

valueToBeInitedLazily - unsafeInterleaveIO $ do
blah
... which explicitly says what you are doing that might be slightly 
unsafe.

Since a lot of the concerns expressed about this seem to centre
around possible abuse of arbitrary IO operations in these top
level constructions, maybe the problem could be addressed by
insisting that a restricted monad was used, call it SafeIO say.
You're taking away a feature I want to use.
1) Initialising global IORefs is a good thing, no matter when it's 
actually done.
2) Being able to initialize things at program startup is a good thing, 
even if they're
not explicitly referred to.
3) Lazy, on-demand initialization of things is a good thing, if you 
know what you're doing.
4) Lazy, on-demand initialization of things (with potential side 
effects) is a bad thing, if you don't know what you're doing.

If we define toplevel IO bindings to be just like the unsafePerformIO 
hack, we get 1,3 and 4 (and 4 is actually a bad thing).
If we define toplevel IO bindings as mdo-style module initialisation, 
we get 1 and 2 directly, and 3 with an obvious use of 
unsafeInterleaveIO. We don't get 4, because obviously, when you use 
unsafeInterleaveIO, you're already claiming to know what you're doing.

Also note that if useless initialization of IORefs ever becomes a 
problem, we can still use lots of nasty hacks inside the compiler to 
optimize for those common functions. But I don't think we'll ever have 
to do this.

Cheers,
Wolfgang
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Module Initialisation? (was Re: [Haskell] (no subject))

2004-10-14 Thread Adrian Hey
On Thursday 14 Oct 2004 10:18 am, Simon Marlow wrote:
 On 13 October 2004 16:17, Wolfgang Thaller wrote:
  We could get away with desugaring them to some very unsafe non-IO-
  bindings and having the module init action do something evil to
  make the IO happen in the right order... should be possible to make
  that look exactly like mdo from the outside.
  We'll end up using the unsafePerformIO hack inside the implementation
  again, so that people end up with two IORefs instead of one, but that
  should be cheap enough:
 
  foo - someAction
 
  ... could be transformed into ...
 
  foo_var = unsafePerformIO $ newIORef (throw NonTermination)
  foo_action = someAction = writeIORef foo_var
  foo = unsafePerformIO $ readIORef foo
 
  ... with the appropriate NOINLINEs.
  The module init action would then make sure that foo_action gets
  invoked.

 Yes, we could do that.  The fact that we're using NOCSE/NOINLINE
 internally still seems very fragile, though.  Oh well, perhaps we have
 to live with that if we don't want the pain of a special binding type
 throughout the compiler.

I'm puzzled about this idea of module init action in a declarative
language. Perhaps, if it's desirable to have some module initialisation
applied to a module if anything from it is used, the way to do this would
be to have a reserved identifier specially for the purpose, like
main, but at the module level. (Though this idea still seems a
bit strange to me).

Also, I'm still not convinced that mdo is something I want emulated
anyway, (well not if it means doing something like the above). If
I've interpreted this correctly this means that someAction will always
get executed, whether or not foo (or anything dependent on foo) is used
elsewhere? This seems like a bad thing to me. It may be harmless enough
if all it does is create a few IORefs which are then promptly garbage
collected, but in some situations it could involve quite complex
and expensive initialisation operations on foreign libraries
(for example).

Since a lot of the concerns expressed about this seem to centre
around possible abuse of arbitrary IO operations in these top
level constructions, maybe the problem could be addressed by
insisting that a restricted monad was used, call it SafeIO say.

So we'd have something like this:
initIORef :: a - SafeIO (IORef a)
initMVar  :: a - SafeIO (MVar a)
initEmptyMVar :: SafeIO (MVar a)
liftSafeIO:: SafeIO a - IO a

The idea being that from within SafeIO you couldn't read or modify IORefs
or do any other IO operation, all you could do is create new ones (or
incorporate existing ones into the data structure). Wouldn't this + mdo
suffice for the safe construction and initialisation of complex mutable data
structures (which is probably all people want most of the time)?

I guess you'd still need a get out occasionally, especially for FFI..
flakyLiftIO :: IO a - SafeIO a
:-)

So at the top level you'd probably have..

myThing :: Thing
myThing - safeNewThing

safeNewThing :: SafeIO Thing
safeNewThing = mdo ...

newThing :: IO Thing
newThing = liftSafeIO safeNewThing

Now that all seems so simple, I'm certain I must have overlooked
something :-(

Regards
--
Adrian Hey

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