Home
Archives
About us...
Advertising
Contacts
Site Map
 

ruby in steel

 

SMALLTALK : A BEGINNER'S GUIDE #2

Also see Part One of this tutorial

Having got to grips with the fundamentals of Smalltalk last month, it’s time to open a Bag, read a Dictionary and get lost on the Northern Line.
by Huw Collingbourne

Requirements:
A Smalltalk system such as Squeak:
www.squeak.org
or Dolphin Smalltalk:
www.object-arts.com

 

Download The Source Code:
smalltalk2.zip

 

See also: Learn Dolphin Smalltalk

Once again, we’ll be using Squeak for this month’s tutorial. Squeak is a small, free Smalltalk development suite which you can download from www.squeak.org. To follow this lesson, you should first install Squeak and our tutorial file. With a few minor changes the code can also be used by other flavours of Smalltalk. In fact, I’ve also created a version for Object Arts’ excellent Dolphin Smalltalk. If you are using this instead of Squeak, refer to Smalltalk For Dolphins.

This month I'll be delving into the Smalltalk class hierarchy and adding some classes of my own. I've decided to create a mapping project. This could, in theory, form the basis of something as serious as a route-planner or as frivolous as a game. We'll end up with a simple maze game based loosely on the map of the London Underground. The player will start at some location on the map and will have to find a route that leads to the final destination, Mornington Crescent.

Ultimately, we shall need to define a class for each location object which, according to the conventions of computer games, we shall call a Room. Each Room will contain several pieces of data indicating the Rooms to which it adjoins at each of four exits. For example, 'Room 1' might have an exit on its South side which leads to 'Room 2'.

However, before we do that we must first decide on an appropriate data structure to represent the map that will contain our Room objects. The obvious candidate is an array. In Smalltalk, an Array is just another type of class. You can examine all the methods its contains using the System Browser. Load this now by pressing ALT-B.


To find a class, right-click the top-left pane of the System Browser and select ‘Find Class’ from the popup menu

In the Browser, right-click the top left-hand pane to pop up a mouse menu and select Find Class (or use the shortcut ALT-F). This displays a Find Class Name or Fragment dialog. In this enter the name, Array and click the Accept button. This will display a list of items. Click the first item, Array. This highlights the Array class in the second pane. The code displayed in the first horizontal pane shows that Array is a subclass of ArrayedCollection. To see the relationships of descendant classes more clearly you can use the Hierarchy Browser. With Array selected in the second pane of the System Browser, right-click and select Browse Hierarchy (or press the ALT-H shortcut). The top-left hand pane in this new browser shows the ancestry of each class. You may need to expand the window and use the scroll bar to see this clearly. Notice that Array descends from ArrayedCollection which itself descends from SequenceableCollection, Collection and, ultimately, Object. When examining the methods available to a selected class (shown in the top right-hand pane) you should always bear in mind that it also inherits the methods of its ancestor classes.

The methods of a class are generally grouped according to categories displayed in the top middle pane. Select Array in the left pane and 'converting' in the middle pane. You will see several methods in this category in the top-right pane. Select evalStrings . Notice that the code of the method appears in the bottom pane.


Here I have selected Array in the top-left pane of the Hierarchy Browser, the ‘converting’ category in the middle pane and the evalStrings method in the right-hand pane. The code of the method is shown in the bottom pane

If you select SequenceableCollection and Collection, you will see many other useful methods, some of which we shall try out in a moment. As you work your way through our examples, you may find it useful to refer back to the Class Hierarchy Browser from time to time to see which methods are available to each class.

Hip, Hip, Array!

Now let's try a few experiments. First, clean up your workspace by minimising the Class Hierarchy Browser and the System Browser (click the ‘O’ at the top right of the caption bars). Now load our tutorial file, smalltalk2.st. In Squeak you can do this by first clicking the Tools tab on the right of the workspace and then dragging a File List from the Tools palette into the workspace. Use its top-left pane to navigate to the appropriate directory. Highlight the file smalltalk2.st in the top-right pane. Right-click to pop up a menu and select ‘workspace with contents’ Users of Dolphin Smalltalk can simply load the tutorial file using the File, Open menu in one of the Workspace windows.


