Re: important news: refocusing discussion

2006-04-05 Thread Marcin 'Qrczak' Kowalczyk
Simon Marlow [EMAIL PROTECTED] writes:

 I think it would be a mistake to relegate concurrency to an addendum;
 it is a central feature of the language, and in fact is one area where
 Haskell (strictly speaking GHC) is really beginning to demonstrate
 significant advantages over other languages.  We should make the most
 of it.

I agree.

Concurrency is needed for finalizers (except those which only call
system functions, without mutating other objects).

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


Re: concurrency (was Re: important news: refocusing discussion)

2006-03-30 Thread Tomasz Zielonka
On Tue, Mar 28, 2006 at 10:49:36AM +0100, Malcolm Wallace wrote:
 Tomasz Zielonka [EMAIL PROTECTED] wrote:
  http://www.uncurry.com/repos/FakeSTM/
  
  Perhaps it could serve as a drop-in replacement for STM in haskell
  compilers which don't implement STM directly.
 
 Nice idea.  But your code already uses a whole heap of Haskell
 extensions which may or may not make it into Haskell'.
 
monad transformer lib (requires MPTC)
exceptions
dynamically extensible exceptions
deriving non-standard classes
extended newtype deriving
pattern guards

You read the whole code? Wow! I myself would have trouble understanding
how it does what it does now ;-)

I could easily get rid of:

deriving non-standard classes
extended newtype deriving
pattern guards

I used GHC's exceptions, because I wanted my STM to handle them
correctly, as in the STM paper. In a implementation without exceptions,
I could probably get away with hand made exception handling.

The rest would be a bit more difficult to remove, but I think it could
be possible more or less elegantly.

Best regards
Tomasz
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Concurrency (was: RE: Re[2]: important news: refocusing discussion)

2006-03-29 Thread John Meacham
On Mon, Mar 27, 2006 at 03:36:55PM +0100, Simon Marlow wrote:
 But before we get carried away figuring out all the pros and cons of
 various options, let me point out once again that
   
   This is just a marketing decision
 
 Because
 
  (a) we're going to standardise concurrency anyway

concurrency is a hugely overloaded term in this whole discussion. I am
hoping to break out what it actually means on the wiki some more.

 
  (b) it is unlikely that Hugs or JHC will implement concurrency
  even if it goes into the standard

Well, if the standard is unimplemented for certain compilers,  I think
we need to work on the standard because that would be a deficiency of
it. I would very much like to be able to write portable concurrent
programs which doesn't necessarily mean GHC style concurrency or nothing.


given the choice between

1. a standard specifying something most people can't implement
2. a widely available but not mentioned in the standard extension

2 seems much more preferable and we should err on that side.

of course, this is a false dichotomy as there are happy mediums in the
middle I hope we can arrive at.


I am thinking jhc will offer two concurrency mechanisms eventually,

1. state-thread based threading based on a portable user space library.
so you get O'Haskell or hugsish concurrency by just using the right
library.

2. one OS thread per haskell thread, no guarentees about repeated work
between threads. the reasoning being that a programer can avoid the
problem of repeated work by being clever, but the run-time cost of
suspending partial evaluations and protecting in-progress computations
is unavoidable. some profiling support will probably be needed to aid a
programmer in determining if repeated work is an issue.


I think it is very likely that hugs and jhc and yhc will all implement
concurrency of some sort so it would be odd if ghc's happened to be the
only one that is standards compliant by definition.

  (c) the question is just whether the brand Haskell' encompasses
  concurrency or not (I thought I'd use that word because I
  know JL likes it so much :-)

I don't think it should necessarily, at least not a type of concurrency
that can't be widely implemented. it would be bad for the brand and
sort of negate one of the points of haskell' if GHC were the only true
implementation.

 Yes there are several ramifications of this decision, but none of them
 are technical.  As I see it, we either specify Concurrency as an
 addendum, or NoConcurrency as an addendum, and both options are about
 the same amount of work.

this is a big big understatement. the concurrency specifications are
completly underspecified and there is a lot of technical work that would
be needed to bring them up to snuff. the current proposal basically says
do what GHC does in a lot of words.

 So on that note, I'll restate my preference that Haskell' should include
 concurrency, and leave it at that.  We can start the standardisation
 process without arriving at a conclusion on this issue anyway.

indeed. but I feel that just saying GHC style or nothing would sort of
suck as there are very fruitful intermediate options without the caveats
of the ghc model. I think we actually are going to need to dig into the
details of concurrency, one way or another and I'd like to see something
portable/good/and uncompromising come out of the commitee if it exists.
If we are going to add concurrency, I'd like to see it done right.

John


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


