Re: Trivial Haskell Concurrency problem

2000-02-17 Thread George Russell

George Russell wrote:
 
 George Russell wrote:
  Exactly the same happens at the same time to Processor 2.
  Now somehow you have to distinguish between Processor 1 and Processor 2,
  because only one is going to get to lower the flags.  But I don't think
  with the existing Concurrency extensions plus standard Haskell you can.
 I take that back.  There's a fundamental error in this analysis.  Concurrent
 Haskell allows you to get the ThreadId of the current thread, and ThreadId
 DOES implement Ord.  I thought of this last night and tried to work out a
 way of making the thread with the least ThreadId win, but couldn't quite do
 it.  But it may still be possible.
I think I now have a solution to my original problem.  As said before, if
we had a Unique type which implements ordering, it is easy, since we can
attach one to each Flag, and make sure we take from the Flag with the lowest
Uniq value first.  I attach a file which implements Unique with NO global
variables or unsafePerformIO, with comparison done in (at most) a logarithmic
number of steps.  The only fly in the ointment is that comparison itself
has to construct the ordering on the fly, and so is an action and not a function.
Also of course Marcin's suggested restrictions (Unique values must increase
through the thread) cannot be implemented by this approach, since without
global variables you can't know what order actions are called in.
 Unique.hs


Re: Trivial Haskell Concurrency problem

2000-02-17 Thread Tom Pledger

George Russell writes:
  Tom Pledger wrote:
   For two threads to have access to the same MVar, they must have a
   common ancestor, right?  Could a common ancestor spawn a transaction
   broker thread?  That would be similar to what database management
   systems do.  It'd still be centralised, but wouldn't need to do unsafe
   IO.
  
  Well, all threads trivially have a common ancestor.  But I don't
  see how you can pick a particular ancestor.  The flags could easily
  have been passed around in a fairly general fashion along
  polymorphic channels.

Sorry, I didn't make that suggestion very clearly.

The suggestion is that the ancestor act in this order:

 1. Create the MVars etc. for communication with the transaction
broker thread.

 2. Fork the transaction broker's (initial) thread.

 3. Do whatever else the program involves, including forking threads
which will be clients of the transaction broker.  If these threads
create their own MVars etc., and need to apply transaction
management to them, they must communicate that need to the
transaction broker.  This is analogous to creating a table in a
database, or inserting a row into an existing table: the DBMS
becomes responsible for transaction management.

Regards,
Tom



Re: Trivial Haskell Concurrency problem

2000-02-16 Thread George Russell

Tom Pledger wrote:
 For two threads to have access to the same MVar, they must have a
 common ancestor, right?  Could a common ancestor spawn a transaction
 broker thread?  That would be similar to what database management
 systems do.  It'd still be centralised, but wouldn't need to do unsafe
 IO.
Well, all threads trivially have a common ancestor.  But I don't see how
you can pick a particular ancestor.  The flags could easily have been passed
around in a fairly general fashion along polymorphic channels.



Re: Trivial Haskell Concurrency problem

2000-02-16 Thread George Russell

Marcin 'Qrczak' Kowalczyk wrote:
 ...relative time of IO events that occured in a single thread.
 (=) imposes the sequencing.
Yes OK.  I see no problem with required elements of the Unique type to
increase in a single thread.  But I suspect anything stronger than this
could slow things down and/or cause difficulties.
 BTW: The random generator from the IO monad seems to be not
 thread-safe. Oops. I think it should be either fixed or documented.
Haha.  That'll teach them to write global variables into the standard,
won't it?
 That's why I said Integer, not Int :-)
It's important in the application I have in mind (the Two-Flags
problem is a real one in UniForM) that the Unique type be as fast as possible.
So I really do not want it to be tied to any particular thing.  For example
I suggest that for GHC the most efficient implementation might be an
Int64 or a 64-bit pointer (to nothing) on machines which support that, or when not
a Double with incrementing done by the nextAfter function.  Integer is just too
slow.  (You have to allocate two blocks of memory for it I think.)



