RE: ghc with shared libraries ?

2000-04-12 Thread Simon Marlow

> I read that message and I'm afraid I'm puzzled.
> 
> Do you mean that GHC-compiled Haskell libraries don't have a stable
> ABI ?  I can see that that might be true, but it might also be
> possible to have a souped-up dynamic linker that could fix things up
> (possibly with, as you say in the message, adverse effects on the
> sharedness of the library).

Well, there wouldn't be any benefit to GHC in the sense that libraries could
be replaced without recompiling the binaries, because the dependencies are
much more complicated than simply the function names and types exported by
the library.  However, if you compile your programs without cross-module
optimisation (or fix GHC to not do cross-module optimisation from a
library), then the libraries become more stable.

Even C is having trouble in this area, though: witness the recent trouble
with upgrading versions of glibc.  They tried to avoid bumping the major
version of the shared library, but didn't manage to keep the ABI stable with
the result that there were a whole host of weird incompatibilites.

> But if that's all that the problem is it doesn't explain why even when
> exactly the same object files are put together via dynamic linking
> instead of just static it doesn't work (as I infer from people's
> messages - I haven't tried it).

Actually, I didn't know you could do this (maybe my misunderstanding is
caused by the fact that you certainly couldn't do this with older ld.so's,
maybe the Linux one is more generic).

And it does seem to work!  Cool.

> I was under the impression that at least on sensible platforms like
> Linux, the relocation and linking that is done by the dynamic linker
> is very similar to that done by the compile-time linker.  In fact, on
> Linux you don't even need to compile your code -fpic: without it there
> are simply lots more relocations in the resulting object files and
> hence in the shared library, and you end up not sharing most of the
> text (because the dynamic linker has to edit it when relocating it).
> So without -fpic things work, but there's just a performance penalty.
>
> You say:
> > ... for example the assumption that  a data object consists 
> of a symbol
> > followed by a fixed amount of data, so that certain data 
> objects can be
> > copied into the binary's data segment at runtime.  GHC's 
> object files don't
> > follow these rules, so can't be made into shared objects easily.
> 
> It seems to me that this view of `data object' is simply the
> definition of what ought to go into the initialised data segment of
> the resulting shared object.  Unix shared libraries don't have a view
> about what a `data object' is.

No, but -fpic does.  As I recall, it inserts .size directives so that data
objects can be copied into the binary's data segment at load time This is
because static data referenced from the program must be resolved to an
absolute address at link-time (this isn't the case with DLLs, where the
program may reference the static data through an indirection, but this
requires knowing at compile-time whether you're going to be linking with a
shared or static library).  The concept of .size (and .type?) doesn't fit
with GHC's strange storage layout with data mixed with code.

But, it seems that -fpic isn't required for dynamic-linkness, just for
sharedness, so we may have dynamically-linked libraries for GHC soon...

Thanks for the pointer, Ian!

Cheers,
Simon




putMVar on full MVar

2000-04-12 Thread Claus Reinke

> There's still some discussion to be had on what putMVar should
> do when presented with a full MVar.  The options are
>
> 1. throw an exception (as now)
> 2. block until the MVar is empty
> 3. succeed, replacing the current value in the MVar
> 4. succeed, adding the new value to a buffer in the MVar
>
> (1) is easy to implement.  (2) is more convenient occasionally,
> but can always be implemented with an extra MVar.  (3) is also
> more convenient in certain cases (imagine an MVar that held
> mouse movement events), but again can be implemented with extra
> MVars.  (4) adds some complication to the MVar implementation.

This is one aspect of the Concurrent Haskell design I have never
been happy with - I would much prefer (2) over (1), the original
CH paper also mentioned ordered (4a) and unordered buffering
(4b). Here are some arguments for the discussion:

a. Ease of implementation should never be the first argument;-)

b. In contrast to other things, that can be built on top of the
   current MVars, (1) is not only inconvenient, but unsafe,
   unless (and in a sense even if, see (d)) you always protect
   each use of putMVar with an exception handler (do you?).

