Next: , Previous: , Up: C and Smalltalk  


5.10 Incubator support

The incubator concept provides a mechanism to protect newly created objects from being accidentally garbage collected before they can be attached to some object which is reachable from the root set.

If you are creating some set of objects which will not be immediately (that means, before the next object is allocated from the Smalltalk memory system) be attached to an object which is still “live” (reachable from the root set of objects), you’ll need to use this interface.

If you are writing a C call-out from Smalltalk (for example, inside a module), you will not have direct access to the incubator; instead the functions described in Smalltalk types automatically put the objects that they create in the incubator, and the virtual machine takes care of wrapping C call-outs so that the incubator state is restored at the end of the call.

This section describes its usage from the point of view of a program that is linking with libgst.a. Such a program has much finer control to the incubator. The interface provides the following operations:

Macro: void INC_ADD_OOP (OOP anOOP)

Adds a new object to the protected set.

Macro: inc_ptr INC_SAVE_POINTER ()

Retrieves the current incubator pointer. Think of the incubator as a stack, and this operation returns the current stack pointer for later use (restoration) with the incRestorePointer function.

Macro: void INC_RESTORE_POINTER (inc_ptr ptr)

Sets (restores) the incubator pointer to the given pointer value.

Typically, when you are within a function which allocates more than one object at a time, either directly or indirectly, you’d want to use the incubator mechanism. First you’d save a copy of the current pointer in a local variable. Then, for each object you allocate (except the last, if you want to be optimal), after you create the object you add it to the incubator’s list. When you return, you need to restore the incubator’s pointer to the value you got with INC_SAVE_POINTER using the INC_RESTORE_POINTER macro.

Here’s an example from cint.c:

The old code was (the comments are added for this example):

  desc = (_gst_cfunc_descriptor)
     new_instance_with (cFuncDescriptorClass, numArgs);
  desc->cFunction = _gst_cobject_new (funcAddr);    // 1
  desc->cFunctionName = _gst_string_new (funcName); // 2
  desc->numFixedArgs = FROM_INT (numArgs);
  desc->returnType = _gst_classify_type_symbol (returnTypeOOP, true);
  for (i = 1; i <= numArgs; i++) {
    desc->argTypes[i - 1] =
     _gst_classify_type_symbol(ARRAY_AT(argsOOP, i), false);
  }

  return (_gst_alloc_oop(desc));

desc is originally allocated via newInstanceWith and allocOOP, two private routines which are encapsulated by the public routine objectAlloc. At “1”, more storage is allocated, and the garbage collector has the potential to run and free (since no live object is referring to it) desc’s storage. At “2” another object is allocated, and again the potential for losing both desc and desc->cFunction is there if the GC runs (this actually happened!).

To fix this code to use the incubator, modify it like this:

  OOP     descOOP;
  IncPtr  ptr;

  incPtr = INC_SAVE_POINTER();
  desc = (_gst_cfunc_descriptor)
     new_instance_with (cFuncDescriptorClass, numArgs);
  descOOP = _gst_alloc_oop(desc);
  INC_ADD_OOP (descOOP);

  desc->cFunction = _gst_cobject_new (funcAddr);    // 1
  INC_ADD_OOP (desc->cFunction);

  desc->cFunctionName = _gst_string_new (funcName); // 2
  /* since none of the rest of the function (or the functions it calls)
   * allocates any storage, we don’t have to add desc->cFunctionName
   * to the incubator’s set of objects, although we could if we wanted
   * to be completely safe against changes to the implementations of
   * the functions called from this function.
   */

  desc->numFixedArgs = FROM_INT (numArgs);
  desc->returnType = _gst_classify_type_symbol (returnTypeOOP, true);
  for (i = 1; i <= numArgs; i++) {
    desc->argTypes[i - 1] =
     _gst_classify_type_symbol(ARRAY_AT(argsOOP, i), false);
  }

  return (_gst_alloc_oop(desc));

Note that it is permissible for two or more functions to cooperate with their use of the incubator. For example, say function A allocates some objects, then calls function B which allocates some more objects, and then control returns to A where it does some more execution with the allocated objects. If B is only called by A, B can leave the management of the incubator pointer up to A, and just register the objects it allocates with the incubator. When A does a INC_RESTORE_POINTER, it automatically clears out the objects that B has registered from the incubator’s set of objects as well; the incubator doesn’t know about functions A & B, so as far as it is concerned, all of the registered objects were registered from the same function.


Next: , Previous: , Up: C and Smalltalk