Back: C callout
Up: C and Smalltalk
Forward: Smalltalk types
 
Top: GNU Smalltalk User's Guide
Contents: Table of Contents
Index: Class index
About: About this document

4.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 holds a pointer to a C type variable. The variable have been allocated from Smalltalk by doing type new, where type is a CType subclass instance, or it may have been returned through the C callout mechanism as a return value. Thinking about this facet of the implementation (that CObject point to C objects) tends to confuse me when I'm thinking about having CObjects which are, say, of type long*... so I try to think of CObject as just representing a C data object and not thinking about the implementation. To talk about the type long*, you'd create an instance of CPtrCType (because all CType instances represent C types, not C objects), via
 
"use the existing CLongCType instance"
CPtrCType elementType: CLongType.

To allocate one of these C objects, you'd do:
 
longPtr := (CPtrCType elementType: CLongType) new.

Now you have a C variable of type "long *" accessible from longPtr.

Scalars fetch their value when sent the value message, and change their value when sent the value: message.

CStrings can be indexed using at: with a zero based index, which returns a Smalltalk Character instance corresponding to the indexed element of the string. To change the value at a given index, use at:put:.

To produce a pointer to a character, use addressAt:. To dereference the string, like *(char *)foo, use deref: this returns an object of type CChar, not a Character instance). To replace the first character in the string, use deref: and pass in a CChar instance. These operations aren't real useful for CStrings, but they are present for completeness and for symmetry with pointers: after all, you can say *string in C and get the first character of the string, just like you can say *string = 'f'.

Also for symmetry (but this is useful in fact) + anInteger returns a CString object pointing to integer bytes from the start of the string. - acts like + if it is given an integer as its parameter. If a pointer 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.

replaceWith: aString replaces the string the instance points to with the new string. Actually, it copies the bytes from the Smalltalk String instance aString into the C string object, and null terminates. Be sure that the C string has enough room! You can also use a Smalltalk ByteArray as the data source.

Instances of CArray represent an array of some C data. The underlying element type is provided by a CType subclass instance which is associated with the CPtr instance. They have at: and at:put: operations just like Strings. at: returns a Smalltalk datatype for the given element of the array (if the element type is a scalar, otherwise it returns a CObject subclass instance whose type is that of the element type); at:put: works similarly. addressAt: returns a CObject subclass instance no matter what, which you then can send value or or value: to get or set its value. CArray's also support deref, deref:, + and - with equivalent semantics to CString.

CPtrs are similar to CArrays (as you might expect given the similarity between pointers and arrays in C) and even more similar to CStrings (as you might again expect since strings are pointers in C). In fact both CPtrs and CArrays are subclasses of a common subclass, CAggregate. Just like CArrays, the underlying element type is provided by a CType subclass instance which is associated with the CPtr instance.

CPtr's also have value and value: which get or change the underlying value that's pointed to. Like CStrings, they have #incr, #decr, #incrBy: and #decrBy:. They also have #+ and #- which do what you'd expect.

Finally, there are CStruct and CUnion, which are abstract subclasses of CObject(11). In the following I 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

  • long (unsigned too)
  • short (unsigned too)
  • char (unsigned too) & byte type
  • double (and float)
  • string (NUL terminated char *, with special accessors)
  • arrays of any type
  • pointers to any type
  • other structs containing any fixed size types

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))
        classVariableNames: ''
        poolDictionaries: ''
        category: 'C interface-Audio'
!

CStruct subclass: #AudioInfo
        declaration: #( (#play #{AudioPrinfo} )
                        (#record #{AudioPrinfo} )
                        (#monitorGain #uLong)
                        (#yyy (#array #uLong 4)))
        classVariableNames: ''
        poolDictionaries: ''
        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 instanceVariableNames replaced by declaration(12). 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 `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
   #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.




This document was generated on May, 12 2002 using texi2html