Re: Re[2]: important news: refocusing discussion

2006-03-29 Thread Ross Paterson
On Tue, Mar 28, 2006 at 10:25:04AM +0100, Simon Marlow wrote:
 On 28 March 2006 00:24, Ross Paterson wrote:
  How about STM (minus retry/orElse) and TVars as the portable
  interface? They're trivial for a single-threaded implementation, and
  provide a comfortable interface for everyone.
 
 It just occurred to me that STM isn't completely trivial in a
 single-threaded implementation, because exceptions have to abort a
 transaction in progress.

Almost trivial, though:

import Prelude hiding (catch)
import Control.Exception
import Data.IORef

-- The reference contains a rollback action to be executed on exceptions
newtype STM a = STM (IORef (IO ()) - IO a)
unSTM (STM f) = f

instance Functor STM where
fmap f (STM m) = STM (fmap f . m)

instance Monad STM where
return x = STM (const (return x))
STM m = k = STM $ \ r - do
x - m r
unSTM (k x) r

atomically :: STM a - IO a
atomically (STM m) = do
r - newIORef (return ())
m r `catch` \ ex - do
rollback - readIORef r
rollback
throw ex

catchSTM :: STM a - (Exception - STM a) - STM a
catchSTM (STM m) h = STM $ \ r - m r `catch` \ ex - unSTM (h ex) r

newtype TVar a = TVar (IORef a)

newTVar :: a - STM (TVar a)
newTVar a = STM $ const $ do
ref - newIORef a
return (TVar ref)

readTVar :: TVar a - STM a
readTVar (TVar ref) = STM (const (readIORef ref))

writeTVar :: TVar a - a - STM ()
writeTVar (TVar ref) a = STM $ \ r - do
oldval - readIORef ref
modifyIORef r (writeIORef ref oldval )
writeIORef ref a

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Re[2]: important news: refocusing discussion

2006-03-29 Thread Simon Marlow
On 29 March 2006 11:00, Ross Paterson wrote:

 On Tue, Mar 28, 2006 at 10:25:04AM +0100, Simon Marlow wrote:
 On 28 March 2006 00:24, Ross Paterson wrote:
 How about STM (minus retry/orElse) and TVars as the portable
 interface? They're trivial for a single-threaded implementation, and
 provide a comfortable interface for everyone.
 
 It just occurred to me that STM isn't completely trivial in a
 single-threaded implementation, because exceptions have to abort a
 transaction in progress.
 
 Almost trivial, though:
 
 import Prelude hiding (catch)
 import Control.Exception
 import Data.IORef
 
 -- The reference contains a rollback action to be executed on 
 newtype STM a = STM (IORef (IO ()) - IO a)

very clever ;-)

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Re[2]: important news: refocusing discussion

2006-03-28 Thread Simon Marlow
On 28 March 2006 00:24, Ross Paterson wrote:

 On Mon, Mar 27, 2006 at 09:36:28AM +0100, Simon Marlow wrote:

 The portable interface could be Control.Concurrent.MVar, perhaps.
 
 As Malcolm pointed out, using MVars requires some care, even if you
 were just aiming to be thread-safe.

I don't really understand the problem, maybe I'm missing something.  I
thought the idea would be that a thread-safe library would simply use
MVar instead of IORef.  So instead of this:

   do 
  x - readIORef r
  ...
  writeIORef r x'

you would write

   do
  modifyMVar_ r $ \x -
...
return x'

actually the second version is not only thread-safe, but exception-safe
too.

Malcolm's objections:

 But Q2 explicitly raises the issue of whether a non-concurrent
 implementation must still follow a minimum API.  That could be a
 reasonable requirement, if we fleshed out the detail a bit more.
 The specific suggestion of requiring MVars makes me a tiny bit
 worried though.  After all, MVars capture the idea of
 synchronisation between threads, and I assume that since a
 non-concurrent implementation has only one thread, that thread will
 be trying to MVar-synchronise with something that does not exist,
 and hence be blocked for ever.  I can imagine that there are
 situations where synchronisation is entirely safe
 and free of blocking, but how to specify when it would be unsafe?

There's no synchronisation, because we're not writing multi-threaded
code here.  Just code that doesn't have any race conditions on its
mutable state when run in a multi-threaded setting.

Maybe you could elaborate on what problems you envisage?

Back to Ross:
 How about STM (minus retry/orElse) and TVars as the portable
 interface? They're trivial for a single-threaded implementation, and
 provide a comfortable interface for everyone.

Now that's a rather good idea.   It does raise the bar for the
concurrent implementations, though, and STM is not nearly as mature and
well-understood as MVars.  There do exist implementations of STM in
terms of MVars (at least two I know of).

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Re[2]: important news: refocusing discussion

