Re: FFI, safe vs unsafe

2006-03-30 Thread John Meacham
On Thu, Mar 30, 2006 at 10:44:36AM +0100, Simon Marlow wrote:
 You're optimising for the single-threaded case, and that's fine.  In
 GHC, a call-in is similar to what I outlined above except that we can
 optimise away the RPC and perform the call directly in the OS thread
 that requested it, due to the way bound threads are implemented.  Doing
 that requires that a lot more of the runtime needs to be thread-safe,
 though. 


yeah, if you actually have a OS threaded RTS, then everything is a whole
different ball of wax. But there is a lot to be said for a
state-threaded version like hugs. Even in C-land many people choose
state-threads over posix threads or vice versa depending on many
criteria and we shouldn't assume that one is necessarily superior.
state-threads arn't second class, just a different way to go.

Although I was skeptical at the beginning that we could come up with a
standard based on forkIO that could encompass both models without
compromising performance or implementation flexability, I now think that
we can! and that is good, because it means we won't need to make
concurrency an addendum or just accept the fact that many haskell-prime
implementations will be incomplete!


mainly, I think we need to keep a couple goals in mind, which are sometimes
in opposition, but not really so much:

 * not require anything that will rule out or arbitrarily reduce the
  efficiency of a absolutely-zero-overhead in the non-concurrent case
  implementation of straightforward state-threads.

 * not require anything that will inhibit the SMP scalability or
   scheduling freedom of OS threaded implementations. 

I think if we stick to these 'caps' at both ends then all the
intermediate implementations we have talked about will be accomodated
and since state-threads can _almost_ be implemented in pure haskell, we
can be pretty sure we arn't constraining future as yet to be thought of
implementation models too much.

A sticky point might be whether we say anything about duplicated work,
however, the haskell report never really says anything about guarenteed
sharing anyway so we can probably be silent on the matter.

we certainly shouldn't treat state-threads as second class or a lesser
implementation of the standard though! they can often be faster than OS
threads but with their own set of tradeoffs.

glossary:

OS threaded - ghc -threaded, context switching at arbitrary points, not
necessarily under the control of the haskell runtime.

state-threading - hugs,jhc context switching at block-points chosen by the
implementation and user via yield.

yhc is somewhere in between. basically state-threading, but with more
context switching under the control of the yhc run-time.

 It's true that this is a fairly large overhead to impose on all Haskell
 implementations.  I'm coming around to the idea that requiring this is
 too much, and perhaps multi-threaded call-ins should be an optional
 extra (including concurrent/reentrant foreign calls).

yeah, a much touted feature of haskell concurrency is that it is _fast_
_fast_, we shouldn't compromise that or its potential without very good
reason.

John

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


RE: Pre-emptive or co-operative concurrency (was: Concurrency)

2006-03-30 Thread Simon Marlow
On 29 March 2006 17:34, Neil Mitchell wrote:

 context-switches happen only on specific events, which every
 thread will usually engage in, although it need not always do so:
 
 1 only calls to yield
 2 any calls to concurrency library api
 3 any allocation
 
 The Yhc concurrency switches every n instructions, and therefore even
 an evil thread cannot lock up the system.
 
 Of course, even with fully pre-emptive scheduling, you've still got
 deadlocks... 

Neil,

What does YHC do about in-progress thunk evaluations when a context
switch happens?  Does it use blackholing like GHC, or does it
portentially duplicate the work, or something else?

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


Re: Pre-emptive or co-operative concurrency (was: Concurrency)

2006-03-30 Thread John Meacham
On Thu, Mar 30, 2006 at 10:54:01AM +0100, Simon Marlow wrote:
 Not true - in GHC with SMP a thread doing no allocation can be running
 concurrently with any number of other threads.  It's only the
 single-threaded implementation that has this bug where a thread that
 doesn't allocate can starve the other threads.  In fact, even on a
 uniprocessor, you can use GHC's SMP mode to work around the bug by
 pretending you have 2 CPUs.

it should be noted that I don't consider this a bug, but a design
choice. of course, since you made the choice differently then for GHC it
is a bug :)


 GHC's SMP mode is truly preemptive, operations from multiple threads can
 be arbitrarily interleaved.  So let's stop saying that all known
 implementations are non-preemptive, please ;-)

well, as preemptive as the pthreads implementation at least. which is
usually very, but not so with some userspace implementations of
pthreads.