Re: Trivial Haskell Concurrency problem

2000-02-15 Thread Wolfram Kahl


Simon Peyton-Jones [EMAIL PROTECTED] writes:
  
  | elegant.  If MVar's were instances of Ord as well as Eq, a 
  | neat solution would
  | be to always get the least MVar first, but they aren't.  So 
  | what should one do?
  
  But you could make Flag an instance of Ord
  
   data Flag = MkFlag Int (MVar Bool)
  
  Now newMVar needs to consult a global variable to get the
  next Flag number, but after that there's no global locking.
  
  This is, of course, precisely what we'd have to do to make
  MVars an instance of Ord --- but it would impose a cost on
  all MVars, whether or not they needed it, which is why we've not
  done it.
  
This is something that I have long been wondering about
(perhaps it is just because of my ignorance):
Wouldn't stable pointers be a cheaper and more appropriate means
to get Ord for MVars, STRefs, and IORefs?


Best regards,

Wolfram



Re: Trivial Haskell Concurrency problem

2000-02-15 Thread Marcin 'Qrczak' Kowalczyk

Tue, 15 Feb 2000 11:20:45 +0100, George Russell [EMAIL PROTECTED] pisze:

 In this case it could be filled by having a supply of guaranteed
 distinct elements from a linear order, which doesn't have to require
 a central dispatch centre.  (For example, you could allocate them
 on each processor and append a processor id.)

If the IO monad can maintain a random number generator, it can as
well mainain unique Integer supply. The interface is clean.

And what about having unsafePtrCompare in addition to IOExts.unsafePtrEq?

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ 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-




Re: Trivial Haskell Concurrency problem

2000-02-15 Thread George Russell

Marcin 'Qrczak' Kowalczyk wrote:
 If the IO monad can maintain a random number generator, it can as
 well mainain unique Integer supply. The interface is clean.
It can, but according to the current specification, it doesn't.  Maybe
it should.  I think Integer is a little too specific - how about

type Unique implements (Ord,Eq)
newUnique :: IO Unique

?
 
 And what about having unsafePtrCompare in addition to IOExts.unsafePtrEq?
I don't think unsafePtrCompare will get us out of jail here.  Compacting
garbage collection might change the order of the pointers around inbetween
one thread comparing them and the other.



Re: Trivial Haskell Concurrency problem

2000-02-15 Thread Michael Hobbs

George Russell wrote:
 Does the phrase "Dining Philosophers Problem" ring a bell with anyone?

And AFAIK, the existing solutions to that problem requires a knowledge
of who all the philosophers are and what they are attempting to do. That
gets back to the issue of having a global value that stores a list of
all philosophers.



Re: Trivial Haskell Concurrency problem

2000-02-15 Thread Marcin 'Qrczak' Kowalczyk

Tue, 15 Feb 2000 14:14:09 +0100, George Russell [EMAIL PROTECTED] pisze:

 I think Integer is a little too specific - how about
 
 type Unique implements (Ord,Eq)
 newUnique:: IO Unique

Somebody may want to generate unique idenifiers or unique values of
another concrete type.

The requirement could be even stronger, that the integers are
increasing, so one can compare relative time of IO events without
either relying on high resolution clock (which does not guarantee
uniqueness) or passing such generator everywhere explicitly.

And with the ability of initialization to a specific value (plus one),
so the unique sequence can be continued in another session. Like the
random number generator.

The implementation is very simple, but can't be done using only
standard functions efficiently (one could at most store the state
in some file).

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ 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-




Re: Trivial Haskell Concurrency problem

2000-02-15 Thread Tom Pledger

Hi.

