Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Slang
Last updated at 4:31 pm UTC on 9 April 2019

Overview

David T. Lewis (in a mail April 2nd 2019)

The term "Slang" refers to the subset of the Smalltalk language and objects that can directly translated to C (or other language, such as Javascript). It is not really a language in itself, rather it is a part of the existing Smalltalk environment in Squeak. For various reasons, the "slang" extensions are now maintained separately from the core of Squeak, but conceptually (and in early Squeak releases), the C translation capability should be considered an integral part of Squeak, as described in this original paper:

http://www.vpri.org/pdf/tr1997001_backto.pdf

The actual "slang" translator consists of a set of TMethod and TParseNode classes that are used to map the parse tree for a Smalltalk method into translated C code, along with a CCodeGenerator class that coordinates the translation process.

The Smalltalk to C (or Javascript) capability is not intended to be a general purpose languange. The general purpose language in this case is of course Smalltalk itself, and the slang translator serves as an optimizer to translate the virtual machine (which is written primarily in Smalltalk) into C to produce a high performance runtime.

Slang is not a new language.

It is just a specific way of writing Smaltalk code that facilitates automatic translations to other source languages like C. Slang is Smalltalk code that can be transpiled into other source code like C or Javascript.

Implementation

A code generator class is used to coordinate the process of translating Smalltalk classes into a high-level source code. This generator maps Smalltalk parse tree nodes into a set of TMethod and TParseNode classes which, in turn, do the actual translation. Look at CCodeGenerator or JSCodeGenerator for examples.

Examples

Smalltalk code intended to transpiled to other languages uses a sub-set of Smalltalk. It does not have blocks (except for a few control structures), message sending or even objects. dispatchOn:in: is mapped to a C switch{} statement specially to make the interpreter efficient. The package VMMaker contains many classes using the Slang subset of Smalltalk. The methods in classes such as Interpreter or SlangTests are the best sources to learn about Slang code. The class MemoryAccess also illustrates how low level memory operations often encounted in C programs can be written in Slang Smalltalk.

The typical sequence is:
  1. Write classes in Slang Smalltalk
  2. Instantiate a CodeGenerator (e.g. CCodeGenerator)
  3. add classes to this instance with addClass:
  4. To generate code file, send
  5. To generate a header file, send
Object subclass: #FooBar
       instanceVariableNames: 'counter'
       classVariablesNames: ''
       poolDictionaries: ''
       category:'Foo-FooBar'

foo
    ^self malloc: 100

counter
    ^counter + 1
We can now generate its corresponding C code with an instance of CCodeGenerator:
FooBarCG := CCodeGenerator new.
FooBarCG addClass: FooBar.  "add more classes like this"
...
FooBarCG storeCodeOnFile: 'foobar.c' doInlining: true.

Slang Operators

   "&"    "|"    and:    or:    not
   "+"    "-"   "//"    "\\"    min:    max:
  bitAnd: bitOr: bitXor: bitShift:
   "<"    "<="  "="     ">"     ">="    "~="   "=="
  isNil   notNil
  whileTrue:     whileFalse:    to:do:           to:by:do:
  ifTrue:        ifFalse:       ifTrue:ifFalse:  ifFalse:ifTrue:
  at:     at:put:
  <<      >>     bitInvert32    preIncrement     integerValueOf:
  integerObjectOf:              isIntegerObject: 

Slang Statements

Here are some examples of translations
Slang
C Code
instanceVariableNames: 'foregroundColor backgroundColor'
sqInt foregroundColor, backgroundColor;
classVariableNames: 'MemorySize'
#define MemorySize 10
^a+b
return (a+b);
a bitShift: 4
a >> 4;
now := FooBar foo: x bar: y
now = foobar(x,y);
^self bigEndian ifTrue: [16r6502] ifFalse: [16r0265]
return bigEndian() ? 0x6502 : 0x0265;
1 to: 10 by: 2 do: [:i | a at: 1 put: (i*2)]
for(i=1; i = 10; i += 2) { a[i] := (i*2); }
flag whileTrue: [ self check ]
while (flag) { check(); }
getName
  <returnTypeC: 'char *'>
  | newStr |
  var: #newStr type: 'char*'>
  newStr := 'helen'
  ^newStr
char *getName(void)
{
    char*newStr = "hello";
    return newStr;
}
defaultWidth
    <inline: true>
    ^10

width
   <inline: false>
   ^width ifNil: [ width := defaultWidth ].
static sqInt
width(void)
{
   return width == nilObj ? (width = 10) : width;
}

About the name

Slang is a language that rolls up its sleeves, spits on its hands, and goes to work. –Carl Sandburg, poet and biographer (1878-1967)

The name Slang was coined by Frank Zdybel during an Interval lunch at Swagat in Palo Alto in 1997. (verified by Craig Latta, who was at the lunch). It is unrelated to S-Lang (http://www.s-lang.org/).


See also