If you haven't seen closures before (e.g., `lambda' in Scheme or LISP, `\' in Hashell, `fun' in ML), the idea of a block may be somewhat confusing. This message is to try to explain one way to think about what a block does. (For those who have seen it before, we're going to use the beta rule from the lambda calculus.) Let's consider 1 argument blocks first. The simplest way to understand a block with one argument is to substitute the value of the actual argument for the formal parameter of the block. This is called the beta rule and is a reasonable approximation to the true semantics of blocks. For example, we may calculate the value of sending a 1-argument block the `value:' message as follows [ :x | x + 2 ] value: 3 = 3 + 2 = 5 A slightly more accurate way of conceiving the execution of blocks takes into account that the formal parameter is actually a local variable of the block's body. This is called the "environment model". In the environment model, you think of `[ :x | x + 2 ]' as a (unnamed) procedure that takes 1 argument, called `x', with body `x+2' (or `return x+2' for C fans). The passing of actual parameters to formals is model by bindings in the new environment. For example, the expression [ :x | x + 2 ] value: 3 creates a new environment in which the formal parameter variable `x' is bound to the value of the actual parameter, 3, and then runs the expression `x + 2' in that environment, so that when we look up the `x' during the evaluation of the expression `x + 2', we get 3. Therefore, as long as we don't assign to the formal parameter during the execution of the block's body, the execution is exactly the same as described by the beta rule. Another calculation may help: [ :y | (y + 2) printOn: Transcript. y ] value: 4 = (4 + 2) printOn: Transcript. 4 = "6 printed, then" 4 However, the above calculation does not show the details of the environment model. To do this, and to handle side effects like the above example, it's helpful to introduce more notation. Let `Effect(exp,env)' stand for the effect of expression `exp' in the environment `env'. We write environments (in ASCII) as `{ x |-> 3}', meaning the function that binds `x' to 3. The result of Effect is a pair containing a value and a new environment. For example Effect(y := 2, {y |-> 4}) = (2, {y |-> 2}). To formalize the treatment of environments, we also introduce two other pieces of notation. The notation `(val,env) - v', where (val,env) is a pair of a value and an environment is the pair (val,env2), where env2 is the same as env, except that it is undefined on `v'. The notation f + {x |-> y} means the function g such that g(x) = y, and for w not equal to x, g(w) = f(w). So we can calculate, for example: Effect([ :z | i := z + 1. z ] value: 3, {i |-> 2}) = Effect(i := z + 1. z, {i |-> 2} + {z |-> 3}) - z = Effect(i := z + 1. z, {i |-> 2, z |-> 3}) - z = Effect(z, {i |-> 4, z |-> 3}) - z = Effect(3, {i |-> 4, z |-> 3}) - z = Effect(3, {i |-> 4}) So in general, the meaning of a block with one argument is as follows: Effect([ :fm1 | body] value: act1, env) = Effect(body, env0 + {fml |-> v}) - fml where Effect(act1,env) = (v, env0) In simple cases, where the evaluation of the actual printer, act1, does not have any side effects, env = env0, and we have Effect([ :fm1 | body] value: act1, env) = Effect(body, env + {fml |-> v}) - fml where Effect(act1,env) = (v, env) In words, evaluate the body in an environment where the formal is bound to the actual, and return the result (together with any side effects on the environment). We could treat side-effects to the store similarly, but this would really get us into denotational semantics... Briefly, the meaning of a zero argument block is as follows Effect([ body ] value, env) = Effect([ :fresh | body] value: nil, env) where fresh is a variable that does not occur either in body or in the domain of env. Finally, the meaning of a n>1 argument block can be expressed in terms of the meaning of an n-1 argument block as follows: Effect([ :v1 :v2 ... :vn |body ] value: arg1 ... value: argn, env) = Effect(([ :v1 | [ :v2 ... :vn | body]] value: arg1) value: arg2 ... value: argn, env) I'll let you puzzle that out for yourself; or just try it out.