The endymion compiler

Introduction
Macros, any, every, expand, untrace, trace
Special forms

Introduction

The Endymion compiler is the piece of code that converts a symbolic expression into a Lisp expression, and then evaluates it. Here is an example; in non-verbose mode, only lines starting with `(1)' are printed. Normally, input is in red, errors are in blue, everything else is black. Example.

(1)  f(x):= let([u,v]=x, addl([u,v,2]));
Macro expansion -> f(x) := let([u, v] = x, addl([u, v, 2]))
Macro expansion <- f := nlambda(f, [x], let([u, v] = x, addl([u, v, 2])))
Making a value for f
f may be recursive.
Macro expansion -> let([u, v] = x, addl([u, v, 2]))
Macro expansion <- let([g2 = need_length_equal(x, 2), u = 0, v = 0], 

u := car(g2), g2 := cdr(g2), v := car(g2), addl([u, v, 2]))

(defun #:gensym:g1 (x)
  (let ((#:gensym:g2 (:need_length_equal x 2)) (u 0) (v 0))
       (setq u (:car #:gensym:g2))
       (setq #:gensym:g2 (:cdr #:gensym:g2))
       (setq v (:car #:gensym:g2))
       (:+ u v 2)
) )

(#:ed:symbs:set 'f f)

(1)                             <FUNCTION: f>

Let's explain what happens. The input expression has the form A:=B;, thus is an assignment of the LHS to the RHS. If you assign something to a variable, you can later on retrieve the value. If the LHS has the form f(x), you are defining a function; if it has the form f[x] you store someting in an array; if it has the form [x,y] you assign multiple variables. You say A::=B when you want to define a macro (this assigns something to f). Finally, assignments can be temporary, either implicit when a function is called and formal arguments are bound to actual values, or explicit, in a case like let(x=1,...).

You can see that Endymion says "Macro expansion -> foo" followed by "Macro expansion <- bar". This means that the macro-expanser has transformed "foo" into "bar". This is in general because the main operator is a macro. See the section macros for what are the predefined macros, and how to add new macros to the system. In order to avoid infinite loops, the main operator of "bar" should be different from that of "foo". In the example above, we have two expansions, with the same operator; this is correct, because we have two special operators that act in some cases as a macro, and in some other cases as a special form (see the section special forms). If f is a user macro such that f(x) expands to itself, then the macro-expanser pretends that its work is done; after that the compiler behaves like funcall(f,x), namely provokes an error. If f is a user macro such that f(x) expands to f(y) and f(y) expands to f(x), then after a number of calls, an error is signaled.

Special forms are operators known by the compiler; the list of all these is defined in this page (they can be accessed via the alphabetic index). They are special in that the arguments are not evaluated in a normal way. A typical special form is the if operator: evaluation of some arguments depend on the value of other arguments. As a consequence, in the example below, you cannot replace addn by let (a special form) or by repeat (a macro).

(2) let([f=addn, g= muln], if(2<3) then  f(1,2,3) else g(1,2,3));
(let ((f ':addn) (g ':muln))
     (if (< 2 3) (:funcall f 1 2 3) (:funcall g 1 2 3))
)

(2)                                   6

In the case of example (2), the macro-expander tried to expand the let, but nothing interesting happened, so that nothing was printed. The meaning of expression (2) is: define two temporary assignments, of f to addn and of g to muln, then apply one of these to some arguments, depending on some condition. Notice that the argument list is the same, and this can be factored as in

(3) let([f=addn, g= muln], (if(2<3) then  f else g) (1,2,3));

(let ((f ':addn) (g ':muln)) (:funcall (if (< 2 3) f g) 1 2 3))

(3)                                   6

Since addn is the functional version of addition and muln that of multiplication, our example is also if (sometest) then 1+2+3 else 1*2*3, and this gives 6, whatever the value of the test. In examples (2) and (3), the result of the compiler is a Lisp expression, that is printed on the terminal, then evaluated. They are much alike the symbolic code. There is one main difference. In Lisp, a symbol can have a functional value, and a value that is a function. If you say (f x), then the functional value of the symbol is used; if you say (funcall f x), then f is evaluated, and the result of that is applied; in symbolic mode, there is only one value, and the funcall can be omitted. As a consequence, (a+b)(c+d) is the application of one sum to the other, not an implicit product. The colon before the symbol in :addn or :funcall, means that the symbolic version is used.

Let's explain the second "macro expansion" of example (1), with a simpler case. The first argument of let is a list of equalities (brackets can be omitted if the list has only a single element). If an equality is a=b, this means that a is locally bound to b. If a is a list, each element is bound to the corresponding element of b. In the example, you can see that the list on the RHS is put in a temporary variable, each variable is initialised to zero, then to the correct value. Note that the compiler could test, in this example, that the list has the right length.

(4) let([u,v]=[1,2], 0);
Macro expansion -> let([u, v] = [1, 2], 0)
Macro expansion <- let([g3 = need_length_equal([1, 2], 2), u = 0, v = 0], 

u := car(g3), g3 := cdr(g3), v := car(g3), 0)

(4)                                   0

Note that the variable g3 above is really #:gensym:g3, but the package is not printed by the symbolic printer (but the Lisp printer prints it, see example (1)). The last expression printed by the compiler in the case (1) is (#:ed:symbs:set 'f f). As a result, the evaluator stores in some table, some value for the variable f; the value is a symbolic function named f (the Lisp printer prints the name of the function, the symbolic printer adds a prefix). The value of this function is #:gensym:g1, the function whose definition is given just above. The only non-trivial point is that the compiler replaces addl([u,v,2]) by u+v+2, because the compiler knows some properties of some functions.

Macros

A macro is something defined by the ::= operator, or is one of the built-in macros: one of :=, trace, untrace, do, let, and, or, in, case, ocase, <<, lambda, slet, slambda, and sequential_let. Some macros are defined in Endymion syntax, they are newl, expand, any, every, repeat, repeat_fix, kill, ratprotect, timing, Xdefine_array_function, Xdefarray, Xredefarray, RETURN, BREAK, break, NEXT, Xremember_lambda, make_get_set, catcherror, loopforever, incr1, and decr1.

A macro definition has the form f(x)::= buildq(x+1). In this case, each call to f(y) is replaced by y+1. The following forms f(x,y,[z])::= buildq(g(x,y,z)) and f(x,y,dot,z)::= buildq(g(x,y,z)) are equivalent, they define a macro with at least two arguments, and z will be bound to the list of all arguments, starting with the third. The body of the macro can be more complicated. In particular, it can depend on the number of arguments, and it is possible to access the value of any argument by position.

In a first approximation, buildq behaves like let; for instance, if the macro is f(x)::= buildq(a=x,b=g(x),a+b+x), an association list is created; it holds initially x=X, where X is the argument, then a=X is added (the x is replaced by its value), then b=g(X) is added, and the result is X+g(X)+X. This is independent of the value or form of the argument; there is a limited way of making the result depend on the argument. For instance (see example below), one can test the type of an argument; if you say b=g(splice(x)), this puts g(u,v) in b if x is u+v or [u,v]. More subtleties will be explained later. Here is an example of a non-trivial macro

remember_lambda(f,args,[body])::=
  local_macro(remaux(f,largs,body)::=
    buildq(table=gensym,res=gensym,
      alls=largs,
      [alls]=all,
      let(table=makearray("rem_table","hash",all,splice(alls)),
        f:=nlambda(f,largs,
             if test_array_element(table,splice(largs))
             then table[splice(largs)]
             else let(res=block(":=",splice(body)),
                      table[splice(largs)]:=res,
                      res)))),
  if type(args)=="list"
  then buildq(expand(w)=remaux(f,args,body),w)
  else buildq(expand(w)=remaux(f,[args],body),w));

The body of a macro can be local_macro(X,Y,Z,etc), where each but the last item is a macro definition, and the last item is a nl-macro-body; the body can be be a conditional, introduced by if, as can been seen in the example above, a normal body, introduced by buildq, an error body introduced by errwna, these three case as called nl-macro-body. Example (1) shows the case where there is no local macro in the list, in example (2) the body is missing; example (3) shows two local macros, it will be explained later; example (4) shows that the last item cannot have local macros; example (5) shows that these local macros must have different names. The body can be errwna(x). For a real example of use, see expand. Example (6) shows that errwna(x) accepts more than one argument. But at least one is required, and the first has to be an integer. Example (7) shows the error message in case the macro is expanded.

(1) f()::=local_macro(buildq(x));

(1)                                 FALSE

(2) f()::=local_macro();
Error : bad syntax in macro : f(...) ::= local_macro()

(3) foo(x,y)::= local_macro(a(x)::=buildq(x+1), b(x)::=buildq(x+2),
(3)     buildq(expand(w1) = a(x),  expand(w2) = b(y), f(w1,w2)));

(3)                                 FALSE

(4) f()::=local_macro(a()::=buildq(0), local_macro(xx ));
Error : bad syntax in macro : f(...) ::= local_macro(xx)

(5) f()::=local_macro(a(x)::=buildq(0), a(y)::=buildq(0),buildq(c));
Error : multiple local macros : f(...) ::= local_macro(a(...) ::= ..., 

a(...) ::= ..., ...)

(6) f([x])::=errwna(24,"foo") ;

(6)                                 FALSE

(7) f(1,2);
Error : user errwna : [f(1, 2), errwna(24, foo)]
(8) f()::=0;
Error : bad syntax in macro : f(...) ::= 0
(9) f()::=f();
Error : bad syntax in macro : f(...) ::= f()

In the case where a macro contains local macros, these are stored somewhere, and can be used explicitly in two cases. These macros must have unique names (two local macros cannot have the same name), but the scope is limited to the current macro. Said otherwise, inside a macro f you can have a local macro with the same name. In example (3) above, a statement like expand(w2) = b(y) means: expand the RHS, and store this in the variable w2. Hence, example (3) defines a macro foo(x,y) that expands to f(x+1,y+2). Here the local macros can be easily removed.

In the case of remember_lambda, the idea is that brackets around the second arguments are optional, so that remember_lambda(f, x, a(),b(),c()) is the same as remember_lambda(f, [x], a(),b(),c()). The macro behaves like f:=nlambda(f,[x],a(),b(),c()) (and here brackets are optional), with the exception that evaluations are remembered in a table. This is done by the commands if intable(x) then table[x] else compute_and_store(). The command test_array_element(T,x,y) returns true if the hash table T has an entry at (x,y), hence if T[x,y] is not undefined. Effective computation is done by let(res= block(":=", a(), b(), c()), T[x]:= res, res). The purpose of this complicated piece of code is that the body could execute RETURN(xx), this exits the current function with some value; here we have to trap (remember that RETURN(xx) is just return(":=";xx)), since all values must be remembered.

The table is defined by makearray("rem_table","hash",Tr,T1, T2, ...). Here the first argument is the name of the table (there is no way to access the table, so that its name is useless), the second argument says that it is a hash table, then comes the type of the array, and the type of the indices (all means that there is no type-check). If the remember-lambda has two arguments, we need 3 all in a row. Assume that the arguments of the function are x and y. Then the second argument of rem_aux is [x,y]. The line alls=largs makes a copy. The line [alls]=all has some special action. The list on the LHS can be [V], [V,G], [E,V], or [E,V,G] where 'E' stands for expand. The value of V should be a list; for each element of the list the RHS is evaluated, and the resulting list replaces the value of V. In our case, this will put [all,all] in alls. An non trivial example are the macros any and every. There is another example below. In the general case, local variables are substitued in the RHS. If expand is given, then local macros are expanded; this is the second case where local macros can be expanded. If G is given, then for each iteration a new symbol is created, this symbol can be used in the RHS. At the end, G will hold the list of all these variables. Example

(1) f([x])::= local_macro(g(x)::=buildq(B(x,x)),
(1) buildq(
(1)    [x,G] = (G  = A(x)),
(1)    [expand,x]=g(x),
(1)   C(x,G)));

(1)                                 FALSE

(2) f(a,b,c);
Macro expansion -> g(g1 = A(a))
Macro expansion <- B(g1 = A(a), g1 = A(a))
Macro expansion -> g(g2 = A(b))
Macro expansion <- B(g2 = A(b), g2 = A(b))
Macro expansion -> g(g3 = A(c))
Macro expansion <- B(g3 = A(c), g3 = A(c))
Macro expansion -> f(a, b, c)
Macro expansion <- C([B(g1 = A(a), g1 = A(a)), B(g2 = A(b), g2 = A(b)), 

B(g3 = A(c), g3 = A(c))], [g1, g2, g3])

(2)  C([

B(g1 = A(a), g1 = A(a)), B(g2 = A(b), g2 = A(b)), B(g3 = A(c), g3 = A(c))], 

[g1, g2, g3])

Conditional macros

The body of a macro can have the form if test then mac1 else mac2, where mac1 and mac2 are nl-macro-bodies (with a possible conditional in it). The test can be not test1, this is the negation of test1. Otherwise, it must be one of a=b, a<b, a>b, a<=b, a>=b, a<>b or a==c. The quantity b has to be an integer, c can be arbitrary. The quantity a is either an argument, or nbargs(), denoting the number of arguments of the macro, or arg(n), where n is an integer, denoting an argument of the macro, or type(y), operator(y) denoting the type or the operator of y, which is either an argument or of the form arg(n). Note: the type of something is either list for a list, number for an integer, atom for an atomic expression and expression otherwise. The operator of an atomic expression is none. In the case of a==c, if the LHS is a symbol, and the RHS is a string, then the RHS is converted to a symbol. Thus type(x)=="list" is true if x is a list. Examples

(1) f(x,y,[z]) ::= 
(1)   if(nbargs()=2) then 
(1)       if(x=="A") then buildq(1)
(1)       else if (arg(1)=="B") then buildq(2)
(1)       else if (arg(1)==C) then buildq(3)
(1)       else buildq(25)
(1)   else  if(nbargs() =3) then
(1)         if (arg(3)=="D") then buildq(4)
(1)         else if(type(x)==number) then  buildq(5)
(1)         else if(type(x)==atom) then  buildq(6)
(1)         else if(type(x)==expression) then  buildq(7)
(1)         else if(type(x)==list) then  buildq(8)
(1)         else buildq (impossible)
(1)   else  if(nbargs() >5) then
(1)      if(nbargs()>=7) then buildq(9)
(1)      else if(operator(x)==none) then buildq(10)
(1)      else if(operator(x)=="w") then  buildq(11)
(1)      else if(operator(arg(2))=="+") then buildq(12)
(1)      else if(operator(arg(2))=="[") then  buildq(13)
(1)      else if(operator(z)=="[") then buildq(14)
(1)      else buildq(impossible)
(1)   else if(x=250) then  buildq(15)
(1)   else if(x>=200) then buildq(16)
(1)   else if(x>100) then buildq(17)
(1)   else if(x<=10) then buildq(18)
(1)   else if(x<20) then buildq(19)
(1)   else if(x<>30) then buildq(20)
(1)   else buildq(21);

(1)                                 FALSE

This shows how to use the macro

(2) f("C",bar);
(2)                                   25
(3) f(1,2,D);
(3)                                   4
(4) f(1,2,3);
(4)                                   5
(5) f(w,2,3);
(5)                                   6
(7) f(w+1,2,3);
(7)                                   7
(8) f([w],2,3);
(8)                                   8
(9) f(1,2,3,4,5,6,7,8,9);
(9)                                   9
(10) f(1,2,3,4,5,6,7,8);
(10)                                  9
(11) f(1,2,3,4,5,6,7);
(11)                                  9
(12) f(1,2,3,4,5,6);
(12)                                  10
(13) f(w(1),2,3,4,5,6);
(13)                                  11
(14) f(ww(1),a+b,3,4,5,6);
(14)                                  12
(15) f(ww(1),[a+b],3,4,5,6);
(15)                                  13
(16) f(ww(1),a=b,3,4,5,6);
(16)                                  14
(17) f(250,2,3,4);
(17)                                  15
(18) f(200,2,3,4);
(18)                                  16
(19) f(201,2,3,4);
(19)                                  16
(20) f(101,2,3,4);
(20)                                  17
(21) f(10,2,3,4);
(21)                                  18
(22) f(9,2,3,4);
(22)                                  18
(23) f(19,2,3,4);
(23)                                  19
(24) f(11,2,3,4);
(24)                                  19
(25) f(20,2,3,4);
(25)                                  20
(26) f(100,2,3,4);
(26)                                  20
(27) f(37,2,3,4);
(27)                                  20
(28) f(30,2,3,4);
(28)                                  21

More examples, with some errors. If you look at example (6), you see that f(u, v, w) has been called; that f is some macro, containing the test arg(2) = 3 (it will be negated, but this is not indicated), and that arg(2) = v.

(1) f(x)::=if type(z)==y then buildq(x) else buildq(y);
Error : bad syntax in macro : f(x) ::= IF type(z) == y THEN ... ELSE ...

(2) f([x])::=if arg(2)=3 then buildq(x) else buildq(y);

(2)                                FALSE

(3) f(1);
Error : bad argument reference : [f(1), f(...) ::=
IF arg(2) = 3 THEN ...  ELSE ...]
(4) f(u,v,w);
Error : integer needed in macro expansion : [f(u, v, w), f(...) ::= 

IF arg(2) = 3 THEN ... ELSE ..., arg(2) = v]

(5) f([x])::=if not arg(2)=3 then buildq(x) else buildq(y);

(5)                                FALSE

(6) f(u,v,w);
Error : integer needed in macro expansion : [f(u, v, w), f(...) ::= 

IF arg(2) = 3 THEN ... ELSE ..., arg(2) = v]
(7) f(u,3,w);

(7)                                  y

(8) f(u,4,w);

(8)                              [u, 4, w]

Building the body

As explained above, the body of a macro contains buildq(a=b, c=d, ..., x=y, z) and each element but the last is an equality. Expressions b, d, y, z are evaluated (all elements in the current association list are replaced by their values), and a new item is added to the association list. The association list associates initially formal arguments and actual ones. It is an error if a name appears twice in the association list, for instance as in f(x,x)::=buildq(etc) or f(x)::=buildq(a=b,a=y,x);. It is an error if the LHS is not a name, as in f(x)::=buildq(a=b,g(x)=y,x);.

There are some exceptions to this rule. You can say expand(a)=b instead of a=b. In this case, local macros are expanded in the RHS. In the example below, we try to convert a+b into a-b and a*b into a/b. The only way to get the operator of an expression is via using a conditional in a local macro. This macro will return the new operator. Note: this cannot be a dash (syntax error), nor a string (that cannot be applied), hence we use symbol("-"). When the macro-expansor substitutes variables in the RHS, it replaces splice(x) by the elements of the list given as argument. For instance, if x is [a,b], then g(u,splice(x),v) is transformed in g(u,a,b,v). For instance kill is defined essentially as kill([x])::= buildq([x]=(x:=_undef_), << splice(x),done >>);. Thus kill(a,b) is the same as <<a:=_undef_,b:=_undef_,done>>, the rule below explains how the argument of splice is constructed.

Instead of a=b you can say arg(b)=a, args(b)=a, listify(b)=a, arguments(b)=a, string(b)=a, or args(b)=a. Note the order: the RHS is the variable that holds the result. If you say arg(3)=a, this puts the third argument into a, if you say args(3)=a, this stores in a the argument list without the first 3 ones. If you say arguments(b)=a, this puts in a the arguments of the expression b (for instance, if b is u+v, this yields [u,v]). If you say listify(b)=a, this adds also the operator, (for instance, if b is f(u,v), this yields [f,u,v]). Finally, string(b)=a converts the value into a string. As the example below shows, f(x,y) gives "(f x y)", because the Lisp printer is used.

(1) F([x])::= local_macro(k(x)::=if operator(x)=="+" then 
(1)    buildq(symbol("-")) else buildq(symbol("/")),
(1) buildq(
(1)   arg(1)=a,
(1)   arg(2)=b,
(1)   args(1) = c,
(1)   listify(a) =d,
(1)   arguments(a) = e,
(1)   expand(f) = k(a),
(1)   string(b) = g,
(1)  [a,b,c,d,e, f(splice(e)) ,g]));

(1)                                 FALSE

(2) F(a+b,c+d,e,f,g,h);
Macro expansion -> k(a + b)
Macro expansion <- symbol(-)
Macro expansion -> F(a + b, c + d, e, f, g, h)
Macro expansion <- [a + b, c + d, [c + d, e, f, g, h], [+, a, b], [a, b], 

symbol(-)(a, b), (+ c d)]

(2)  [a + b, c + d, [c + d, e, f, g, h], [+, a, b], [a, b], a - b, (+ c d)]

As already mentioned, in a=b the LHS can be [V], [V,G], [expand,V], or [expand,V,G]. Here V and G are variables, V is already know, G is new. The value of V should be a list. For each element of the list the RHS is evaluated, and the resulting list replaces the value of V. If expand is given, then local macros are expanded. If G is given, then for each iteration a new symbol is created, this symbol can be used in the RHS. At the end, G will hold the list of all these variables. We give here an example where each element of a list is replaced by the list itself. This has little interest; notice however how error messages are printed in the case where an error is signaled in a sub-macro.

(3) f(x)::= local_macro(
(3)      g(y)::= local_macro(
(3)         h(z,t)::= buildq([t]=z,t),
(3)        buildq(expand(a) = h(y,y), a)),
(3)    buildq(expand(b)=g(x),b));

(3)                                 FALSE

(4) f([A,B]);

(4)                            [[A, B], [A, B]]

(5) f(A);
Error : bad argument in splice : [f(A), f(...) ::= local_macro(g(...) ::= 

..., ...), g(A), g(...) ::= local_macro(h(...) ::= ..., ...), h(A, A), 

h(...) ::= buildq([t] = z), z = A]

any(p, x1,..., xn) (Macro with at least two arguments)

The macro is defined according to the code below; in this implementation no error is signalled in the case of one argument.

1   any(p,[L])::=
2      if nbargs()=1
3      then buildq (false) 
4      else buildq (begin=gensym,
5                   res=gensym,
6                   [L,G] = (G =makeseq(L)),
7                   E=G,
8                   [G,H] = (H=popseq(G)),
9                   [E]= endofseq(E),
10                let([res=false,splice(L)],
11                     tagbody(label(begin),
12                             if ?"or"(splice(E)) then done else
13                             let(G, if p(splice(H))
14                                    then res:=true else goto(begin))),
15                     res));

If you say any(f,[1,2,3]) this returns true if f(1) or f(2) or f(3) is true. You can say any(f,X,Y), the result is true if there is an index i such that f(X[i],Y[i]) is true; here X[i] denotes the ith element of the sequence associated to X. The expansion of any(f,X,Y) is the following

16  let([g14 = false, g15 = makeseq(X), g16 = makeseq(Y)], 
17    tagbody(
18      label(g13),
19      if endofseq(g15) or endofseq(g16)
20      then done
21      else let([g17 = popseq(g15), g18 = popseq(g16)],
22             if f(g17, g18)
23              then g14 := true else goto(g13))),
24      g14);

Let's explain in details what happens. Line 1 says that the macro takes at least one argument, say p, plus others, that are in a list L. Lines 2 and 3 say that, if only one argument is given, then macro returns false. In lines 4 to 9, we define some local variables begin, res, G, E, and H. The value of the first two variables is not gensym, but some new symbols, say g13 and g14. Line 6 contains [L,G] = (G =makeseq(L)). For each Li in L a Gi is created, Gi=makeseq(Li) is considered. The list of these quantities is put in L and the list of Gi in G. For instance, we might have [g15 = makeseq(X), g16 = makeseq(Y)] and [g15, g16]. Line 7 makes a copy of this list, and line 9 maps some operator on the list; as a result E will be [endofseq(g15), endofseq(g16)]. Line 8 is like line 6. This will put [g17 = makeseq(g15), g18 = makeseq(g16)] in G and [g17, g18] in H. Lines 10 to 15 produce the body of the macro. Line 12 reads if ?"or"(splice(E)) .... This is transformed into if ?"or"(endofseq(g15), endofseq(g16)) .... Since ?"or" is the same as symbol("or"), this line has the same meaning as line 19; as a consequence if the end of one sequence is seen, the loop stops, and any return false; otherwise, we say let(G,...), (see line 21), this puts the next element of the first sequence in g17 and the second one in g18. The expression p(splice(H)) applies the function to these arguments, if this gives true, then the result is set to true, otherwise, we continue looping.

every(p, x1,..., xn) (Macro with at least two arguments)

The macro is defined according to the code below; in this implementation no error is signalled in the case of one argument.

every(p,[L])::=
  if nbargs()=1 
  then buildq(true)
  else if nbargs()=2
  then buildq (begin=gensym,
                 res=gensym,
                 seq=gensym,
                 val=gensym,
                 arg(2)=x,
               let([res=true,seq=makeseq(x)],
                   tagbody(label(begin),
                           if endofseq(seq) 
                           then done
                           else let(val=popseq(seq),
                                    if p(val)
                                    then goto(begin)
                                    else res:=false)),
                   res))
  else buildq (begin=gensym,res=gensym,
                [L,G] = (G =makeseq(L)),
                E=G,
                [G,H] = (H=popseq(G)),
                [E]= endofseq(E),
               let([res=true,splice(L)],
                   tagbody(label(begin),
                           if ?"or"(splice(E)) 
                           then if ?"and"(splice(E))
                                then res:=true else res:=false
                           else let(G, if p(splice(H))
                                then goto (begin) else res:=false)),
                   res));

If you say every(f,[1,2,3]) this returns true if f(1) and f(2) and f(3) are true. This is the same as f(1) and f(2) and f(3) but can be used in the case where the elements of the list are not known a priori. You can say every(f,X,Y). The result is true if for every valid index i f(X[i],Y[i]) is true; here X[i] denotes the ith element of the sequence associated to X. In the case where some index is valid for one argument but not the other, the result is false. The body has the form if any(endofseq,G) then if every(endofseq,G) then true else false else action. Instead of using the every macro, we use the following if ?"or"(splice(E)) then if ?"and"(splice(E)) .... The case where the function takes a single argument is optimised. With two arguments, the expansion looks like this:

let([g14 = true, g15 = makeseq(X), g16 = makeseq(Y)], 
    tagbody(label(g13),
        if endofseq(g15) or endofseq(16) then 
          if endofseq(15) and endofseq(g16)
          then g14 := true
          else g14 := false
       else let([g17 = popseq(g15), g18 = popseq(g16)], 
       if fct(g17, g18) then goto(g13) else g14 := false)),
    g14)

expand(x, y,z ) (Macro with 1, 2 or 3 arguments)

The macro call the function expand3 with some arguments. It is described here. The macro is defined as follows:

expand([x])::=
    if nbargs()=1 
    then buildq(expand3(splice(x),maxposex,maxnegex))
    else if nbargs()=2 
    then buildq (expand3(splice(x),maxnegex))
    else if nbargs()=3
    then buildq(expand3(splice(x)))
    else errwna (1,"one two or three arguments");

untrace(x1, ..., xn) (Macro)

The untrace macro removes the trace of its arguments: untrace(foo) is the same as trace([foo, when=false]). Any number of arguments is allowed.

trace(x1, ..., xn) (Macro)

The trace macro can be used to trace functions and objects. For each argument X, an object Y is created, and the result is <<Y1,...,Ym,done>>. A non-list argument X is considered as the list of length one [X]. An argument should be of the form [A1, ... ,Ai, B1, ... ,Bj]. Each Ai is a symbol (the name of an object to be traced), and Bj is a specification. A specification is an equality, it can be entry=a, exit=b, array=c, fun=d, eval=d, simp=e, level=f, when=g. If no specification is given, when=true is assumed. Keywords fun=d and eval=d have the same meaning. If when=g is given, missing values are replaced by g. In this fashion, a set of specifications C is created, for each Ai, trace_one(Ai,C) is added to the result.

(1) trace(foo)?;
Macro expansion -> trace(foo)
Macro expansion <- {trace_one(foo, <<level = true, simp = true, fun = true, 

exit = true, array = true, entry = true>>), done}

(2) trace([foo,bar,fun=a,when=b])?;
Macro expansion -> trace([foo, bar, fun = a, when = b])
Macro expansion <- {trace_one(bar, <<level = b, simp = b, exit = b, 

array = b, entry = b, fun = a>>), trace_one(foo, <<level = b, simp = b, 

exit = b, array = b, entry = b, fun = a>>), done}
(3) untrace(foo)?;
Macro expansion -> untrace(foo)
Macro expansion <- trace([foo, when = FALSE])
Macro expansion -> trace([foo, when = FALSE])
Macro expansion <- {trace_one(foo, <<level = false, simp = false, 

fun = false, exit = false, array = false, entry = false>>), done}

Special forms

Assignments

The assignment operator is `:=', as in x:=1. It takes two arguments, so that symbol(":=")(x,y,z); is an error. In a case like x:=y:=1, this assigns to x the value of y:=1, so that both x and y will be defined to one. In a case like f():= g():=z; this defines f as a function without argument, that returns a function without argument that returns z. This function is called g. It happens that g is a closed variable of f, so that the global variable g is not modified. Details will be explained later. We start with some small examples.