2006-03-28 Thread Simon Marlow
On 28 March 2006 00:24, Ross Paterson wrote:

 How about STM (minus retry/orElse) and TVars as the portable
 interface? They're trivial for a single-threaded implementation, and
 provide a comfortable interface for everyone.

It just occurred to me that STM isn't completely trivial in a
single-threaded implementation, because exceptions have to abort a
transaction in progress.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


concurrency (was Re: important news: refocusing discussion)

2006-03-28 Thread Malcolm Wallace
Tomasz Zielonka [EMAIL PROTECTED] wrote:

 It may be relevant for this discussion: I believe I reimplemented STM,
 including retry and orElse, on top of old GHC's concurrency
 primitives.

 http://www.uncurry.com/repos/FakeSTM/
 
 Perhaps it could serve as a drop-in replacement for STM in haskell
 compilers which don't implement STM directly.

Nice idea.  But your code already uses a whole heap of Haskell
extensions which may or may not make it into Haskell'.

   monad transformer lib (requires MPTC)
   exceptions
   dynamically extensible exceptions
   deriving non-standard classes
   extended newtype deriving
   pattern guards

Certainly, no compiler other than GHC currently implements all of these
extensions.

Regards,
Malcolm
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


concurrency (was Re: important news: refocusing discussion)

2006-03-28 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote:

  The portable interface could be Control.Concurrent.MVar, perhaps.
 
 I don't really understand the problem, maybe I'm missing something.  I
 thought the idea would be that a thread-safe library would simply use
 MVar instead of IORef.

I was misled by several people's hand-waving assertion that, provided
you used MVars correctly, there would be no synchronisation problems.
But no-one had yet defined what correct meant.  I kind of assumed they
meant you could write concurrent threaded code (with only some minor
restrictions) and have it work in a single-threaded implementation
without change.  This seemed like a pretty strong (and dubious) claim to
me.

But now I see you are actually saying something quite different.  (And I
recall some discussion on these points from a few months ago.)

  * IORef is inherently thread-unsafe, and so we should eliminate IORefs
from the language.

  * One can write single-threaded code using MVars instead of IORefs,
and it will be safe on a multi-threaded implementation.

The latter point is quite the opposite of what I thought was being
proposed.

Regards,
Malcolm
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Concurrency (was: RE: Re[2]: important news: refocusing discussion)

2006-03-28 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote:

  (a) we're going to standardise concurrency anyway

Well, but that only begs the question, what *kind* of concurrency are we
going to standardise on?  e.g. Will we admit all variations of scheduling
(co-operative, time-slice, and pre-emptive)?

  (b) it is unlikely that Hugs or JHC will implement concurrency
  even if it goes into the standard

Now this is something that puzzles me.  I was under the impression that
Hugs already implements concurrency, using pretty much the same APIs as
ghc.

I'd also like to know a bit more about jhc's position here.  Is it just
that JohnM wants to keep his compiler pure and free from having a
runtime-system?  Or are there other issues?

 Yes there are several ramifications of this decision, but none of them
 are technical.  As I see it, we either specify Concurrency as an
 addendum, or NoConcurrency as an addendum, and both options are about
 the same amount of work.

There are certainly technical questions.  If Hugs's implementation of
concurrency is not concurrency after all, on what basis do we make that
determination?  Why is a definition of concurrency that encompasses both
ghc and Hugs models unacceptable?

Regards,
Malcolm
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: important news: refocusing discussion

2006-03-28 Thread Ross Paterson
On Tue, Mar 28, 2006 at 10:14:27AM +0100, Simon Marlow wrote:
 On 28 March 2006 00:24, Ross Paterson wrote:
  As Malcolm pointed out, using MVars requires some care, even if you
  were just aiming to be thread-safe.
 
 I don't really understand the problem, maybe I'm missing something.  I
 thought the idea would be that a thread-safe library would simply use
 MVar instead of IORef.

MVars certainly require more care than IORefs: you have to ensure your
takes and puts are matched, for example.

And there's the possibility of deadlock when you have more than one
variable.  I was toying with an interface like

newRef :: a - IO (Ref a)
modifyRef :: Ref a - (a - (a, r)) - IO r
modifyRef2 :: Ref a - Ref b - (a - b - (a, b, r)) - IO r
...

where Refs are MVars plus a stable ordering, so all the primitives
lock (i.e. take) them in the same order.  It's a bit clunky, though.

On Tue, Mar 28, 2006 at 10:25:04AM +0100, Simon Marlow wrote:
 It just occurred to me that STM isn't completely trivial in a
 single-threaded implementation, because exceptions have to abort a
 transaction in progress.

