Next: Object representation, Previous: Smalltalk callbacks, Up: C and Smalltalk
In addition to the functions described so far, the VMProxy
that is
available to modules contains entry-points for many functions that aid
in developing GNU Smalltalk extensions in C. This node documents these
functions and the macros that are defined by libgst/gstpub.h.
This functions accepts a function pointer and an OOP (or NULL
, but
not an arbitrary pointer) and sets up the interpreter to call the
function as soon as the next message send is executed.
Caution: This and the next two are the only functions in the
intepreterProxy
that are thread-safe.
This functions accepts an OOP for a Semaphore
object and signals
that object so that one of the processes waiting on that semaphore is
waken up. Since a Smalltalk call-in is not an atomic operation, the
correct way to signal a semaphore is not to send the signal
method to the object but, rather, to use:
asyncSignal(semaphoreOOP)
The signal request will be processed as soon as the next message send is executed.
This functions accepts an OOP for a Semaphore
object and signals
that object so that one of the processes waiting on that semaphore is
waken up; the signal request will be processed as soon as the next
message send is executed. The object is then removed from the registry.
When no Smalltalk process is running, GNU Smalltalk tries to limit CPU usage
by pausing until it gets a signal from the OS. wakeUp
is an
alternative way to wake up the main Smalltalk loop. This should rarely
be necessary, since the above functions already call it automatically.
This functions accepts an OOP for a Semaphore
object and signals
that object so that one of the processes waiting on that semaphore is
waken up. If the semaphore has no process waiting in the queue and
the second argument is true, an excess signal is added to the semaphore.
Since a Smalltalk call-in is not an atomic operation, the correct way to
signal a semaphore is not to send the signal
or notify
methods to the object but, rather, to use:
syncSignal(semaphoreOOP, true)
The sync
in the name of this function distinguishes it from
asyncSignal
, in that it can only be called from a procedure
already scheduled with asyncCall
. It cannot be called from
a call-in, or from other threads than the interpreter thread.
This function is present for backwards-compatibility only and should not be used.
This functions show a backtrace on the given file.
The objectAlloc
function allocates an OOP for a newly created
instance of the class whose OOP is passed as the first parameter; if
that parameter is not a class the results are undefined (for now, read
as “the program will most likely core dump”, but that could change in
a future version).
The second parameter is used only if the class is an indexable one,
otherwise it is discarded: it contains the number of indexed instance
variables in the object that is going to be created. Simple uses of
objectAlloc
include:
OOP myClassOOP; OOP myNewObject; myNewObjectData obj; … myNewObject = objectAlloc(myClassOOP, 0); obj = (myNewObjectData) OOP_TO_OBJ (myNewObject); obj->arguments = objectAlloc(classNameToOOP("Array"), 10); …
Return the number of indexed instance variables in the given object.
Return an indexed instance variable of the given object. The index is in the second parameter and is zero-based. The function aborts if the index is out of range.
Put the object given as the third parameter into an indexed instance variable of the object given as the first parameter. The index in the second parameter and is zero-based. The function aborts if the index is out of range.
The function returns the old value of the indexed instance variable.
Return the kind of indexed instance variables that the given object has.
Return a pointer to the first indexed instance variable of the given object. The program should first retrieve the kind of data using OOPIndexedKind.
Return the class of the Smalltalk object passed as a parameter.
Return the superclass of the class given by the Smalltalk object, that is passed as a parameter.
Return true if the class given as the first parameter, is the same or a superclass of the class given as the second parameter.
Return true if the object given as the first parameter is an instance of the class given as the second parameter, or of any of its subclasses.
Return true if the class given as the first parameter implements or overrides the method whose selector is given as the second parameter.
Return true if instances of the class given as the first parameter respond to the message whose selector is given as the second parameter.
Return true if the object given as the first parameter responds to the message whose selector is given as the second parameter.
Finally, several slots of the interpreter proxy provide access to the system objects and to the most important classes. These are:
nilOOP
, trueOOP
, falseOOP
, processorOOP
objectClass
, arrayClass
, stringClass
,
characterClass
, smallIntegerClass
, floatDClass
,
floatEClass
, byteArrayClass
, objectMemoryClass
,
classClass
, behaviorClass
, blockClosureClass
,
contextPartClass
, blockContextClass
,
methodContextClass
, compiledMethodClass
,
compiledBlockClass
, fileDescriptorClass
,
fileStreamClass
, processClass
, semaphoreClass
,
cObjectClass
More may be added in the future
The macros are20:
Dereference a pointer to an OOP into a pointer to the actual object data
(see Object representation). The result of OOP_TO_OBJ
is not
valid anymore if a garbage-collection happens; for this reason, you
should assume that a pointer to object data is not valid after doing a
call-in, calling objectAlloc
, and caling any of the “C to
Smalltalk” functions (see Smalltalk types).
Return the OOP for the class of the given object. For example,
OOP_CLASS(proxy->stringToOOP("Wonderful GNU Smalltalk"))
is the
String
class, as returned by classNameToOOP("String")
.
Return a Boolean indicating whether or not the OOP is an Integer object;
the value of SmallInteger objects is encoded directly in the OOP, not
separately in a gst_object
structure. It is not safe to use
OOP_TO_OBJ
and OOP_CLASS
if isInt
returns false.
Return a Boolean indicating whether or not the OOP is a ‘real’ object
(and not a SmallInteger). It is safe to use OOP_TO_OBJ
and
OOP_CLASS
only if IS_OOP
returns true.
Access the character given in the second parameter of the given Array
object. Note that this is necessary because of the way
gst_object
is defined, which prevents indexedOOP
from
working.
Access the character given in the second parameter of the given String
or ByteArray object. Note that this is necessary because of the way
gst_object
is defined, which prevents indexedByte
from
working.
Access the given indexed instance variable in a
variableWordSubclass
. The first parameter must be a structure
declared as described in Object representation).
Access the given indexed instance variable in a
variableByteSubclass
. The first parameter must be a structure
declared as described in Object representation).
Access the given indexed instance variable in a variableSubclass
.
The first parameter must be a structure declared as described in
Object representation).
IS_NIL and IS_CLASS have been removed because
they are problematic in shared libraries (modules), where they
caused undefined symbols to be present in the shared library. These
are now private to libgst.a. You should use the nilOOP
field of the interpreter proxy, or getObjectClass
.
Next: Object representation, Previous: Smalltalk callbacks, Up: C and Smalltalk