(1)  x:=y:=1;

(1)                                   1

(2)  f():=g():=10;

(2)                             <FUNCTION: f>

(3)  f();

(3)                             <FUNCTION: g>

(4)  f()();

(4)                                   10

(5)  expop:=-5;
#:feval:expop : argument out of bounds : -5
(6)  [a,b,c]:=[1,2,3];

(6)                                  3

(7)  F(a,b,c);

(7)                              F(1, 2, 3)

(8)  x[1,2,3]:=4;
eval : not an array : 1[1, 2, 3] := 4

The assignment operator behaves sometimes like a macro. First of all, the LHS of the assignment is expanded; see examples (2) and (3) below, where Array(a,b,c) is a synonym of a[b,c]. In the case where the LHS is array reference, say array(a,x1,...,xn), the expansion is arrstore(a,v,x1,...xn), where v is the RHS.

(1) Array(x,[y])::=buildq(x[splice(y)]);

(1)                                 FALSE

(2) Array(a,b,c);
eval : not an array : a[b, c]
(3) Array(a,b,c):=d;
Macro expansion -> Array(a, b, c)
Macro expansion <- a[b, c]
Macro expansion -> Array(a, b, c) := d
Macro expansion <- arrstore(a, d, b, c)
eval : not an array : a[b, c] := d

