5.6 Code blocks
The Account/Saving/Checking example from the last chapter
has several deficiencies. It has no record of the
checks and their values. Worse, it allows you to write a
check when there are no more checks--the Integer value for
the number of checks will just calmly go negative! To fix
these problems we will need to introduce more sophisticated
control structures.
5.6.1 Conditions and decision making
Let's first add some code to keep you from writing too
many checks. We will simply update our current method for
the Checking class; if you have entered the methods from the
previous chapters, the old definition will be overridden by
this new one.
| !Checking methodsFor: 'spending'!
writeCheck: amount
| num |
(checksleft < 1)
ifTrue: [ ^self error: 'Out of checks' ].
num := checknum.
checknum := checknum + 1.
checksleft := checksleft - 1.
self spend: amount
^ num
! !
|
The two new lines are:
| (checksleft < 1)
ifTrue: [ ^self error: 'Out of checks' ].
|
At first glance, this appears to be a completely new structure.
But, look again! The only new construct is the square
brackets.
The first line is a simple boolean expression. checksleft
is our integer, as initialized by our Checking class.
It is sent the message < , and the argument 1. The current
number bound to checksleft compares itself against 1, and
returns a boolean object telling whether it is less than 1.
Now this boolean, which is either true or false, is sent the
message ifTrue: , with an argument which is called a code
block. A code block is an object, just like any other. But
instead of holding a number, or a Set, it holds executable
statements. So what does a boolean do with a code block which
is an argument to a ifTrue: message? It depends on which boolean!
If the object is the true object, it executes the code
block it has been handed. If it is the false object, it
returns without executing the code block. So the traditional
conditional construct has been replaced in
Smalltalk with boolean objects which execute the indicated
code block or not, depending on their truth-value.
(25)
In the case of our example, the actual code within the
block sends an error message to the current object. error:
is handled by the parent class Object, and will pop up an
appropriate complaint when the user tries to write too many
checks. In general, the way you handle a fatal error in
Smalltalk is to send an error message to yourself (through
the self pseudo-variable), and let the error handling
mechanisms inherited from the Object class take over.
As you might guess, there is also an ifFalse: message
which booleans accept. It works exactly like ifTrue: ,
except that the logic has been reversed; a boolean false
will execute the code block, and a boolean true will not.
You should take a little time to play with this method
of representing conditionals. You can run your checkbook,
but can also invoke the conditional functions directly:
| true ifTrue: [ 'Hello, world!' printNl ] !
false ifTrue: [ 'Hello, world!' printNl ] !
true ifFalse: [ 'Hello, world!' printNl ] !
false ifFalse: [ 'Hello, world!' printNl ] !
|
5.6.2 Iteration and collections
Now that we have some sanity checking in place, it
remains for us to keep a log of the checks we write. We
will do so by adding a Dictionary object to our Checking
class, logging checks into it, and providing some messages
for querying our check-writing history. But this enhancement
brings up a very interesting question--when we change
the "shape" of an object (in this case, by adding our dictionary
as a new instance variable to the Checking class),
what happens to the existing class, and its objects?
The answer is that the old objects are mutated to keep their
new shape, and all methods are recompiled so that they work
with the new shape. New objects will have exactly the same shape
as old ones, but old objects might happen to be initialized
incorrectly (since the newly added variables will be simply
put to nil). As this can lead to very puzzling behavior, it is
usually best to eradicate all of the old objects, and then
implement your changes.
If this were more than a toy object
accounting system, this would probably entail saving the
objects off, converting to the new class, and reading the
objects back into the new format. For now, we'll just
ignore what's currently there, and define our latest Checking
class.
| Account subclass: #Checking
instanceVariableNames: 'checknum checksleft history'
classVariableNames: ''
poolDictionaries: ''
category: nil !
|
This is the same syntax as the last time we defined a
checking account, except that we have three instance variables:
the checknum and checksleft which have always been
there, and our new history variable; since we have removed no
instance variables, the old method will be recompiled without
errors. We must now feed in our definitions for each of the
messages our object can handle, since we are basically
defining a new class under an old name.
With our new Checking instance variable, we are all set
to start recording our checking history. Our first change
will be in the handling of the init message:
| !Checking methodsFor: 'initialization'!
init
checksleft := 0.
history := Dictionary new.
^ super init
! !
|
This provides us with a Dictionary, and hooks it to our new
history variable.
Our next method records each check as it's written.
The method is a little more involved, as we've added some
more sanity checks to the writing of checks.
| !Checking methodsFor: 'spending'!
writeCheck: amount
| num |
"Sanity check that we have checks left in our checkbook"
(checksleft < 1)
ifTrue: [ ^self error: 'Out of checks' ].
"Make sure we've never used this check number before"
num := checknum.
(history includesKey: num)
ifTrue: [ ^self error: 'Duplicate check number' ].
"Record the check number and amount"
history at: num put: amount.
"Update our next checknumber, checks left, and balance"
checknum := checknum + 1.
checksleft := checksleft - 1.
self spend: amount.
^ num
! !
|
We have added three things to our latest version of
writeCheck: . First, since our routine has become somewhat
involved, we have added comments. In Smalltalk, single
quotes are used for strings; double quotes enclose comments.
We have added comments before each section of code.
Second, we have added a sanity check on the check number
we propose to use. Dictionary objects respond to the
includesKey: message with a boolean, depending on whether
something is currently stored under the given key in the
dictionary. If the check number is already used, the error:
message is sent to our object, aborting the operation.
Finally, we add a new entry to the dictionary. We have
already seen the at:put: message (often found written
as #at:put: , with a sharp in front of it) at the start of
this tutorial. Our use here simply associates a check number with
an amount of money spent.(26) With this, we now have a working Checking
class, with reasonable sanity checks and per-check information.
Let us finish the chapter by enhancing our ability to
get access to all this information. We will start with some
simple print-out functions.
| !Checking methodsFor: 'printing'!
printOn: stream
super printOn: stream.
', checks left: ' printOn: stream.
checksleft printOn: stream.
', checks written: ' printOn: stream.
(history size) printOn: stream.
!
check: num
| c |
c := history
at: num
ifAbsent: [ ^self error: 'No such check #' ].
^c
! !
|
There should be very few surprises here. We format and
print our information, while letting our parent classes handle
their own share of the work. When looking up a check
number, we once again take advantage of the fact that blocks
of executable statements are an object; in this case, we are
using the at:ifAbsent: message supported by the
Dictionary class. As you can probably anticipate, if the
requested key value is not found in the
dictionary, the code block is executed. This allows us to
customize our error handling, as the generic error would only
tell the user "key not found".
While we can look up a check if we know its number, we
have not yet written a way to "riffle through" our collection
of checks. The following function loops over the
checks, printing them out one per line. Because there is
currently only a single numeric value under each key, this
might seem wasteful. But we have already considered storing
multiple values under each check number, so it is best to
leave some room for each item. And, of course, because we
are simply sending a printing message to an object, we will
not have to come back and re-write this code so long as the
object in the dictionary honors our printNl /printOn: messages
sages.
| !Checking methodsFor: 'printing'!
printChecks
history associationsDo: [ :assoc |
(assoc key) print.
' - ' print.
(assoc value) printNl.
]
! !
|
We still see a code block object being passed to the
dictionary, but :assoc | is something new. A code
block can optionally receive arguments. In this case, the
argument is the key/value pair, known in Smalltalk as an
Association. This is the way that a dictionary object
stores its key/value pairs internally. In fact, when you
sent an at:put: message to a dictionary object, the first thing it
does is pack them into a new object from the Association class.
If you only wanted the value portion, you could call
history with a do: message instead; if you only wanted the
key portion, you could call history with a keysDo: message instead.
Our code merely uses the key and value messages to
ask the association for the two values. We then invoke our
printing interface upon them. We don't want a newline until the
end, so the print message is used instead. It is pretty
much the same as printNl , since both
implicitly use Transcript , except it doesn't add a newline.
It is important that you be clear on the relationship
between an Association and the argument to a code block. In
this example, we passed a associationsDo: message to a
dictionary. A dictionary invokes the passed code block with an
Association when processing an associationsDo: message. But
code blocks can receive any type of argument: the type is
determined by the code which invokes the code block; Dictionary's
associationDo: method, in this case. In the next chapter
we'll see more on how code blocks are used; we'll also look at how
you can invoke code blocks in your own code.
|