Common Processes

Metadata

Author
Richard A. O'Keefe
Date Created
2011.08.30
Date Revised
2012.03.02
Experts
(any implementors want to volunteer?)
Prerequisites
None
Supersessions
None
Incompatibility
None known
Existing material
The Blue Book; Inside Smalltalk; VisualWorks Smalltalk; VisualAge Smalltalk; Squeak; Pharo; Dolphin Smalltalk; GNU Smalltalk; POSIX.2 (Single Unix Specification)
License
The code in my Smalltalk is completely free, as is all code in this STEP.
Editor
Richard A. O'Keefe until replaced.
Abstract
The Blue Book description of concurrency support in Smalltalk-80 still holds good, or very nearly so, for the Smalltalks listed above. It's time this was in the standard. Multicore machines are now commonplace; in order to exploit this in portable Smalltalk we need standard concurrency support. The de jure concurrency interface might as well be the de facto one.

Motivation

There is no concurrency support in the ANSI Smalltalk standard.

There are at least four reasons why we need concurrency support.

As it happens, I don't much care for the Smalltalk concurrency model. It's a simple model, but a dangerous one. For my own system, I was originally glad that concurrency was not in the standard, because that left me free to explore the possibility of shared-nothing message-passing concurrency like Erlang's. However, as a step towards that, I quickly hacked up a thread library to sit on top of POSIX threads, and was shocked at how quickly it came together and how close it was possible to get to the Blue Book.

Now if only there were some way we could all know what concurrency operations were expected to be portable…

Technical Specification

Warning: this is a draft. I have couched it in the classic language of classes, rather than the Standard's language of protocols.

Process states

For the purposes of this description, each Process will be in exactly one of the following states:

waiting
The Process is not executing because it is waiting for some event, such as a Semaphore being signalled.
suspended
The Process is not executing because it has just been created or has suspended itself.
terminated
The Process has completed execution, either successfully or unsuccessfully. It could be useful to discover whether a Process was terminated because of an uncaught exception, but that's not (yet) in this interface, so we do not need to distinguish these kinds of termination.
ready
The Process is ready to run. Some Smalltalk systems call this “runable”, which is a spelling mistake not to be perpetuated.
active
The Process is actually executing.

There is a standard way to tell whether aProcess isTerminated; there is no standard way to discriminate the other states, because the current state of a Process is an evanescent property, except for being terminated, which is stable.

“Evanescence” refers to the fact that in a truly concurrent system, if you ask what state a shared object is in, by the time you look at the answer the object may well not be in that state any more. Even in a single-core machine, if there is pre-emptive scheduling such properties must always be treated as out of date. Some properties, like names given to processes, could change and so be evanescent, but in practice they don't change, and have been omitted. One aim in developing this proposal is that no properties that change evanescently as part of normal operation should be included. That does not mean that existing systems cannot continue to offer everything they offer now, only that intrinsically unreliable operations should not be in the standard.

global constant Processor

Each Process sees a global constant called Processor. Since a Processor might have the responsibility of scheduling tasks on a particular core, it is credible that there might be a Processor object per core. It is therefore not specified whether there is one Processor variable or many. Since a Process might be moved from one core to another, it is not guaranteed that a process will always see the same Processor object:

Processor yield; yourself == Processor

might answer false because the process was migrated between the two evaluations of Processor; just as any other global variable might have different values before and after a #yield.

The class that the/each Processor belongs to is not specified. In particular, ProcessorScheduler is not to be part of the standard.

The methods specified here for Processor all either refer to the “active” process (the one making the request) or return a fixed constant.

object methods

Note that Processor lowestPriority ≤ Processor userBackgroundPriority ≤ Processor userSchedulingPriority ≤ Processor userInterruptPriority ≤ Processor highestPriority, but any or all of them might be equal.

While #lowestPriority is not implemented in all the systems I checked, it is implementable by adding a one-liner.

Only Dolphin has #suspendActive, but that's a one-line addition. It is important not to include a facility for suspending any other process in the standard.