It is possible to do multiple assignment in parallel. Examples

(1) [a,b]:=[1,2] ?; [a,b];

(2)                                 [1, 2]

(3) [[a,b,dot,c],d]:=[[1,2,3,4,5],6] ?; [a,b,c,d];


(4)                          [1, 2, [3, 4, 5], 6]

(5) [a,b]:=[1,2,3,4];
need_length_equal : length of list not 2 : [1, 2, 3, 4]
(6) [a,b,dot,c]:=[1];
need_length_greater : length of list not > 1 : [1]

The expansion of f(x):=y is f:=nlambda(f,x,y). This assigns to f a function named f. Thus a construct like a[x](y):=b; stores into the array a, at position x the function with one argument y that returns b, with name a[x]. The name is not exactlty this, but is obtained by the printer, see example (6) below.

(1) f(x)(y):=x+y;

(1)                            <FUNCTION: f>

(2) f(t);

(2)                          <FUNCTION: f(x)>

(3) %(17);

(3)                                17 + t

(4) V:=#vector(1,2,3,4,5)?; x:=1?;
(6) V[x^2](y):=b;

(6)                         <FUNCTION: V[x**2]>

(7) g(x):= if(x<=2) then 1 else g(x-1) + g(x-2);

(7)                             <FUNCTION: g>

(8) g(20) - #fib(20);

(8)                                  0

(9) g:= lambda(x, if(x<=19) then 1 else g(x-1) + g(x-2));

(9)                            <FUNCTION: u>

(10) g(20);

(10)                                  2

(11) a:=g?; g(x):=x?; 

(13) a(20);

(13)                                  37

Local assignments

If you say let(a=b,c), the effect is roughly the same as t:=a, a:=b, protect(c,a:=t), where t is a new variable. Remember that protect evaluates its first argument, and this gives the return value; but the second argument is evaluated, even in case of error. Hence, evaluation of let(a=b,c) leaves a unchanged (in weird situations, this may be false). The first item in a let can be a list, for instance let([a1=b1,a2=b2],c), and this is equivalent to t1:=a1, t2:=a2, a1:=b1, a2:=b2,protect(c,a1:=t1,a2:=t2). Whenever possible, the compiler uses a Lisp let, said otherwise, an anonymous function; this means that the old value of the variables are stored on the stack, rather than in temporary variables, and protect is not needed. Let's start with easy examples. We show in each case the Lisp code. In example (5) below you see a protect because expop is a special variable. In example (6), you will see what happens in a more complex situation. If the second assignment fails, the first one is not restored. For this reason, a let inside a let should be used in such cases.

