Home
Archives
About us...
Advertising
Contacts
Site Map
 

ruby in steel

 

LEARN DOLPHIN SMALLTALK

To start learning Smalltalk, download our free copy of Dolphin Smalltalk for Windows and follow our step-by-step tutorials
by Huw Collingbourne

Requirements:
Dolphin Smalltalk
Download Page
Dolphin Smalltalk is a product of Object Arts:
www.object-arts.com

Download The Source Code:
smalltalk2.zip

 

If you are new to Smalltalk, we suggest that you follow our two part beginner’s guide. This explains how to program a simple maze-type game in which you navigate around some stations of the London Underground in search of Mornington Crescent. While the game itself is extremely simple, the tutorial will introduce you to many important features of the Smalltalk language and environment. By the time you’ve completed this tutorial, you will have enough knowledge of Smalltalk to start writing more serious programs of your own.


Dolphin Smalltalk has a neat integrated environment with tools for programming, browsing, editing and debugging

The first lesson in the tutorial can be used with either the free Squeak Smalltalk or with Dolphin Smalltalk. Where there are differences between the two systems (for example, in the menus or keystrokes that you must use), these are indicated in the text. In the second lesson, there are a few potentially confusing differences between Squeak and Dolphin. For that reason, we have provided a separate Dolphin version of Lesson Two, below.

NOTE: Before you do anything in Dolphin Smalltalk, it’s a good idea to save a ‘clean image’. An image is a snapshot of the entire Dolphin Smalltalk system - including the size and position of its windows and (crucially) the current state of the class library and objects. Just select File, Save Image As and enter an image name such as ‘FreshInstall’

New to Smalltalk? Start With Lesson One

If you are completely new to Smalltalk, you should start with Lesson One. First download the tutorial file: smalltalk1.st and load it into Dolphin Smalltalk by selecting File, Open from one of the Workspace windows or pressing the Ctrl+O keyboard shortcut. The tutorial document contain step-by-step instructions. For more guidance, refer to the introductory Smalltalk lesson which guides you through the code in the tutorial document. Once you have followed Lesson One (or you already know some Smalltalk but are new to Dolphin), move on to Lesson Two, below.

When following these lessons, remember that you should Evaluate (Ctrl+E) or Display (Ctrl+D) every piece of code in the tutorial document in the order indicated. Some pieces of code in the tutorials rely on earlier pieces of code having been evaluated first - so don’t skip anything! Also, bear in mind that what Dolphin calls ‘Evaluate’ is what Squeak calls ‘Do’; what Dolphin calls ‘Display’ is what Squeak calls ‘Print’. In Lesson One, when we say ‘Do It’ in Squeak, you should press Ctrl+E to evaluate an expression in Dolphin. If the lesson says ‘Print It’ in Squeak, press Ctrl+D to evaluate an expression display the result in Dolphin.

Moving On? Start Here With Lesson Two

While the versions of the Smalltalk language implemented by Dolphin and Squeak are largely compatible, a few differences show up in the second part of our tutorial. For this reason, we have prepared a Dolphin-specific tutorial document for this lesson. Download and extract the zipped source code smalltalk2.zip and use the Dolphin tutorial document smalltalk_dolphin2.st with the lesson below (note, the Squeak version of lesson two, smalltalk2.st, is also provided in the zip file).

In this lesson, 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 ultimate destination, Mornington Crescent.

Ultimately, we shall need to define a class for each ‘location object’ which, according to the conventions of computer adventure games, we shall call a Room. Each Room will contain several pieces of data indicating any adjoining Rooms at each of the 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 Class Hierarchy Browser. Load this now by selecting Tools, Class Browser.


As an alternative to menus and keystrokes, you can also load many of the windows and tools from the System Folder seen here. Double-click the Class Browser icon to load a Browser.

In the Browser, press Ctrl+Shift+F (or right-click the top-left browser pane and select Find; or use the top-level menu, Class, Find) to bring up a Find dialog and enter the name, 'Array'. This will show the classes matching the string. Select ‘Array’ and click OK. The Array class is now selected. You will see that it occupies a branch beneath ArrayedCollection. This indicates that Array is a descendant of ArrayedCollection and of all classes above it, such as SequenceableCollection and Collection. When examining the methods available to a selected class (shown in the top right-hand pane) you should bear in mind that it also inherits the methods of its ancestor classes.


Here we are using the Find tool to search for any classes matching the string ‘Array’

The methods of a class are generally grouped according to categories displayed in the top middle pane. Select Array in the left pane and 'adding' in the middle pane. You will see that there is just one method in this category, addAnsweringIndex: . Select this method in the right-hand pane and you will see its code in the bottom pane.

Hip, Hip, Array!

Now let's try a few experiments. Load up our sample file by selecting File, Open (or Ctrl+O) and double-clicking the file named smalltalk_dolphin2.st. This will load the document into a new window.

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 Ctrl-E:

map := Array new: 10.

Remember that you should always press Ctrl-E to evaluate an expression and Ctrl-D to Display 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 Ctrl-E:

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

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. If you don't understand this, you may need to refer to the first part of this tutorial.

You can check that the map has been initialised as expected by displaying (Ctrl+D) over 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 (Ctrl+D) 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 tutorial document contains an example of implementing the map as a Bag. Evaluate and Display the code as instructed to see this in action. For our purposes, I don't think a Bag is quite right. 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. For example, try Displaying 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. You may want to follow the instructions in the document to try out various bits of code. When you arrive at the part that talks about the Room class, return to this tutorial for further guidance.

Class Distinction