VisualAge does not have #terminateActive, but that's a one-line addition. It is important not to include a facility for terminating any other process in the standard.

class Process

class methods

None presented.

instance methods

Rationale

VisualAge lacks #isTerminated; I'm not sure if #isDead is the same thing, but I think so. This state test is included because once it becomes true, it remains true. Other state tests are evanescent.

The Blue Book (and Common) methods #suspend and #terminate are deliberately absent from this draft. The safe uses of them have been replaced by #suspendActive and #terminateActive in Processor.

#suspend and #resume are useful building blocks for an operating system, which is why they have a place in real Smalltalks. They are disasters for building reliable user-level programs, because any synchronisation pattern you might set up could be disrupted from the outside. To quote the Java documentation:

Why are Thread.suspend and Thread.resume deprecated?

Thread.suspend is inherently deadlock-prone. If the target thread holds a lock on the monitor protecting a critical system resource when it is suspended, no thread can access this resource until the target thread is resumed. If the thread that would resume the target thread attempts to lock this monitor prior to calling resume, deadlock results. Such deadlocks typically manifest themselves as 'frozen' processes.

In addition, if you want to implement Smalltalk threads on top of POSIX threads, it matters that pthreads do not provide suspension or resumption.

#onUncaughtException: is new. The intention is to underpin an Erlang-style linking mechanism so that a failing Process can take down a whole group of Processes, or so that a worker can be restarted by a supervisor. But any approach you might want needs to be hooked in somehow, and allowing a single block to be invoked seemed the simplest and most general.

<niladicBlock>

instance methods

<blocks in general>

instance methods

As shown, any Smalltalk that supports #newProcess and the Process methods #name:, #priority:, and #resume can trivially support all of these methods.

class Semaphore

A Semaphore may be thought of as containing a non-negative integer counter and a possibly empty queue of suspended processes. Semaphores are identity objects.

class methods

instance methods

The #signalAfter: and #signalAt: methods are new to Semaphore. Most Smalltalks give that responsibility to Processor. The Blue Book and VisualAge have #signal:atTime:, GNU Smalltalk has #signal:atMilliseconds:, and Dolphin has #signal:afterMilliseconds:. Squeak has #timeoutSemaphore:afterMSecs: and puts it in Delay. With no agreement over what class has the responsibility, I've chosen to put delayed signalling in the same class as undelayed signalling. This provides a common interface to the implementation-specific methods.

DELETED METHODS

Beware! These are consensus methods. It is common practice for a Semaphore to be a LinkedList instead of having one, which results in these methods being inherited. They are well missing from VisualAge, where Semaphores are not collections of any kind, but have trivial implementations.

However, these are evanescent properties. In a truly concurrent environment, the fact that a semaphore's queue was (or was not) empty when you asked a few nanoseconds ago doesn't mean it is still empty (or not) now.

They are not part of this specification.

Semaphores have a grave defect, which is that if a process tries to acquire a resource it is already holding, it deadlocks itself. Another kind of synchronisation object is needed, which Pharo and my Smalltalk, following POSIX, calls a “Mutex” and VW and GNU ST call a RecursionLock. Mutex may be added to the next draft.

Priorities have been a strong feature of Smalltalk concurrency since the Blue Book. Locking using semaphores can lead to priority inversion, where a high priority process is delayed while waiting for a semaphore held by a low priority process. The best known methods for coping with this rely on knowing which process holds a lock so that its priority can be temporarily adjusted. As noted in the previous paragraph, there is no notion of a semaphore being held by a particular process. Even a semaphore created forMutualExclusion is just a semaphore initialised a particular way. This is another reason why Mutex (or RecursionLock) really belongs in the standard.

class SharedQueue

class methods

instance methods

DELETED METHODS

Beware! #isEmpty, #notEmpty, #peek, #size are consensus methods, but they do not make sense in a truly concurrent system. In a classic system we expect

(x := aSharedQueue peek) isNil or: [x = aSharedQueue next]

to be true, but in a truly concurrent system (or even a single core system with pre-emptive scheduling) this can easily fail. These methods may be removed from the next draft.

