Re: FFI, safe vs unsafe
On Fri, Mar 31, 2006 at 06:41:18PM -0500, Wolfgang Thaller wrote: > >I am confused, why would anything in particular need to happen at all? > > > >the threads are completly independent. The non-concurrent calls could > >just be haskell code that happens to not contain any pre-emption > >points > >for all it cares. in particular, in jhc, non-concurrent foreign > >imports > >and exports are just C function calls. no boilerplate at all in either > >direction. calling an imported foreign function is no different than > >calling one written in haskell so the fact that threads A and B are > >calling foregin functions doesn't really change anything. > > In an implementation which runs more than one Haskell thread inside > one OS thread, like ghc without -threaded or hugs, the threads are > NOT completely independent, because they share one C stack. So while > bar executes, stack frames for both foreign functions will be on the > stack, and it will be impossible to return from foo before bar and > the foreign function that called it completes. I think this kind of > semantics is seriously scary and has no place as default behaviour in > the language definition. no, state-threads, a la NSPR, state-threads.sf.net, or any other of a bunch of implementations. each thread has its own stack, you 'longjmp' between them. it can almost practically be done in portable C except the mallocing of the new stack, but there are many free libraries (less a library, more a header file with some #ifdefs) for all processors out there that support that, or at least that gcc supports in the first place. this would be by far the easist way to add concurrency to any haskell compiler, other than the addition of the 'create a new stack' and 'longjmp' primitives, it can be implemented 100% in the standard libraries with haskell code. that is why I am confident in saying it probably won't rule out future implementations we have not thought of yet. since it is mostly pure haskell anyway. > If you implement concurrency by using the pthreads library, you need > to either make sure that only one thread mutates the heap at a time, > or deal with SMP. In either case, concurrent foreign calls would be > trivial. indeed. but pthreads has its own tradeoffs. there is certainly room for both types of haskell implementations. > >>4.) Should there be any guarantee about (Haskell) threads not making > >>any progress while another (Haskell) thread is executing a non- > >>concurrent call? > > > >I don't understand why we would need that at all. > > Good. Neither do I, but in the discussions about this issue that we > had three years ago several people seemed to argue for that. wacky. I can't think of a reason, it would be quite tricky to pull off with a fully pthreaded implementation anyway. > >>5.) [...] So what > >>should the poor library programmer A do? > > > >He should say just 'reentrant' since concurrent isn't needed for > >correctness because the tessalation routines are basic calculations > >and > >will return. > > Let's say they will return after a few minutes. So having them block > the GUI is a show-stopper for programmer C. > And if programmer C happens to use a Haskell implementation that > supports "concurrent reentrant" but also a more efficient "non- > concurrent reentrant", he will not be able to use the library. well, I think he has a choice to make there about what is more important to him. I admit, it has to be a judgement call at some point, as eventually performance problems become correctness ones. but perhaps this is an argument for a concurrent-hint flag, "make this concurrent and reentrant if possible, but its gonna be reentrant anyway no matter what" I mean, one could bend the rules any say coooperative systems do implement "concurrent reentrant" with just an incredibly crappy scheduling algorithm, but I think I'd rather have it fail outright than "pretend". but a 'concurrent-hint' flag could be useful, as a library writer may not know the preference of his user. a completely different solution would be just to foreign import the routine twice, with each convention and have some way for the user of a library to choose which one they want, perhaps with a flag. of course, both might not be available with all implementations. in any case, I don't think it is a showstopper. > >everyone wins. in the absolute worst case there are always #ifdefs > >but I > >doubt they will be needed. > > Except for programmer C on some haskell implementations. I don't buy > it yet :-). Well, certain implementations will always have their own extensions that people might rely on. I just don't want the language standard itself to rule out valid and useful implementation methods. Haskell with IO multiplexing is a very powerful platform indeed and this proposal lets us keep it in the language proper and that is very nice, from an implementor and a library writers point of view. often concurrent
Re: Concurrency
On Fri, Mar 31, 2006 at 02:49:53PM -0800, John Meacham wrote: > > threading if it's available, but can degrade gracefully if not? Should > > I be forced to use something like cpphs to detect the presence of > > threading in advance? It would be better to detect this at runtime than > > fail to compile at all on a system that doesn't support threading, IMHO. > > Yeah, actually. cpphs (or something in cabal) seems like just the right > way to go. because it is set at compile time. you don't make run-time > decisions as to whether to use unboxed arrays, control.arrow or any > other library. it would seem very odd to do so for concurrency. Well then, this mechanism ought also to be standardized by Haskell'. To support concurrency (or not) but to not provide an automated way of graceful degradation is not, to me, a good solution. > Concurrency might be hidden deep in a library, you don't want to > suddenly get an unexpected "concurrency not supported" error because you > happened to use a library you didn't write in a new way. better to be > safe and catch those known errors at compile-time. That does make sense. I am concerned about the mechanism. AFAIK, Haskell98 didn't mandate cpphs or any tool like it. Will Haskell'? If not, then we are back to the original problem. -- John ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: FFI, safe vs unsafe
John Meacham wrote: first of all, a quick note, for GHC, the answers will be "the same thing it does now with -threaded". but I will try to answer with what a simple cooperative system would do. Sure. Unless someone dares answer "yes" to question 4, GHC will stay as it is. 2.) Assume the same situation as in 1, and assume that the answer to 1 is yes. While 'foo' is running, (Haskell) thread B makes a non- concurrent, reentrant foreign call. The foreign function calls back to the foreign-exported Haskell function 'bar'. Because the answer to 1 was yes, 'foo' will resume executing concurrently with 'bar'. If 'foo' finishes executing before 'bar' does, what will happen? I am confused, why would anything in particular need to happen at all? the threads are completly independent. The non-concurrent calls could just be haskell code that happens to not contain any pre-emption points for all it cares. in particular, in jhc, non-concurrent foreign imports and exports are just C function calls. no boilerplate at all in either direction. calling an imported foreign function is no different than calling one written in haskell so the fact that threads A and B are calling foregin functions doesn't really change anything. In an implementation which runs more than one Haskell thread inside one OS thread, like ghc without -threaded or hugs, the threads are NOT completely independent, because they share one C stack. So while bar executes, stack frames for both foreign functions will be on the stack, and it will be impossible to return from foo before bar and the foreign function that called it completes. I think this kind of semantics is seriously scary and has no place as default behaviour in the language definition. If you implement concurrency by using the pthreads library, you need to either make sure that only one thread mutates the heap at a time, or deal with SMP. In either case, concurrent foreign calls would be trivial. 4.) Should there be any guarantee about (Haskell) threads not making any progress while another (Haskell) thread is executing a non- concurrent call? I don't understand why we would need that at all. Good. Neither do I, but in the discussions about this issue that we had three years ago several people seemed to argue for that. 5.) [...] So what should the poor library programmer A do? He should say just 'reentrant' since concurrent isn't needed for correctness because the tessalation routines are basic calculations and will return. Let's say they will return after a few minutes. So having them block the GUI is a show-stopper for programmer C. And if programmer C happens to use a Haskell implementation that supports "concurrent reentrant" but also a more efficient "non- concurrent reentrant", he will not be able to use the library. everyone wins. in the absolute worst case there are always #ifdefs but I doubt they will be needed. Except for programmer C on some haskell implementations. I don't buy it yet :-). 6.) Why do people consider it too hard to do interthread messaging for handling a "foreign export" from arbitrary OS threads, when they already agree to spend the same effort on interthread messaging for handling a "foreign import concurrent"? Are there any problems that I am not aware of? it is not that it is hard (well it is sort of), it is just absurdly inefficient and you would have no choice but to pay that price for _every_ foregin export. even when not needed which it mostly won't be. the cost of a foreign export should be a simple 'call' instruction (potentially) when an implementation supports that. As we seem to agree that the performance issue is non-existant for implementations that use one OS thread for every haskell thread, and that we don't want to change how GHC works, the following refers to a system like hugs where all Haskell code and the entire runtime system always runs in a single OS thread. It might not be absolutely easy to implement "concurrent reentrant", but it's no harder than concurrent non-reentrant calls. If a haskell implementation has a hacker on its team who is able to do the former, then this is no problem either. As for the efficiency argument: if it is sufficiently slow, then that is an argument for including "nonconcurrent reentrant" as an option. It is not an argument for making it the default, or for leaving out "concurrent reentrant". the cost of a foreign import concurrent nonreentrant is only paid when actually using such a function, and quite cheap. on linux at least, a single futex, a cached pthread and it gets rolled into the main event loop. so a couple system calls max overhead. Sure. But what gives you the idea that the cost of a foreign export or a foreign import concurrent reentrant would be paid when you are not using them? If we include nonconcurrent reentrant foreign imports in the system, or if we just optimise foreign i
Re: Concurrency
On Fri, Mar 31, 2006 at 03:59:41PM -0600, John Goerzen wrote: > On Fri, Mar 31, 2006 at 01:51:14PM -0800, John Meacham wrote: > > > If so, we should specify what exception is raised if, say, forkIO is > > > called on such a system. We should also make it clear that > > > single-threaded implementations are required of things such as MVars. > > > Finally, we should add a function that indicates the level of threading > > > support on the running system. > > > > routines that are guarenteed to fail becaues they arn't supported should > > not exist, haskell tries hard to catch so many errors at compile time, > > it would seem odd to delegate the error of missing a whole subsystem to > > run-time :) > > Not really. What if I'm writing a program that can take advantage of > threading if it's available, but can degrade gracefully if not? Should > I be forced to use something like cpphs to detect the presence of > threading in advance? It would be better to detect this at runtime than > fail to compile at all on a system that doesn't support threading, IMHO. Yeah, actually. cpphs (or something in cabal) seems like just the right way to go. because it is set at compile time. you don't make run-time decisions as to whether to use unboxed arrays, control.arrow or any other library. it would seem very odd to do so for concurrency. Concurrency might be hidden deep in a library, you don't want to suddenly get an unexpected "concurrency not supported" error because you happened to use a library you didn't write in a new way. better to be safe and catch those known errors at compile-time. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Concurrency
On Fri, Mar 31, 2006 at 04:29:59PM -0600, Taral wrote: > On 3/31/06, John Meacham <[EMAIL PROTECTED]> wrote: > > > - I wouldn't include threadWaitRead, threadWaitWrite, > > > or threadDelay at all. These can all be implemented using > > > FFI, so don't belong in the concurrency library. Their > > > presence is largely historical. > > > > They all have special implementations on a 'epoll' based system. > > threadDelay turns into the timeout parameter to select, waitread/write > > turn into the basic building blocks of your epoll wait-list. We > > definitly want these in the interface as primitves. > > And they're all a pain because they don't take sets of files, only > single ones. Can we please have something like: > > threadWait :: Timeout -> [Handle] -> IO ? Oh, that is definitly planned as part of an 'epoll' interface I have been calling Event. depending on the compiler, Concurrent might be implemented on top of Event or Event might be implemented on top of Concurrent :) In any case, I left it out of the proposal here because it is relatively orthogonal (from a design, not an implemenatition point of view) but I definitly think it should exist. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Concurrency
On 3/31/06, John Meacham <[EMAIL PROTECTED]> wrote: > > - I wouldn't include threadWaitRead, threadWaitWrite, > > or threadDelay at all. These can all be implemented using > > FFI, so don't belong in the concurrency library. Their > > presence is largely historical. > > They all have special implementations on a 'epoll' based system. > threadDelay turns into the timeout parameter to select, waitread/write > turn into the basic building blocks of your epoll wait-list. We > definitly want these in the interface as primitves. And they're all a pain because they don't take sets of files, only single ones. Can we please have something like: threadWait :: Timeout -> [Handle] -> IO ? -- 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: Concurrency
On Fri, Mar 31, 2006 at 01:51:14PM -0800, John Meacham wrote: > > If so, we should specify what exception is raised if, say, forkIO is > > called on such a system. We should also make it clear that > > single-threaded implementations are required of things such as MVars. > > Finally, we should add a function that indicates the level of threading > > support on the running system. > > routines that are guarenteed to fail becaues they arn't supported should > not exist, haskell tries hard to catch so many errors at compile time, > it would seem odd to delegate the error of missing a whole subsystem to > run-time :) Not really. What if I'm writing a program that can take advantage of threading if it's available, but can degrade gracefully if not? Should I be forced to use something like cpphs to detect the presence of threading in advance? It would be better to detect this at runtime than fail to compile at all on a system that doesn't support threading, IMHO. -- John ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Concurrency
On Fri, Mar 31, 2006 at 10:21:16AM -0600, John Goerzen wrote: > On Fri, Mar 31, 2006 at 04:41:06AM -0800, John Meacham wrote: > > optional preemption - ability to preempt pure code, fairness guarentees, > > interleaved evaluation operators (merge, nmerge) > > Under the "what is provided" section, did you intend that to apply to > all compilers, even ones that don't implement threading? the point is that all compilers will implement threading now and provide everything in that section. rather than having all of concurrency being an option, we have found a way to get a good portion of concurrency guarenteed to be supportable on all systems without any compromises in run-time for the non-concurrent case or restricting the range of future implementation techniques. > If so, we should specify what exception is raised if, say, forkIO is > called on such a system. We should also make it clear that > single-threaded implementations are required of things such as MVars. > Finally, we should add a function that indicates the level of threading > support on the running system. routines that are guarenteed to fail becaues they arn't supported should not exist, haskell tries hard to catch so many errors at compile time, it would seem odd to delegate the error of missing a whole subsystem to run-time :) 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
On Fri, Mar 31, 2006 at 03:16:50PM -0500, Wolfgang Thaller wrote: > So I'm going to ask a few questions about the semantics of non- > concurrent reentrant calls, and if people can provide answers that > don't scare me, I'll concede that they have a place in the language > standard. first of all, a quick note, for GHC, the answers will be "the same thing it does now with -threaded". but I will try to answer with what a simple cooperative system would do. > 1.) Assume thread A and B are running. Thread A makes a non- > concurrent, reentrant call to Foreign Lands. The foreign function > calls a foreign-exported Haskell function 'foo'. > While 'foo' is executing, does thread B resume running? if 'foo' blocks on a mvar,read,write,etc... then yes. > 2.) Assume the same situation as in 1, and assume that the answer to > 1 is yes. While 'foo' is running, (Haskell) thread B makes a non- > concurrent, reentrant foreign call. The foreign function calls back > to the foreign-exported Haskell function 'bar'. Because the answer to > 1 was yes, 'foo' will resume executing concurrently with 'bar'. > If 'foo' finishes executing before 'bar' does, what will happen? I am confused, why would anything in particular need to happen at all? the threads are completly independent. The non-concurrent calls could just be haskell code that happens to not contain any pre-emption points for all it cares. in particular, in jhc, non-concurrent foreign imports and exports are just C function calls. no boilerplate at all in either direction. calling an imported foreign function is no different than calling one written in haskell so the fact that threads A and B are calling foregin functions doesn't really change anything. > 3.) Same situation as in 1. When 'foo' is called, it forks (using > forkIO) a Haskell thread C. How many threads are running now? 3 potentially runable. > 4.) Should there be any guarantee about (Haskell) threads not making > any progress while another (Haskell) thread is executing a non- > concurrent call? I don't understand why we would need that at all. > Two more questions, not related to semantics: > > 5.) Assume that Haskell Programmer A writes a Haskell library that > uses some foreign code with callbacks, like for example, the GLU > Tesselator (comes with OpenGL), or, as a toy example, the C Standard > Library's qsort function. Should Programmer A specify "concurrent > reentrant" on his foreign import? > Programmer B will say "please don't", as he wants to use a Haskell > implementation which doesn't support "concurrent reentrant". > Programmer C will say "please do", as he wants his application's GUI > to stay responsive while the library code is executing. So what > should the poor library programmer A do? He should say just 'reentrant' since concurrent isn't needed for correctness because the tessalation routines are basic calculations and will return. However, on a system like GHC that actually can run code concurrently and actually would have issues enforcing a 'non-concurrent' guarentee it would run concurrently anyway. It would be hard not to on an implementation that supported true OS threads actually. everyone wins. in the absolute worst case there are always #ifdefs but I doubt they will be needed. > 6.) Why do people consider it too hard to do interthread messaging > for handling a "foreign export" from arbitrary OS threads, when they > already agree to spend the same effort on interthread messaging for > handling a "foreign import concurrent"? Are there any problems that I > am not aware of? it is not that it is hard (well it is sort of), it is just absurdly inefficient and you would have no choice but to pay that price for _every_ foregin export. even when not needed which it mostly won't be. the cost of a foreign export should be a simple 'call' instruction (potentially) when an implementation supports that. the cost of a foreign import concurrent nonreentrant is only paid when actually using such a function, and quite cheap. on linux at least, a single futex, a cached pthread and it gets rolled into the main event loop. so a couple system calls max overhead. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Concurrency
I just realized that my mailer futzed this one and its headers don't match where it was actually sent. so if you are responding to it, the mail most likely is not going out to the list. make sure it is to haskell-prime and not hasuell-prime. 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
On Fri, Mar 31, 2006 at 03:16:50PM -0500, Wolfgang Thaller wrote: > Before adding non-concurrent, reentrant calls to the language > standard, please take some time to think about what that means. If > you have forkIO'ed multiple threads, things start to interact in > strange ways. I think this is a can of worms we don't want to open. > (Or open again. It's still open in GHC's non-threaded RTS, and the > worms are crawling all over the place there). I am still digesting your message, but a quick note is that when you specify non-concurrent, you arn't saying "it can't be concurrent" but rather "I don't absolutely need it to be" so GHC would still treat all reentrant calls as concurrent and that is a-okay by the spec. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Concurrency
On Fri, Mar 31, 2006 at 04:21:26PM +0100, Simon Marlow wrote: > Great. Apart from my misgivings about allowing cooperative scheduling > at all, here's a few comments on the proposal: much much preferable to a standard that not everyone can implement. :) > - I wouldn't include threadWaitRead, threadWaitWrite, > or threadDelay at all. These can all be implemented using > FFI, so don't belong in the concurrency library. Their > presence is largely historical. They all have special implementations on a 'epoll' based system. threadDelay turns into the timeout parameter to select, waitread/write turn into the basic building blocks of your epoll wait-list. We definitly want these in the interface as primitves. In particular, foregin concurrent calls will most likely be implemented in _terms_ of threadWaitRead on cooperative systems. > - yield bothers me a little. If it weren't for cooperative > systems, yield would be semantically a no-op, because the > no-starvation guarantee means you never need it for > correctness. I think it's ok, just a bit unsettling. even pthreads provides it. I think you place a lot of faith in pre-emption. :) In my experience, it doesn't actually buy you a whole lot over state-threading in the non SMP case. everything would be different if we were thinking of different processes on the same computer, where you wouldn't want one buggy one interfering with others, but in general you consider a single program buggy or bug-free as a unit. In any case, IO multiplexing is 90% of the uses of threading anyway, (ginsu,yi,gui apps that don't do background processing, etc...) which cooperative threading is ideal for. not that there arn't itches that only preemptive threads can scratch too. > - In the optional OS threads section it says "allows multiple > haskell threads to run at once" - actually you can provide > all that without allowing multiple haskell threads to run > at once, eg. ghc-6.4.1 with -threaded. I'll modify it. okay. yeah, I just sort of outlined the options figuring we would fill in the details later. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
FFI, safe vs unsafe
Hi everyone, Before adding non-concurrent, reentrant calls to the language standard, please take some time to think about what that means. If you have forkIO'ed multiple threads, things start to interact in strange ways. I think this is a can of worms we don't want to open. (Or open again. It's still open in GHC's non-threaded RTS, and the worms are crawling all over the place there). So I'm going to ask a few questions about the semantics of non- concurrent reentrant calls, and if people can provide answers that don't scare me, I'll concede that they have a place in the language standard. 1.) Assume thread A and B are running. Thread A makes a non- concurrent, reentrant call to Foreign Lands. The foreign function calls a foreign-exported Haskell function 'foo'. While 'foo' is executing, does thread B resume running? 2.) Assume the same situation as in 1, and assume that the answer to 1 is yes. While 'foo' is running, (Haskell) thread B makes a non- concurrent, reentrant foreign call. The foreign function calls back to the foreign-exported Haskell function 'bar'. Because the answer to 1 was yes, 'foo' will resume executing concurrently with 'bar'. If 'foo' finishes executing before 'bar' does, what will happen? 3.) Same situation as in 1. When 'foo' is called, it forks (using forkIO) a Haskell thread C. How many threads are running now? 4.) Should there be any guarantee about (Haskell) threads not making any progress while another (Haskell) thread is executing a non- concurrent call? Two more questions, not related to semantics: 5.) Assume that Haskell Programmer A writes a Haskell library that uses some foreign code with callbacks, like for example, the GLU Tesselator (comes with OpenGL), or, as a toy example, the C Standard Library's qsort function. Should Programmer A specify "concurrent reentrant" on his foreign import? Programmer B will say "please don't", as he wants to use a Haskell implementation which doesn't support "concurrent reentrant". Programmer C will say "please do", as he wants his application's GUI to stay responsive while the library code is executing. So what should the poor library programmer A do? 6.) Why do people consider it too hard to do interthread messaging for handling a "foreign export" from arbitrary OS threads, when they already agree to spend the same effort on interthread messaging for handling a "foreign import concurrent"? Are there any problems that I am not aware of? If I am wrong and we should indeed provide non-concurrent reentrant calls in a concurrent Haskell system, then I think there should be satisfying answers to the above questions... Cheers, Wolfgang ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: MVar semantics: proposal
John - You are, in effect, proposing a memory model for MVars and IORefs. The high-level model for programmers is "In order to communicate data between threads, you *must* use an MVar, and never an IORef." But the devil is in the details. I'd like to strongly urge *against* adopting the extremely loose model you have proposed. The following things seem particularly important: * reads and writes to IORefs should be atomic, meaning either a complete update is observed or no change is observed. In the absence of this guarantee, misuse of IORefs can cause programs to crash in unrepeatable ways. If the machine doesn't make this easy, the implementor ought to sweat a little so that Haskell programmers don't have to sweat at all. * I assume forkIO constitutes a sequence point. I suspect throwTo et al ought to as well. * I would urge that atomicModifyIORef constitute a sequence point---I suspect it loses a great deal of its utility otherwise. Now, on to more difficult issues... Consider the following example (untested): data RefList a = Nil | Cons a (IORef (RefList a)) cons :: a -> RefList a -> IO (RefList a) cons x xs = do a <- newIORef xs return (Cons x a) hd :: RefList a -> a hd (Cons a _) = a tl :: RefList a -> IO (RefList a) tl (Cons a t) = readIORef a setTl :: RefList a -> RefList a -> IO () setTl (Cons a t) t' = writeIORef t t' main = do a <- cons 'a' Nil forkIO $ do c <- cons 'c' Nil b <- cons 'b' Nil setTl b c setTl a b at <- tl a case at of Nil -> return () Cons _ _ -> do putChar (hd at) att <- tl at This program is, by your informal model, buggy. The question is this: how badly wrong is it? Let's say at happens to read b. Is (hd at) well defined? That's assuming very strong consistency from the memory system already. How about the IORef in at? Is that fully allocated, and properly initialized? Again, if it is, that implies some pretty strong consistency from the memory system. Now, what about att? By your argument, it may or may not be c. We can ask the same questions about its contents assuming it happens to be c. People have talked a lot about weakly-ordered NUMA machines for more than a decade, and they're always just a couple of years away. In practical terms, non-atomic NUMA memory models tend to be so hard to program that these machines have never found any traction---you need to throw away all of your software, including your OS, and start afresh with programmers that are vastly more skilled than the ones who wrote the stuff you've already got. My feeling is that the purely-functional portion of the Haskell language already makes pretty stringent demands of memory consistency. In light of those demands, and the fact that mutable state is used in pretty tightly-controlled ways, it's worth considering much stronger memory models than the one you propose. I'd even go so far as to say "IORefs and IOArrays are sequentially consistent". The only argument against this behavior is their use in the internals of arrays, file I/O, the FFI, etc., etc. (though really it's all about IOUArrays in the latter cases) where we might conceivably pay a bundle in performance. Another possibility is an algebraic model based on commuting IO actions. That approach is a particular bias of mine, having tangled with these issues extensively in the past. It'd go something like this: * Any data written to an IORef can safely be read by another thread; we cannot observe partially-written objects. * readIORef commutes with readIORef. * newIORef commutes with newIORef. * writeIORef and newIORef commute with writeIORef or readIORef to a different IORef. * Nothing commutes with readMVar, writeMVar, or atomicModifyIORef. * Nothing before a forkIO can be commuted to after forkIO. I think it's a Good Idea to choose a model that is conceptually simple now, at the cost of imposing a few constraints on implementors, rather than a complex specification which permits maximum implementation flexibility but is utterly opaque. Realistically, the machines which are likely to be built will make it easy to comply with a strong specification. -Jan-Willem Maessen ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: New syntax
On Fri, Mar 31, 2006 at 01:26:52PM +0100, Simon Peyton-Jones wrote: > | > Template Haskell breaks expressions with $, > | > | It's very bad that with TH enabled you cannot write sections of the > form ($ x) > | anymore which are sometimes very handy. > > I'd prefer it if TH only sprang into action when you wrote > $x > or > $(f x) > > That is, no space after the $. If you put spaces, you should get the > H98 $. Isn't that the current behaviour? Thanks Ian ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: FFI, safe vs unsafe
This is the way it is right now in GHC: the default is "safe", and safe means both reentrant and concurrent. This is for the reason you give: the default should be the safest, in some sense. .. So we can't have the default (unanotated) foreign call be something that isn't required by the standard. why not? you'd only need to make sure that in standard mode, no unannotated foreign declarations are accepted (or that a warning is given). claus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Concurrency
I have tried to summarize the current thinking into a proposal on the wiki. http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/Concurrency I split it into 3 parts. the standard - all haskell' compilers must implement optional preemption - ability to preempt pure code, fairness guarentees, interleaved evaluation operators (merge, nmerge) optional OS threads - bound threads, SMP, reentrant concurrent FFI calls supported. comment or modify it at will. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: Re[2]: thread priorities?
On 31 March 2006 10:24, Bulat Ziganshin wrote: > Hello Simon, > > Friday, March 31, 2006, 12:24:23 PM, you wrote: > >>> threadSetPriority :: ThreadID -> Int -> IO () > >> I'd rather not, if we can avoid it. The only rationale I'll offer is >> that we don't have it in GHC, and people manage to do a lot without >> priorities. Priorities come with a whole can of worms that I'd >> rather not deal with. > > it was requested by Joel Reymont, and he even give us information how > that is implemented in Erlang, together with hint to assign higher > priorities to consuming threads. Yes, but the Erlang implementation doesn't do anything about priority inversion. Also, I don't think Joel really wanted priorities, his problem could have been solved by using bounded channels. Cheers, Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: MVar semantics: proposal
On Fri, Mar 31, 2006 at 01:43:15PM +0100, Simon Marlow wrote: > > 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. > > Slightly less overhead than an MVar, because you only need one > lock/release to implement atomicModifyIORef, but two lock/release > combinations are involved in an update of an MVar. hmm.. is atomicModifyIORef meant to be atomic with respect to all other IORef calls or _just_ other atomicModifyIORef calls? because if the second then that is a whole lot easier to implement and I could be on board with that. :) > > > atomicModifyIORef also cannot (easily) be implemented on > > implementations > > that use update-in-place rather than indirections for thunk updates. > > I don't follow you - how would that make it harder? for instance in a TIM implementation (do any exist?) you have both a code pointer and a frame address to represent a value, most arches don't have an atomic way to set two memory locations at once. However, these implementations perhaps could use a single indirection just for implementing IORefs... jhc would be in this boat as it modifies values by rewriting nodes, not by swizzling pointers, but I can make IORefs go through an indirection if needed. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: MVar semantics: proposal
Sequence points... yes, all seems reasonable to me. On 31 March 2006 00:50, John Meacham wrote: > 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. Slightly less overhead than an MVar, because you only need one lock/release to implement atomicModifyIORef, but two lock/release combinations are involved in an update of an MVar. atomicModifyIORef would be a sequence point, BTW. Semantically, think of it as having a hidden MVar attached to the IORef: withMVar m $ \_ -> do x <- readIORef r let (x',y) = f x writeIORef r x' return y as long as you have some way to enforce exclusion with respect to other atomicModifyIORef operations on a given IORef, you can implement it like this. > atomicModifyIORef also cannot (easily) be implemented on > implementations > that use update-in-place rather than indirections for thunk updates. I don't follow you - how would that make it harder? Cheers, Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: New syntax
| > Template Haskell breaks expressions with $, | | It's very bad that with TH enabled you cannot write sections of the form ($ x) | anymore which are sometimes very handy. I'd prefer it if TH only sprang into action when you wrote $x or $(f x) That is, no space after the $. If you put spaces, you should get the H98 $. If anyone feels like fixing this, I think it'd be a good thing to do. S ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: Pre-emptive or co-operative concurrency (was: Concurrency)
On 30 March 2006 22:01, Claus Reinke wrote: >>> 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? > > yes. I'm all for Haskell' having both ffi and concurrency, but that > means that the feature interactions have to be investigated. I know > you made a start on that, so I was just pointing out some further > corners that may need looking into: > > - if foreign code is used in Haskell' scheduling, what properties of > the foreign code need to be specified, how does long-running > foreign code interact with the scheduler, and are the current > annotations sufficient for all that? > > - if Haskell' code involving concurrency is foreign exported, what > does that mean? does it work out of the box, or what are the > limitations? Rather than answer these directly, I'll point to this paper which addresses these questions and more: http://www.haskell.org/~simonmar/papers/conc-ffi.pdf GHC implements exactly what is in that paper. For Haskell', I expect we won't require all of it, some will be relegated to extensions. > I was looking for a practical example involving concurrency and ffi > in such a way as to expose some of the questions that need to be > answered. you're mentioning forkIO, so that's an example of such > questions: why shouldn't we be able to foreign export that? The (slightly glib) answer to this question is "because it doesn't have a legal FFI type". If you want to foreign export forkIO, you'll have to give me a version that I can foreign export. And that involves some important decisions: just where do you want to run the IO() action, on the server, or the client? If it's on the server, then how to I get the IO() in the first place? YOu must provide some more API functions to build a FunPtr(IO()), or something. (by server I mean the library proferring the forkIO API, by client I mean the client of this API). Cheers, Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: FFI, safe vs unsafe
On 30 March 2006 21:40, 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? > > 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). This is the way it is right now in GHC: the default is "safe", and safe means both reentrant and concurrent. This is for the reason you give: the default should be the safest, in some sense. However, John has argued, and I agree, that requiring the combination of concurrent and reentrant to be supported is too much, and furthermore is often unnecessary. So we can't have the default (unanotated) foreign call be something that isn't required by the standard. Hence, the proposal states that concurrent foreign calls have to be annotated as such, and it is the specific case of 'concurrent' alone, as opposed to 'concurrent nonreentrant' that is an extension. http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/ForeignBlo cking Cheers, Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: MVar semantics: proposal
Of course, let me know if I am just being overly paranoid about crazy future NUMA machines. We can just say full read-write memory barrier on every putMVar, takeMVar and leave it at that. :) John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: thread priorities?
On Fri, Mar 31, 2006 at 10:30:51AM +0100, Malcolm Wallace wrote: > > threadSetPriority :: ThreadID -> Int -> IO () > > In any case, if priorities were to be introduced, I would not use Ints > to represent them. How many priority levels are sufficient? A partial > ordering between ThreadIDs would be preferable. Sometimes priorities are > genuinely incomparable, so there is no point in forcing a particular > ordering. Well, that is just the sort of complication I wanted to avoid by keeping them simple. I did not want to specify a scheduling algorithm in particular. In cooperative systems, it is quite convinient to have some control over which thread is run next, however, preemptive systems might as well ignore them as eventually every thread will get its time. It is not that important to me though. I'll probably implement it as an extension in jhc since it is straightforward, but have no particular attachment to it being in the standard if others don't feel it belongs in there. John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: thread priorities?
> > Thinking about it some. I think we will need some sort of very basic > > thread priorities. > > I'd rather not, if we can avoid it. Agreed. If someone wants to provide them as an optional extra, fine. (We had thread priorities In concurrent embedded Gofer, a long time ago. They can certainly be useful when interfacing with hardware, but there are other ways to achieve the same goals.) As Simon says: > Priorities come with a whole can of worms that I'd rather not deal with. They certainly do. Unintentional priority inversion is the most basic problem, covered early in any course on real-time systems. > threadSetPriority :: ThreadID -> Int -> IO () In any case, if priorities were to be introduced, I would not use Ints to represent them. How many priority levels are sufficient? A partial ordering between ThreadIDs would be preferable. Sometimes priorities are genuinely incomparable, so there is no point in forcing a particular ordering. Regards, Malcolm ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re[2]: thread priorities?
Hello Simon, Friday, March 31, 2006, 12:24:23 PM, you wrote: >> threadSetPriority :: ThreadID -> Int -> IO () > I'd rather not, if we can avoid it. The only rationale I'll offer is > that we don't have it in GHC, and people manage to do a lot without > priorities. Priorities come with a whole can of worms that I'd rather > not deal with. it was requested by Joel Reymont, and he even give us information how that is implemented in Erlang, together with hint to assign higher priorities to consuming threads. I personally also want to had priorities, in order to run my I/O thread anytime when previous I/O operation is completed, in order to raise overall program performance I also don't see principal implementation problems - instead of round-robin selecting of next thread to run, it should be some more complex structure -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: thread priorities?
Hello John, Friday, March 31, 2006, 5:48:30 AM, you wrote: > threadSetPriority :: ThreadID -> Int -> IO () > 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. afair, Erlang has different strategy. Threads with lesser priority should get _LESSER_ amount of time, but they should still be running -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: Specification of newtype deriving
On Thu, Mar 30, 2006 at 09:48:14PM +0200, Twan van Laarhoven wrote: > 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. Thank you for taking up that challenge. It is important to know whether newtype deriving is sugar or not, even though the translation will never be used by a compiler. By the way, the description in the GHC User's Guide 7.4.12.2: newtype T v1...vn = T' (S t1...tk vk+1...vn) deriving (c1...cm) is too restrictive in requiring that S must be a type constructor of the same arity as T, forbidding things like newtype Wrap m a = Wrap (m a) deriving (Monad, Eq) It should be newtype T v1...vn = T' (t vk+1...vn) deriving (c1...cm) with vk+1...vn not free in the type expression t. It should also mention that T may not be recursive, unless all the classes are those derivable by the existing mechanism. (There is some awkwardness in the overlap between the two mechanisms.) Your translation looks good, but I think you missed a bit: > 4. If T is an algebraic 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. The T you were talking about before would be an application of an algebraic data type constructor to types T_i. If you just substitute those for the a's, the expansion could go on forever. I think it's necessary to assign each type constructor a higher-rank version of wrap/unwrap along the lines of Ralf Hinze's "Polytypic values possess polykinded types". It looks doable, but it's disturbing that something with trivial operational semantics is so hard to describe. ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
Re: thread priorities?
"Simon Marlow" <[EMAIL PROTECTED]> writes: > I'd rather not, if we can avoid it. The only rationale I'll offer is that we > don't have it in GHC, and people manage to do a lot without priorities. > Priorities come with a whole can of worms that I'd rather not deal with. Thread priorities are somewhere between important and necessary for hOp/House. I haven't seen them really required elsewhere though. -- I've tried to teach people autodidactism,| ScannedInAvian.com but it seems they always have to learn it for themselves.| Shae Matijs Erisson ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime
RE: thread priorities?
On 31 March 2006 02:49, John Meacham wrote: > 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 = ... I'd rather not, if we can avoid it. The only rationale I'll offer is that we don't have it in GHC, and people manage to do a lot without priorities. Priorities come with a whole can of worms that I'd rather not deal with. Cheers, Simon ___ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime