Next: , Previous: , Up: C and Smalltalk  


5.3 The C data type manipulation system

CType is a class used to represent C data types themselves (no storage, just the type). There are subclasses called things like CmumbleCType. The instances can answer their size and alignment. Their valueType is the underlying type of data. It’s either an integer, which is interpreted by the interpreter as the scalar type, or the underlying element type, which is another CType subclass instance.

To make life easier, there are global variables which hold onto instances of CScalarCType: they are called CmumbleType (like CIntType, not like CIntCType), and can be used wherever a C datatype is used. If you had an array of strings, the elements would be CStringType’s (a specific instance of CScalarCType).

CObject is the base class of the instances of C data. It has a subclass called CScalar, which has subclasses called Cmumble. These subclasses can answer size and alignment information.

Instances of CObject can hold a raw C pointer (for example in malloced heap)), or can delegate their storage to a ByteArray. In the latter case, the storage is automatically garbage collected when the CObject becomes dead, and the VM checks accesses to make sure they are in bounds. On the other hand, the storage may move, and for this reason extra care must be put when using this kind of CObject with C routines that call back into Smalltalk, or that store the passed pointer somewhere.

Instances of CObject can be created in many ways:

CStruct and CUnion subclasses are special. First, new allocates a new instance with malloc instead of initializing the pointer to NULL. Second, they support gcNew which creates a new instance backed by garbage-collected storage.

CObjects created by the C callout mechanism are never backed by garbage-collected storage.

CObject and its subclasses represent a pointer to a C object and as such provide the full range of operations supported by C pointers. For example, + anInteger which returns a CObject which is higher in memory by anInteger times the size of each item. There is also - which acts like + if it is given an integer as its parameter. If a CObject is given, it returns the difference between the two pointers. incr, decr, incrBy:, decrBy: adjust the string either forward or backward, by either 1 or n characters. Only the pointer to the string is changed; the actual characters in the string remain untouched.

CObjects can be divided into two families, scalars and non-scalars, just like C data types. Scalars fetch a Smalltalk object when sent the value message, and change their value when sent the value: message. Non-scalars do not support these two messages. Non-scalars include instances of CArray and subclasses of CStruct and CUnion (but not CPtr).

CPtrs and CArrays get their underlying element type through a CType subclass instance which is associated with the CArray or CPtr instance.

CPtr’s value and value: method get or change the underlying value that’s pointed to. value returns another CObject corresponding to the pointed value. That’s because, for example, a CPtr to long points to a place in memory where a pointer to long is stored. It is really a long ** and must be dereferenced twice with cPtr value value to get the long.

CString is a subclass of CPtr that answers a Smalltalk String when sent value, and automatically allocates storage to copy and null-terminate a Smalltalk String when sent value:. replaceWith: replaces the string the instance points to with a new string or ByteArray, passed as the argument. Actually, it copies the bytes from the Smalltalk String instance aString into the same buffer already pointed to by the CString, with a null terminator.

Finally, there are CStruct and CUnion, which are abstract subclasses of CObject18. The following will refer to CStruct, but the same considerations apply to CUnion as well, with the only difference that CUnions of course implement the semantics of a C union.

These classes provide direct access to C data structures including

Here is an example struct decl in C:

struct audio_prinfo {
    unsigned    channels;
    unsigned    precision;
    unsigned    encoding;
    unsigned    gain;
    unsigned    port;
    unsigned    _xxx[4];
    unsigned    samples;
    unsigned    eof;
    unsigned char       pause;
    unsigned char       error;
    unsigned char       waiting;
    unsigned char       _ccc[3];
    unsigned char       open;
    unsigned char       active;
};

struct audio_info {
    audio_prinfo_t      play;
    audio_prinfo_t      record;
    unsigned    monitor_gain;
    unsigned    _yyy[4];
};

And here is a Smalltalk equivalent decision:

CStruct subclass: AudioPrinfo [
    <declaration: #( (#sampleRate #uLong)
                     (#channels #uLong)
                     (#precision #uLong)
                     (#encoding #uLong)
                     (#gain #uLong)
                     (#port #uLong)
                     (#xxx (#array #uLong 4))
                     (#samples #uLong)
                     (#eof #uLong)
                     (#pause #uChar)
                     (#error #uChar)
                     (#waiting #uChar)
                     (#ccc (#array #uChar 3))
                     (#open #uChar)
                     (#active #uChar))>

    <category: 'C interface-Audio'>
]

CStruct subclass: AudioInfo [
    <declaration: #( (#play #{AudioPrinfo} )
                     (#record #{AudioPrinfo} )
                     (#monitorGain #uLong)
                     (#yyy (#array #uLong 4)))>

    <category: 'C interface-Audio'>
]

This creates two new subclasses of CStruct called AudioPrinfo and AudioInfo, with the given fields. The syntax is the same as for creating standard subclasses, with the additional metadata declaration:. You can make C functions return CObjects that are instances of these classes by passing AudioPrinfo type as the parameter to the returning: keyword.

AudioPrinfo has methods defined on it like:

    #sampleRate
    #channels
    #precision
    #encoding

etc. These access the various data members. The array element accessors (xxx, ccc) just return a pointer to the array itself.

For simple scalar types, just list the type name after the variable. Here’s the set of scalars names, as defined in kernel/CStruct.st:

   #long                   CLong
   #uLong                  CULong
   #ulong                  CULong
   #byte                   CByte
   #char                   CChar
   #uChar                  CUChar
   #uchar                  CUChar
   #short                  CShort
   #uShort                 CUShort
   #ushort                 CUShort
   #int                    CInt
   #uInt                   CUInt
   #uint                   CUInt
   #float                  CFloat
   #double                 CDouble
   #longDouble             CLongDouble
   #string                 CString
   #smalltalk              CSmalltalk
   #{...}                  A given subclass of CObject

The #{…} syntax is not in the Blue Book, but it is present in GNU Smalltalk and other Smalltalks; it returns an Association object corresponding to a global variable.

To have a pointer to a type, use something like:

        (#example (#ptr #long))

To have an array pointer of size size, use:

        (#example (#array #string size))

Note that this maps to char *example[size] in C.

The objects returned by using the fields are CObjects; there is no implicit value fetching currently. For example, suppose you somehow got ahold of an instance of class AudioPrinfo as described above (the instance is a CObject subclass and points to a real C structure somewhere). Let’s say you stored this object in variable audioInfo. To get the current gain value, do

    audioInfo gain value

to change the gain value in the structure, do

    audioInfo gain value: 255

The structure member message just answers a CObject instance, so you can hang onto it to directly refer to that structure member, or you can use the value or value: methods to access or change the value of the member.

Note that this is the same kind of access you get if you use the addressAt: method on CStrings or CArrays or CPtrs: they return a CObject which points to a C object of the right type and you need to use value and value: to access and modify the actual C variable.


Footnotes

(18)

Actually they have a common superclass named CCompound.


Next: , Previous: , Up: C and Smalltalk