Here I am using the Squeak System Browser to locate the demo file in a directory on my hard disk. Right-click the file name and select ‘workspace with contents’ top load it.

First of all, we are going to create a new Array with 10 slots. In the tutorial document, you evaluate this expression by placing your cursor on the same line and pressing ALT-D:

map := Array new: 10.

Note that you should always press ALT-D (short for ‘Do It’) to evaluate an expression and ALT-P to Display (or ‘Print’) an expression. Displaying has the effect of evaluating the expression and showing the result. You must be sure to evaluate or display everything in the correct order otherwise some objects may not be created and code later in the document will not run.

Now add ten objects to the map array by evaluating this block of code. This time, be sure to highlight the entire code block prior to pressing ALT-D:

|  i  |
i := 1.
10 timesRepeat: [
  map at: i put: ('Room ', i printString).
  i := i + 1.
].


Here I have marked off a block of code with the mouse. I can evaluate of ‘do it’ by pressing ALT-D. If I want to evaluate and display (or ‘print’) the results I can press ALT-P or alternatively I can right-click and make a selection from the mouse menu

This code simply uses a local variable, i, to iterate through the 10 slots of the array, putting a string such as 'Room 1' at each subscript. Eventually we want to be able to store special Room objects. However, since we haven't yet defined a Room class, we shall do all our initial experiments with strings and adapt our code later on. Notice that the printString message is sent to the integer, i, in order that it may be appended to the string, 'Room' using the comma ',' concatenation operator. In simple terms, think of printString as a method or function of the integer, i,. If you don't understand this, you may need to refer to last month's tutorial.

You can check that the map has been initialised as expected by displaying (ALT-P) the map variable. All being well, you should obtain this return value:

#('Room 1' 'Room 2' 'Room 3' 'Room 4' 'Room 5' 'Room 6' 'Room 7' 'Room 8' 'Room 9' 'Room 10')

Various methods are available to check that an array includes a certain item, to obtain the item at a given subscript or to put a new item at a specified subscript. The tutorial document contains some examples of these methods. To see how they are used, Display each line of code one by one.

An Array certainly could be used for storing Room objects. In the final implementation, we could give the Room class four integer fields, N, S, E, W, to indicate the Room to which it is connected (that is the Room at that Array subscript) in a given direction. If the S field of 'Room 1' is 2 then that would indicate that it leads to the Room in slot 2 of the array, namely 'Room 2'.

The main drawback of using an array is that the developer would have to keep referring back to the array in order to figure out which object is at any given subscript. The Room's name won't necessarily have any relationship to this subscript. For example, in an array representing the London Underground, an object called 'Camden Town' might contain a S field with the value 4. Without counting through the items in the array, there would be no way to tell that slot 4 contains 'Mornington Crescent'.

In The Bag?

Let's see if one of Smalltalk's other Collection classes might be a better choice. One possibility is a Bag. Unlike an array, a Bag has no intrinsic numerical order. Think of it as a bag of sweets. You can put sweets into the bag and you can take sweets out of the bag. You could even choose a red sweet or a yellow one. But it wouldn't make any sense to say "I want sweet number 5".


The Inspector window lets us look inside pour Bag to see what it contains

The tutorial document contains an example of implementing the map as a Bag. Evaluate and Display the code as instructed to see this in action. We have code that can be used to Inspect the Bag (this will pop up another window) and test for membership of the Bag. When we try to access a bag element by numerical position, however, an error occurs for the reason explained above.

 


The contents of a Bag aren’t in numerical order so trying to obtain the item at position 3 has caused this error

For our purposes, I don't think a Bag is quite the right class for the map. After all, my map or Rooms isn't really like a bag of sweets since it does have some kind of order - but not a numerical order. You might say that the stations in the London Underground are ordered by name. Instead of being Stations 1 to 4 they are stations 'Belsize Park' to 'Mornington Crescent' and so on.

Now, it turns out that Smalltalk has one type of Collection which is ordered in precisely this way. It's called a Dictionary. Instead of using array subscripts to identify or locate an object, it uses keys. These keys could be integers, if you wished. So, for instance, it would be possible to create a Dictionary such as this:

map at: 1 put: 'Belsize Park';
  at: 2 put: 'Chalk Farm'.