There is another reason for omitting #peek, which is that existing systems do not agree. As described in Inside Smalltalk and implemented in GNU Smalltalk, if the queue is currently empty, #peek waits until there is an element and then returns it. As implemented in Squeak, VisualWorks, and Dolphin, #peek is really #peekOrNil, answering nil if there's nothing there at the moment.

Squeak offers a #nextOrNil method which answers nil if the queue is currently empty. Dolphin calls it #nextNoWait. Other Smalltalks do not seem to have it. Something like this might be in the next draft.

class Delay

The argument for putting Delay in the standard is that it is standard. All Smalltalk systems known to me include a Delay class which can be used to make a Process wait some amount of time, and they all include Blue Book methods.

The argument against putting Delay in the standard is that the behaviour is not common. Systems do not agree on the answer to “once a Process has begun to wait on a Delay, when is it safe to use that Delay again?” I've found three answers:

The presence of #resumptionTime in the Blue Book protocol isn't compatible with the answer “at once”, although its undefinition when there is no delayed Process isn't compatible with safe use either.

One problem is that there isn't any commonly available way to tell whether a Delay is in use by another process (other than knowing that it has not escaped to any other process, or course) and in a multicore system there is no possible simple way to tell, this being an evanescent property.

The standard could provide Delay with single-shot semantics, which the other systems could support. The problem is that programmers using multi-shot Delays in their systems might think “I am using Delays; Delays are standard; therefore my program is standard” when it is not. This code, taken from a well known Smalltalk system, is not portable:

delay := Delay forMilliseconds: 50.
[self anyButtonPressed] whileFalse: [delay wait].

variable Transcript

One new method is required so that concurrent threads may safely share the transcript.

object methods

Negative properties

With the exception of the classes and objects in this STEP, no standard objects are intended to be shared by concurrent processes. An object may be created by one thread and handed off to another, but there must be at least one synchronisation operation between the last access from the first thread and the first from the second.

Rationale

Processor

There appears to be no reason for most programs to be aware of the ProcessorScheduler class, so it's not included. Assorted books claim that there is only one Processor object. My system makes Processor a class with no instances, the easiest way to get a single named object, but that cannot be imposed on other systems. There are advantages in having a “scheduler” object per CPU core, but there's no reason that object has to be Processor.

The #terminateActive and #suspendActive methods cover the safe uses of #terminate and #suspend, so that we do not need to include those rather dangerous operations in the standard.

SharedQueue

If you have Semaphores, you can have SharedQueues; the Blue Book is quite clear about how to do that. So there's really very little reason not to provide them.

Backwards-incompatible changes

As noted, #suspend and #terminate are not in this interface. Nothing prevents an implementation adding them.

There are two changes that deserves serious consideration.

For the first we have the example of the Single Unix Specification before us. A process that terminates itself can be assumed to know what locks it is holding and to be responsible for ensuring that breaking these locks is safe. But if one process terminates another, the killer cannot know what locks the victim holds or whether it is safe to break its hold on them, nor is the victim expecting to be killed so that it can make this safe. POSIX offers robust locks: if a thread that holds a mutex is killed, the next thread to claim the mutex is given it, but warned that it is in an inconsistent state. That thread may then repair the state, and tell the mutex that all is well again. If not, a second attempt to claim the lock will be treated as an error. Mimicking that requires the inclusion of Mutex/RecursionLock.

Reference implementation

Existing Smalltalk implementations are already pretty close to this. I could supply change sets for Squeak, Pharo, Dolphin, and Visual Works, and an additional source file for GNU Smalltalk easily enough.

Additions to Processor

This is expressed in terms of ProcessorScheduler, just so that it can be used with some existing systems.

ProcessorScheduler
  methods:
    suspendActive
      self activeProcess suspend.
    terminateActive
      self activeProcess terminate.
    waitFor: aDuration
      (Delay forSeconds: aDuration asSeconds) wait.
    waitUntil: aDateAndTime
      self waitFor: DateAndTime now - aDateAndTime

Additions to Semaphore