Ah, and it seemed so simple.  Still, exception-safety would be a nice
property for a state abstraction to have.

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Re[2]: important news: refocusing discussion

2006-03-28 Thread Manuel M T Chakravarty
Simon Marlow:
 On 26 March 2006 03:44, Ross Paterson wrote:
 
  On Sat, Mar 25, 2006 at 05:31:04PM -0800, isaac jones wrote:
  I have no idea if it would work, but one solution that Simon didn't
  mention in his enumeration (below) is that we could find a group of
  people willing to work hard to implement concurrency in Hugs, for
  example, under Ross's direction.
  
  I'm no expert on Hugs internals, and certainly not qualified to direct
  such an effort, but I don't have great hopes for it.  Apart from the
  fact that Hugs is written in a legacy language and uses a quite a bit
  of global state, it also makes heavy use of the C stack, and any
  implementation that does that will have trouble, I think.
 
 Yes, I don't see an easy way to do it.  You could have one OS thread per
 Haskell thread (let the OS manage the separate C stacks), a giant lock
 around the interpreter (to protect all the global state), and explicit
 yield() from time to time to simulate pre-emption.  This isn't too bad,
 but you still have to implement GC somehow, and hence traverse all the
 live C stacks, and that sounds tricky to me.

True, but so what?  I mean, honestly, we should decide language features
by their merit to applications and maturity.  We should also take into
account what the power/weight ratio of a feature is in terms of general
implementation costs.  But discussing the costs to one particular
implementation that's already been stretched light years beyond what it
originally was intended for, seems a bit much.

Manuel


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: concurrency (was Re: important news: refocusing discussion)

2006-03-28 Thread isaac jones
On Tue, 2006-03-28 at 11:05 +0100, Malcolm Wallace wrote:
(snip)
   * IORef is inherently thread-unsafe, and so we should eliminate IORefs
 from the language.

That's not quite true, as you can have an IORef guarded by an MVar.  Why
would you want such a thing?  For instance, you might write a library
with two IORefs and one MVar instead of two MVars in order to reduce the
possibility of deadlock.

Is it the case that a library is thread-safe as long as it doesn't use
IORefs, though?  I trolled around base looking for libraries that might
not be thread-safe and found only that HashTable uses an IORef, and
indeed there's a FIXME that says it should use an MVar.  I didn't look
very hard, though.

peace,

  isaac

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: important news: refocusing discussion

2006-03-27 Thread Malcolm Wallace
John Goerzen [EMAIL PROTECTED] wrote:

 On Fri, Mar 24, 2006 at 11:07:53AM +, Malcolm Wallace wrote:
   I assume that since a non-concurrent implementation has
  only one thread, that thread will be trying to MVar-synchronise with
  something that does not exist, and hence be blocked for ever.
 
 Not necessarily.  An MVar is a useful tool in place of an IORef.  It
 works well when a given hunk of code is used in a threaded program,
 but it also works well in a non-threaded program.  If they are used
 correctly, there is no problem.

Your final sentence is the one that I want to emphasise.  What does it
mean to use an MVar correctly, such that one can avoid blocking in a
non-threaded implementation?

Regards,
Malcolm
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Concurrency (was: RE: Re[2]: important news: refocusing discussion)

2006-03-27 Thread Simon Marlow
On 26 March 2006 02:31, isaac jones wrote:

 Possible Interests:
  1. I can write tools like filesystems, web servers, and GUIs in
 Haskell'
  2. Libraries that I use are thread-safe
  3. I can compile my code with any Haskell' compiler
  4. Tools such as debuggers and tracers that claim to support Haskell'
 actually work on my code.
  5. That there not be too many Haskell's
  6. That there be a diversity of Haskell' implementations
  7. That concurrency be reasonable to implement for existing
 compilers/interpreters.
  8. That it be reasonable to implement for new compilers/interpreters.
  9. Show off how effective Haskell can be in this area (possibly
 attracting new users).
 
 By 5 I mean that it might be nice to have a core Haskell and a bunch
 of addenda.  But this could cause no two Haskell' implementations to
 be the same. (My Haskell' might have concurrency and FFI, but no class
 system, or something.)  The more optional addenda we have, the more we
 actually fracture the language.  We could be in the same situation
 we're in today.
 
 Isaac's Interests
  * 1-6, 9
 
 Simon's Interests:
  * He's mentioned 9, I'm sure that there are others.

I'd count all of 1-9 as interests - they're all desirable.  But we
haven't found a design that satisfies 1-9, and in the absence of that we
have to compromise somewhere.

