Back: Looking at objects
Up: Tutorial
Forward: The existing hierarchy
 
Top: GNU Smalltalk User's Guide
Contents: Table of Contents
Index: Class index
About: About this document

5.9 Coexisting in the Class Hierarchy

The early chapters of this tutorial discussed classes in one of two ways. The "toy" classes we developed were rooted at Object; the system-provided classes were treated as immutable entities. While one shouldn't modify the behavior of the standard classes lightly, "plugging in" your own classes in the right place among their system-provided brethren can provide you powerful new classes with very little effort.

This chapter will create two complete classes which enhance the existing Smalltalk hierarchy. The discussion will start with the issue of where to connect our new classes, and then continue onto implementation. Like most programming efforts, the result will leave many possibilities for improvements. The framework, however, should begin to give you an intuition of how to develop your own Smalltalk classes.

5.9.1 The Existing Class Hierarchy  We've been talking about it for a while, so here it is at last
5.9.2 Playing with Arrays  Again.
5.9.3 Adding a New Kind of Number  Sounds interesting, doesn't it?
5.9.4 Inheritance and Polymorphism  Sounds daunting, doesn't it?


5.9.1 The Existing Class Hierarchy

To discuss where a new class might go, it is helpful to have a map of the current classes. The following is the basic class hierarchy of GNU Smalltalk. Indentation means that the line inherits from the earlier line with one less level of indentation.(30).

 
  Object
    Behavior
      ClassDescription
        Class
        Metaclass
    BlockClosure
    Boolean
      False
      True
    Browser
    CFunctionDescriptor
    CObject
      CAggregate
        CArray
        CPtr
      CCompound
        CStruct
        CUnion
      CScalar
        CChar
        CDouble
        CFloat
        CInt
        CLong
        CShort
        CSmalltalk
        CString
        CUChar
          CByte
            CBoolean
        CUInt
        CULong
        CUShort
    Collection
      Bag
      MappedCollection
      SequenceableCollection
        ArrayedCollection
          Array
          ByteArray
          WordArray
          LargeArrayedCollection
            LargeArray
            LargeByteArray
            LargeWordArray
          CompiledCode
            CompiledMethod
            CompiledBlock
          Interval
          CharacterArray
            String
              Symbol
        LinkedList
          Semaphore
        OrderedCollection
          RunArray
          SortedCollection
      HashedCollection
        Dictionary
          IdentityDictionary
            MethodDictionary
          RootNamespace
            Namespace
            SystemDictionary
        Set
          IdentitySet
    ContextPart
      BlockContext
      MethodContext
    CType
      CArrayCType
      CPtrCType
      CScalarCType
    Delay
    DLD
    DumperProxy
      AlternativeObjectProxy
        NullProxy
          VersionableObjectProxy
        PluggableProxy
    File
      Directory
    FileSegment
    Link
      Process
      SymLink
    Magnitude
      Association
      Character
      Date
      LargeArraySubpart
      Number
        Float
        Fraction
        Integer
          LargeInteger
            LargeNegativeInteger
            LargePositiveInteger
              LargeZeroInteger
          SmallInteger
      Time
    Memory
    Message
      DirectedMessage
    MethodInfo
    NullProxy
    PackageLoader
    Point
    ProcessorScheduler
    Rectangle
    SharedQueue
    Signal
      Exception
        Error
          Halt
            ArithmeticError
              ZeroDivide
            MessageNotUnderstood
          UserBreak
        Notification
          Warning
    Stream
      ObjectDumper
      PositionableStream
        ReadStream
        WriteStream
          ReadWriteStream
            ByteStream
              FileStream
      Random
      TextCollector
      TokenStream
    TrappableEvent
      CoreException
      ExceptionCollection
    UndefinedObject
    ValueAdaptor
      NullValueHolder
      PluggableAdaptor
        DelayedAdaptor
      ValueHolder

While initially a daunting list, you should take the time to hunt down the classes we've examined in this tutorial so far. Notice, for instance, how an Array is a subclass below the SequenceableCollection class. This makes sense; you can walk an Array from one end to the other. By contrast, notice how this is not true for Sets: it doesn't make sense to walk a Set from one end to the other.

A little puzzling is the relationship of a Bag to a Set, since a Bag is actually a Set supporting multiple occurrences of its elements. The answer lies in the purpose of both a Set and a Bag. Both hold an unordered collection of objects; but a Bag needs to be optimized for the case when an object has possibly thousands of occurrences, while a Set is optimized for checking object uniqueness. That's why Set being a subclass or Bag, or the other way round, would be a source of problems in the actual implementation of the class. Currently a Bag holds a Dictionary associating each object to each count; it would be feasible however to have Bag as a subclass of HashedCollection and a sibling of Set.