But the keys could equally well be string descriptions:

map at: 'Station 1' put: 'Belsize Park';
  at: 'Station 2' put: 'Chalk Farm';
  at: 'Station 3' put: 'Camden Town';
  at: 'Your destination' put: 'Mornington Crescent'.

In the above example, 'Station 1' is a key and 'Belsize Park' is the value associated with it. Here the value is a string but it could just as well be any type of object. You can use these keys in much the same way that you would use the subscripts of an array, to retrieve or alter the values associated with them. Be sure to evaluate the code to create a Dictionary and put items into it in the order in which the code appears in our tutorial document. Having done this, try Displaying (ALT-P) this code:

map at: 'Station 2'.

You will see that the return value is 'Chalk Farm' since this is associated with the key, 'Station 2'. The tutorial document provides other examples of Dictionary access methods.


Be sure to evaluate all four lines of the code block seen at the top here, which create and initialises the map. Then print (ALT-P) the line beneath to find the value of the object at the ‘Station 2’ key.

Class Distinction

Now that we've decided on a suitable class for our map object, we need to create a new class for the Rooms. This is where things start to get interesting. To create a Room class we need to extend the Smalltalk Class hierarchy itself.

Every new class descends from an existing class. If we wanted to inherit the features of an array, for example, we would need to make our class descend from the Array class. In fact, our Room class is going to be pretty simple, so we can make it a direct descendant of the Object class.

Let's do that now. If it’s still on screen but minimized, open your System Browser by clicking the ‘O’ in its title bar. If it is not on screen, press ALT-S to open a new browser. Right-click the top left-hand pane and select Find Class from the menu. Enter Object, click Accept and select Object from the list that appears. Right-click Object in the second pane. Select ‘more…’ from the bottom of the popup menu and select ‘subclass template’ from the new menu. This creates an ‘empty’ descendant class of Object whose code is displayed in the bottom pane of the System Browser. Let’s turn this into a Room object.

Edit the first line of the class definition by giving the class the name ‘Room’ as follows:

Object subclass: #Room

The Class Definition also contains an item called instanceVariableNames: . The argument is currently an empty string. We can replace this with a string containing a list of the instance variables or 'fields' we want to be added to each Room object. Edit the string as follows:

instanceVariableNames: 'description n s w e'

The complete Class definition should now look like this:

Object subclass: #Room
instanceVariableNames: 'description n s w e'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Kernel-Objects'

With the code window selected, press ALT-S to save your changes. A new pane will appear below this informing you that this class has no comment. As it’s good practice to document new classes, you can do so now simply by entering some text into the bottom pane. I suggest something such as “The Room class defines a location with four exits”. Now, with the documentation pane still selected press ALT-S to save your comment.


Here I have added the Room class using the System Browser. It is a subclass of Object and I’ve add its instance variables in the pane second from bottom, plus a comment in the pane beneath that

If there are any syntax errors (for example, if you enter the name ‘room’ with a lowercase initial, which is invalid in Smalltalk), an error message will be displayed. In that case, check the code carefully, correct any mistakes and try saving again.

If you have done Object Orientated programming with C++, Java or Delphi you may be used to accessing the instance variables of an object using dot notation in the form:

someob.somevar

You cannot do this in Smalltalk. It doesn't even make syntactic sense since a Smalltalk dot terminates an expression so someob and somevar would be evaluated as two separate expressions. Whereas it is generally thought 'good style' to provide accessor methods to get and set instance variables in many OOP languages, this is often left at the discretion of the programmer. By contrast, accessor methods are absolutely required in Smalltalk.

If we want to be able to retrieve the name of a given Room object, we need to write a method that enables the object to tell us its name. This is simply done. With Room still highlighted in the System Browser, make sure that the Instance button is selected at the bottom of the second pane. This ensures that our methods will be associated with each instance of the Room object rather than with the Class.

Squeak provides a simple way of adding get and set accessors to return or assign values for variables. Right-click Room in the second pane, select ‘more…’ from the menu, then select ‘create inst var accessors’ from the next menu. If prompted for your initials, enter these and press Accept.


Here I’ve selected ‘create instant var accessors’ from a popup menu. Instantly ‘get’ and ‘set’ accessors for all the instance variables I added to the Room class are created and displayed in the top-right pane.