But before we get carried away figuring out all the pros and cons of
various options, let me point out once again that
  
  This is just a marketing decision

Because

 (a) we're going to standardise concurrency anyway

 (b) it is unlikely that Hugs or JHC will implement concurrency
 even if it goes into the standard

 (c) the question is just whether the brand Haskell' encompasses
 concurrency or not (I thought I'd use that word because I
 know JL likes it so much :-)

Yes there are several ramifications of this decision, but none of them
are technical.  As I see it, we either specify Concurrency as an
addendum, or NoConcurrency as an addendum, and both options are about
the same amount of work.

So on that note, I'll restate my preference that Haskell' should include
concurrency, and leave it at that.  We can start the standardisation
process without arriving at a conclusion on this issue anyway.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: important news: refocusing discussion

2006-03-27 Thread Neil Mitchell
 it's too hard to implement (and it's not always hard
 - the YHC guys
 managed it in a matter of days

Tom is the one who implemented it in Yhc, and details can be found
http://www.haskell.org/haskellwiki/Yhc/RTS/Concurrency

but some of the reasons that it was easier than in other compilers are:

* We compile to byte code, then execute the bytecode. Because of this,
to add support for concurrency only really changes the executer, which
is a standalone program.

* Bytecode also means we can just schedule each process for n instructions.

* Its simulated concurrency, if you have two processors, only one will
ever be used.  The only exception is FFI, where a number of FFI calls
can run in parallel with some Haskell code. This means that no locking
is needed on the global heap.

If compiling to native code, and aiming for proper concurrency at the
operating system level, it would be a lot more work! If you wanted
high performance concurrency, like GHC, you would need to do that
extra work.

Thanks

Neil
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: important news: refocusing discussion

2006-03-27 Thread Ross Paterson
On Mon, Mar 27, 2006 at 09:36:28AM +0100, Simon Marlow wrote:
 On 26 March 2006 03:44, Ross Paterson wrote:
  [...] the key point is that
  a Haskell' module that does not use concurrency, but is thread-safe,
  ought to work with non-concurrent implementations too.
  
  To make that work, we'd need two interfaces:
   * one for applications that make use of concurrency.  This would be
 unavailable on some implementations.
   * one for thread-safe use of state.  This would be available on all
 implementations, and authors not requiring concurrency would be
 encouraged to use it for maximum portability.
 
 Sure, I think this is a point on which we're all agreed.
 
 The portable interface could be Control.Concurrent.MVar, perhaps.

As Malcolm pointed out, using MVars requires some care, even if you were
just aiming to be thread-safe.  Packaged things like atomicModifyIORef
are safe, but awkward, and need extra stuff to handle multiple variables.

How about STM (minus retry/orElse) and TVars as the portable interface?
They're trivial for a single-threaded implementation, and provide a
comfortable interface for everyone.

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: important news: refocusing discussion

2006-03-27 Thread Taral
On 3/27/06, Ross Paterson [EMAIL PROTECTED] wrote:
 How about STM (minus retry/orElse) and TVars as the portable interface?
 They're trivial for a single-threaded implementation, and provide a
 comfortable interface for everyone.

+1 on STM as the core interface. Why do you suggest omitting retry/orElse?

--
Taral [EMAIL PROTECTED]
You can't prove anything.
-- Gödel's Incompetence Theorem
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: important news: refocusing discussion

2006-03-27 Thread Aaron Denney
On 2006-03-28, Taral [EMAIL PROTECTED] wrote:
 On 3/27/06, Ross Paterson [EMAIL PROTECTED] wrote:
 How about STM (minus retry/orElse) and TVars as the portable interface?
 They're trivial for a single-threaded implementation, and provide a
 comfortable interface for everyone.

 +1 on STM as the core interface. Why do you suggest omitting retry/orElse?

-1.  STM is a cool little abstraction making it easy to write dead-lock
free code.  I haven't wrapped my head around writing _quick_ dead-lock free
code, where as the MVar model has all sorts of abstractions built that
make that, well, not _easy_, but the difficulties are understood.

-- 
Aaron Denney
--

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: important news: refocusing discussion

2006-03-25 Thread Bulat Ziganshin
Hello Ross,

Saturday, March 25, 2006, 4:16:01 AM, you wrote:

 On Fri, Mar 24, 2006 at 02:47:09PM -, Simon Marlow wrote:
 I think it would be a mistake to relegate concurrency to an addendum; it
 is a central feature of the language, and in fact is one area where
 Haskell (strictly speaking GHC) is really beginning to demonstrate
 significant advantages over other languages.  We should make the most of
 it.

 Essential for many applications, certainly, but central?  How can you
 say that?

