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

Last change on this file since 11790 was 11790, checked in by ehuelsmann, 14 years ago

Remove a NIL block which doesn't seem to matter.
Since we add named blocks all over the place,
surely adding an implicit NIL block isn't a good thing.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 38.8 KB
Line 
1;;; compiler-pass1.lisp
2;;;
3;;; Copyright (C) 2003-2008 Peter Graves
4;;; $Id: compiler-pass1.lisp 11790 2009-04-27 21:27:51Z 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 '(&optional &rest &key &allow-other-keys &aux) :test 'eq)
50           nil)
51          (t
52           (setf body (copy-tree body))
53           (list 'LAMBDA lambda-list (precompile-form (list* 'BLOCK block-name body) t)))))
54  ) ; EVAL-WHEN
55
56;;; Pass 1.
57
58
59;; Returns a list of declared free specials, if any are found.
60(declaim (ftype (function (list list) list) process-declarations-for-vars))
61(defun process-declarations-for-vars (body variables)
62  (let ((free-specials '()))
63    (dolist (subform body)
64      (unless (and (consp subform) (eq (%car subform) 'DECLARE))
65        (return))
66      (let ((decls (%cdr subform)))
67        (dolist (decl decls)
68          (case (car decl)
69            ((DYNAMIC-EXTENT FTYPE INLINE NOTINLINE OPTIMIZE)
70             ;; Nothing to do here.
71             )
72            ((IGNORE IGNORABLE)
73             (process-ignore/ignorable (%car decl) (%cdr decl) variables))
74            (SPECIAL
75             (dolist (name (%cdr decl))
76               (let ((variable (find-variable name variables)))
77                 (cond ((and variable
78                             ;; see comment below (and DO-ALL-SYMBOLS.11)
79                             (eq (variable-compiland variable) *current-compiland*))
80                        (setf (variable-special-p variable) t))
81                       (t
82                        (dformat t "adding free special ~S~%" name)
83                        (push (make-variable :name name :special-p t) free-specials))))))
84            (TYPE
85             (dolist (name (cddr decl))
86               (let ((variable (find-variable name variables)))
87                 (when (and variable
88                            ;; Don't apply a declaration in a local function to
89                            ;; a variable defined in its parent. For an example,
90                            ;; see CREATE-GREEDY-NO-ZERO-MATCHER in cl-ppcre.
91                            ;; FIXME suboptimal, since we ignore the declaration
92                            (eq (variable-compiland variable) *current-compiland*))
93                   (setf (variable-declared-type variable)
94                         (make-compiler-type (cadr decl)))))))
95            (t
96             (dolist (name (cdr decl))
97               (let ((variable (find-variable name variables)))
98                 (when variable
99                   (setf (variable-declared-type variable)
100                         (make-compiler-type (%car decl)))))))))))
101    free-specials))
102
103(defun check-name (name)
104  ;; FIXME Currently this error is signalled by the precompiler.
105  (unless (symbolp name)
106    (compiler-error "The variable ~S is not a symbol." name))
107  (when (constantp name)
108    (compiler-error "The name of the variable ~S is already in use to name a constant." name))
109  name)
110
111(declaim (ftype (function (t) t) p1-body))
112(defun p1-body (body)
113  (declare (optimize speed))
114  (let ((tail body))
115    (loop
116      (when (endp tail)
117        (return))
118      (setf (car tail) (p1 (%car tail)))
119      (setf tail (%cdr tail))))
120  body)
121
122(defknown p1-default (t) t)
123(declaim (inline p1-default))
124(defun p1-default (form)
125  (setf (cdr form) (p1-body (cdr form)))
126  form)
127
128(defknown p1-if (t) t)
129(defun p1-if (form)
130  (let ((test (cadr form)))
131    (cond ((unsafe-p test)
132           (cond ((and (consp test)
133                       (memq (%car test) '(GO RETURN-FROM THROW)))
134                  (p1 test))
135                 (t
136                  (let* ((var (gensym))
137                         (new-form
138                          `(let ((,var ,test))
139                             (if ,var ,(third form) ,(fourth form)))))
140                    (p1 new-form)))))
141          (t
142           (p1-default form)))))
143
144
145(defmacro p1-let/let*-vars 
146    (varlist variables-var var body1 body2)
147  (let ((varspec (gensym))
148  (initform (gensym))
149  (name (gensym)))
150    `(let ((,variables-var ()))
151       (dolist (,varspec ,varlist)
152   (cond ((consp ,varspec)
153              ;; FIXME Currently this error is signalled by the precompiler.
154    (unless (= (length ,varspec) 2)
155      (compiler-error "The LET/LET* binding specification ~S is invalid."
156          ,varspec))
157    (let* ((,name (%car ,varspec))
158           (,initform (p1 (%cadr ,varspec)))
159           (,var (make-variable :name (check-name ,name) :initform ,initform)))
160      (push ,var ,variables-var)
161      ,@body1))
162         (t
163    (let ((,var (make-variable :name (check-name ,varspec))))
164      (push ,var ,variables-var)
165      ,@body1))))
166       ,@body2)))
167
168(defknown p1-let-vars (t) t)
169(defun p1-let-vars (varlist)
170  (p1-let/let*-vars 
171   varlist vars var
172   ()
173   ((setf vars (nreverse vars))
174    (dolist (variable vars)
175      (push variable *visible-variables*)
176      (push variable *all-variables*))
177    vars)))
178
179(defknown p1-let*-vars (t) t)
180(defun p1-let*-vars (varlist)
181  (p1-let/let*-vars 
182   varlist vars var
183   ((push var *visible-variables*)
184    (push var *all-variables*))
185   ((nreverse vars))))
186
187(defun p1-let/let* (form)
188  (declare (type cons form))
189  (let* ((*visible-variables* *visible-variables*)
190         (block (make-block-node '(LET)))
191         (*blocks* (cons block *blocks*))
192         (op (%car form))
193         (varlist (cadr form))
194         (body (cddr form)))
195    (aver (or (eq op 'LET) (eq op 'LET*)))
196    (when (eq op 'LET)
197      ;; Convert to LET* if possible.
198      (if (null (cdr varlist))
199          (setf op 'LET*)
200          (dolist (varspec varlist (setf op 'LET*))
201            (or (atom varspec)
202                (constantp (cadr varspec))
203                (eq (car varspec) (cadr varspec))
204                (return)))))
205    (let ((vars (if (eq op 'LET)
206                    (p1-let-vars varlist)
207                    (p1-let*-vars varlist))))
208      ;; Check for globally declared specials.
209      (dolist (variable vars)
210        (when (special-variable-p (variable-name variable))
211          (setf (variable-special-p variable) t)))
212      ;; For processing declarations, we want to walk the variable list from
213      ;; last to first, since declarations apply to the last-defined variable
214      ;; with the specified name.
215      (setf (block-free-specials block) (process-declarations-for-vars body (reverse vars)))
216      (setf (block-vars block) vars)
217      ;; Make free specials visible.
218      (dolist (variable (block-free-specials block))
219        (push variable *visible-variables*)))
220    (setf body (p1-body body))
221    (setf (block-form block) (list* op varlist body))
222    block))
223
224(defun p1-locally (form)
225  (let ((*visible-variables* *visible-variables*)
226        (specials (process-special-declarations (cdr form))))
227    (dolist (name specials)
228;;       (format t "p1-locally ~S is special~%" name)
229      (push (make-variable :name name :special-p t) *visible-variables*))
230    (setf (cdr form) (p1-body (cdr form)))
231    form))
232
233(defknown p1-m-v-b (t) t)
234(defun p1-m-v-b (form)
235  (when (= (length (cadr form)) 1)
236    (let ((new-form `(let* ((,(caadr form) ,(caddr form))) ,@(cdddr form))))
237      (return-from p1-m-v-b (p1-let/let* new-form))))
238  (let* ((*visible-variables* *visible-variables*)
239         (block (make-block-node '(MULTIPLE-VALUE-BIND)))
240         (*blocks* (cons block *blocks*))
241         (varlist (cadr form))
242         (values-form (caddr form))
243         (body (cdddr form)))
244    ;; Process the values-form first. ("The scopes of the name binding and
245    ;; declarations do not include the values-form.")
246    (setf values-form (p1 values-form))
247    (let ((vars ()))
248      (dolist (symbol varlist)
249        (let ((var (make-variable :name symbol)))
250          (push var vars)
251          (push var *visible-variables*)
252          (push var *all-variables*)))
253      ;; Check for globally declared specials.
254      (dolist (variable vars)
255        (when (special-variable-p (variable-name variable))
256          (setf (variable-special-p variable) t)))
257      (setf (block-free-specials block) (process-declarations-for-vars body vars))
258      (setf (block-vars block) (nreverse vars)))
259    (setf body (p1-body body))
260    (setf (block-form block) (list* 'MULTIPLE-VALUE-BIND varlist values-form body))
261    block))
262
263(defun p1-block (form)
264  (let* ((block (make-block-node (cadr form)))
265         (*blocks* (cons block *blocks*)))
266    (setf (cddr form) (p1-body (cddr form)))
267    (setf (block-form block) form)
268    block))
269
270(defun p1-catch (form)
271  (let* ((tag (p1 (cadr form)))
272         (body (cddr form))
273         (result '()))
274    (dolist (subform body)
275      (let ((op (and (consp subform) (%car subform))))
276        (push (p1 subform) result)
277        (when (memq op '(GO RETURN-FROM THROW))
278          (return))))
279    (setf result (nreverse result))
280    (when (and (null (cdr result))
281               (consp (car result))
282               (eq (caar result) 'GO))
283      (return-from p1-catch (car result)))
284    (push tag result)
285    (push 'CATCH result)
286    (let ((block (make-block-node '(CATCH))))
287      (setf (block-form block) result)
288      block)))
289
290(defun p1-unwind-protect (form)
291  (if (= (length form) 2)
292      (p1 (second form)) ; No cleanup forms: (unwind-protect (...)) => (...)
293      (let* ((block (make-block-node '(UNWIND-PROTECT)))
294             (*blocks* (cons block *blocks*)))
295        (setf (block-form block) (p1-default form))
296        block)))
297
298(defknown p1-return-from (t) t)
299(defun p1-return-from (form)
300  (let* ((name (second form))
301         (block (find-block name)))
302    (when (null block)
303      (compiler-error "RETURN-FROM ~S: no block named ~S is currently visible."
304                      name name))
305    (dformat t "p1-return-from block = ~S~%" (block-name block))
306    (setf (block-return-p block) t)
307    (cond ((eq (block-compiland block) *current-compiland*)
308           ;; Local case. If the RETURN is nested inside an UNWIND-PROTECT
309           ;; which is inside the block we're returning from, we'll do a non-
310           ;; local return anyway so that UNWIND-PROTECT can catch it and run
311           ;; its cleanup forms.
312           (dformat t "*blocks* = ~S~%" (mapcar #'block-name *blocks*))
313           (let ((protected
314                  (dolist (enclosing-block *blocks*)
315                    (when (eq enclosing-block block)
316                      (return nil))
317                    (when (equal (block-name enclosing-block) '(UNWIND-PROTECT))
318                      (return t)))))
319             (dformat t "p1-return-from protected = ~S~%" protected)
320             (when protected
321               (setf (block-non-local-return-p block) t))))
322          (t
323           (setf (block-non-local-return-p block) t)))
324    (when (block-non-local-return-p block)
325      (dformat t "non-local return from block ~S~%" (block-name block))))
326  (list* 'RETURN-FROM (cadr form) (mapcar #'p1 (cddr form))))
327
328(defun p1-tagbody (form)
329  (let* ((block (make-block-node '(TAGBODY)))
330         (*blocks* (cons block *blocks*))
331         (*visible-tags* *visible-tags*)
332         (body (cdr form)))
333    ;; Make all the tags visible before processing the body forms.
334    (dolist (subform body)
335      (when (or (symbolp subform) (integerp subform))
336        (let* ((tag (make-tag :name subform :label (gensym) :block block)))
337          (push tag *visible-tags*))))
338    (let ((new-body '())
339          (live t))
340      (dolist (subform body)
341        (cond ((or (symbolp subform) (integerp subform))
342               (push subform new-body)
343               (setf live t))
344              ((not live)
345               ;; Nothing to do.
346               )
347              (t
348               (when (and (consp subform)
349                          (memq (%car subform) '(GO RETURN-FROM THROW)))
350                 ;; Subsequent subforms are unreachable until we see another
351                 ;; tag.
352                 (setf live nil))
353               (push (p1 subform) new-body))))
354      (setf (block-form block) (list* 'TAGBODY (nreverse new-body))))
355    block))
356
357(defknown p1-go (t) t)
358(defun p1-go (form)
359  (let* ((name (cadr form))
360         (tag (find-tag name)))
361    (unless tag
362      (error "p1-go: tag not found: ~S" name))
363    (let ((tag-block (tag-block tag)))
364      (cond ((eq (tag-compiland tag) *current-compiland*)
365             ;; Does the GO leave an enclosing UNWIND-PROTECT?
366             (let ((protected
367                    (dolist (enclosing-block *blocks*)
368                      (when (eq enclosing-block tag-block)
369                        (return nil))
370                      (when (equal (block-name enclosing-block) '(UNWIND-PROTECT))
371                        (return t)))))
372               (when protected
373                 (setf (block-non-local-go-p tag-block) t))))
374            (t
375             (setf (block-non-local-go-p tag-block) t)))))
376  form)
377
378(defun validate-name-and-lambda-list (name lambda-list context)
379  (unless (or (symbolp name) (setf-function-name-p name))
380    (compiler-error "~S is not a valid function name." name))
381  (when (or (memq '&optional lambda-list)
382            (memq '&key lambda-list))
383    (let ((state nil))
384      (dolist (arg lambda-list)
385        (cond ((memq arg lambda-list-keywords)
386               (setf state arg))
387              ((memq state '(&optional &key))
388               (when (and (consp arg) (not (constantp (second arg))))
389                 (compiler-unsupported
390                  "~A: can't handle ~A argument with non-constant initform."
391                  context
392                  (if (eq state '&optional) "optional" "keyword")))))))))
393
394(defmacro with-local-functions-for-flet/labels 
395    (form local-functions-var lambda-name lambda-list-var name-var body-var body1 body2)
396  `(progn (incf (compiland-children *current-compiland*) (length (cadr ,form)))
397    (let ((*visible-variables* *visible-variables*)
398    (*local-functions* *local-functions*)
399    (*current-compiland* *current-compiland*)
400    (,local-functions-var '()))
401      (dolist (definition (cadr ,form))
402        (let ((,name-var (car definition))
403        (,lambda-list-var (cadr definition)))
404    (validate-name-and-lambda-list ,name-var ,lambda-list-var ,lambda-name)
405 
406    (let* ((,body-var (cddr definition))
407           (compiland (make-compiland :name ,name-var
408              :parent *current-compiland*)))
409      ,@body1)))
410      (setf ,local-functions-var (nreverse ,local-functions-var))
411      ;; Make the local functions visible.
412      (dolist (local-function ,local-functions-var)
413        (push local-function *local-functions*)
414        (let ((variable (local-function-variable local-function)))
415    (when variable
416      (push variable *visible-variables*))))
417      ,@body2)))
418
419(defun p1-flet (form)
420  (with-local-functions-for-flet/labels 
421      form local-functions 'FLET lambda-list name body
422      ((let ((local-function (make-local-function :name name
423             :compiland compiland)))
424   (multiple-value-bind (body decls) (parse-body body)
425     (let* ((block-name (fdefinition-block-name name))
426      (lambda-expression
427       `(lambda ,lambda-list ,@decls (block ,block-name ,@body)))
428      (*visible-variables* *visible-variables*)
429      (*local-functions* *local-functions*)
430      (*current-compiland* compiland))
431       (setf (compiland-lambda-expression compiland) lambda-expression)
432       (setf (local-function-inline-expansion local-function)
433       (generate-inline-expansion block-name lambda-list body))
434       (p1-compiland compiland)))
435   (when *closure-variables*
436     (let ((variable (make-variable :name (gensym))))
437       (setf (local-function-variable local-function) variable)
438       (push variable *all-variables*)))
439   (push local-function local-functions)))
440      ((with-saved-compiler-policy
441     (process-optimization-declarations (cddr form))
442   (list* (car form) local-functions (p1-body (cddr form)))))))
443
444
445(defun p1-labels (form)
446  (with-local-functions-for-flet/labels 
447      form local-functions 'LABELS lambda-list name body
448      ((let* ((variable (make-variable :name (gensym)))
449        (local-function (make-local-function :name name
450               :compiland compiland
451               :variable variable)))
452   (multiple-value-bind (body decls) (parse-body body)
453     (setf (compiland-lambda-expression compiland)
454     `(lambda ,lambda-list ,@decls (block ,name ,@body))))
455   (push variable *all-variables*)
456   (push local-function local-functions)))
457      ((dolist (local-function local-functions)
458   (let ((*visible-variables* *visible-variables*)
459         (*current-compiland* (local-function-compiland local-function)))
460     (p1-compiland (local-function-compiland local-function))))
461       (list* (car form) local-functions (p1-body (cddr form))))))
462
463(defknown p1-funcall (t) t)
464(defun p1-funcall (form)
465  (unless (> (length form) 1)
466    (compiler-warn "Wrong number of arguments for ~A." (car form))
467    (return-from p1-funcall form))
468  (let ((function-form (%cadr form)))
469    (when (and (consp function-form)
470               (eq (%car function-form) 'FUNCTION))
471      (let ((name (%cadr function-form)))
472;;         (format t "p1-funcall name = ~S~%" name)
473        (let ((source-transform (source-transform name)))
474          (when source-transform
475;;             (format t "found source transform for ~S~%" name)
476;;             (format t "old form = ~S~%" form)
477;;             (let ((new-form (expand-source-transform form)))
478;;               (when (neq new-form form)
479;;                 (format t "new form = ~S~%" new-form)
480;;                 (return-from p1-funcall (p1 new-form))))
481            (let ((new-form (expand-source-transform (list* name (cddr form)))))
482;;               (format t "new form = ~S~%" new-form)
483              (return-from p1-funcall (p1 new-form)))
484            )))))
485  ;; Otherwise...
486  (p1-function-call form))
487
488(defun p1-function (form)
489  (let ((form (copy-tree form))
490        local-function)
491    (cond ((and (consp (cadr form))
492                (or (eq (caadr form) 'LAMBDA)
493                    (eq (caadr form) 'NAMED-LAMBDA)))
494           (let* ((named-lambda-p (eq (caadr form) 'NAMED-LAMBDA))
495                  (named-lambda-form (when named-lambda-p
496                                       (cadr form)))
497                  (name (when named-lambda-p
498                          (cadr named-lambda-form)))
499                  (lambda-form (if named-lambda-p
500                                   (cons 'LAMBDA (cddr named-lambda-form))
501                                   (cadr form)))
502                  (lambda-list (cadr lambda-form))
503                  (body (cddr lambda-form))
504                  (compiland (make-compiland :name (if named-lambda-p
505                                                       name (gensym "ANONYMOUS-LAMBDA-"))
506                                             :lambda-expression lambda-form
507                                             :parent *current-compiland*)))
508             (when *current-compiland*
509               (incf (compiland-children *current-compiland*)))
510             (multiple-value-bind (body decls)
511                 (parse-body body)
512               (setf (compiland-lambda-expression compiland)
513                     ;; if there still was a doc-string present, remove it
514                     `(lambda ,lambda-list ,@decls ,@body))
515               (let ((*visible-variables* *visible-variables*)
516                     (*current-compiland* compiland))
517                 (p1-compiland compiland)))
518             (list 'FUNCTION compiland)))
519          ((setf local-function (find-local-function (cadr form)))
520           (dformat t "p1-function local function ~S~%" (cadr form))
521           (let ((variable (local-function-variable local-function)))
522             (when variable
523                 (dformat t "p1-function ~S used non-locally~%" (variable-name variable))
524                 (setf (variable-used-non-locally-p variable) t)))
525           form)
526          (t
527           form))))
528
529(defun p1-lambda (form)
530  (let* ((lambda-list (cadr form))
531         (body (cddr form))
532         (auxvars (memq '&AUX lambda-list)))
533    (when (or (memq '&optional lambda-list)
534              (memq '&key lambda-list))
535      (let ((state nil))
536        (dolist (arg lambda-list)
537          (cond ((memq arg lambda-list-keywords)
538                 (setf state arg))
539                ((memq state '(&optional &key))
540                 (when (and (consp arg)
541                            (not (constantp (second arg))))
542                   (compiler-unsupported
543                    "P1-LAMBDA: can't handle optional argument with non-constant initform.")))))))
544    (when auxvars
545      (setf lambda-list (subseq lambda-list 0 (position '&AUX lambda-list)))
546      (setf body (list (append (list 'LET* (cdr auxvars)) body))))
547    (p1-function (list 'FUNCTION (list* 'LAMBDA lambda-list body)))))
548
549(defun p1-eval-when (form)
550  (list* (car form) (cadr form) (mapcar #'p1 (cddr form))))
551
552(defknown p1-progv (t) t)
553(defun p1-progv (form)
554  ;; We've already checked argument count in PRECOMPILE-PROGV.
555  (let ((new-form (rewrite-progv form)))
556    (when (neq new-form form)
557      (return-from p1-progv (p1 new-form))))
558  (let ((symbols-form (cadr form))
559        (values-form (caddr form))
560        (body (cdddr form)))
561    `(progv ,(p1 symbols-form) ,(p1 values-form) ,@(p1-body body))))
562
563(defknown rewrite-progv (t) t)
564(defun rewrite-progv (form)
565  (let ((symbols-form (cadr form))
566        (values-form (caddr form))
567        (body (cdddr form)))
568    (cond ((or (unsafe-p symbols-form) (unsafe-p values-form))
569           (let ((g1 (gensym))
570                 (g2 (gensym)))
571             `(let ((,g1 ,symbols-form)
572                    (,g2 ,values-form))
573                (progv ,g1 ,g2 ,@body))))
574          (t
575           form))))
576
577(defun p1-quote (form)
578  (unless (= (length form) 2)
579    (compiler-error "Wrong number of arguments for special operator ~A (expected 1, but received ~D)."
580                    'QUOTE
581                    (1- (length form))))
582  (let ((arg (%cadr form)))
583    (if (or (numberp arg) (characterp arg))
584        arg
585        form)))
586
587(defun p1-setq (form)
588  (unless (= (length form) 3)
589    (error "Too many arguments for SETQ."))
590  (let ((arg1 (%cadr form))
591        (arg2 (%caddr form)))
592    (let ((variable (find-visible-variable arg1)))
593      (if variable
594          (progn
595            (when (variable-ignore-p variable)
596              (compiler-style-warn
597               "Variable ~S is assigned even though it was declared to be ignored."
598               (variable-name variable)))
599            (incf (variable-writes variable))
600            (cond ((eq (variable-compiland variable) *current-compiland*)
601                   (dformat t "p1-setq: write ~S~%" arg1))
602                  (t
603                   (dformat t "p1-setq: non-local write ~S~%" arg1)
604                   (setf (variable-used-non-locally-p variable) t))))
605          (dformat t "p1-setq: unknown variable ~S~%" arg1)))
606    (list 'SETQ arg1 (p1 arg2))))
607
608(defun p1-the (form)
609  (unless (= (length form) 3)
610    (compiler-error "Wrong number of arguments for special operator ~A (expected 2, but received ~D)."
611                    'THE
612                    (1- (length form))))
613  (let ((type (%cadr form))
614        (expr (%caddr form)))
615    (cond ((and (listp type) (eq (car type) 'VALUES))
616           ;; FIXME
617           (p1 expr))
618          ((= *safety* 3)
619           (let* ((sym (gensym))
620                  (new-expr `(let ((,sym ,expr))
621                               (require-type ,sym ',type)
622                               ,sym)))
623             (p1 new-expr)))
624          (t
625           (list 'THE type (p1 expr))))))
626
627(defun p1-truly-the (form)
628  (unless (= (length form) 3)
629    (compiler-error "Wrong number of arguments for special operator ~A (expected 2, but received ~D)."
630                    'TRULY-THE
631                    (1- (length form))))
632  (list 'TRULY-THE (%cadr form) (p1 (%caddr form))))
633
634(defknown unsafe-p (t) t)
635(defun unsafe-p (args)
636  (cond ((node-p args)
637         (unsafe-p (node-form args)))
638        ((atom args)
639         nil)
640        (t
641         (case (%car args)
642           (QUOTE
643            nil)
644           (LAMBDA
645            nil)
646           ((RETURN-FROM GO CATCH THROW UNWIND-PROTECT BLOCK)
647            t)
648           (t
649            (dolist (arg args)
650              (when (unsafe-p arg)
651                (return t))))))))
652
653(defknown rewrite-throw (t) t)
654(defun rewrite-throw (form)
655  (let ((args (cdr form)))
656    (if (unsafe-p args)
657        (let ((syms ())
658              (lets ()))
659          ;; Tag.
660          (let ((arg (first args)))
661            (if (constantp arg)
662                (push arg syms)
663                (let ((sym (gensym)))
664                  (push sym syms)
665                  (push (list sym arg) lets))))
666          ;; Result. "If the result-form produces multiple values, then all the
667          ;; values are saved."
668          (let ((arg (second args)))
669            (if (constantp arg)
670                (push arg syms)
671                (let ((sym (gensym)))
672                  (cond ((single-valued-p arg)
673                         (push sym syms)
674                         (push (list sym arg) lets))
675                        (t
676                         (push (list 'VALUES-LIST sym) syms)
677                         (push (list sym (list 'MULTIPLE-VALUE-LIST arg)) lets))))))
678          (list 'LET* (nreverse lets) (list* 'THROW (nreverse syms))))
679        form)))
680
681(defknown p1-throw (t) t)
682(defun p1-throw (form)
683  (let ((new-form (rewrite-throw form)))
684    (when (neq new-form form)
685      (return-from p1-throw (p1 new-form))))
686  (list* 'THROW (mapcar #'p1 (cdr form))))
687
688(defknown rewrite-function-call (t) t)
689(defun rewrite-function-call (form)
690  (let ((args (cdr form)))
691    (if (unsafe-p args)
692        (let ((arg1 (car args)))
693          (cond ((and (consp arg1) (eq (car arg1) 'GO))
694                 arg1)
695                (t
696                 (let ((syms ())
697                       (lets ()))
698                   ;; Preserve the order of evaluation of the arguments!
699                   (dolist (arg args)
700                     (cond ((constantp arg)
701                            (push arg syms))
702                           ((and (consp arg) (eq (car arg) 'GO))
703                            (return-from rewrite-function-call
704                                         (list 'LET* (nreverse lets) arg)))
705                           (t
706                            (let ((sym (gensym)))
707                              (push sym syms)
708                              (push (list sym arg) lets)))))
709                   (list 'LET* (nreverse lets) (list* (car form) (nreverse syms)))))))
710        form)))
711
712(defknown p1-function-call (t) t)
713(defun p1-function-call (form)
714  (let ((new-form (rewrite-function-call form)))
715    (when (neq new-form form)
716;;       (let ((*print-structure* nil))
717;;         (format t "old form = ~S~%" form)
718;;         (format t "new form = ~S~%" new-form))
719      (return-from p1-function-call (p1 new-form))))
720  (let* ((op (car form))
721         (local-function (find-local-function op)))
722    (cond (local-function
723;;            (format t "p1 local call to ~S~%" op)
724;;            (format t "inline-p = ~S~%" (inline-p op))
725
726           (when (and *enable-inline-expansion* (inline-p op))
727             (let ((expansion (local-function-inline-expansion local-function)))
728               (when expansion
729                 (let ((explain *explain*))
730                   (when (and explain (memq :calls explain))
731                     (format t ";   inlining call to local function ~S~%" op)))
732                 (return-from p1-function-call (p1 (expand-inline form expansion))))))
733
734           ;; FIXME
735           (dformat t "local function assumed not single-valued~%")
736           (setf (compiland-%single-valued-p *current-compiland*) nil)
737
738           (let ((variable (local-function-variable local-function)))
739             (when variable
740               (dformat t "p1 ~S used non-locally~%" (variable-name variable))
741               (setf (variable-used-non-locally-p variable) t))))
742          (t
743           ;; Not a local function call.
744           (dformat t "p1 non-local call to ~S~%" op)
745           (unless (single-valued-p form)
746;;                (format t "not single-valued op = ~S~%" op)
747             (setf (compiland-%single-valued-p *current-compiland*) nil)))))
748  (p1-default form))
749
750(defknown p1 (t) t)
751(defun p1 (form)
752  (cond ((symbolp form)
753         (let (value)
754           (cond ((null form)
755                  form)
756                 ((eq form t)
757                  form)
758                 ((keywordp form)
759                  form)
760                 ((and (constantp form)
761                       (progn
762                         (setf value (symbol-value form))
763                         (or (numberp value)
764                             (stringp value)
765                             (pathnamep value))))
766                  (setf form value))
767                 (t
768                  (let ((variable (find-visible-variable form)))
769                    (when (null variable)
770          (unless (or (special-variable-p form)
771                                  (memq form *undefined-variables*))
772      (compiler-style-warn "Undefined variable: ~S" form)
773      (push form *undefined-variables*))
774                      (setf variable (make-variable :name form :special-p t))
775                      (push variable *visible-variables*))
776                    (let ((ref (make-var-ref variable)))
777                      (unless (variable-special-p variable)
778                        (when (variable-ignore-p variable)
779                          (compiler-style-warn
780                           "Variable ~S is read even though it was declared to be ignored."
781                           (variable-name variable)))
782                        (push ref (variable-references variable))
783                        (incf (variable-reads variable))
784                        (cond ((eq (variable-compiland variable) *current-compiland*)
785                               (dformat t "p1: read ~S~%" form))
786                              (t
787                               (dformat t "p1: non-local read ~S variable-compiland = ~S current compiland = ~S~%"
788                                        form
789                                        (compiland-name (variable-compiland variable))
790                                        (compiland-name *current-compiland*))
791                               (setf (variable-used-non-locally-p variable) t))))
792                      (setf form ref)))
793                  form))))
794        ((atom form)
795         form)
796        (t
797         (let ((op (%car form))
798               handler)
799           (cond ((symbolp op)
800                  (when (compiler-macro-function op)
801                    (unless (notinline-p op)
802                      (multiple-value-bind (expansion expanded-p)
803                          (compiler-macroexpand form)
804                        ;; Fall through if no change...
805                        (when expanded-p
806                          (return-from p1 (p1 expansion))))))
807                  (cond ((setf handler (get op 'p1-handler))
808                         (funcall handler form))
809                        ((macro-function op *compile-file-environment*)
810                         (p1 (macroexpand form *compile-file-environment*)))
811                        ((special-operator-p op)
812                         (compiler-unsupported "P1: unsupported special operator ~S" op))
813                        (t
814                         (p1-function-call form))))
815                 ((and (consp op) (eq (%car op) 'LAMBDA))
816                  (p1 (list* 'FUNCALL form)))
817                 (t
818                  form))))))
819
820(defun install-p1-handler (symbol handler)
821  (setf (get symbol 'p1-handler) handler))
822
823(defun initialize-p1-handlers ()
824  (dolist (pair '((AND                  p1-default)
825                  (BLOCK                p1-block)
826                  (CATCH                p1-catch)
827                  (DECLARE              identity)
828                  (EVAL-WHEN            p1-eval-when)
829                  (FLET                 p1-flet)
830                  (FUNCALL              p1-funcall)
831                  (FUNCTION             p1-function)
832                  (GO                   p1-go)
833                  (IF                   p1-if)
834                  (LABELS               p1-labels)
835                  (LAMBDA               p1-lambda)
836                  (LET                  p1-let/let*)
837                  (LET*                 p1-let/let*)
838                  (LOAD-TIME-VALUE      identity)
839                  (LOCALLY              p1-locally)
840                  (MULTIPLE-VALUE-BIND  p1-m-v-b)
841                  (MULTIPLE-VALUE-CALL  p1-default)
842                  (MULTIPLE-VALUE-LIST  p1-default)
843                  (MULTIPLE-VALUE-PROG1 p1-default)
844                  (OR                   p1-default)
845                  (PROGN                p1-default)
846                  (PROGV                p1-progv)
847                  (QUOTE                p1-quote)
848                  (RETURN-FROM          p1-return-from)
849                  (SETQ                 p1-setq)
850                  (SYMBOL-MACROLET      identity)
851                  (TAGBODY              p1-tagbody)
852                  (THE                  p1-the)
853                  (THROW                p1-throw)
854                  (TRULY-THE            p1-truly-the)
855                  (UNWIND-PROTECT       p1-unwind-protect)))
856    (install-p1-handler (%car pair) (%cadr pair))))
857
858(initialize-p1-handlers)
859
860(defun invoke-compile-xep (xep-lambda-expression compiland)
861  (let ((xep-compiland
862   (make-compiland :lambda-expression 
863       (precompile-form xep-lambda-expression t)
864       :class-file (compiland-class-file compiland))))
865    (compile-xep xep-compiland)))
866
867(defun p1-compiland (compiland)
868;;   (format t "p1-compiland name = ~S~%" (compiland-name compiland))
869  (let ((form (compiland-lambda-expression compiland)))
870    (aver (eq (car form) 'LAMBDA))
871    (process-optimization-declarations (cddr form))
872
873    (let* ((lambda-list (cadr form))
874           (body (cddr form))
875           (auxvars (memq '&AUX lambda-list)))
876      (when auxvars
877        (setf lambda-list (subseq lambda-list 0 (position '&AUX lambda-list)))
878        (setf body (list (append (list 'LET* (cdr auxvars)) body))))
879
880      (when (and (null (compiland-parent compiland))
881                 ;; FIXME support SETF functions!
882                 (symbolp (compiland-name compiland)))
883        (when (memq '&OPTIONAL lambda-list)
884          (unless (or (memq '&KEY lambda-list) (memq '&REST lambda-list))
885            (let ((required-args (subseq lambda-list 0 (position '&OPTIONAL lambda-list)))
886                  (optional-args (cdr (memq '&OPTIONAL lambda-list))))
887            (dformat t "optional-args = ~S~%" optional-args)
888            (when (= (length optional-args) 1)
889              (let* ((optional-arg (car optional-args))
890                     (name (if (consp optional-arg) (%car optional-arg) optional-arg))
891                     (initform (if (consp optional-arg) (cadr optional-arg) nil))
892                     (supplied-p-var (and (consp optional-arg)
893                                          (= (length optional-arg) 3)
894                                          (third optional-arg)))
895                     (all-args
896                      (append required-args (list name)
897                              (when supplied-p-var (list supplied-p-var)))))
898                (when (<= (length all-args) call-registers-limit)
899                  (dformat t "optional-arg = ~S~%" optional-arg)
900                  (dformat t "supplied-p-var = ~S~%" supplied-p-var)
901                  (dformat t "required-args = ~S~%" required-args)
902                  (dformat t "all-args = ~S~%" all-args)
903                  (cond (supplied-p-var
904                         (let ((xep-lambda-expression
905                                `(lambda ,required-args
906                                   (let* ((,name ,initform)
907                                          (,supplied-p-var nil))
908                                     (%call-internal ,@all-args)))))
909                           (dformat t "xep-lambda-expression = ~S~%" xep-lambda-expression)
910         (invoke-compile-xep xep-lambda-expression compiland))
911                         (let ((xep-lambda-expression
912                                `(lambda ,(append required-args (list name))
913                                   (let* ((,supplied-p-var t))
914                                     (%call-internal ,@all-args)))))
915                           (dformat t "xep-lambda-expression = ~S~%" xep-lambda-expression)
916         (invoke-compile-xep xep-lambda-expression compiland))
917                         (setf lambda-list all-args)
918                         (setf (compiland-kind compiland) :internal))
919                        (t
920                         (let ((xep-lambda-expression
921                                `(lambda ,required-args
922                                   (let* ((,name ,initform))
923                                     (,(compiland-name compiland) ,@all-args)))))
924                           (dformat t "xep-lambda-expression = ~S~%" xep-lambda-expression)
925         (invoke-compile-xep xep-lambda-expression compiland))
926                         (setf lambda-list all-args))))))))))
927
928      (let* ((closure (make-closure `(lambda ,lambda-list nil) nil))
929             (syms (sys::varlist closure))
930             (vars nil))
931        (dolist (sym syms)
932          (let ((var (make-variable :name sym
933                                    :special-p (special-variable-p sym))))
934            (push var vars)
935            (push var *all-variables*)))
936        (setf (compiland-arg-vars compiland) (nreverse vars))
937        (let ((*visible-variables* *visible-variables*))
938          (dolist (var (compiland-arg-vars compiland))
939            (push var *visible-variables*))
940          (let ((free-specials (process-declarations-for-vars body *visible-variables*)))
941            (dolist (var free-specials)
942              (push var *visible-variables*)))
943          (setf (compiland-p1-result compiland)
944                (list* 'LAMBDA lambda-list (p1-body body))))))))
945
946(provide "COMPILER-PASS1")
Note: See TracBrowser for help on using the repository browser.