Look at the treatment of numbers--starting with the class Magnitude. While numbers can indeed be ordered by less than, greater than, and so forth, so can a number of other objects. Each subclass of Magnitude is such an object. So we can compare characters with other characters, dates with other dates, and times with other times, as well as numbers with numbers.

Finally, you will have probably noted some pretty strange classes, representing language entities that you might have never thought of as objects themselves: Namespace, Class and even CompiledMethod. They are the base of Smalltalk's "reflection" mechanism which will be discussed later, in The truth on metaclasses.


5.9.2 Playing with Arrays

Imagine that you need an array, but alas you need that if an index is out of bounds, it returns nil. You could modify the Smalltalk implementation, but that might break some code in the image, so it is not practical. Why not add a subclass?

 
   Array variableSubclass: #NiledArray
       instanceVariableNames: ''
       classVariableNames: ''
       poolDictionaries: ''
       category: nil !

   !NiledArray methodsFor: 'bounds checking'!
   boundsCheck: index
       ^(index < 1) | (index > (self basicSize))
   ! !

   !NiledArray methodsFor: 'basic'!
   at: index
       ^(self boundsCheck: index)
           ifTrue: [ nil ]
           ifFalse: [ super at: index ]

   !
   at: index put: val
       ^(self boundsCheck: index)
           ifTrue: [ val ]
           ifFalse: [ super at: index put: val ]
   ! !

Much of the machinery of adding a class should be familiar. Instead of our usual subclass: message, we use a variableSubclass: message. This reflects the underlying structure of an Array object; we'll delay discussing this until the chapter on the nuts and bolts of arrays. In any case, we inherit all of the actual knowledge of how to create arrays, reference them, and so forth. All that we do is intercept at: and at:put: messages, call our common function to validate the array index, and do something special if the index is not valid. The way that we coded the bounds check bears a little examination.

Making a first cut at coding the bounds check, you might have coded the bounds check in NiledArray's methods twice (once for at:, and again for at:put:. As always, it's preferable to code things once, and then re-use them. So we instead add a method for bounds checking boundsCheck:, and use it for both cases. If we ever wanted to enhance the bounds checking (perhaps emit an error if the index is < 1 and answer nil only for indices greater than the array size?), we only have to change it in one place.

The actual math for calculating whether the bounds have been violated is a little interesting. The first part of the expression returned by the method:
 
   (index < 1) | (index > (self basicSize))

is true if the index is less than 1, otherwise it's false. This part of the expression thus becomes the boolean object true or false. The boolean object then receives the message |, and the argument (index > (self basicSize)). | means "or"---we want to OR together the two possible out-of-range checks. What is the second part of the expression? (31)

index is our argument, an integer; it receives the message >, and thus will compare itself to the value self basicSize returns. While we haven't covered the underlying structures Smalltalk uses to build arrays, we can briefly say that the #basicSize message returns the number of elements the Array object can contain. So the index is checked to see if it's less than 1 (the lowest legal Array index) or greater than the highest allocated slot in the Array. If it is either (the | operator!), the expression is true, otherwise false.

From there it's downhill; our boolean object, returned by boundsCheck:, receives the ifTrue:ifFalse: message, and a code block which will do the appropriate thing. Why do we have at:put: return val? Well, because that's what it's supposed to do: look at every implementor of at:put or at: and you'll find that it returns its second parameter. In general, the result is discarded; but one could write a program which uses it, so we'll write it this way anyway.


5.9.3 Adding a New Kind of Number

If we were programming an application which did a large amount of complex math, we could probably manage it with a number of two-element arrays. But we'd forever be writing in-line code for the math and comparisons; it would be much easier to just implement an object class to support the complex numeric type. Where in the class hierarchy would it be placed?

You've probably already guessed--but let's step down the hierarchy anyway. Everything inherits from Object, so that's a safe starting point. Complex numbers can not be compared with < and >, and yet we strongly suspect that, since they are numbers, we should place them under the Number class. But Number inherits from Magnitude--how do we resolve this conflict? A subclass can place itself under a superclass which allows some operations the subclass doesn't wish to allow. All that you must do is make sure you intercept these messages and return an error. So we will place our new Complex class under Number, and make sure to disallow comparisons.

