Smalltalk

Some Similarities between Smalltalk and Java

Key Differences between Smalltalk and Java

Available Implementations

I'll use Squeak to demonstrate Smalltalk in class. I also recommend this implementation for anyone who wants to experiment with the language: it's freely available for most platforms, and comes with lots of cool stuff. Follow the link to see tutorials, download instructions, etc.

Language Overview

We'll now give a quick overview of the language, via a few small examples. Basic concepts: Syntax: Precedence:

Note that we will very frequently be composing messages -- for example

Time now hours + 1
first sends the message now to the class Time, which returns the current time (an instance of Time). We then send this object the message hours, which returns an integer. Then we send the message + with the argument 1 to this integer, returning another integer (which will be the current hour plus 1).


Example 1: Stack

First we define a new class: Object subclass: #Stack instanceVariableNames: 'anArray top' classVariableNames: '' poolDictionaries: '' Now define some methods: push: item top := top+1. anArray at: top put: item pop | item | item := anArray at: top. top := top-1. ^ item setsize: n anArray := Array new: n. top := 0. Some code to test the stack: S := Stack new. S setsize: 10. S inspect. S push: 'hi there'. S push: 3.14159. S pop Adding error checking and growing: push: item | save | top := top+1. top > anArray size ifTrue: "anArray is about to overflow. make a new array twice as big, and copy the old values into it" [save := anArray. anArray := Array new: 2*save size. 1 to: save size do: [:k | anArray at: k put: (save at: k)]]. anArray at: top put: item pop | item | self isEmpty ifTrue: [self error: 'trying to pop an empty stack']. item := anArray at: top. top := top-1. ^ item isEmpty ^ top=0


Introduction to the Class Hierarchy

Here is a simplified picture: At the top of the hierarchy, is of course, Object. All classes are subclasses of the Object class. A few important methods defined by Object are:
  1. Equality Tests: = and ~= (these are like Scheme's equal?)
  2. Identity Tests: == and ~~ (these are like Scheme's eq?)
  3. Copying: copy
  4. Printing: printString and printOn: aStream
Numbers pretty much respond to messages as we'd expect (+, -, *, /, >, <, etc.). We never have to explicitly convert between the number classes (conversions are done automatically). For instance if we say: 3.4 + 3, the result will be 6.4 (a Float). Numbers are converted to more general classes as necessary (Floats are more general than Fractions are more general than Integers).


Control Abstractions

All control structures are done with blocks (closures) and message passing. This is characteristic of pure object-oriented languages, but not of hybrid languages. Many of the basic control structures are implemented as methods in the classes True or False.

Blocks

A block is Smalltalk jargon for a lexical closure (like a lambda expression in Scheme).
| c1 c2  x |
x  := 0.
c1 := [ x := x+1 ].       "c1 is a block"
c2 := [ :i | x := x+i ].  "c2 is a block w/ one parm"

c1 value.                 "evaluate c1"
c2 value: 20.             "evaluate c2, with the argument 20"

" now x equals 21... "
We use square brackets to define a block. The names before the | in the block are parameters to the block (they must start with a colon). We can send a block the value message to force it to evaluate itself.

Boolean "operators"

Here are the method definitions which implement and, or, and not for True objects.
True

   printOn: stream
      stream nextPutAll: 'true'


   & b   "evaluating and"
      ^ b


   | b   "evaluating or"
      ^ true


   not
      ^ false


   and: block   "short-circuit and"
      ^ block value


   or: block   "short-circuit or"
      ^ true
Here are the method definitions which implement and, or, and not for False objects.
False

   printOn: stream
      stream nextPutAll: false'


   & b   "evaluating and"
      ^ false


   | b   "evaluating or"
      ^ b


   not
      ^ true


   and: block   "short-circuit and"
      ^ false


   or: block   "short-circuit or"
      ^ block value

Examples of Boolean expressions:

  (3=4) & (2>1)

  (3=4) | (2>1)

  (3=2) not

  true & false not

  (3=4) and: [(1/0) = 8]

Conditionals

Conditionals are also implemented as methods on True or False:
True

   ifTrue: block
      ^ block value

   ifFalse: block
      ^ nil

   ifTrue: tBlock ifFalse: fBlock
      ^ tBlock value


False

   ifTrue: block
      ^ nil

   ifFalse: block
      ^ block value

   ifTrue: tBlock ifFalse: fBlock
      ^ fBlock value

Examples of Conditionals:

  3=4 ifTrue: [x := 10].


  x=y ifTrue: [x := 8] ifFalse: [x := 9].

  x := x=y ifTrue: [8] ifFalse: [9].

Simple Iteration

Blocks and the boolean classes are also used to implement iteratation.
a := 1.
[a < 10] whileTrue: [Transcript show: a printString.  a := a+1].

a := 1.
[a > 10] whileFalse: [Transcript show: a printString.  a := a+1].

1 to: 10 do: [:x | Transcript show: x printString].

Iterating over Collections

Collection

   add: newObject      
	"add newObject to the receiver"

   remove: oldObject   
	"remove oldObject from the receiver, report error if not found"

   remove: oldObject ifAbsent: aBlock
	"remove oldObject from receiver, evaluate aBlock if not found"

   isEmpty
	"answer whether receiver is empty"

   size
        "answer the number of elements in the receiver"

   do: aBlock
	"evaluate aBlock for each element"

   collect: aBlock
	"like Scheme map -- make a new collection by applying aBlock to each 
	element and collecting the results"
Note that because of Smalltalk's support for first-class closures (blocks) we don't need separate Iterator objects as in Java -- we can just implement methods such as do: for collections.

Examples:

    a := #(3 4 5 6).   "an array literal"

    a collect: [:j | j+10]    "this returns (13 14 15 16)"

    sum := 0.
    a do: [:n | sum := sum+n]
    "sum is now 18"