George Russell writes:
  I _think_ your (Tom Pledger's) solution can deadlock.
  Suppose we have two simultaneous calls to lowerFlags
  (call 1)   lowerFlags f1 f2
  (call 2)   lowerFlags f2 f1
  Then we have
  
  (initially f1 and f2 are both Up)
  Call 1   Call 2
  (sag) putMVar f1 Sagging (sag) putMVar f2 Sagging
  takeMVar f2 (result is Sagging)  takeMVar f1 (result is Sagging)
  swapMVar f1 up   swapMVar f2 up   
  
  At this point both calls must deadlock, since you can't do a
  swapMVar on an empty MVar.

True.  :-(

That would be fixed by putting the taken flag before swapping the
other flag - but only in the case when the call is retreating for a
retry.

Anyway, my approach is at best a small special case of Michael Hobbs's
approach.

For two threads to have access to the same MVar, they must have a
common ancestor, right?  Could a common ancestor spawn a transaction
broker thread?  That would be similar to what database management
systems do.  It'd still be centralised, but wouldn't need to do unsafe
IO.

Regards,
Tom



Re: Trivial Haskell Concurrency problem

2000-02-15 Thread Marcin 'Qrczak' Kowalczyk

Tue, 15 Feb 2000 18:57:51 +0100, George Russell [EMAIL PROTECTED] pisze:

  The requirement could be even stronger, that the integers are
  increasing, so one can compare relative time of IO events without
 Absolutely not.  If you have 5000 processors, how are they to work out
 which one did an IO event first?  I don't really see the point anyway.

...relative time of IO events that occured in a single thread.
(=) imposes the sequencing.

Or maybe more: including also the order of events in different threads
that were sequenced by MVar operations.

It seems easy to promise anyway, at least the first. A global counter,
either protected by MVar, which gives also the second, or separate
for each thread, which does not and may be faster but I guess requires
support in the compiler itself, not only libraries.

BTW: The random generator from the IO monad seems to be not
thread-safe. Oops. I think it should be either fixed or documented.

 I definitely prefer my abstract "Unique" type.  Easy to implement
 efficiently on any conceivable system.

AFAIK Tcl requires inventing window identifiers, which should be unique
if I want fresh windows. TclHaskell frees the programmer from the
requirement to do it himself, maintaining its own unique supply. It
uses its own monad, IO with state. In some cases it would be very
inconvenient to require the user of a library to use a different
monad *only* because the library needs a supply of unique strings!

 Also it means whoever writes the definition doesn't have to worry
 about whether to use "Int" or "Integer".  (If someone writes a
 server in Haskell which manages to stay up for years it could very
 easily overflow Int . . .)

That's why I said Integer, not Int :-)

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a22 C+++$ UL++$ 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-




Re: Trivial Haskell Concurrency problem

2000-02-15 Thread Wolfram Kahl

Simon Peyton-Jones [EMAIL PROTECTED] answers my question:
  
  | This is something that I have long been wondering about
  | (perhaps it is just because of my ignorance):
  | Wouldn't stable pointers be a cheaper and more appropriate means
  | to get Ord for MVars, STRefs, and IORefs?
  
  Could be -- but do we really want to clog up the stable-pointer table
  with an entry for every MVar, whether or not anyone is interested in
  ordering?
  
  I think what you want is a distributed way to get a unique,
  as George suggested.  Then you can pair that with an MVar when
  you want something comparable.  The unique can include the processor
  id, so it can be globally unique.  64 bits?
  
  I'm still leery of putting such a unique inside every MVar, IORef etc.
  But maybe I shouldn't worry.
  

Perhaps I should give some background:
I am interested in implementing graph structures,
and would need to handle mappings between graphs,
or node labellings, or whatever.
All these mappings need not reside in the graph itself,
so they would require some FiniteMap structure.
However, most decent such data types require Ord
for being able to work efficiently.
If IORefs (or whatever I use) are not ordered,
then I have essentially two possibilities:

1) Do the Integer trick: slows down my program
   (as actually experienced in OCaml)

2) Do the memory management myself by allocating
   huge arrays and using the indices which are in Ord: clumsy and unwieldy

So  I would already be happy if IORefs, STRefs and MVars came with a variant
in Ord (consider this as a concrete proposal for the standard library)
--- even if some implementations choose to implement that via the
Integer trick: hopefully the best implementations
would provide something faster ;-)


