Anybody who knows me well as a developer, knows that I like Smalltalk, and probably that it’s my favourite language, in truth tho’, I have barely written Smalltalk in nearly 20 years, after spending a couple of years working on financial modelling software.

It’s an elegant language, the set of reserved keywords is tiny, just true, false, nil, self, super, and thisContext.

The rest of the Smalltalk language is built up from this, and it has a small core, but it never took off as a commercial development language.

Around 20 years ago, there were a number of reasonably successful implementations, and the one I learned and worked with was Dolphin Smalltalk, which was recently open-sourced.

I decided to dust off my Smalltalk knowledge, and it turned out to be harder than I thought it would be, Dolphin unfortunately only works in Windows, and the main commercial Smalltalk is now Cincom, but it’s not easily downloadable.

I was left with Pharo, Squeak and GNU Smalltalk.

I decided to go with the rather minimalist GNU Smalltalk, and get started on one of my favourite Katas, Matteo Vaccari’s Birthday Kata.

Most Smalltalks are IDEs built in and around the “Image” but the GNU Smalltalk implementation is more file-oriented.

It’s easy to write the Smalltalk in files, and crucially run the tests.

The Kata requires an Employee, so I’m going to start from the bottom-up for a change, and start by asserting that an Employee knows whether or not their birthday is on a provided date.

GNU Smalltalk comes with SUnit the grandparent of modern unittest frameworks.

I’ll start by writing a test to a file EmployeeTest.st

TestCase subclass: EmployeeTestCase [
    <comment: nil>
    <category: 'BirthdayKata-EmployeeTests'>

    testIsBirthdayWhenDateIsBirthday [
        <category: 'tests'>
        | e today birthDate |
        birthDate := Date newDay: 14 month: #Feb year: 1990.
        today := Date newDay: 14 month: #Feb year: 2019.

        e := Employee new birthDate: birthDate.

        self assert: (e isBirthday: today)
    ]

    testIsBirthdayWhenDateIsNotBirthday [
        <category: 'tests'>
        | e today birthDate |
        birthDate := Date newDay: 14 month: #Feb year: 1990.
        today := Date newDay: 1 month: #Feb year: 2019.

        e := Employee new birthDate: birthDate.

        self deny: (e isBirthday: today)
    ]
]

This probably looks really odd if you’ve never seen any Smalltalk, but also familiar if you’ve used xUnit style tests.

There are two tests, testIsBirthdayWhenDateIsBirthday and testIsBirthdayWhenDateIsNotBirthday.

The tests have instance variables, | e today birthDate | and they are simple Arrange, Act, Assert layout tests.

birthDate := Date newDay: 14 month: #Feb year: 1990.

This creates a new Date object called birthDate by sending a Date class a message newDay: with parameters month: #Feb year: 1990, this is a Keyword message type method.

The method newDay: takes two keyword parameters, month and year.

The #Feb object is a Symbol, this is similar to atoms in Erlang and Elixir, and symbols in Ruby and Clojure.

Unsurprisingly, this results in a Date object representing the 14th of February 1990.

e := Employee new birthDate: birthDate.

This creates a new Employee e with new and then sends that a birthDate: birthDate message, to assign the employee’s birthday.

Smalltalk syntax reads left-to-right, and it will evaluate the Employee new part, and then send it the birthDate: message.

birthDate: consists of the birthDate: message, and the aDate parameter.

The syntax is probably alien, but the logic isn’t hard to read.

self assert: (e isBirthday: today)

This code is probably familiar from other xUnit implmentations, it’s essentially the equivalent of assertTrue and it passes the result of the expression:

(e isBirthday: today)

This sends a message isBirthday: with today as the parameter to e the created employee.

After some poking around, I found that I could run the SUnit tests with gst-sunit.

  $ gst-sunit -f BirthdayTest.st EmployeeTestCase