Now that we've decided on a suitable class (a Dictionary) 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 its not already visible, open a Class Browser (from the Tools menu). Select Object, right at the top of the hierarchy in the top left-hand pane. Click the Class menu and choose 'New'. When prompted for a name, enter Room and click OK. This creates a basic Room class and displays it in the Browser.


To create a new class just enter its name, Room (with an initial capital ‘R’) into the Create Class dialog

The code in the Class Definition pane shows that Room has subclassed from (in other words, that it is a direct descendant of) Object:

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'

 
To add some variables to each Room object (that is, each ‘instance’ of the Room class) just enter the variable names into the Class definition pane as I have done here

The complete Class definition should now look like this:

Object subclass: #Room
    instanceVariableNames: 'description n s w e'
    classVariableNames: ''
    poolDictionaries: ''

Save this definition by pressing Ctrl+S. If there are any syntax errors, an error message will be displayed. In this case, check the code carefully, correct any mistakes and try saving again.

If you have done Object Orientated programming with other languages 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 languages such as C++, Java and Delphi, this is 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 Class Browser, make sure that the Instance tab is selected This ensures that our methods will be associated with each instance of the Room object rather than with its Class.

Now click the Method menu and select New. A blank Method Source pane will appear. Inside this pane add this code:

description
   ^description

This creates a method called description which returns the value of the instance variable that is also called description. You don't have to give an access method the same name as the matching variable, but it is a convention to do so. In Smalltalk, return values are indicated by the caret symbol ^. Press Ctrl-S to save this.

Now we need to create a method to set the value of the description variable. Select Method, New and in the Method Source pane enter this code:

description: anObject
   description := anObject

Here the colon after the name of the method indicates that it expects an argument. This argument is then assigned to the instance variable, description. Save this method. You should now see the names of your two new methods in the top right-hand pane:

description
description:


You can add get and set accessor methods in the Method source pane. Here I’ve added the description and description: accessors. The colon at the end of the method name shows that it is a ‘set’ accessor so it takes an argument which will be used to initialise the internal description value.

Really we should write similar accessor methods for all the other variables in this class. That would be a bit tedious, though. Fortunately, Dolphin has a shortcut. Click Room in the top-left pane and right-click the mouse. From the Class menu select ‘create accessors'. A box lists all the variables for which accessor methods may be defined. Select e, n, s and w (but leave description unselected as we’ve already defined its accessors). Click OK. Instantly, all the accessor methods are generated and you can see they have been added to the list in the right-hand pane.


Save yourself some coding effort by letting Dolphin create accessors for you. Here I am created accessors for the selected variables: e, n, s, and w

 
In the Methods pane, you can see the list of all the accessors which Dolphin has created. The Method source pane contains the automatically generated code of the selected accessor method

But how do we set all the values for a Room's internal variables in the first place? Well 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 constructor method that accepts arguments for each variable.

A constructor must be a class method since the object it constructs (the 'instance') necessarily does not exist until it has been constructed! Click the Class tab in the top centre pane. Now select Method, New. In the Method Source pane add and save 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.


With the Class tab selected, I have created a constructor which takes five arguments to initialise the variables of each object when it is created.

Now that we've defined the Room class we 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. This is the code:

"Dictionary Map"
map := Dictionary new.
map at: 'Belsize Park' put: (Room description: 'a leafy suburb' 
                          n: 'Hampstead' 
                          s: 'Chalk Farm' 
                          w: 'nowhere' 
                          e: 'nowhere');
    at: 'Chalk Farm' put:   (Room description: 'a rural corner' 
                          n: 'Belsize Park' 
                          s: 'Camden Town' 
                          w: 'nowhere' 
                          e: 'nowhere');   
    at: 'Camden Town' put: (Room description: 'a fashionable quarter' 
                          n: 'Chalk Farm' 
                          s: 'Mornington Crescent' 
                          w: 'nowhere' 
                          e: 'Euston').

Having evaluated this Dictionary in order to create all the essential data, I've been able to try out various bits of code. Before looking at this, 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!'].

The whileTrue: message is sent to a block of code, in square brackets. As long as this block continues to evaluate to true, a second block of code continues to be executed. For example, this code would print 1 to 9 in the Transcript window:

| num |
num := 1.
[num < 10] whileTrue: [Transcript print: num printString; cr. num := num + 1].

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 prompter box:

dir := Prompter prompt: 'Enter a one-letter direction: N,S,W,E' caption: pos

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. "… et cetera"]

Once I was happy with this code, I needed to adapt it to deal with all the other directions. You can see this new code under the label "Test 2".

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 and to terminate the game when 'Mornington Crescent' has been reached.

NOTE: It’s a good idea to save a new ‘image’ of your work before and after you make any major changes to the class library. That gives you a simple way of backing out of any changes without having to remove classes one by one. To save an image, select File, Save Image As. For example, after first installing Dolphin Smalltalk you might save an image called ‘FreshInstall’. After installing the Mornington Crescent package you might save an image called ‘MorningtonCrescent’. The extension ‘img’ is added automatically. To load up an image from disk, just double-click the file name using the Windows Explorer.

Assuming you decide to call the class that runs game 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 (use the Class, New menu item in the Hierarchy Browser) 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 tab and create all the methods needed to run the game. Start by writing a method called initialize. Once you've finished (or if you get stuck along the way) you can compare your version with mine. You can load my classes from a special 'package' file called MorningtonCrescent.pac. Instructions are provided in the tutorial document.

Have fun!


LOADING A PACKAGE


Select Tools, Package Browser…


When the Package Browser appears select Install Package….


Browse the disk and load the MorningtonCrescent.pac package. This will install our MapMaster and Room classes.

 

August 2005

 


Home | Archives | Contacts

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