(2) let(x=1,x) =x;

(:= (let ((x 1)) x) 'x)

(2)                                 1 = x

(3) let(x=1, let([y=x,x=2], [x,y]));

(let ((x 1)) (let ((y x) (x 2)) (:[ x y)))

(3)                                 [2, 1]

(4) let(x=1, let([x=2,y=x], [x,y]));

(let ((x 1)) (let ((x 2) (y x)) (:[ x y)))

(4)                                 [2, 1]

(5) let(expop=10, x);

(let ((#:gensym:g13 (:expop))) (:expop 10) (protect 'x (:expop #:gensym:g13)))

(5)                                   x

(6) let([expop=1/2,expon=1/3], car(0));

(let ((#:gensym:g21 1/2)
      (#:gensym:g23 1/3)
      (#:gensym:g22 (:expop))
      (#:gensym:g24 (:expon))
     )
     (:expop #:gensym:g21)
     (:expon #:gensym:g23)
     (protect (:car 0) (progn (:expop #:gensym:g22) (:expon #:gensym:g24)))
)

#:feval:expop : not a fixnum : 1/2

If you say let(a=b,c), the effect is rougly the same as t:=a, a:=b, protect(c,a:=t). As the example below shows, the LHS of the assignment a=b is expanded first. We might get something like x[y]=b. The assignment associated to this is arrstore(x,b,y), and the code looks like t:=array(x,y), arrstore(x,b,y), protect(c, arrstore(x,t,y)). Quantities x and y may be non-constant, so that they are evaluated only once, and temporaries are used. Example (5) below shows order of evaluation in the case of multiple assignments: the array, the value to store, the indices, and this for all array assignments. Then all old values are computed (statements of the form t:=array(x,y)). After that, we know that x is an array, and y is a valid index. Notice that the assignement arrstore(x,b,y) could fail (in the same way as the expop in the example above). If these assignments do not fail, then everything will be restored properly.

(1) f(x):=x+1;

(1)                             <FUNCTION: f>

(2)  Array(x,[y])::=buildq(x[splice(y)]);

(2)                                 FALSE

(3)  V:=#vector(1,2,3,4);

(3)                          <vector: 1, 2, 3, 4>

(4) let(Array(V,f(2)) = f(10), print(V));

<vector: 1, 2, 3, 11>

(4)                                  done

(5) let([Array(V,f(2))=f(10), Array(V,f(1))=f(30)], print(V));

(let ((#:gensym:g18 '#[1 2 3 4])
      (#:gensym:g19 (:funcall 'f 10))
      (#:gensym:g20 (:funcall 'f 2))
      (#:gensym:g21 0)
      (#:gensym:g22 '#[1 2 3 4])
      (#:gensym:g23 (:funcall 'f 30))
      (#:gensym:g24 (:funcall 'f 1))
      (#:gensym:g25 0)
     )
     (setq #:gensym:g21 (:array #:gensym:g18 #:gensym:g20))
     (setq #:gensym:g25 (:array #:gensym:g22 #:gensym:g24))
     (:arrstore #:gensym:g18 #:gensym:g19 #:gensym:g20)
     (:arrstore #:gensym:g22 #:gensym:g23 #:gensym:g24)
     (protect (:print '#[1 2 3 4]) 
              (:arrstore #:gensym:g18 #:gensym:g21 #:gensym:g20)
              (:arrstore #:gensym:g22 #:gensym:g25 #:gensym:g24)
)    )
<vector: 1, 2, 31, 11>

(5)                                  done

If you say let([a,b]=c,d), this binds a and b to the two elements of the list obtained by evaluating c. In the case let([a,dot,b]=c,d), the list must have at least one element (bound to a, the remaining will be bound to b. The example that follows combines some of the features described above.

(1) V:=#vector(1,2,3,4)?;
(2) let([[expop,b,dot,V[3]],d]=[[1,2,3,4,5],6], [expop,b,V[3],d]);

(let ((#:gensym:g28 (:need_length_equal (:[ (:[ 1 2 3 4 5) 6) 2))
      (#:gensym:g29 0)
      (b 0)
      (#:gensym:g31 '#[1 2 3 4])
      (#:gensym:g32 0)
      (d 0)
      (#:gensym:g30 (:expop))
     )
     (setq #:gensym:g29 (:need_length_greater (:car #:gensym:g28) 1))
     (setq #:gensym:g28 (:cdr #:gensym:g28))
     (setq d (:car #:gensym:g28))
     (:expop (:car #:gensym:g29))
     (setq #:gensym:g29 (:cdr #:gensym:g29))
     (setq b (:car #:gensym:g29))
     (setq #:gensym:g29 (:cdr #:gensym:g29))
     (setq #:gensym:g32 (:array #:gensym:g31 3))
     (:arrstore #:gensym:g31 #:gensym:g29 3)
     (protect (:[ (:expop) b (:array '#[1 2 3 4] 3) d) 
              (progn (:expop #:gensym:g30)
                     (:arrstore #:gensym:g31 #:gensym:g32 3)
)    )        )

(2)                          [1, 2, [3, 4, 5], 6]

(3) let(T=0,let([V[T++],V[T++]]=[7,8],print(V)));
<vector: 1, 7, 8, 4>

(3)                                 done

Sequential evaluation

If you say <<x,y,z>>, this evaluates arguments in order; the lisp code is (progn x y z). The less-less operator is a macro in that if only one argument is given, the expansion is this argument.


Valid XHTML 1.0 Strict back to home page © INRIA 2005, 2006 Last modified $Date: 2008/08/04 06:51:31 $