$ gst-sunit -f BirthdayTest.st EmployeeTestCase
did not understand #new
TestCondensedLog(TestVerboseLog)>>logError: (SUnit.star#VFS.ZipFile/SUnit.st:608)
TestCondensedLog>>logError: (SUnit.star#VFS.ZipFile/SUnit.st:668)
EmployeeTestCase(TestCase)>>logError: (SUnit.star#VFS.ZipFile/SUnit.st:870)
[] in TestResult>>runCase: (SUnit.star#VFS.ZipFile/SUnit.st:443)

Boom!

This blows up, because the Employee doesn’t exist, so it fails when attempting to instantiate an Employee with new.

Object subclass: Employee [
  <comment: 'I represent an Employee in the Kata'>
  <category: 'BirthdayKata'>
  | birthDate |
]

This is a simple Employee, it has a birthdate, the code basically defines a new Employee subclass of Object with a comment, and a category, and a single instance variable birthDate.

I need to include the new Employee.st file in the source list to compile when running the tests.

  $ gst-sunit -f Employee.st -f EmployeeTest.st EmployeeTestCase
$ gst-sunit -f Employee.st -f EmployeeTest.st EmployeeTestCase
did not understand #birthDate:
TestCondensedLog(TestVerboseLog)>>logError: (SUnit.star#VFS.ZipFile/SUnit.st:608)
TestCondensedLog>>logError: (SUnit.star#VFS.ZipFile/SUnit.st:668)
EmployeeTestCase(TestCase)>>logError: (SUnit.star#VFS.ZipFile/SUnit.st:870)
[] in TestResult>>runCase: (SUnit.star#VFS.ZipFile/SUnit.st:443)

Getting somewhere, the Employee object doesn’t respond to the birthDate: message (also called a selector in Smalltalk).

I added a birthDate instance variable, but, I didn’t add any accessor messages, and Smalltalk instance variables are, like most languages, private.

Object subclass: Employee [
  <comment: 'I represent an Employee in the Kata.'>
  <category: 'BirthdayKata'>
  | birthDate |

  birthDate: aDate [
    "Set the value of the receiver's 'birthDate' instance variable to the argument aDate."
    <category: 'accessing'>
    birthDate := aDate.
  ]
]

This is fairly simple to understand, Smalltalk is not a strongly typed language, so it’s not uncommon to give type hints in the argument names, and the small bit of code birthDate := aDate does the assignment

By default the method returns self, i.e. the receiver, which allows chaining of methods as we’ll see later, this might surprise folks who are used to explicit returns, or “returns the last expression”, as is common in Ruby, Scala etc.

I can now start up the GNU Smalltalk interpreter, file-in (the Smalltalk term for load) the source and experiment with the object:

$ gst
GNU Smalltalk ready

st> FileStream fileIn: 'Employee.st'.
FileStream
st> e := Employee new.
an Employee
st> e birthDate: 'test'.
an Employee
st>

That an Employee comes from the base Object method that displays things on the console, printOn: which accepts aStream.

printOn: aStream [
  "Print a represention of the receiver on aStream"
  <category: 'printing'>
  aStream
    nextPutAll: self class article;
    space;
    nextPutAll: self class name
]

So, for the Employee class it’s easy enough to include the birthDate:

printOn: stream [
  <category: 'printing'>
  super printOn: stream.
  stream nextPutAll: ' born on '. birthDate printOn: stream
]

Testing the code from before:

$ gst
GNU Smalltalk ready

st> FileStream fileIn: 'Employee.st'.
FileStream
st> e := Employee new.
an Employee born on nil
st> birthDate: (Date newDay: 14 month: #Feb year: 1990).
an Employee born on 14-Feb-1990
st>

Now it’s outputting the Employee’s birthDay as part of the display of the object.

I’ve still got failing tests to fix up tho’:

$ gst-sunit -f Employee.st -f EmployeeTest.st EmployeeTestCase
did not understand #isBirthday:
TestCondensedLog(TestVerboseLog)>>logError: (SUnit.star#VFS.ZipFile/SUnit.st:608)
TestCondensedLog>>logError: (SUnit.star#VFS.ZipFile/SUnit.st:668)
EmployeeTestCase(TestCase)>>logError: (SUnit.star#VFS.ZipFile/SUnit.st:870)

Oops, yes, need to add some code to determine whether or not a provided date is the employee’s birthday.

isBirthday: aDate [
  "Returns true if the provided date is the same as the birthDate of the receiver."
  <category: 'accessing'>
  ^((self isBirthdayMonth: aDate) & (self isBirthdayDay: aDate))
]

isBirthdayMonth: aDate [
<category: 'private'>
  "Returns true if the provided date is in the same month as the receiver's birthDate."
  ^birthDate month = aDate month
]

isBirthdayDay: aDate [
<category: 'private'>
  "Returns true if the provided date is the same day of the month as the receiver's birthDate."
  ^birthDate day = aDate day
]

This code is relatively simple, the only new syntax is the ^birthDate month = aDate month logic.

As I said above, by default Smalltalk returns self, the ^ operator indicates that the method should return the operand.

So, isBirthday: returns the logical and of isBirthdayMonth: and isBirthdayDay:.

Running the tests:

$ gst-sunit -f Employee.st -f EmployeeTest.st EmployeeTestCase
2 run, 2 passes

Yay! Success, the two tests are now passing, I can add -v to the arguments to gst-sunit:

$ gst-sunit -v -f Employee.st -f EmployeeTest.st EmployeeTestCase
Loading Employee.st
Loading EmployeeTest.st
EmployeeTestCase>>##testIsBirthdayWhenDateIsBirthday .
EmployeeTestCase>>##testIsBirthdayWhenDateIsNotBirthday .
2 run, 2 passes

Phew…it’s nearly 28C here, so that’s probably enough, next, getting some tests working for the core logic.