it becomes central language feature just because it's much easier to
write concurrent programs in Haskell than in other languages and
because ghc's implementation of user-level threads is blazing fast,
outperforming closest competitor in hundreds (!) times in the Language
Shootout concurrency testing

so, the concurrent programming, may be, the only area at now, where
real-world, commercial programmers should prefer Haskell over all
other languages. in this light, leaving the concurrency outside of
language standard will decrease our chances of pushing the language to
the commercial arena and gathering critical mass of Haskellers

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: important news: refocusing discussion

2006-03-25 Thread isaac jones
On Sat, 2006-03-25 at 13:17 +0300, Bulat Ziganshin wrote:
 Hello Ross,
 
 Saturday, March 25, 2006, 4:16:01 AM, you wrote:
 
  On Fri, Mar 24, 2006 at 02:47:09PM -, Simon Marlow wrote:
  I think it would be a mistake to relegate concurrency to an addendum; it
  is a central feature of the language, and in fact is one area where
  Haskell (strictly speaking GHC) is really beginning to demonstrate
  significant advantages over other languages.  We should make the most of
  it.
 
  Essential for many applications, certainly, but central?  How can you
  say that?
 
 it becomes central language feature just because it's much easier to
 write concurrent programs in Haskell than in other languages and
 because ghc's implementation of user-level threads is blazing fast,
 outperforming closest competitor in hundreds (!) times in the Language
 Shootout concurrency testing

I don't think central to the language is a particularly helpful
concept here.  Let's try to frame debates like this in terms of
interests, not positions.  That is, an interest is we should be
able to write thread-safe libraries and a position is Haskell' should
have concurrency.  Once we understand each-others' interests, we can
look to find solutions that satisfy a compelling set of interests.

I'll try to frame some interests that various folks seem to have
expressed, and I admit that I may miss some and be wrong, so please add
to or correct the list below (maybe it should go on the wiki):

Possible Interests:
 1. I can write tools like filesystems, web servers, and GUIs in
Haskell'
 2. Libraries that I use are thread-safe
 3. I can compile my code with any Haskell' compiler
 4. Tools such as debuggers and tracers that claim to support Haskell'
actually work on my code.
 5. That there not be too many Haskell's
 6. That there be a diversity of Haskell' implementations
 7. That concurrency be reasonable to implement for existing
compilers/interpreters.
 8. That it be reasonable to implement for new compilers/interpreters.
 9. Show off how effective Haskell can be in this area (possibly
attracting new users).

By 5 I mean that it might be nice to have a core Haskell and a bunch
of addenda.  But this could cause no two Haskell' implementations to be
the same. (My Haskell' might have concurrency and FFI, but no class
system, or something.)  The more optional addenda we have, the more we
actually fracture the language.  We could be in the same situation we're
in today.

Isaac's Interests
 * 1-6, 9

Simon's Interests:
 * He's mentioned 9, I'm sure that there are others.

Ross and John Meacham I think have both expressed worry about 7 and 8.

I have no idea if it would work, but one solution that Simon didn't
mention in his enumeration (below) is that we could find a group of
people willing to work hard to implement concurrency in Hugs, for
example, under Ross's direction.  That might satisfy interest number 7.

Please help me to build this understanding of various folks' interests,
an solutions to satisfy them.

peace,

  isaac



Simon Marlow Wrote:
 It boils down to a choice between:
 
  (1) Haskell' does not include concurrency.  Concurrent programs 
  are not Haskell'.
 
  (2) Haskell' includes concurrency.  Concurrent programs are
  Haskell', but there are some compilers that do not implement
  all of Haskell'.
 
  (3) There are two variants of Haskell', Haskell' and
  Haskell'+Concurrency.  Compilers and programs choose which
  variant of the language they implement/are implemented in.
 
  (4) The same as (3), but the two variants are Haskell' and
  Haskell'-Concurrency  (where -Concurrency is a negative
  addendum, an addendum that subtracts from the standard).

-- 
isaac jones [EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: important news: refocusing discussion

2006-03-24 Thread Ross Paterson
On Wed, Mar 22, 2006 at 10:54:57AM -, Simon Marlow wrote:
 On 21 March 2006 23:51, isaac jones wrote:
  Concurrency is summarized here:
 
 http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/Concurrency
 
 I have updated the concurrency page with a skeleton proposal.

Do you envisage Haskell' implementations that do not support concurrency?

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: important news: refocusing discussion

2006-03-24 Thread Simon Marlow
On 24 March 2006 09:55, Ross Paterson wrote:

 Do you envisage Haskell' implementations that do not support
 concurrency? 

Clearly there will be some, the question is what status do they have.
It boils down to a choice between:

 (1) Haskell' does not include concurrency.  Concurrent programs 
 are not Haskell'.

 (2) Haskell' includes concurrency.  Concurrent programs are
 Haskell', but there are some compilers that do not implement
 all of Haskell'.

 (3) There are two variants of Haskell', Haskell' and
 Haskell'+Concurrency.  Compilers and programs choose which
 variant of the language they implement/are implemented in.

 (4) The same as (3), but the two variants are Haskell' and
 Haskell'-Concurrency  (where -Concurrency is a negative
 addendum, an addendum that subtracts from the standard).

