XEmacs 21.2-b1
[chise/xemacs-chise.git.1] / lisp / byte-optimize.el
1 ;;; byte-opt.el --- the optimization passes of the emacs-lisp byte compiler.
2
3 ;;; Copyright (c) 1991, 1994 Free Software Foundation, Inc.
4
5 ;; Author: Jamie Zawinski <jwz@netscape.com>
6 ;;      Hallvard Furuseth <hbf@ulrik.uio.no>
7 ;; Keywords: internal
8
9 ;; This file is part of XEmacs.
10
11 ;; XEmacs is free software; you can redistribute it and/or modify it
12 ;; under the terms of the GNU General Public License as published by
13 ;; the Free Software Foundation; either version 2, or (at your option)
14 ;; any later version.
15
16 ;; XEmacs is distributed in the hope that it will be useful, but
17 ;; WITHOUT ANY WARRANTY; without even the implied warranty of
18 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 ;; General Public License for more details.
20
21 ;; You should have received a copy of the GNU General Public License
22 ;; along with XEmacs; see the file COPYING.  If not, write to the 
23 ;; Free Software Foundation, Inc., 59 Temple Place - Suite 330,
24 ;; Boston, MA 02111-1307, USA.
25
26 ;;; Synched up with: FSF 19.30.
27
28 ;;; Commentary:
29
30 ;; ========================================================================
31 ;; "No matter how hard you try, you can't make a racehorse out of a pig.
32 ;; You can, however, make a faster pig."
33 ;;
34 ;; Or, to put it another way, the emacs byte compiler is a VW Bug.  This code
35 ;; makes it be a VW Bug with fuel injection and a turbocharger...  You're 
36 ;; still not going to make it go faster than 70 mph, but it might be easier
37 ;; to get it there.
38 ;;
39
40 ;; TO DO:
41 ;;
42 ;; (apply '(lambda (x &rest y) ...) 1 (foo))
43 ;;
44 ;; maintain a list of functions known not to access any global variables
45 ;; (actually, give them a 'dynamically-safe property) and then
46 ;;   (let ( v1 v2 ... vM vN ) <...dynamically-safe...> )  ==>
47 ;;   (let ( v1 v2 ... vM ) vN <...dynamically-safe...> )
48 ;; by recursing on this, we might be able to eliminate the entire let.
49 ;; However certain variables should never have their bindings optimized
50 ;; away, because they affect everything.
51 ;;   (put 'debug-on-error 'binding-is-magic t)
52 ;;   (put 'debug-on-abort 'binding-is-magic t)
53 ;;   (put 'debug-on-next-call 'binding-is-magic t)
54 ;;   (put 'mocklisp-arguments 'binding-is-magic t)
55 ;;   (put 'inhibit-quit 'binding-is-magic t)
56 ;;   (put 'quit-flag 'binding-is-magic t)
57 ;;   (put 't 'binding-is-magic t)
58 ;;   (put 'nil 'binding-is-magic t)
59 ;; possibly also
60 ;;   (put 'gc-cons-threshold 'binding-is-magic t)
61 ;;   (put 'track-mouse 'binding-is-magic t)
62 ;; others?
63 ;;
64 ;; Simple defsubsts often produce forms like
65 ;;    (let ((v1 (f1)) (v2 (f2)) ...)
66 ;;       (FN v1 v2 ...))
67 ;; It would be nice if we could optimize this to 
68 ;;    (FN (f1) (f2) ...)
69 ;; but we can't unless FN is dynamically-safe (it might be dynamically
70 ;; referring to the bindings that the lambda arglist established.)
71 ;; One of the uncountable lossages introduced by dynamic scope...
72 ;;
73 ;; Maybe there should be a control-structure that says "turn on 
74 ;; fast-and-loose type-assumptive optimizations here."  Then when
75 ;; we see a form like (car foo) we can from then on assume that
76 ;; the variable foo is of type cons, and optimize based on that.
77 ;; But, this won't win much because of (you guessed it) dynamic 
78 ;; scope.  Anything down the stack could change the value.
79 ;; (Another reason it doesn't work is that it is perfectly valid
80 ;; to call car with a null argument.)  A better approach might
81 ;; be to allow type-specification of the form
82 ;;   (put 'foo 'arg-types '(float (list integer) dynamic))
83 ;;   (put 'foo 'result-type 'bool)
84 ;; It should be possible to have these types checked to a certain
85 ;; degree.
86 ;;
87 ;; collapse common subexpressions
88 ;;
89 ;; It would be nice if redundant sequences could be factored out as well,
90 ;; when they are known to have no side-effects:
91 ;;   (list (+ a b c) (+ a b c))   -->  a b add c add dup list-2
92 ;; but beware of traps like
93 ;;   (cons (list x y) (list x y))
94 ;;
95 ;; Tail-recursion elimination is not really possible in Emacs Lisp.
96 ;; Tail-recursion elimination is almost always impossible when all variables
97 ;; have dynamic scope, but given that the "return" byteop requires the
98 ;; binding stack to be empty (rather than emptying it itself), there can be
99 ;; no truly tail-recursive Emacs Lisp functions that take any arguments or
100 ;; make any bindings.
101 ;;
102 ;; Here is an example of an Emacs Lisp function which could safely be
103 ;; byte-compiled tail-recursively:
104 ;;
105 ;;  (defun tail-map (fn list)
106 ;;    (cond (list
107 ;;           (funcall fn (car list))
108 ;;           (tail-map fn (cdr list)))))
109 ;;
110 ;; However, if there was even a single let-binding around the COND,
111 ;; it could not be byte-compiled, because there would be an "unbind"
112 ;; byte-op between the final "call" and "return."  Adding a 
113 ;; Bunbind_all byteop would fix this.
114 ;;
115 ;;   (defun foo (x y z) ... (foo a b c))
116 ;;   ... (const foo) (varref a) (varref b) (varref c) (call 3) END: (return)
117 ;;   ... (varref a) (varbind x) (varref b) (varbind y) (varref c) (varbind z) (goto 0) END: (unbind-all) (return)
118 ;;   ... (varref a) (varset x) (varref b) (varset y) (varref c) (varset z) (goto 0) END: (return)
119 ;;
120 ;; this also can be considered tail recursion:
121 ;;
122 ;;   ... (const foo) (varref a) (call 1) (goto X) ... X: (return)
123 ;; could generalize this by doing the optimization
124 ;;   (goto X) ... X: (return)  -->  (return)
125 ;;
126 ;; But this doesn't solve all of the problems: although by doing tail-
127 ;; recursion elimination in this way, the call-stack does not grow, the
128 ;; binding-stack would grow with each recursive step, and would eventually
129 ;; overflow.  I don't believe there is any way around this without lexical
130 ;; scope.
131 ;;
132 ;; Wouldn't it be nice if Emacs Lisp had lexical scope.
133 ;;
134 ;; Idea: the form (lexical-scope) in a file means that the file may be 
135 ;; compiled lexically.  This proclamation is file-local.  Then, within 
136 ;; that file, "let" would establish lexical bindings, and "let-dynamic"
137 ;; would do things the old way.  (Or we could use CL "declare" forms.)
138 ;; We'd have to notice defvars and defconsts, since those variables should
139 ;; always be dynamic, and attempting to do a lexical binding of them
140 ;; should simply do a dynamic binding instead.
141 ;; But!  We need to know about variables that were not necessarily defvarred
142 ;; in the file being compiled (doing a boundp check isn't good enough.)
143 ;; Fdefvar() would have to be modified to add something to the plist.
144 ;;
145 ;; A major disadvantage of this scheme is that the interpreter and compiler 
146 ;; would have different semantics for files compiled with (dynamic-scope).  
147 ;; Since this would be a file-local optimization, there would be no way to
148 ;; modify the interpreter to obey this (unless the loader was hacked 
149 ;; in some grody way, but that's a really bad idea.)
150 ;;
151 ;; HA!  RMS removed the following paragraph from his version of
152 ;; byte-opt.el.
153 ;;
154 ;; Really the Right Thing is to make lexical scope the default across
155 ;; the board, in the interpreter and compiler, and just FIX all of 
156 ;; the code that relies on dynamic scope of non-defvarred variables.
157
158 ;; Other things to consider:
159
160 ;; Associative math should recognize subcalls to identical function:
161 ;;(disassemble (lambda (x) (+ (+ (foo) 1) (+ (bar) 2))))
162 ;; This should generate the same as (1+ x) and (1- x)
163
164 ;;(disassemble (lambda (x) (cons (+ x 1) (- x 1))))
165 ;; An awful lot of functions always return a non-nil value.  If they're
166 ;; error free also they may act as true-constants.
167
168 ;;(disassemble (lambda (x) (and (point) (foo))))
169 ;; When 
170 ;;   - all but one arguments to a function are constant
171 ;;   - the non-constant argument is an if-expression (cond-expression?)
172 ;; then the outer function can be distributed.  If the guarding
173 ;; condition is side-effect-free [assignment-free] then the other
174 ;; arguments may be any expressions.  Since, however, the code size
175 ;; can increase this way they should be "simple".  Compare:
176
177 ;;(disassemble (lambda (x) (eq (if (point) 'a 'b) 'c)))
178 ;;(disassemble (lambda (x) (if (point) (eq 'a 'c) (eq 'b 'c))))
179
180 ;; (car (cons A B)) -> (progn B A)
181 ;;(disassemble (lambda (x) (car (cons (foo) 42))))
182
183 ;; (cdr (cons A B)) -> (progn A B)
184 ;;(disassemble (lambda (x) (cdr (cons 42 (foo)))))
185
186 ;; (car (list A B ...)) -> (progn B ... A)
187 ;;(disassemble (lambda (x) (car (list (foo) 42 (bar)))))
188
189 ;; (cdr (list A B ...)) -> (progn A (list B ...))
190 ;;(disassemble (lambda (x) (cdr (list 42 (foo) (bar)))))
191
192
193 ;;; Code:
194
195 (require 'byte-compile "bytecomp")
196
197 (defun byte-compile-log-lap-1 (format &rest args)
198   (if (aref byte-code-vector 0)
199       (error "The old version of the disassembler is loaded.  Reload new-bytecomp as well."))
200   (byte-compile-log-1
201    (apply 'format format
202      (let (c a)
203        (mapcar '(lambda (arg)
204                   (if (not (consp arg))
205                       (if (and (symbolp arg)
206                                (string-match "^byte-" (symbol-name arg)))
207                           (intern (substring (symbol-name arg) 5))
208                         arg)
209                     (if (integerp (setq c (car arg)))
210                         (error "non-symbolic byte-op %s" c))
211                     (if (eq c 'TAG)
212                         (setq c arg)
213                       (setq a (cond ((memq c byte-goto-ops)
214                                      (car (cdr (cdr arg))))
215                                     ((memq c byte-constref-ops)
216                                      (car (cdr arg)))
217                                     (t (cdr arg))))
218                       (setq c (symbol-name c))
219                       (if (string-match "^byte-." c)
220                           (setq c (intern (substring c 5)))))
221                     (if (eq c 'constant) (setq c 'const))
222                     (if (and (eq (cdr arg) 0)
223                              (not (memq c '(unbind call const))))
224                         c
225                       (format "(%s %s)" c a))))
226                args)))))
227
228 (defmacro byte-compile-log-lap (format-string &rest args)
229   (list 'and
230         '(memq byte-optimize-log '(t byte))
231         (cons 'byte-compile-log-lap-1
232               (cons format-string args))))
233
234 \f
235 ;;; byte-compile optimizers to support inlining
236
237 (put 'inline 'byte-optimizer 'byte-optimize-inline-handler)
238
239 (defun byte-optimize-inline-handler (form)
240   "byte-optimize-handler for the `inline' special-form."
241   (cons 'progn
242         (mapcar
243          '(lambda (sexp)
244             (let ((fn (car-safe sexp)))
245               (if (and (symbolp fn)
246                     (or (cdr (assq fn byte-compile-function-environment))
247                       (and (fboundp fn)
248                         (not (or (cdr (assq fn byte-compile-macro-environment))
249                                  (and (consp (setq fn (symbol-function fn)))
250                                       (eq (car fn) 'macro))
251                                  (subrp fn))))))
252                   (byte-compile-inline-expand sexp)
253                 sexp)))
254          (cdr form))))
255
256
257 ;; Splice the given lap code into the current instruction stream.
258 ;; If it has any labels in it, you're responsible for making sure there
259 ;; are no collisions, and that byte-compile-tag-number is reasonable
260 ;; after this is spliced in.  The provided list is destroyed.
261 (defun byte-inline-lapcode (lap)
262   (setq byte-compile-output (nconc (nreverse lap) byte-compile-output)))
263
264
265 (defun byte-compile-inline-expand (form)
266   (let* ((name (car form))
267          (fn (or (cdr (assq name byte-compile-function-environment))
268                  (and (fboundp name) (symbol-function name)))))
269     (if (null fn)
270         (progn
271           (byte-compile-warn "attempt to inline %s before it was defined" name)
272           form)
273       ;; else
274       (if (and (consp fn) (eq (car fn) 'autoload))
275           (progn
276             (load (nth 1 fn))
277             (setq fn (or (cdr (assq name byte-compile-function-environment))
278                          (and (fboundp name) (symbol-function name))))))
279       (if (and (consp fn) (eq (car fn) 'autoload))
280           (error "file \"%s\" didn't define \"%s\"" (nth 1 fn) name))
281       (if (symbolp fn)
282           (byte-compile-inline-expand (cons fn (cdr form)))
283         (if (compiled-function-p fn)
284             (progn
285               (fetch-bytecode fn)
286               (cons (list 'lambda (compiled-function-arglist fn)
287                           (list 'byte-code
288                                 (compiled-function-instructions fn)
289                                 (compiled-function-constants fn)
290                                 (compiled-function-stack-depth fn)))
291                     (cdr form)))
292           (if (not (eq (car fn) 'lambda)) (error "%s is not a lambda" name))
293           (cons fn (cdr form)))))))
294
295 ;;; ((lambda ...) ...)
296 ;;; 
297 (defun byte-compile-unfold-lambda (form &optional name)
298   (or name (setq name "anonymous lambda"))
299   (let ((lambda (car form))
300         (values (cdr form)))
301     (if (compiled-function-p lambda)
302         (setq lambda (list 'lambda (compiled-function-arglist lambda)
303                           (list 'byte-code
304                                 (compiled-function-instructions lambda)
305                                 (compiled-function-constants lambda)
306                                 (compiled-function-stack-depth lambda)))))
307     (let ((arglist (nth 1 lambda))
308           (body (cdr (cdr lambda)))
309           optionalp restp
310           bindings)
311       (if (and (stringp (car body)) (cdr body))
312           (setq body (cdr body)))
313       (if (and (consp (car body)) (eq 'interactive (car (car body))))
314           (setq body (cdr body)))
315       (while arglist
316         (cond ((eq (car arglist) '&optional)
317                ;; ok, I'll let this slide because funcall_lambda() does...
318                ;; (if optionalp (error "multiple &optional keywords in %s" name))
319                (if restp (error "&optional found after &rest in %s" name))
320                (if (null (cdr arglist))
321                    (error "nothing after &optional in %s" name))
322                (setq optionalp t))
323               ((eq (car arglist) '&rest)
324                ;; ...but it is by no stretch of the imagination a reasonable
325                ;; thing that funcall_lambda() allows (&rest x y) and
326                ;; (&rest x &optional y) in arglists.
327                (if (null (cdr arglist))
328                    (error "nothing after &rest in %s" name))
329                (if (cdr (cdr arglist))
330                    (error "multiple vars after &rest in %s" name))
331                (setq restp t))
332               (restp
333                (setq bindings (cons (list (car arglist)
334                                           (and values (cons 'list values)))
335                                     bindings)
336                      values nil))
337               ((and (not optionalp) (null values))
338                (byte-compile-warn "attempt to open-code %s with too few arguments" name)
339                (setq arglist nil values 'too-few))
340               (t
341                (setq bindings (cons (list (car arglist) (car values))
342                                     bindings)
343                      values (cdr values))))
344         (setq arglist (cdr arglist)))
345       (if values
346           (progn
347             (or (eq values 'too-few)
348                 (byte-compile-warn
349                  "attempt to open-code %s with too many arguments" name))
350             form)
351         (let ((newform 
352                (if bindings
353                    (cons 'let (cons (nreverse bindings) body))
354                  (cons 'progn body))))
355           (byte-compile-log "  %s\t==>\t%s" form newform)
356           newform)))))
357
358 \f
359 ;;; implementing source-level optimizers
360
361 (defun byte-optimize-form-code-walker (form for-effect)
362   ;;
363   ;; For normal function calls, We can just mapcar the optimizer the cdr.  But
364   ;; we need to have special knowledge of the syntax of the special forms
365   ;; like let and defun (that's why they're special forms :-).  (Actually,
366   ;; the important aspect is that they are subrs that don't evaluate all of
367   ;; their args.)
368   ;;
369   (let ((fn (car-safe form))
370         tmp)
371     (cond ((not (consp form))
372            (if (not (and for-effect
373                          (or byte-compile-delete-errors
374                              (not (symbolp form))
375                              (eq form t))))
376              form))
377           ((eq fn 'quote)
378            (if (cdr (cdr form))
379                (byte-compile-warn "malformed quote form: %s"
380                                   (prin1-to-string form)))
381            ;; map (quote nil) to nil to simplify optimizer logic.
382            ;; map quoted constants to nil if for-effect (just because).
383            (and (nth 1 form)
384                 (not for-effect)
385                 form))
386           ((or (compiled-function-p fn)
387                (eq 'lambda (car-safe fn)))
388            (byte-compile-unfold-lambda form))
389           ((memq fn '(let let*))
390            ;; recursively enter the optimizer for the bindings and body
391            ;; of a let or let*.  This for depth-firstness: forms that
392            ;; are more deeply nested are optimized first.
393            (cons fn
394              (cons
395               (mapcar '(lambda (binding)
396                          (if (symbolp binding)
397                              binding
398                            (if (cdr (cdr binding))
399                                (byte-compile-warn "malformed let binding: %s"
400                                                   (prin1-to-string binding)))
401                            (list (car binding)
402                                  (byte-optimize-form (nth 1 binding) nil))))
403                       (nth 1 form))
404               (byte-optimize-body (cdr (cdr form)) for-effect))))
405           ((eq fn 'cond)
406            (cons fn
407                  (mapcar '(lambda (clause)
408                             (if (consp clause)
409                                 (cons
410                                  (byte-optimize-form (car clause) nil)
411                                  (byte-optimize-body (cdr clause) for-effect))
412                               (byte-compile-warn "malformed cond form: %s"
413                                                  (prin1-to-string clause))
414                               clause))
415                          (cdr form))))
416           ((eq fn 'progn)
417            ;; as an extra added bonus, this simplifies (progn <x>) --> <x>
418            (if (cdr (cdr form))
419                (progn
420                  (setq tmp (byte-optimize-body (cdr form) for-effect))
421                  (if (cdr tmp) (cons 'progn tmp) (car tmp)))
422              (byte-optimize-form (nth 1 form) for-effect)))
423           ((eq fn 'prog1)
424            (if (cdr (cdr form))
425                (cons 'prog1
426                      (cons (byte-optimize-form (nth 1 form) for-effect)
427                            (byte-optimize-body (cdr (cdr form)) t)))
428              (byte-optimize-form (nth 1 form) for-effect)))
429           ((eq fn 'prog2)
430            (cons 'prog2
431              (cons (byte-optimize-form (nth 1 form) t)
432                (cons (byte-optimize-form (nth 2 form) for-effect)
433                      (byte-optimize-body (cdr (cdr (cdr form))) t)))))
434           
435           ((memq fn '(save-excursion save-restriction save-current-buffer))
436            ;; those subrs which have an implicit progn; it's not quite good
437            ;; enough to treat these like normal function calls.
438            ;; This can turn (save-excursion ...) into (save-excursion) which
439            ;; will be optimized away in the lap-optimize pass.
440            (cons fn (byte-optimize-body (cdr form) for-effect)))
441           
442           ((eq fn 'with-output-to-temp-buffer)
443            ;; this is just like the above, except for the first argument.
444            (cons fn
445              (cons
446               (byte-optimize-form (nth 1 form) nil)
447               (byte-optimize-body (cdr (cdr form)) for-effect))))
448           
449           ((eq fn 'if)
450            (cons fn
451              (cons (byte-optimize-form (nth 1 form) nil)
452                (cons
453                 (byte-optimize-form (nth 2 form) for-effect)
454                 (byte-optimize-body (nthcdr 3 form) for-effect)))))
455           
456           ((memq fn '(and or))  ; remember, and/or are control structures.
457            ;; take forms off the back until we can't any more.
458            ;; In the future it could conceivably be a problem that the
459            ;; subexpressions of these forms are optimized in the reverse
460            ;; order, but it's ok for now.
461            (if for-effect
462                (let ((backwards (reverse (cdr form))))
463                  (while (and backwards
464                              (null (setcar backwards
465                                            (byte-optimize-form (car backwards)
466                                                                for-effect))))
467                    (setq backwards (cdr backwards)))
468                  (if (and (cdr form) (null backwards))
469                      (byte-compile-log
470                       "  all subforms of %s called for effect; deleted" form))
471                  (and backwards
472                       (cons fn (nreverse backwards))))
473              (cons fn (mapcar 'byte-optimize-form (cdr form)))))
474
475           ((eq fn 'interactive)
476            (byte-compile-warn "misplaced interactive spec: %s"
477                               (prin1-to-string form))
478            nil)
479           
480           ((memq fn '(defun defmacro function
481                       condition-case save-window-excursion))
482            ;; These forms are compiled as constants or by breaking out
483            ;; all the subexpressions and compiling them separately.
484            form)
485
486           ((eq fn 'unwind-protect)
487            ;; the "protected" part of an unwind-protect is compiled (and thus
488            ;; optimized) as a top-level form, so don't do it here.  But the
489            ;; non-protected part has the same for-effect status as the
490            ;; unwind-protect itself.  (The protected part is always for effect,
491            ;; but that isn't handled properly yet.)
492            (cons fn
493                  (cons (byte-optimize-form (nth 1 form) for-effect)
494                        (cdr (cdr form)))))
495            
496           ((eq fn 'catch)
497            ;; the body of a catch is compiled (and thus optimized) as a
498            ;; top-level form, so don't do it here.  The tag is never
499            ;; for-effect.  The body should have the same for-effect status
500            ;; as the catch form itself, but that isn't handled properly yet.
501            (cons fn
502                  (cons (byte-optimize-form (nth 1 form) nil)
503                        (cdr (cdr form)))))
504
505           ;; If optimization is on, this is the only place that macros are
506           ;; expanded.  If optimization is off, then macroexpansion happens
507           ;; in byte-compile-form.  Otherwise, the macros are already expanded
508           ;; by the time that is reached.
509           ((not (eq form
510                     (setq form (macroexpand form
511                                             byte-compile-macro-environment))))
512            (byte-optimize-form form for-effect))
513           
514           ((not (symbolp fn))
515            (or (eq 'mocklisp (car-safe fn)) ; ha!
516                (byte-compile-warn "%s is a malformed function"
517                                   (prin1-to-string fn)))
518            form)
519
520           ((and for-effect (setq tmp (get fn 'side-effect-free))
521                 (or byte-compile-delete-errors
522                     (eq tmp 'error-free)
523                     (progn
524                       (byte-compile-warn "%s called for effect"
525                                          (prin1-to-string form))
526                       nil)))
527            (byte-compile-log "  %s called for effect; deleted" fn)
528            ;; appending a nil here might not be necessary, but it can't hurt.
529            (byte-optimize-form
530             (cons 'progn (append (cdr form) '(nil))) t))
531           
532           (t
533            ;; Otherwise, no args can be considered to be for-effect,
534            ;; even if the called function is for-effect, because we
535            ;; don't know anything about that function.
536            (cons fn (mapcar 'byte-optimize-form (cdr form)))))))
537
538
539 (defun byte-optimize-form (form &optional for-effect)
540   "The source-level pass of the optimizer."
541   ;;
542   ;; First, optimize all sub-forms of this one.
543   (setq form (byte-optimize-form-code-walker form for-effect))
544   ;;
545   ;; after optimizing all subforms, optimize this form until it doesn't
546   ;; optimize any further.  This means that some forms will be passed through
547   ;; the optimizer many times, but that's necessary to make the for-effect
548   ;; processing do as much as possible.
549   ;;
550   (let (opt new)
551     (if (and (consp form)
552              (symbolp (car form))
553              (or (and for-effect
554                       ;; we don't have any of these yet, but we might.
555                       (setq opt (get (car form) 'byte-for-effect-optimizer)))
556                  (setq opt (get (car form) 'byte-optimizer)))
557              (not (eq form (setq new (funcall opt form)))))
558         (progn
559 ;;        (if (equal form new) (error "bogus optimizer -- %s" opt))
560           (byte-compile-log "  %s\t==>\t%s" form new)
561           (setq new (byte-optimize-form new for-effect))
562           new)
563       form)))
564
565
566 (defun byte-optimize-body (forms all-for-effect)
567   ;; optimize the cdr of a progn or implicit progn; all forms is a list of
568   ;; forms, all but the last of which are optimized with the assumption that
569   ;; they are being called for effect.  the last is for-effect as well if
570   ;; all-for-effect is true.  returns a new list of forms.
571   (let ((rest forms)
572         (result nil)
573         fe new)
574     (while rest
575       (setq fe (or all-for-effect (cdr rest)))
576       (setq new (and (car rest) (byte-optimize-form (car rest) fe)))
577       (if (or new (not fe))
578           (setq result (cons new result)))
579       (setq rest (cdr rest)))
580     (nreverse result)))
581
582 \f
583 ;;; some source-level optimizers
584 ;;;
585 ;;; when writing optimizers, be VERY careful that the optimizer returns
586 ;;; something not EQ to its argument if and ONLY if it has made a change.
587 ;;; This implies that you cannot simply destructively modify the list;
588 ;;; you must return something not EQ to it if you make an optimization.
589 ;;;
590 ;;; It is now safe to optimize code such that it introduces new bindings.
591
592 ;; I'd like this to be a defsubst, but let's not be self-referential...
593 (defmacro byte-compile-trueconstp (form)
594   ;; Returns non-nil if FORM is a non-nil constant.
595   (` (cond ((consp (, form)) (eq (car (, form)) 'quote))
596            ((not (symbolp (, form))))
597            ((eq (, form) t)))))
598
599 ;; If the function is being called with constant numeric args,
600 ;; evaluate as much as possible at compile-time.  This optimizer 
601 ;; assumes that the function is associative, like + or *.
602 (defun byte-optimize-associative-math (form)
603   (let ((args nil)
604         (constants nil)
605         (rest (cdr form)))
606     (while rest
607       (if (numberp (car rest))
608           (setq constants (cons (car rest) constants))
609           (setq args (cons (car rest) args)))
610       (setq rest (cdr rest)))
611     (if (cdr constants)
612         (if args
613             (list (car form)
614                   (apply (car form) constants)
615                   (if (cdr args)
616                       (cons (car form) (nreverse args))
617                       (car args)))
618             (apply (car form) constants))
619         form)))
620
621 ;; If the function is being called with constant numeric args,
622 ;; evaluate as much as possible at compile-time.  This optimizer
623 ;; assumes that the function satisfies
624 ;;   (op x1 x2 ... xn) == (op ...(op (op x1 x2) x3) ...xn)
625 ;; like - and /.
626 (defun byte-optimize-nonassociative-math (form)
627   (if (or (not (numberp (car (cdr form))))
628           (not (numberp (car (cdr (cdr form))))))
629       form
630     (let ((constant (car (cdr form)))
631           (rest (cdr (cdr form))))
632       (while (numberp (car rest))
633         (setq constant (funcall (car form) constant (car rest))
634               rest (cdr rest)))
635       (if rest
636           (cons (car form) (cons constant rest))
637           constant))))
638
639 ;;(defun byte-optimize-associative-two-args-math (form)
640 ;;  (setq form (byte-optimize-associative-math form))
641 ;;  (if (consp form)
642 ;;      (byte-optimize-two-args-left form)
643 ;;      form))
644
645 ;;(defun byte-optimize-nonassociative-two-args-math (form)
646 ;;  (setq form (byte-optimize-nonassociative-math form))
647 ;;  (if (consp form)
648 ;;      (byte-optimize-two-args-right form)
649 ;;      form))
650
651 ;; jwz: (byte-optimize-approx-equal 0.0 0.0) was returning nil
652 ;; in xemacs 19.15 because it used < instead of <=.
653 (defun byte-optimize-approx-equal (x y)
654   (<= (* (abs (- x y)) 100) (abs (+ x y))))
655
656 ;; Collect all the constants from FORM, after the STARTth arg,
657 ;; and apply FUN to them to make one argument at the end.
658 ;; For functions that can handle floats, that optimization
659 ;; can be incorrect because reordering can cause an overflow
660 ;; that would otherwise be avoided by encountering an arg that is a float.
661 ;; We avoid this problem by (1) not moving float constants and
662 ;; (2) not moving anything if it would cause an overflow.
663 (defun byte-optimize-delay-constants-math (form start fun)
664   ;; Merge all FORM's constants from number START, call FUN on them
665   ;; and put the result at the end.
666   (let ((rest (nthcdr (1- start) form))
667         (orig form)
668         ;; t means we must check for overflow.
669         (overflow (memq fun '(+ *))))
670     (while (cdr (setq rest (cdr rest)))
671       (if (integerp (car rest))
672           (let (constants)
673             (setq form (copy-sequence form)
674                   rest (nthcdr (1- start) form))
675             (while (setq rest (cdr rest))
676               (cond ((integerp (car rest))
677                      (setq constants (cons (car rest) constants))
678                      (setcar rest nil))))
679             ;; If necessary, check now for overflow
680             ;; that might be caused by reordering.
681             (if (and overflow
682                      ;; We have overflow if the result of doing the arithmetic
683                      ;; on floats is not even close to the result
684                      ;; of doing it on integers.
685                      (not (byte-optimize-approx-equal
686                             (apply fun (mapcar 'float constants))
687                             (float (apply fun constants)))))
688                 (setq form orig)
689               (setq form (nconc (delq nil form)
690                                 (list (apply fun (nreverse constants)))))))))
691     form))
692
693 (defun byte-optimize-plus (form)
694   (setq form (byte-optimize-delay-constants-math form 1 '+))
695   (if (memq 0 form) (setq form (delq 0 (copy-sequence form))))
696   ;;(setq form (byte-optimize-associative-two-args-math form))
697   (cond ((null (cdr form))
698          (condition-case ()
699              (eval form)
700            (error form)))
701
702         ;; `add1' and `sub1' are a marginally fewer instructions
703         ;; than `plus' and `minus', so use them when possible.
704         ((and (null (nthcdr 3 form))
705               (eq (nth 2 form) 1))
706          (list '1+ (nth 1 form)))       ; (+ x 1)  -->  (1+ x)
707         ((and (null (nthcdr 3 form))
708               (eq (nth 1 form) 1))
709          (list '1+ (nth 2 form)))       ; (+ 1 x)  -->  (1+ x)
710         ((and (null (nthcdr 3 form))
711               (eq (nth 2 form) -1))
712          (list '1- (nth 1 form)))       ; (+ x -1)  -->  (1- x)
713         ((and (null (nthcdr 3 form))
714               (eq (nth 1 form) -1))
715          (list '1- (nth 2 form)))       ; (+ -1 x)  -->  (1- x)
716
717 ;;; It is not safe to delete the function entirely
718 ;;; (actually, it would be safe if we know the sole arg
719 ;;; is not a marker).
720 ;;      ((null (cdr (cdr form))) (nth 1 form))
721         (t form)))
722
723 (defun byte-optimize-minus (form)
724   ;; Put constants at the end, except the last constant.
725   (setq form (byte-optimize-delay-constants-math form 2 '+))
726   ;; Now only first and last element can be a number.
727   (let ((last (car (reverse (nthcdr 3 form)))))
728     (cond ((eq 0 last)
729            ;; (- x y ... 0)  --> (- x y ...)
730            (setq form (copy-sequence form))
731            (setcdr (cdr (cdr form)) (delq 0 (nthcdr 3 form))))
732           ;; If form is (- CONST foo... CONST), merge first and last.
733           ((and (numberp (nth 1 form))
734                 (numberp last))
735            (setq form (nconc (list '- (- (nth 1 form) last) (nth 2 form))
736                              (delq last (copy-sequence (nthcdr 3 form))))))))
737   (setq form
738 ;;; It is not safe to delete the function entirely
739 ;;; (actually, it would be safe if we know the sole arg
740 ;;; is not a marker).
741 ;;;  (if (eq (nth 2 form) 0)
742 ;;;      (nth 1 form)                   ; (- x 0)  -->  x
743     (byte-optimize-predicate
744      (if (and (null (cdr (cdr (cdr form))))
745               (eq (nth 1 form) 0))      ; (- 0 x)  -->  (- x)
746          (cons (car form) (cdr (cdr form)))
747        form))
748 ;;;    )
749     )
750
751   ;; `add1' and `sub1' are a marginally fewer instructions than `plus'
752   ;; and `minus', so use them when possible.
753   (cond ((and (null (nthcdr 3 form))
754               (eq (nth 2 form) 1))
755          (list '1- (nth 1 form)))       ; (- x 1)  -->  (1- x)
756         ((and (null (nthcdr 3 form))
757               (eq (nth 2 form) -1))
758          (list '1+ (nth 1 form)))       ; (- x -1)  -->  (1+ x)
759         (t
760          form))
761   )
762
763 (defun byte-optimize-multiply (form)
764   (setq form (byte-optimize-delay-constants-math form 1 '*))
765   ;; If there is a constant in FORM, it is now the last element.
766   (cond ((null (cdr form)) 1)
767 ;;; It is not safe to delete the function entirely
768 ;;; (actually, it would be safe if we know the sole arg
769 ;;; is not a marker or if it appears in other arithmetic).
770 ;;;     ((null (cdr (cdr form))) (nth 1 form))
771         ((let ((last (car (reverse form))))
772            (cond ((eq 0 last)  (cons 'progn (cdr form)))
773                  ((eq 1 last)  (delq 1 (copy-sequence form)))
774                  ((eq -1 last) (list '- (delq -1 (copy-sequence form))))
775                  ((and (eq 2 last)
776                        (memq t (mapcar 'symbolp (cdr form))))
777                   (prog1 (setq form (delq 2 (copy-sequence form)))
778                     (while (not (symbolp (car (setq form (cdr form))))))
779                     (setcar form (list '+ (car form) (car form)))))
780                  (form))))))
781
782 (defsubst byte-compile-butlast (form)
783   (nreverse (cdr (reverse form))))
784
785 (defun byte-optimize-divide (form)
786   (setq form (byte-optimize-delay-constants-math form 2 '*))
787   (let ((last (car (reverse (cdr (cdr form))))))
788     (if (numberp last)
789         (cond ((= (length form) 3)
790                (if (and (numberp (nth 1 form))
791                         (not (zerop last))
792                         (condition-case nil
793                             (/ (nth 1 form) last)
794                           (error nil)))
795                    (setq form (list 'progn (/ (nth 1 form) last)))))
796               ((= last 1)
797                (setq form (byte-compile-butlast form)))
798               ((numberp (nth 1 form))
799                (setq form (cons (car form)
800                                 (cons (/ (nth 1 form) last)
801                                       (byte-compile-butlast (cdr (cdr form)))))
802                      last nil))))
803     (cond 
804 ;;;       ((null (cdr (cdr form)))
805 ;;;        (nth 1 form))
806           ((eq (nth 1 form) 0)
807            (append '(progn) (cdr (cdr form)) '(0)))
808           ((eq last -1)
809            (list '- (if (nthcdr 3 form)
810                         (byte-compile-butlast form)
811                       (nth 1 form))))
812           (form))))
813
814 (defun byte-optimize-logmumble (form)
815   (setq form (byte-optimize-delay-constants-math form 1 (car form)))
816   (byte-optimize-predicate
817    (cond ((memq 0 form)
818           (setq form (if (eq (car form) 'logand)
819                          (cons 'progn (cdr form))
820                        (delq 0 (copy-sequence form)))))
821          ((and (eq (car-safe form) 'logior)
822                (memq -1 form))
823           (cons 'progn (cdr form)))
824          (form))))
825
826
827 (defun byte-optimize-binary-predicate (form)
828   (if (byte-compile-constp (nth 1 form))
829       (if (byte-compile-constp (nth 2 form))
830           (condition-case ()
831               (list 'quote (eval form))
832             (error form))
833         ;; This can enable some lapcode optimizations.
834         (list (car form) (nth 2 form) (nth 1 form)))
835     form))
836
837 (defun byte-optimize-predicate (form)
838   (let ((ok t)
839         (rest (cdr form)))
840     (while (and rest ok)
841       (setq ok (byte-compile-constp (car rest))
842             rest (cdr rest)))
843     (if ok
844         (condition-case ()
845             (list 'quote (eval form))
846           (error form))
847         form)))
848
849 (defun byte-optimize-identity (form)
850   (if (and (cdr form) (null (cdr (cdr form))))
851       (nth 1 form)
852     (byte-compile-warn "identity called with %d arg%s, but requires 1"
853                        (length (cdr form))
854                        (if (= 1 (length (cdr form))) "" "s"))
855     form))
856
857 (put 'identity 'byte-optimizer 'byte-optimize-identity)
858
859 (put '+   'byte-optimizer 'byte-optimize-plus)
860 (put '*   'byte-optimizer 'byte-optimize-multiply)
861 (put '-   'byte-optimizer 'byte-optimize-minus)
862 (put '/   'byte-optimizer 'byte-optimize-divide)
863 (put 'max 'byte-optimizer 'byte-optimize-associative-math)
864 (put 'min 'byte-optimizer 'byte-optimize-associative-math)
865
866 (put '=   'byte-optimizer 'byte-optimize-binary-predicate)
867 (put 'eq  'byte-optimizer 'byte-optimize-binary-predicate)
868 (put 'eql 'byte-optimizer 'byte-optimize-binary-predicate)
869 (put 'equal   'byte-optimizer 'byte-optimize-binary-predicate)
870 (put 'string= 'byte-optimizer 'byte-optimize-binary-predicate)
871 (put 'string-equal 'byte-optimizer 'byte-optimize-binary-predicate)
872
873 (put '<   'byte-optimizer 'byte-optimize-predicate)
874 (put '>   'byte-optimizer 'byte-optimize-predicate)
875 (put '<=  'byte-optimizer 'byte-optimize-predicate)
876 (put '>=  'byte-optimizer 'byte-optimize-predicate)
877 (put '1+  'byte-optimizer 'byte-optimize-predicate)
878 (put '1-  'byte-optimizer 'byte-optimize-predicate)
879 (put 'not 'byte-optimizer 'byte-optimize-predicate)
880 (put 'null  'byte-optimizer 'byte-optimize-predicate)
881 (put 'memq  'byte-optimizer 'byte-optimize-predicate)
882 (put 'consp 'byte-optimizer 'byte-optimize-predicate)
883 (put 'listp 'byte-optimizer 'byte-optimize-predicate)
884 (put 'symbolp 'byte-optimizer 'byte-optimize-predicate)
885 (put 'stringp 'byte-optimizer 'byte-optimize-predicate)
886 (put 'string< 'byte-optimizer 'byte-optimize-predicate)
887 (put 'string-lessp 'byte-optimizer 'byte-optimize-predicate)
888
889 (put 'logand 'byte-optimizer 'byte-optimize-logmumble)
890 (put 'logior 'byte-optimizer 'byte-optimize-logmumble)
891 (put 'logxor 'byte-optimizer 'byte-optimize-logmumble)
892 (put 'lognot 'byte-optimizer 'byte-optimize-predicate)
893
894 (put 'car 'byte-optimizer 'byte-optimize-predicate)
895 (put 'cdr 'byte-optimizer 'byte-optimize-predicate)
896 (put 'car-safe 'byte-optimizer 'byte-optimize-predicate)
897 (put 'cdr-safe 'byte-optimizer 'byte-optimize-predicate)
898
899
900 ;; I'm not convinced that this is necessary.  Doesn't the optimizer loop 
901 ;; take care of this? - Jamie
902 ;; I think this may some times be necessary to reduce ie (quote 5) to 5,
903 ;; so arithmetic optimizers recognize the numeric constant.  - Hallvard
904 (put 'quote 'byte-optimizer 'byte-optimize-quote)
905 (defun byte-optimize-quote (form)
906   (if (or (consp (nth 1 form))
907           (and (symbolp (nth 1 form))
908                ;; XEmacs addition:
909                (not (keywordp (nth 1 form)))
910                (not (memq (nth 1 form) '(nil t)))))
911       form
912     (nth 1 form)))
913
914 (defun byte-optimize-zerop (form)
915   (cond ((numberp (nth 1 form))
916          (eval form))
917         (byte-compile-delete-errors
918          (list '= (nth 1 form) 0))
919         (form)))
920
921 (put 'zerop 'byte-optimizer 'byte-optimize-zerop)
922
923 (defun byte-optimize-and (form)
924   ;; Simplify if less than 2 args.
925   ;; if there is a literal nil in the args to `and', throw it and following
926   ;; forms away, and surround the `and' with (progn ... nil).
927   (cond ((null (cdr form)))
928         ((memq nil form)
929          (list 'progn
930                (byte-optimize-and
931                 (prog1 (setq form (copy-sequence form))
932                   (while (nth 1 form)
933                     (setq form (cdr form)))
934                   (setcdr form nil)))
935                nil))
936         ((null (cdr (cdr form)))
937          (nth 1 form))
938         ((byte-optimize-predicate form))))
939
940 (defun byte-optimize-or (form)
941   ;; Throw away nil's, and simplify if less than 2 args.
942   ;; If there is a literal non-nil constant in the args to `or', throw away all
943   ;; following forms.
944   (if (memq nil form)
945       (setq form (delq nil (copy-sequence form))))
946   (let ((rest form))
947     (while (cdr (setq rest (cdr rest)))
948       (if (byte-compile-trueconstp (car rest))
949           (setq form (copy-sequence form)
950                 rest (setcdr (memq (car rest) form) nil))))
951     (if (cdr (cdr form))
952         (byte-optimize-predicate form)
953       (nth 1 form))))
954
955 (defun byte-optimize-cond (form)
956   ;; if any clauses have a literal nil as their test, throw them away.
957   ;; if any clause has a literal non-nil constant as its test, throw
958   ;; away all following clauses.
959   (let (rest)
960     ;; This must be first, to reduce (cond (t ...) (nil)) to (progn t ...)
961     (while (setq rest (assq nil (cdr form)))
962       (setq form (delq rest (copy-sequence form))))
963     (if (memq nil (cdr form))
964         (setq form (delq nil (copy-sequence form))))
965     (setq rest form)
966     (while (setq rest (cdr rest))
967       (cond ((byte-compile-trueconstp (car-safe (car rest)))
968              (cond ((eq rest (cdr form))
969                     (setq form
970                           (if (cdr (car rest))
971                               (if (cdr (cdr (car rest)))
972                                   (cons 'progn (cdr (car rest)))
973                                 (nth 1 (car rest)))
974                             (car (car rest)))))
975                    ((cdr rest)
976                     (setq form (copy-sequence form))
977                     (setcdr (memq (car rest) form) nil)))
978              (setq rest nil)))))
979   ;;
980   ;; Turn (cond (( <x> )) ... ) into (or <x> (cond ... ))
981   (if (eq 'cond (car-safe form))
982       (let ((clauses (cdr form)))
983         (if (and (consp (car clauses))
984                  (null (cdr (car clauses))))
985             (list 'or (car (car clauses))
986                   (byte-optimize-cond
987                    (cons (car form) (cdr (cdr form)))))
988           form))
989     form))
990
991 (defun byte-optimize-if (form)
992   ;; (if <true-constant> <then> <else...>) ==> <then>
993   ;; (if <false-constant> <then> <else...>) ==> (progn <else...>)
994   ;; (if <test> nil <else...>) ==> (if (not <test>) (progn <else...>))
995   ;; (if <test> <then> nil) ==> (if <test> <then>)
996   (let ((clause (nth 1 form)))
997     (cond ((byte-compile-trueconstp clause)
998            (nth 2 form))
999           ((null clause)
1000            (if (nthcdr 4 form)
1001                (cons 'progn (nthcdr 3 form))
1002              (nth 3 form)))
1003           ((nth 2 form)
1004            (if (equal '(nil) (nthcdr 3 form))
1005                (list 'if clause (nth 2 form))
1006              form))
1007           ((or (nth 3 form) (nthcdr 4 form))
1008            (list 'if
1009                  ;; Don't make a double negative;
1010                  ;; instead, take away the one that is there.
1011                  (if (and (consp clause) (memq (car clause) '(not null))
1012                           (= (length clause) 2)) ; (not xxxx) or (not (xxxx))
1013                      (nth 1 clause)
1014                    (list 'not clause))
1015                  (if (nthcdr 4 form)
1016                      (cons 'progn (nthcdr 3 form))
1017                    (nth 3 form))))
1018           (t
1019            (list 'progn clause nil)))))
1020
1021 (defun byte-optimize-while (form)
1022   (if (nth 1 form)
1023       form))
1024
1025 (put 'and   'byte-optimizer 'byte-optimize-and)
1026 (put 'or    'byte-optimizer 'byte-optimize-or)
1027 (put 'cond  'byte-optimizer 'byte-optimize-cond)
1028 (put 'if    'byte-optimizer 'byte-optimize-if)
1029 (put 'while 'byte-optimizer 'byte-optimize-while)
1030
1031 ;; byte-compile-negation-optimizer lives in bytecomp.el
1032 ;(put '/= 'byte-optimizer 'byte-compile-negation-optimizer)
1033 (put 'atom 'byte-optimizer 'byte-compile-negation-optimizer)
1034 (put 'nlistp 'byte-optimizer 'byte-compile-negation-optimizer)
1035
1036
1037 (defun byte-optimize-funcall (form)
1038   ;; (funcall '(lambda ...) ...) ==> ((lambda ...) ...)
1039   ;; (funcall 'foo ...) ==> (foo ...)
1040   (let ((fn (nth 1 form)))
1041     (if (memq (car-safe fn) '(quote function))
1042         (cons (nth 1 fn) (cdr (cdr form)))
1043         form)))
1044
1045 (defun byte-optimize-apply (form)
1046   ;; If the last arg is a literal constant, turn this into a funcall.
1047   ;; The funcall optimizer can then transform (funcall 'foo ...) -> (foo ...).
1048   (let ((fn (nth 1 form))
1049         (last (nth (1- (length form)) form))) ; I think this really is fastest
1050     (or (if (or (null last)
1051                 (eq (car-safe last) 'quote))
1052             (if (listp (nth 1 last))
1053                 (let ((butlast (nreverse (cdr (reverse (cdr (cdr form)))))))
1054                   (nconc (list 'funcall fn) butlast
1055                          (mapcar '(lambda (x) (list 'quote x)) (nth 1 last))))
1056               (byte-compile-warn
1057                "last arg to apply can't be a literal atom: %s"
1058                (prin1-to-string last))
1059               nil))
1060         form)))
1061
1062 (put 'funcall 'byte-optimizer 'byte-optimize-funcall)
1063 (put 'apply   'byte-optimizer 'byte-optimize-apply)
1064
1065
1066 (put 'let 'byte-optimizer 'byte-optimize-letX)
1067 (put 'let* 'byte-optimizer 'byte-optimize-letX)
1068 (defun byte-optimize-letX (form)
1069   (cond ((null (nth 1 form))
1070          ;; No bindings
1071          (cons 'progn (cdr (cdr form))))
1072         ((or (nth 2 form) (nthcdr 3 form))
1073          form)
1074          ;; The body is nil
1075         ((eq (car form) 'let)
1076          (append '(progn) (mapcar 'car-safe (mapcar 'cdr-safe (nth 1 form)))
1077                  '(nil)))
1078         (t
1079          (let ((binds (reverse (nth 1 form))))
1080            (list 'let* (reverse (cdr binds)) (nth 1 (car binds)) nil)))))
1081
1082
1083 (put 'nth 'byte-optimizer 'byte-optimize-nth)
1084 (defun byte-optimize-nth (form)
1085   (if (and (= (safe-length form) 3) (memq (nth 1 form) '(0 1)))
1086       (list 'car (if (zerop (nth 1 form))
1087                      (nth 2 form)
1088                    (list 'cdr (nth 2 form))))
1089     (byte-optimize-predicate form)))
1090
1091 (put 'nthcdr 'byte-optimizer 'byte-optimize-nthcdr)
1092 (defun byte-optimize-nthcdr (form)
1093   (if (and (= (safe-length form) 3) (not (memq (nth 1 form) '(0 1 2))))
1094       (byte-optimize-predicate form)
1095     (let ((count (nth 1 form)))
1096       (setq form (nth 2 form))
1097       (while (>= (setq count (1- count)) 0)
1098         (setq form (list 'cdr form)))
1099       form)))
1100 \f
1101 ;;; enumerating those functions which need not be called if the returned 
1102 ;;; value is not used.  That is, something like
1103 ;;;    (progn (list (something-with-side-effects) (yow))
1104 ;;;           (foo))
1105 ;;; may safely be turned into
1106 ;;;    (progn (progn (something-with-side-effects) (yow))
1107 ;;;           (foo))
1108 ;;; Further optimizations will turn (progn (list 1 2 3) 'foo) into 'foo.
1109
1110 ;;; I wonder if I missed any :-\)
1111 (let ((side-effect-free-fns
1112        '(% * + - / /= 1+ 1- < <= = > >= abs acos append aref ash asin atan
1113          assoc assq
1114          boundp buffer-file-name buffer-local-variables buffer-modified-p
1115          buffer-substring
1116          capitalize car-less-than-car car cdr ceiling concat
1117          ;; coordinates-in-window-p not in XEmacs
1118          copy-marker cos count-lines
1119          default-boundp default-value documentation downcase
1120          elt exp expt fboundp featurep
1121          file-directory-p file-exists-p file-locked-p file-name-absolute-p
1122          file-newer-than-file-p file-readable-p file-symlink-p file-writable-p
1123          float floor format
1124          get get-buffer get-buffer-window getenv get-file-buffer
1125          int-to-string
1126          length log log10 logand logb logior lognot logxor lsh
1127          marker-buffer max member memq min mod
1128          next-window nth nthcdr number-to-string
1129          parse-colon-path previous-window
1130          radians-to-degrees rassq regexp-quote reverse round
1131          sin sqrt string< string= string-equal string-lessp string-to-char
1132          string-to-int string-to-number substring symbol-plist
1133          tan upcase user-variable-p vconcat
1134          ;; XEmacs change: window-edges -> window-pixel-edges
1135          window-buffer window-dedicated-p window-pixel-edges window-height
1136          window-hscroll window-minibuffer-p window-width
1137          zerop))
1138       (side-effect-and-error-free-fns
1139        '(arrayp atom
1140          bobp bolp buffer-end buffer-list buffer-size buffer-string bufferp
1141          car-safe case-table-p cdr-safe char-or-string-p char-table-p
1142          characterp commandp cons
1143          consolep console-live-p consp
1144          current-buffer
1145          ;; XEmacs: extent functions, frame-live-p, various other stuff
1146          devicep device-live-p
1147          dot dot-marker eobp eolp eq eql equal eventp extentp
1148          extent-live-p floatp framep frame-live-p
1149          get-largest-window get-lru-window
1150          identity ignore integerp integer-or-marker-p interactive-p
1151          invocation-directory invocation-name
1152          ;; keymapp may autoload in XEmacs, so not on this list!
1153          list listp
1154          make-marker mark mark-marker markerp memory-limit minibuffer-window
1155          ;; mouse-movement-p not in XEmacs
1156          natnump nlistp not null number-or-marker-p numberp
1157          one-window-p ;; overlayp not in XEmacs
1158          point point-marker point-min point-max processp
1159          range-table-p
1160          selected-window sequencep stringp subrp symbolp syntax-table-p
1161          user-full-name user-login-name user-original-login-name
1162          user-real-login-name user-real-uid user-uid
1163          vector vectorp
1164          window-configuration-p window-live-p windowp)))
1165   (while side-effect-free-fns
1166     (put (car side-effect-free-fns) 'side-effect-free t)
1167     (setq side-effect-free-fns (cdr side-effect-free-fns)))
1168   (while side-effect-and-error-free-fns
1169     (put (car side-effect-and-error-free-fns) 'side-effect-free 'error-free)
1170     (setq side-effect-and-error-free-fns (cdr side-effect-and-error-free-fns)))
1171   nil)
1172
1173
1174 (defun byte-compile-splice-in-already-compiled-code (form)
1175   ;; form is (byte-code "..." [...] n)
1176   (if (not (memq byte-optimize '(t lap)))
1177       (byte-compile-normal-call form)
1178     (byte-inline-lapcode
1179      (byte-decompile-bytecode-1 (nth 1 form) (nth 2 form) t))
1180     (setq byte-compile-maxdepth (max (+ byte-compile-depth (nth 3 form))
1181                                      byte-compile-maxdepth))
1182     (setq byte-compile-depth (1+ byte-compile-depth))))
1183
1184 (put 'byte-code 'byte-compile 'byte-compile-splice-in-already-compiled-code)
1185
1186 \f
1187 (defconst byte-constref-ops
1188   '(byte-constant byte-constant2 byte-varref byte-varset byte-varbind))
1189
1190 ;;; This function extracts the bitfields from variable-length opcodes.
1191 ;;; Originally defined in disass.el (which no longer uses it.)
1192
1193 (defun disassemble-offset ()
1194   "Don't call this!"
1195   ;; fetch and return the offset for the current opcode.
1196   ;; return NIL if this opcode has no offset
1197   ;; OP, PTR and BYTES are used and set dynamically
1198   (defvar op)
1199   (defvar ptr)
1200   (defvar bytes)
1201   (cond ((< op byte-nth)
1202          (let ((tem (logand op 7)))
1203            (setq op (logand op 248))
1204            (cond ((eq tem 6)
1205                   (setq ptr (1+ ptr))   ;offset in next byte
1206                   ;; char-to-int to avoid downstream problems
1207                   ;; caused by chars appearing where ints are
1208                   ;; expected.  In bytecode the bytes in the
1209                   ;; opcode string are always interpreted as ints.
1210                   (char-to-int (aref bytes ptr)))
1211                  ((eq tem 7)
1212                   (setq ptr (1+ ptr))   ;offset in next 2 bytes
1213                   (+ (aref bytes ptr)
1214                      (progn (setq ptr (1+ ptr))
1215                             (lsh (aref bytes ptr) 8))))
1216                  (t tem))))             ;offset was in opcode
1217         ((>= op byte-constant)
1218          (prog1 (- op byte-constant)    ;offset in opcode
1219            (setq op byte-constant)))
1220         ((and (>= op byte-constant2)
1221               (<= op byte-goto-if-not-nil-else-pop))
1222          (setq ptr (1+ ptr))            ;offset in next 2 bytes
1223          (+ (aref bytes ptr)
1224             (progn (setq ptr (1+ ptr))
1225                    (lsh (aref bytes ptr) 8))))
1226         ;; XEmacs: this code was here before.  FSF's first comparison
1227         ;; is (>= op byte-listN).  It appears that the rel-goto stuff
1228         ;; does not exist in FSF 19.30.  It doesn't exist in 19.28
1229         ;; either, so I'm going to assume that this is an improvement
1230         ;; on our part and leave it in. --ben
1231         ((and (>= op byte-rel-goto)
1232               (<= op byte-insertN))
1233          (setq ptr (1+ ptr))            ;offset in next byte
1234          ;; Use char-to-int to avoid downstream problems caused by
1235          ;; chars appearing where ints are expected.  In bytecode
1236          ;; the bytes in the opcode string are always interpreted as
1237          ;; ints.
1238          (char-to-int (aref bytes ptr)))))
1239
1240
1241 ;;; This de-compiler is used for inline expansion of compiled functions,
1242 ;;; and by the disassembler.
1243 ;;;
1244 ;;; This list contains numbers, which are pc values,
1245 ;;; before each instruction.
1246 (defun byte-decompile-bytecode (bytes constvec)
1247   "Turns BYTECODE into lapcode, referring to CONSTVEC."
1248   (let ((byte-compile-constants nil)
1249         (byte-compile-variables nil)
1250         (byte-compile-tag-number 0))
1251     (byte-decompile-bytecode-1 bytes constvec)))
1252
1253 ;; As byte-decompile-bytecode, but updates
1254 ;; byte-compile-{constants, variables, tag-number}.
1255 ;; If MAKE-SPLICEABLE is true, then `return' opcodes are replaced
1256 ;; with `goto's destined for the end of the code.
1257 ;; That is for use by the compiler.
1258 ;; If MAKE-SPLICEABLE is nil, we are being called for the disassembler.
1259 ;; In that case, we put a pc value into the list
1260 ;; before each insn (or its label).
1261 (defun byte-decompile-bytecode-1 (bytes constvec &optional make-spliceable)
1262   (let ((length (length bytes))
1263         (ptr 0) optr tags op offset
1264         ;; tag unused
1265         lap tmp
1266         endtag
1267         ;; (retcount 0) unused
1268         )
1269     (while (not (= ptr length))
1270       (or make-spliceable
1271           (setq lap (cons ptr lap)))
1272       (setq op (aref bytes ptr)
1273             optr ptr
1274             offset (disassemble-offset)) ; this does dynamic-scope magic
1275       (setq op (aref byte-code-vector op))
1276       ;; XEmacs: the next line in FSF 19.30 reads
1277       ;; (cond ((memq op byte-goto-ops)
1278       ;; see the comment above about byte-rel-goto in XEmacs.
1279       (cond ((or (memq op byte-goto-ops)
1280                  (cond ((memq op byte-rel-goto-ops)
1281                         (setq op (aref byte-code-vector
1282                                        (- (symbol-value op)
1283                                           (- byte-rel-goto byte-goto))))
1284                         (setq offset (+ ptr (- offset 127)))
1285                         t)))
1286              ;; it's a pc
1287              (setq offset
1288                    (cdr (or (assq offset tags)
1289                             (car (setq tags
1290                                        (cons (cons offset
1291                                                    (byte-compile-make-tag))
1292                                              tags)))))))
1293             ((cond ((eq op 'byte-constant2) (setq op 'byte-constant) t)
1294                    ((memq op byte-constref-ops)))
1295              (setq tmp (aref constvec offset)
1296                    offset (if (eq op 'byte-constant)
1297                               (byte-compile-get-constant tmp)
1298                             (or (assq tmp byte-compile-variables)
1299                                 (car (setq byte-compile-variables
1300                                            (cons (list tmp)
1301                                                  byte-compile-variables)))))))
1302             ((and make-spliceable
1303                   (eq op 'byte-return))
1304              (if (= ptr (1- length))
1305                  (setq op nil)
1306                (setq offset (or endtag (setq endtag (byte-compile-make-tag)))
1307                      op 'byte-goto))))
1308       ;; lap = ( [ (pc . (op . arg)) ]* )
1309       (setq lap (cons (cons optr (cons op (or offset 0)))
1310                       lap))
1311       (setq ptr (1+ ptr)))
1312     ;; take off the dummy nil op that we replaced a trailing "return" with.
1313     (let ((rest lap))
1314       (while rest
1315         (cond ((numberp (car rest)))
1316               ((setq tmp (assq (car (car rest)) tags))
1317                ;; this addr is jumped to
1318                (setcdr rest (cons (cons nil (cdr tmp))
1319                                   (cdr rest)))
1320                (setq tags (delq tmp tags))
1321                (setq rest (cdr rest))))
1322         (setq rest (cdr rest))))
1323     (if tags (error "optimizer error: missed tags %s" tags))
1324     (if (null (car (cdr (car lap))))
1325         (setq lap (cdr lap)))
1326     (if endtag
1327         (setq lap (cons (cons nil endtag) lap)))
1328     ;; remove addrs, lap = ( [ (op . arg) | (TAG tagno) ]* )
1329     (mapcar (function (lambda (elt)
1330                         (if (numberp elt)
1331                             elt
1332                           (cdr elt))))
1333             (nreverse lap))))
1334
1335 \f
1336 ;;; peephole optimizer
1337
1338 (defconst byte-tagref-ops (cons 'TAG byte-goto-ops))
1339
1340 (defconst byte-conditional-ops
1341   '(byte-goto-if-nil byte-goto-if-not-nil byte-goto-if-nil-else-pop
1342     byte-goto-if-not-nil-else-pop))
1343
1344 (defconst byte-after-unbind-ops
1345    '(byte-constant byte-dup
1346      byte-symbolp byte-consp byte-stringp byte-listp byte-numberp byte-integerp
1347      byte-eq byte-equal byte-not
1348      byte-cons byte-list1 byte-list2    ; byte-list3 byte-list4
1349      byte-interactive-p)
1350    ;; How about other side-effect-free-ops?  Is it safe to move an
1351    ;; error invocation (such as from nth) out of an unwind-protect?
1352    "Byte-codes that can be moved past an unbind.")
1353
1354 (defconst byte-compile-side-effect-and-error-free-ops
1355   '(byte-constant byte-dup byte-symbolp byte-consp byte-stringp byte-listp
1356     byte-integerp byte-numberp byte-eq byte-equal byte-not byte-car-safe
1357     byte-cdr-safe byte-cons byte-list1 byte-list2 byte-point byte-point-max
1358     byte-point-min byte-following-char byte-preceding-char
1359     byte-current-column byte-eolp byte-eobp byte-bolp byte-bobp
1360     byte-current-buffer byte-interactive-p))
1361
1362 (defconst byte-compile-side-effect-free-ops
1363   (nconc 
1364    '(byte-varref byte-nth byte-memq byte-car byte-cdr byte-length byte-aref
1365      byte-symbol-value byte-get byte-concat2 byte-concat3 byte-sub1 byte-add1
1366      byte-eqlsign byte-gtr byte-lss byte-leq byte-geq byte-diff byte-negate
1367      byte-plus byte-max byte-min byte-mult byte-char-after byte-char-syntax
1368      byte-buffer-substring byte-string= byte-string< byte-nthcdr byte-elt
1369      byte-member byte-assq byte-quo byte-rem)
1370    byte-compile-side-effect-and-error-free-ops))
1371
1372 ;;; This piece of shit is because of the way DEFVAR_BOOL() variables work.
1373 ;;; Consider the code
1374 ;;;
1375 ;;;     (defun foo (flag)
1376 ;;;       (let ((old-pop-ups pop-up-windows)
1377 ;;;             (pop-up-windows flag))
1378 ;;;         (cond ((not (eq pop-up-windows old-pop-ups))
1379 ;;;                (setq old-pop-ups pop-up-windows)
1380 ;;;                ...))))
1381 ;;;
1382 ;;; Uncompiled, old-pop-ups will always be set to nil or t, even if FLAG is
1383 ;;; something else.  But if we optimize
1384 ;;;
1385 ;;;     varref flag
1386 ;;;     varbind pop-up-windows
1387 ;;;     varref pop-up-windows
1388 ;;;     not
1389 ;;; to
1390 ;;;     varref flag
1391 ;;;     dup
1392 ;;;     varbind pop-up-windows
1393 ;;;     not
1394 ;;;
1395 ;;; we break the program, because it will appear that pop-up-windows and 
1396 ;;; old-pop-ups are not EQ when really they are.  So we have to know what
1397 ;;; the BOOL variables are, and not perform this optimization on them.
1398 ;;;
1399
1400 ;;; This used to hold a large list of boolean variables, which had to
1401 ;;; be updated every time a new DEFVAR_BOOL is added, making it very
1402 ;;; hard to maintain.  Such a list is not necessary under XEmacs,
1403 ;;; where we can use `built-in-variable-type' to query for boolean
1404 ;;; variables.
1405
1406 ;(defconst byte-boolean-vars
1407 ;  '(abbrev-all-caps purify-flag find-file-compare-truenames
1408 ;    find-file-use-truenames delete-auto-save-files byte-metering-on
1409 ;    x-seppuku-on-epipe zmacs-regions zmacs-region-active-p
1410 ;    zmacs-region-stays atomic-extent-goto-char-p
1411 ;    suppress-early-error-handler-backtrace noninteractive
1412 ;    inhibit-early-packages inhibit-autoloads debug-paths
1413 ;    inhibit-site-lisp debug-on-quit debug-on-next-call
1414 ;    modifier-keys-are-sticky x-allow-sendevents
1415 ;    mswindows-dynamic-frame-resize focus-follows-mouse
1416 ;    inhibit-input-event-recording enable-multibyte-characters
1417 ;    disable-auto-save-when-buffer-shrinks
1418 ;    allow-deletion-of-last-visible-frame indent-tabs-mode
1419 ;    load-in-progress load-warn-when-source-newer
1420 ;    load-warn-when-source-only load-ignore-elc-files
1421 ;    load-force-doc-strings fail-on-bucky-bit-character-escapes
1422 ;    popup-menu-titles menubar-show-keybindings completion-ignore-case
1423 ;    canna-empty-info canna-through-info canna-underline
1424 ;    canna-inhibit-hankakukana enable-multibyte-characters
1425 ;    re-short-flag x-handle-non-fully-specified-fonts
1426 ;    print-escape-newlines print-readably delete-exited-processes
1427 ;    windowed-process-io visible-bell no-redraw-on-reenter
1428 ;    cursor-in-echo-area inhibit-warning-display
1429 ;    column-number-start-at-one parse-sexp-ignore-comments
1430 ;    words-include-escapes scroll-on-clipped-lines)
1431 ;  "DEFVAR_BOOL variables.  Giving these any non-nil value sets them to t.
1432 ;If this does not enumerate all DEFVAR_BOOL variables, the byte-optimizer
1433 ;may generate incorrect code.")
1434
1435 (defun byte-optimize-lapcode (lap &optional for-effect)
1436   "Simple peephole optimizer.  LAP is both modified and returned."
1437   (let (lap0 ;; off0 unused
1438         lap1 ;; off1
1439         lap2 ;; off2
1440         (keep-going 'first-time)
1441         (add-depth 0)
1442         rest tmp tmp2 tmp3
1443         (side-effect-free (if byte-compile-delete-errors
1444                               byte-compile-side-effect-free-ops
1445                             byte-compile-side-effect-and-error-free-ops)))
1446     (while keep-going
1447       (or (eq keep-going 'first-time)
1448           (byte-compile-log-lap "  ---- next pass"))
1449       (setq rest lap
1450             keep-going nil)
1451       (while rest
1452         (setq lap0 (car rest)
1453               lap1 (nth 1 rest)
1454               lap2 (nth 2 rest))
1455
1456         ;; You may notice that sequences like "dup varset discard" are
1457         ;; optimized but sequences like "dup varset TAG1: discard" are not.
1458         ;; You may be tempted to change this; resist that temptation.
1459         (cond ;;
1460               ;; <side-effect-free> pop -->  <deleted>
1461               ;;  ...including:
1462               ;; const-X pop   -->  <deleted>
1463               ;; varref-X pop  -->  <deleted>
1464               ;; dup pop       -->  <deleted>
1465               ;;
1466               ((and (eq 'byte-discard (car lap1))
1467                     (memq (car lap0) side-effect-free))
1468                (setq keep-going t)
1469                (setq tmp (aref byte-stack+-info (symbol-value (car lap0))))
1470                (setq rest (cdr rest))
1471                (cond ((= tmp 1)
1472                       (byte-compile-log-lap
1473                        "  %s discard\t-->\t<deleted>" lap0)
1474                       (setq lap (delq lap0 (delq lap1 lap))))
1475                      ((= tmp 0)
1476                       (byte-compile-log-lap
1477                        "  %s discard\t-->\t<deleted> discard" lap0)
1478                       (setq lap (delq lap0 lap)))
1479                      ((= tmp -1)
1480                       (byte-compile-log-lap
1481                        "  %s discard\t-->\tdiscard discard" lap0)
1482                       (setcar lap0 'byte-discard)
1483                       (setcdr lap0 0))
1484                      ((error "Optimizer error: too much on the stack"))))
1485               ;;
1486               ;; goto*-X X:  -->  X:
1487               ;;
1488               ((and (memq (car lap0) byte-goto-ops)
1489                     (eq (cdr lap0) lap1))
1490                (cond ((eq (car lap0) 'byte-goto)
1491                       (setq lap (delq lap0 lap))
1492                       (setq tmp "<deleted>"))
1493                      ((memq (car lap0) byte-goto-always-pop-ops)
1494                       (setcar lap0 (setq tmp 'byte-discard))
1495                       (setcdr lap0 0))
1496                      ((error "Depth conflict at tag %d" (nth 2 lap0))))
1497                (and (memq byte-optimize-log '(t byte))
1498                     (byte-compile-log "  (goto %s) %s:\t-->\t%s %s:"
1499                                       (nth 1 lap1) (nth 1 lap1)
1500                                       tmp (nth 1 lap1)))
1501                (setq keep-going t))
1502               ;;
1503               ;; varset-X varref-X  -->  dup varset-X
1504               ;; varbind-X varref-X  -->  dup varbind-X
1505               ;; const/dup varset-X varref-X --> const/dup varset-X const/dup
1506               ;; const/dup varbind-X varref-X --> const/dup varbind-X const/dup
1507               ;; The latter two can enable other optimizations.
1508               ;;
1509               ((and (eq 'byte-varref (car lap2))
1510                     (eq (cdr lap1) (cdr lap2))
1511                     (memq (car lap1) '(byte-varset byte-varbind)))
1512                (if (and (setq tmp (eq (built-in-variable-type (car (cdr lap2)))
1513                                       'boolean))
1514                         (not (eq (car lap0) 'byte-constant)))
1515                    nil
1516                  (setq keep-going t)
1517                  (if (memq (car lap0) '(byte-constant byte-dup))
1518                      (progn
1519                        (setq tmp (if (or (not tmp)
1520                                          (memq (car (cdr lap0)) '(nil t)))
1521                                      (cdr lap0)
1522                                    (byte-compile-get-constant t)))
1523                        (byte-compile-log-lap "  %s %s %s\t-->\t%s %s %s"
1524                                              lap0 lap1 lap2 lap0 lap1
1525                                              (cons (car lap0) tmp))
1526                        (setcar lap2 (car lap0))
1527                        (setcdr lap2 tmp))
1528                    (byte-compile-log-lap "  %s %s\t-->\tdup %s" lap1 lap2 lap1)
1529                    (setcar lap2 (car lap1))
1530                    (setcar lap1 'byte-dup)
1531                    (setcdr lap1 0)
1532                    ;; The stack depth gets locally increased, so we will
1533                    ;; increase maxdepth in case depth = maxdepth here.
1534                    ;; This can cause the third argument to byte-code to
1535                    ;; be larger than necessary.
1536                    (setq add-depth 1))))
1537               ;;
1538               ;; dup varset-X discard  -->  varset-X
1539               ;; dup varbind-X discard  -->  varbind-X
1540               ;; (the varbind variant can emerge from other optimizations)
1541               ;;
1542               ((and (eq 'byte-dup (car lap0))
1543                     (eq 'byte-discard (car lap2))
1544                     (memq (car lap1) '(byte-varset byte-varbind)))
1545                (byte-compile-log-lap "  dup %s discard\t-->\t%s" lap1 lap1)
1546                (setq keep-going t
1547                      rest (cdr rest))
1548                (setq lap (delq lap0 (delq lap2 lap))))
1549               ;;
1550               ;; not goto-X-if-nil              -->  goto-X-if-non-nil
1551               ;; not goto-X-if-non-nil          -->  goto-X-if-nil
1552               ;;
1553               ;; it is wrong to do the same thing for the -else-pop variants.
1554               ;;
1555               ((and (eq 'byte-not (car lap0))
1556                     (or (eq 'byte-goto-if-nil (car lap1))
1557                         (eq 'byte-goto-if-not-nil (car lap1))))
1558                (byte-compile-log-lap "  not %s\t-->\t%s"
1559                                      lap1
1560                                      (cons
1561                                       (if (eq (car lap1) 'byte-goto-if-nil)
1562                                           'byte-goto-if-not-nil
1563                                         'byte-goto-if-nil)
1564                                       (cdr lap1)))
1565                (setcar lap1 (if (eq (car lap1) 'byte-goto-if-nil)
1566                                 'byte-goto-if-not-nil
1567                                 'byte-goto-if-nil))
1568                (setq lap (delq lap0 lap))
1569                (setq keep-going t))
1570               ;;
1571               ;; goto-X-if-nil     goto-Y X:  -->  goto-Y-if-non-nil X:
1572               ;; goto-X-if-non-nil goto-Y X:  -->  goto-Y-if-nil     X:
1573               ;;
1574               ;; it is wrong to do the same thing for the -else-pop variants.
1575               ;; 
1576               ((and (or (eq 'byte-goto-if-nil (car lap0))
1577                         (eq 'byte-goto-if-not-nil (car lap0)))  ; gotoX
1578                     (eq 'byte-goto (car lap1))                  ; gotoY
1579                     (eq (cdr lap0) lap2))                       ; TAG X
1580                (let ((inverse (if (eq 'byte-goto-if-nil (car lap0))
1581                                   'byte-goto-if-not-nil 'byte-goto-if-nil)))
1582                  (byte-compile-log-lap "  %s %s %s:\t-->\t%s %s:"
1583                                        lap0 lap1 lap2
1584                                        (cons inverse (cdr lap1)) lap2)
1585                  (setq lap (delq lap0 lap))
1586                  (setcar lap1 inverse)
1587                  (setq keep-going t)))
1588               ;;
1589               ;; const goto-if-* --> whatever
1590               ;;
1591               ((and (eq 'byte-constant (car lap0))
1592                     (memq (car lap1) byte-conditional-ops))
1593                (cond ((if (or (eq (car lap1) 'byte-goto-if-nil)
1594                               (eq (car lap1) 'byte-goto-if-nil-else-pop))
1595                           (car (cdr lap0))
1596                         (not (car (cdr lap0))))
1597                       (byte-compile-log-lap "  %s %s\t-->\t<deleted>"
1598                                             lap0 lap1)
1599                       (setq rest (cdr rest)
1600                             lap (delq lap0 (delq lap1 lap))))
1601                      (t
1602                       (if (memq (car lap1) byte-goto-always-pop-ops)
1603                           (progn
1604                             (byte-compile-log-lap "  %s %s\t-->\t%s"
1605                              lap0 lap1 (cons 'byte-goto (cdr lap1)))
1606                             (setq lap (delq lap0 lap)))
1607                         (byte-compile-log-lap "  %s %s\t-->\t%s" lap0 lap1
1608                          (cons 'byte-goto (cdr lap1))))
1609                       (setcar lap1 'byte-goto)))
1610                (setq keep-going t))
1611               ;;
1612               ;; varref-X varref-X  -->  varref-X dup
1613               ;; varref-X [dup ...] varref-X  -->  varref-X [dup ...] dup
1614               ;; We don't optimize the const-X variations on this here,
1615               ;; because that would inhibit some goto optimizations; we
1616               ;; optimize the const-X case after all other optimizations.
1617               ;;
1618               ((and (eq 'byte-varref (car lap0))
1619                     (progn
1620                       (setq tmp (cdr rest))
1621                       (while (eq (car (car tmp)) 'byte-dup)
1622                         (setq tmp (cdr tmp)))
1623                       t)
1624                     (eq (cdr lap0) (cdr (car tmp)))
1625                     (eq 'byte-varref (car (car tmp))))
1626                (if (memq byte-optimize-log '(t byte))
1627                    (let ((str ""))
1628                      (setq tmp2 (cdr rest))
1629                      (while (not (eq tmp tmp2))
1630                        (setq tmp2 (cdr tmp2)
1631                              str (concat str " dup")))
1632                      (byte-compile-log-lap "  %s%s %s\t-->\t%s%s dup"
1633                                            lap0 str lap0 lap0 str)))
1634                (setq keep-going t)
1635                (setcar (car tmp) 'byte-dup)
1636                (setcdr (car tmp) 0)
1637                (setq rest tmp))
1638               ;;
1639               ;; TAG1: TAG2: --> TAG1: <deleted>
1640               ;; (and other references to TAG2 are replaced with TAG1)
1641               ;;
1642               ((and (eq (car lap0) 'TAG)
1643                     (eq (car lap1) 'TAG))
1644                (and (memq byte-optimize-log '(t byte))
1645                     (byte-compile-log "  adjacent tags %d and %d merged"
1646                                       (nth 1 lap1) (nth 1 lap0)))
1647                (setq tmp3 lap)
1648                (while (setq tmp2 (rassq lap0 tmp3))
1649                  (setcdr tmp2 lap1)
1650                  (setq tmp3 (cdr (memq tmp2 tmp3))))
1651                (setq lap (delq lap0 lap)
1652                      keep-going t))
1653               ;;
1654               ;; unused-TAG: --> <deleted>
1655               ;;
1656               ((and (eq 'TAG (car lap0))
1657                     (not (rassq lap0 lap)))
1658                (and (memq byte-optimize-log '(t byte))
1659                     (byte-compile-log "  unused tag %d removed" (nth 1 lap0)))
1660                (setq lap (delq lap0 lap)
1661                      keep-going t))
1662               ;;
1663               ;; goto   ... --> goto   <delete until TAG or end>
1664               ;; return ... --> return <delete until TAG or end>
1665               ;;
1666               ((and (memq (car lap0) '(byte-goto byte-return))
1667                     (not (memq (car lap1) '(TAG nil))))
1668                (setq tmp rest)
1669                (let ((i 0)
1670                      (opt-p (memq byte-optimize-log '(t lap)))
1671                      str deleted)
1672                  (while (and (setq tmp (cdr tmp))
1673                              (not (eq 'TAG (car (car tmp)))))
1674                    (if opt-p (setq deleted (cons (car tmp) deleted)
1675                                    str (concat str " %s")
1676                                    i (1+ i))))
1677                  (if opt-p
1678                      (let ((tagstr 
1679                             (if (eq 'TAG (car (car tmp)))
1680                                 (format "%d:" (car (cdr (car tmp))))
1681                               (or (car tmp) ""))))
1682                        (if (< i 6)
1683                            (apply 'byte-compile-log-lap-1
1684                                   (concat "  %s" str
1685                                           " %s\t-->\t%s <deleted> %s")
1686                                   lap0
1687                                   (nconc (nreverse deleted)
1688                                          (list tagstr lap0 tagstr)))
1689                          (byte-compile-log-lap
1690                           "  %s <%d unreachable op%s> %s\t-->\t%s <deleted> %s"
1691                           lap0 i (if (= i 1) "" "s")
1692                           tagstr lap0 tagstr))))
1693                  (rplacd rest tmp))
1694                (setq keep-going t))
1695               ;;
1696               ;; <safe-op> unbind --> unbind <safe-op>
1697               ;; (this may enable other optimizations.)
1698               ;;
1699               ((and (eq 'byte-unbind (car lap1))
1700                     (memq (car lap0) byte-after-unbind-ops))
1701                (byte-compile-log-lap "  %s %s\t-->\t%s %s" lap0 lap1 lap1 lap0)
1702                (setcar rest lap1)
1703                (setcar (cdr rest) lap0)
1704                (setq keep-going t))
1705               ;;
1706               ;; varbind-X unbind-N         -->  discard unbind-(N-1)
1707               ;; save-excursion unbind-N    -->  unbind-(N-1)
1708               ;; save-restriction unbind-N  -->  unbind-(N-1)
1709               ;;
1710               ((and (eq 'byte-unbind (car lap1))
1711                     (memq (car lap0) '(byte-varbind byte-save-excursion
1712                                        byte-save-restriction))
1713                     (< 0 (cdr lap1)))
1714                (if (zerop (setcdr lap1 (1- (cdr lap1))))
1715                    (delq lap1 rest))
1716                (if (eq (car lap0) 'byte-varbind)
1717                    (setcar rest (cons 'byte-discard 0))
1718                  (setq lap (delq lap0 lap)))
1719                (byte-compile-log-lap "  %s %s\t-->\t%s %s"
1720                  lap0 (cons (car lap1) (1+ (cdr lap1)))
1721                  (if (eq (car lap0) 'byte-varbind)
1722                      (car rest)
1723                    (car (cdr rest)))
1724                  (if (and (/= 0 (cdr lap1))
1725                           (eq (car lap0) 'byte-varbind))
1726                      (car (cdr rest))
1727                    ""))
1728                (setq keep-going t))
1729               ;;
1730               ;; goto*-X ... X: goto-Y  --> goto*-Y
1731               ;; goto-X ...  X: return  --> return
1732               ;;
1733               ((and (memq (car lap0) byte-goto-ops)
1734                     (memq (car (setq tmp (nth 1 (memq (cdr lap0) lap))))
1735                           '(byte-goto byte-return)))
1736                (cond ((and (not (eq tmp lap0))
1737                            (or (eq (car lap0) 'byte-goto)
1738                                (eq (car tmp) 'byte-goto)))
1739                       (byte-compile-log-lap "  %s [%s]\t-->\t%s"
1740                                             (car lap0) tmp tmp)
1741                       (if (eq (car tmp) 'byte-return)
1742                           (setcar lap0 'byte-return))
1743                       (setcdr lap0 (cdr tmp))
1744                       (setq keep-going t))))
1745               ;;
1746               ;; goto-*-else-pop X ... X: goto-if-* --> whatever
1747               ;; goto-*-else-pop X ... X: discard --> whatever
1748               ;;
1749               ((and (memq (car lap0) '(byte-goto-if-nil-else-pop
1750                                        byte-goto-if-not-nil-else-pop))
1751                     (memq (car (car (setq tmp (cdr (memq (cdr lap0) lap)))))
1752                           (eval-when-compile
1753                            (cons 'byte-discard byte-conditional-ops)))
1754                     (not (eq lap0 (car tmp))))
1755                (setq tmp2 (car tmp))
1756                (setq tmp3 (assq (car lap0) '((byte-goto-if-nil-else-pop
1757                                               byte-goto-if-nil)
1758                                              (byte-goto-if-not-nil-else-pop
1759                                               byte-goto-if-not-nil))))
1760                (if (memq (car tmp2) tmp3)
1761                    (progn (setcar lap0 (car tmp2))
1762                           (setcdr lap0 (cdr tmp2))
1763                           (byte-compile-log-lap "  %s-else-pop [%s]\t-->\t%s"
1764                                                 (car lap0) tmp2 lap0))
1765                  ;; Get rid of the -else-pop's and jump one step further.
1766                  (or (eq 'TAG (car (nth 1 tmp)))
1767                      (setcdr tmp (cons (byte-compile-make-tag)
1768                                        (cdr tmp))))
1769                  (byte-compile-log-lap "  %s [%s]\t-->\t%s <skip>"
1770                                        (car lap0) tmp2 (nth 1 tmp3))
1771                  (setcar lap0 (nth 1 tmp3))
1772                  (setcdr lap0 (nth 1 tmp)))
1773                (setq keep-going t))
1774               ;;
1775               ;; const goto-X ... X: goto-if-* --> whatever
1776               ;; const goto-X ... X: discard   --> whatever
1777               ;;
1778               ((and (eq (car lap0) 'byte-constant)
1779                     (eq (car lap1) 'byte-goto)
1780                     (memq (car (car (setq tmp (cdr (memq (cdr lap1) lap)))))
1781                           (eval-when-compile
1782                             (cons 'byte-discard byte-conditional-ops)))
1783                     (not (eq lap1 (car tmp))))
1784                (setq tmp2 (car tmp))
1785                (cond ((memq (car tmp2)
1786                             (if (null (car (cdr lap0)))
1787                                 '(byte-goto-if-nil byte-goto-if-nil-else-pop)
1788                               '(byte-goto-if-not-nil
1789                                 byte-goto-if-not-nil-else-pop)))
1790                       (byte-compile-log-lap "  %s goto [%s]\t-->\t%s %s"
1791                                             lap0 tmp2 lap0 tmp2)
1792                       (setcar lap1 (car tmp2))
1793                       (setcdr lap1 (cdr tmp2))
1794                       ;; Let next step fix the (const,goto-if*) sequence.
1795                       (setq rest (cons nil rest)))
1796                      (t
1797                       ;; Jump one step further
1798                       (byte-compile-log-lap
1799                        "  %s goto [%s]\t-->\t<deleted> goto <skip>"
1800                        lap0 tmp2)
1801                       (or (eq 'TAG (car (nth 1 tmp)))
1802                           (setcdr tmp (cons (byte-compile-make-tag)
1803                                             (cdr tmp))))
1804                       (setcdr lap1 (car (cdr tmp)))
1805                       (setq lap (delq lap0 lap))))
1806                (setq keep-going t))
1807               ;;
1808               ;; X: varref-Y    ...     varset-Y goto-X  -->
1809               ;; X: varref-Y Z: ... dup varset-Y goto-Z
1810               ;; (varset-X goto-BACK, BACK: varref-X --> copy the varref down.)
1811               ;; (This is so usual for while loops that it is worth handling).
1812               ;;
1813               ((and (eq (car lap1) 'byte-varset)
1814                     (eq (car lap2) 'byte-goto)
1815                     (not (memq (cdr lap2) rest)) ;Backwards jump
1816                     (eq (car (car (setq tmp (cdr (memq (cdr lap2) lap)))))
1817                         'byte-varref)
1818                     (eq (cdr (car tmp)) (cdr lap1))
1819                     (not (eq (built-in-variable-type (car (cdr lap1)))
1820                              'boolean)))
1821                ;;(byte-compile-log-lap "  Pulled %s to end of loop" (car tmp))
1822                (let ((newtag (byte-compile-make-tag)))
1823                  (byte-compile-log-lap
1824                   "  %s: %s ... %s %s\t-->\t%s: %s %s: ... %s %s %s"
1825                   (nth 1 (cdr lap2)) (car tmp)
1826                   lap1 lap2
1827                   (nth 1 (cdr lap2)) (car tmp)
1828                   (nth 1 newtag) 'byte-dup lap1
1829                   (cons 'byte-goto newtag)
1830                   )
1831                  (setcdr rest (cons (cons 'byte-dup 0) (cdr rest)))
1832                  (setcdr tmp (cons (setcdr lap2 newtag) (cdr tmp))))
1833                (setq add-depth 1)
1834                (setq keep-going t))
1835               ;;
1836               ;; goto-X Y: ... X: goto-if*-Y  -->  goto-if-not-*-X+1 Y:
1837               ;; (This can pull the loop test to the end of the loop)
1838               ;;
1839               ((and (eq (car lap0) 'byte-goto)
1840                     (eq (car lap1) 'TAG)
1841                     (eq lap1
1842                         (cdr (car (setq tmp (cdr (memq (cdr lap0) lap))))))
1843                     (memq (car (car tmp))
1844                           '(byte-goto byte-goto-if-nil byte-goto-if-not-nil
1845                                       byte-goto-if-nil-else-pop)))
1846 ;;             (byte-compile-log-lap "  %s %s, %s %s  --> moved conditional"
1847 ;;                                   lap0 lap1 (cdr lap0) (car tmp))
1848                (let ((newtag (byte-compile-make-tag)))
1849                  (byte-compile-log-lap
1850                   "%s %s: ... %s: %s\t-->\t%s ... %s:"
1851                   lap0 (nth 1 lap1) (nth 1 (cdr lap0)) (car tmp)
1852                   (cons (cdr (assq (car (car tmp))
1853                                    '((byte-goto-if-nil . byte-goto-if-not-nil)
1854                                      (byte-goto-if-not-nil . byte-goto-if-nil)
1855                                      (byte-goto-if-nil-else-pop .
1856                                       byte-goto-if-not-nil-else-pop)
1857                                      (byte-goto-if-not-nil-else-pop .
1858                                       byte-goto-if-nil-else-pop))))
1859                         newtag)
1860                   
1861                   (nth 1 newtag)
1862                   )
1863                  (setcdr tmp (cons (setcdr lap0 newtag) (cdr tmp)))
1864                  (if (eq (car (car tmp)) 'byte-goto-if-nil-else-pop)
1865                      ;; We can handle this case but not the -if-not-nil case,
1866                      ;; because we won't know which non-nil constant to push.
1867                    (setcdr rest (cons (cons 'byte-constant
1868                                             (byte-compile-get-constant nil))
1869                                       (cdr rest))))
1870                (setcar lap0 (nth 1 (memq (car (car tmp))
1871                                          '(byte-goto-if-nil-else-pop
1872                                            byte-goto-if-not-nil
1873                                            byte-goto-if-nil
1874                                            byte-goto-if-not-nil
1875                                            byte-goto byte-goto))))
1876                )
1877                (setq keep-going t))
1878               )
1879         (setq rest (cdr rest)))
1880       )
1881     ;; Cleanup stage:
1882     ;; Rebuild byte-compile-constants / byte-compile-variables.
1883     ;; Simple optimizations that would inhibit other optimizations if they
1884     ;; were done in the optimizing loop, and optimizations which there is no
1885     ;;  need to do more than once.
1886     (setq byte-compile-constants nil
1887           byte-compile-variables nil)
1888     (setq rest lap)
1889     (while rest
1890       (setq lap0 (car rest)
1891             lap1 (nth 1 rest))
1892       (if (memq (car lap0) byte-constref-ops)
1893           (if (eq (cdr lap0) 'byte-constant)
1894               (or (memq (cdr lap0) byte-compile-variables)
1895                   (setq byte-compile-variables (cons (cdr lap0)
1896                                                      byte-compile-variables)))
1897             (or (memq (cdr lap0) byte-compile-constants)
1898                 (setq byte-compile-constants (cons (cdr lap0)
1899                                                    byte-compile-constants)))))
1900       (cond (;;
1901              ;; const-C varset-X const-C  -->  const-C dup varset-X
1902              ;; const-C varbind-X const-C  -->  const-C dup varbind-X
1903              ;;
1904              (and (eq (car lap0) 'byte-constant)
1905                   (eq (car (nth 2 rest)) 'byte-constant)
1906                   (eq (cdr lap0) (car (nth 2 rest)))
1907                   (memq (car lap1) '(byte-varbind byte-varset)))
1908              (byte-compile-log-lap "  %s %s %s\t-->\t%s dup %s"
1909                                    lap0 lap1 lap0 lap0 lap1)
1910              (setcar (cdr (cdr rest)) (cons (car lap1) (cdr lap1)))
1911              (setcar (cdr rest) (cons 'byte-dup 0))
1912              (setq add-depth 1))
1913             ;;
1914             ;; const-X  [dup/const-X ...]   -->  const-X  [dup ...] dup
1915             ;; varref-X [dup/varref-X ...]  -->  varref-X [dup ...] dup
1916             ;;
1917             ((memq (car lap0) '(byte-constant byte-varref))
1918              (setq tmp rest
1919                    tmp2 nil)
1920              (while (progn
1921                       (while (eq 'byte-dup (car (car (setq tmp (cdr tmp))))))
1922                       (and (eq (cdr lap0) (cdr (car tmp)))
1923                            (eq (car lap0) (car (car tmp)))))
1924                (setcar tmp (cons 'byte-dup 0))
1925                (setq tmp2 t))
1926              (if tmp2
1927                  (byte-compile-log-lap
1928                   "  %s [dup/%s]...\t-->\t%s dup..." lap0 lap0 lap0)))
1929             ;;
1930             ;; unbind-N unbind-M  -->  unbind-(N+M)
1931             ;;
1932             ((and (eq 'byte-unbind (car lap0))
1933                   (eq 'byte-unbind (car lap1)))
1934              (byte-compile-log-lap "  %s %s\t-->\t%s" lap0 lap1
1935                                    (cons 'byte-unbind
1936                                          (+ (cdr lap0) (cdr lap1))))
1937              (setq keep-going t)
1938              (setq lap (delq lap0 lap))
1939              (setcdr lap1 (+ (cdr lap1) (cdr lap0))))
1940             )
1941       (setq rest (cdr rest)))
1942     (setq byte-compile-maxdepth (+ byte-compile-maxdepth add-depth)))
1943   lap)
1944
1945 (provide 'byte-optimize)
1946
1947 \f
1948 ;; To avoid "lisp nesting exceeds max-lisp-eval-depth" when this file compiles
1949 ;; itself, compile some of its most used recursive functions (at load time).
1950 ;;
1951 (eval-when-compile
1952  (or (compiled-function-p (symbol-function 'byte-optimize-form))
1953      (assq 'byte-code (symbol-function 'byte-optimize-form))
1954      (let ((byte-optimize nil)
1955            (byte-compile-warnings nil))
1956        (mapcar '(lambda (x)
1957                   (or noninteractive (message "compiling %s..." x))
1958                   (byte-compile x)
1959                   (or noninteractive (message "compiling %s...done" x)))
1960                '(byte-optimize-form
1961                  byte-optimize-body
1962                  byte-optimize-predicate
1963                  byte-optimize-binary-predicate
1964                  ;; Inserted some more than necessary, to speed it up.
1965                  byte-optimize-form-code-walker
1966                  byte-optimize-lapcode))))
1967  nil)
1968
1969 ;;; byte-optimize.el ends here