LambdaMessageSend: functional programming in Squeak
(an introduction)
by Stéphane Rollandin
hepta@zogotounga.net
Metaprogramming in Smalltalk
It is often said that the Smalltalk equivalent of a lambda expression is a block. While this is true in a practical sort of way, it should be emphasized that a block is a compiled piece of Smalltalk code (associated with an environment).
In Squeak we have class MessageSend
which is a frozen full message send: when evaluated, the MessageSend
selector is sent with the MessageSend
arguments to the MessageSend
receiver.
To me this looks like the form of choice for metaprogramming in Smalltalk, better than blocks.
Here is a simple MessageSend:
ms := MessageSend
receiver: 1
selector: #+
argument: 2
Doing ms value
returns 3
all right.
There is a severe limitation though: MessageSend
can not be nested.
Here enters LambdaMessageSend
, a subclass of MessageSend
: LambdaMessageSend
s can be nested.
Back to our example:
lms := LambdaMessageSend
receiver: 1
selector: #+
argument: 2
lms printString = '/{1 + 2}' "true"
Doing lms value
also returns 3
.
Now let's try this:
lms := LambdaMessageSend
receiver: lms
selector: #+
argument: 2
lms printString = '/{(1 + 2) + 2}' "true"
This time lms value
returns 5
.
The receiver has been evaluated along with the whole LambdaMessageSend
.
Variables
If we want to change the innermost selector in our example from #+
to #-
we can do so by doing lms receiver selector: #-
We can see that lms
now prints as '/{(1 - 2) + 2}'
and that lms value
indeed returns 1
. But this is a bit cumbersome.
Instead we can define a LambdaMessageSend
with a slot, like this:
lms := (LambdaMessageSend
receiver: (LambdaMessageSend
receiver: 1
selector: (LambdaSlot id: #op)
argument: 2)
selector: #+
argument: 2)
ofVariable: #op.
lms printString = /op.{(1 perform: <op> withArguments: #(2)) + 2}. "true"
lms value = lms "true"
The lms
we just created is actually a function of one variable (labelled #op
).
The last line of code above shows it evaluates to itself.
We can inject #+
into the slot by doing lms substituteSlot: (#op -> #+)
which returns a LambdaMessageSend
printing as '/{(1 + 2) + 2}'
, similar to the one we defined previously.
Note that lms
has not been changed by this substitution, so we can do lms substituteSlot: (#op -> #-)
and get in return the other LambdaMessageSend
, which prints as '/{(1 - 2) + 2}'
.
An usable API (let the fun begin)
Fortunately the horrible code above is not required to construct our function.
It can also be created this way:
lms := ((1 lambda: #(2)) + 2)
while the substitution can itself be performed like this:
lms <@ #+
(lms <@ #+) value = 5 "true"
We may also substitute and evaluate on the fly (this is a one-step evaluation; see below for details):
(lms <~ #+) = 5 "true"
These arrow-like selectors are the functional API for LambdaMessageSend
. There are many of them, and they make it real easy to program functionally in Smalltalk.
Let's see how easy it is with a few examples, where we play with a receiver or an argument instead of a selector:
1 + 2 + 2 "an expression we want to parametrize"
f := 1 + Lambda n + 2 "replacing the inner 2 with a slot"
f printString = '/n.{(1 + <n>) + 2}'
(f <~ -1) = 2 "true"
g := (1 + Lambda n + Lambda m) "replacing both arguments with slots"
g printString = '/n./m.{(1 + <n>) + <m>}'
(g <~~ #(10 100)) = 111 "true"
(g <~ 10 <~ 100) = 111 "true"
h := g <~ 10 "so what is this ?"
h printString = '/m.{11 + <m>}'
Auto-expansion
The simple way to built a lambda expression is based on the fact that a LambdaMessageSend
encoutering a message it does not understand will, instead of raising an error, return another lambda expression, an extended version of itself encompassing the message. This is the auto-expansion mechanism: we can always start with an atomic LambdaMessageSend
and have it grow automatically.
We use Lambda
to form an atomic expression (e.g. an identity function).
When Lambda
is sent a symbol, it returns an identity function using that symbol as the slot identifier.
For example:
Lambda x printString = '/x.{<x>}'
Lambda x <~ 'hello' = 'hello'
Since LambdaMessageSend
s do not understand #,
we can expand our function like this:
f := Lambda x, ' there' .
f <~ 'hello' = 'hello there'
It can be further expanded ad infinitum:
f := Lambda x, ' ', Lambda y .
f <~~ #('hello' 'world') = 'hello world'
f := f copyFrom: Lambda beg to: Lambda end .
f printString = '/x./y./beg./end.{((<x> , '' '') , <y>) copyFrom: <beg> to: <end>}'
f <~~ #('hello' 'world' 5 7) = 'o w'
Composition, quotation and high-order functions
Notice how substitution works:
((Lambda x + 1) <@ 10) printString = '/{10 + 1}'
(Lambda x + 1) <~ 10 = 11
((Lambda x + 1) <~ (Lambda y * 2)) printString = '/{/y.{<y> * 2} + 1}'
The last example seems weird; this is probably not what was intended.
Instead we would like the function Lambda y * 2
to replace the slot x
in Lambda x + 1
in order to obtain a new function of variable y
. So what is missing is the promotion of y
to the rank of variable for the overall resulting function.
This can be asked for explicitely by sending #ofVariable:
(((Lambda x + 1) <~ (Lambda y * 2)) ofVariable: #y) printString = '/y.{(<y> * 2) + 1}'
It can also be done by using #'<='
instead of #'<~'
((Lambda x + 1) <= (Lambda y * 2)) printString = '/y.{(<y> * 2) + 1}'
We can also force a LambdaMessageSend
to expand over a message it does understand by first quoting it.
#quoted
does the job:
Lambda g isLambdaMessageSend = true
Lambda g quoted isLambdaMessageSend isLambdaMessageSend = true
Thus a composition operator could be defined as follows:
compose := Lambda f quoted <= Lambda g. "see why we need #'<=' here ?"
compose printString = '/f./g.{<f> <= <g>}'. "true"
h := compose <~~ {Lambda x + 1 . Lambda y * 2}.
h printString = '/y.{(<y> * 2) + 1}'
Reduction and evaluation strategy
The algorithm followed when evaluating (or "reducing") a lambda expression is not trivial, in the sense that different results can be produced by different evaluation strategies for some higher-order expressions.
The reduction operated after substituting slots via #'<~'
is a one-step reduction in which, like in MessageSend>>#value
, the LambdaMessageSend
receiver is simply sent the selector with the arguments.
If no error is raised then we have the reduced value (else we consider that this LambdaMessageSend
can not be reduced).
A full reduction can also be performed by recursively reducing receiver, selector and arguments before evaluating the LambdaMessageSend
.
To fully reduce the expression we use #'<~&'
:
(((1 lambda + 2) * Lambda x) + 4 <~ 1) printString = '/{((1 + 2) * 1) + 4}'
(((1 lambda + 2) * Lambda x) + 4 <~& 1) = 7
Also, #fullyReduced
performs a full reduction and return the result (the initial expression is left unchanged as always)
(((1 lambda + 2) * Lambda x) + 4 <~ 1) fullyReduced = 7
This evaluation strategy is the default one, but it can be changed for a specific LambdaMessageSend
by sending it #withEvaluationStategy:
See the subclasses of LMSEvaluationStrategy
for the currently implemented strategies.
Normal order evaluation and lambda calculus
Sending #withNormalOrder
to a LambdaMessageSend
returns a lambda expression those evaluation strategy is normal-order (where the arguments are being substituted unevaluated). This is suitable for lambda calculus.
See Lambda
class-side methods for examples; the category 'lambda calculus'
provides a library of common combinators, and a simple (and slow) evaluator.
For example the library defines
(Lambda C: 2) printString = '/f./x.{<f> <~ (<f> <~ <x>)}' "2 as a Church numeral"
Lambda ZEROP printString = '/n.{(<n> <~ /a1.{/x./y.{<y>}}) <~ /x./y.{<x>}}' "Church numeral isZero test"
Lambda IFTHENELSE printString = '/a./b./c.{(<a> <~ <b>) <~ <c>}'
which can be fed to the evaluator as in
Lambda reduce: {#IFTHENELSE . {#ZEROP . {#C: . 2}} . true . false} "array-based lisp-like syntax"
...which returns false
The (in)famous fixed-point combinator Y
is also available:
Lambda Y printString = '/f.{/x.{<f> <~ (<x> <~ <x>)} <~ /x.{<f> <~ (<x> <~ <x>)}}'
(see LambdaTest>>#testY
to see it in action).
For the record, the equivalent combinator when using the default (applicative-order) evaluation strategy is
Lambda LMSY printString = '/f.{/x.{<x> <~ <x>} <~ (<f> <= /x.{<x> <@ <x>})}'
(you will find a derivation of this result in FunctionaltalkTest>>#testRecursion
)
Parameters (and a note on mutability)
In pure functional programming, functions are immutable. Indeed all operations we performed so far only modify copies of lambda expressions.
Now for practical purposes I found it very convenient to define particular slots in a lambda expression as being parameters, associated to a default value which we can change at will (this is extensively used in µO). In this regard immutability is broken.
For example here is how we can define a sine function which first extremum is a specific point:
| p x |
x := Lambda x.
p := Lambda point default: (Float pi@1); description: 'first extremum'.
sine := (((Lambda freq * x) sin * Lambda amp)
<<== {#freq -> (Float quoted pi / (2 * p x)) . #amp -> p y})
ofVariables: {x . p}.
sine printString = '/x./point.{((Float pi / (2 * <point> x)) * <x>) sin * <point> y}'. "true"
sine
is a function of two variables, one of them being a parameter.
Thus it has a default form:
sine default printString = '/x.{((Float pi / 6.283185307179586) * <x>) sin * 1}'
sine default <~& Float pi = 1.
sine reducedDefault printString = '/x.{(0.5 * <x>) sin * 1}'.
sine reducedDefault <~ Float pi = 1.
That default form can be changed by setting the parameter default value:
sine parametrize: #point default: 1@-1.
sine default printString = '/x.{((Float pi / 2) * <x>) sin * -1}'.
sine default <~& 1 = -1.
Compilation
Evaluating a lambda expression is slow. However it can be compiled for efficiency. Its compiled form (cached internally) is a block.
f := Lambda x * Lambda y.
tf := [100000 timesRepeat: [f <~~ #(5 10)]] timeToRun.
f compile.
tfcomp := [100000 timesRepeat: [f compiled value: 5 value: 10]] timeToRun.
tf / tfcomp > 450 "true"
Beware that the compiled form semantics is certain to be the same as the expression only if all the expression inner components (receivers, selectors, arguments) are non-lambdas arguments. It is thus very unsafe to compile high-order functions. Also note that evaluating a compiled form always implies a full reduction.
See FunctionalTest>>#testCompiledFormSemantics
for details.
Arrow operators summary
x := Lambda x.
y := Lambda y.
z := Lambda z.
operator
|
action
|
example
|
returns
|
|
|
x + (y * 10)
|
/x./y.{<x> + (<y> * 10)}
|
<~
|
reduce first variable
|
(x + (y * 10)) <~ 5
|
/y.{5 + (<y> * 10)}
|
<~~
|
reduce first variables
|
(x + (y * 10)) <~~ #(5 1)
|
15
|
<<~
|
reduce specific slot
|
(x + (y * 10)) <<~ (#y -> 5)
|
/x.{<x> + 50}
|
<<~~
|
reduce specific slots
|
(x + (y * 10)) <<~~ {#y -> 5 . #x -> 1}
|
51
|
<@
|
substitute first variable
|
(x + (y * 10)) <@ 5
|
/y.{5 + (<y> * 10)}
|
<@@
|
substitute first variables
|
(x + (y * 10)) <@@ #(5 1)
|
/{5 + (1 * 10)}
|
<<@
|
substitute specific slot
|
(x + (y * 10)) <<@ (#y -> 5)
|
/x.{<x> + (5 * 10)}
|
<<@@
|
substitute specific slots
|
(x + (y * 10)) <<@@ {#y -> 5 . #x -> 1}
|
/{1 + (5 * 10)}
|
<=
|
inline at first variable
|
(x + (y * 10)) <= (z + 1)
|
/z./y.{(<z> + 1) + (<y> * 10)}
|
<==
|
inline at first variables
|
(x + (y * 10)) <== {5 . z sqrt}
|
/z.{5 + (<z> sqrt * 10)}
|
<<=
|
inline at specific slot
|
(x + (y * 10)) <<= (#y -> (z + y))
|
/x./z./y.{<x> + ((<z> + <y>) * 10)}
|
<<==
|
inline at specific slots
|
(x + (y * 10)) <<== {#y -> z . #x -> z}
|
/z.{<z> + (<z> * 10)}
|
o:
|
composition
|
(x + 1) o: (y * 10)
|
/x.{(<x> + 1) * 10}
|
,<~
|
quoted reduction
|
(x + (y * 10)) ,<~ z
|
/x./y./z.{(<x> + (<y> * 10)) <~ <z>}
|
,<~~
|
quoted reduction
|
(x + (y * 10)) ,<~~ {1 . z}
|
/x./y./z.{((<x> + (<y> * 10)) <~ 1) <~ <z>}
|
,,<~
|
quoted reduction
|
(x ,<~ (y * 10)) ,,<~ (z + 1)
|
(/x./y.{<x> <~ (<y> * 10)} <~ /z.{<z> + 1})
|
,,<=
|
quoted inlining
|
(x + (y * 10)) ,,<= (z + 1)
|
(/x./y.{<x> + (<y> * 10)} <= /z.{<z> + 1})
|
to these we must add:
... which makes a total of 49 arrow operators !
Note that some of them may be equivalent depending on the evaluation strategy (for example under normal order #'<~'
does the same as #'<~&'
) and on the nature of their arguments (with a non-lambda argument #'<='
is equivalent to #'<~'
)
Download
The most current code is available on SqueakMap: check up the entry LambdaMessageSend.
It can be installed in a 5.1 or newer image (last tested on 5.2).
You can also get it here: FunctionalTalk-41.sar, although this may not be the latest version.