One can reasonably ask whether the real and imaginary parts of our complex number will be integer or floating point. In the grand Smalltalk tradition, we'll just leave them as objects, and hope that they respond to numeric messages reasonably. If they don't, the user will doubtless receive errors and be able to track back their mistake with little fuss.

We'll define the four basic math operators, as well as the (illegal) relationals. We'll add printOn: so that the printing methods work, and that should give us our Complex class. The class as presented suffers some limitations, which we'll cover later in the chapter.

 
   Number subclass: #Complex
       instanceVariableNames: 'realpart imagpart'
       classVariableNames: ''
       poolDictionaries: ''
       category: nil !
   !Complex class methodsFor: 'creating'!
   new
       ^self error: 'use real:imaginary:'
   !
   new: ignore
       ^self new
   !
   real: r imaginary: i
       ^(super new) setReal: r setImag: i
   ! !

   !Complex methodsFor: 'creating--private'!
   setReal: r setImag: i
       realpart := r.
       imagpart := i.
       ^self
   ! !

   !Complex methodsFor: 'basic'!
   real
       ^realpart
   !
   imaginary
       ^imagpart
   ! !

   !Complex methodsFor: 'math'!
   + val
       ^Complex real: (realpart + val real)
           imaginary: (imagpart + val imaginary)
   !
   - val
       ^Complex real: (realpart - val real)
           imaginary: (imagpart - val imaginary)
   !
   * val
       ^Complex real: (realpart * val real) - (imagpart * val imaginary)
           imaginary: (imagpart * val real) + (realpart * val imaginary)
   !
   / val
       | d r i |
       d := (val real * val real) + (val imaginary * val imaginary).
       r := ((realpart * val real) + (imagpart * val imaginary)).
       i := ((imagpart * val real) - (realpart * val imaginary)).
       ^Complex real: r / d imaginary: i / d
   ! !

   !Complex methodsFor: 'comparison'!

   = val
       ^(realpart = val real) & (imagpart = val imaginary)
   !
   > val
       ^self shouldNotImplement
   !
   >= val
       ^self shouldNotImplement
   !
   < val
       ^self shouldNotImplement
   !
   <= val
       ^self shouldNotImplement
   ! !

   !Complex methodsFor: 'printing'!
   printOn: aStream
       aStream nextPut: $(.
       realpart printOn: aStream.
       aStream nextPut: $,.
       imagpart printOn: aStream.
       aStream nextPut: $)
   ! !

There should be surprisingly little which is actually new in this example. The printing method uses both printOn: as well as nextPut: to do its printing. While we haven't covered it, it's pretty clear that $( generates the ASCII character ( as an object, and nextPut: puts its argument as the next thing on the stream.

The math operations all generate a new object, calculating the real and imaginary parts, and invoking the Complex class to create the new object. Our creation code is a little more compact than earlier examples; instead of using a local variable to name the newly-created object, we just use the return value and send a message directly to the new object. Our initialization code explicitly returns self; what would happen if we left this off?


5.9.4 Inheritance and Polymorphism

This is a good time to look at what we've done with the two previous examples at a higher level. With the NiledArray class, we inherited almost all of the functionality ality of arrays, with only a little bit of code added to address our specific needs. While you may have not thought to try it, all the existing methods for an Array continue to work without further effort-you might find it interesting to ponder why the following still works:
 
   Smalltalk at: #a put: (NiledArray new: 10) !
   a at: 5 put: 1234 !
   a do: [:i| i printNl ] !

The strength of inheritance is that you focus on the incremental changes you make; the things you don't change will generally continue to work.

In the Complex class, the value of polymorphism was exercised. A Complex number responds to exactly the same set of messages as any other number. If you had handed this code to someone, they would know how to do math with Complex numbers without further instruction. Compare this with C, where a complex number package would require the user to first find out if the complex-add function was complex_plus(), or perhaps complex_add(), or add_complex(), or...

However, one glaring deficiency is present in the Complex class: what happens if you mix normal numbers with Complex numbers? Currently, the Complex class assumes that it will only interact with other Complex numbers. But this is unrealistic: mathematically, a "normal" number is simply one with an imaginary part of 0. Smalltalk was designed to allow numbers to coerce themselves into a form which will work with other numbers.

The system is clever and requires very little additional code. Unfortunately, it would have tripled the amount of explanation required. If you're interested in how coercion works in GNU Smalltalk, you should find the Smalltalk library source, and trace back the execution of the retry:coercing: messages. You want to consider the value which the generality message returns for each type of number. Finally, you need to examine the coerce: handling in each numeric class.




This document was generated on May, 12 2002 using texi2html