I suspect that almost everyone agrees that (1) is not an option.  In
practical terms, there isn't much to choose between the others: from a
programmer's point of view, if they want to use concurrency they still
have to choose an implementation that supports it.

So I believe the issue is mainly one of perspective.  Until I wrote this
email I hadn't thought of (4) and my preference was for (2), but now I
quite like the idea of (4).  We would include concurrency in Haskell',
but provide a separate addendum that specifies how imlementations that
don't provide concurrency should behave.  One advantage of (4) over (3)
is that we can unambiguously claim that Haskell' has concurrencey.

This also lets us accommodate John Meacham's earlier point, that it
should be possible to write concurrency-safe libraries in a portable
way, and that means providing parts of Control.Concurrent even in the
absence of concurrency.  For example, MVars would be provided with an
implementation in terms of IORefs.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: important news: refocusing discussion

2006-03-24 Thread Simon Marlow
On 24 March 2006 12:28, Ross Paterson wrote:

 On Fri, Mar 24, 2006 at 11:30:57AM -, Simon Marlow wrote:
 So I believe the issue is mainly one of perspective.  Until I wrote
 this email I hadn't thought of (4) and my preference was for (2),
 but now I quite like the idea of (4).  We would include concurrency
 in Haskell', but provide a separate addendum that specifies how
 imlementations that don't provide concurrency should behave.  One
 advantage of (4) over (3) is that we can unambiguously claim that
 Haskell' has concurrencey. 
 
 And we can unambiguously state that there is only one Haskell'
 implementation (though a second is on the way).
 
 Sure, concurrency is essential to many applications, and should be
 precisely specified.  But it is also irrelevant to a lot of uses of
 Haskell (except for ensuring that one's libraries are also usable on
 concurrent implementations, as JohnM said).  A specification of the
 language without concurrency would be at least as valuable (having
 more implementations).  Perspective, as you say -- most people agree
 we need both -- but I think you're a bit too negative about the
 smaller variant. 

This is just a difference of opinion, and probably won't be easily
resolved.  It comes down to whether you think Haskell' should be a
language that is wide enough to include such applications as a web
server, or whether it has to stop short of including concurrency because
it's too hard to implement (and it's not always hard - the YHC guys
managed it in a matter of days, but I do realise it would be hard in
Hugs).

I think it would be a mistake to relegate concurrency to an addendum; it
is a central feature of the language, and in fact is one area where
Haskell (strictly speaking GHC) is really beginning to demonstrate
significant advantages over other languages.  We should make the most of
it.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: important news: refocusing discussion

2006-03-24 Thread Manuel M T Chakravarty
Simon Marlow:
 On 24 March 2006 12:28, Ross Paterson wrote:
 
  On Fri, Mar 24, 2006 at 11:30:57AM -, Simon Marlow wrote:
  So I believe the issue is mainly one of perspective.  Until I wrote
  this email I hadn't thought of (4) and my preference was for (2),
  but now I quite like the idea of (4).  We would include concurrency
  in Haskell', but provide a separate addendum that specifies how
  imlementations that don't provide concurrency should behave.  One
  advantage of (4) over (3) is that we can unambiguously claim that
  Haskell' has concurrencey. 
  
  And we can unambiguously state that there is only one Haskell'
  implementation (though a second is on the way).
  
  Sure, concurrency is essential to many applications, and should be
  precisely specified.  But it is also irrelevant to a lot of uses of
  Haskell (except for ensuring that one's libraries are also usable on
  concurrent implementations, as JohnM said).  A specification of the
  language without concurrency would be at least as valuable (having
  more implementations).  Perspective, as you say -- most people agree
  we need both -- but I think you're a bit too negative about the
  smaller variant. 
 
 This is just a difference of opinion, and probably won't be easily
 resolved.  It comes down to whether you think Haskell' should be a
 language that is wide enough to include such applications as a web
 server, or whether it has to stop short of including concurrency because
 it's too hard to implement (and it's not always hard - the YHC guys
 managed it in a matter of days, but I do realise it would be hard in
 Hugs).
 
 I think it would be a mistake to relegate concurrency to an addendum; it
 is a central feature of the language, and in fact is one area where
 Haskell (strictly speaking GHC) is really beginning to demonstrate
 significant advantages over other languages.  We should make the most of
 it.

