All commands, alphabetic order; letter E

This page contains the description of the following commands empty_seq, end, endofseq, eof, eol, eol, eq, eqdate, equal, error, err-return, Euler_phi, errcatch, errwna, eval, eval-hook, eval-trace, eval_when, evenp, every, evexit, evtag, EXAMPLES, exit, exp, expand, expand3, expand-path, explode, expon, expop, expr-to-cons,


empty_seq() (symbolic function)

This creates an empty sequence.

(1) X:=empty_seq();

(1)                   <UninitializedSequence: empty>

(2) makeseq(X);

(2)                     <InitializedSequence: empty>

(3) seq_to_list(%);

(3)                                  []

(end x) (Lisp function)

The end function takes zero or one arguments. Evaluation the functions terminates Endymion. If an argument is given the return status is OK (i.e. zero) if the argument is nil, not OK (i.e. one) otherwise. If nor argument is given, the return status is OK, and `Bye' is printed on the screen.

[Endymion] (end 1 2)
end : wrong number of arguments : 2 this should be at most 1
[Endymion] (end)
Bye
myself@mymachine$ echo $?
0

endofseq(x) (Symbolic function)

This returns true if the sequence is exhausted, false otherwise. See makeseq for details.

(eof n) (ITsoft)

If an end of file is seen while reading on channel N, then the channel is marked as closed, and (itsoft 'eof N) is called. In general, this will execute (eof N) (see the itsoft command, for details). The effect of (eof N) is to close then channel N (no error is signaled if that channel is already closed), and evaluate (exit eof N). However, if (in-read-flag) is true an error is signaled, in the form of (error 'read $errsxt11 N) (this prints: EOF during read). The function never returns.

(eol) (ITsoft)

Both functions (eol) and (flush) copy the current output buffer to the output channel (a file, or the terminal), between position 0 and (outpos), and replace all characters by a space, and set (outpos) to zero. The function (eol) outputs also a newline character, and sets the current position to the left margin. These functions are called (as an ITsoft) after printing (print and terpri call eol, prinflush calls flush) or when the buffer is full (if the right margin is reached, then eol is called, otherwise flush is called).

See the itsoft command for how (itsoft 'eol ()) calls in general (eol), but can call some other functions. The function could, for instance, print the current buffer on some transcript file, using the following method: fetch the content of the buffer, print it to channel 17, and in any case use the default behavior (via super-itsoft) to print the string. The important point here is that recursion should be avoided, in particular, the function should set outpos to a smaller value.

(#:display:eol) (Lisp function)

This function is the eol ITsoft used by the symbolic printer. Assume for instance that you want to display to the trace, and that channels C1, C2 and C3 are associated to the trace. Assume that channel C1 is opened as a list (by display-to-list or display-to-string, while C2 and C3 are associated to files or the console. The printer can use (#:display:flush) if the buffer has to be flushed or (#:display:eol) if moreover an end-of-line has to be added. Let S be the string to be printed; this string is in the buffer of the console.

In the case of C2 and C3, the behavior is: use outchan to switch to the channel, put S into its buffer, then call (super-itsoft 'display 'eol ()), or (super-itsoft 'display 'flush ()). In general, this will just print the string on the channel. However, you can redefine the ITsoft. In the case of C1, the channel holds a sequence of strings; eol will add S to the list, and flush will merge S with the last element of the list. In the case of eol, a marker is added to the list, so that if you call eol with A, eol with B, flush with C, eol with D, eol with E, the result is a sequence of four strings, A, B, CD, and E.

The behavior of (display-flush c) is the following. The argument c has to be a virtual channel (default, console, error, trace, or input). Assume that real channels C1, C2, C3 and C4 are associated to this channel, where C1, C2, C3 are as above, C4 is closed. Closed channels are ignored. An end-of-line marker is sent to all other channels; In the case of C1, a marker is inserted as in the case of (#:display:eol). For other channels, each channel is selected and (terpri) is called.

(eq x y) (Lisp function)

The eq function compares two expression, and returns true if they have the same address, and () otherwise. Small integers having the same value are at the same address. Two symbols with the same name have the same address. In other cases, objets can be different even if they print the same. Consider also equal.

[Endymion] (eq 1.2 1.2)
()
[Endymion] (eq 12 12)
true
[Endymion] (eq 'foo 'foo)
true
[Endymion] (eq '(foo) '(foo))
()
[Endymion] (setq x (list 1.2 '(foo)))
(1.2 (foo))
[Endymion] (setq y (list 1.2 '(foo)))
(1.2 (foo))
[Endymion] (eq (car x) (car y))
()
[Endymion] (setq y (append x ()))
(1.2 (foo))
[Endymion] (eq (car x) (car y))
true
[Endymion] (eq (cadr x) (cadr y))
true
[Endymion] (eq x y)
()

(equal x y) (Lisp function)

The equal function compares two objects and returns true if they are the same. Some objects can be circular. In the example that follows, we make x circular, and compare it to y. The result is false. After that, we make y circular. These two objects are of the form 1, 2, 3, etc,. so that equal will loop forever.

[Endymion] (equal 1.2 1.2)
true
[Endymion] (equal 12 12)
true
[Endymion] (equal 124567 124567)
true
[Endymion] (eq 124567 124567)
()
[Endymion] (equal 'foo 'foo)
true
[Endymion] (equal "foo" "foo")
true
[Endymion] (equal '(1 2 #[a b "c" (((a . b)))])'(1 2 #[a b "c" (((a . b)))]))
true
[Endymion] (progn (setq x '(1 2 3)) (nconc x x) (setq y '(1 2 3 1 2 3)))
(1 2 3 1 2 3)
[Endymion] (equal x y)
()
[Endymion] (progn (nconc y y) (cirequal x y))
()
[Endymion] (progn (cirprint x) (cirprint y) 0)
#1=(1 2 3 . #1#)
#1=(1 2 3 1 2 3 . #1#)
0

(eqdate date1 date2) (Lisp function)

The eqdate function returns true if both arguments are the same date. An error is signalled if one argument is not a date. Otherwise, the behavior is the same as equal. See also =date.

(error f m b) (Lisp function)

The error function takes three arguments; it generates an error. If you say (error a b c), the result is the same as (itsoft 'syserror (list a b c)).

[Endymion] (error 'function 'msg 'argument )
function : msg : argument
[Endymion] (error 'function errnva 'argument)
function : not a variable : argument
[Endymion] (setq errexp '(101 odd)) (error 'function 'errwna 4)
(101 odd)
function : wrong number of arguments : 4 this should be 101 or odd

(err-return T x1 ... xn) (Lisp special form)

The err-return special form takes at least two arguments. It behaves like exit. Said otherwise, the first argument has to be a symbol, that is the name of an active tag block. Remaining arguments are evaluated, and a throw to T is executed with, as value, the result of this last evaluation. However, it clears the error status flag just before throwing.

The idea is the following: the error functions calls the syserror ITsoft that the user can redefine freely; however, this function cannot return, thus must throw (an error is signaled if the error function returns...) An error may occur while trying to handle the error (or print the message, or whatever). As a consequence, the error function sets a boolean value, that must be cleared after the error has been sucessfully signaled. This is done by two function, just before throwing, by the default ITsofr, the function syserror, or the special function err-return. The flag is also reset by the toplevel loop before reading the next expression.

[Endymion] (defun #:foo:syserror (f m b) (printerror f m b) 
[Endymion] (print "error catched") (err-return #:system:error-tag 'ok))
#:foo:syserror
[Endymion] (setq #:sys-package:itsoft '(foo))
(foo)
[Endymion] (defun foo () (tag #:system:error-tag (car 0)))
foo
[Endymion] (list (foo) (foo))
car : not a list : 0
error catched
car : not a list : 0
error catched
(ok ok)

(Euler_phi n) (Lisp function)

The Euler_phi function takes as argument a positive integer and returns the Euler Phi function, the number of integers less that n and coprime to it. It can be defined as

(defun Euler_phi (n)
  (let ((r n) (res (ifactor n)))
       (while (consp res)
              (setq r (* r (- 1 (/ 1 (caar res)))) res (cdr res)))
       r))

Example

[Endymion] (Euler_phi 1)
1
[Endymion] (Euler_phi 2)
1
[Endymion] (Euler_phi 10)
4
[Endymion] (Euler_phi (** 2 10))
512
[Endymion] (Euler_phi (fact 300))
29827921150223119426338641365861204679578405812540474062644566253652500098212
02564096963259111590051565943188318717955246869468823382448945290806413268834
98497418151138786620286801199531305701194345380112454297075609769777180026088
29061764065095317377106760073411885845437291741751722674271986892649620441158
88325491778968055795478101723010142315296539483850580361329356443906384856714
81509680871156121091304545900109794358574402577391802809919397859470816946656
98186290321972971773485434557837816711532735151600237438566400000000000000000
000000000000000000000000000000000000000000000000000000000000000000000000000

errcatch(a,b,c) (Special symbolic form)

This special forms evaluates its second argument in protected mode. It first evaluates the first argument, as usual. This returns the list of tags to be be caught (it call be all or a single tag). After that the second argument is evaluated, yielding a list [f,m,v] in case of error, a value w otherwise. There are three cases to consider: if no error occured, then w is returned; if m is in the list a (or equal to a, or if a is all), then c is evaluated in a context where error_occured is the list [f,m,v]; otherwise, an error is signaled. The expression catcherror(a,b) is the same as errcatch (a,[b,false],[error_occured,true]). It always returns a list with two elements, the second being true in case of error. The macro is defined as

catcherror (a,[b])::=
    buildq( errcatch (a,[{splice(b)},false],[error_occured,true]));

Example. In case (1), we have shown the Lisp code that is evaluated. You can see how the Lisp special form catcherror is used to catch errors, and you see also the call to handle-errcatch. Note in cases (2) and (3), that this function gets a list whose second argument is the symbol #:endymion:errnla. In case of error, this symbol is evaluated, and you will see "not a list". It is converted to the formal symbol named errnla when put in error_occured and tested against the first argument of errcatch.

(1)  errcatch([errwna],funcall(car,1,2),error_occured);

(let ((#:gensym:g9 ()) (#:gensym:g10 ()) (#:gensym:g11 (:[ 'errwna)))
     (setq #:gensym:g9 
            (catcherror all
                        (prog1 (:funcall ':car 1 2) (setq #:gensym:g10 true))
     )      )
     (if #:gensym:g10
         #:gensym:g9
         (let ((error_occured
                  (#:ed:util:handle-errcatch #:gensym:g9 #:gensym:g11)
              ))
              error_occured
)    )   )

(1)                            [car, errwna, 2]

(2)  errcatch([errwna],funcall(car,1),error_occured);
car : not a list : 1

(3)  errcatch([errnla],funcall(car,1),[error_occured]);

(3)                            [[car, errnla, 1]]

(4) catcherror(all, funcall(car,1));

(4)                        [[car, errnla, 1], TRUE]

(5) catcherror(all, funcall(car,[1]));

(5)                               [1, FALSE]

errwna (Variable)

The variable #:endymion:errwna holds the error message associated to "Wrong number of arguments"; you can change it, for instance translate it into French. Inside a macro definition, it is a keyword, see the compiler.

(eval x) (Lisp function)

The eval function takes one argument. It evaluates it, and returns this result. Since eval is a function, its argument is evaluated (by eval), so that, in the example that follow, the argument is always evaluated twice. All Lisp objects are constant, except symbols or lists. This means that if the argument of eval is neither a list nor a symbol, the value is the object itself. Let's start with examples showing this rule:

[endymion] (eval 1.L0)
1.L0
[endymion] (eval 1.B0)
0.100000000000000000000000000000000000000e1
[endymion] (eval 1000000000000000000)
1000000000000000000
[endymion] (eval 1000000000000000000/3)
1000000000000000000/3
[endymion] (eval #C(1 2))
[2i+1]
[endymion] (eval "foo")
foo
[endymion] (eval 123)
123
[endymion] (eval 12.3)
12.3
[endymion] (eval #[1 2 3])
#[1 2 3]
[endymion] (eval #PD_s 2 +3*z +4*z^2 +5*z^3;)
#PD_s 2 +3*z +4*z^2 +5*z^3;
[endymion] (eval #M 2 2 1 2 3 4)
#MD 2 2 1 2 3 4

If you say something like (eval (quote (list 1 2))), the evaluator evaluates this expression using the rules described below. In this example, we have to appply eval to (quote (list 1 2)). Since eval is a normal function, the argument is evaluated, and the code of eval is executed. We have to apply quote to (list 1 2). Since quote is a special form, its argument is not evaluated. Moreover, quote returns its argument unchanged. Thus, the evaluation of (quote (list 1 2)) is (list 1 2). This is what eval evaluates. The expression shown above can be entered as (eval '(list 1 2)). The example that follows shows all calls to the evaluator in this case. There are four arrows pointing to the right. They correspond to: evaluation of the argument of traceval, evaluation of the argument to eval (as explained above, the quote special form does not call the evaluator), evaluation of the two arguments of list.

[Endymion] (traceval (eval (quote (list 1 2))))
--> (eval '(list 1 2))
--> '(list 1 2)
<-- (list 1 2)
--> (list 1 2)
--> 1
<-- 1
--> 2
<-- 2
<-- (1 2)
<-- (1 2)
(1 2)

Each symbol have three properties: a property list, a cell value, a function value. Evaluating a symbol consists, in general, of taking its cell value. This can be the special (uninterned) symbol _undef_, case where the symbol is undefined, and evaluating provokes an error. Some symbols have restrictions on their value. In this case a function is used to check the value. For instance, you change the current input base via (ibase 12), and you can get its value via (ibase). You can also get the value by evaluating the symbol itself.

[Endymion] (eval 'foo)
eval : undefined variable : foo
[Endymion] (setq foo 12)
12
[Endymion] (eval 'foo)
12
[Endymion] (eval 'ibase)
10
[Endymion] (setq ibase 9)
9
[Endymion] (eval 'ibase)
9
[Endymion] (ibase)
9

Consider now the case of a list. First, the list has to be a real list. In the case of a dotted pair, like (1 . 2) an error is signalled. An error is also signalled if the list is circular (in fact there is a limit on the length of the list). An error is signaled if the first element of the list is not a function (a symbol or a lambda form).

[Endymion] (eval (cons 'foo 'bar))
eval : bad end of list : (foo . bar)
[Endymion] (eval (list 'foo 'bar))
eval : undefined function : foo
[Endymion] (eval (list '12 'bar))
eval : undefined function : 12
[Endymion] (eval (list '(foo) 'bar))
eval : undefined function : (foo)
[Endymion] (eval (list "foo" 'bar))
eval : undefined function : foo

There are three types of functions: if foo is a normal function, evaluating (foo a b) consists in evaluating the arguments first, from left to right, then applying the body to these arguments. If foo is a special form, the body is applied to the arguments, unavaluated. If foo is a macro, evaluation proceeds as in the case of a special form. However, if the result is a list, with car A and cdr B, then the car of the form is replaced by A and the cdr by B (the form is (foo a b)). This form is evaluated again.

Special forms are defined by a C++ piece of code, examples are if, protect, quote, etc. Macros can be interpreted (user defined) or compiled. For instance ifn is a compiled macro. If you say something like (ifn a b c), the result is a list where the first element is replaced by if, and the second by the list containing not and the second argument. Said otherwise, it is (if (not a) b c). User macros can be defined via dmd. We give here an example of a macro.

[Endymion] (setq x '(ifn a b c))
(ifn a b c)
[Endymion] (eval x)
eval : undefined variable : a
[Endymion] x
(if (not a) b c)
[Endymion] (dmd Ifn (u . v) (mcons 'if (list 'not u) v))
Ifn
[Endymion] (setq y '(ifn a b c))
(ifn a b c)
[Endymion] (eval y)
eval : undefined variable : a
[Endymion] y
(if (not a) b c)

Functions have in general a fixed number of arguments. Special forms may have restrictions (for instance while takes at leat two arguments, setq wants an even number, etc). User functions can be defined by defun. In the case of foo shown below, three arguments are required, in the case of bar, at least three are required. If the number of arguments is invalid an error is signaled. Otherwise, arguments are evaluated, and the function is applied. In the case of foo, the first argument has to be a list, of length at least two (the first element will be bound to a, the second to b, remaining elements are ignored), and the third argument has to be a cons. These tests are done after all arguments are evaluated. The tree structure can be arbitrarily complex.

[Endymion] (defun foo ((a b) c (d . e)) (list a b c d e))
foo
[Endymion] (foo)
foo : wrong number of arguments : 0 this should be 3
[Endymion] (foo 1 2 3)
eval : illegal binding : 1
[Endymion] (foo '(1 2) 3 '(4 . 5))
(1 2 3 4 5)
[Endymion] (defun bar ((a b) c (d . e) . f) (list a b c d e f))
bar
[Endymion] (bar)
bar : wrong number of arguments : 0 this should be at least 3
[Endymion] (bar '(1 2) 3 '(4 . 5))
(1 2 3 4 5 ())
[Endymion] (bar '(1 2) 3 '(4 . 5) 6 7)
(1 2 3 4 5 (6 7))

A function is in general a symbol, but it can be a lambda form (see lambda). This is a list whose first element is lambda. In the example that follows, we define Foo, this behaves exactly like foo, except that you can say (funcall Foo ...) (the symbol is evaluated) or (funcall 'foo ...) (the symbol is not evaluated). See also here, the trace of this example. This page contains examples of the evaluator.

[Endymion] (setq Foo (lambda ((a b) c (d . e)) (list a b c d e)))
(#:system:lambda 3 ((a b) c (d . e)) (list a b c d e))
[Endymion] (setq Bar (lambda ((a b) c (d . e) . f) (list a b c d e f)))
(#:system:lambda -4 ((a b) c (d . e) . f) (list a b c d e f))
[Endymion] (eval (cons Foo '('(1 2) 3 '(4 . 5))))
(1 2 3 4 5)
[Endymion] (eval (cons Bar '('(1 2) 3 '(4 . 5) 6 7)))
(1 2 3 4 5 (6 7))

(eval-hook x) (Lisp function)

The eval-hook argument takes one argument. If this is not a list, nothing happens. Otherwise, all elements in the list are evaluated, one after the other. If the element is not a function with zero argument, the value of the element is nil. Otherwise the function is called. The result of the hook is the result of the last execution. However, if one function call provokes an error, evaluation of the hook is silently aborted. The result is nil in this case.

[Endymion] (setq A (lambda () (print 'ok))
[Endymion]      B (lambda () (print 'ok2))
[Endymion]     C (lambda (x) (print 'ok3))
[Endymion]    D (lambda () (car 0)))
(#:system:lambda 0 () (car 0))
[Endymion] (eval-hook (list A C B))
ok
ok2
ok2
[Endymion] (eval-hook (list A C))
ok
()
[Endymion] (eval-hook (list A B C D A B C D))
ok
ok2
()
[Endymion] (traceval (eval-hook '#.(list A B D)))
--> (eval-hook '((#:system:lambda 0 () (print 'ok)) (#:system:lambda 0 () (
print 'ok2)) (#:system:lambda 0 () (car 0))))
--> '((#:system:lambda 0 () (print 'ok)) (#:system:lambda 0 () (print 'ok2)) 
(#:system:lambda 0 () (car 0)))
<-- ((#:system:lambda 0 () (print 'ok)) (#:system:lambda 0 () (print 'ok2)) (
#:system:lambda 0 () (car 0)))
-->(hook) (#:system:lambda 0 () (print 'ok))
--> (print 'ok)
--> 'ok
<-- ok
ok
<-- ok
<-- ok
-->(hook) (#:system:lambda 0 () (print 'ok2))
--> (print 'ok2)
--> 'ok2
<-- ok2
ok2
<-- ok2
<-- ok2
-->(hook) (#:system:lambda 0 () (car 0))
--> (car 0)
--> 0
<-- 0
Throw to: error-tag ok 0
<-- ()
()

eval-trace (Lisp variable/function)

The eval-trace variable controls whether or not the evaluator is verbose. The internal value is true or false; anything different from nil is true, show as true. The traceval special form sets temporarily eval-trace to true. The eval-trace variable can also be used as a function with zero or one arguments.

[Endymion] (defun foo(x)(let ((eval-trace true)) (eval x)))
foo
[Endymion] (defun bar(x)(let ((eval-trace false)) (eval x)))
bar
[Endymion] (foo '(car (+ 1 2)))
--> (eval x)
--> x
<-- (car (+ 1 2))
--> (car (+ 1 2))
--> (+ 1 2)
--> 1
<-- 1
--> 2
<-- 2
<-- 3
car : not a list : 3
Throw to: error-tag ok 0
eval-trace<-- ()
[Endymion] (traceval (bar '(car (+ 1 2))))
--> (bar '(car (+ 1 2)))
--> '(car (+ 1 2))
<-- (car (+ 1 2))
x--> (car (+ 1 2))
--> (let ((eval-trace false)) (eval x))
--> ((lambda (eval-trace) (eval x)) false)
--> (lambda (eval-trace) (eval x))
--> (#:system:lambda 1 (eval-trace) (eval x))
<-- (#:system:lambda 1 (eval-trace) (eval x))
<-- (#:system:lambda 1 (eval-trace) (eval x))
--> false
<-- ()
eval-trace--> ()
car : not a list : 3
x<-- _undef_

eval_when(L,x1,..xn) (Symbolic special form)

The first argument L should be a list. If it contains eval, then other elements in the list are evaluated. The situation changes if the file is compiled. If the list contains read, then the expressions xi are evaluated at read time. If the list contains compile, then the expression is handled as if it were {x1,...,xn}.

(evenp n) (Lisp function)

This function takes as argeument an integer. It returns the number if it is even, and false otherwise.

[Endymion] (evenp 1/2)
evenp : not a fixnum : 1/2
[Endymion] (oddp 1/2)
oddp : not a fixnum : 1/2
[Endymion] (evenp 10)
10
[Endymion] (oddp 10)
()
[Endymion] (evenp 123456789012345678901)
()
[Endymion] (oddp 123456789012345678901)
123456789012345678901

(every f arg1 ... argn) (Lisp function)

every(f, arg1, ..., argn) (Symbolic macro)

The every function returns true if every application of f to the k-th element of teh arguments returns true; see map. See the compiler for the symbolic macro.

(evtag tagname b1 ... bn) (Lisp special form)

This is a variant of tag where the first argument is evaluated. See also exit.

(EXAMPLES) (Lisp function)

The EXAMPLES function returns a list numbers that are used for testing the speed of the factorisation algorithm of sisyphe, hyperion and Endymion.

(exit tag a1 a2 ... an) (Lisp special form)

(evexit tag a1 a2 ... an) (Lisp special form)

The exit and evexit special forms take at least two arguments. The first argument has to be a symbol. It is not evaluated by exit but it is evaluated by evexit (this is the only difference between these two special forms). This symbol should be the name of a catch handler, that is, the first argument of a tag that is executed. In this case, arguments ai are evaluated, and the evaluation of the last becomes the result of the tag. See examples under tag. It is an error to use the exit special form while another exit is active (inside a protect for instance). If you say (exit #:system:error-tag ()), this interrupts the current evaluation. This command is executed by the error handling function.

[Endymion] (tag foo (exit foo 0))
0
[Endymion] (evtag (concat "foo") (evexit (concat "foo") 2))
2
[Endymion] (exit foo 0)
exit : undefined escape : foo
[Endymion] (exit #:system:error-tag 0)
[Endymion] (tag foo (protect (exit foo 1) 2))
1
[Endymion] (tag foo (protect (exit foo 1) (car 0)))
In throw !!
car : not a list : 0
Internal error, unwind in unwind
1

(exp n) (Lisp/symbolic function)

These functions compute the exponential of the argument. The Lisp function wants a number as as argument, and returns a number; the symbolic function always computes %e^n. The exponential function is the inverse of the logarithm. Since the logarithm is multivaluated, simpfication is automatic only in one way. See also description of the function log and the variables logsimp, logexpand.

(1) exp(100) = #exp(100);

                           100
(1)                      %e    = 2.68811714181614e+43

(2) #exp(a);
exp : not a real number : a
(3) exp("foo");
exp : Cannot compute : **(%e, foo)
(4) exp(a*log(b));

                                    a log(b)
(4)                               %e

(5) let(logsimp=all, exp(a*log(b)));

                                       a
(5)                                   b

(6) [exp(log(x)), log(exp(x)), let(logexpand=true, log(exp(x))) ];

                                         x
(6)                            [x, log(%e ), x]

expand(x, p, n) (Symbolic macro with 1, 2 or 3 arguments)

The expressions expand(x), expand(x,p) and expand(x,p,n) reduce to expand3(x,p,n), explained below, with the same arguments, and maybe some others. The default value of the second argument is maxposex. The default value of the third argument is maxnegex. The source of the macro is shown here. Note that expand(x) can also be used, with a different meaning, in the body of a symbolic macro, see the compiler.

(expand3 x p n) (Symbolic function

This command checks that the arguments P and N are non-negative integers, sets temporarily expop to P and expon to P, and re-simplifies X. If we denote this function by S(X), then S(X) can be defined as follows. If X is a sum, a product, a power, then S is applied to the arguments, and the +, * or ** is called. If X is an expression, a set, a list, an equality, then S is mapped on the argument; the structure of the object is left unchanged. If X is a rat, it is converted to a general expression. Lines 8 and 9 are a bit strange. We evaluate f(x), where f and x are powers. In case 9, expop is positive while evaluating the expression, so that everything is expanded; in case 8, is is not, and the function is not expanded (only the arguments).

(1) E:=f((a+b)^5, 2*(c+d), (u+v)^(-7));

                        /       5                1    \
(1)                    f|(a + b) , 2 (c + d), --------|
                        |                            7|
                        \                     (u + v) /

(2) expand(E);


      / 5    5        4       2  3       3  2      4
(2)  f|a  + b  + 5 a b  + 10 a  b  + 10 a  b  + 5 a  b, 2 c + 2 d, 
      |
      \

                                  1                                  \
---------------------------------------------------------------------|
 7    7        6       2  5       3  4       4  3       5  2      6  |
u  + v  + 7 u v  + 21 u  v  + 35 u  v  + 35 u  v  + 21 u  v  + 7 u  v/

(3) expand(E,1,0);

                        /       5                1    \
(3)                    f|(a + b) , 2 c + 2 d, --------|
                        |                            7|
                        \                     (u + v) /

(4) expand(E,6,0);

      / 5    5        4       2  3       3  2      4                  1    \
(4)  f|a  + b  + 5 a b  + 10 a  b  + 10 a  b  + 5 a  b, 2 c + 2 d, --------|
      |                                                                   7|
      \                                                            (u + v) /

(5) expand(E,0,10);


      /       5
(5)  f|(a + b) , 2 c + 2 d, 
      |
      \

                                  1                                  \
---------------------------------------------------------------------|
 7    7        6       2  5       3  4       4  3       5  2      6  |
u  + v  + 7 u v  + 21 u  v  + 35 u  v  + 35 u  v  + 21 u  v  + 7 u  v/

(6)  F:=[(a+b)**2 = {3*(c+d)}];

                                   2
(6)                        [(a + b)  = {3 (c + d)}]

(7) expand(F);

                         2    2
(7)                    [a  + b  + 2 a b = {3 c + 3 d}]


(8) expand( ((a+b)^2) ((c+d)^3));

                            2   3    3        2      2
(8)                 ((a + b) )(c  + d  + 3 c d  + 3 c  d)

(9) let(expop=43, ((a+b)^2) ((c+d)^3));

                   2    2           3    3        2      2
(9)              (a  + b  + 2 a b)(c  + d  + 3 c d  + 3 c  d)

(expand-path x) (Lisp function)

The expand-path takes an argument. If this is not a name, it is returned. It if does not start with a tilde, or contain a dollar, it is returned. An initial ~foo is replaced by its expansion. Here the name is the longest string not containing a slash. The C procedure getpwnam is used to find the home dir of the user named foo (depending on the OS, another method may be used). The shell variable HOME is used in the case of an empty name. If something is found, it replaces the ~foo part. After that, for every dollar sign, a string like $FOO is replaced by the value of the shell variable FOO (if it exists). Here the longest name that contains no slash and no dollar is considered.

[Endymion] (expand-path 123)
123
[Endymion] (expand-path #[1 2 3])
#[1 2 3]
[Endymion] (expand-path 'foo)
foo
[Endymion] (expand-path "~")
/user/grimm/home
[Endymion] (expand-path "~grimm")
/user/grimm/home
[Endymion] (expand-path "~grimm/a")
/user/grimm/home/a
[Endymion] (expand-path "~/a")
/user/grimm/home/a
[Endymion] (expand-path "~unknown")
~unknown
[Endymion] (expand-path "~unknown/a")
~unknown/a
[Endymion] (expand-path "~/$USER/$TERM$FOO")
/user/grimm/home/grimm/xterm$FOO

(explode x) (Lisp function)

This function behaves like print-to-string but instead of producing a string of character, it returns a list of character codes.

expon (Symbolic variable)

This variable controls the maximum negative exponent for which powers are expanded. See expop below

expop (Symbolic variable)

This variable controls the maximum positive exponent for which powers are expanded. Variables expop and expon must be non-negative integers, less than one million. An exponent n is said to be in range if it is no greater than expop, and if negative, no greater in absolute value than expon.

When x^n is simplified, where x is a Rat, then rat_arith_mixed_flag is considered. If the flag is 'general', or if n is not an integer, then the Rat is converted to an general expression, and this quantity is raised to the power n. If the flag is mixed, or if the exponent is not in range, no simplification occurs. Otherwise, the rat is raised to the power n, and expanded. If x is a sum or a product, the expression is expanded if the exponent is in range. In a case like 1/((a+b)*(c+d)), the product of sums is expanded if expop is non-zero (and the result is inverted). In a case like 1/(a+b)/(c+d), the denominator contains a product of sums, and expansion occurs if expon is non-zero. If a sum appears in a product, it is expanded if either one of expop or expon is non-zero (if the product has only two factors, one of them is an integer, expansion occurs if negdistrib is all, or if it true, and the number is minus one.

(1)  [(a+b)*c, (a+b)*(c+d), (a*b)^4, (a*b)^-4, (a+b)^4, (a+b) ^-4];

       [                                 4    1            4     1    ]
(1)    [c (a + b), (a + b) (c + d), (a b) , ------, (a + b) , --------]
       [                                         4                   4]
       [                                    (a b)             (a + b) ]

(2)  expop:=10;

(2)                                   10

(3)  [(a+b)*c, (a+b)*(c+d), (a*b)^4, (a*b)^-4, (a+b)^4, (a+b) ^-4];

                                         4  4    1      4    4        3
(3)  [a c + b c, a c + a d + b c + b d, a  b , ------, a  + b  + 4 a b
                                                    4
                                               (a b)

      2  2      3       1
 + 6 a  b  + 4 a  b, --------]
                            4
                     (a + b)

(4)  expon:=10;

(4)                                   10

(5)  [(a+b)*c, (a+b)*(c+d), (a*b)^4, (a*b)^-4, (a+b)^4, (a+b) ^-4];

                                         4  4    1     4    4        3
(5)  [a c + b c, a c + a d + b c + b d, a  b , -----, a  + b  + 4 a b
                                                4  4
                                               a  b

      2  2      3                     1
 + 6 a  b  + 4 a  b, -----------------------------------]
                      4    4        3      2  2      3
                     a  + b  + 4 a b  + 6 a  b  + 4 a  b


(6)  expop:=0;

(6)                                   0

(7)  [(a+b)*c, (a+b)*(c+d), (a*b)^4, (a*b)^-4, (a+b)^4, (a+b) ^-4];

                                             4    1           4
(7)  [a c + b c, a c + a d + b c + b d, (a b) , -----, (a + b) , 
                                                 4  4
                                                a  b

                 1
-----------------------------------]
 4    4        3      2  2      3
a  + b  + 4 a b  + 6 a  b  + 4 a  b

(9) expand(2*(a+b)*(u+100)^-10);
                                                                           2
%1 := 100000000000000000000 + 10000000000000000000 u + 450000000000000000 u

                      3                    4                  5
 + 12000000000000000 u  + 210000000000000 u  + 2520000000000 u

                6              7           8         9    10
 + 21000000000 u  + 120000000 u  + 450000 u  + 1000 u  + u


                                  2 a   2 b
(9)                               --- + ---
                                  %1    %1

(#:ed:term:expr-to-cons x) (Lisp function)

This is a useful function to understand what is in an expression. It returns a list with the type of expression, the name of the operator and the arguments. The type is 0 for an operator with one argument, 1 for an operator with two arguments, 2 for a general operator, 3 for a sum, 4 for a product, and 5 for a power. If the operator is a symbolic one, we add ten to this number, and use its name for the second argument.

(1)  [f(),f(x),f(x,y), f(x,y,z), a+b,a*b,a**b];

                                                              b
(1)             [f(), f(x), f(x, y), f(x, y, z), a + b, a b, a ]

(2) bye();

exiting symbolic mode
[Endymion] %
[#:fexpression:#[f ()] #:fexpression:#[f x] #:fexpression:#[f (x . y)] 
#:fexpression:#[f (x y z)] #:fexpression:#[+ (a b)] #:fexpression:#[* (a b)] 
#:fexpression:#[** (a . b)]]
[Endymion] (mapcar '#:ed:term:expr-to-cons (#:ed:term:expr-to-cons %))
((12 f) (10 f x) (11 f x y) (12 f x y z) (3 + a b) (4 * a b) (5 ** a b))

Valid XHTML 1.0 Strict back to home page © INRIA 2005, 2006 Last modified $Date: 2009/01/08 17:43:30 $