5.4 Creating a new class of objects
With the basic techniques presented in the preceding
chapters, we're ready do our first real Smalltalk program.
In this chapter we will construct three new types of objects
(known as classes), using the Smalltalk technique of
inheritance to tie the classes together, create new objects
belonging to these classes (known as creating instances of
the class), and send messages to these objects.
We'll exercise all this by implementing a toy home-finance
accounting system. We will keep track of our overall
cash, and will have special handling for our checking
and savings accounts. From this point on, we will be defining
classes which will be used in future chapters. Since
you will probably not be running this whole tutorial in one
Smalltalk session, it would be nice to save off the state of
Smalltalk and resume it without having to retype all the
previous examples. To save the current state of GNU
Smalltalk, type:
| Smalltalk snapshot: 'myimage.im' !
|
and from your shell, to later restart Smalltalk from this
"snapshot":
Such a snapshot currently takes a little less than 700K bytes,
and contains all variables, classes, and definitions you
have added.
5.4.1 Creating a new class
Guess how you create a new class? This should be getting
monotonous by now--by sending a message to an object.
The way we create our first "custom" class is by sending the
following message:
| Object subclass: #Account
instanceVariableNames: 'balance'
classVariableNames: ''
poolDictionaries: ''
category: nil !
|
Quite a mouthful, isn't it? Most people end up customizing
their editor to pop this up at a push of a button. But
conceptually, it isn't really that bad. The Smalltalk variable
Object is bound to the grand-daddy of all classes on the
system. What we're doing here is telling the Object class
that we want to add to it a subclass known as Account.
The other parts of the message can be ignored, but
instanceVariableNames: 'balance' tells it that each object
in this subclass will have a hidden variable named
balance . (20)
5.4.2 Documenting the class
The next step is to associate a description with the
class. You do this by sending a message to the new class:
| Account comment:
'I represent a place to deposit and withdraw money' !
|
A description is associated with every Smalltalk class, and
it's considered good form to add a description to each new
class you define. To get the description for a given class:
| (Account comment) printNl !
|
And your string is printed back to you. Try this with class
Integer, too:
| (Integer comment) printNl !
|
5.4.3 Defining a method for the class
We have created a class, but it isn't ready to do any
work for us--we have to define some messages which the class
can process first. We'll start at the beginning by defining
methods for instance creation:
| !Account class methodsFor: 'instance creation'!
new
| r |
r := super new.
r init.
^r
! !
|
Again, programming your editor to do this is recommended.
The important points about this are:
-
Account class means that we are defining messages which are
to be sent to the Account class itself.
-
methodsFor: 'instance creation'
is more documentation support; it says that all of the methods
defined will be to support creating objects of type
Account.
-
The text starting with
new and ending with ! !
defined what action to take for the message new .
When you enter this definition, GNU Smalltalk will simply
give you another prompt, but your method has been compiled in
and is ready for use. GNU Smalltalk is pretty quiet on successful
method definitions--but you'll get plenty of error
messages if there's a problem!
This is also the first example where we've had to use
more than one statement, and thus a good place to present
the statement separator--the . period. Like Pascal, and unlike C,
statements are separated rather than terminated. Thus you
need only use a . when you have finished one statement
and are starting another. This is why our last statement,
^r , does not have a . following. Once again like
Pascal, however, Smalltalk won't complain if your enter a spurious
statement separator after the last statement.
The best way to describe how this method works is to
step through it. Imagine we sent a message to the new class
Account with the command line:
Account receives the message new and looks up
how to process this message. It finds our new definition, and
starts running it. The first line, | r | , creates a local
variable named r which can be used as a placeholder for
the objects we create. r will go away as soon as the message
is done being processed.
The first real step is to actually create the object.
The line r := super new does this using a fancy trick.
The word super stands for the same object that the message
new was originally sent to (remember? it's Account ),
except that when Smalltalk goes to search for the methods,
it starts one level higher up in the hierarchy than the current
level. So for a method in the Account class, this is
the Object class (because the class Account inherits from is
Object--go back and look at how we created the Account
class), and the Object class' methods then execute some code
in response to the #new message. As it turns out, Object
will do the actual creation of the object when sent a #new
message.
One more time in slow motion: the Account method #new
wants to do some fiddling about when new objects are created,
but he also wants to let his parent do some work with
a method of the same name. By saying r := super new he
is letting his parent create the object, and then he is attaching
it to the variable r . So after this line of code executes,
we have a brand new object of type Account, and r
is bound to it. You will understand this better as time
goes on, but for now scratch your head once, accept it as a
recipe, and keep going.
We have the new object, but we haven't set it up correctly.
Remember the hidden variable balance which we saw
in the beginning of this chapter? super new gives us the
object with the balance field containing nothing, but we want
our balance field to start at 0. (21)
So what we need to do is ask the object to set itself up.
By saying r init , we are sending the init
message to our new Account. We'll define
this method in the next section--for now just assume that
sending the init message will get our Account set up.
Finally, we say ^r . In English, this is return what
r is attached to. This means that whoever sent to Account
the new message will get back this brand new account. At
the same time, our temporary variable r ceases to exist.
5.4.4 Defining an instance method
We need to define the init method for our Account
objects, so that our new method defined above will work.
Here's the Smalltalk code:
| !Account methodsFor: 'instance initialization'!
init
balance := 0
! !
|
It looks quite a bit like the previous method definition,
except that the first one said
Account class methodsFor:... , and ours says
Account methodsFor:... .
The difference is that the first one defined a method for
messages sent directly to Account , but the second one is
for messages which are sent to Account objects once they are
created.
The method named init has only one line, balance := 0 .
This initializes the hidden variable balance (actually
called an instance variable) to zero, which makes
sense for an account balance. Notice that the method
doesn't end with ^r or anything like it: this method
doesn't return a value to the message sender. When you do
not specify a return value, Smalltalk defaults the return
value to the object currently executing. For clarity of
programming, you might consider explicitly returning self
in cases where you intend the return value to be used.(22)
5.4.5 Looking at our Account
Let's create an instance of class Account:
| Smalltalk at: #a put: (Account new) !
|
Can you guess what this does? The Smalltalk at: #a put: <something>
creates a Smalltalk variable. And the Account new creates a new
Account, and returns it. So this line creates a Smalltalk
variable named a , and attaches it to a new Account--all in
one line. Let's take a look at the Account object we just created:
It prints:
Hmmm... not very informative. The problem is that we didn't
tell our Account how to print itself, so we're just getting
the default system printNl method--which tells what the
object is, but not what it contains. So clearly we must add
such a method:
| !Account methodsFor: 'printing'!
printOn: stream
super printOn: stream.
stream nextPutAll: ' with balance: '.
balance printOn: stream
! !
|
Now give it a try again:
which prints:
| an Account with balance: 0
|
This may seem a little strange. We added a new method,
printOn:, and our printNl message starts behaving differently.
It turns out that the printOn: message is the central
printing function--once you've defined it, all of the
other printing methods end up calling it. Its argument is a
place to print to--quite often it is the variable Transcript .
This variable is usually hooked to your terminal, and thus
you get the printout to your screen.
The super printOn: stream lets our parent do what it
did before--print out what our type is. The an Account
part of the printout came from this.
stream nextPutAll: ' with balance: ' creates the
string with balance: , and prints it out to the stream,
too; note that we don't use printOn: here because that would
enclose our string within quotes. Finally, balance printOn: stream
asks whatever object is hooked to the balance variable to print
itself to the stream. We set balance to 0, so the 0 gets printed out.
5.4.6 Moving money around
We can now create accounts, and look at them. As it
stands, though, our balance will always be 0--what a tragedy!
Our final methods will let us deposit and spend money.
They're very simple:
| !Account methodsFor: 'moving money'!
spend: amount
balance := balance - amount
!
deposit: amount
balance := balance + amount
! !
|
With these methods you can now deposit and spend amounts of
money. Try these operations:
| a deposit: 125!
a deposit: 20!
a printNl!
a spend: 10!
a printNl!
|
5.4.7 What's next?
We now have a generic concept, an "Account". We can create them,
check their balance, and move money in and out of
them. They provide a good foundation, but leave out important
information that particular types of accounts might
want. In the next chapter, we'll take a look at fixing this
problem using subclasses.
|