Immediately you will see a set of accessor methods matching the names of the variables in the right-hand pane. The ‘get’ methods have the same names as the variables themselves. So, for example, the description accessor simply returns the value of the description variable:

description
  ^description

Here, instead of the '^', Squeak displays an up-arrow symbol (entered by pressing ‘^’ on the keyboard). This is Smalltalk’s return operator. The ‘set’ accessors have the same names as the variables plus a colon at the end to show that a value must be used when calling this method. This is the set accessor for the description variable:

description: anObject
  description := anObject

The left-arrow symbol displayed by Squeak is an alternative form of the := assignment operator.

Now that we have a Room class it’s time to create some actual room objects. But how do we assign values to each of the variables? We could create each Room using the normal 'new' constructor method and then set each variable using an appropriate accessor method. But that's rather long-winded. Instead, it would be simpler to write a new class method that accepts arguments for each variable.

With Room selected, click the Class button beneath the second pane. Now select ‘no messages’ in the third pane. In the code pane, select and delete everything and replace it with this code:

description: aDescription n: aN s: aS w: aW e: aE
| newroom | 
	newroom := self new.
	newroom description: aDescription; n: aN; s: aS; w: aW; e: aE.
	^newroom.

Pres ALT-S to save this. You will see description:n:s:w:e: in the right hand pane. This is a class constructor method. It can be called when you create a new Room object, passing to it values for each of the five variables.


Make sure the Class button is activated when you want to add class or ‘constructor’ methods. These are associated with the class itself rather than with specific instances so they can be called before you have created any actual objects based on a class

Having defined the Room class you are ready to make a map. One of the great things about Smalltalk is that you don't have to write a complete program just to try out a piece of code. You can open a workspace window and experiment there. This is what I've done in the tutorial document. I have first created a Dictionary object named map and then added Room objects at various keys. Each key has the name of a particular underground station.

Evaluate this code:

map := Dictionary new.

Now try out the various bits of code that follow this in the tutorial document. It is all explained in the comments.


Be sure to select and evaluate this entire block of code in order to create a Dictionary named map containing items with keys such as ‘Belsize Park’ and values provided by Room objects.

Next you'll need to know a bit about Smalltalk's Boolean class. This provides methods to test values and expressions for a true or false result. The most important Boolean methods are the following:

ifTrue: 
ifTrue: ifFalse:
whileTrue:

The ifTrue: message can be sent to an expression, normally enclosed in round brackets. If the expression evaluates to true, a block of code in square brackets is executed. Here is an example:

(1 < 10) ifTrue: [^'Correct!'].

The ifTrue:ifFalse message is much the same but includes an extra block of code that is executed if the expression evaluates to false:

(1 > 10) ifTrue: [^'Correct!'] ifFalse: [^'Wrong!'].

You can try out all these examples in the tutorial document. Once you've understood this, take a look at the code labelled "Test 1". This defines two temporary variables, dir and pos. The pos variable is assigned the name of the starting position, 'Chalk farm', which is also a key in the map Dictionary.

The dir variable is initialised with the text entered by the user into a popup FillInTheBlank prompter box. In this first test, the code only has a valid response when the user enters the capital letter, 'N'. In this case, it updates the pos variable to the string returned by current the Room's method n. This provides a new key into the map and the pos variable is set to this key, thereby 'moving' the player to the new room:

( dir = 'N' )
  ifTrue: [ pos := (map at: pos) n. "… etcetera"]

Before evaluating this code, be sure to drag a Transcript window from the Tools palette. The code should., of course, be able to deal with all the other directions too. You can see this new code under the label "Test 2".


Click the Tools tab and drag out a Transcript (top item). Here we have evaluated the code in the tutorial document and displayed the results in the Transcript which is seen here beneath it.

Let’s see what I’ve added here. First of all I had to extend the range of user input that could be handled. Since I will only be dealing with one-letter commands, I needed to extract the first character from any string entered and, while I'm at it, I might as well convert it to lower case so that both 'N' and 'n' are treated equally:

dir := (dir at: 1) asLowercase.