Semaphore
  methods:  
    signalAfter: aDuration
      |d|
      0 < (d := aDuration asSeconds) 
        ifTrue:  [[(Delay forSeconds: d) wait. self signal] fork]
        ifFalse: [self signal].
    signalAt: aDateAndTime
      self signalAfter: aDateAndTime - DateAndTime now.

SharedQueue

Here I provide a model implementation of SharedQueue for three reasons.

Time millisecondsToRun: [
  |n q|
  n ← 1000.
  q ← class new: n.
  1 to: n do: [:x | q nextPut: x].
  1 to: 1000000 do: [:i | q nextPut: q next]]
Dialect Built-in This versionSpeedup
VisualWorks12,345 msec 400 msec 30·85
Pharo 57,490 msec1,094 msec 52·55
GNU 5,274 msec3,801 msec 1·39
Dolphin 6,815 msec5,406 msec 1·26
astc* 585 msec 342 msec 1·71

This is of course a contrived case, but it's easy to contrive. [*] The astc code uses POSIX mutexes and conditions rather than semaphores.

Object subclass: #SharedQueue
  instanceVariableNames: 'array head tail size capacity mutex avail'
  “invariants:
    array isMemberOf: Array
    array size = capacity
    1 ≤ head ≤ capacity
    1 ≤ tail ≤ capacity
    0 ≤ size ≤ capacity
    avail size = size”

  class methods for: 'instance creation'
    new
      ↑self new: 5
    new: n
      ↑self basicNew pvtPostNew: (n max: 1)

  methods for: 'initialization'
    pvtPostNew: n
      array    ← Array new: n.
      capacity ← n.
      size     ← 0.
      head     ← 1.
      tail     ← 1.
      mutex    ← Semaphore forMutualExclusion.
      avail    ← Semaphore new.

  methods for: 'accessing'      
    next
      |r|
      avail wait.
      mutex critical: [
        r ← array at: head.
        array at: head put: nil.
        head ← head = capacity ifTrue: [1] ifFalse: [head + 1].
        size ← size - 1].
      ↑r
    nextPut: item
      mutex critical: [
        size = capacity ifTrue: [
          |a n p|
	  n ← capacity + size.
	  a ← Array new: n.
	  p ← head.
	  1 to: size do: [:i |
            a at: i put: (array at: p).
            p ← p = capacity ifTrue: [1] ifFalse: [p + 1]].
	  array    ← a.
	  capacity ← n.
	  head     ← 1.
	  tail     ← head + size].
	array at: tail put: item.
	tail ← tail = capacity ifTrue: [1] ifFalse: [tail + 1].
	size ← size + 1].
      avail signal.
      ↑item
    nextPutAll: items
      mutex critical: [
	|m|
	m ← items size.
	size + m > capacity
	  ifTrue: [
            |a n p|
	    n ← (capacity max: m) + size.
	    a ← Array new: n.
	    p ← head.
	    1 to: size do: [:i |
	      a at: i put: (array at: p).
	      p ← p = capacity ifTrue: [1] ifFalse: [p + 1]].
	    items do: [:each |
	      a at: (size ← size + 1) put: each].
	    array    ← a.
	    capacity ← n.
	    head     ← 1.
	    tail     ← head + size]
          ifFalse: [
	    items do: [:each |
	      a at: tail put: each.
	      tail ← tail = capacity ifTrue: [1] ifFalse: [tail + 1]].
	    size ← size + m]].
        1 to: m do: [:i | avail signal].
      ↑items

Additions to Block and NiladicBlock

Block
  methods:
    newProcessWith: anArray
      ((anArray isKindOf: Array) and:
       [anArray size = self argumentCount]
      ) ifFalse: [self valueWithArguments: anArray "die"].
      ↑[self valueWithArguments: anArray] newProcess

NiladicBlock
  methods:
    atPriority: aPriority
      |thisProcess oldPriority|
      thisProcess ← Processor activeProcess.
      oldPriority ← thisProcess priority.
      ↑[thisProcess priority: aPriority. self value]
         ensure: [thisProcess priority: oldPriority]

The End.