c. Exceptions should be reserved for exceptional circumstances.

   Trying to execute putMVar on an MVar that has been filled
   already doesn't look exceptional to me in the presence of
   shared access from other concurrent, unsynchronised processes.

   It takes explicit programming to ensure that this situation
   cannot occur (or is handled correctly), but if this
   programming is needed in each and every case, it should be
   reused by incorporating it into the implementation (or into a
   library - why isn't everybody using CVars, btw?).

   Why would you want to treat as an exception a condition that
   occurs frequently and could be handled safely and implicitly
   by other means, such as (2), or CVars?

d. With (2), scheduling determines which of two conflicting
   writers gets to fill an MVar, and the loser simply blocks
   until the MVar is empty again. With (1), however, scheduling
   determines **whether or not there will be an exception**: if a
   reader is scheduled on a filled MVar before the second writer,
   everything is fine, whereas if the second writer is scheduled
   before any readers, you'll have an exception. Such things are
   fun to debug..

e. With the original CH semantics, exceptions would propagate to
   the top-level, absorbing the whole process network. Combine
   this with (d), and I do not understand why anyone would have
   wanted (1) in the first place (apart from supporting the case
   for exception handling?-).

   Exception handling can help here, but without grouping of
   processes, exception handling can only be global (which would
   mean losing your current process network) or immediate in each
   process that tries putMVar.  In fact, I would guess that in
   almost all cases the exception handling code is right next to
   the putMVar, so why use a non-local language construct
   (exceptions) for dealing with a perfectly localised situation?

   Of course, this assumes that you never forget to handle your
   exceptions..  If you `forgetĀ“ your exception handling, you
   will have a system that may or may not die at any time, giving
   bugs that are hard to reproduce (or might even go unnoticed
   for a while..).

f. there are lots of similarities between CH and Petri nets, and
   to get leverage from the popularity of Petri nets and from the
   experience of the Petri net community, it seems advisable not
   to introduce unnecessary differences.  Petri nets tend to use
   (2), or an unlimited capacity variant of (2) (mostly (4b)
   without, sometimes (4a) with ordering of buffer elements).

   Unordered, unlimited capacity buffers are a nice high-level
   abstraction, and limited capacity buffers can easily be
   modelled with pairs of unlimited capacity buffers, but as long
   as the outcome of conflicting putMVars is non-deterministic,
   single-place buffers should be fine for CH, and they are
   easier to implement efficiently;-)

   The point is: with (2), you could take persons used to
   coloured Petri nets (CPNs) and tell them that CH is very
   similar to what they have been using in their projects for
   ages.  There is added flexibility in CH, and added structural
   stability in CPNs - but CH can be embedded in CPNs easily, and
   more interestingly, an implementation of (a variant of) CPNs
   in CH could support a nice graphical frontend for CH..

So I can see lots of reasons against (1) and only one in favour
of (1) - easy implementation.

The main reason why I did not speak up before is that the
original CH paper seemed to suggest that MVars would only be used
at the most basic implementation level, whereas users and
libraries would almost certainly use safe variants (e.g., CVars)
built, in CH, on top of MVars. This would have achieved ease of
implementation while also protecting us

Re: putMVar on full MVar

2000-04-12 Thread George Russell

Claus Reinke wrote:
> a. Ease of implementation should never be the first argument;-)
No.  Speed should be.  I do use MVars a lot via the UniForM workbench,
and the most important thing is to have something simple and lightweight
that can be built upon.  If I were offered a 100% increase in functionality
in exchange for a 10% slowdown, I would refuse it.

The fact is that MVars are rightly incredibly primitive.  If you are doing
anything advanced with concurrency you need a better way of communicating,
such as channels, or the first-class events that Einar Karlsen put into the
UniForM workbench.  But both these can be built easily from MVars.




Re: putMVar on full MVar

2000-04-12 Thread Marcin 'Qrczak' Kowalczyk

Wed, 12 Apr 2000 15:12:31 +0100, Claus Reinke <[EMAIL PROTECTED]> pisze:

> PS. As for tryTakeMVar or locks on MVars, what is wrong
>with using MMVar a = (MVar (MayBe a)) and a suitable
>access protocol?
> 
>MVar empty--> MMVar is locked
>MVar Nothing --> MMVar is empty, not locked
>MVar (Just v)  --> MMVar holds value v, not locked

That it's impossible to implement the equivalent of takeMVar
(block until it is full).

-- 
 __("$ P+++ L++>$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+>++ DI D- G+ e> h! r--%>++ y-





tryTakeMVar

2000-04-12 Thread Claus Reinke

> > PS. As for tryTakeMVar or locks on MVars, what is wrong
> >with using MMVar a = (MVar (MayBe a)) and a suitable
> >access protocol?
> >
> >MVar empty--> MMVar is locked
> >MVar Nothing --> MMVar is empty, not locked
> >MVar (Just v)  --> MMVar holds value v, not locked
>
> That it's impossible to implement the equivalent of takeMVar
> (block until it is full).

In the simple design I had in mind, it would indeed be the writer that
chooses whether reading is blocking or not. In addition, you want the
reader to be able to choose (if the writer permits).

Let's see: for the reader to have a choice, the writer has to operate
the channel in two modes (for blocking and for non-blocking reading),
so a naive modification would be:

MVar (Bool,MVar a)

with states:

MVar empty
MVar (False,MVar empty)
MVar (True,Mvar v)

Hmm, almost. The problem is that the first reader to block on the
inner MVar is likely to get the data, even if a non-blocking reader just
happens to be looking at the True flag..

So we need to be slightly more systematic: readers now come in two
variants, depending on which operation they use to access the channel.

We don't want blocking readers (brs) to be presented with no input when
they wake up, right? And we cannot enter non-blocking readers (nbrs) into
the waiting list because they are not prepared to wait. Then an nbr could
temporarily occupy the front of the queue (and leave it immediately either
with an item of data or knowing that there is nothing on offer) or we have
to make sure that, as long as a br blocks on the channel, no nbr can beat
it to the data. Again, there are some options here: nbrs could observe
empty/full, but not the data items themselves; nbrs could have access to
a copy of the last item that has been written to the blocking channel.

In any case, there is an interaction between nbrs and the queue of brs,
so we need to know whether the queue is empty or not. For such cases,
the CH paper suggests (in 4, control over scheduling) to maintain a list
of blocked processes.

Here is one option for our problem, giving brs priority over nbrs: brs don't
all block on one MVar, but create a private MVar each to block on and
add their private MVars to a queue. Our channel type is modified to:

MVar (Either (MayBe a) [MVar a])

with states:

MVar empty
MVar (Left Nothing)
MVar (Left (Just v))
MVar (Right queue)-- not.null queue

The writer checks whether any brs are queued, and if so, passes the
item to the first br in the queue (replacing the Right-tagged queue with
a Left-tagged Nothing, if the queue becomes empty). If not, it announces
the item as free for all (Left (Just v)). This part is similar to the
quantity
semaphores example.

nbrs operate on Left-tagged information, Right-tagged information is
none of their business (they could return with Nothing, as there is no data
for them to collect before the queue gets empty again). If there is a
Left-tagged item, they can take it or make a copy.

brs operate on both tags, either consuming a Left-tagged item or
adding their private MVar to a new or existing Right-tagged queue.

I don't see how to give nbrs priority over brs. Using a pair type instead
of Either, the writer could temporarily put each item into the free for all
section, then check back to give it to the next br if it hasn't been taken,
but this doesn't feel right..

Perhaps tryTakeMVar should not be required to return immediately,
but be given a timeout parameter instead. That might simplify the
implementation.

What have I missed this time?

Claus






Re: putMVar on full MVar

2000-04-12 Thread Manuel M. T. Chakravarty

"Claus Reinke" <[EMAIL PROTECTED]> wrote,

> > There's still some discussion to be had on what putMVar should
> > do when presented with a full MVar.  The options are
> >
> > 1. throw an exception (as now)
> > 2. block until the MVar is empty
> > 3. succeed, replacing the current value in the MVar
> > 4. succeed, adding the new value to a buffer in the MVar
> >
> > (1) is easy to implement.  (2) is more convenient occasionally,
> > but can always be implemented with an extra MVar.  (3) is also
> > more convenient in certain cases (imagine an MVar that held
> > mouse movement events), but again can be implemented with extra
> > MVars.  (4) adds some complication to the MVar implementation.
> 
> This is one aspect of the Concurrent Haskell design I have never
> been happy with - I would much prefer (2) over (1), the original
> CH paper also mentioned ordered (4a) and unordered buffering
> (4b). Here are some arguments for the discussion:
> 
> a. Ease of implementation should never be the first argument;-)

In the case of basic functionality like the synchronisation
provided by MVars, ease of implementation and efficiency go
often hand in hand.  For such a basic structure, efficiency
matters a lot.

> b. In contrast to other things, that can be built on top of the
>current MVars, (1) is not only inconvenient, but unsafe,
>unless (and in a sense even if, see (d)) you always protect
>each use of putMVar with an exception handler (do you?).

Whenever the program logic (in all possible schedules)
guarantees that an MVar is never written to a second time
before it is read at least once, there is no need for an
exception handler.  Whenever the program logic does not give
that guarantee, you have to either use an exception handler
or establish this guarantee by using a second MVar.

This is like using partially defined functions.  If you
define a function partially, you have to make sure that you
never call it with a value not in its domain; otherwise, you 
get a runtime error, like with MVars.

Manuel