Next I needed to be able to test for the four characters $n, $s, $w and $e (a character is indicated by a preceding dollar sign in Smalltalk). I didn't fancy using multiple nested ifTrue:ifFalse messages. So, instead, I defined an array of valid characters:

commands := #( $n $s $w $e).

This allows me to test if the character, dir, is included in this array:

(commands includes: dir)

Now, in most other languages, this test wouldn't have got me very far. I would still have needed to code an individual response for each of the four possible characters. Smalltalk, however, has a special bit of magic that lets me create code on-the-fly. It comes in the form of a method called perform: . This takes a symbol as an argument and runs it as code. You can convert a string or a character to a symbol using the asSymbol method. So characters such as $n or $e can be converted to the symbols #n or #e and these can then be sent as messages to a Room object, causing the n and e methods to be executed. This is the code:

newpos := (map at: pos) perform: dir asSymbol.

There are more examples in the tutorial document which should help you to understand this better. Once you've tried out this code, you should be in a position to create a new class that initialises and runs the game. You may what to try to program this class yourself.

It will need to be provided with its own Dictionary (an instance variable) to contain Room objects. It will need a method to initialise this Dictionary and set the starting position. It will also need methods to get input from the user after each move and to terminate the game when 'Mornington Crescent' has been reached.

Assuming you decide to name this class MapMaster, it should be possible to start a new game by evaluating this expression:

MapMaster new.

This means that you will need to write a constructor method, new, that will create a new instance of MapMaster. Having added the MapMaster class you can create this constructor clicking the Class Tab and selecting Method, New. Then enter this code and press [CTRL]-S to save it:

new
  ^super new initialize.

Now click the Instance button and create all the methods needed to run the game. Start by writing a method called initialize. Incidentally, if you need a few hints on how to complete this project, you may want to take a look at the MapMaster.cls file. This is the definition of the MapMaster class ‘which I filed out’ (saved) from Dolphin Smalltalk. This contains my implementation of methods such as initialize, getinput and move:. Note that some code will need to be tweaked for use with Squeak. For example, you should use the FillInTheBlank class instead of Dolphin’s Prompter. Refer to our Smalltalk Web resources for extra help with squeak and the Smalltalk language.

Have fun!


Smalltalk For Dolphins


I’ve provided a slightly different tutorial file for users of Dolphin Smalltalk. This includes a ready-to-run game in which you can navigate around locations by entering single letter directions such as ‘N’, ‘S’ or ‘Q’ for quit in the quest for Mornington Crescent

While Squeak is a good Smalltalk system, I must admit that I personally feel more at home with Dolphin Smalltalk from Object Arts. The downside of Dolphin Smalltalk is that it is a commercial system (Squeak is free) and that it is restricted to Windows (Squeak also comes in Unix, Mac OS and Acorn RISC OS flavours). The thing I like about Dolphin Smalltalk is that it is just so easy to use. In addition to browsers and mouse menus, it also has normal Windows-style menus and keyboard shortcuts. If you want to open a file, for example, you just select File, Open. In terms of the Smalltalk language and class libraries, Squeak and Dolphin are reasonably compatible. There are some differences, however, which make it impossible to load and run the same tutorial code in both systems. For that reason, I’ve also provided a Dolphin compatible version of our tutorial document. If you are using Dolphin Smalltalk, load the file smalltalk_dolphin2.st then follow the comments for help on using the code. I’ve also created a special ‘package’ file, MorningtonCrescent.pac, containing a slightly more complete version of the Mornington Crescent program. Instructions on using this are provided in the tutorial document.


Smalltalk Web Resources

If you want to learn more about programming in Smalltalk, Stéphane Ducasse’s library of free online Smalltalk books is the place to start http://www.iam.unibe.ch/~ducasse/FreeBooks.html. Here you can download out some great, out of print Smalltalk books in PDF format. For beginners, the SmalltalkV Tutorial is probably a good place to start. For serious Smalltalkers, Smalltalk-80 by Adele Goldberg is a must-have. There is even a book specifically about Squeak. A superb resource but, be warned, some of these downloads are tens of megabytes in size so may take quite a while to download if you haven’t got broadband.

June 2005

 


Home | Archives | Contacts

Copyright © 2006 Dark Neon Ltd. :: not to be reproduced without permission