Both are allowed by the standard so counting on preemption is a bad
idea in general, even with ghc. (though, perhaps this isn't true, ghc
has its own mini-threads underneath OS threads in -threaded mode if I
understand it properly and that makes things less simplistic.)

however, this is all just reiteration of the never count on the
scheduler rule when writing threaded apps when you didn't write the
operating system :) (hard real-time bug-free systems exempt)

John

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


Re: Pre-emptive or co-operative concurrency (was: Concurrency)

2006-03-30 Thread Claus Reinke

GHC's SMP mode is truly preemptive, operations from multiple threads can
be arbitrarily interleaved.  So let's stop saying that all known
implementations are non-preemptive, please ;-)


but gladly, if that is the default!-) 

so if we take that hypothetical example of foreign exporting GHC's 
concurrency support, can we assume that the (IO a)s implemented in 
foreign code will be given their own OS thread when using that 
concurrency library? all of them, or only the non-atomic ones?


if, say, Hugs was to foreign import that library from GHC, its IO actions
wouldn't do much (GHC-side )allocation; and if Hugs was to import that
same library from YHC, it wouldn't do many (YHC-side) abstract machine
steps; etc.; we could try real time-slicing, but how would we suspend/restart
foreign code? so there doesn't seem to be much choice for integrating
foreign IO code into the schedule, other than giving it its own OS-thread;
of course, Hugs' IO actions may not be thread-safe, so that may not
be an option, either.

the point being: the FFI says something about how to integrate
foreign and Haskell memory management; should it also say something
about threadability of foreign code (wrt to scheduling, and wrt thread-safety)?

cheers,
claus

ps: Neil said:

If all Haskell' prime implementations depend on GHC the library,
then do we really have many Haskell' prime implementations, or just a
pile of wrappers around GHC?


are you implying that implementing external libraries in Haskell is
in any way inferior to implementing them in C?-)

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


Re: FFI, safe vs unsafe

2006-03-30 Thread Claus Reinke

It is not like inserting yields needs to be done much at all since we have
progress guarentees, so we know the program is doing something and on
any blocking call that could potentially take a while, the library will
yield for you.


where do we get the progress guarantees from? do we need a 
yield-analysis? something that will automatically insert yields
in the code after every n atomic steps, and complain if it cannot 
infer that some piece of code is atomic, but cannot insert a yield 
either? how much of the burden do you want to shift from the

implementer to the programmer?

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


Re: FFI, safe vs unsafe

2006-03-30 Thread John Meacham
On Thu, Mar 30, 2006 at 01:16:08PM +0100, Claus Reinke wrote:
 It is not like inserting yields needs to be done much at all since we have
 progress guarentees, so we know the program is doing something and on
 any blocking call that could potentially take a while, the library will
 yield for you.
 
 where do we get the progress guarantees from? do we need a 
 yield-analysis? something that will automatically insert yields
 in the code after every n atomic steps, and complain if it cannot 
 infer that some piece of code is atomic, but cannot insert a yield 
 either? how much of the burden do you want to shift from the
 implementer to the programmer?

no, because there are only certain defined actions that can switch a
thread's state from 'runnable' to 'not-runnable'. In order to
meet the progress guarentee you just need to make sure that when the
current thread switches from 'runnable' to 'not-runnable' that another
thread is chosen.

examples of these points would be:

 - calling a foreign concurrent import
 - waiting for input on a handle
 - waiting for a UNIX signal
 - changing thread priorities (possibly)

in any case, the compiler need do nothing special in general, it is
basically a library issue.

John


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


RE: FFI, safe vs unsafe

2006-03-30 Thread Simon Marlow
On 30 March 2006 13:05, John Meacham wrote:

 but the debugging/deterministic
 benefits could be useful. you could be guarenteed to reproduce a given
 sequence of context switches which could make finding concurrent
 heisenbugs easier.

Actually +RTS -C0 already gives deterministic concurrency in GHC.  And
you're right, it's essential for debugging.  SMP has made my life
somewhat more painful of late :-)

 or something like concurrent 'hat' or another
 debugger might find it easier to work in such a mode.
 
 In any case, what I think of when I think of 'writing a portable app'
 is that from _the spec alone_ I can write something that I can expect
 to work on any compliant system. This goal can be achieved to various
 degrees. But if the specification says, 'the implementation might be
 cooperative' and I write assuming that, then it pretty much will
 definitly work anywhere perhaps with some spurious 'yields'.

Absolutely, but a preemptive implementation has no way to tell you if
you missed out a 'yield', and that essentially is the same as
non-portabiliy.  It doesn't matter that the spec told you you needed the
yield, if the implementation you're using works fine without it,
non-portable software will be the result.

What's more, in some cases it isn't even possible to insert enough
yields.  It's entirely reasonable to have an application that runs some
CPU-bound pure computation in one thread and a GUI in some other
threads.  This type of application can't be implemented if the standard
guarantees nothing more than cooperative scheduling.  Worse, no static
property of the code tells you that.

 however
 if it says something to the effect of 'runnable threads will be
 timeshared via some fair algorithm for some definition of fair'

No, I'm suggesting the specific fairness guarantees mentioned earlier
(and on the wiki page).

 then
 it doesn't help much writing portable apps since you would want to
 test on the various compilers to see what their definiton of fair
 is.

Given those fairness guarantees, programmers will not need to care
whether the implementation is using preemption based on allocation, or
one based on reductions, or arbitrary inter-instruction preemption.
Because it is hard to write a program that can tell the difference,
especially if you stick to using proper synchronisation primitives,
nobody will do it by accident.

Contrast this with a standard that allows both cooperative and
preemptive scheduling.  It's much easier to write a program that can
show the difference, and I'm worried that people will do it all the
time, by accident.  That's bad.

 I thought yhc supported unboxed values, so a loop like
 
 count 0 = 0
 count n = count (n - 1)
 
 count 10
 
 could block the runtime (assuming it was properly unboxed by the
 compiler) since it never calls back into it and is just a straight up
 countdown loop?

are we talking about the same compiler?  YHC is fully interpreted, has
no unboxed types, and AFAIK it is impossible to write any code that
doesn't get preempted after a while.

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


RE: Pre-emptive or co-operative concurrency (was: Concurrency)

2006-03-30 Thread Simon Marlow
On 30 March 2006 12:44, Claus Reinke wrote:

 so if we take that hypothetical example of foreign exporting GHC's
 concurrency support, can we assume that the (IO a)s implemented in
 foreign code will be given their own OS thread when using that
 concurrency library? all of them, or only the non-atomic ones?

