Next: , Previous: , Up: More subclassing  


6.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 [
       | realpart imagpart |

       "This is a quick way to define class-side methods."
       Complex class >> new [
           <category: 'instance creation'>
           ^self error: 'use real:imaginary:'
       ]
       Complex class >> new: ignore [
           <category: 'instance creation'>
           ^self new
       ]
       Complex class >> real: r imaginary: i [
           <category: 'instance creation'>
           ^(super new) setReal: r setImag: i
       ]

       setReal: r setImag: i [
           <category: 'basic'>
           realpart := r.
           imagpart := i.
           ^self
       ]

       real [
           <category: 'basic'>
           ^realpart
       ]
       imaginary [
           <category: 'basic'>
           ^imagpart
       ]

       + val [
           <category: 'math'>
           ^Complex real: (realpart + val real)
               imaginary: (imagpart + val imaginary)
       ]
       - val [
           <category: 'math'>
           ^Complex real: (realpart - val real)
               imaginary: (imagpart - val imaginary)
       ]
       * val [
           <category: 'math'>
           ^Complex real: (realpart * val real) - (imagpart * val imaginary)
               imaginary: (imagpart * val real) + (realpart * val imaginary)
       ]
       / val [
           <category: 'math'>
           | 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
       ]

       = val [
           <category: 'comparison'>
           ^(realpart = val real) & (imagpart = val imaginary)
       ]

       "All other comparison methods are based on <"
       < val [
           <category: 'comparison'>
           ^self shouldNotImplement
       ]

       printOn: aStream [
           <category: 'printing'>
           realpart printOn: aStream.
           aStream nextPut: $+.
           imagpart printOn: aStream.
           aStream nextPut: $i
       ]
   ]

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 object37, 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?


Footnotes

(37)

A GNU Smalltalk extension allows you to type characters by ASCII code too, as in $<43>.


Next: , Previous: , Up: More subclassing