I 100% agree!!  Personally, I think, after the FFI, a good story about
concurrency and exceptions is what H98 misses most for applications
other than variations on the compiler theme.

Manuel


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: important news: refocusing discussion

2006-03-24 Thread Ross Paterson
On Fri, Mar 24, 2006 at 02:47:09PM -, Simon Marlow wrote:
 I think it would be a mistake to relegate concurrency to an addendum; it
 is a central feature of the language, and in fact is one area where
 Haskell (strictly speaking GHC) is really beginning to demonstrate
 significant advantages over other languages.  We should make the most of
 it.

Essential for many applications, certainly, but central?  How can you
say that?

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: important news: refocusing discussion

2006-03-22 Thread Simon Marlow
On 21 March 2006 23:51, isaac jones wrote:

 Concurrency is summarized here:

http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/Concurrenc
y

I have updated the concurrency page with a skeleton proposal.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: important news: refocusing discussion

2006-03-22 Thread Manuel M T Chakravarty
Simon Marlow:
 On 21 March 2006 23:51, isaac jones wrote:
 
  Concurrency is summarized here:
 
 http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/Concurrenc
 y
 
 I have updated the concurrency page with a skeleton proposal.

Yes, good plan.

Manuel


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


important news: refocusing discussion

2006-03-21 Thread isaac jones
Greetings,

While discussion on this mailing list has been coming fast  furious,
actual tangible progress, even as measured on the wiki, has not been as
fast. 

To remedy this, we propose to focus immediately and intently on a few of
the most critical topics, and to focus all of our energies on them until
they are done.  We'd like to go so far as to ask folks to drop
discussion on other items until these are solved.

The goal of this approach is that we will spend the most time on the
critical (and hard) stuff, instead of leaving it for last.  We know that
we can spend a _lot_ of time and energy discussing relatively small
things, and so we want to make sure that these relatively small things
don't take up all of our time.  We will tackle them later.

The topics that John and I feel are critical, and rather unsolved,
are:
 * The class system (MPTC Dilemma, etc)
 * Concurrency
 * (One more, perhaps standard libraries)

The logic here is that Haskell' will be accepted by the community  if we
solved these problems, and if we go with some of the most robust and
uncontroversial extensions already out there.

We will probably partition the committee into subcommittees to focus on
each topic.

Our goal will be to bring these topics to beta quality by mid April.
That is, something that we could be happy with, but that perhaps needs
some polishing.  After that, we may try to pick the next most critical
topics with the goal of having everything at beta quality by the
face-to-face we're hoping to have at PLDI in June.

With an eye toward considering related proposals together, we've added a
topic field to the wiki, and a new query to the front page which
groups the proposals by topic:

http://hackage.haskell.org/trac/haskell-prime/query?status=newstatus=assignedstatus=reopenedgroup=topiccomponent=Proposalorder=priority

I'd like to ask folks to please bring currently open threads to a close
and to document the consensus in tickets.  Anyone can edit tickets, so
please don't be shy.


your chairs,

  Isaac Jones
  John Launchbury

-- 
isaac jones [EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: important news: refocusing discussion

2006-03-21 Thread Taral
On 3/21/06, isaac jones [EMAIL PROTECTED] wrote:
 I'd like to ask folks to please bring currently open threads to a close
 and to document the consensus in tickets.  Anyone can edit tickets, so
 please don't be shy.

Claus, can you document some of your FD work in the
FunctionalDependencies ticket? I think that the new confluence results
lends a lot towards the adoption of FDs in Haskell'.

--
Taral [EMAIL PROTECTED]
You can't prove anything.
-- Gödel's Incompetence Theorem
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: important news: refocusing discussion

2006-03-21 Thread isaac jones
On Tue, 2006-03-21 at 15:27 -0800, Ashley Yakeley wrote:
 isaac jones wrote:
 
  The topics that John and I feel are critical, and rather unsolved,
  are:
   * The class system (MPTC Dilemma, etc)
   * Concurrency
   * (One more, perhaps standard libraries)
 
 Could you summarise the current state of these?

AFAIK, the class system is summarized on this page:
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/MultiParamTypeClassesDilemma

Although there are some proposals here that are not really covered by
that topic, they should probably be considered together:
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/query?status=newstatus=assignedstatus=reopenedgroup=topiccomponent=Proposalorder=priority


Concurrency is summarized here:
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/Concurrency

and libraries have not really been discussed much at all.

peace,

  isaac

-- 
isaac jones [EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime