source: trunk/abcl/src/org/armedbear/lisp/compiler-pass1.lisp @ 12154

Last change on this file since 12154 was 12154, checked in by ehuelsmann, 16 years ago

TAGBODY efficiency: only check those tags which are being used

as "targets" for Go exceptions.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 46.7 KB
Line 
1;;; compiler-pass1.lisp
2;;;
3;;; Copyright (C) 2003-2008 Peter Graves
4;;; $Id: compiler-pass1.lisp 12154 2009-09-18 20:40:44Z ehuelsmann $
5;;;
6;;; This program is free software; you can redistribute it and/or
7;;; modify it under the terms of the GNU General Public License
8;;; as published by the Free Software Foundation; either version 2
9;;; of the License, or (at your option) any later version.
10;;;
11;;; This program is distributed in the hope that it will be useful,
12;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
13;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14;;; GNU General Public License for more details.
15;;;
16;;; You should have received a copy of the GNU General Public License
17;;; along with this program; if not, write to the Free Software
18;;; Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301, USA.
19;;;
20;;; As a special exception, the copyright holders of this library give you
21;;; permission to link this library with independent modules to produce an
22;;; executable, regardless of the license terms of these independent
23;;; modules, and to copy and distribute the resulting executable under
24;;; terms of your choice, provided that you also meet, for each linked
25;;; independent module, the terms and conditions of the license of that
26;;; module.  An independent module is a module which is not derived from
27;;; or based on this library.  If you modify this library, you may extend
28;;; this exception to your version of the library, but you are not
29;;; obligated to do so.  If you do not wish to do so, delete this
30;;; exception statement from your version.
31
32(in-package "JVM")
33
34(eval-when (:compile-toplevel :load-toplevel :execute)
35  (require "LOOP")
36  (require "FORMAT")
37  (require "CLOS")
38  (require "PRINT-OBJECT")
39  (require "COMPILER-TYPES")
40  (require "KNOWN-FUNCTIONS")
41  (require "KNOWN-SYMBOLS")
42  (require "DUMP-FORM")
43  (require "OPCODES")
44  (require "JAVA"))
45
46
47(eval-when (:compile-toplevel :load-toplevel :execute)
48  (defun generate-inline-expansion (block-name lambda-list body)
49    (cond ((intersection lambda-list
50                         '(&optional &rest &key &allow-other-keys &aux)
51                         :test #'eq)
52           nil)
53          (t
54           (setf body (copy-tree body))
55           (list 'LAMBDA lambda-list
56                 (list* 'BLOCK block-name body)))))
57  ) ; EVAL-WHEN
58
59;;; Pass 1.
60
61
62;; Returns a list of declared free specials, if any are found.
63(declaim (ftype (function (list list block-node) list)
64                process-declarations-for-vars))
65(defun process-declarations-for-vars (body variables block)
66  (let ((free-specials '()))
67    (dolist (subform body)
68      (unless (and (consp subform) (eq (%car subform) 'DECLARE))
69        (return))
70      (let ((decls (%cdr subform)))
71        (dolist (decl decls)
72          (case (car decl)
73            ((DYNAMIC-EXTENT FTYPE INLINE NOTINLINE OPTIMIZE)
74             ;; Nothing to do here.
75             )
76            ((IGNORE IGNORABLE)
77             (process-ignore/ignorable (%car decl) (%cdr decl) variables))
78            (SPECIAL
79             (dolist (name (%cdr decl))
80               (let ((variable (find-variable name variables)))
81                 (cond ((and variable
82                             ;; see comment below (and DO-ALL-SYMBOLS.11)
83                             (eq (variable-compiland variable)
84                                 *current-compiland*))
85                        (setf (variable-special-p variable) t))
86                       (t
87                        (dformat t "adding free special ~S~%" name)
88                        (push (make-variable :name name :special-p t
89                                             :block block)
90                              free-specials))))))
91            (TYPE
92             (dolist (name (cddr decl))
93               (let ((variable (find-variable name variables)))
94                 (when (and variable
95                            ;; Don't apply a declaration in a local function to
96                            ;; a variable defined in its parent. For an example,
97                            ;; see CREATE-GREEDY-NO-ZERO-MATCHER in cl-ppcre.
98                            ;; FIXME suboptimal, since we ignore the declaration
99                            (eq (variable-compiland variable)
100                                *current-compiland*))
101                   (setf (variable-declared-type variable)
102                         (make-compiler-type (cadr decl)))))))
103            (t
104             (dolist (name (cdr decl))
105               (let ((variable (find-variable name variables)))
106                 (when variable
107                   (setf (variable-declared-type variable)
108                         (make-compiler-type (%car decl)))))))))))
109    free-specials))
110
111(defun check-name (name)
112  ;; FIXME Currently this error is signalled by the precompiler.
113  (unless (symbolp name)
114    (compiler-error "The variable ~S is not a symbol." name))
115  (when (constantp name)
116    (compiler-error "The name of the variable ~S is already in use to name a constant." name))
117  name)
118
119(declaim (ftype (function (t) t) p1-body))
120(defun p1-body (body)
121  (declare (optimize speed))
122  (let ((tail body))
123    (loop
124      (when (endp tail)
125        (return))
126      (setf (car tail) (p1 (%car tail)))
127      (setf tail (%cdr tail))))
128  body)
129
130(defknown p1-default (t) t)
131(declaim (inline p1-default))
132(defun p1-default (form)
133  (setf (cdr form) (p1-body (cdr form)))
134  form)
135
136(defknown p1-if (t) t)
137(defun p1-if (form)
138  (let ((test (cadr form)))
139    (cond ((unsafe-p test)
140           (cond ((and (consp test)
141                       (memq (%car test) '(GO RETURN-FROM THROW)))
142                  (p1 test))
143                 (t
144                  (let* ((var (gensym))
145                         (new-form
146                          `(let ((,var ,test))
147                             (if ,var ,(third form) ,(fourth form)))))
148                    (p1 new-form)))))
149          (t
150           (p1-default form)))))
151
152
153(defmacro p1-let/let*-vars 
154    (block varlist variables-var var body1 body2)
155  (let ((varspec (gensym))
156  (initform (gensym))
157  (name (gensym)))
158    `(let ((,variables-var ()))
159       (dolist (,varspec ,varlist)
160   (cond ((consp ,varspec)
161                ;; Even though the precompiler already signals this
162                ;; error, double checking can't hurt; after all, we're
163                ;; also rewriting &AUX into LET* bindings.
164    (unless (<= 1 (length ,varspec) 2)
165      (compiler-error "The LET/LET* binding specification ~S is invalid."
166          ,varspec))
167    (let* ((,name (%car ,varspec))
168           (,initform (p1 (%cadr ,varspec)))
169           (,var (make-variable :name (check-name ,name)
170                                            :initform ,initform
171                                            :block ,block)))
172      (push ,var ,variables-var)
173      ,@body1))
174         (t
175    (let ((,var (make-variable :name (check-name ,varspec)
176                                           :block ,block)))
177      (push ,var ,variables-var)
178      ,@body1))))
179       ,@body2)))
180
181(defknown p1-let-vars (t) t)
182(defun p1-let-vars (block varlist)
183  (p1-let/let*-vars block
184   varlist vars var
185   ()
186   ((setf vars (nreverse vars))
187    (dolist (variable vars)
188      (push variable *visible-variables*)
189      (push variable *all-variables*))
190    vars)))
191
192(defknown p1-let*-vars (t) t)
193(defun p1-let*-vars (block varlist)
194  (p1-let/let*-vars block
195   varlist vars var
196   ((push var *visible-variables*)
197    (push var *all-variables*))
198   ((nreverse vars))))
199
200(defun p1-let/let* (form)
201  (declare (type cons form))
202  (let* ((*visible-variables* *visible-variables*)
203         (block (make-let/let*-node))
204         (op (%car form))
205         (varlist (cadr form))
206         (body (cddr form)))
207    (aver (or (eq op 'LET) (eq op 'LET*)))
208    (when (eq op 'LET)
209      ;; Convert to LET* if possible.
210      (if (null (cdr varlist))
211          (setf op 'LET*)
212          (dolist (varspec varlist (setf op 'LET*))
213            (or (atom varspec)
214                (constantp (cadr varspec))
215                (eq (car varspec) (cadr varspec))
216                (return)))))
217    (let ((vars (if (eq op 'LET)
218                    (p1-let-vars block varlist)
219                    (p1-let*-vars block varlist))))
220      ;; Check for globally declared specials.
221      (dolist (variable vars)
222        (when (special-variable-p (variable-name variable))
223          (setf (variable-special-p variable) t
224                (let-environment-register block) t)))
225      ;; For processing declarations, we want to walk the variable list from
226      ;; last to first, since declarations apply to the last-defined variable
227      ;; with the specified name.
228      (setf (let-free-specials block)
229            (process-declarations-for-vars body (reverse vars) block))
230      (setf (let-vars block) vars)
231      ;; Make free specials visible.
232      (dolist (variable (let-free-specials block))
233        (push variable *visible-variables*)))
234    (let ((*blocks* (cons block *blocks*)))
235      (setf body (p1-body body)))
236    (setf (let-form block) (list* op varlist body))
237    block))
238
239(defun p1-locally (form)
240  (let* ((*visible-variables* *visible-variables*)
241         (block (make-locally-node))
242         (free-specials (process-declarations-for-vars (cdr form) nil block)))
243    (setf (locally-free-specials block) free-specials)
244    (dolist (special free-specials)
245;;       (format t "p1-locally ~S is special~%" name)
246      (push special *visible-variables*))
247    (let ((*blocks* (cons block *blocks*)))
248      (setf (locally-form block)
249            (list* 'LOCALLY (p1-body (cdr form))))
250      block)))
251
252(defknown p1-m-v-b (t) t)
253(defun p1-m-v-b (form)
254  (when (= (length (cadr form)) 1)
255    (let ((new-form `(let* ((,(caadr form) ,(caddr form))) ,@(cdddr form))))
256      (return-from p1-m-v-b (p1-let/let* new-form))))
257  (let* ((*visible-variables* *visible-variables*)
258         (block (make-m-v-b-node))
259         (varlist (cadr form))
260         ;; Process the values-form first. ("The scopes of the name binding and
261         ;; declarations do not include the values-form.")
262         (values-form (p1 (caddr form)))
263         (*blocks* (cons block *blocks*))
264         (body (cdddr form)))
265    (let ((vars ()))
266      (dolist (symbol varlist)
267        (let ((var (make-variable :name symbol :block block)))
268          (push var vars)
269          (push var *visible-variables*)
270          (push var *all-variables*)))
271      ;; Check for globally declared specials.
272      (dolist (variable vars)
273        (when (special-variable-p (variable-name variable))
274          (setf (variable-special-p variable) t
275                (m-v-b-environment-register block) t)))
276      (setf (m-v-b-free-specials block)
277            (process-declarations-for-vars body vars block))
278      (dolist (special (m-v-b-free-specials block))
279        (push special *visible-variables*))
280      (setf (m-v-b-vars block) (nreverse vars)))
281    (setf body (p1-body body))
282    (setf (m-v-b-form block)
283          (list* 'MULTIPLE-VALUE-BIND varlist values-form body))
284    block))
285
286(defun p1-block (form)
287  (let* ((block (make-block-node (cadr form)))
288         (*blocks* (cons block *blocks*)))
289    (setf (cddr form) (p1-body (cddr form)))
290    (setf (block-form block) form)
291    block))
292
293(defun p1-catch (form)
294  (let* ((tag (p1 (cadr form)))
295         (body (cddr form))
296         (block (make-catch-node))
297         ;; our subform processors need to know
298         ;; they're enclosed in a CATCH block
299         (*blocks* (cons block *blocks*))
300         (result '()))
301    (dolist (subform body)
302      (let ((op (and (consp subform) (%car subform))))
303        (push (p1 subform) result)
304        (when (memq op '(GO RETURN-FROM THROW))
305          (return))))
306    (setf result (nreverse result))
307    (when (and (null (cdr result))
308               (consp (car result))
309               (eq (caar result) 'GO))
310      (return-from p1-catch (car result)))
311    (push tag result)
312    (push 'CATCH result)
313    (setf (catch-form block) result)
314    block))
315
316(defun p1-threads-synchronized-on (form)
317  (let* ((synchronized-object (p1 (cadr form)))
318         (body (cddr form))
319         (block (make-synchronized-node))
320         (*blocks* (cons block *blocks*))
321         result)
322    (dolist (subform body)
323      (let ((op (and (consp subform) (%car subform))))
324        (push (p1 subform) result)
325        (when (memq op '(GO RETURN-FROM THROW))
326          (return))))
327    (setf (synchronized-form block)
328          (list* 'threads:synchronized-on synchronized-object
329                 (nreverse result)))
330    block))
331
332(defun p1-unwind-protect (form)
333  (if (= (length form) 2)
334      (p1 (second form)) ; No cleanup forms: (unwind-protect (...)) => (...)
335
336      ;; in order to compile the cleanup forms twice (see
337      ;; p2-unwind-protect-node), we need to p1 them twice; p1 outcomes
338      ;; can be compiled (in the same compiland?) only once.
339      ;;
340      ;; However, p1 transforms the forms being processed, so, we
341      ;; need to copy the forms to create a second copy.
342      (let* ((block (make-unwind-protect-node))
343             ;; a bit of jumping through hoops...
344             (unwinding-forms (p1-body (copy-tree (cddr form))))
345             (unprotected-forms (p1-body (cddr form)))
346             ;; ... because only the protected form is
347             ;; protected by the UNWIND-PROTECT block
348             (*blocks* (cons block *blocks*))
349             (protected-form (p1 (cadr form))))
350        (setf (unwind-protect-form block)
351              `(unwind-protect ,protected-form
352                 (progn ,@unwinding-forms)
353                 ,@unprotected-forms))
354        block)))
355
356(defknown p1-return-from (t) t)
357(defun p1-return-from (form)
358  (let* ((name (second form))
359         (block (find-block name)))
360    (when (null block)
361      (compiler-error "RETURN-FROM ~S: no block named ~S is currently visible."
362                      name name))
363    (dformat t "p1-return-from block = ~S~%" (block-name block))
364    (cond ((eq (block-compiland block) *current-compiland*)
365           ;; Local case. If the RETURN is nested inside an UNWIND-PROTECT
366           ;; which is inside the block we're returning from, we'll do a non-
367           ;; local return anyway so that UNWIND-PROTECT can catch it and run
368           ;; its cleanup forms.
369           ;;(dformat t "*blocks* = ~S~%" (mapcar #'node-name *blocks*))
370           (let ((protected (enclosed-by-protected-block-p block)))
371             (dformat t "p1-return-from protected = ~S~%" protected)
372             (if protected
373                 (setf (block-non-local-return-p block) t)
374                 ;; non-local GO's ensure environment restoration
375                 ;; find out about this local GO
376                 (when (null (block-needs-environment-restoration block))
377                   (setf (block-needs-environment-restoration block)
378                         (enclosed-by-environment-setting-block-p block))))))
379          (t
380           (setf (block-non-local-return-p block) t)))
381    (when (block-non-local-return-p block)
382      (dformat t "non-local return from block ~S~%" (block-name block))))
383  (list* 'RETURN-FROM (cadr form) (mapcar #'p1 (cddr form))))
384
385(defun p1-tagbody (form)
386  (let* ((block (make-tagbody-node))
387         (*blocks* (cons block *blocks*))
388         (*visible-tags* *visible-tags*)
389         (local-tags '())
390         (body (cdr form)))
391    ;; Make all the tags visible before processing the body forms.
392    (dolist (subform body)
393      (when (or (symbolp subform) (integerp subform))
394        (let* ((tag (make-tag :name subform :label (gensym) :block block)))
395          (push tag local-tags)
396          (push tag *visible-tags*))))
397    (let ((new-body '())
398          (live t))
399      (dolist (subform body)
400        (cond ((or (symbolp subform) (integerp subform))
401               (push subform new-body)
402               (push (find subform local-tags :key #'tag-name :test #'eql)
403                     (tagbody-tags block))
404               (setf live t))
405              ((not live)
406               ;; Nothing to do.
407               )
408              (t
409               (when (and (consp subform)
410                          (memq (%car subform) '(GO RETURN-FROM THROW)))
411                 ;; Subsequent subforms are unreachable until we see another
412                 ;; tag.
413                 (setf live nil))
414               (push (p1 subform) new-body))))
415      (setf (tagbody-form block) (list* 'TAGBODY (nreverse new-body))))
416    block))
417
418(defknown p1-go (t) t)
419(defun p1-go (form)
420  (let* ((name (cadr form))
421         (tag (find-tag name)))
422    (unless tag
423      (error "p1-go: tag not found: ~S" name))
424    (setf (tag-used tag) t)
425    (let ((tag-block (tag-block tag)))
426      (cond ((eq (tag-compiland tag) *current-compiland*)
427             ;; Does the GO leave an enclosing UNWIND-PROTECT or CATCH?
428             (if (enclosed-by-protected-block-p tag-block)
429                 (setf (tagbody-non-local-go-p tag-block) t
430                       (tag-used-non-locally tag) t)
431                 ;; non-local GO's ensure environment restoration
432                 ;; find out about this local GO
433                 (when (null (tagbody-needs-environment-restoration tag-block))
434                   (setf (tagbody-needs-environment-restoration tag-block)
435                         (enclosed-by-environment-setting-block-p tag-block)))))
436            (t
437             (setf (tagbody-non-local-go-p tag-block) t
438                   (tag-used-non-locally tag) t)))))
439  form)
440
441(defun validate-function-name (name)
442  (unless (or (symbolp name) (setf-function-name-p name))
443    (compiler-error "~S is not a valid function name." name)))
444
445(defmacro with-local-functions-for-flet/labels
446    (form local-functions-var lambda-list-var name-var body-var body1 body2)
447  `(progn (incf (compiland-children *current-compiland*) (length (cadr ,form)))
448    (let ((*visible-variables* *visible-variables*)
449    (*local-functions* *local-functions*)
450    (*current-compiland* *current-compiland*)
451    (,local-functions-var '()))
452      (dolist (definition (cadr ,form))
453        (let ((,name-var (car definition))
454        (,lambda-list-var (cadr definition)))
455    (validate-function-name ,name-var)
456    (let* ((,body-var (cddr definition))
457           (compiland (make-compiland :name ,name-var
458              :parent *current-compiland*)))
459      ,@body1)))
460      (setf ,local-functions-var (nreverse ,local-functions-var))
461      ;; Make the local functions visible.
462      (dolist (local-function ,local-functions-var)
463        (push local-function *local-functions*)
464        (let ((variable (local-function-variable local-function)))
465    (when variable
466      (push variable *visible-variables*))))
467      ,@body2)))
468
469(defun split-decls (forms specific-vars)
470  (let ((other-decls nil)
471        (specific-decls nil))
472    (dolist (form forms)
473      (unless (and (consp form) (eq (car form) 'DECLARE)) ; shouldn't happen
474        (return))
475      (dolist (decl (cdr form))
476        (case (car decl)
477          ((OPTIMIZE DECLARATION DYNAMIC-EXTENT FTYPE INLINE NOTINLINE)
478           (push (list 'DECLARE decl) other-decls))
479          (SPECIAL
480           (dolist (name (cdr decl))
481             (if (memq name specific-vars)
482                 (push `(DECLARE (SPECIAL ,name)) specific-decls)
483                 (push `(DECLARE (SPECIAL ,name)) other-decls))))
484          (TYPE
485           (dolist (name (cddr decl))
486             (if (memq name specific-vars)
487                 (push `(DECLARE (TYPE ,(cadr decl) ,name)) specific-decls)
488                 (push `(DECLARE (TYPE ,(cadr decl) ,name)) other-decls))))
489          (t
490           (dolist (name (cdr decl))
491             (if (memq name specific-vars)
492                 (push `(DECLARE (,(car decl) ,name)) specific-decls)
493                 (push `(DECLARE (,(car decl) ,name)) other-decls)))))))
494    (values (nreverse other-decls)
495            (nreverse specific-decls))))
496
497(defun rewrite-aux-vars (form)
498  (let* ((lambda-list (cadr form))
499         (aux-p (memq '&AUX lambda-list))
500         (lets (cdr aux-p))
501         aux-vars)
502    (unless aux-p
503      ;; no rewriting required
504      (return-from rewrite-aux-vars form))
505    (multiple-value-bind (body decls)
506        (parse-body (cddr form))
507      (dolist (form lets)
508        (cond ((consp form)
509               (push (car form) aux-vars))
510              (t
511               (push form aux-vars))))
512      (setf lambda-list (subseq lambda-list 0 (position '&AUX lambda-list)))
513      (multiple-value-bind (let-decls lambda-decls)
514          (split-decls decls (lambda-list-names lambda-list))
515        `(lambda ,lambda-list
516           ,@lambda-decls
517           (let* ,lets
518             ,@let-decls
519             ,@body))))))
520
521(defun rewrite-lambda (form)
522  (setf form (rewrite-aux-vars form))
523  (let* ((lambda-list (cadr form)))
524    (if (not (or (memq '&optional lambda-list)
525                 (memq '&key lambda-list)))
526        ;; no need to rewrite: no arguments with possible initforms anyway
527        form
528      (multiple-value-bind (body decls doc)
529          (parse-body (cddr form))
530        (let (state let-bindings new-lambda-list
531                    (non-constants 0))
532          (do* ((vars lambda-list (cdr vars))
533                (var (car vars) (car vars)))
534               ((endp vars))
535            (push (car vars) new-lambda-list)
536            (let ((replacement (gensym)))
537              (flet ((parse-compound-argument (arg)
538                       "Returns the values NAME, KEYWORD, INITFORM, INITFORM-P,
539   SUPPLIED-P and SUPPLIED-P-P assuming ARG is a compound argument."
540                       (destructuring-bind
541                             (name &optional (initform nil initform-supplied-p)
542                                   (supplied-p nil supplied-p-supplied-p))
543                           (if (listp arg) arg (list arg))
544                         (if (listp name)
545                             (values (cadr name) (car name)
546                                     initform initform-supplied-p
547                                     supplied-p supplied-p-supplied-p)
548                             (values name (make-keyword name)
549                                     initform initform-supplied-p
550                                     supplied-p supplied-p-supplied-p)))))
551                (case var
552                  (&optional (setf state :optional))
553                  (&key (setf state :key))
554                  ((&whole &environment &rest &body &allow-other-keys)
555                   ;; do nothing special
556                   )
557                  (t
558                   (cond
559                     ((atom var)
560                      (setf (car new-lambda-list)
561                            (if (eq state :key)
562                                (list (list (make-keyword var) replacement))
563                                replacement))
564                      (push (list var replacement) let-bindings))
565                     ((constantp (second var))
566                      ;; so, we must have a consp-type var we're looking at
567                      ;; and it has a constantp initform
568                      (multiple-value-bind
569                            (name keyword initform initform-supplied-p
570                                  supplied-p supplied-p-supplied-p)
571                          (parse-compound-argument var)
572                        (let ((var-form (if (eq state :key)
573                                            (list keyword replacement)
574                                            replacement))
575                              (supplied-p-replacement (gensym)))
576                          (setf (car new-lambda-list)
577                                (cond
578                                  ((not initform-supplied-p)
579                                   (list var-form))
580                                  ((not supplied-p-supplied-p)
581                                   (list var-form initform))
582                                  (t
583                                   (list var-form initform
584                                         supplied-p-replacement))))
585                          (push (list name replacement) let-bindings)
586                          ;; if there was a 'supplied-p' variable, it might
587                          ;; be used in the declarations. Since those will be
588                          ;; moved below the LET* block, we need to move the
589                          ;; supplied-p parameter too.
590                          (when supplied-p-supplied-p
591                            (push (list supplied-p supplied-p-replacement)
592                                  let-bindings)))))
593                     (t
594                      (incf non-constants)
595                      ;; this is either a keyword or an optional argument
596                      ;; with a non-constantp initform
597                      (multiple-value-bind
598                            (name keyword initform initform-supplied-p
599                                  supplied-p supplied-p-supplied-p)
600                          (parse-compound-argument var)
601                        (declare (ignore initform-supplied-p))
602                        (let ((var-form (if (eq state :key)
603                                            (list keyword replacement)
604                                            replacement))
605                              (supplied-p-replacement (gensym)))
606                          (setf (car new-lambda-list)
607                                (list var-form nil supplied-p-replacement))
608                          (push (list name `(if ,supplied-p-replacement
609                                                ,replacement ,initform))
610                                let-bindings)
611                          (when supplied-p-supplied-p
612                            (push (list supplied-p supplied-p-replacement)
613                                  let-bindings)))))))))))
614          (if (zerop non-constants)
615              ;; there was no reason to rewrite...
616              form
617              (let ((rv
618                     `(lambda ,(nreverse new-lambda-list)
619                        ,@(when doc (list doc))
620                        (let* ,(nreverse let-bindings)
621                          ,@decls ,@body))))
622                rv)))))))
623
624(defun p1-flet (form)
625  (with-local-functions-for-flet/labels
626      form local-functions lambda-list name body
627      ((let ((local-function (make-local-function :name name
628                                                  :compiland compiland)))
629   (multiple-value-bind (body decls) (parse-body body)
630     (let* ((block-name (fdefinition-block-name name))
631      (lambda-expression
632                   (rewrite-lambda
633       `(lambda ,lambda-list ,@decls (block ,block-name ,@body))))
634      (*visible-variables* *visible-variables*)
635      (*local-functions* *local-functions*)
636      (*current-compiland* compiland))
637       (setf (compiland-lambda-expression compiland) lambda-expression)
638       (setf (local-function-inline-expansion local-function)
639       (generate-inline-expansion block-name lambda-list body))
640       (p1-compiland compiland)))
641   (push local-function local-functions)))
642      ((with-saved-compiler-policy
643     (process-optimization-declarations (cddr form))
644         (let* ((block (make-flet-node))
645                (*blocks* (cons block *blocks*))
646                (body (cddr form))
647                (*visible-variables* *visible-variables*))
648           (setf (flet-free-specials block)
649                 (process-declarations-for-vars body nil block))
650           (dolist (special (flet-free-specials block))
651             (push special *visible-variables*))
652           (setf (flet-form block)
653                 (list* (car form) local-functions (p1-body (cddr form))))
654           block)))))
655
656
657(defun p1-labels (form)
658  (with-local-functions-for-flet/labels
659      form local-functions lambda-list name body
660      ((let* ((variable (make-variable :name (gensym)))
661        (local-function (make-local-function :name name
662               :compiland compiland
663               :variable variable)))
664   (multiple-value-bind (body decls) (parse-body body)
665     (setf (compiland-lambda-expression compiland)
666                 (rewrite-lambda
667     `(lambda ,lambda-list ,@decls (block ,name ,@body)))))
668   (push variable *all-variables*)
669   (push local-function local-functions)))
670      ((dolist (local-function local-functions)
671   (let ((*visible-variables* *visible-variables*)
672         (*current-compiland* (local-function-compiland local-function)))
673     (p1-compiland (local-function-compiland local-function))))
674       (let* ((block (make-labels-node))
675              (*blocks* (cons block *blocks*))
676              (body (cddr form))
677              (*visible-variables* *visible-variables*))
678         (setf (labels-free-specials block)
679               (process-declarations-for-vars body nil block))
680         (dolist (special (labels-free-specials block))
681           (push special *visible-variables*))
682         (setf (labels-form block)
683               (list* (car form) local-functions (p1-body (cddr form))))
684         block))))
685
686(defknown p1-funcall (t) t)
687(defun p1-funcall (form)
688  (unless (> (length form) 1)
689    (compiler-warn "Wrong number of arguments for ~A." (car form))
690    (return-from p1-funcall form))
691  (let ((function-form (%cadr form)))
692    (when (and (consp function-form)
693               (eq (%car function-form) 'FUNCTION))
694      (let ((name (%cadr function-form)))
695;;         (format t "p1-funcall name = ~S~%" name)
696        (let ((source-transform (source-transform name)))
697          (when source-transform
698;;             (format t "found source transform for ~S~%" name)
699;;             (format t "old form = ~S~%" form)
700;;             (let ((new-form (expand-source-transform form)))
701;;               (when (neq new-form form)
702;;                 (format t "new form = ~S~%" new-form)
703;;                 (return-from p1-funcall (p1 new-form))))
704            (let ((new-form (expand-source-transform (list* name (cddr form)))))
705;;               (format t "new form = ~S~%" new-form)
706              (return-from p1-funcall (p1 new-form)))
707            )))))
708  ;; Otherwise...
709  (p1-function-call form))
710
711(defun p1-function (form)
712  (let ((form (copy-tree form))
713        local-function)
714    (cond ((and (consp (cadr form))
715                (or (eq (caadr form) 'LAMBDA)
716                    (eq (caadr form) 'NAMED-LAMBDA)))
717           (let* ((named-lambda-p (eq (caadr form) 'NAMED-LAMBDA))
718                  (named-lambda-form (when named-lambda-p
719                                       (cadr form)))
720                  (name (when named-lambda-p
721                          (cadr named-lambda-form)))
722                  (lambda-form (if named-lambda-p
723                                   (cons 'LAMBDA (cddr named-lambda-form))
724                                   (cadr form)))
725                  (lambda-list (cadr lambda-form))
726                  (body (cddr lambda-form))
727                  (compiland (make-compiland :name (if named-lambda-p
728                                                       name (gensym "ANONYMOUS-LAMBDA-"))
729                                             :lambda-expression lambda-form
730                                             :parent *current-compiland*)))
731             (when *current-compiland*
732               (incf (compiland-children *current-compiland*)))
733             (multiple-value-bind (body decls)
734                 (parse-body body)
735               (setf (compiland-lambda-expression compiland)
736                     ;; if there still was a doc-string present, remove it
737                     (rewrite-lambda
738                      `(lambda ,lambda-list ,@decls ,@body)))
739               (let ((*visible-variables* *visible-variables*)
740                     (*current-compiland* compiland))
741                 (p1-compiland compiland)))
742             (list 'FUNCTION compiland)))
743          ((setf local-function (find-local-function (cadr form)))
744           (dformat t "p1-function local function ~S~%" (cadr form))
745           (let ((variable (local-function-variable local-function)))
746             (when variable
747                 (dformat t "p1-function ~S used non-locally~%"
748                          (variable-name variable))
749                 (setf (variable-used-non-locally-p variable) t)))
750           form)
751          (t
752           form))))
753
754(defun p1-lambda (form)
755  (setf form (rewrite-lambda form))
756  (let* ((lambda-list (cadr form)))
757    (when (or (memq '&optional lambda-list)
758              (memq '&key lambda-list))
759      (let ((state nil))
760        (dolist (arg lambda-list)
761          (cond ((memq arg lambda-list-keywords)
762                 (setf state arg))
763                ((memq state '(&optional &key))
764                 (when (and (consp arg)
765                            (not (constantp (second arg))))
766                   (compiler-unsupported
767                    "P1-LAMBDA: can't handle optional argument with non-constant initform.")))))))
768    (p1-function (list 'FUNCTION form))))
769
770(defun p1-eval-when (form)
771  (list* (car form) (cadr form) (mapcar #'p1 (cddr form))))
772
773(defknown p1-progv (t) t)
774(defun p1-progv (form)
775  ;; We've already checked argument count in PRECOMPILE-PROGV.
776
777  (let ((new-form (rewrite-progv form)))
778    (when (neq new-form form)
779      (return-from p1-progv (p1 new-form))))
780  (let* ((symbols-form (p1 (cadr form)))
781         (values-form (p1 (caddr form)))
782         (block (make-progv-node))
783         (*blocks* (cons block *blocks*))
784         (body (cdddr form)))
785;;  The (commented out) block below means to detect compile-time
786;;  enumeration of bindings to be created (a quoted form in the symbols
787;;  position).
788;;    (when (and (quoted-form-p symbols-form)
789;;               (listp (second symbols-form)))
790;;      (dolist (name (second symbols-form))
791;;        (let ((variable (make-variable :name name :special-p t)))
792;;          (push
793    (setf (progv-form block)
794          `(progv ,symbols-form ,values-form ,@(p1-body body))
795          (progv-environment-register block) t)
796    block))
797
798(defknown rewrite-progv (t) t)
799(defun rewrite-progv (form)
800  (let ((symbols-form (cadr form))
801        (values-form (caddr form))
802        (body (cdddr form)))
803    (cond ((or (unsafe-p symbols-form) (unsafe-p values-form))
804           (let ((g1 (gensym))
805                 (g2 (gensym)))
806             `(let ((,g1 ,symbols-form)
807                    (,g2 ,values-form))
808                (progv ,g1 ,g2 ,@body))))
809          (t
810           form))))
811
812(defun p1-quote (form)
813  (unless (= (length form) 2)
814    (compiler-error "Wrong number of arguments for special operator ~A (expected 1, but received ~D)."
815                    'QUOTE
816                    (1- (length form))))
817  (let ((arg (%cadr form)))
818    (if (or (numberp arg) (characterp arg))
819        arg
820        form)))
821
822(defun p1-setq (form)
823  (unless (= (length form) 3)
824    (error "Too many arguments for SETQ."))
825  (let ((arg1 (%cadr form))
826        (arg2 (%caddr form)))
827    (let ((variable (find-visible-variable arg1)))
828      (if variable
829          (progn
830            (when (variable-ignore-p variable)
831              (compiler-style-warn
832               "Variable ~S is assigned even though it was declared to be ignored."
833               (variable-name variable)))
834            (incf (variable-writes variable))
835            (cond ((eq (variable-compiland variable) *current-compiland*)
836                   (dformat t "p1-setq: write ~S~%" arg1))
837                  (t
838                   (dformat t "p1-setq: non-local write ~S~%" arg1)
839                   (setf (variable-used-non-locally-p variable) t))))
840          (dformat t "p1-setq: unknown variable ~S~%" arg1)))
841    (list 'SETQ arg1 (p1 arg2))))
842
843(defun p1-the (form)
844  (unless (= (length form) 3)
845    (compiler-error "Wrong number of arguments for special operator ~A (expected 2, but received ~D)."
846                    'THE
847                    (1- (length form))))
848  (let ((type (%cadr form))
849        (expr (%caddr form)))
850    (cond ((and (listp type) (eq (car type) 'VALUES))
851           ;; FIXME
852           (p1 expr))
853          ((= *safety* 3)
854           (let* ((sym (gensym))
855                  (new-expr `(let ((,sym ,expr))
856                               (require-type ,sym ',type)
857                               ,sym)))
858             (p1 new-expr)))
859          ((and (<= 1 *safety* 2) ;; at safety 1 or 2 check relatively
860                (symbolp type))   ;; simple types (those specified by a single symbol)
861           (let* ((sym (gensym))
862                  (new-expr `(let ((,sym ,expr))
863                               (require-type ,sym ',type)
864                               ,sym)))
865             (p1 new-expr)))
866          (t
867           (list 'THE type (p1 expr))))))
868
869(defun p1-truly-the (form)
870  (unless (= (length form) 3)
871    (compiler-error "Wrong number of arguments for special operator ~A (expected 2, but received ~D)."
872                    'TRULY-THE
873                    (1- (length form))))
874  (list 'TRULY-THE (%cadr form) (p1 (%caddr form))))
875
876(defknown unsafe-p (t) t)
877(defun unsafe-p (args)
878  (cond ((node-p args)
879         (unsafe-p (node-form args)))
880        ((atom args)
881         nil)
882        (t
883         (case (%car args)
884           (QUOTE
885            nil)
886           (LAMBDA
887            nil)
888           ((RETURN-FROM GO CATCH THROW UNWIND-PROTECT BLOCK)
889            t)
890           (t
891            (dolist (arg args)
892              (when (unsafe-p arg)
893                (return t))))))))
894
895(defknown rewrite-throw (t) t)
896(defun rewrite-throw (form)
897  (let ((args (cdr form)))
898    (if (unsafe-p args)
899        (let ((syms ())
900              (lets ()))
901          ;; Tag.
902          (let ((arg (first args)))
903            (if (constantp arg)
904                (push arg syms)
905                (let ((sym (gensym)))
906                  (push sym syms)
907                  (push (list sym arg) lets))))
908          ;; Result. "If the result-form produces multiple values, then all the
909          ;; values are saved."
910          (let ((arg (second args)))
911            (if (constantp arg)
912                (push arg syms)
913                (let ((sym (gensym)))
914                  (cond ((single-valued-p arg)
915                         (push sym syms)
916                         (push (list sym arg) lets))
917                        (t
918                         (push (list 'VALUES-LIST sym) syms)
919                         (push (list sym
920                                     (list 'MULTIPLE-VALUE-LIST arg))
921                               lets))))))
922          (list 'LET* (nreverse lets) (list* 'THROW (nreverse syms))))
923        form)))
924
925(defknown p1-throw (t) t)
926(defun p1-throw (form)
927  (let ((new-form (rewrite-throw form)))
928    (when (neq new-form form)
929      (return-from p1-throw (p1 new-form))))
930  (list* 'THROW (mapcar #'p1 (cdr form))))
931
932(defknown rewrite-function-call (t) t)
933(defun rewrite-function-call (form)
934  (let ((args (cdr form)))
935    (if (unsafe-p args)
936        (let ((arg1 (car args)))
937          (cond ((and (consp arg1) (eq (car arg1) 'GO))
938                 arg1)
939                (t
940                 (let ((syms ())
941                       (lets ()))
942                   ;; Preserve the order of evaluation of the arguments!
943                   (dolist (arg args)
944                     (cond ((constantp arg)
945                            (push arg syms))
946                           ((and (consp arg) (eq (car arg) 'GO))
947                            (return-from rewrite-function-call
948                                         (list 'LET* (nreverse lets) arg)))
949                           (t
950                            (let ((sym (gensym)))
951                              (push sym syms)
952                              (push (list sym arg) lets)))))
953                   (list 'LET* (nreverse lets)
954                         (list* (car form) (nreverse syms)))))))
955        form)))
956
957(defknown p1-function-call (t) t)
958(defun p1-function-call (form)
959  (let ((new-form (rewrite-function-call form)))
960    (when (neq new-form form)
961;;       (let ((*print-structure* nil))
962;;         (format t "old form = ~S~%" form)
963;;         (format t "new form = ~S~%" new-form))
964      (return-from p1-function-call (p1 new-form))))
965  (let* ((op (car form))
966         (local-function (find-local-function op)))
967    (cond (local-function
968;;            (format t "p1 local call to ~S~%" op)
969;;            (format t "inline-p = ~S~%" (inline-p op))
970
971           (when (and *enable-inline-expansion* (inline-p op))
972             (let ((expansion (local-function-inline-expansion local-function)))
973               (when expansion
974                 (let ((explain *explain*))
975                   (when (and explain (memq :calls explain))
976                     (format t ";   inlining call to local function ~S~%" op)))
977                 (return-from p1-function-call
978                   (p1 (expand-inline form expansion))))))
979
980           ;; FIXME
981           (dformat t "local function assumed not single-valued~%")
982           (setf (compiland-%single-valued-p *current-compiland*) nil)
983
984           (let ((variable (local-function-variable local-function)))
985             (when variable
986               (dformat t "p1 ~S used non-locally~%" (variable-name variable))
987               (setf (variable-used-non-locally-p variable) t))))
988          (t
989           ;; Not a local function call.
990           (dformat t "p1 non-local call to ~S~%" op)
991           (unless (single-valued-p form)
992;;                (format t "not single-valued op = ~S~%" op)
993             (setf (compiland-%single-valued-p *current-compiland*) nil)))))
994  (p1-default form))
995
996(defknown p1 (t) t)
997(defun p1 (form)
998  (cond ((symbolp form)
999         (let (value)
1000           (cond ((null form)
1001                  form)
1002                 ((eq form t)
1003                  form)
1004                 ((keywordp form)
1005                  form)
1006                 ((and (constantp form)
1007                       (progn
1008                         (setf value (symbol-value form))
1009                         (or (numberp value)
1010                             (stringp value)
1011                             (pathnamep value))))
1012                  (setf form value))
1013                 (t
1014                  (let ((variable (find-visible-variable form)))
1015                    (when (null variable)
1016          (unless (or (special-variable-p form)
1017                                  (memq form *undefined-variables*))
1018      (compiler-style-warn
1019                         "Undefined variable ~S assumed special" form)
1020      (push form *undefined-variables*))
1021                      (setf variable (make-variable :name form :special-p t))
1022                      (push variable *visible-variables*))
1023                    (let ((ref (make-var-ref variable)))
1024                      (unless (variable-special-p variable)
1025                        (when (variable-ignore-p variable)
1026                          (compiler-style-warn
1027                           "Variable ~S is read even though it was declared to be ignored."
1028                           (variable-name variable)))
1029                        (push ref (variable-references variable))
1030                        (incf (variable-reads variable))
1031                        (cond ((eq (variable-compiland variable) *current-compiland*)
1032                               (dformat t "p1: read ~S~%" form))
1033                              (t
1034                               (dformat t "p1: non-local read ~S variable-compiland = ~S current compiland = ~S~%"
1035                                        form
1036                                        (compiland-name (variable-compiland variable))
1037                                        (compiland-name *current-compiland*))
1038                               (setf (variable-used-non-locally-p variable) t))))
1039                      (setf form ref)))
1040                  form))))
1041        ((atom form)
1042         form)
1043        (t
1044         (let ((op (%car form))
1045               handler)
1046           (cond ((symbolp op)
1047                  (when (compiler-macro-function op)
1048                    (unless (notinline-p op)
1049                      (multiple-value-bind (expansion expanded-p)
1050                          (compiler-macroexpand form)
1051                        ;; Fall through if no change...
1052                        (when expanded-p
1053                          (return-from p1 (p1 expansion))))))
1054                  (cond ((setf handler (get op 'p1-handler))
1055                         (funcall handler form))
1056                        ((macro-function op *compile-file-environment*)
1057                         (p1 (macroexpand form *compile-file-environment*)))
1058                        ((special-operator-p op)
1059                         (compiler-unsupported "P1: unsupported special operator ~S" op))
1060                        (t
1061                         (p1-function-call form))))
1062                 ((and (consp op) (eq (%car op) 'LAMBDA))
1063                  (p1 (list* 'FUNCALL form)))
1064                 (t
1065                  form))))))
1066
1067(defun install-p1-handler (symbol handler)
1068  (setf (get symbol 'p1-handler) handler))
1069
1070(defun initialize-p1-handlers ()
1071  (dolist (pair '((AND                  p1-default)
1072                  (BLOCK                p1-block)
1073                  (CATCH                p1-catch)
1074                  (DECLARE              identity)
1075                  (EVAL-WHEN            p1-eval-when)
1076                  (FLET                 p1-flet)
1077                  (FUNCALL              p1-funcall)
1078                  (FUNCTION             p1-function)
1079                  (GO                   p1-go)
1080                  (IF                   p1-if)
1081                  (LABELS               p1-labels)
1082                  (LAMBDA               p1-lambda)
1083                  (LET                  p1-let/let*)
1084                  (LET*                 p1-let/let*)
1085                  (LOAD-TIME-VALUE      identity)
1086                  (LOCALLY              p1-locally)
1087                  (MULTIPLE-VALUE-BIND  p1-m-v-b)
1088                  (MULTIPLE-VALUE-CALL  p1-default)
1089                  (MULTIPLE-VALUE-LIST  p1-default)
1090                  (MULTIPLE-VALUE-PROG1 p1-default)
1091                  (OR                   p1-default)
1092                  (PROGN                p1-default)
1093                  (PROGV                p1-progv)
1094                  (QUOTE                p1-quote)
1095                  (RETURN-FROM          p1-return-from)
1096                  (SETQ                 p1-setq)
1097                  (SYMBOL-MACROLET      identity)
1098                  (TAGBODY              p1-tagbody)
1099                  (THE                  p1-the)
1100                  (THROW                p1-throw)
1101                  (TRULY-THE            p1-truly-the)
1102                  (UNWIND-PROTECT       p1-unwind-protect)
1103                  (THREADS:SYNCHRONIZED-ON
1104                                        p1-threads-synchronized-on)))
1105    (install-p1-handler (%car pair) (%cadr pair))))
1106
1107(initialize-p1-handlers)
1108
1109(defun p1-compiland (compiland)
1110;;   (format t "p1-compiland name = ~S~%" (compiland-name compiland))
1111  (let ((form (compiland-lambda-expression compiland)))
1112    (aver (eq (car form) 'LAMBDA))
1113    (setf form (rewrite-lambda form))
1114    (process-optimization-declarations (cddr form))
1115
1116    (let* ((lambda-list (cadr form))
1117           (body (cddr form))
1118           (*visible-variables* *visible-variables*)
1119           (closure (make-closure `(lambda ,lambda-list nil) nil))
1120           (syms (sys::varlist closure))
1121           (vars nil))
1122      (dolist (sym syms)
1123        (let ((var (make-variable :name sym
1124                                  :special-p (special-variable-p sym))))
1125          (push var vars)
1126          (push var *all-variables*)
1127          (push var *visible-variables*)))
1128      (setf (compiland-arg-vars compiland) (nreverse vars))
1129      (let ((free-specials (process-declarations-for-vars body vars nil)))
1130        (setf (compiland-free-specials compiland) free-specials)
1131        (dolist (var free-specials)
1132          (push var *visible-variables*)))
1133      (setf (compiland-p1-result compiland)
1134            (list* 'LAMBDA lambda-list (p1-body body))))))
1135
1136(provide "COMPILER-PASS1")
Note: See TracBrowser for help on using the repository browser.