Previous: , Up: Code blocks (I)  


6.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.

Checking extend [
    | history |

This is the same syntax as the last time we defined a checking account, except that we start with extend (since the class is already there). Then, the two instance variables we had defined remain, and we add a new history variable; the old methods 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:

       init [
           <category: 'initialization'>
           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.

   writeCheck: amount [
       <category: 'spending'>
       | 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.31 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.

   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.

    printChecks [
        history keysAndValuesDo: [ :key :value |
            key print.
            ' - ' print.
            value printNl.
        ]
    ]
]

We still see a code block object being passed to the dictionary, but :key :value | is something new. A code block can optionally receive arguments. In this case, the two arguments represent a key/value pair. 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.

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 that in principle there is no relationship between the code block and the dictionary you passed it to. The dictionary just invokes the passed code block with a key/value pair when processing a keysAndValuesDo: message. But the same two-parameter code block can be passed to any message that wishes to evaluate it (and passes the exact number of parameters to it). 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.


Footnotes

(31)

You might start to wonder what one would do if you wished to associate two pieces of information under one key. Say, the value and who the check was written to. There are several ways; the best would probably be to create a new, custom object which contained this information, and then store this object under the check number key in the dictionary. It would also be valid (though probably overkill) to store a dictionary as the value—and then store as many pieces of information as you’d like under each slot!


Previous: , Up: Code blocks (I)