Best regards,

Wolfram




Trivial Haskell Concurrency problem

2000-02-14 Thread George Russell

Sorry if you don't want to be bothered with my problems, but I think this
problem which I've just encountered is rather amusing.  Is there a neat solution?
I confess to finding concurrency problems difficult so there might be.

I want to implement a type Flag.  Each flag is either Up or Down.  When you
create a flag (there is a newFlag :: IO Flag operation) it is Up.  The only
operation permitted on Flags is

lowerFlags :: Flag - Flag - IO Bool

If both arguments are Up, lowerFlags should lower them both and return
True, otherwise it should leave them as they are and return False.
The problem is that lowerFlags should appear to be atomic, so that
if lowerFlags is called simultaneously in different threads, the result
should be the same as if one of the calls completed before the other started.

So for example the following code
   type Flag = MVar Bool -- True means Up

   newFlag = newMVar True

   lowerFlags flag1 flag2 =
  if (flag1 == flag2)
  then
 error "Illegal call to lowerFlags" -- this is not allowed
  else
 do
val1 - takeMVar flag1
-- point A
val2 - takeMVar flag2
let success = (val1  val2)
putMVar flag2 (not success  val2)
putMVar flag1 (not success  val1)
won't work, because if lowerFlags is called simultaneously with the same arguments
but in a different order, and both calls reach point A simultanously, then both
threads will block when they attempt the takeMVar in the next line.

What is the neatest solution?  There is an obvious solution, which is to
crudely sequence all calls to lowerFlags by making them lock a single
global variable (created using, sigh, unsafePerformIO) but this doesn't seem very
elegant.  If MVar's were instances of Ord as well as Eq, a neat solution would
be to always get the least MVar first, but they aren't.  So what should one do?



Trivial Haskell Concurrency problem

2000-02-14 Thread Tom Pledger

Tom Pledger writes:
  [...]
  
  Something along these lines:

But without the bug and the eccentricities.  :-(

  [...]
  wasDown2 - sag flag2

This just moved the deadlock.  Instead of doing a busy wait for a
non-sagging flag2, we must put flag1 back up and try again from the
beginning of lowerFlags.

  _ - takeMVar flag1 -- We know flag1 is now sagging

Or:takeMVar flag1

  if wasDown2 then putMVar flag1 Up else do
_ - takeMVar flag2   -- We know flag2 is now sagging
putMVar flag2 Down

Or:if ...
 swapMVar flag2 Down

Regards,
Tom



Re: Trivial Haskell Concurrency problem

2000-02-14 Thread Michael Hobbs

George Russell wrote:
 The problem is that lowerFlags should appear to be atomic, so that
 if lowerFlags is called simultaneously in different threads, the result
 should be the same as if one of the calls completed before the other started.

If you want lowerFlags to be atomic, in the global sense, then you
really have no other option than to create a "global" variable (read:
unsafePerformIO). Intuitively, this make sense: if some thread needs to
know whether or not it has permission to perform lowerFlags, then there
must be some sort of common mutex with which to communicate with the
other threads. Depending on your situation, this common mutex could
perhaps exist in a closure.

However, I believe that you can be "reasonably" atomic without a global
variable. That is, if two or more lowerFlags calls are called with the
same Flag value, they will execute serially. I haven't thought enough
about it to come up with a concrete solution. If this is good enough,
I'll see if I can noodle on it some more.

- Michael Hobbs



Re: Trivial Haskell Concurrency problem

2000-02-14 Thread Michael Hobbs

George Russell wrote:
 What is the neatest solution?  There is an obvious solution, which is to
 crudely sequence all calls to lowerFlags by making them lock a single
 global variable (created using, sigh, unsafePerformIO) but this doesn't seem very
 elegant.  If MVar's were instances of Ord as well as Eq, a neat solution would
 be to always get the least MVar first, but they aren't.  So what should one do?

Okay, I thought about this a little more. You are very much on the right
track here. Breaking it down to fundamentals: somehow, some way, you
need to "lock" a Flag variable, so that if some other thread performs
lowerFlags with the same variable, it will wait. Then, considering that
the function takes two Flag variables in any arbitrary order, we can get
into a deadlock situation depending on which one is locked first. (We're
assuming that we can't lock them both simultaneously) Therefore, to get
around this, we need to impose some sort of ordering on the variables so
that one is always locked before the other, regardless of the order in
which they're passed.

Here's the solution: random. Since newFlag is declared IO Flag, you
should be able to easily embed a random number into the data type for
Flag. Granted, there is still the possibility that two Flag values get
assigned the same random number, in which case you won't know which one
will get locked first. But I think the odds of that happening are small
enough (unless you're generating billions of Flags and performing
trillions of lowerFlags calls).

A more sure-fire way of generating a unique number is to create a
"sequence" function, which will return the next number in a sequence
each time it's called. But again, such a function would require an
unsafePerformIO if it is to be used globally.

...or querying the system time, down to the nanosecond...

- Michael Hobbs



Re: Trivial Haskell Concurrency problem

2000-02-14 Thread Michael Hobbs

Michael Hobbs wrote:
 (We're assuming that we can't lock them both simultaneously)

I knew I should have read the literature on deadlock avoidance before
posting that message. :-/  In fact, I should have used the word
"atomically" above instead of "simultaneously". As it turns out, I
believe that assumption was incorrect. That is, it is possible to create
an atomic operation that locks two values, while avoiding deadlock.
Here's my stab at it. (NB: This is simply an off-the-cuff attempt. It
looks like it should work right, but it is far from rigorously tested or
analyzed.)

type PairMVar a = (MVar Bool, IORef a)

takePairMVar :: PairMVar a - PairMVar b - IO (a, b)
takePairMVar a@(claimA, refA) b@(claimB, refB) = do
  -- Attempt to lay claim to the A value. This will block if some other
thread
  -- has successfully completed A takePairMVar call using this value.
  aIsClaimed - takeMVar claimA
  if aIsClaimed then do
-- Some other thread has snuck in and laid claim to A. Release
claimA and
-- try again.
putMVar claimA aIsClaimed
takePairMVar a b
   else do
-- Establish our claim on A and release claimA.
putMVar claimA True
-- Attempt to lay claim to the B value.
bIsClaimed - takeMVar claimB
-- We need to takeMVar claimA regardless of whether bIsClaimed or
not.
-- At this point, we have a lock on claimB and are attempting to
lock
-- claimA. If some other thread has a lock on claimA and is
attempting to
-- lock claimB, we have a deadlock. However, this should never
happen since
-- we have established our claim on A so no other thread should have
claimA
-- locked indefinitely.
takeMVar claimA
if bIsClaimed then do
  -- Some other thread has snuck in and laid claim to B. Relinquish
all of
  -- our claims and try again.
  putMVar claimA False
  putMVar claimB bIsClaimed
  takePairMVar a b
 else do
  -- We have successfully locked claimA and claimB. We never
explicitly set
  -- claimB to True, since we have implicitly claimed it by keeping
it
  -- locked.
  valA - readIORef refA
  valB - readIORef refB
  return (valA, valB)

putPairMVar :: PairMVar a - PairMVar b - a - b - IO ()
putPairMVar (claimA, refA) (claimB, refB) a b = do
  -- Fairly straightforward. Write the values and relinquish all claims.
  writeIORef refA a
  writeIORef refB b
  putMVar claimA False
  putMVar claimB False
  return ()



Re: Trivial Haskell Concurrency problem

2000-02-14 Thread Michael Hobbs

Michael Hobbs wrote:
 Here's my stab at it. (NB: This is simply an off-the-cuff attempt. It
 looks like it should work right, but it is far from rigorously tested or
 analyzed.)

grumble/

I discovered a path that would cause a deadlock in that code as well.
However, I have a change that /should/ prevent the deadlock. If anyone's
interested, email me privately, so I don't waste this list's bandwidth
with continuous revisions.

- Michael Hobbs