1
2@table @b
3
4@item What this manual presents
5This document provides a tutorial introduction to the Smalltalk language
6in general, and the @gst{} implementation in particular.
7It does not provide exhaustive coverage of every feature of the language
8and its libraries; instead, it attempts to introduce a critical mass of
9ideas and techniques to get the Smalltalk novice moving in the
10right direction.
11
12@item Who this manual is written for
13This manual assumes that the reader is acquainted with
14the basics of computer science, and has reasonable proficiency
15with a procedural language such as C.  It also assumes that the reader
16is already familiar with the usual janitorial tasks associated with
17programming: editing, moving files, and so forth.
18@end table
19
20@menu
21* Getting started::              Starting to explore @gst{}
22* Some classes::                 Using some of the Smalltalk classes
23* The hierarchy::                The Smalltalk class hierarchy
24* Creating classes::             Creating a new class of objects
25* Creating subclasses::          Adding subclasses to another class
26* Code blocks (I)::              Control structures in Smalltalk
27* Code blocks (II)::             Guess what?  More control structures
28* Debugging::                    Things go bad in Smalltalk too!
29* More subclassing::             Coexisting in the class hierarchy
30* Streams::                      A powerful abstraction useful in scripts
31* Exception handling::           More sophisticated error handling
32* Behind the scenes::            Some nice stuff from the Smalltalk innards
33* And now::                      Some final words
34* The syntax::                   For the most die-hard computer scientists
35@end menu
36
37@node Getting started
38@section Getting started
39
40@menu
41* Starting Smalltalk::           Starting up Smalltalk
42* Saying hello::                 Saying hello
43* What happened::                But how does it say hello?
44* Doing math::                   Smalltalk too can do it!
45* Math in Smalltalk::            But in a peculiar way of course...
46@end menu
47
48@node Starting Smalltalk
49@subsection Starting up Smalltalk
50
51Assuming that @gst{} has been installed on your
52system, starting it is as simple as:
53@example
54   @b{$} gst
55@end example
56the system loads in Smalltalk, and displays a startup banner
57like:
58@display
59     GNU Smalltalk ready
60
61     st>
62@end display
63
64You are now ready to try your hand at Smalltalk!  By the
65way, when you're ready to quit, you exit Smalltalk by typing
66@kbd{control-D} on an empty line.
67
68@node Saying hello
69@subsection Saying hello
70An initial exercise is to make Smalltalk say ``hello'' to
71you.  Type in the following line (@code{printNl} is a upper case
72N and a lower case L):
73@example
74   'Hello, world' printNl
75@end example
76The system then prints back 'Hello, world' to you.  It prints it
77twice, the first time because you asked to print and the second
78time because the snipped evaluated to the 'Hello, world' string.@footnote{
79    You can also have the system print out a lot of statistics which
80    provide information on the performance of the underlying Smalltalk
81    engine.  You can enable them by starting Smalltalk as:
82@example
83   @b{$} gst -V
84@end example
85}
86
87@node What happened
88@subsection What actually happened
89
90The front-line Smalltalk interpreter gathers all text
91until a '!' character and executes it.  So the actual
92Smalltalk code executed was:
93@example
94   'Hello, world' printNl
95@end example
96
97This code does two things.  First, it creates an object of
98type @code{String} which contains the characters ``Hello, world''.
99Second, it sends the message named @code{printNl} to the object.
100When the object is done processing the message, the code is
101done and we get our prompt back.
102You'll notice that we didn't say anything about printing
103ing the string, even though that's in fact what happened.
104This was very much on purpose: the code we typed in doesn't
105know anything about printing strings.  It knew how to get a
106string object, and it knew how to send a message to that
107object.  That's the end of the story for the code we wrote.
108
109But for fun, let's take a look at what happened when the
110string object received the @code{printNl} message.  The string object
111then went to a table @footnote{Which table?  This is determined by the type
112of the object.  An object has a type, known as the
113class to which it belongs.  Each class has a table
114of methods.  For the object we created, it is
115known as a member of the @code{String} class.  So we go
116to the table associated with the String class.}
117which lists the messages which strings can receive, and what code to
118execute.  It found that there is indeed an entry for
119@code{printNl} in that table and ran this code.  This code then walked through
120its characters, printing each of them out to the terminal.  @footnote{
121Actually, the message @code{printNl} was inherited
122from Object.  It sent a @code{print} message, also
123inherited by Object, which then sent @code{printOn:} to
124the object, specifying that it print to the @code{Transcript}
125object.  The String class then prints its characters to the
126standard output.}
127
128The central point is that an object is entirely self-contained;
129only the object knew how to print itself out.  When we want an
130object to print out, we ask the object itself to do the printing.
131
132@node Doing math
133@subsection Doing math
134
135A similar piece of code prints numbers:
136@example
137  1234 printNl
138@end example
139
140Notice how we used the same message, but have sent it to a
141new type of object---an integer (from class @code{Integer}).  The
142way in which an integer is printed is much different from
143the way a string is printed on the inside, but because we
144are just sending a message, we do not have to be aware of
145this.  We tell it to @code{printNl}, and it prints itself out.
146
147As a user of an object, we can thus usually send a particular
148message and expect basically the same kind of behavior,
149regardless of object's internal structure (for
150instance, we have seen that sending @code{printNl} to an object
151makes the object print itself).  In later chapters we will
152see a wide range of types of objects.  Yet all of them can
153be printed out the same way---with @code{printNl}.
154
155White space is ignored, except as it separates words.
156This example could also have looked like:
157@example
158              1234 printNl
159@end example
160
161However, @gst{} tries to execute each line by itself if
162possible.  If you wanted to write the code on two lines, you
163might have written something like:
164@example
165(1234
166    printNl)
167@end example
168
169From now on, we'll omit @code{printNl} since @gst{}
170does the service of printing the answer for us.
171
172An integer can be sent a number of messages in addition
173to just printing itself.  An important set of messages for
174integers are the ones which do math:
175
176@example
177   9 + 7
178@end example
179
180Answers (correctly!) the value 16.  The way that it does
181this, however, is a significant departure from a procedural
182language.
183
184@node Math in Smalltalk
185@subsection Math in Smalltalk
186
187In this case, what happened was that the object @code{9} (an
188Integer), received a @code{+} message with an argument of @code{7}
189(also an Integer).  The @code{+} message for integers then caused
190Smalltalk to create a new object @code{16} and return it as the
191resultant object.  This @code{16} object was then given the
192@code{printNl} message, and printed @code{16} on the terminal.
193
194Thus, math is not a special case in Smalltalk; it is
195done, exactly like everything else, by creating objects, and
196sending them messages.  This may seem odd to the Smalltalk
197novice, but this regularity turns out to be quite a boon:
198once you've mastered just a few paradigms, all of the language
199``falls into place''. Before you go on to the next
200chapter, make sure you try math involving @code{*} (multiplication),
201@code{-} (subtraction), and @code{/} (division) also.  These
202examples should get you started:
203
204@example
205   8 * (4 / 2)
206   8 - (4 + 1)
207   5 + 4
208   2/3 + 7
209   2 + 3 * 4
210   2 + (3 * 4)
211@end example
212
213@node Some classes
214@section Using some of the Smalltalk classes
215
216This chapter has examples which need a place to hold
217the objects they create.  Such place is created automatically
218as necessary; when you want to discard all the objects you
219stored, write an exclamation mark at the end of the statement.
220
221Now let's create some new objects.
222
223@menu
224* Arrays::                   An array in Smalltalk
225* Sets::                     A set in Smalltalk
226* Dictionaries::             Getting more sophisticated, eh?
227* Closing thoughts::         There always ought to be some closing thoughts
228@end menu
229
230@node Arrays
231@subsection An array in Smalltalk
232
233An array in Smalltalk is similar to an array in any
234other language, although the syntax may seem peculiar at
235first.  To create an array with room for 20 elements, do@footnote{
236    @gst{} supports completion in the same way as Bash or @sc{gdb}.
237    To enter the following line, you can for example type
238    @samp{x := Arr@kbd{<TAB>} new: 20}.  This can come in handy
239    when you have to type long names such as @code{IdentityDictionary},
240    which becomes @samp{Ide@kbd{<TAB>}D@kbd{<TAB>}}.  Everything
241    starting with a capital letter or ending with a colon can
242    be completed.}:
243@example
244   x := Array new: 20
245@end example
246
247The @code{Array new: 20} creates the array; the @code{x :=} part
248connects the name @code{x} with the object.  Until you assign
249something else to @code{x}, you can refer to this array by the name
250@code{x}.  Changing elements of the array is not done using the
251@code{:=} operator; this operator is used only to bind names to
252objects.  In fact, you never modify data structures;
253instead, you send a message to the object, and it will modify itself.
254
255For instance:
256@example
257   x at: 1
258@end example
259@noindent
260which prints:
261@example
262   nil
263@end example
264
265The slots of an array are initially set to ``nothing'' (which
266Smalltalk calls @code{nil}).  Let's set the first slot to the
267number 99:
268@example
269   x at: 1 put: 99
270@end example
271@noindent
272and now make sure the 99 is actually there:
273@example
274   x at: 1
275@end example
276@noindent
277which then prints out:
278@example
279   99
280@end example
281
282These examples show how to manipulate an array.  They also
283show the standard way in which messages are passed arguments
284ments.  In most cases, if a message takes an argument, its
285name will end with `:'.@footnote{Alert readers will remember that the math
286examples of the previous chapter deviated from this.}
287
288So when we said @code{x at: 1} we were sending a message to whatever
289object was currently bound to @code{x} with an argument of 1.  For an
290array, this results in the first slot of the array being returned.
291
292The second operation, @code{x at: 1 put: 99} is a message
293with two arguments.  It tells the array to place the second
294argument (99) in the slot specified by the first (1).  Thus,
295when we re-examine the first slot, it does indeed now
296contain 99.
297
298There is a shorthand for describing the messages you
299send to objects.  You just run the message names together.
300So we would say that our array accepts both the @code{at:} and
301@code{at:put:} messages.
302
303There is quite a bit of sanity checking built into an
304array.  The request
305@example
306   6 at: 1
307@end example
308@noindent
309fails with an error; 6 is an integer, and can't be indexed.  Further,
310@example
311   x at: 21
312@end example
313@noindent
314fails with an error, because the array we created only has
315room for 20 objects.
316
317Finally, note that the object stored
318in an array is just like any other object, so we can do
319things like:
320@example
321   (x at: 1) + 1
322@end example
323@noindent
324which (assuming you've been typing in the examples) will
325print 100.
326
327@node Sets
328@subsection A set in Smalltalk
329
330We're done with the array we've been using, so we'll
331assign something new to our @code{x} variable.  Note that we
332don't need to do anything special about the old array: the
333fact that nobody is using it any more will be automatically
334detected, and the memory reclaimed.  This is known as @i{garbage collection}
335and it is generally done when Smalltalk finds that it is
336running low on memory.  So, to get our new object, simply do:
337@example
338   x := Set new
339@end example
340@noindent
341which creates an empty set.  To view its contents, do:
342@example
343   x
344@end example
345
346The kind of object is printed out (i.e., @code{Set}), and then the
347members are listed within parenthesis.  Since it's empty, we
348see:
349@example
350   Set ()
351@end example
352
353Now let's toss some stuff into it.  We'll add the numbers 5
354and 7, plus the string 'foo'.  This is also the first example
355where we're using more than one statement, and thus a good place to present
356the statement separator---the @code{.} period:
357
358@example
359   x add: 5. x add: 7. x add: 'foo'
360@end example
361
362Like Pascal, and unlike C, statements are separated rather than
363terminated.  Thus you need only use a @code{.} when you have finished
364one statement and are starting another.  This is why our last statement,
365@code{^r}, does not have a @code{.} following.  Once again like Pascal,
366however, Smalltalk won't complain if your enter a spurious
367statement separator after @i{the last} statement.
368
369However, we can save a little typing by using a Smalltalk shorthand:
370
371@example
372   x add: 5; add: 7; add: 'foo'
373@end example
374
375This line does exactly what the previous one did.
376The trick is that the semicolon operator causes
377the message to be sent to the same object as the last message
378sent.  So saying @code{; add: 7} is the same as saying
379@code{x add: 7}, because @code{x} was the last thing a message was sent
380to.
381
382This may not seem like such a big savings, but compare
383the ease when your variable is named @code{aVeryLongVariableName}
384instead of just @code{x}!  We'll revisit some other occasions
385where @code{;} saves you trouble, but for now let's continue with
386our set.  Type either version of the example, and make sure
387that we've added 5, 7, and ``foo'':
388@example
389   x
390@end example
391@noindent
392
393we'll see that it now contains our data:
394@example
395   Set ('foo' 5 7)
396@end example
397
398What if we add something twice?  No problem---it just stays in
399the set.  So a set is like a big checklist---either it's in
400there, or it isn't.  To wit:
401@example
402   x add:5; add: 5; add: 5; add: 5; yourself
403@end example
404
405We've added @i{5} several times, but when we printed our set
406back out, we just see:
407@example
408   Set ('foo' 5 7)
409@end example
410
411@code{yourself} is commonly sent at the end of the cascade,
412if what you are interested in is the object itself---in this
413case, we were not interested in the return value of @code{add: 5},
414which happens to be @code{5} simply.  There's nothing magic in
415@code{yourself}; it is a unary message like @code{printNl},
416which does nothing but returning the object itself.  So you
417can do this too:
418
419@example
420   x yourself
421@end example
422
423What you put into a set with @code{add:}, you can take out
424with @code{remove:}.  Try:
425
426@example
427   x remove: 5
428   x printNl
429@end example
430
431The set now prints as:
432@example
433   Set ('foo' 7)
434@end example
435
436The ``5'' is indeed gone from the set.
437
438We'll finish up with one more of the many things you
439can do with a set---checking for membership.  Try:
440@example
441   x includes: 7
442   x includes: 5
443@end example
444
445From which we see that x does indeed contain 7, but not 5.
446Notice that the answer is printed as @code{true} or @code{false}.
447Once again, the thing returned is an object---in this case, an
448object known as a boolean.  We'll look at the use of
449booleans later, but for now we'll just say that booleans are
450nothing more than objects which can only either be true or
451false---nothing else.  So they're very useful for answers to
452yes or no questions, like the ones we just posed.  Let's
453take a look at just one more kind of data structure:
454
455@node Dictionaries
456@subsection Dictionaries
457
458A dictionary is a special kind of collection.  With a
459regular array, you must index it with integers.  With
460dictionaries, you can index it with any object at all.
461Dictionaries thus provide a very powerful way of correlating
462one piece of information to another.  Their only downside is
463that they are somewhat less efficient than simple arrays.
464Try the following:
465@example
466   y := Dictionary new
467   y at: 'One' put: 1
468   y at: 'Two' put: 2
469   y at: 1 put: 'One'
470   y at: 2 put: 'Two'
471@end example
472
473This fills our dictionary in with some data.  The data is
474actually stored in pairs of key and value (the key is what
475you give to @code{at:}---it specifies a slot; the value is what is
476actually stored at that slot).  Notice how we were able to
477specify not only integers but also strings as both the key
478and the value.  In fact, we can use any kind of object we
479want as either---the dictionary doesn't care.
480
481Now we can map each key to a value:
482@example
483   y at: 1
484   y at: 'Two'
485@end example
486
487which prints respectively:
488@example
489   'One'
490   2
491@end example
492
493We can also ask a dictionary to print itself:
494@example
495   y
496@end example
497@noindent
498
499which prints:
500@example
501   Dictionary (1->'One' 2->'Two' 'One'->1 'Two'->2 )
502@end example
503@noindent
504
505where the first member of each pair is the key, and the second
506the value.  It is now time to take a final look at the objects
507we have created, and send them to oblivion:
508
509@example
510   y
511   x!
512@end example
513
514The exclamation mark deleted @gst{}'s knowledge of both
515variables.  Asking for them again will return just @code{nil}.
516
517@node Closing thoughts
518@subsection Closing thoughts
519
520You've seen how Smalltalk provides you with some very
521powerful data structures.  You've also seen how Smalltalk
522itself uses these same facilities to implement the language.
523But this is only the tip of the iceberg---Smalltalk is much
524more than a collection of ``neat'' facilities to use.
525The objects and methods which are automatically available
526are only the beginning of the foundation on which you
527build your programs---Smalltalk allows you to add your own
528objects and methods into the system, and then use them along
529with everything else.  The art of programming in Smalltalk
530is the art of looking at your problems in terms of objects,
531using the existing object types to good effect, and enhancing
532Smalltalk with new types of objects.  Now that you've
533been exposed to the basics of Smalltalk manipulation, we can
534begin to look at this object-oriented technique of programming.
535
536@node The hierarchy
537@section The Smalltalk class hierarchy
538
539When programming in Smalltalk, you sometimes need to
540create new kinds of objects, and define what various
541messages will do to these objects.  In the next chapter we will
542create some new classes, but first we need to understand how
543Smalltalk organizes the types and objects it contains.
544Because this is a pure ``concept'' chapter, without any actual
545Smalltalk code to run, we will keep it short and to the
546point.
547
548@menu
549* Class Object::                The grandfather of every class
550* Animals::                     A classic in learning OOP!
551* But why::                     The bottom line of the class hierarchy
552@end menu
553
554@node Class Object
555@subsection Class @code{Object}
556
557Smalltalk organizes all of its classes as a tree hierarchy.
558At the very top of this hierarchy is class @i{Object}.
559Following somewhere below it are more specific classes, such
560as the ones we've worked with---strings, integers, arrays, and
561so forth.  They are grouped together based on their similarities;
562for instance, types of objects which may be compared
563as greater or less than each other fall under a class known
564as @i{Magnitude}.
565
566One of the first tasks when creating a new object is to
567figure out where within this hierarchy your object falls.
568Coming up with an answer to this problem is at least as much
569art as science, and there are no hard-and-fast rules to nail
570it down.  We'll take a look at three kinds of objects to
571give you a feel for how this organization matters.
572
573@node Animals
574@subsection Animals
575
576Imagine that we have three kinds of objects, representing
577@i{Animals}, @i{Parrots}, and @i{Pigs}.  Our messages will be
578@i{eat}, @i{sing}, and @i{snort}.  Our first pass at
579inserting these objects into the Smalltalk hierarchy would
580organize them like:
581@example
582   @r{Object}
583       @r{Animals}
584       @r{Parrots}
585       @r{Pigs}
586@end example
587
588This means that Animals, Parrots, and Pigs are all direct
589descendants of @i{Object}, and are not descendants of each
590other.
591
592Now we must define how each animal responds to each
593kind of message.
594
595@example
596       @r{Animals}
597           @r{eat --> Say ``I have now eaten''}
598           @r{sing --> Error}
599           @r{snort --> Error}
600       @r{Parrots}
601           @r{eat --> Say ``I have now eaten''}
602           @r{sing --> Say ``Tweet''}
603           @r{snort --> Error}
604       @r{Pigs}
605           @r{eat --> Say ``I have now eaten"''}
606           @r{sing --> Error}
607           @r{snort --> Say ``Oink''}
608@end example
609
610Notice how we kept having to indicate an action for @i{eat}.
611An experienced object designer would immediately recognize
612this as a clue that we haven't set up our hierarchy correctly.
613Let's try a different organization:
614@example
615   @r{Object}
616       @r{Animals}
617           @r{Parrots}
618                  @r{Pigs}
619@end example
620
621That is, Parrots inherit from Animals, and Pigs from Parrots.
622Now Parrots inherit all of the actions from Animals,
623and Pigs from both Parrots and Animals.  Because of this
624inheritance, we may now define a new set of actions which
625spares us the redundancy of the previous set:
626@example
627       @r{Animals}
628           @r{eat --> Say ``I have now eaten''}
629           @r{sing --> Error}
630           @r{snort --> Error}
631       @r{Parrots}
632           @r{sing --> Say ``Tweet''}
633       @r{Pigs}
634           @r{snort --> Say ``Oink''}
635@end example
636
637Because Parrots and Pigs both inherit from Animals, we have
638only had to define the @i{eat} action once.  However, we have
639made one mistake in our class setup---what happens when we
640tell a Pig to @i{sing}?  It says ``Tweet'', because we have put
641Pigs as an inheritor of Parrots.  Let's try one final
642organization:
643@example
644   @r{Object}
645       @r{Animals}
646           @r{Parrots}
647           @r{Pigs}
648@end example
649
650Now Parrots and Pigs inherit from Animals, but not from each
651other.  Let's also define one final pithy set of actions:
652@example
653       @r{Animals}
654           @r{eat --> Say ``I have eaten''}
655       @r{Parrots}
656           @r{sing --> Say ``Tweet''}
657       @r{Pigs}
658           @r{snort --> Say ``Oink''}
659@end example
660
661The change is just to leave out messages which are inappropriate.
662If Smalltalk detects that a message is not known by
663an object or any of its ancestors, it will automatically
664give an error---so you don't have to do this sort of thing
665yourself.  Notice that now sending @i{sing} to a Pig does
666indeed not say ``Tweet''---it will cause a Smalltalk error
667instead.
668
669@node But why
670@subsection The bottom line of the class hierarchy
671
672The goal of the class hierarchy is to allow you to
673organize objects into a relationship which allows a particular
674object to inherit the code of its ancestors.  Once you
675have identified an effective organization of types, you
676should find that a particular technique need only be implemented
677once, then inherited by the children below.  This
678keeps your code smaller, and allows you to fix a bug in a
679particular algorithm in only once place---then have all users
680of it just inherit the fix.
681
682You will find your decisions for adding objects change
683as you gain experience.  As you become more familiar with
684the existing set of objects and messages, your selections
685will increasingly ``fit in'' with the existing ones.  But even
686a Smalltalk @i{pro} stops and thinks carefully at this stage,
687so don't be daunted if your first choices seem difficult and
688error-prone.
689
690@node Creating classes
691@section Creating a new class of objects
692
693With the basic techniques presented in the preceding
694chapters, we're ready do our first real Smalltalk program.
695In this chapter we will construct three new types of objects
696(known as @i{classes}), using the Smalltalk technique of
697inheritance to tie the classes together, create new objects
698belonging to these classes (known as creating instances of
699the class), and send messages to these objects.
700
701We'll exercise all this by implementing a toy home-finance
702accounting system.  We will keep track of our overall
703cash, and will have special handling for our checking
704and savings accounts.  From this point on, we will be defining
705classes which will be used in future chapters.  Since
706you will probably not be running this whole tutorial in one
707Smalltalk session, it would be nice to save off the state of
708Smalltalk and resume it without having to retype all the
709previous examples.  To save the current state of @gst{},
710type:
711
712@example
713   ObjectMemory snapshot: 'myimage.im'
714@end example
715@noindent
716
717and from your shell, to later restart Smalltalk from this
718``snapshot'':
719@example
720   @b{$} gst -I myimage.im
721@end example
722
723Such a snapshot currently takes a little more than a megabyte,
724and contains all variables, classes, and definitions you
725have added.
726
727@menu
728* A new class::                  Creating a new class
729* Documenting the class::        So anybody will know what it's about
730* Defining methods::             So it will be useful
731* Instance methods::             One of two kind of methods (the others,
732                                 class methods, are above)
733* A look at our object::         which will sorely show that something
734                                 is still missing.
735* Moving money around::          Let's make it more fun!
736* Next coming::                  Yeah, what's next?!?
737@end menu
738
739@node A new class
740@subsection Creating a new class
741
742Guess how you create a new class?  This should be getting
743monotonous by now---by sending a message to an object.
744The way we create our first ``custom'' class is by sending the
745following message:
746
747@example
748   Object subclass: #Account.
749   Account instanceVariableNames: 'balance'.
750@end example
751
752Quite a mouthful, isn't it?  @gst{} provides a
753simpler way to write this, but for now let's stick with this.
754Conceptually, it isn't really that bad.  The Smalltalk variable
755@i{Object} is bound to the grand-daddy of all classes on the
756system.  What we're doing here is telling the @i{Object} class
757that we want to add to it a subclass known as @i{Account}.
758Then, @code{instanceVariableNames: 'balance'} tells the new
759class that each of its objects (@dfn{instances}) will have a
760hidden variable named @code{balance}.
761
762@node Documenting the class
763@subsection Documenting the class
764
765The next step is to associate a description with the
766class.  You do this by sending a message to the new class:
767@example
768   Account comment:
769   'I represent a place to deposit and withdraw money'
770@end example
771
772A description is associated with every Smalltalk class, and
773it's considered good form to add a description to each new
774class you define.  To get the description for a given class:
775@example
776   Account comment
777@end example
778
779And your string is printed back to you.  Try this with class
780Integer, too:
781@example
782   Integer comment
783@end example
784
785However, there is another way to define classes.  This still
786translates to sending objects, but looks more like a traditional
787programming language or scripting language:
788
789@example
790Object subclass: Account [
791    | balance |
792    <comment:
793        'I represent a place to deposit and withdraw money'>
794]
795@end example
796
797This has created a class.  If we want to access it again, for
798example to modify the comment, we can do so like this:
799
800@example
801Account extend [
802    <comment:
803        'I represent a place to withdraw money that has been deposited'>
804]
805@end example
806
807This instructs Smalltalk to pick an existing class, rather than
808trying to create a subclass.
809
810@node Defining methods
811@subsection Defining a method for the class
812
813We have created a class, but it isn't ready to do any
814work for us---we have to define some messages which the class
815can process first.  We'll start at the beginning by defining
816methods for instance creation:
817@example
818    Account class extend [
819       new [
820           | r |
821           <category: 'instance creation'>
822           r := super new.
823           r init.
824           ^r
825      ]
826   ]
827@end example
828
829The important points about this are:
830
831@itemize @bullet
832@item
833@code{Account class} means that we are defining messages which are
834to be sent to the Account class itself.
835
836@item
837@code{<category: 'instance creation'>}
838is more documentation support; it says that the methods
839we are defining supports creating objects of type
840Account.
841
842@item
843The text starting with @code{new [} and ending with @code{]}
844defined what action to take for the message @code{new}.
845When you enter this definition, @gst{} will simply
846give you another prompt, but your method has been compiled in
847and is ready for use.  @gst{} is pretty quiet on successful
848method definitions---but you'll get plenty of error
849messages if there's a problem!
850
851If you're familiar with other Smalltalks, note that the body
852of the method is always in brackets.
853@end itemize
854
855The best way to describe how this method works is to
856step through it.  Imagine we sent a message to the new class
857Account with the command line:
858@example
859   Account new
860@end example
861
862@code{Account} receives the message @code{new} and looks up
863how to process this message.  It finds our new definition, and
864starts running it.  The first line, @code{| r |}, creates a local
865variable named @code{r} which can be used as a placeholder for
866the objects we create.  @code{r} will go away as soon as the message
867is done being processed; note the parallel with @code{balance}, which
868goes away as soon as the object is not used anymore.  And note that
869here you have to declare local variables explicitly, unlike what
870you did in previous examples.
871
872The first real step is to actually create the object.
873The line @code{r := super new} does this using a fancy trick.
874The word @code{super} stands for the same object that the message
875@code{new} was originally sent to (remember?  it's @code{Account}),
876except that when Smalltalk goes to search for the methods,
877it starts one level higher up in the hierarchy than the current
878level.  So for a method in the Account class, this is
879the Object class (because the class Account inherits from is
880Object---go back and look at how we created the Account
881class), and the Object class' methods then execute some code
882in response to the @code{#new} message.  As it turns out, Object
883will do the actual creation of the object when sent a @code{#new}
884message.
885
886One more time in slow motion: the Account method @code{#new}
887wants to do some fiddling about when new objects are created,
888but he also wants to let his parent do some work with
889a method of the same name.  By saying @code{r := super new} he
890is letting his parent create the object, and then he is attaching
891it to the variable @code{r}.  So after this line of code executes,
892we have a brand new object of type Account, and @code{r}
893is bound to it.  You will understand this better as time
894goes on, but for now scratch your head once, accept it as a
895recipe, and keep going.
896
897We have the new object, but we haven't set it up correctly.
898Remember the hidden variable @code{balance} which we saw
899in the beginning of this chapter?  @code{super new} gives us the
900object with the @code{balance} field containing nothing, but we want
901our balance field to start at 0.  @footnote{And unlike C, Smalltalk
902draws a distinction between @code{0} and @code{nil}.  @code{nil}
903is the @i{nothing} object, and you will receive an error if you
904try to do, say, math on it.  It really does matter that we
905initialize our instance variable to the number 0 if we wish
906to do math on it in the future.}
907
908So what we need to do is ask the object to set itself up.
909By saying @code{r init}, we are sending the @code{init}
910message to our new Account.  We'll define
911this method in the next section---for now just assume that
912sending the @code{init} message will get our Account set up.
913
914Finally, we say @code{^r}.  In English, this is @i{return what
915r is attached to}.  This means that whoever sent to Account
916the @code{new} message will get back this brand new account.  At
917the same time, our temporary variable @code{r} ceases to exist.
918
919@node Instance methods
920@subsection Defining an instance method
921
922We need to define the @code{init} method for our Account
923objects, so that our @code{new} method defined above will work.
924Here's the Smalltalk code:
925@example
926Account extend [
927    init [
928        <category: 'initialization'>
929        balance := 0
930    ]
931]
932@end example
933
934It looks quite a bit like the previous method definition,
935except that the first one said
936@code{Account class extend}, and ours says
937@code{Account extend}.
938
939The difference is that the first one defined a method for
940messages sent directly to @code{Account}, but the second one is
941for messages which are sent to Account objects once they are
942created.
943
944The method named @code{init} has only one line, @code{balance := 0}.
945This initializes the hidden variable @code{balance} (actually
946called an instance variable) to zero, which makes
947sense for an account balance.  Notice that the method
948doesn't end with @code{^r} or anything like it: this method
949doesn't return a value to the message sender.  When you do
950not specify a return value, Smalltalk defaults the return
951value to the object currently executing.  For clarity of
952programming, you might consider explicitly returning @code{self}
953in cases where you intend the return value to be used.@footnote{
954And why didn't the designers default the
955return value to nil?  Perhaps they didn't appreciate
956the value of void functions.  After all, at
957the time Smalltalk was being designed, C didn't
958even have a void data type.}
959
960Before going on, ere is how you could have written this code in a
961single declaration (i.e.@: without using @code{extend}):
962
963@example
964Object subclass: Account [
965    | balance |
966    <comment:
967        'I represent a place to deposit and withdraw money'>
968    Account class >> new [
969        <category: 'instance creation'>
970        | r |
971        r := super new.
972        r init.
973        ^r
974    ]
975    init [
976        <category: 'initialization'>
977        balance := 0
978    ]
979]
980@end example
981
982@node A look at our object
983@subsection Looking at our Account
984
985Let's create an instance of class Account:
986@example
987   a := Account new
988@end example
989
990Can you guess what this does?  The @code{Smalltalk at: #a put: <something>}
991creates a Smalltalk variable.  And the @code{Account new} creates a new
992Account, and returns it.  So this line creates a Smalltalk
993variable named @code{a}, and attaches it to a new Account---all in
994one line.  It also prints the Account object we just created:
995@example
996   an Account
997@end example
998
999Hmmm...  not very informative.  The problem is that we didn't
1000tell our Account how to print itself, so we're just getting
1001the default system @code{printNl} method---which tells what the
1002object is, but not what it contains.  So clearly we must add
1003such a method:
1004@example
1005    Account extend [
1006        printOn: stream [
1007            <category: 'printing'>
1008            super printOn: stream.
1009            stream nextPutAll: ' with balance: '.
1010            balance printOn: stream
1011        ]
1012    ]
1013@end example
1014
1015Now give it a try again:
1016@example
1017   a
1018@end example
1019
1020@noindent
1021which prints:
1022@example
1023   an Account with balance: 0
1024@end example
1025
1026This may seem a little strange.  We added a new method,
1027printOn:, and our printNl message starts behaving differently.
1028It turns out that the printOn: message is the central
1029printing function---once you've defined it, all of the
1030other printing methods end up calling it.  Its argument is a
1031place to print to---quite often it is the variable @code{Transcript}.
1032This variable is usually hooked to your terminal, and thus
1033you get the printout to your screen.
1034
1035The @code{super printOn: stream} lets our parent do what it
1036did before---print out what our type is.  The @code{an Account}
1037part of the printout came from this.
1038@code{stream nextPutAll: ' with balance: '} creates the
1039string @code{ with balance: }, and prints it out to the stream,
1040too; note that we don't use @code{printOn:} here because that would
1041enclose our string within quotes.  Finally, @code{balance printOn: stream}
1042asks whatever object is hooked to the @code{balance} variable to print
1043itself to the stream.  We set @code{balance} to 0, so the 0 gets printed out.
1044
1045@node Moving money around
1046@subsection Moving money around
1047
1048We can now create accounts, and look at them.  As it
1049stands, though, our balance will always be 0---what a tragedy!
1050Our final methods will let us deposit and spend money.
1051They're very simple:
1052
1053@example
1054   Account extend [
1055       spend: amount [
1056           <category: 'moving money'>
1057           balance := balance - amount
1058       ]
1059       deposit: amount [
1060           <category: 'moving money'>
1061           balance := balance + amount
1062       ]
1063   ]
1064@end example
1065
1066With these methods you can now deposit and spend amounts of
1067money.  Try these operations:
1068@example
1069   a deposit: 125
1070   a deposit: 20
1071   a spend: 10
1072@end example
1073
1074@node Next coming
1075@subsection What's next?
1076
1077We now have a generic concept, an ``Account''.  We can create them,
1078check their balance, and move money in and out of
1079them.  They provide a good foundation, but leave out important
1080information that particular types of accounts might
1081want.  In the next chapter, we'll take a look at fixing this
1082problem using subclasses.
1083
1084@node Creating subclasses
1085@section Two Subclasses for the Account Class
1086
1087This chapter continues from the previous chapter in
1088demonstrating how one creates classes and subclasses in
1089Smalltalk.  In this chapter we will create two special subclasses
1090of Account, known as Checking and Savings.  We will
1091continue to inherit the capabilities of Account, but will
1092tailor the two kinds of objects to better manage particular
1093kinds of accounts.
1094
1095@menu
1096* The Savings class::           One of the two subclasses we'll put together
1097* The Checking class::          And here is the other
1098* Writing checks::              Only in Smalltalk, of course
1099@end menu
1100
1101@node The Savings class
1102@subsection The Savings class
1103
1104We create the Savings class as a subclass of Account.
1105It holds money, just like an Account, but has an additional
1106property that we will model: it is paid interest based on
1107its balance.  We create the class Savings as a subclass of
1108Account.
1109@example
1110   Account subclass: Savings [
1111       | interest |
1112@end example
1113
1114This is already telling something:
1115the instance variable @code{interest} will accumulate interest
1116paid.  Thus, in addition to the @code{spend:} and
1117@code{deposit:} messages which we inherit from our parent,
1118Account, we will need to define a method to add in interest
1119deposits, and a way to clear the interest variable (which
1120we would do yearly, after we have paid taxes).  We first define
1121a method for allocating a new account---we need to make sure that the
1122interest field starts at 0.
1123
1124We can do so within the @code{Account subclass: Savings} scope,
1125which we have not closed above.
1126@example
1127   init [
1128       <category: 'initialization'>
1129       interest := 0.
1130       ^super init
1131   ]
1132@end example
1133
1134Recall that the parent took care of the @code{new} message, and
1135created a new object of the appropriate size.  After creation,
1136the parent also sent an @code{init} message to the new
1137object.  As a subclass of Account, the new object will
1138receive the @code{init} message first; it sets up its own
1139instance variable, and then passes the @code{init} message up the
1140chain to let its parent take care of its part of the
1141initialization.
1142
1143With our new @code{Savings} account created, we can define
1144two methods for dealing specially with such an account:
1145
1146@example
1147   interest: amount [
1148       interest := interest + amount.
1149       self deposit: amount
1150   ]
1151   clearInterest [
1152       | oldinterest |
1153       oldinterest := interest.
1154       interest := 0.
1155       ^oldinterest
1156   ]
1157@end example
1158
1159We are now finished, and close the class scope:
1160
1161@example
1162]
1163@end example
1164
1165The first method says that we add the @code{amount} to our
1166running total of interest.  The line @code{self deposit: amount}
1167tells Smalltalk to send ourselves a message, in this case
1168@code{deposit: amount}.  This then causes Smalltalk to look up
1169the method for @code{deposit:}, which it finds in our parent,
1170Account.  Executing this method then updates our overall
1171balance.@footnote{@code{self} is much like @code{super}, except that
1172@code{self} will start looking for a method at the bottom
1173of the type hierarchy for the object, while
1174@code{super} starts looking one level up from the current
1175level.  Thus, using @code{super} forces inheritance,
1176but @code{self} will find the first definition
1177of the message which it can.}
1178
1179One may wonder why we don't just replace this with the
1180simpler @code{balance := balance + amount}.  The answer lies
1181in one of the philosophies of object-oriented languages in general,
1182and Smalltalk in particular.  Our goal is to encode a
1183technique for doing something once only, and then re-using
1184that technique when needed.  If we had directly encoded
1185@code{balance := balance + amount} here, there would have been
1186two places that knew how to update the balance from a
1187deposit.  This may seem like a useless difference.  But consider
1188if later we decided to start counting the number of
1189deposits made.  If we had encoded
1190@code{balance := balance + amount} in each place that needed to
1191update the balance, we would have to hunt each of them down in
1192order to update the count of deposits.  By sending @code{self}
1193the message @code{deposit:}, we need only update this method
1194once; each sender of this message would then automatically get the correct
1195up-to-date technique for updating the balance.
1196
1197The second method, @code{clearInterest}, is simpler.  We
1198create a temporary variable @code{oldinterest} to hold the current
1199amount of interest.  We then zero out our interest to
1200start the year afresh.  Finally, we return the old interest
1201as our result, so that our year-end accountant can see how
1202much we made.@footnote{Of course, in a real accounting system we
1203would never discard such information---we'd probably
1204throw it into a Dictionary object, indexed by the
1205year that we're finishing.  The ambitious might
1206want to try their hand at implementing such an
1207enhancement.}
1208
1209
1210@node The Checking class
1211@subsection The Checking class
1212
1213Our second subclass of Account represents a checking
1214account.  We will keep track of two facets:
1215
1216@itemize @bullet
1217@item
1218What check number we are on
1219
1220@item
1221How many checks we have left in our checkbook
1222@end itemize
1223
1224We will define this as another subclass of Account:
1225@example
1226Account subclass: Checking [
1227    | checknum checksleft |
1228@end example
1229
1230We have two instance variables, but we really only need to
1231initialize one of them---if there are no checks left, the current
1232check number can't matter.  Remember, our parent class
1233Account will send us the @code{init} message.  We don't need our
1234own class-specific @code{new} function, since our parent's will
1235provide everything we need.
1236@example
1237    init [
1238       <category: 'initialization'>
1239       checksleft := 0.
1240       ^super init
1241   ]
1242@end example
1243
1244As in Savings, we inherit most of abilities from our superclass,
1245Account.  For initialization, we leave @code{checknum}
1246alone, but set the number of checks in our checkbook to
1247zero.  We finish by letting our parent class do its own
1248initialization.
1249
1250@node Writing checks
1251@subsection Writing checks
1252
1253We will finish this chapter by adding a method for
1254spending money through our checkbook.  The mechanics of taking
1255a message and updating variables should be familiar:
1256@example
1257   newChecks: number count: checkcount [
1258       <category: 'spending'>
1259       checknum := number.
1260       checksleft := checkcount
1261   ]
1262
1263   writeCheck: amount [
1264       <category: 'spending'>
1265       | num |
1266       num := checknum.
1267       checknum := checknum + 1.
1268       checksleft := checksleft - 1.
1269       self spend: amount.
1270       ^ num
1271   ]
1272]
1273@end example
1274
1275@code{newChecks:} fills our checkbook with checks.  We record
1276what check number we're starting with, and update the count
1277of the number of checks in the checkbook.
1278
1279@code{writeCheck:} merely notes the next check number, then
1280bumps up the check number, and down the check count.  The
1281message @code{self spend: amount} resends the message
1282@code{spend:} to our own object.  This causes its method to be looked
1283up by Smalltalk.  The method is then found in our parent class,
1284Account, and our balance is then updated to reflect our
1285spending.
1286
1287You can try the following examples:
1288@example
1289   c := Checking new
1290   c deposit: 250
1291   c newChecks: 100 count: 50
1292   c writeCheck: 32
1293   c
1294@end example
1295
1296For amusement, you might want to add a printOn: message to
1297the checking class so you can see the checking-specific
1298information.
1299
1300In this chapter, you have seen how to create subclasses
1301of your own classes.  You have added new methods, and inherited
1302methods from the parent classes.  These techniques provide
1303the majority of the structure for building solutions to
1304problems.  In the following chapters we will be filling in
1305details on further language mechanisms and types, and providing
1306details on how to debug software written in Smalltalk.
1307
1308@node Code blocks (I)
1309@section Code blocks
1310
1311The Account/Saving/Checking example from the last chapter
1312has several deficiencies.  It has no record of the
1313checks and their values.  Worse, it allows you to write a
1314check when there are no more checks---the Integer value for
1315the number of checks will just calmly go negative!  To fix
1316these problems we will need to introduce more sophisticated
1317control structures.
1318
1319@menu
1320* Conditions::               Making some decisions
1321* Iteration::                Making some loops
1322@end menu
1323
1324@node Conditions
1325@subsection Conditions and decision making
1326
1327Let's first add some code to keep you from writing too
1328many checks.  We will simply update our current method for
1329the Checking class; if you have entered the methods from the
1330previous chapters, the old definition will be overridden by
1331this new one.
1332@example
1333Checking extend [
1334    writeCheck: amount [
1335       | num |
1336
1337       (checksleft < 1)
1338           ifTrue: [ ^self error: 'Out of checks' ].
1339       num := checknum.
1340       checknum := checknum + 1.
1341       checksleft := checksleft - 1.
1342       self spend: amount
1343       ^ num
1344   ]
1345]
1346@end example
1347
1348The two new lines are:
1349@example
1350   (checksleft < 1)
1351       ifTrue: [ ^self error: 'Out of checks' ].
1352@end example
1353
1354At first glance, this appears to be a completely new structure.
1355But, look again!  The only new construct is the square
1356brackets, which appear within a method and not only surround it.
1357
1358The first line is a simple boolean expression.  @code{checksleft}
1359is our integer, as initialized by our Checking class.
1360It is sent the message @code{<}, and the argument 1.  The current
1361number bound to @code{checksleft} compares itself against 1, and
1362returns a boolean object telling whether it is less than 1.
1363
1364Now this boolean, which is either true or false, is sent the
1365message @code{ifTrue:}, with an argument which is called a code
1366block.  A code block is an object, just like any other.  But
1367instead of holding a number, or a Set, it holds executable
1368statements.  So what does a boolean do with a code block which
1369is an argument to a @code{ifTrue:} message?  It depends on which boolean!
1370If the object is the @code{true} object, it executes the code
1371block it has been handed.  If it is the @code{false} object, it
1372returns without executing the code block.  So the traditional
1373@i{conditional construct} has been replaced in
1374Smalltalk with boolean objects which execute the indicated
1375code block or not, depending on their truth-value.
1376@footnote{It is interesting to note that because of the
1377way conditionals are done, conditional constructs
1378are not part of the Smalltalk language, instead they are
1379merely a defined behavior for the Boolean class of
1380objects.}
1381
1382In the case of our example, the actual code within the
1383block sends an error message to the current object.  @code{error:}
1384is handled by the parent class Object, and will pop up an
1385appropriate complaint when the user tries to write too many
1386checks.  In general, the way you handle a fatal error in
1387Smalltalk is to send an error message to yourself (through
1388the @code{self} pseudo-variable), and let the error handling
1389mechanisms inherited from the Object class take over.
1390
1391As you might guess, there is also an @code{ifFalse:} message
1392which booleans accept.  It works exactly like @code{ifTrue:},
1393except that the logic has been reversed; a boolean @code{false}
1394will execute the code block, and a boolean @code{true} will not.
1395
1396You should take a little time to play with this method
1397of representing conditionals.  You can run your checkbook,
1398but can also invoke the conditional functions directly:
1399@example
1400   true ifTrue: [ 'Hello, world!' printNl ]
1401   false ifTrue: [ 'Hello, world!' printNl ]
1402   true ifFalse: [ 'Hello, world!' printNl ]
1403   false ifFalse: [ 'Hello, world!' printNl ]
1404@end example
1405
1406@node Iteration
1407@subsection Iteration and collections
1408
1409Now that we have some sanity checking in place, it
1410remains for us to keep a log of the checks we write.  We
1411will do so by adding a Dictionary object to our Checking
1412class, logging checks into it, and providing some messages
1413for querying our check-writing history.  But this enhancement
1414brings up a very interesting question---when we change
1415the ``shape'' of an object (in this case, by adding our dictionary
1416as a new instance variable to the Checking class),
1417what happens to the existing class, and its objects?
1418The answer is that the old objects are mutated to keep their
1419new shape, and all methods are recompiled so that they work
1420with the new shape.  New objects will have exactly the same shape
1421as old ones, but old objects might happen to be initialized
1422incorrectly (since the newly added variables will be simply
1423put to nil).  As this can lead to very puzzling behavior, it is
1424usually best to eradicate all of the old objects, and then
1425implement your changes.
1426
1427If this were more than a toy object
1428accounting system, this would probably entail saving the
1429objects off, converting to the new class, and reading the
1430objects back into the new format.  For now, we'll just
1431ignore what's currently there, and define our latest Checking
1432class.
1433
1434@example
1435Checking extend [
1436    | history |
1437@end example
1438
1439This is the same syntax as the last time we defined a checking account,
1440except that we start with @code{extend} (since the class is already
1441there).  Then, the two instance variables we had defined remain, and we
1442add a new @code{history} variable; the old methods will be recompiled
1443without errors.  We must now feed in our definitions for each of the
1444messages our object can handle, since we are basically defining a new
1445class under an old name.
1446
1447With our new Checking instance variable, we are all set to start recording
1448our checking history.  Our first change will be in the handling of the
1449@code{init} message:
1450@example
1451       init [
1452           <category: 'initialization'>
1453           checksleft := 0.
1454           history := Dictionary new.
1455           ^ super init
1456       ]
1457@end example
1458
1459This provides us with a Dictionary, and hooks it to our new
1460@code{history} variable.
1461
1462Our next method records each check as it's written.
1463The method is a little more involved, as we've added some
1464more sanity checks to the writing of checks.
1465
1466@example
1467   writeCheck: amount [
1468       <category: 'spending'>
1469       | num |
1470
1471       "Sanity check that we have checks left in our checkbook"
1472       (checksleft < 1)
1473           ifTrue: [ ^self error: 'Out of checks' ].
1474
1475       "Make sure we've never used this check number before"
1476       num := checknum.
1477       (history includesKey: num)
1478           ifTrue: [ ^self error: 'Duplicate check number' ].
1479
1480       "Record the check number and amount"
1481       history at: num put: amount.
1482
1483       "Update our next checknumber, checks left, and balance"
1484       checknum := checknum + 1.
1485       checksleft := checksleft - 1.
1486       self spend: amount.
1487       ^ num
1488   ]
1489@end example
1490
1491We have added three things to our latest version of
1492@code{writeCheck:}.  First, since our routine has become somewhat
1493involved, we have added comments.  In Smalltalk, single
1494quotes are used for strings; double quotes enclose comments.
1495We have added comments before each section of code.
1496
1497Second, we have added a sanity check on the check number
1498we propose to use.  Dictionary objects respond to the
1499@code{includesKey:} message with a boolean, depending on whether
1500something is currently stored under the given key in the
1501dictionary.  If the check number is already used, the @code{error:}
1502message is sent to our object, aborting the operation.
1503
1504Finally, we add a new entry to the dictionary.  We have
1505already seen the @code{at:put:} message (often found written
1506as @code{#at:put:}, with a sharp in front of it) at the start of
1507this tutorial.  Our use here simply associates a check number with
1508an amount of money spent.@footnote{You might start to wonder what
1509one would do if you wished to associate two pieces of
1510information under one key.  Say, the value and who the
1511check was written to.  There are several ways; the
1512best would probably be to create a new, custom
1513object which contained this information, and then
1514store this object under the check number key in
1515the dictionary.  It would also be valid (though
1516probably overkill) to store a dictionary as the
1517value---and then store as many pieces of information
1518as you'd like under each slot!} With this, we now have a working Checking
1519class, with reasonable sanity checks and per-check information.
1520
1521Let us finish the chapter by enhancing our ability to
1522get access to all this information.  We will start with some
1523simple print-out functions.
1524
1525@example
1526   printOn: stream [
1527       super printOn: stream.
1528       ', checks left: ' printOn: stream.
1529       checksleft printOn: stream.
1530       ', checks written: ' printOn: stream.
1531       (history size) printOn: stream.
1532   ]
1533   check: num [
1534       | c |
1535       c := history
1536           at: num
1537           ifAbsent: [ ^self error: 'No such check #' ].
1538       ^c
1539   ]
1540@end example
1541
1542There should be very few surprises here.  We format and
1543print our information, while letting our parent classes handle
1544their own share of the work.  When looking up a check
1545number, we once again take advantage of the fact that blocks
1546of executable statements are an object; in this case, we are
1547using the @code{at:ifAbsent:} message supported by the
1548Dictionary class.  As you can probably anticipate, if the
1549requested key value is not found in the
1550dictionary, the code block is executed.  This allows us to
1551customize our error handling, as the generic error would only
1552tell the user ``key not found''.
1553
1554While we can look up a check if we know its number, we
1555have not yet written a way to ``riffle through'' our collection
1556of checks.  The following function loops over the
1557checks, printing them out one per line.  Because there is
1558currently only a single numeric value under each key, this
1559might seem wasteful.  But we have already considered storing
1560multiple values under each check number, so it is best to
1561leave some room for each item.  And, of course, because we
1562are simply sending a printing message to an object, we will
1563not have to come back and re-write this code so long as the
1564object in the dictionary honors our @code{printNl}/@code{printOn:} messages
1565sages.
1566
1567@example
1568    printChecks [
1569        history keysAndValuesDo: [ :key :value |
1570            key print.
1571            ' - ' print.
1572            value printNl.
1573        ]
1574    ]
1575]
1576@end example
1577
1578We still see a code block object being passed to the
1579dictionary, but @code{:key :value |} is something new.  A code
1580block can optionally receive arguments.  In this case, the
1581two arguments represent a key/value pair.
1582If you only wanted the value portion, you could call
1583history with a @code{do:} message instead; if you only wanted the
1584key portion, you could call history with a @code{keysDo:} message instead.
1585
1586We then invoke our printing interface upon them.  We don't want a
1587newline until the end, so the @code{print} message is used instead.
1588It is pretty much the same as @code{printNl}, since both implicitly use
1589@code{Transcript}, except it doesn't add a newline.
1590
1591It is important that you be clear that in principle there is
1592no relationship between the code block and the dictionary you
1593passed it to.  The dictionary just invokes the passed code block
1594with a key/value pair when processing a keysAndValuesDo: message.  But
1595the same two-parameter code block can be passed to any message that
1596wishes to evaluate it (and passes the exact number of parameters to
1597it).  In the next chapter
1598we'll see more on how code blocks are used; we'll also look at how
1599you can invoke code blocks in your own code.
1600
1601@node Code blocks (II)
1602@section Code blocks, part two
1603
1604In the last chapter, we looked at how code blocks could
1605be used to build conditional expressions, and how you could
1606iterate across all entries in a collection.@footnote{The
1607  @code{do:} message is understood by most types
1608  of Smalltalk collections.  It works for the
1609  Dictionary class, as well as sets, arrays, strings,
1610  intervals, linked lists, bags, and streams.  The
1611  @code{keysDo:} message, for example, works only with dictionaries.}
1612We built our own code blocks, and handed them off for use by system
1613objects.  But there is nothing magic about invoking code
1614blocks; your own code will often need to do so.  This chapter
1615will shows some examples of loop construction in
1616Smalltalk, and then demonstrate how you invoke code blocks
1617for yourself.
1618
1619@menu
1620* Integer loops::            Well, Smalltalk too has them
1621* Intervals::                And of course here's a peculiar way to use them
1622* Invoking code blocks::     You can do it, too
1623@end menu
1624
1625@node Integer loops
1626@subsection Integer loops
1627
1628Integer loops are constructed by telling a number to
1629drive the loop.  Try this example to count from 1 to 20:
1630@example
1631   1 to: 20 do: [:x | x printNl ]
1632@end example
1633
1634There's also a way to count up by more than one:
1635@example
1636   1 to: 20 by: 2 do: [:x | x printNl ]
1637@end example
1638
1639Finally, counting down is done with a negative step:
1640@example
1641   20 to: 1 by: -1 do: [:x | x printNl ]
1642@end example
1643
1644Note that the @code{x} variable is local to the block.
1645@example
1646   x
1647@end example
1648@noindent
1649just prints @code{nil}.
1650
1651@node Intervals
1652@subsection Intervals
1653     It is also possible to represent a range of numbers as
1654a standalone object.  This allows you to represent a range
1655of numbers as a single object, which can be passed around
1656the system.
1657@example
1658   i := Interval from: 5 to: 10
1659   i do: [:x | x printNl]
1660@end example
1661
1662As with the integer loops, the Interval class can also
1663represent steps greater than 1.  It is done much like it was
1664for our numeric loop above:
1665@example
1666   i := (Interval from: 5 to: 10 by: 2)
1667   i do: [:x| x printNl]
1668@end example
1669
1670@node Invoking code blocks
1671@subsection Invoking code blocks
1672
1673Let us revisit the checking example and add a method
1674for scanning only checks over a certain amount.  This would
1675allow our user to find ``big'' checks, by passing in a value
1676below which we will not invoke their function.  We will
1677invoke their code block with the check number as an argument
1678ment; they can use our existing check: message to get the
1679amount.
1680
1681@example
1682   Checking extend [
1683       checksOver: amount do: aBlock
1684           history keysAndValuesDo: [:key :value |
1685               (value > amount)
1686                      ifTrue: [aBlock value: key]
1687           ]
1688   ]
1689@end example
1690
1691The structure of this loop is much like our printChecks message
1692sage from chapter 6.  However, in this case we consider each
1693entry, and only invoke the supplied block if the check's
1694value is greater than the specified amount.  The line:
1695
1696@example
1697   ifTrue: [aBlock value: key]
1698@end example
1699
1700@noindent
1701invokes the user-supplied block, passing as an argument the
1702key, which is the check number.  The @code{value:}
1703message, when received by a code block, causes the code
1704block to execute.  Code blocks take @code{value}, @code{value:},
1705@code{value:value:}, and @code{value:value:value:} messages, so you
1706can pass from 0 to 3 arguments to a code block.@footnote{
1707There is also a @code{valueWithArguments:} message
1708which accepts an array holding as many arguments
1709as you would like.}
1710
1711You might find it puzzling that an association takes a
1712@code{value} message, and so does a code block.  Remember, each
1713object can do its own thing with a message.  A code block gets
1714run when it receives a @code{value} message.  An association merely
1715returns the value part of its key/value pair.  The fact that
1716both take the same message is, in this case, coincidence.
1717
1718Let's quickly set up a new checking account with $250
1719(wouldn't this be nice in real life?) and write a couple
1720checks.  Then we'll see if our new method does the job
1721correctly:
1722@example
1723   mycheck := Checking new.
1724   mycheck deposit: 250
1725   mycheck newChecks: 100 count: 40
1726   mycheck writeCheck: 10
1727   mycheck writeCheck: 52
1728   mycheck writeCheck: 15
1729   mycheck checksOver: 1 do: [:x | x printNl]
1730   mycheck checksOver: 17 do: [:x | x printNl]
1731   mycheck checksOver: 200 do: [:x | x printNl]
1732@end example
1733
1734We will finish this chapter with an alternative way of
1735writing our @code{checksOver:} code.  In this example, we will use
1736the message @code{select:} to pick the checks which exceed our
1737value, instead of doing the comparison ourselves.  We can
1738then invoke the new resulting collection against the user's
1739code block.
1740
1741@example
1742   Checking extend [
1743       checksOver: amount do: aBlock [
1744           | chosen |
1745           chosen := history select: [:amt| amt > amount].
1746           chosen keysDo: aBlock
1747       ]
1748   ]
1749@end example
1750
1751Note that @code{extend} will also overwrite methods.  Try
1752the same tests as above, they should yield the same result!
1753
1754@node Debugging
1755@section When Things Go Bad
1756
1757So far we've been working with examples which work the
1758first time.  If you didn't type them in correctly, you probably
1759received a flood of unintelligible complaints.  You
1760probably ignored the complaints, and typed the example
1761again.
1762
1763When developing your own Smalltalk code, however, these
1764messages are the way you find out what went wrong.  Because
1765your objects, their methods, the error printout, and your
1766interactive environment are all contained within the same
1767Smalltalk session, you can use these error messages to debug
1768your code using very powerful techniques.
1769
1770@menu
1771* Simple errors::                   Those that only happen in examples
1772* Nested calls::                    Those that actually happen in real life
1773* Looking at objects::              Trying to figure it out
1774@end menu
1775
1776@node Simple errors
1777@subsection A Simple Error
1778
1779First, let's take a look at a typical error.  Type:
1780@example
1781   7 plus: 1
1782@end example
1783
1784This will print out:
1785@example
1786   7 did not understand selector 'plus:'
1787   <blah blah>
1788   UndefinedObject>>#executeStatements
1789@end example
1790
1791The first line is pretty simple; we sent a message to the
1792@code{7} object which was not understood; not surprising since
1793the @code{plus:} operation should have been @code{+}.  Then there are
1794a few lines of gobbledegook: just ignore them, they reflect
1795the fact that the error passed throgh @gst{}'s exception
1796handling system.  The remaining line reflect the way the
1797@gst{} invokes code which we type to our command prompt; it
1798generates a block of code which is invoked via an internal
1799method @code{executeStatements} defined in class Object and evaluated
1800like @code{nil executeStatements} (nil is an instance of @i{UndefinedObject}).
1801Thus, this output tells you that you directly typed a line which sent an
1802invalid message to the @code{7} object.
1803
1804All the error output but the first line is actually a
1805stack backtrace.  The most recent call is the one nearer the
1806top of the screen.  In the next example, we will cause an
1807error which happens deeper within an object.
1808
1809@node Nested calls
1810@subsection Nested Calls
1811
1812Type the following lines:
1813@example
1814   x := Dictionary new
1815   x at: 1
1816@end example
1817
1818The error you receive will look like:
1819@example
1820   Dictionary new: 31 "<0x33788>" error: key not found
1821   @i{@r{@dots{}blah blah@dots{}}}
1822   Dictionary>>#error:
1823   [] in Dictionary>>#at:
1824   [] in Dictionary>>#at:ifAbsent:
1825   Dictionary(HashedCollection)>>#findIndex:ifAbsent:
1826   Dictionary>>#at:ifAbsent:
1827   Dictionary>>#at:
1828   UndefinedObject(Object)>>#executeStatements
1829@end example
1830
1831The error itself is pretty clear; we asked for something
1832within the Dictionary which wasn't there.  The object
1833which had the error is identified as @code{Dictionary new: 31}.
1834A Dictionary's default size is 31; thus, this is the object
1835we created with @code{Dictionary new}.
1836
1837The stack backtrace shows us the inner structure of how
1838a Dictionary responds to the @code{#at:} message.  Our hand-entered
1839command causes the usual entry for @code{UndefinedObject(Object)}.
1840Then we see a Dictionary object responding to an @code{#at:} message
1841(the ``Dictionary>>#at:'' line).  This code called the object
1842with an @code{#at:ifAbsent:} message.  All of a sudden,
1843Dictionary calls that strange method @code{#findIndex:ifAbsent:},
1844which evaluates two blocks, and then the error happens.
1845
1846To understand this better, it is necessary to know that
1847a very common way to handle errors in Smalltalk is to
1848hand down a block of code which will be called when an error
1849occurs.  For the Dictionary code, the @code{at:} message passes
1850in a block of code to the at:ifAbsent: code to be called
1851when @code{at:ifAbsent:} can't find the given key, and
1852@code{at:ifAbsent:} does the same with @code{findIndex:ifAbsent:}.
1853Thus, without even looking at the code for Dictionary itself, we can
1854guess something of the code for Dictionary's implementation:
1855
1856@example
1857   findIndex: key ifAbsent: errCodeBlock [
1858       @i{@r{@dots{}look for key@dots{}}}
1859       (keyNotFound) ifTrue: [ ^(errCodeBlock value) ]
1860       @i{@r{@dots{}}}
1861   ]
1862
1863   at: key [
1864       ^self at: key ifAbsent: [^self error: 'key not found']
1865   ]
1866@end example
1867
1868Actually, @code{findIndex:ifAbsent:} lies in class @code{HashedCollection},
1869as that @code{Dictionary(HashedCollection)} in the backtrace says.
1870
1871It would be nice if each entry on the stack backtrace included
1872source line numbers.  Unfortunately, at this point @gst{} doesn't
1873provide this feature.  Of course, you have the source code
1874available...
1875
1876
1877@node Looking at objects
1878@subsection Looking at Objects
1879
1880When you are chasing an error, it is often helpful to
1881examine the instance variables of your objects.  While
1882strategic calls to @code{printNl} will no doubt help, you can look at an
1883object without having to write all the code yourself.  The
1884@code{inspect} message works on any object, and dumps out the
1885values of each instance variable within the object.@footnote{When using
1886the Blox GUI, it actually pops up a so-called @dfn{Inspector window}.}
1887
1888Thus:
1889@example
1890   x := Interval from: 1 to: 5.
1891   x inspect
1892@end example
1893
1894displays:
1895@example
1896   An instance of Interval
1897   start: 1
1898   stop: 5
1899   step: 1
1900   contents: [
1901       [1]: 1
1902       [2]: 2
1903       [3]: 3
1904       [4]: 4
1905       [5]: 5
1906   ]
1907@end example
1908
1909We'll finish this chapter by emphasizing a technique
1910which has already been covered: the use of the @code{error:}
1911message in your own objects.  As you saw in the case of Dictionary,
1912an object can send itself an @code{error:} message with a
1913descriptive string to abort execution and dump a stack backtrace.
1914You should plan on using this technique in your own
1915objects.  It can be used both for explicit user-caused
1916errors, as well as in internal sanity checks.
1917
1918
1919@node More subclassing
1920@section Coexisting in the Class Hierarchy
1921
1922The early chapters of this tutorial discussed classes in
1923one of two ways.  The ``toy'' classes we developed were rooted
1924at Object; the system-provided classes were treated as
1925immutable entities.  While one shouldn't modify the behavior
1926of the standard classes lightly, ``plugging in'' your own
1927classes in the right place among their system-provided
1928brethren can provide you powerful new classes with very little
1929effort.
1930
1931This chapter will create two complete classes which
1932enhance the existing Smalltalk hierarchy.  The discussion
1933will start with the issue of where to connect our new
1934classes, and then continue onto implementation.  Like most
1935programming efforts, the result will leave many possibilities
1936for improvements.  The framework, however, should begin
1937to give you an intuition of how to develop your own
1938Smalltalk classes.
1939
1940@menu
1941* The existing hierarchy::           We've been talking about it for a while,
1942                                     so here it is at last
1943* Playing with Arrays::              Again.
1944* New kinds of Numbers::             Sounds interesting, doesn't it?
1945* Inheritance and Polymorphism::     Sounds daunting, doesn't it?
1946@end menu
1947
1948@node The existing hierarchy
1949@subsection The Existing Class Hierarchy
1950
1951To discuss where a new class might go, it is helpful to
1952have a map of the current classes.  The following is the
1953basic class hierarchy of @gst{}.  Indentation means
1954that the line inherits from the earlier line with one less
1955level of indentation.@footnote{This listing is courtesy of the
1956printHierarchy method supplied by @gst{} author Steve
1957Byrne.  It's in the @file{kernel/Browser.st} file.}.
1958
1959@display
1960@t{  }Object
1961@t{    }Behavior
1962@t{      }ClassDescription
1963@t{        }Class
1964@t{        }Metaclass
1965@t{    }BlockClosure
1966@t{    }Boolean
1967@t{      }False
1968@t{      }True
1969@t{    }Browser
1970@t{    }CFunctionDescriptor
1971@t{    }CObject
1972@t{      }CAggregate
1973@t{        }CArray
1974@t{        }CPtr
1975@t{      }CCompound
1976@t{        }CStruct
1977@t{        }CUnion
1978@t{      }CScalar
1979@t{        }CChar
1980@t{        }CDouble
1981@t{        }CFloat
1982@t{        }CInt
1983@t{        }CLong
1984@t{        }CShort
1985@t{        }CSmalltalk
1986@t{        }CString
1987@t{        }CUChar
1988@t{          }CByte
1989@t{            }CBoolean
1990@t{        }CUInt
1991@t{        }CULong
1992@t{        }CUShort
1993@t{    }Collection
1994@t{      }Bag
1995@t{      }MappedCollection
1996@t{      }SequenceableCollection
1997@t{        }ArrayedCollection
1998@t{          }Array
1999@t{          }ByteArray
2000@t{          }WordArray
2001@t{          }LargeArrayedCollection
2002@t{            }LargeArray
2003@t{            }LargeByteArray
2004@t{            }LargeWordArray
2005@t{          }CompiledCode
2006@t{            }CompiledMethod
2007@t{            }CompiledBlock
2008@t{          }Interval
2009@t{          }CharacterArray
2010@t{            }String
2011@t{              }Symbol
2012@t{        }LinkedList
2013@t{          }Semaphore
2014@t{        }OrderedCollection
2015@t{          }RunArray
2016@t{          }SortedCollection
2017@t{      }HashedCollection
2018@t{        }Dictionary
2019@t{          }IdentityDictionary
2020@t{            }MethodDictionary
2021@t{          }RootNamespace
2022@t{            }Namespace
2023@t{            }SystemDictionary
2024@t{        }Set
2025@t{          }IdentitySet
2026@t{    }ContextPart
2027@t{      }BlockContext
2028@t{      }MethodContext
2029@t{    }CType
2030@t{      }CArrayCType
2031@t{      }CPtrCType
2032@t{      }CScalarCType
2033@t{    }Delay
2034@t{    }DLD
2035@t{    }DumperProxy
2036@t{      }AlternativeObjectProxy
2037@t{        }NullProxy
2038@t{          }VersionableObjectProxy
2039@t{        }PluggableProxy
2040@t{    }File
2041@t{      }Directory
2042@t{    }FileSegment
2043@t{    }Link
2044@t{      }Process
2045@t{      }SymLink
2046@t{    }Magnitude
2047@t{      }Association
2048@t{      }Character
2049@t{      }Date
2050@t{      }LargeArraySubpart
2051@t{      }Number
2052@t{        }Float
2053@t{        }Fraction
2054@t{        }Integer
2055@t{          }LargeInteger
2056@t{            }LargeNegativeInteger
2057@t{            }LargePositiveInteger
2058@t{              }LargeZeroInteger
2059@t{          }SmallInteger
2060@t{      }Time
2061@t{    }Memory
2062@t{    }Message
2063@t{      }DirectedMessage
2064@t{    }MethodInfo
2065@t{    }NullProxy
2066@t{    }PackageLoader
2067@t{    }Point
2068@t{    }ProcessorScheduler
2069@t{    }Rectangle
2070@t{    }SharedQueue
2071@t{    }Signal
2072@t{      }Exception
2073@t{        }Error
2074@t{          }Halt
2075@t{            }ArithmeticError
2076@t{              }ZeroDivide
2077@t{            }MessageNotUnderstood
2078@t{          }UserBreak
2079@t{        }Notification
2080@t{          }Warning
2081@t{    }Stream
2082@t{      }ObjectDumper
2083@t{      }PositionableStream
2084@t{        }ReadStream
2085@t{        }WriteStream
2086@t{          }ReadWriteStream
2087@t{            }ByteStream
2088@t{              }FileStream
2089@t{      }Random
2090@t{      }TextCollector
2091@t{      }TokenStream
2092@t{    }TrappableEvent
2093@t{      }CoreException
2094@t{      }ExceptionCollection
2095@t{    }UndefinedObject
2096@t{    }ValueAdaptor
2097@t{      }NullValueHolder
2098@t{      }PluggableAdaptor
2099@t{        }DelayedAdaptor
2100@t{      }ValueHolder
2101@end display
2102
2103While initially a daunting list, you should take the
2104time to hunt down the classes we've examined in this tutorial
2105so far.  Notice, for instance, how an Array is a subclass
2106below the @i{SequenceableCollection} class.  This makes sense;
2107you can walk an Array from one end to the other.  By contrast,
2108notice how this is not true for Sets: it doesn't make sense
2109to walk a Set from one end to the other.
2110
2111A little puzzling is the relationship of a Bag to a Set, since
2112a Bag is actually a Set supporting multiple occurrences of its
2113elements.  The answer lies in the purpose of both a Set and a
2114Bag.  Both hold an unordered collection of objects; but a Bag
2115needs to be optimized for the case when an object has possibly
2116thousands of occurrences, while a Set is optimized for checking
2117object uniqueness.  That's why Set being a subclass or Bag, or
2118the other way round, would be a source of problems in the actual
2119implementation of the class.  Currently a Bag holds a Dictionary
2120associating each object to each count; it would be feasible however
2121to have Bag as a subclass of HashedCollection and a sibling of Set.
2122
2123Look at the treatment of numbers---starting with the class
2124@i{Magnitude}.  While numbers can indeed be ordered by @emph{less than},
2125@emph{greater than}, and so forth, so can a number of other
2126objects.  Each subclass of Magnitude is such an
2127object.  So we can compare characters with other characters,
2128dates with other dates, and times with other times, as well
2129as numbers with numbers.
2130
2131Finally, you will have probably noted some pretty strange classes,
2132representing language entities that you might have never thought
2133of as objects themselves: @i{Namespace}, @i{Class} and even
2134@i{CompiledMethod}.  They are the base of Smalltalk's ``reflection''
2135mechanism which will be discussed later, in @ref{Why is #new
2136there?!?, , The truth on metaclasses}.
2137
2138@node Playing with Arrays
2139@subsection Playing with Arrays
2140
2141Imagine that you need an array, but alas you need that if an index
2142is out of bounds, it returns nil.  You could modify the Smalltalk
2143implementation, but that might break some code in the image, so it
2144is not practical.  Why not add a subclass?
2145
2146@example
2147   "We could subclass from Array, but that class is specifically
2148    optimized by the VM (which assumes, among other things, that
2149    it does not have any instance variables).  So we use its
2150    abstract superclass instead.  The discussion below holds
2151    equally well."
2152   ArrayedCollection subclass: NiledArray [
2153       <shape: #pointer>
2154
2155       boundsCheck: index [
2156           ^(index < 1) | (index > (self basicSize))
2157       ]
2158
2159       at: index [
2160           ^(self boundsCheck: index)
2161               ifTrue: [ nil ]
2162               ifFalse: [ super at: index ]
2163       ]
2164
2165       at: index put: val [
2166           ^(self boundsCheck: index)
2167               ifTrue: [ val ]
2168               ifFalse: [ super at: index put: val ]
2169       ]
2170   ]
2171@end example
2172
2173Much of the machinery of adding a class should be
2174familiar.  We see another declaration like @code{comment:},
2175that is @code{shape:} message.  This sets up @code{NiledArray}
2176to have the same underlying
2177structure of an @code{Array} object; we'll delay discussing this
2178until the chapter on the nuts and bolts of arrays.  In any
2179case, we inherit all of the actual knowledge of how to create
2180arrays, reference them, and so forth.  All that we do is
2181intercept @code{at:} and @code{at:put:} messages, call our common
2182function to validate the array index, and do something special
2183if the index is not valid.  The way that we coded
2184the bounds check bears a little examination.
2185
2186Making a first cut at coding the bounds check, you
2187might have coded the bounds check in NiledArray's methods
2188twice (once for @code{at:}, and again for @code{at:put:}.  As
2189always, it's preferable to code things once, and then re-use them.
2190So we instead add a method for bounds checking @code{boundsCheck:}, and
2191use it for both cases.  If we ever wanted to enhance the
2192bounds checking (perhaps emit an error if the index is < 1 and
2193answer nil only for indices greater than the array size?), we only
2194have to change it in one place.
2195
2196The actual math for calculating whether the bounds have
2197been violated is a little interesting.  The first part of
2198the expression returned by the method:
2199@example
2200   (index < 1) | (index > (self basicSize))
2201@end example
2202
2203@noindent
2204is true if the index is less than 1, otherwise it's false.
2205This part of the expression thus becomes the boolean object
2206true or false.  The boolean object then receives the message
2207@code{|}, and the argument @code{(index > (self basicSize))}.
2208@code{|} means ``or''---we want to OR together the two possible
2209out-of-range checks.  What is the second part of the expression?
2210@footnote{Smalltalk also offers an @code{or:} message, which
2211is different in a subtle way from @code{|}.  or: takes
2212a code block, and only invokes the code block if
2213it's necessary to determine the value of the
2214expression.  This is analogous to the guaranteed C
2215semantic that @code{||} evaluates left-to-right only as
2216far as needed.  We could have written the expressions
2217as @code{((index < 1) or: [index > (self basicSize)])}.
2218Since we expect both sides of or: to be
2219false most of the time, there isn't much reason to
2220delay evaluation of either side in this case.}
2221
2222@code{index} is our argument, an integer; it receives the
2223message @code{>}, and thus will compare itself to the value
2224@code{self basicSize} returns.  While we haven't covered the
2225underlying structures Smalltalk uses to build arrays, we can
2226briefly say that the @code{#basicSize} message returns the number
2227of elements the Array object can contain.  So the index is checked
2228to see if it's less than 1 (the lowest legal Array index) or
2229greater than the highest allocated slot in the Array.  If it
2230is either (the @code{|} operator!), the expression is true,
2231otherwise false.
2232
2233From there it's downhill; our boolean object, returned by
2234@code{boundsCheck:}, receives the @code{ifTrue:ifFalse:} message,
2235and a code block which will do the appropriate thing.  Why do we
2236have @code{at:put:} return val?  Well, because that's what it's
2237supposed to do: look at every implementor of @code{at:put} or @code{at:}
2238and you'll find that it returns its second parameter.  In general, the
2239result is discarded; but one could write a program which uses it, so
2240we'll write it this way anyway.
2241
2242
2243@node New kinds of Numbers
2244@subsection Adding a New Kind of Number
2245
2246If we were programming an application which did a large
2247amount of complex math, we could probably manage it with a
2248number of two-element arrays.  But we'd forever be writing
2249in-line code for the math and comparisons; it would be much
2250easier to just implement an object class to support the complex
2251numeric type.  Where in the class hierarchy would it be
2252placed?
2253
2254You've probably already guessed---but let's step down the
2255hierarchy anyway.  Everything inherits from Object, so
2256that's a safe starting point.  Complex numbers can not be
2257compared with @code{<} and @code{>}, and yet we strongly suspect that,
2258since they are numbers, we should place them under the Number
2259class.  But Number inherits from Magnitude---how do we
2260resolve this conflict?  A subclass can place itself under a
2261superclass which allows some operations the subclass doesn't
2262wish to allow.  All that you must do is make sure you intercept
2263these messages and return an error.  So we will place
2264our new Complex class under Number, and make sure to disallow
2265comparisons.
2266
2267One can reasonably ask whether the real and imaginary
2268parts of our complex number will be integer or floating
2269point.  In the grand Smalltalk tradition, we'll just leave
2270them as objects, and hope that they respond to numeric messages
2271reasonably.  If they don't, the user will doubtless
2272receive errors and be able to track back their mistake with
2273little fuss.
2274
2275We'll define the four basic math operators, as well as
2276the (illegal) relationals.  We'll add @code{printOn:} so that the
2277printing methods work, and that should give us our Complex
2278class.  The class as presented suffers some limitations,
2279which we'll cover later in the chapter.
2280
2281@example
2282   Number subclass: Complex [
2283       | realpart imagpart |
2284
2285       "This is a quick way to define class-side methods."
2286       Complex class >> new [
2287           <category: 'instance creation'>
2288           ^self error: 'use real:imaginary:'
2289       ]
2290       Complex class >> new: ignore [
2291           <category: 'instance creation'>
2292           ^self new
2293       ]
2294       Complex class >> real: r imaginary: i [
2295           <category: 'instance creation'>
2296           ^(super new) setReal: r setImag: i
2297       ]
2298
2299       setReal: r setImag: i [
2300           <category: 'basic'>
2301           realpart := r.
2302           imagpart := i.
2303           ^self
2304       ]
2305
2306       real [
2307           <category: 'basic'>
2308           ^realpart
2309       ]
2310       imaginary [
2311           <category: 'basic'>
2312           ^imagpart
2313       ]
2314
2315       + val [
2316           <category: 'math'>
2317           ^Complex real: (realpart + val real)
2318               imaginary: (imagpart + val imaginary)
2319       ]
2320       - val [
2321           <category: 'math'>
2322           ^Complex real: (realpart - val real)
2323               imaginary: (imagpart - val imaginary)
2324       ]
2325       * val [
2326           <category: 'math'>
2327           ^Complex real: (realpart * val real) - (imagpart * val imaginary)
2328               imaginary: (imagpart * val real) + (realpart * val imaginary)
2329       ]
2330       / val [
2331           <category: 'math'>
2332           | d r i |
2333           d := (val real * val real) + (val imaginary * val imaginary).
2334           r := ((realpart * val real) + (imagpart * val imaginary)).
2335           i := ((imagpart * val real) - (realpart * val imaginary)).
2336           ^Complex real: r / d imaginary: i / d
2337       ]
2338
2339       = val [
2340           <category: 'comparison'>
2341           ^(realpart = val real) & (imagpart = val imaginary)
2342       ]
2343
2344       "All other comparison methods are based on <"
2345       < val [
2346           <category: 'comparison'>
2347           ^self shouldNotImplement
2348       ]
2349
2350       printOn: aStream [
2351           <category: 'printing'>
2352           realpart printOn: aStream.
2353           aStream nextPut: $+.
2354           imagpart printOn: aStream.
2355           aStream nextPut: $i
2356       ]
2357   ]
2358@end example
2359
2360There should be surprisingly little which is actually
2361new in this example.  The printing method uses both @code{printOn:}
2362as well as @code{nextPut:} to do its printing.  While we haven't
2363covered it, it's pretty clear that @code{$+} generates the ASCII
2364character @code{+} as an object@footnote{A @gst{} extension
2365  allows you to type characters by ASCII code too, as in
2366  @code{$<43>}.}, and @code{nextPut:} puts its argument
2367as the next thing on the stream.
2368
2369The math operations all generate a new object, calculating
2370the real and imaginary parts, and invoking the Complex
2371class to create the new object.  Our creation code is a
2372little more compact than earlier examples; instead of using
2373a local variable to name the newly-created object, we just
2374use the return value and send a message directly to the new
2375object.  Our initialization code explicitly returns self;
2376what would happen if we left this off?
2377
2378@node Inheritance and Polymorphism
2379@subsection Inheritance and Polymorphism
2380
2381This is a good time to look at what we've done with the
2382two previous examples at a higher level.  With the
2383NiledArray class, we inherited almost all of the functionality
2384ality of arrays, with only a little bit of code added to
2385address our specific needs.  While you may have not thought
2386to try it, all the existing methods for an Array continue to
2387work without further effort-you might find it interesting to
2388ponder why the following still works:
2389@example
2390   a := NiledArray new: 10
2391   a at: 5 put: 1234
2392   a do: [:i| i printNl ]
2393@end example
2394
2395The strength of inheritance is that you focus on the incremental
2396changes you make; the things you don't change will generally
2397continue to work.
2398
2399In the Complex class, the value of polymorphism was
2400exercised.  A Complex number responds to exactly the same
2401set of messages as any other number.  If you had handed this
2402code to someone, they would know how to do math with Complex
2403numbers without further instruction.  Compare this with C,
2404where a complex number package would require the user to
2405first find out if the complex-add function was
2406complex_plus(), or perhaps complex_add(), or add_complex(),
2407or@dots{}
2408
2409However, one glaring deficiency is present in the Complex class:
2410what happens if you mix normal numbers with Complex numbers?
2411Currently, the Complex class assumes that it will only
2412interact with other Complex numbers.  But this is unrealistic:
2413mathematically, a ``normal'' number is simply one with an
2414imaginary part of 0.  Smalltalk was designed to allow numbers
2415to coerce themselves into a form which will work with
2416other numbers.
2417
2418The system is clever and requires very little additional
2419code.  Unfortunately, it would have tripled the
2420amount of explanation required.  If you're interested in how
2421coercion works in @gst{}, you should find the
2422Smalltalk library source, and trace back the execution of
2423the @code{retry:coercing:} messages.  You want to consider the
2424value which the @code{generality} message returns for each type
2425of number.  Finally, you need to examine the @code{coerce:} handling
2426in each numeric class.
2427
2428
2429@node Streams
2430@section Smalltalk Streams
2431
2432Our examples have used a mechanism extensively, even
2433though we haven't discussed it yet.  The Stream class provides
2434a framework for a number of data structures, including
2435input and output functionality, queues, and endless sources
2436of dynamically-generated data.  A Smalltalk stream is quite
2437similar to the UNIX streams you've used from C.  A stream
2438provides a sequential view to an underlying resource; as you
2439read or write elements, the stream position advances until
2440you finally reach the end of the underlying medium.  Most
2441streams also allow you to set the current position, providing
2442random access to the medium.
2443
2444@menu
2445* The output stream::                Which, even though you maybe didn't know
2446                                     it, we've used all the time
2447* Your own stream::                  Which, instead, is something new
2448* Files::                            Which are streams too
2449* Dynamic Strings::                  A useful application of Streams
2450@end menu
2451
2452@node The output stream
2453@subsection The Output Stream
2454
2455The examples in this book all work because they write
2456their output to the @code{Transcript} stream.  Each class implements
2457the @code{printOn:} method, and writes its output to the supplied
2458stream.  The @code{printNl} method all objects use is simply to
2459send the current object a @code{printOn:} message whose argument is
2460@code{Transcript} (by default attached to the standard output stream
2461found in the @code{stdout} global).  You can invoke the standard output stream
2462directly:
2463@example
2464   'Hello, world' printOn: stdout
2465   stdout inspect
2466@end example
2467
2468@noindent
2469or you can do the same for the Transcript, which is yet another stream:
2470@example
2471   'Hello, world' printOn: stdout
2472   Transcript inspect
2473@end example
2474
2475@noindent
2476the last @code{inspect} statement will show you how the @code{Transcript} is
2477linked to @code{stdout}@footnote{Try executing it under Blox, where the
2478Transcript is linked to the omonymous window!}.
2479
2480@node Your own stream
2481@subsection Your Own Stream
2482
2483Unlike a pipe you might create in C, the underlying
2484storage of a Stream is under your control.  Thus, a Stream
2485can provide an anonymous buffer of data, but it can also
2486provide a stream-like interpretation to an existing array of
2487data.  Consider this example:
2488@example
2489   a := Array new: 10
2490   a at: 4 put: 1234
2491   a at: 9 put: 5678
2492   s := ReadWriteStream on: a.
2493   s inspect
2494   s position: 1
2495   s inspect
2496   s nextPut: 11; nextPut: 22
2497   (a at: 1) printNl
2498   a do: [:x| x printNl]
2499   s position: 2
2500   s do: [:x| x printNl]
2501   s position: 5
2502   s do: [:x| x printNl]
2503   s inspect
2504@end example
2505
2506The key is the @code{on:} message; it tells a stream class to
2507create itself in terms of the existing storage.  Because of
2508polymorphism, the object specified by on: does not have to
2509be an Array; any object which responds to numeric at: messages
2510can be used.  If you happen to have the NiledArray
2511class still loaded from the previous chapter, you might try
2512streaming over that kind of array instead.
2513
2514You're wondering if you're stuck with having to know
2515how much data will be queued in a Stream at the time you
2516create the stream.  If you use the right class of stream,
2517the answer is no.  A ReadStream provides read-only access to
2518an existing collection.  You will receive an error if you
2519try to write to it.  If you try to read off the end of the
2520stream, you will also get an error.
2521
2522By contrast, WriteStream and ReadWriteStream (used in
2523our example) will tell the underlying collection to grow
2524when you write off the end of the existing collection.  Thus,
2525if you want to write several strings, and don't want to add up their
2526lengths yourself:
2527
2528@example
2529   s := ReadWriteStream on: String new
2530   s inspect
2531   s nextPutAll: 'Hello, '
2532   s inspect
2533   s nextPutAll: 'world'
2534   s inspect
2535   s position: 1
2536   s inspect
2537   s do: [:c | stdout nextPut: c ]
2538   s contents
2539@end example
2540
2541In this case, we have used a String as the collection
2542for the Stream.  The @code{printOn:} messages add bytes to the initially
2543empty string.  Once we've added the data, you can
2544continue to treat the data as a stream.  Alternatively, you
2545can ask the stream to return to you the underlying object.
2546After that, you can use the object (a String, in this example)
2547using its own access methods.
2548
2549There are many amenities available on a stream object.
2550You can ask if there's more to read with @code{atEnd}.  You can
2551query the position with @code{position}, and set it with @code{position:}.
2552You can see what will be read next with @code{peek}, and
2553you can read the next element with @code{next}.
2554
2555In the writing direction, you can write an element with
2556@code{nextPut:}.  You don't need to worry about objects doing a
2557@code{printOn:} with your stream as a destination; this operation
2558ends up as a sequence of @code{nextPut:} operations to your stream.
2559If you have a collection of things to write, you can use
2560@code{nextPutAll:} with the collection as an argument; each member
2561of the collection will be written onto the stream.  If you
2562want to write an object to the stream several times, you
2563can use @code{next:put:}, like this:
2564
2565@example
2566   s := ReadWriteStream on: (Array new: 0)
2567   s next: 4 put: 'Hi!'
2568   s position: 1
2569   s do: [:x | x printNl]
2570@end example
2571
2572@node Files
2573@subsection Files
2574
2575Streams can also operate on files.  If you wanted to
2576dump the file @file{/etc/passwd} to your terminal, you could
2577create a stream on the file, and then stream over its contents:
2578@example
2579   f := FileStream open: '/etc/passwd' mode: FileStream read
2580   f linesDo: [ :c | Transcript nextPutAll: c; nl ]
2581   f position: 30
2582   25 timesRepeat: [ Transcript nextPut: (f next) ]
2583   f close
2584@end example
2585
2586and, of course, you can load Smalltalk source code into your
2587image:
2588@example
2589   FileStream fileIn: '/Users/myself/src/source.st'
2590@end example
2591
2592@node Dynamic Strings
2593@subsection Dynamic Strings
2594
2595Streams provide a powerful abstraction for a number of
2596data structures.  Concepts like current position, writing
2597the next position, and changing the way you view a data
2598structure when convenient combine to let you write compact,
2599powerful code.  The last example is taken from the actual
2600Smalltalk source code---it shows a general method for making
2601an object print itself onto a string.
2602
2603@example
2604   printString [
2605       | stream |
2606       stream := WriteStream on: (String new).
2607       self printOn: stream.
2608       ^stream contents
2609   ]
2610@end example
2611
2612This method, residing in Object, is inherited by every
2613class in Smalltalk.  The first line creates a WriteStream
2614which stores on a String whose length is currently 0
2615(@code{String new} simply creates an empty string.  It
2616then invokes the current object with @code{printOn:}.  As the
2617object prints itself to ``stream'', the String grows to accommodate
2618new characters.  When the object is done printing,
2619the method simply returns the underlying string.
2620
2621As we've written code, the assumption has been that
2622printOn: would go to the terminal.  But replacing a stream
2623to a file like @file{/dev/tty} with a stream to a data
2624structure (@code{String new}) works just as well.  The last line
2625tells the Stream to return its underlying collection, which will
2626be the string which has had all the printing added to it.  The
2627result is that the @code{printString} message returns an object of
2628the String class whose contents are the printed representation
2629of the very object receiving the message.
2630
2631
2632@node Exception handling
2633@section Exception handling in Smalltalk
2634
2635Up to this point of the tutorial, you used the original Smalltalk-80
2636error signalling mechanism:
2637
2638@example
2639   check: num [
2640       | c |
2641       c := history
2642           at: num
2643           ifAbsent: [ ^self error: 'No such check #' ].
2644       ^c
2645   ]
2646@end example
2647
2648In the above code, if a matching check number is found, the method will
2649answer the object associated to it.  If no prefix is found, Smalltalk
2650will unwind the stack and print an error message including the message
2651you gave and stack information.
2652
2653@example
2654CheckingAccount new: 31 "<0x33788>" error: No such check #
2655@i{@r{@dots{}blah blah@dots{}}}
2656CheckingAccount>>#error:
2657[] in Dictionary>>#at:ifAbsent:
2658Dictionary(HashedCollection)>>#findIndex:ifAbsent:
2659Dictionary>>#at:ifAbsent:
2660[] in CheckingAccount>>#check:
2661CheckingAccount>>#check:
2662UndefinedObject(Object)>>#executeStatements
2663@end example
2664
2665Above we see the object that received the #error: message, the message
2666text itself, and the frames (innermost-first) running when the error was
2667captured by the system.  In addition, the rest of the code in methods
2668like @code{CheckingAccount>>#check:} was not executed.
2669
2670So simple error reporting gives us most of the features we want:
2671
2672@itemize @bullet
2673@item
2674Execution stops immediately, preventing programs from continuing as if
2675nothing is wrong.
2676
2677@item
2678The failing code provides a more-or-less useful error message.
2679
2680@item
2681Basic system state information is provided for diagnosis.
2682
2683@item
2684A debugger can drill further into the state, providing information like
2685details of the receivers and arguments on the stack.
2686@end itemize
2687
2688However, there is a more powerful and complex error handling mechanism,
2689that is @dfn{exception}.  They are like "exceptions" in other programming
2690languages, but are more powerful and do not always indicate error
2691conditions.  Even though we use the term "signal" often with regard
2692to them, do not confuse them with the signals like @code{SIGTERM} and
2693@code{SIGINT} provided by some operating systems; they are a different
2694concept altogether.
2695
2696Deciding to use exceptions instead of @code{#error:} is a matter of
2697aesthetics, but you can use a simple rule: use exceptions only if you want
2698to provide callers with a way to recover sensibly from certain errors,
2699and then only for signalling those particular errors.
2700
2701For example, if you are writing a word processor, you might provide the
2702user with a way to make regions of text read-only.  Then, if the user
2703tries to edit the text, the objects that model the read-only text can
2704signal a @code{ReadOnlyText} or other kind of exception, whereupon the
2705user interface code can stop the exception from unwinding and report
2706the error to the user.
2707
2708When in doubt about whether exceptions would be useful, err on the side
2709of simplicity; use @code{#error:} instead.  It is much easier to convert an
2710#error: to an explicit exception than to do the opposite.
2711
2712@menu
2713* Creating exceptions::                Starting to use the mechanism
2714* Raising exceptions::                 What to do when exceptional events happen
2715* Handling exceptions::                The other side
2716* When an exception isn't handled::    Default actions
2717* Creating new exception classes::     Your own exceptions
2718* Hooking into the stack unwinding::   An alternative exception handling system
2719* Handler stack unwinding caveat::     Differences with other languages
2720@end menu
2721
2722@node Creating exceptions
2723@subsection Creating exceptions
2724
2725@gst{} provides a few exceptions, all of which are subclasses of
2726@code{Exception}.  Most of the ones you might want to create yourself are
2727in the @code{SystemExceptions} namespace.  You can browse the builtin
2728exceptions in the base library reference, and look at their names with
2729@code{Exception printHierarchy}.
2730
2731Some useful examples from the system exceptions are
2732@code{SystemExceptions.InvalidValue}, whose meaning should be obvious, and
2733@code{SystemExceptions.WrongMessageSent}, which we will demonstrate below.
2734
2735Let's say that you change one of your classes to no longer support #new
2736for creating new instances.  However, because you use the first-class
2737classes feature of Smalltalk, it is not so easy to find and change
2738all sends.  Now, you can do something like this:
2739
2740@example
2741Object subclass: Toaster [
2742    Toaster class >> new [
2743        ^SystemExceptions.WrongMessageSent
2744            signalOn: #new useInstead: #toast:
2745    ]
2746
2747    Toaster class >> toast: reason [
2748        ^super new reason: reason; yourself
2749    ]
2750
2751    ...
2752]
2753@end example
2754
2755Admittedly, this doesn't quite fit the conditions for using exceptions.
2756However, since the exception type is already provided, it is probably
2757easier to use it than #error: when you are doing defensive programming
2758of this sort.
2759
2760@node Raising exceptions
2761@subsection Raising exceptions
2762
2763Raising an exception is really a two-step process.  First, you create
2764the exception object; then, you send it @code{#signal}.
2765
2766If you look through the hierarchy, you'll see many class methods
2767that combine these steps for convenience.  For example, the class
2768@code{Exception} provides @code{#new} and @code{#signal}, where the
2769latter is just @code{^self new signal}.
2770
2771You may be tempted to provide only a signalling variant of your own
2772exception creation methods.  However, this creates the problem that
2773your subclasses will not be able to trivially provide new instance
2774creation methods.
2775
2776@example
2777Error subclass: ReadOnlyText [
2778    ReadOnlyText class >> signalOn: aText range: anInterval [
2779        ^self new initText: aText range: anInterval; signal
2780    ]
2781
2782    initText: aText range: anInterval [
2783        <category: 'private'>
2784        ...
2785    ]
2786]
2787@end example
2788
2789Here, if you ever want to subclass @code{ReadOnlyText} and add new
2790information to the instance before signalling it, you'll have to use
2791the private method @code{#initText:range:}.
2792
2793We recommend leaving out the signalling instance-creation variant in new
2794code, as it saves very little work and makes signalling code less clear.
2795Use your own judgement and evaluation of the situation to determine when
2796to include a signalling variant.
2797
2798@node Handling exceptions
2799@subsection Handling exceptions
2800
2801To handle an exception when it occurs in a particular block of code,
2802use @code{#on:do:} like this:
2803
2804@example
2805^[someText add: inputChar beforeIndex: i]
2806    on: ReadOnlyText
2807    do: [:sig | sig return: nil]
2808@end example
2809
2810This code will put a handler for @code{ReadOnlyText} signals on the
2811handler stack while the first block is executing.  If such an exception
2812occurs, and it is not handled by any handlers closer to the point of
2813signalling on the stack (known as "inner handlers"), the exception object
2814will pass itself to the handler block given as the @code{do:} argument.
2815
2816You will almost always want to use this object to handle the exception
2817somehow.  There are six basic handler actions, all sent as messages to
2818the exception object:
2819
2820@table @code
2821@item return:
2822Exit the block that received this @code{#on:do:}, returning the given value.
2823You can also leave out the argument by sending @code{#return}, in which case
2824it will be nil.  If you want this handler to also handle exceptions in
2825whatever value you might provide, you should use @code{#retryUsing:} with a
2826block instead.
2827
2828@item retry
2829Acts sort of like a "goto" by restarting the first block.  Obviously,
2830this can lead to an infinite loop if you don't fix the situation that
2831caused the exception.
2832
2833@code{#retry} is a good way to implement reinvocation upon recovery,
2834because it does not increase the stack height.  For example, this:
2835
2836@example
2837  frobnicate: n [
2838    ^[do some stuff with n]
2839        on: SomeError
2840        do: [:sig | sig return: (self frobnicate: n + 1)]
2841    ]
2842@end example
2843
2844@noindent
2845should be replaced with retry:
2846
2847@example
2848  frobnicate: aNumber [
2849    | n |
2850    n := aNumber.
2851    ^[do some stuff with n]
2852        on: SomeError
2853        do: [:sig | n := 1 + n. sig retry]
2854  ]
2855@end example
2856
2857@item retryUsing:
2858Like @code{#retry}, except that it effectively replaces the original
2859block with the one given as an argument.
2860
2861@item pass
2862If you want to tell the exception to let an outer handler handle it,
2863use @code{#pass} instead of @code{#signal}.  This is just like rethrowing
2864a caught exception in other languages.
2865
2866@item resume:
2867This is the really interesting one.  Instead of unwinding the stack,
2868this will effectively answer the argument from the @code{#signal} send.
2869Code that sends @code{#signal} to resumable exceptions can use this
2870value, or ignore it, and continue executing.  You can also leave out
2871the argument, in which case the @code{#signal} send will answer nil.
2872Exceptions that want to be resumable must register this capability by
2873answering @code{true} from the @code{#isResumable} method, which is
2874checked on every @code{#resume:} send.
2875
2876@item outer
2877This is like @code{#pass}, but if an outer handler uses @code{#resume:},
2878this handler block will be resumed  (and @code{#outer} will answer the
2879argument given to @code{#resume:}) rather than the piece of code that
2880sent @code{#signal} in the first place.
2881@end table
2882
2883None of these methods return to the invoking handler block except for
2884@code{#outer}, and that only in certain cases described for it above.
2885
2886Exceptions provide several more features; see the methods on the classes
2887@code{Signal} and @code{Exception} for the various things you can do
2888with them.  Fortunately, the above methods can do what you want in almost
2889all cases.
2890
2891If you don't use one of these methods or another exception feature to exit
2892your handler, Smalltalk will assume that you meant to @code{sig return:}
2893whatever you answer from your handler block.  We don't recommend relying
2894on this; you should use an explicit @code{sig return:} instead.
2895
2896A quick shortcut to handling multiple exception types is the
2897@code{ExceptionSet}, which allows you to have a single handler for the
2898exceptions of a union of classes:
2899
2900@example
2901^[do some stuff with n]
2902    on: SomeError, ReadOnlyError
2903    do: [:sig | ...]
2904@end example
2905
2906In this code, any @code{SomeError} or @code{ReadOnlyError} signals will
2907be handled by the given handler block.
2908
2909@node When an exception isn't handled
2910@subsection When an exception isn't handled
2911
2912Every exception chooses one of the above handler actions by default when
2913no handler is found, or they all use @code{#pass}.  This is invoked by
2914sending @code{#defaultAction} to the class.
2915
2916One example of a default action is presented above as part of the example
2917of @code{#error:} usage; that default action prints a message, backtrace,
2918and unwinds the stack all the way.
2919
2920The easiest way to choose a default action for your own exception classes
2921is to subclass from an exception class that already chose the right one,
2922as explained in the next section.  For example, some exceptions, such
2923as warnings, resume by default, and thus should be treated as if they
2924will almost always resume.
2925
2926Selecting by superclass is by no means a requirement.  Specializing your
2927@code{Error} subclass to be resumable, or even to resume by default,
2928is perfectly acceptable when it makes sense for your design.
2929
2930@node Creating new exception classes
2931@subsection Creating new exception classes
2932
2933If you want code to be able to handle your signalled exceptions, you will
2934probably want to provide a way to pick those kinds out automatically.
2935The easiest way to do this is to subclass @code{Exception}.
2936
2937First, you should choose an exception class to specialize.  @code{Error}
2938is the best choice for non-resumable exceptions, and @code{Notification}
2939or its subclass @code{Warning} is best for exceptions that should resume
2940with @code{nil} by default.
2941
2942Exceptions are just normal objects; include whatever information you think
2943would be useful to handlers.  Note that there are two textual description
2944fields, a @dfn{description} and a @dfn{message text}.  The description,
2945if provided, should be a more-or-less constant string answered from a
2946override method on @code{#description}, meant to describe all instances
2947of your exception class.  The message text is meant to be provided at
2948the point of signalling, and should be used for any extra information
2949that code might want to provide.  Your signalling code can provide the
2950@code{messageText} by using @code{#signal:} instead of @code{#signal}.
2951This is yet another reason why signalling variants of instance creation
2952messages can be more trouble than they're worth.
2953
2954@node Hooking into the stack unwinding
2955@subsection Hooking into the stack unwinding
2956
2957More often useful than even @code{#on:do:} is @code{#ensure:}, which
2958guarantees that some code is executed when the stack unwinds, whether
2959because of normal execution or because of a signalled exception.
2960
2961Here is an example of use of @code{#ensure:} and a situation where the
2962stack can unwind even without a signal:
2963
2964@example
2965Object subclass: ExecuteWithBreak [
2966  | breakBlock |
2967
2968  break: anObject [
2969    breakBlock value: anObject
2970  ]
2971
2972  valueWithBreak: aBlock [
2973    "Sets up breakBlock before entering the block,
2974     and passes self to the block."
2975    | oldBreakBlock |
2976    oldBreakBlock := breakBlock.
2977    ^[breakBlock := [:arg | ^arg].
2978      aBlock value]
2979        ensure: [breakBlock := oldBreakBlock]
2980  ]
2981]
2982@end example
2983
2984This class provides a way to stop the execution of a block without
2985exiting the whole method as using @code{^} inside a block would do.
2986The use of @code{#ensure:} guarantees (hence the name "ensure") that even
2987if @code{breakBlock} is invoked or an error is handled by unwinding,
2988the old ``break block'' will be restored.
2989
2990The definition of @code{breakBlock} is extremely simply; it is an
2991example of the general unwinding feature of blocks, that you have
2992probably already used:
2993
2994@example
2995       (history includesKey: num)
2996           ifTrue: [ ^self error: 'Duplicate check number' ].
2997@end example
2998
2999You have probably been using @code{#ensure:} without knowing.  For example,
3000@code{File>>#withReadStreamDo:} uses it to ensure that the file is
3001closed when leaving the block.
3002
3003@node Handler stack unwinding caveat
3004@subsection Handler stack unwinding caveat
3005
3006One important difference between Smalltalk and other languages is
3007that when a handler is invoked, the stack is not unwound.
3008The Smalltalk exception system is designed this way because it's rare
3009to write code that could break because of this difference, and the
3010@code{#resume:} feature doesn't make sense if the stack is unwound.
3011It is easy enough to unwind a stack later, and is not so easy to wind
3012it again if done too early.
3013
3014For almost all applications, this will not matter, but it technically
3015changes the semantics significantly so should be kept in mind.  One
3016important case in which it might matter is when using @code{#ensure:}
3017blocks @emph{and} exception handlers.  For comparison, this Smalltalk
3018code:
3019
3020@example
3021| n |
3022n := 42.
3023[[self error: 'error'] ensure: [n := 24]]
3024    on: Error
3025    do: [:sig | n printNl. sig return].
3026n printNl.
3027@end example
3028
3029@noindent
3030will put "42" followed by "24" on the transcript, because the @code{n :=
303124} will not be executed until @code{sig return} is invoked, unwinding
3032the stack.  Similar Java code acts differently:
3033
3034@example
3035int n = 42;
3036try
3037  @{
3038    try @{throw new Exception ("42");@}
3039    finally @{n = 24;@}
3040  @}
3041catch (Exception e)
3042  @{
3043    System.out.println (n);
3044  @}
3045System.out.println (n);
3046@end example
3047
3048@noindent
3049printing "24" twice, because the stack unwinds before executing the
3050catch block.
3051
3052@node Behind the scenes
3053@section Some nice stuff from the Smalltalk innards
3054
3055Just like with everything else, you'd probably end up asking yourself:
3056how's it done?  So here's this chapter, just to wheten your appetite...
3057
3058@menu
3059* Inside Arrays::                    Delving into something old
3060* Two flavors of equality::          Delving into something new
3061* Why is #new there?!?::	     Or, the truth on metaclasses
3062* Performance::			     Hmm...  they told me Smalltalk is slow...
3063@end menu
3064
3065@node Inside Arrays
3066@subsection How Arrays Work
3067Smalltalk provides a very adequate selection of predefined
3068classes from which to choose.  Eventually, however,
3069you will find the need to code a new basic data structure.
3070Because Smalltalk's most fundamental storage allocation
3071facilities are arrays, it is important that you understand
3072how to use them to gain efficient access to this kind of
3073storage.
3074
3075@b{The Array Class.} Our examples have already shown the Array class, and
3076its use is fairly obvious.  For many applications, it will
3077fill all your needs---when you need an array in a new class,
3078you keep an instance variable, allocate a new Array and
3079assign it to the variable, and then send array accesses via
3080the instance variable.
3081
3082This technique even works for string-like objects,
3083although it is wasteful of storage.  An Array object uses a
3084Smalltalk pointer for each slot in the array; its exact size
3085is transparent to the programmer, but you can generally
3086guess that it'll be roughly the word size of your machine.
3087@footnote{For @gst{}, the size of a C @code{long}, which
3088is usually 32 bits.} For storing an array of characters, therefore,
3089an Array works but is inefficient.
3090
3091@b{Arrays at a Lower Level.} So let's step down to a lower level of data
3092structure.  A ByteArray is much like an Array, but each slot holds only
3093an integer from 0 to 255-and each slot uses only a byte of
3094storage.  If you only needed to store small quantities in
3095each array slot, this would therefore be a much more efficient
3096choice than an Array.  As you might guess, this is the
3097type of array which a String uses.
3098
3099Aha!  But when you go back to chapter 9 and look at the
3100Smalltalk hierarchy, you notice that String does not inherit
3101from ByteArray.  To see why, we must delve down yet another
3102level, and arrive at the basic methods for setting up the
3103structure of the instances of a class.
3104
3105When we implemented our NiledArray example, we used
3106@code{<shape: #inherit>}.  The shape is exactly that:
3107the fundamental structure of Smalltalk objects created within a given
3108class.  Let's consider the differences in the next sub-sections.
3109
3110@table @asis
3111@item Nothing
3112The default shape specifies the simplest
3113Smalltalk object.  The object consists only of the storage
3114needed to hold the instance variables.  In C, this would be
3115a simple structure with zero or more scalar fields.@footnote{C
3116requires one or more; zero is allowed in Smalltalk}.
3117
3118@item @code{#pointer}
3119Storage is still allocated for any instance
3120variables, but the objects of the class must be created with a
3121@code{new:} message.
3122The number passed as an argument to @code{new:} causes the new
3123object, in addition to the space for instance variables, to
3124also have that many slots of unnamed (indexed) storage allocated.
3125The analog in C would be to have a dynamically allocated structure
3126with some scalar fields, followed at its end by a array of pointers.
3127
3128@item @code{#byte}
3129The storage allocated as specified by new: is an array of bytes.
3130The analog in C would be a dynamically allocated structure with
3131scalar fields@footnote{This is not always true for other Smalltalk
3132implementations, who don't allow instance variables in variableByteSubclasses
3133and variableWordSubclasses.}, followed by a array of @code{char}.
3134
3135@item @code{#word}
3136The storage allocated as specified by new: is an array of C unsigned longs,
3137which are represented in Smalltalk by Integer objects.  The analog in
3138C would be a dynamically allocated structure with scalar fields, followed
3139by an array of @code{long}.  This kind of subclass is only used in a few
3140places in Smalltalk.
3141
3142@item @code{#character}
3143The storage allocated as specified by new: is an array of characters.
3144The analog in C would be a dynamically allocated structure with
3145scalar fields, followed by a array of @code{char}.
3146@end table
3147
3148There are many more shapes for more specialized usage.  All of them
3149specify the same kind of ``array-like'' behavior, with different
3150data types.
3151
3152How to access this new arrays?  You already know how to access instance
3153variables---by name.  But there doesn't seem to be a name for this new
3154storage.  The way an object accesses it is to send itself
3155array-type messages like @code{at:}, @code{at:put:}, and so forth.
3156
3157The problem is when an object wants to add a new level
3158of interpretation to these messages.  Consider
3159a Dictionary---it is a pointer-holding object
3160but its @code{at:} message is in terms of a key, not an integer
3161index of its storage.  Since it has redefined the @code{at:} message, how
3162does it access its fundamental storage?
3163
3164The answer is that Smalltalk has defined @code{basicAt:} and
3165@code{basicAt:put:}, which will access the basic storage even when
3166the @code{at:} and @code{at:put:} messages have been defined to provide
3167a different abstraction.
3168
3169This can get pretty confusing in the abstract, so let's
3170do an example to show how it's pretty simple in practice.
3171Smalltalk arrays tend to start at 1; let's define an array
3172type whose permissible range is arbitrary.
3173
3174@example
3175   ArrayedCollection subclass: RangedArray [
3176       | offset |
3177       <comment: 'I am an Array whose base is arbitrary'>
3178       RangedArray class >> new: size [
3179           <category: 'instance creation'>
3180           ^self new: size base: 1
3181       ]
3182       RangedArray class >> new: size base: b [
3183           <category: 'instance creation'>
3184           ^(super new: size) init: b
3185       ]
3186
3187       init: b [
3188           <category: 'init'>
3189           offset := (b - 1).   "- 1 because basicAt: works with a 1 base"
3190           ^self
3191      ]
3192      rangeCheck: i [
3193           <category: 'basic'>
3194           (i <= offset) | (i > (offset + self basicSize)) ifTrue: [
3195               'Bad index value: ' printOn: stderr.
3196               i printOn: stderr.
3197               Character nl printOn: stderr.
3198               ^self error: 'illegal index'
3199           ]
3200       ]
3201       at: [
3202           self rangeCheck: i.
3203           ^self basicAt: i - offset
3204       ]
3205       at: i put: v [
3206           self rangeCheck: i.
3207           ^self basicAt: i - offset put: v
3208       ]
3209   ]
3210@end example
3211
3212The code has two parts; an initialization, which simply
3213records what index you wish the array to start with, and the
3214at: messages, which adjust the requested index so that the
3215underlying storage receives its 1-based index instead.
3216We've included a range check; its
3217utility will demonstrate itself in a moment:
3218@example
3219   a := RangedArray new: 10 base: 5.
3220   a at: 5 put: 0
3221   a at: 4 put: 1
3222@end example
3223
3224Since 4 is below our base of 5, a range check error occurs.
3225But this check can catch more than just our own misbehavior!
3226
3227@example
3228   a do: [:x| x printNl]
3229@end example
3230
3231Our do: message handling is broken!  The stack backtrace
3232pretty much tells the story:
3233
3234@example
3235   RangedArray>>#rangeCheck:
3236   RangedArray>>#at:
3237   RangedArray>>#do:
3238@end example
3239
3240Our code received a do: message.  We didn't define one, so
3241we inherited the existing do: handling.  We see that an
3242Integer loop was constructed, that a code block was invoked,
3243and that our own at: code was invoked.  When we range
3244checked, we trapped an illegal index.  Just by coincidence,
3245this version of our range checking code also dumps the
3246index.  We see that do: has assumed that all arrays start at
32471.
3248
3249The immediate fix is obvious; we implement our own do:
3250
3251@example
3252   RangedArray extend [
3253       do: aBlock [
3254           <category: 'basic'>
3255           1 to: (self basicSize) do: [:x|
3256               aBlock value: (self basicAt: x)
3257           ]
3258       ]
3259   ]
3260@end example
3261
3262But the issues start to run deep.  If our parent class
3263believed that it knew enough to assume a starting index of
32641@footnote{Actually, in @gst{} @code{do:} is not the only
3265message assuming that.}, why didn't it also assume that it could
3266call basicAt:?  The answer is that of the two choices, the designer
3267of the parent class chose the one which was less likely to cause
3268trouble; in fact all standard Smalltalk collections do have indices
3269starting at 1, yet not all of them are implemented so
3270that calling basicAt: would work.@footnote{Some of these classes
3271actually redefine @code{do:} for performance reasons, but they
3272would work even if the parent class' implementation of @code{do:}
3273was kept.}
3274
3275Object-oriented methodology says that one object should be
3276entirely opaque to another.  But what sort of privacy should
3277there be between a higher class and its subclasses?  How
3278many assumption can a subclass make about its superclass,
3279and how many can the superclass make before it begins
3280infringing on the sovereignty of its subclasses?
3281
3282Alas, there are rarely easy answers, and this is just an example.
3283For this particular problem, there is an easy solution.  When the
3284storage need not be accessed with peak efficiency, you can use the
3285existing array classes.  When every access counts, having the
3286storage be an integral part of your own object allows for
3287the quickest access---but remember that when you move into this
3288area, inheritance and polymorphism become trickier, as
3289each level must coordinate its use of the underlying array
3290with other levels.
3291
3292
3293@node Two flavors of equality
3294@subsection Two flavors of equality
3295As first seen in chapter two, Smalltalk keys its dictionary
3296with things like @i{#word}, whereas we generally use
3297@i{'word'}.  The former, as it turns out, is from class Symbol.
3298The latter is from class String.  What's the real difference
3299between a Symbol and a String?  To answer the question, we'll
3300use an analogy from C.
3301
3302In C, if you have a function for comparing strings, you
3303might try to write it:
3304@example
3305   streq(char *p, char *q)
3306   @{
3307       return (p == q);
3308   @}
3309@end example
3310
3311But clearly this is wrong!  The reason is that you can have
3312two copies of a string, each with the same contents but each
3313at its own address.  A correct string compare must walk its
3314way through the strings and compare each element.
3315
3316In Smalltalk, exactly the same issue exists, although
3317the details of manipulating storage addresses are hidden.
3318If we have two Smalltalk strings, both with the same contents,
3319we don't necessarily know if they're at the same
3320storage address.  In Smalltalk terms, we don't know if
3321they're the same object.
3322
3323The Smalltalk dictionary is searched frequently.  To
3324speed the search, it would be nice to not have to compare
3325the characters of each element, but only compare the address
3326itself.  To do this, you need to have a guarantee that all
3327strings with the same contents are the same object.  The
3328String class, created like:
3329@example
3330   y := 'Hello'
3331@end example
3332@noindent
3333does not satisfy this.  Each time you execute this line, you
3334may well get a new object.  But a very similar class, Symbol,
3335will always return the same object:
3336@example
3337   y := #Hello
3338@end example
3339
3340In general, you can use strings for almost all your tasks.
3341If you ever get into a performance-critical function which
3342looks up strings, you can switch to Symbol.  It takes longer
3343to create a Symbol, and the memory for a Symbol is never
3344freed (since the class has to keep tabs on it indefinitely
3345to guarantee it continues to return the same object).  You
3346can use it, but use it with care.
3347
3348This tutorial has generally used the strcmp()-ish kind of
3349checks for equality.  If you ever need to ask the question
3350``is this the same object?'', you use the @code{==} operator
3351instead of @code{=}:
3352@example
3353   x := y := 'Hello'
3354   (x = y) printNl
3355   (x == y) printNl
3356   y := 'Hel', 'lo'
3357   (x = y) printNl
3358   (x == y) printNl
3359   x := #Hello
3360   y := #Hello
3361   (x = y) printNl
3362   (x == y) printNl
3363@end example
3364
3365Using C terms, @code{=} compares contents like @code{strcmp()}.
3366@code{==} compares storage addresses, like a pointer comparison.
3367
3368@node Why is #new there?!?
3369@subsection The truth about metaclasses
3370
3371Everybody, sooner or later, looks for the implementation of the
3372@code{#new} method in Object class.  To their surprise, they
3373don't find it; if they're really smart, they search for implementors
3374of #new in the image and they find out it is implemented by
3375@code{Behavior}... which turns out to be a subclass of Object!  The
3376truth starts showing to their eyes about that sentence that everybody
3377says but few people understand: ``classes are objects''.
3378
3379Huh? Classes are objects?!? Let me explain.
3380
3381@ifinfo
3382Open up an image; then type the text following the
3383@code{st>} prompt.
3384@end ifinfo
3385@ifhtml
3386Open up an image; then type the text following the
3387@code{st>} prompt.
3388@end ifhtml
3389@iftex
3390Open up an image; then type the text printed in
3391@t{mono-spaced} font.
3392@end iftex
3393
3394@display
3395    st> @t{Set superclass!}
3396    HashedCollection
3397
3398    st> @t{HashedCollection superclass!}
3399    Collection
3400
3401    st> @t{Collection superclass!}
3402    Object
3403
3404    st> @t{Object superclass!}
3405    nil
3406@end display
3407
3408Nothing new for now.  Let's try something else:
3409
3410@display
3411    st> @t{#(1 2 3) class!}
3412    Array
3413
3414    st> @t{'123' class!}
3415    String
3416
3417    st> @t{Set class!}
3418    Set class
3419
3420    st> @t{Set class class!}
3421    Metaclass
3422@end display
3423
3424You get it, that strange @code{Set class} thing is something
3425called ``a meta-class''... let's go on:
3426
3427@display
3428    st> @t{^Set class superclass!}
3429    Collection class
3430
3431    st> @t{^Collection class superclass!}
3432    Object class
3433@end display
3434
3435You see, there is a sort of `parallel' hierarchy between classes
3436and metaclasses.  When you create a class, Smalltalk creates a
3437metaclass; and just like a class describes how methods for its
3438instances work, a metaclass describes how class methods for that
3439same class work.
3440
3441@code{Set} is an instance of the metaclass, so when you invoke
3442the @code{#new} class method, you can also say you are invoking
3443an instance method implemented by @code{Set class}.  Simply put,
3444class methods are a lie: they're simply instance methods that
3445are understood by instances of metaclasses.
3446
3447Now you would expect that @code{Object class superclass} answers
3448@code{nil class}, that is @code{UndefinedObject}.  Yet you saw that
3449@code{#new} is not implemented there... let's try it:
3450
3451@display
3452    st> @t{^Object class superclass!}
3453    Class
3454@end display
3455
3456Uh?!? Try to read it aloud: the @code{Object class} class inherits
3457from the @code{Class} class.  @code{Class} is the abstract superclass
3458of all metaclasses, and provides the logic that allows you to create
3459classes in the image.  But it is not the termination point:
3460
3461@display
3462    st> @t{^Class superclass!}
3463    ClassDescription
3464
3465    st> @t{^ClassDescription superclass!}
3466    Behavior
3467
3468    st> @t{^Behavior superclass!}
3469    Object
3470@end display
3471
3472Class is a subclass of other classes.  @code{ClassDescription} is
3473abstract; @code{Behavior} is concrete but lacks the methods
3474and state that allow classes to have named instance variables,
3475class comments and more.  Its instances are called
3476@emph{light-weight} classes because they don't have separate
3477metaclasses, instead they all share @code{Behavior} itself as
3478their metaclass.
3479
3480Evaluating @code{Behavior superclass} we have worked our way up to
3481class Object again:  Object is the superclass of all instances as well
3482as all metaclasses.  This complicated system is extremely powerful,
3483and allows you to do very interesting things that you probably did
3484without thinking about it---for example, using methods such as
3485@code{#error:} or @code{#shouldNotImplement} in class methods.
3486
3487Now, one final question and one final step: what are metaclasses
3488instances of?  The question makes sense: if everything has a class,
3489should not metaclasses have one?
3490
3491Evaluate the following:
3492
3493@display
3494    st> @t{meta := Set class}
3495    st> @t{0 to: 4 do: [ :i |}
3496    st> @t{    i timesRepeat: [ Transcript space ]}
3497    st> @t{    meta printNl}
3498    st> @t{    meta := meta class}
3499    st> @t{]}
3500    Set class
3501     Metaclass
3502      Metaclass class
3503       Metaclass
3504        Metaclass class
3505    0
3506@end display
3507
3508If you send @code{#class} repeatedly, it seems that you end up
3509in a loop made of class @code{Metaclass}@footnote{Which turns
3510out to be another subclass of @code{ClassDescription}.} and its
3511own metaclass, @code{Metaclass class}.  It looks like class
3512Metaclass is @i{an instance of an instance of itself}.
3513
3514To understand the role of @code{Metaclass}, it can be useful
3515to know that the class creation is implemented there.
3516Think about it.
3517
3518@itemize @bullet
3519@item
3520@code{Random class} implements creation and
3521initialization of its instances' random number seed;
3522analogously, @code{Metaclass class} implements creation and
3523initialization of its instances, which are metaclasses.
3524
3525@item
3526And @code{Metaclass} implements creation and initialization of
3527its instances, which are classes (subclasses of @code{Class}).
3528@end itemize
3529
3530The circle is closed.  In the end, this mechanism implements a
3531clean, elegant and (with some contemplation) understandable
3532facility for self-definition of classes.  In other words, it
3533is what allows classes to talk about themselves, posing the
3534foundation for the creation of browsers.
3535
3536
3537@node Performance
3538@subsection The truth of Smalltalk performance
3539
3540Everybody says Smalltalk is slow, yet this is not completely true for
3541at least three reasons.  First, most of the time in graphical applications
3542is spent waiting for the user to ``do something'', and most of the time
3543in scripting applications (which @gst{} is particularly well
3544versed in) is spent in disk I/O; implementing a travelling salesman
3545problem in Smalltalk would indeed be slow, but for most real applications
3546you can indeed exchange performance for Smalltalk's power and development
3547speed.
3548
3549Second, Smalltalk's automatic memory management is faster than C's manual
3550one.  Most C programs are sped up if you relink them with one of the
3551garbage collecting systems available for C or C++.
3552
3553Third, even though very few Smalltalk virtual machines are as optimized as,
3554say, the Self environment (which reaches half the speed of optimized C!),
3555they do perform some optimizations on Smalltalk code which make them run
3556many times faster than a naive bytecode interpreter.  Peter Deutsch, who
3557among other things invented the idea of a just-in-time compiler like those
3558you are used to seeing for Java@footnote{And like the one that @gst{}
3559includes as an experimental feature.}, once observed that implementing a
3560language like Smalltalk efficiently requires the implementor to cheat...
3561but that's okay as long as you don't get caught.  That is, as long as you
3562don't break the language semantics.  Let's look at some of these optimizations.
3563
3564For certain frequently used 'special selectors', the compiler emits a
3565send-special-selector bytecode instead of a send-message bytecode.
3566Special selectors have one of three behaviors:
3567
3568@itemize @bullet
3569@item
3570A few selectors are assigned to special bytecode solely in order to
3571save space.  This is the case for @code{#do:} for example.
3572
3573@item
3574Three selectors (@code{#at:}, @code{#at:put:}, @code{#size}) are
3575assigned to special bytecodes because they are subject to a special
3576caching optimization.  These selectors often result in calling a
3577virtual machine primitive, so @gst{} remembers which primitve
3578was last called as the result of sending them.  If we send @code{#at:}
3579100 times for the same class, the last 99 sends are directly mapped
3580to the primitive, skipping the method lookup phase.
3581
3582@item
3583For some pairs of receiver classes and special selectors, the
3584interpreter never looks up the method in the class; instead it swiftly
3585executes the same code which is tied to a particular primitive.  Of
3586course a special selector whose receiver or argument is not of the
3587right class to make a no-lookup pair is looked up normally.
3588@end itemize
3589
3590No-lookup methods do contain a primitive number specification,
3591@code{<primitive: xx>}, but it is used only when the method is
3592reached through a @code{#perform:@dots{}} message send.  Since
3593the method is not normally looked up, deleting the primitive name
3594specification cannot in general prevent this primitive from running.
3595No-lookup pairs are listed below:
3596
3597@multitable @columnfractions .35 .1 .55
3598@item @code{Integer}/@code{Integer} @*
3599@code{Float}/@code{Integer} @*
3600@code{Float}/@code{Float}
3601@tab @ @* for
3602@tab @ @* @code{+ - * =  ~=  >  <  >=  <=}
3603
3604@item @code{Integer}/@code{Integer}
3605@tab for
3606@tab @code{//  \\     bitOr:  bitShift:  bitAnd:}
3607
3608@item Any pair of objects
3609@tab for
3610@tab @code{==  isNil  notNil  class}
3611
3612@item BlockClosure
3613@tab for
3614@tab @code{value value: blockCopy:}@footnote{You
3615won't ever send this message in Smalltalk programs.  The compiler uses it when
3616compiling blocks.}
3617@end multitable
3618
3619Other messages are open coded by the compiler.  That is, there are
3620no message sends for these messages---if the compiler sees blocks
3621without temporaries and with the correct number of arguments at the
3622right places, the compiler unwinds them using jump bytecodes,
3623producing very efficient code.  These are:
3624
3625@example
3626  to:by:do: if the second argument is an integer literal
3627  to:do:
3628  timesRepeat:
3629  and:, or:
3630  ifTrue:ifFalse:, ifFalse:ifTrue:, ifTrue:, ifFalse:
3631  whileTrue:, whileFalse:
3632@end example
3633
3634Other minor optimizations are done.  Some are done by a peephole optimizer
3635which is ran on the compiled bytecodes.  Or, for example, when @gst{} pushes a
3636boolean value on the stack, it automatically checks whether the following
3637bytecode is a jump (which is a common pattern resulting from most of the
3638open-coded messages above) and combines the execution of the two bytecodes.
3639All these snippets can be optimized this way:
3640
3641@example
3642  1 to: 5 do: [ :i | @dots{} ]
3643  a < b and: [ @dots{} ]
3644  myObject isNil ifTrue: [ @dots{} ]
3645@end example
3646
3647That's all.  If you want to know more, look at the virtual machine's source
3648code in @file{libgst/interp-bc.inl} and at the compiler in
3649@file{libgst/comp.c}.
3650
3651@node And now
3652@section Some final words
3653
3654The question is always how far to go in one document.
3655At this point, you know how to create classes.  You know how
3656to use inheritance, polymorphism, and the basic storage management
3657mechanisms of Smalltalk.  You've also seen a sampling
3658of Smalltalk's powerful classes.  The rest of this
3659chapter simply points out areas for further study; perhaps a
3660newer version of this document might cover these in further
3661chapters.
3662
3663@table @b
3664
3665@item Viewing the Smalltalk Source Code
3666Lots of experience can be gained by looking at the source code
3667for system methods; all of them are visible: data structure classes,
3668the innards of the magic that makes classes be themselves objects and
3669have a class, a compiler written in Smalltalk itself, the classes
3670that implement the Smalltalk GUI and those that wrap sockets.
3671
3672@item Other Ways to Collect Objects
3673We've seen Array, ByteArray, Dictionary, Set, and the
3674various streams.  You'll want to look at the Bag,
3675OrderedCollection, and SortedCollection classes.  For special purposes,
3676you'll want to examine the CObject and CType hierarchies.
3677
3678@item Flow of Control
3679@gst{} has support for non-preemptive multiple threads of
3680execution.  The state is embodied in a Process class object;
3681you'll also want to look at the Semaphore and ProcessorScheduler
3682class.
3683
3684@item Smalltalk Virtual Machine
3685@gst{} is implemented as a virtual instruction
3686set.  By invoking @gst{} with the @code{-D} option, you can
3687view the byte opcodes which are generated as files on the
3688command line are loaded.  Similarly, running @gst{}
3689with @code{-E} will trace the execution of instructions in your
3690methods.
3691
3692You can look at the @gst{} source to gain more information
3693on the instruction set.  With a few modifications, it is based
3694on the set described in the canonical book from two of the
3695original designers of Smalltalk: @i{Smalltalk-80: The Language
3696and its Implementation}, by Adele Goldberg and David Robson.
3697
3698@item Where to get Help
3699The Usenet @t{comp.lang.smalltalk} newsgroup is read by many people
3700with a great deal of Smalltalk experience.  There are several
3701commercial Smalltalk implementations; you can buy support for
3702these, though it isn't cheap.  For the @gst{} system in
3703particular, you can try the mailing list at:
3704@example
3705   @mailto{help-smalltalk@@gnu.org}
3706@end example
3707
3708No guarantees, but the subscribers will surely do their best!
3709@end table
3710
3711
3712@node The syntax
3713@section A Simple Overview of Smalltalk Syntax
3714
3715Smalltalk's power comes from its treatment of objects.
3716In this document, we've mostly avoided the issue of syntax
3717by using strictly parenthesized expressions as needed.  When
3718this leads to code which is hard to read due to the density
3719of parentheses, a knowledge of Smalltalk's syntax can let
3720you simplify expressions.  In general, if it was hard for
3721you to tell how an expression would parse, it will be hard
3722for the next person, too.
3723
3724The following presentation presents the grammar a couple
3725of related elements at a time.  We use an EBNF style of
3726grammar.  The form:
3727@example
3728   [ @dots{}  ]
3729@end example
3730
3731@noindent
3732means that ``@dots{}'' can occur zero or one times.
3733
3734@example
3735   [ @dots{}  ]*
3736@end example
3737
3738@noindent
3739means zero or more;
3740
3741@example
3742   [ @dots{}  ]+
3743@end example
3744
3745@noindent
3746means one or more.
3747
3748@example
3749   @dots{}  | @dots{}  [ | @dots{}  ]*
3750@end example
3751
3752@noindent
3753means that one of the variants must be chosen.  Characters
3754in double quotes refer to the literal characters.  Most elements
3755may be separated by white space; where this is not legal, the
3756elements are presented without white space
3757between them.
3758
3759@table @b
3760
3761@item @t{methods: ``!'' id [``class''] ``methodsFor:'' string ``!'' [method ``!'']+ ``!''}
3762Methods are introduced by first naming a class (the id element),
3763specifying ``class'' if you're adding class methods
3764instead of instance methods, and sending a string argument
3765to the @code{methodsFor:} message.  Each method is terminated with
3766an ``!''; two bangs in a row (with a space in the middle)
3767signify the end of the new methods.
3768
3769@item @t{method: message [pragma] [temps] exprs}
3770@itemx @t{message: id | binsel id | [keysel id]+}
3771@itemx @t{pragma: ``<'' keymsg ``>''}
3772@itemx @t{temps: ``|'' [id]* ``|''}
3773A method definition starts out with a kind of template.  The
3774message to be handled is specified with the message names
3775spelled out and identifiers in the place of arguments.  A
3776special kind of definition is the pragma; it has not been
3777covered in this tutorial and it provides a way to mark a
3778method specially as well as the interface to the underlying
3779Smalltalk virtual machine.  temps is the declaration
3780of local variables.  Finally, exprs (covered soon) is
3781the actual code for implementing the method.
3782
3783@item @t{unit: id | literal | block | arrayconstructor | ``('' expr ``)''}
3784@itemx @t{unaryexpr: unit [ id ]+}
3785@itemx @t{primary: unit | unaryexpr}
3786These are the ``building blocks'' of Smalltalk expressions.  A
3787unit represents a single Smalltalk value, with the highest
3788syntactic precedence.  A unaryexpr is simply a unit which
3789receives a number of unary messages.  A unaryexpr has the
3790next highest precedence.  A primary is simply a convenient
3791left-hand-side name for one of the above.
3792
3793@item @t{exprs: [expr ``.'']* [[``^''] expr]}
3794@itemx @t{expr: [id ``:='']* expr2} @*
3795@itemx @t{expr2: primary | msgexpr [ ``;'' cascade ]*}
3796A sequence of expressions is separated by dots and can end
3797with a returned value (@code{^}).  There can be leading assignments;
3798unlike C, assignments apply only to simple variable names.  An
3799expression is either a primary (with highest precedence) or
3800a more complex message.  cascade does not apply to primary
3801constructions, as they are too simple to require the construct.
3802Since all primary construct are unary, you can just add more unary messages:
3803@example
3804   1234 printNl printNl printNl
3805@end example
3806
3807@item @t{msgexpr: unaryexpr | binexpr | keyexpr}
3808A complex message is either a unary message (which we have
3809already covered), a binary message (@code{+}, @code{-}, and so forth),
3810or a keyword message (@code{at:}, @code{new:}, @dots{}) Unary has the
3811highest precedence, followed by binary, and keyword messages
3812have the lowest precedence.  Examine the two versions of the
3813following messages.  The second have had parentheses added
3814to show the default precedence.
3815@example
3816   myvar at: 2 + 3 put: 4
3817   mybool ifTrue: [ ^ 2 / 4 roundup ]
3818
3819   (myvar at: (2 + 3) put: (4))
3820   (mybool ifTrue: ([ ^ (2 / (4 roundup)) ]))
3821@end example
3822
3823@item @t{cascade: id | binmsg | keymsg}
3824A cascade is used to direct further messages to the same
3825object which was last used.  The three types of messages (
3826id is how you send a unary message) can thus be sent.
3827
3828@item @t{binexpr: primary binmsg [ binmsg ]*}
3829@itemx @t{binmsg: binsel primary}
3830@itemx @t{binsel: binchar[binchar]}
3831A binary message is sent to an object, which primary has
3832identified.  Each binary message is a binary selector, constructed
3833from one or two characters, and an argument which
3834is also provided by a primary.
3835@example
3836   1 + 2 - 3 / 4
3837@end example
3838
3839@noindent
3840which parses as:
3841@example
3842   (((1 + 2) - 3) / 4)
3843@end example
3844
3845@item @t{keyexpr: keyexpr2 keymsg}
3846@itemx @t{keyexpr2: binexpr | primary}
3847@itemx @t{keymsg: [keysel keyw2]+}
3848@itemx @t{keysel: id``:''}
3849Keyword expressions are much like binary expressions, except
3850that the selectors are made up of identifiers with a colon
3851appended.  Where the arguments to a binary function can only
3852be from primary, the arguments to a keyword can be binary
3853expressions or primary ones.  This is because keywords have
3854the lowest precedence.
3855
3856@item @t{block: ``['' [[``:'' id]* ``|'' ] [temps] exprs ``]''}
3857A code block is square brackets around a collection of
3858Smalltalk expressions.  The leading ``: id'' part is for block
3859arguments.  Note that it is possible for a block to have
3860temporary variables of its own.
3861
3862@item @t{arrayconstructor: ``@{'' exprs ``@}''}
3863Not covered in this tutorial, this syntax allows to create
3864arrays whose values are not literals, but are instead evaluated
3865at run-time.  Compare @code{#(a b)}, which results in an Array
3866of two symbols @code{#a} and @code{#b}, to @code{@{a. b+c@}} which
3867results in an Array whose two elements are the contents of variable
3868@code{a} and the result of summing @code{c} to @code{b}.
3869
3870@item @t{literal: number | string | charconst | symconst | arrayconst | binding | eval}
3871@itemx @t{arrayconst: ``#'' array | ``#'' bytearray}
3872@itemx @t{bytearray: ``['' [number]* ``]''}
3873@itemx @t{array: ``('' [literal | array | bytearray | arraysym | ]* ``)''}
3874@itemx @t{number: [[dig]+ ``r''] [``-''] [alphanum]+ [``.'' [alphanum]+] [exp [``-''][dig]+].}
3875@itemx @t{string: "'"[char]*"'"}
3876@itemx @t{charconst: ``$''char}
3877@itemx @t{symconst: ``#''symbol | ``#''string }
3878@itemx @t{arraysym: [id | ``:'']*}
3879@itemx @t{exp: ``d'' | ``e'' | ``q'' | ``s''}
3880We have already shown the use of many of these constants.
3881Although not covered in this tutorial, numbers can have a base
3882specified at their front, and a trailing scientific notation.
3883We have seen examples of character, string, and symbol constants.
3884Array constants are simple enough; they would look like:
3885@example
3886   a := #(1 2 'Hi' $x #Hello 4 16r3F)
3887@end example
3888
3889There are also ByteArray constants, whose elements are constrained
3890to be integers between 0 and 255; they would look like:
3891@example
3892   a := #[1 2 34 16r8F 26r3H 253]
3893@end example
3894
3895Finally, there are three types of floating-point constants with
3896varying precision (the one with the @code{e} being the less
3897precise, followed by @code{d} and @code{q}), and scaled-decimal
3898constants for a special class which does exact computations but
3899truncates comparisons to a given number of decimals.  For example,
3900@code{1.23s4} means ``the value @code{1.23}, with four significant
3901decimal digits''.
3902
3903@item @t{binding: ``#@{'' [id ``.'']* id ``@}''}
3904This syntax has not been used in the tutorial, and results in an
3905Association literal (known as a @dfn{variable binding}) tied to
3906the class that is named between braces.  For example,
3907@code{#@{Class@} value} is the same as @code{Class}.  The
3908dot syntax is required for supporting namespaces:
3909@code{#@{Smalltalk.Class@}} is the same as
3910@code{Smalltalk associationAt: #Class}, but is resolved
3911at compile-time rather than at run-time.
3912
3913@item @t{symbol: id | binsel | keysel[keysel]*}
3914Symbols are mostly used to represent the names of methods.
3915Thus, they can hold simple identifiers, binary selectors,
3916and keyword selectors:
3917@example
3918   #hello
3919   #+
3920   #at:put:
3921@end example
3922
3923@item @t{eval: ``##('' [temps] exprs ``)''}
3924This syntax also has not been used in the tutorial, and results
3925in evaluating an arbitrarily complex expression at compile-time,
3926and substituting the result: for example @code{##(Object allInstances
3927size)} is the number of instances of @code{Object} held in the
3928image @emph{at the time the method is compiled}.
3929
3930@item @t{id: letter[alphanum]*}
3931@itemx @t{binchar: ``+'' | ``-'' | ``*'' | ``/'' | ``~'' | ``|'' | ``,'' |}
3932@itemx @t{``<'' | ``>'' | ``='' | ``&'' | ``@@'' | ``?'' | ``\'' | ``%''}
3933@itemx @t{alphanum: dig | letter}
3934@itemx @t{letter: ``A''..``Z''}
3935@itemx @t{dig: ``0''..``9''}
3936These are the categories of characters and how they are combined
3937at the most basic level.  binchar simply lists the
3938characters which can be combined to name a binary message.
3939
3940@end table
3941