I'm sorry, I completely fail to see what you're getting at with this
line of discussion.  Could you say in more detail how you expect to
provide access to concurrency via the FFI?  And what the point of it is?
(it's not obvious how to foreign export forkIO, for example).

 the point being: the FFI says something about how to integrate
 foreign and Haskell memory management; should it also say something
 about threadability of foreign code (wrt to scheduling, and wrt
 thread-safety)? 

If Haskell' includes concurrency then of course it must say something
about the behaviour of foreign calls with respect to concurrency (if
that's what you mean by threadability).  Is that what you're asking?

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


RE: seq as a class method

2006-03-30 Thread Simon Marlow
Hi Andy,

This is a good question, and something we hit in GHC quite often too.
Our solution is to use a mixture of strictness annotations, deepSeq,
smart constructors, and hand-waving optimism that things will be
evaluated soon enough anyway.

Having to occasionally deepSeq the structore to force the thunks has
quite a few problems, as you say.  A better approach might be to
establish a guarantee that the data type isn't leaky; that is, every
field is either strict, or guaranteed to be deepSeq'd at construction by
a smart constructor.  To enforce the smart constructor, you might want
ReadOnlyConstructors (see the Haskell' proposal).

So for things like this:

   regs ::  !Array Int RegVal

You either use a strict Array type, or deepSeq the Array when
constructing the record.

To support record update without having to re-deepSeq everything in the
record you would want to provide record updaters as part of the abstract
datatype.

Hope this helps...

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


Re: FFI, safe vs unsafe

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

  I thought yhc supported unboxed values, so a loop like
  
  count 0 = 0
  count n = count (n - 1)
  
  count 10
  
  could block the runtime (assuming it was properly unboxed by the
  compiler) since it never calls back into it and is just a straight
  up countdown loop?
 
 are we talking about the same compiler?  YHC is fully interpreted, has
 no unboxed types, and AFAIK it is impossible to write any code that
 doesn't get preempted after a while.

Indeed.  But unboxing is not the issue - the main reason is that yhc
cannot currently compile that code into a loop - jumps only go forwards
in the bytecode, never backwards.  The only possible bytecode
representation of a loop is as a recursive call, which immediately
presents an opportunity to insert a yield.

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


Re: Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

2006-03-30 Thread Tomasz Zielonka
On Wed, Mar 29, 2006 at 12:50:02PM +0100, Jon Fairbairn wrote:
 [...]

 but add [a] pragma[s] to the effect that evaluation should
 be input driven, and that ll, ww, and cc are to be given
 equal time. Something like {-# STEPPER cs; ROUND_ROBIN
 ll,ww,cc #-} (please do not take this as a suggestion of
 real syntax!).
 
 The way I would implement this is to add a new primitive,
 STEP, which is like seq except that it only evaluates its
 argument until it encounters another STEP. (It really isn't
 much different to seq).

 [...]
 
 It seems to me that this wouldn't take much effort to
 implement, but it would provide a simple means of removing
 space leaks from a whole bunch of programmes without
 mangling the source code much.

Actually, it may require no effort from compiler implementors.
I just managed to get the desired effect in current GHC! :-)

I implemented your idea of stepper by writing the function stepper that
rewrites the list invoking yield every 500 processed elements. This
way I can concurrently consume the list without the space leak - when a
thread evaluates too many list elements, it gets preempted. I think it
suffices if RTS employs a round-robin scheduler. I am not sure it's
important.

The code isn't as beautiful as the naive wc implementation. That's
because I haven't yet thought how to hide newEmptyMVar, forkIO, putMVar
i takeMVar. Perhaps someone will come up with a solution to this.

import Control.Concurrent
import Control.Monad
import System.IO.Unsafe (unsafePerformIO)

stepper l = s n l
  where
n = 500
s 0 (x:xs) = unsafePerformIO $ do
yield
return (x : s n xs)
s i (x:xs) = x : s (i-1) xs
s _ [] = []

main = do
cs - liftM stepper getContents
ll - newEmptyMVar
ww - newEmptyMVar
cc - newEmptyMVar
forkIO $ putMVar ll $! length (lines cs)
forkIO $ putMVar ww $! length (words cs)
forkIO $ putMVar cc $! length cs
takeMVar ll = print
takeMVar ww = print
takeMVar cc = print

See how well it works:

$ cat words words words words | ./A +RTS -sstderr
./A +RTS -K8M -sstderr
394276
394272
3725868 - that's the size of cs
643,015,284 bytes allocated in the heap
 72,227,708 bytes copied during GC
109,948 bytes maximum residency (46 sample(s))  - no space leak!

   2452 collections in generation 0 (  0.33s)
 46 collections in generation 1 (  0.00s)

  2 Mb total memory in use  - no space leak!

  INIT  time0.00s  (  0.01s elapsed)
  MUT   time1.25s  (  1.27s elapsed)
  GCtime0.33s  (  0.36s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time1.58s  (  1.64s elapsed)

  %GC time  20.9%  (22.0% elapsed)

  Alloc rate514,412,227 bytes per MUT second

  Productivity  79.1% of total user, 76.2% of total elapsed

Thanks for your idea, Jon! :-)

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


Re: Pre-emptive or co-operative concurrency (was: Concurrency)

2006-03-30 Thread Neil Mitchell
Hi

 What does YHC do about in-progress thunk evaluations when a context
 switch happens?  Does it use blackholing like GHC, or does it
 portentially duplicate the work, or something else?

As far as I am aware, since it only switches on instruction
boundaries, it never has to worry about this. It certainly doesn't
duplicate work, and I think the blackholing is just used for circular
dependancy problems, exactly as before threading became used.

To be honest, for concurrency I'm a bit out of my depth, Tom did all
the design and implementation.

Thanks

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


Specification of newtype deriving

2006-03-30 Thread Twan van Laarhoven
The Trac page for 'Generalised deriving for newtype' remarks that it is 
'difficult to specify without saying the same representation'.


I assume that no one has tried yet, so I'll take a shot at it.

Say we have a declaration of the form:
 class C a where
x :: T a -- any type that can contain a
..

 -- instance declaration, can also be more general
 instance Ctx p = C (OldT p) where
x = ..
..

 newtype NewT p = Constr (OldT p)
deriving C

Where p can be any number of type variables and Ctx is a context 
depending on them.

The instance for C NewT can be derived with the following algorithm.

The new instance declaration will be:
 instance Ctx b = C (NewT b) where
x = wrap_T (x :: T a)
..

Now the details of the wrap function depend on the type T. There are 
four cases:


1. If T is a type not containg a, i.e.
type T a = T'
   then define:
wrap_T   x = x
unwrap_T x = x

2. If T is exactly the type a, possible applied to arguments:
type T a = a
   or
type T a = a b ..
   then define:
wrap_T   x = Constr x
unwrap_T x = case x of (Constr x') - x'

3. If T is a function type:
type T a = T1 a - T2 a
   then define
wrap_T   f = \arg - wrap_T2   (f (unwrap_T1 arg))
unwrap_T f = \arg - unwrap_T2 (f (wrap_T1   arg))

4. If T is an abstract data type:
data T a = C1 (T1 a) ..
 | ..
   then define:
wrap_T   x = case x of
 (C1 x1 ..) - C1 (wrap_T1 x1) ..
 ..
unwrap_T x = case x of
 (C1 x1 ..) - C1 (unwrap_T1 x1) ..
 ..
   With an alternative for each constructor of T.

All these wrap/unwrap functions are specific for the type NewT and the 
definition x. The T in wrap_T should be read as a subscript where T is 
the actual type, and not as a value named wrap_T. '..' stands for a 
repetition of the same principle.





Here is also an example from the wiki page:
 -- | Unique integer generator monad transformer.
 newtype UniqT m a = UniqT (StateT Int m a)
deriving Monad

The class is:
 class Monad m where
(=) :: m a - (a - m b) - m b
..

There is an instance:
 instance Monad m = Monad (StateT s m)

Now the newtype declaration desugars to (using wr_T for wrap_T and un_T 
for unwrap_T):

 newtype UniqT m a = UniqT (StateT Int m a)

 instance Monad m = Monad (UniqT m a) where
  (=) = w (= :: StateT Int m a)
   where
wr_T  f = \arg - wr_T2 (f (un_T1 arg)) -- m a - (a - m b) - m b
un_T1 x = case x of (UniqT x') - x'-- m a
wr_T2 f = \arg - wr_T4 (f (un_T3 arg)) --(a - m b) - m b
un_T3 f = \arg - un_T6 (f (wr_T5 arg)) -- a - m b
wr_T4 x = UniqT x   --  m b
wr_T5 x = x -- a
un_T6 x = case x of (UniqT x') - x'--  m b

Cleaning up leads to:
 instance Monad m = Monad (UniqT m a) where
wr_T = \(UniqT a0) a2 - UniqT
  (a0 = ( \a3 - case (a2 a3) of (UniqT x') - x' ))

Which is essentially the same as what the programmer would have written 
himself.


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


Re: seq as a class method

2006-03-30 Thread Tomasz Zielonka
On Wed, Mar 29, 2006 at 05:58:24PM +0100, Jon Fairbairn wrote:
 Or do what I suggested in
 http://www.haskell.org//pipermail/haskell-prime/2006-March/001120.html
 [EMAIL PROTECTED] and make seq a
 pragma.  It really doesn't matter that pragmas in C are
 optional: we don't have to follow that.

Would that really change that much. Anyone who likes the old
seq function (less characters to type than with pragma) will
be able to define it:

seq a b = {-# SEQ a #-} b

Perhaps if you allowed syntax for forcing many expressions
people would be more willing to use it:

{-# SEQ a, b, c, d #-} e

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


Re: FFI, safe vs unsafe

2006-03-30 Thread Claus Reinke

I updated the ForeignBlocking wiki page with what I believe is the
current state of this proposal; see


didn't I mention that concurrent may be inappropriate and misleading, 
and that I think it is bad practice to rely on the programmer annotating 
the dangerous cases, instead of the safe cases?


wouldn't the safe approach be to assume that the foreign call may do 
anything, unless the programmer explicitly tells you about what things 
it won't do (thus taking responsibility).


cheers,
claus


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


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


Re: FFI, safe vs unsafe

2006-03-30 Thread John Meacham
On Thu, Mar 30, 2006 at 09:39:44PM +0100, Claus Reinke wrote:
 I updated the ForeignBlocking wiki page with what I believe is the
 current state of this proposal; see
 
 didn't I mention that concurrent may be inappropriate and misleading, 
 and that I think it is bad practice to rely on the programmer annotating 
 the dangerous cases, instead of the safe cases?

I think dangerous is a misleading term here. you are already using the
FFI, all bets are off. and it is not really dangerous to accidentally
hold up your VM when you didn't expect, it is more just a simple bug.

Unsafe or dangerous means potentially leading to undefined behavior, not
just incorrect behavior or we'd have to label 2 as unsafe becaues you
might have meant to write 3. :)

 wouldn't the safe approach be to assume that the foreign call may do 
 anything, unless the programmer explicitly tells you about what things 
 it won't do (thus taking responsibility).

I think the worse problem will be all the libraries that are only tested
on ghc that suddenly get very poor performance or don't compile at all
when attempted elsewhere.

However, the 'nonreentrant' case actually is dangerous in that it could
lead to undefined behavior which is why that one was not on by default.

John

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


deeqSeq proposal

2006-03-30 Thread Andy Gill
For the reasons talked about in previous posts, I'd like to propose a  
deepSeq

for Haskell'.

 - It provides a mechanism to allow an effective, systematic  
tracking down of

 a class of space leaks.
 - It provides a mechanism to simply stomp on a class of space leaks.
 - It avoids the user having to explicitly declare instances for a  
homebrew deepSeq

  for every type in your program.
- It has a declarative feel; this expression is hyper strict.
- Is a specification of strictness.
- It will open up various optimization opportunities, avoiding  
building thunks.

   (I dont talk about this more, but I'm happy to elaborate)
- It can have an efficient implementation, or a simple (slow)  
implementation.

   (The fast implementation one can be used to stomp space leaks,
   the slow one can help find the same leaks.)

What I would like to propose for Haskell' are four things:

(Essential) Add a deepSeq function into Haskell'

deepSeq :: a - b - b

- Don't really care if its in a class or not; would prefer not for
   the reasons John Hughes talked about.
- This would deepSeq all its children for regular constructors.
- deepSeq would not indirect into IO or MVar.
- functions would be evaluated to (W?)HNF.
- IO, ST are functions under the hood.

(Easy) Add a $!! function, and a strict function

f $!! a = a `deepSeq` f a
strict a = a `deepSeq` a

(Nice) Add a !! notation, where we have ! in datatypes.

data StrictList a = Cons (!!a) (!!StrictList a) | Nil

(Perhaps) Add a way of making *all* the fields strict/hyperstrict.

data !!StrictList a = ..,

We could also do this for !

--

Implementation:

deepSeq (RAW_CONS is_deep_seq'd_bit ... fields ) =
if is_deep_seq'd_bit == True
then return  /* hey, we've already deepSeq'd this */
else set is_deep_seq'd_bit to True.
 deepSeq (field_1)
 ...
 deepSeq (field_n)
deepSEQ (REF/MVAR...) = return

So we only deepSeq any specific constructor once! Sorta like lazy  
evaluation :-)

We'd need to catch exceptions, unset the is_deep_seq'd_bit, so that any
subsequent call of deepSeq would also have the option of raising the  
exception.


So,

 - How easy is this to add to the compilers? It looks pretty simple  
to me,

   and would provide huge bang-for-buck for Galois.
 - Any alternatives to the key concern; stomping on space leaks.
   (This proposal is orthogonal to the seq/Class discussion)

Andy Gill
Galois

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


MVar semantics: proposal

2006-03-30 Thread John Meacham
Based on discussion, I'd like to offer up this concrete proposal when it
comes to MVars, IORefs, and what we can guarentee when it comes to their
interaction with concurrency.

My wording can use some cleaning up but I want to get this out there
while it is fresh in mind  and before I forget the subtleties that led
me to this formulation.

its primary goals are
 * let us reason sanely about and provide the tools needed to write concurrent
   programs.
 * not break SMP scalability. programs we write now should work on
   systems of the future.

some definitions

action - a memory read/write either MVar or IORef that is theoretically
observable by a different thread, not necessarily atomic or ordered.

sequence point - exactly and only the actions putMVar and takeMVar

in a given thread, for some sequence of actions before a sequence point,
and some sequence of actions after it. another particular thread may
observe those actions in an arbitrary order, at an arbitrary time in the
future, except actions may not cross the sequence point boundry.

for example

thread 1 :  A B SP C
thread 2 may observe A B C  or B A C, but not A C B. 

another formulation would be that if any action after the sequence point
is observable, then all actions before it are guarenteed to be
observable in the current thread.

putMVar and takeMVar are atomic.

this is the _one and only_ guarentee when it comes to different threads
observing the same memory locations. in particular, IORefs cannot safely
be used except in a single-threaded manner.

This is a _pairwise guarentee_ between specific threads, for
threads 1,2,and 3 where thread 1 is writing to memory. threads 2 and 3
may observe completly different orderings but each is independently
subject to the sequence point constraint. You cannot reason about the
observable behavior of a group of threads except insofar as what you can
infer by applying this rule pairwise to the members of the group. 

sequence points are _not_ atomic global events. for the case above

thread 1: A B SP C

thread 2 might see A B C  before thread 3 even sees A. however both are
guarenteed to see A and B before they see C. just because one thread
reaches and passes a sequence point, it does not mean any other thread
has done so. 

how this relates to IORefs:

IORefs do not introduce sequence points nor are operations on them
guarenteed to be atomic. given the sequence point constraint above, the
following rule is needed for safety

IORefs must be used in a single threaded manner, when IORefs are
protected by an MVar, the MVar _must_ be locked by the same thread that
is using the IORefs. so no locking an MVar and then telling another
thread to go ahead and modify some IORefs as the other thread may not
have even observed the 'locking' sequence point yet.

I believe this lets us sanely reason about concurrent accesses to memory
and won't hamper SMP scalable implementations of haskell.

notes:

We should drop atomicModifyIORef since we have MVars, for architectures
with only a test and set instruction and no atomic exchange, supporting
atomicModifyIORef would entail the same overhead as MVars.
atomicModifyIORef also cannot (easily) be implemented on implementations
that use update-in-place rather than indirections for thunk updates.

IORefs are not even guarenteed to be atomic. so, if thread 1 writes A
then B to an IORef, thread 2 is not even guarenteed to see A or B when
it reads it. it may see an intermediate value or even crash the system.
if however thread 1 creates a sequence point after writing to the IORef
and thread 2 waits for that sequence point to be visible (by say waiting
on an MVar) then it may safely read the IORef.

if you have not guessed, sequence points correspond exactly to where
memory barriers need to be placed in the instruction stream or the much
more expensive bus locks on architectures that don't support true memory
barriers (cough. x86.). Using the weaker memory barrier semantics for
sequence points is a concious decision as it is vital vital for
reasonable SMP scaling and global atomic sequence points can be
simulated when needed with MVars between an arbitrary number of threads
by pairwise sequenceing them. (perhaps we can provide some library
routines to make this easy if it turns out to be a common thing people
want?)

John


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


Re: FFI, safe vs unsafe

2006-03-30 Thread Claus Reinke
didn't I mention that concurrent may be inappropriate and misleading, 
and that I think it is bad practice to rely on the programmer annotating 
the dangerous cases, instead of the safe cases?


I think dangerous is a misleading term here. you are already using the
FFI, all bets are off. and it is not really dangerous to accidentally
hold up your VM when you didn't expect, it is more just a simple bug.


perhaps dangerous was too strong a term, but if programmers don't
annotate an ffi declaration, what is more likely: that they meant to state
a property of that function, or that they didn't mean to? 

if there is a way to avoid simple bugs by not making assumptions about 
undeclared properties, then I'd prefer that to be the default route. if, 
on the other hand, programmers do annotate the ffi declaration, then 
it is up to them to make sure that the function actually has the property 
they claim for it (even in such cases, Haskell usually checks the 
declaration, but that isn't an option here).


Unsafe or dangerous means potentially leading to undefined behavior, 
not just incorrect behavior or we'd have to label 2 as unsafe becaues 
you might have meant to write 3. :)


you mean your compiler won't catch such a simple mistake?-)

but, seriously, that isn't quite the same: if I write a Num, it's my 
responsibility to write the Num I meant, because the implementation

can't check that. but if I don't write a Num, I'd rather not have the
implementation insert one that'll make the code go fastest, assuming
that would always be my main objective! (although that would be
a nice optional feature!-)

wouldn't the safe approach be to assume that the foreign call may do 
anything, unless the programmer explicitly tells you about what things 
it won't do (thus taking responsibility).


I think the worse problem will be all the libraries that are only tested
on ghc that suddenly get very poor performance or don't compile at all
when attempted elsewhere.


- GHC and the other implementations should issue a warning for
   using non-standard or non-implemented features (that includes code
   that won't obviously run without non-standard features)
- if an implementation doesn't implement a feature, there is no way
   around admitting that, standard or not
- if adding valid annotations are necessary to make non-GHC 
   implementations happy, then that's what programmers will have to do 
   if they want portable code; if such annotation would not be valid, we 
   can't pretend it is, and we can't pretend that other implementations 
   will be able to handle the code


- if only performance is affected, that is another story; different
   implementations have different strengths, and the standard shouldn't
   assume any particular implementation, if several are viable
- but: if certain kinds of program will only run well on a single 
   implementation, then programmers depending on that kind of program 
   will only use that single implementation, no matter what the standard 
   says (not all my Haskell programs need concurrency, but for those 
   that do, trying to fit them into Hugs is not my aim)



However, the 'nonreentrant' case actually is dangerous in that it could
lead to undefined behavior which is why that one was not on by default.


why not be consistent then, and name all attributes so that they are off 
by default, and so that implementations that can't handle the off case will

issue a warning at least?

cheers,
claus

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


Re: FFI, safe vs unsafe

2006-03-30 Thread John Meacham
On Fri, Mar 31, 2006 at 12:52:11AM +0100, Claus Reinke wrote:
 didn't I mention that concurrent may be inappropriate and misleading, 
 and that I think it is bad practice to rely on the programmer annotating 
 the dangerous cases, instead of the safe cases?
 
 I think dangerous is a misleading term here. you are already using the
 FFI, all bets are off. and it is not really dangerous to accidentally
 hold up your VM when you didn't expect, it is more just a simple bug.
 
 perhaps dangerous was too strong a term, but if programmers don't
 annotate an ffi declaration, what is more likely: that they meant to state
 a property of that function, or that they didn't mean to? 
 
 if there is a way to avoid simple bugs by not making assumptions about 
 undeclared properties, then I'd prefer that to be the default route. if, 
 on the other hand, programmers do annotate the ffi declaration, then 
 it is up to them to make sure that the function actually has the property 
 they claim for it (even in such cases, Haskell usually checks the 
 declaration, but that isn't an option here).

Well, I would consider the performance bug the more serious one. in
fact, they both are performance/scalability bugs rather than correctness
ones. but one is obvious when you get it wrong, the other is subtle and
could go unnoticed a long time and just make you think haskell is a slow
language. we should make it so the obvious one is the more likely
failure route so people fix it right away.
 
 wouldn't the safe approach be to assume that the foreign call may do 
 anything, unless the programmer explicitly tells you about what things 
 it won't do (thus taking responsibility).
 
 I think the worse problem will be all the libraries that are only tested
 on ghc that suddenly get very poor performance or don't compile at all
 when attempted elsewhere.
 
 - GHC and the other implementations should issue a warning for
using non-standard or non-implemented features (that includes code
that won't obviously run without non-standard features)
 - if an implementation doesn't implement a feature, there is no way
around admitting that, standard or not

well, there is if you didn't need the feature in the first place, but
didn't realize it because it was obscured. the bigger danger is that the
feature will be implemented, but very sub-optimally as in, hundreds of
times slower than a fast call could easily be true so you get a very
silent but fatal bug. FFI routines do need to be annotated correctly,
sometimes for correctness and sometimes for performance. when
correctness is at stake, you should err on the side of correct, when
performance is at stake you should err on the side of what will cause
the most rukus when you get it wrong :)

 However, the 'nonreentrant' case actually is dangerous in that it could
 lead to undefined behavior which is why that one was not on by default.
 
 why not be consistent then, and name all attributes so that they are off 
 by default, and so that implementations that can't handle the off case will
 issue a warning at least?

yeah, that is what I originally proposed, but Simon brought up the good
point (paraphrasing, I think this was his reasoning) that 'reentrant' is
important for the safety of the system (as in, segfaults and corruption
result when getting it wrong) while 'concurrent' is simply a choice on
the part of the programmer as to what behavior they want.

John

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


thread priorities?

2006-03-30 Thread John Meacham
Thinking about it some. I think we will need some sort of very basic
thread priorities.

honoring these priorities will be _manditory_ for cooperative
implementations but advisory for preemptive ones that meet the fairness
guarentees. priorities are sometimes needed in cooperative systems to
ensure certain things get run, but the fairness guarentees of preemptive
systems make them less important. Another reason to make them advisory
in preemptive implementations is because they might be using OS level
threads and hence not have their own scheduler to tweak priorities in.


I am thinking 

threadSetPriority :: ThreadID - Int - IO ()
threadSetPriority = ...

with a small modification to the progress guarentee saying that when
threads of different priorities are runnable, one of the threads of the
highest priority will be running. we should also say something about
priority inheritance via MVars...

but perhaps this is too complicated for the spec and should be left up
to the implementations (or just make it always advisory). let me know
what y'all think.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
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