source: branches/1.0.x/abcl/src/org/armedbear/lisp/compiler-pass1.lisp

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

Remove two unnecessary EVAL-WHEN forms.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 53.4 KB
Line 
1;;; compiler-pass1.lisp
2;;;
3;;; Copyright (C) 2003-2008 Peter Graves
4;;; $Id: compiler-pass1.lisp 13533 2011-08-23 12:48:24Z 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(require "LOOP")
35(require "FORMAT")
36(require "CLOS")
37(require "PRINT-OBJECT")
38(require "COMPILER-TYPES")
39(require "KNOWN-FUNCTIONS")
40(require "KNOWN-SYMBOLS")
41(require "DUMP-FORM")
42(require "OPCODES")
43(require "JAVA")
44
45
46(defun generate-inline-expansion (name lambda-list body
47                                  &optional (args nil args-p))
48  "Generates code that can be used to expand a named local function inline.
49It can work either per-function (no args provided) or per-call."
50  (if args-p
51      (expand-function-call-inline nil lambda-list
52                                   (copy-tree `((block ,name ,@body)))
53                                   args)
54      (cond ((intersection lambda-list
55                           '(&optional &rest &key &allow-other-keys &aux)
56                           :test #'eq)
57             nil)
58            (t
59             (setf body (copy-tree body))
60             (list 'LAMBDA lambda-list
61                   (list* 'BLOCK name body))))))
62
63
64;;; Pass 1.
65
66(defun parse-lambda-list (lambda-list)
67  "Breaks the lambda list into the different elements, returning the values
68
69 required-vars
70 optional-vars
71 key-vars
72 key-p
73 rest-var
74 allow-other-keys-p
75 aux-vars
76 whole-var
77 env-var
78
79where each of the vars returned is a list with these elements:
80
81 var      - the actual variable name
82 initform - the init form if applicable; optional, keyword and aux vars
83 p-var    - variable indicating presence
84 keyword  - the keyword argument to match against
85
86"
87  (let ((state :req)
88        req opt key rest whole env aux key-p allow-others-p)
89    (dolist (arg lambda-list)
90      (case arg
91        (&optional (setf state :opt))
92        (&key (setf state :key
93                    key-p t))
94        (&rest (setf state :rest))
95        (&aux (setf state :aux))
96        (&allow-other-keys (setf state :none
97                                 allow-others-p t))
98        (&whole (setf state :whole))
99        (&environment (setf state :env))
100        (t
101         (case state
102           (:req (push arg req))
103           (:rest (setf rest (list arg)
104                        state :none))
105           (:env (setf env (list arg)
106                       state :req))
107           (:whole (setf whole (list arg)
108                         state :req))
109           (:none
110            (error "Invalid lambda list: argument found in :none state."))
111           (:opt
112            (cond
113              ((symbolp arg)
114               (push (list arg nil nil nil) opt))
115              ((consp arg)
116               (push (list (car arg) (cadr arg) (caddr arg)) opt))
117              (t
118               (error "Invalid state."))))
119           (:aux
120            (cond
121              ((symbolp arg)
122               (push (list arg nil nil nil) aux))
123              ((consp arg)
124               (push (list (car arg) (cadr arg) nil nil) aux))
125              (t
126               (error "Invalid :aux state."))))
127           (:key
128            (cond
129              ((symbolp arg)
130               (push (list arg nil nil (sys::keywordify arg)) key))
131              ((and (consp arg)
132                    (consp (car arg)))
133               (push (list (cadar arg) (cadr arg) (caddr arg) (caar arg)) key))
134              ((consp arg)
135               (push (list (car arg) (cadr arg) (caddr arg)
136                           (sys::keywordify (car arg))) key))
137              (t
138               (error "Invalid :key state."))))
139           (t (error "Invalid state found."))))))
140    (values
141     (nreverse req)
142     (nreverse opt)
143     (nreverse key)
144     key-p
145     rest allow-others-p
146     (nreverse aux) whole env)))
147
148(define-condition lambda-list-mismatch (error)
149  ((mismatch-type :reader lambda-list-mismatch-type :initarg :mismatch-type)))
150
151(defmacro push-argument-binding (var form temp-bindings bindings)
152  (let ((g (gensym)))
153    `(let ((,g (gensym (symbol-name '#:temp))))
154       (push (list ,g ,form) ,temp-bindings)
155       (push (list ,var ,g) ,bindings))))
156
157(defun match-lambda-list (parsed-lambda-list arguments)
158  (flet ((pop-required-argument ()
159     (if (null arguments)
160         (error 'lambda-list-mismatch :mismatch-type :too-few-arguments)
161         (pop arguments)))
162   (var (var-info) (car var-info))
163   (initform (var-info) (cadr var-info))
164   (p-var (var-info) (caddr var-info)))
165    (destructuring-bind (req opt key key-p rest allow-others-p aux whole env)
166  parsed-lambda-list
167      (declare (ignore whole env))
168      (let (req-bindings temp-bindings bindings ignorables)
169  ;;Required arguments.
170  (setf req-bindings
171        (loop :for var :in req :collect `(,var ,(pop-required-argument))))
172
173  ;;Optional arguments.
174  (when opt
175    (dolist (var-info opt)
176      (if arguments
177    (progn
178      (push-argument-binding (var var-info) (pop arguments)
179           temp-bindings bindings)
180      (when (p-var var-info)
181        (push `(,(p-var var-info) t) bindings)))
182    (progn
183      (push `(,(var var-info) ,(initform var-info)) bindings)
184      (when (p-var var-info)
185        (push `(,(p-var var-info) nil) bindings)))))
186    (setf bindings (nreverse bindings)))
187 
188  (unless (or key-p rest (null arguments))
189    (error 'lambda-list-mismatch :mismatch-type :too-many-arguments))
190
191  ;;Keyword and rest arguments.
192  (if key-p
193      (multiple-value-bind (kbindings ktemps kignor)
194    (match-keyword-and-rest-args 
195     key allow-others-p rest arguments)
196        (setf bindings (append bindings kbindings)
197        temp-bindings (append temp-bindings ktemps)
198        ignorables (append kignor ignorables)))
199      (when rest
200        (let (rest-binding)
201    (push-argument-binding (var rest) `(list ,@arguments)
202               temp-bindings rest-binding)
203    (setf bindings (append bindings rest-binding)))))
204  ;;Aux parameters.
205  (when aux
206    (setf bindings
207    `(,@bindings
208      ,@(loop
209           :for var-info :in aux
210           :collect `(,(var var-info) ,(initform var-info))))))
211  (values (append req-bindings temp-bindings bindings)
212    ignorables)))))
213
214(defun match-keyword-and-rest-args (key allow-others-p rest arguments)
215  (flet ((var (var-info) (car var-info))
216   (initform (var-info) (cadr var-info))
217   (p-var (var-info) (caddr var-info))
218   (keyword (var-info) (cadddr var-info)))
219    (when (oddp (list-length arguments))
220      (error 'lambda-list-mismatch
221       :mismatch-type :odd-number-of-keyword-arguments))
222   
223    (let (temp-bindings bindings other-keys-found-p ignorables already-seen
224    args)
225      ;;If necessary, make up a fake argument to hold :allow-other-keys,
226      ;;needed later. This also handles nicely:
227      ;;  3.4.1.4.1 Suppressing Keyword Argument Checking
228      ;;third statement.
229      (unless (find :allow-other-keys key :key #'keyword)
230  (let ((allow-other-keys-temp (gensym (symbol-name :allow-other-keys))))
231    (push allow-other-keys-temp ignorables)
232    (push (list allow-other-keys-temp nil nil :allow-other-keys) key)))
233     
234      ;;First, let's bind the keyword arguments that have been passed by
235      ;;the caller. If we encounter an unknown keyword, remember it.
236      ;;As per the above, :allow-other-keys will never be considered
237      ;;an unknown keyword.
238      (loop
239   :for var :in arguments :by #'cddr
240   :for value :in (cdr arguments) :by #'cddr
241   :do (let ((var-info (find var key :key #'keyword)))
242         (if (and var-info (not (member var already-seen)))
243       ;;var is one of the declared keyword arguments
244       (progn
245         (push-argument-binding (var var-info) value
246              temp-bindings bindings)
247         (when (p-var var-info)
248           (push `(,(p-var var-info) t) bindings))
249         (push var args)
250         (push (var var-info) args)
251         (push var already-seen))
252       (let ((g (gensym)))
253         (push `(,g ,value) temp-bindings)
254         (push var args)
255         (push g args)
256         (push g ignorables)
257         (unless var-info
258           (setf other-keys-found-p t))))))
259     
260      ;;Then, let's bind those arguments that haven't been passed in
261      ;;to their default value, in declaration order.
262      (let (defaults)
263  (loop
264     :for var-info :in key
265     :do (unless (find (var var-info) bindings :key #'car)
266     (push `(,(var var-info) ,(initform var-info)) defaults)
267     (when (p-var var-info)
268       (push `(,(p-var var-info) nil) defaults))))
269  (setf bindings (append (nreverse defaults) bindings)))
270     
271      ;;If necessary, check for unrecognized keyword arguments.
272      (when (and other-keys-found-p (not allow-others-p))
273  (if (loop
274         :for var :in arguments :by #'cddr
275         :if (eq var :allow-other-keys)
276         :do (return t))
277      ;;We know that :allow-other-keys has been passed, so we
278      ;;can access the binding for it and be sure to get the
279      ;;value passed by the user and not an initform.
280      (let* ((arg (var (find :allow-other-keys key :key #'keyword)))
281       (binding (find arg bindings :key #'car))
282       (form (cadr binding)))
283        (if (constantp form)
284      (unless (eval form)
285        (error 'lambda-list-mismatch
286         :mismatch-type :unknown-keyword))
287      (setf (cadr binding)
288      `(or ,(cadr binding)
289           (error 'program-error
290            "Unrecognized keyword argument")))))
291      ;;TODO: it would be nice to report *which* keyword
292      ;;is unknown
293      (error 'lambda-list-mismatch :mismatch-type :unknown-keyword)))
294      (when rest
295  (setf bindings (append bindings `((,(var rest) (list ,@(nreverse args)))))))
296      (values bindings temp-bindings ignorables))))
297
298#||test for the above
299(handler-case
300    (let ((lambda-list
301     (multiple-value-list
302      (jvm::parse-lambda-list
303       '(a b &optional (c 42) &rest foo &key (bar c) baz ((kaz kuz) bar))))))
304      (jvm::match-lambda-list
305       lambda-list
306       '((print 1) 3 (print 32) :bar 2)))
307  (jvm::lambda-list-mismatch (x) (jvm::lambda-list-mismatch-type x)))
308||#
309
310(defun expand-function-call-inline (form lambda-list body args)
311  (handler-case
312      (multiple-value-bind (bindings ignorables)
313    (match-lambda-list (multiple-value-list
314            (parse-lambda-list lambda-list))
315           args)
316  `(let* ,bindings
317     ,@(when ignorables
318       `((declare (ignorable ,@ignorables))))
319     ,@body))
320    (lambda-list-mismatch (x)
321      (compiler-warn "Invalid function call: ~S (mismatch type: ~A)"
322         form (lambda-list-mismatch-type x))
323      form)))
324
325;; Returns a list of declared free specials, if any are found.
326(declaim (ftype (function (list list block-node) list)
327                process-declarations-for-vars))
328(defun process-declarations-for-vars (body variables block)
329  (let ((free-specials '()))
330    (dolist (subform body)
331      (unless (and (consp subform) (eq (%car subform) 'DECLARE))
332        (return))
333      (let ((decls (%cdr subform)))
334        (dolist (decl decls)
335          (case (car decl)
336            ((DYNAMIC-EXTENT FTYPE INLINE NOTINLINE OPTIMIZE)
337             ;; Nothing to do here.
338             )
339            ((IGNORE IGNORABLE)
340             (process-ignore/ignorable (%car decl) (%cdr decl) variables))
341            (SPECIAL
342             (dolist (name (%cdr decl))
343               (let ((variable (find-variable name variables)))
344                 (cond ((and variable
345                             ;; see comment below (and DO-ALL-SYMBOLS.11)
346                             (eq (variable-compiland variable)
347                                 *current-compiland*))
348                        (setf (variable-special-p variable) t))
349                       (t
350                        (dformat t "adding free special ~S~%" name)
351                        (push (make-variable :name name :special-p t
352                                             :block block)
353                              free-specials))))))
354            (TYPE
355             (dolist (name (cddr decl))
356               (let ((variable (find-variable name variables)))
357                 (when (and variable
358                            ;; Don't apply a declaration in a local function to
359                            ;; a variable defined in its parent. For an example,
360                            ;; see CREATE-GREEDY-NO-ZERO-MATCHER in cl-ppcre.
361                            ;; FIXME suboptimal, since we ignore the declaration
362                            (eq (variable-compiland variable)
363                                *current-compiland*))
364                   (setf (variable-declared-type variable)
365                         (make-compiler-type (cadr decl)))))))
366            (t
367             (dolist (name (cdr decl))
368               (let ((variable (find-variable name variables)))
369                 (when variable
370                   (setf (variable-declared-type variable)
371                         (make-compiler-type (%car decl)))))))))))
372    free-specials))
373
374(defun check-name (name)
375  ;; FIXME Currently this error is signalled by the precompiler.
376  (unless (symbolp name)
377    (compiler-error "The variable ~S is not a symbol." name))
378  (when (constantp name)
379    (compiler-error "The name of the variable ~S is already in use to name a constant." name))
380  name)
381
382(declaim (ftype (function (t) t) p1-body))
383(defun p1-body (body)
384  (declare (optimize speed))
385  (let ((tail body))
386    (loop
387      (when (endp tail)
388        (return))
389      (setf (car tail) (p1 (%car tail)))
390      (setf tail (%cdr tail))))
391  body)
392
393(defknown p1-default (t) t)
394(declaim (inline p1-default))
395(defun p1-default (form)
396  (setf (cdr form) (p1-body (cdr form)))
397  form)
398
399(defmacro p1-let/let*-vars
400    (block varlist variables-var var body1 body2)
401  (let ((varspec (gensym))
402  (initform (gensym))
403  (name (gensym)))
404    `(let ((,variables-var ()))
405       (dolist (,varspec ,varlist)
406   (cond ((consp ,varspec)
407                ;; Even though the precompiler already signals this
408                ;; error, double checking can't hurt; after all, we're
409                ;; also rewriting &AUX into LET* bindings.
410    (unless (<= 1 (length ,varspec) 2)
411      (compiler-error "The LET/LET* binding specification ~S is invalid."
412          ,varspec))
413    (let* ((,name (%car ,varspec))
414           (,initform (p1 (%cadr ,varspec)))
415           (,var (make-variable :name (check-name ,name)
416                                            :initform ,initform
417                                            :block ,block)))
418      (when (neq ,initform (cadr ,varspec))
419        (setf (cadr ,varspec) ,initform))
420      (push ,var ,variables-var)
421      ,@body1))
422         (t
423    (let ((,var (make-variable :name (check-name ,varspec)
424                                           :block ,block)))
425      (push ,var ,variables-var)
426      ,@body1))))
427       ,@body2)))
428
429(defknown p1-let-vars (t) t)
430(defun p1-let-vars (block varlist)
431  (p1-let/let*-vars block
432   varlist vars var
433   ()
434   ((setf vars (nreverse vars))
435    (dolist (variable vars)
436      (push variable *visible-variables*)
437      (push variable *all-variables*))
438    vars)))
439
440(defknown p1-let*-vars (t) t)
441(defun p1-let*-vars (block varlist)
442  (p1-let/let*-vars block
443   varlist vars var
444   ((push var *visible-variables*)
445    (push var *all-variables*))
446   ((nreverse vars))))
447
448(defun p1-let/let* (form)
449  (declare (type cons form))
450  (let* ((*visible-variables* *visible-variables*)
451         (block (make-let/let*-node))
452   (*block* block)
453         (op (%car form))
454         (varlist (cadr form))
455         (body (cddr form)))
456    (aver (or (eq op 'LET) (eq op 'LET*)))
457    (when (eq op 'LET)
458      ;; Convert to LET* if possible.
459      (if (null (cdr varlist))
460          (setf op 'LET*)
461          (dolist (varspec varlist (setf op 'LET*))
462            (or (atom varspec)
463                (constantp (cadr varspec))
464                (eq (car varspec) (cadr varspec))
465                (return)))))
466    (let ((vars (if (eq op 'LET)
467                    (p1-let-vars block varlist)
468                    (p1-let*-vars block varlist))))
469      ;; Check for globally declared specials.
470      (dolist (variable vars)
471        (when (special-variable-p (variable-name variable))
472          (setf (variable-special-p variable) t
473                (let-environment-register block) t)))
474      ;; For processing declarations, we want to walk the variable list from
475      ;; last to first, since declarations apply to the last-defined variable
476      ;; with the specified name.
477      (setf (let-free-specials block)
478            (process-declarations-for-vars body (reverse vars) block))
479      (setf (let-vars block) vars)
480      ;; Make free specials visible.
481      (dolist (variable (let-free-specials block))
482        (push variable *visible-variables*)))
483    (let ((*blocks* (cons block *blocks*)))
484      (setf body (p1-body body)))
485    (setf (let-form block) (list* op varlist body))
486    block))
487
488(defun p1-locally (form)
489  (let* ((*visible-variables* *visible-variables*)
490         (block (make-locally-node))
491   (*block* block)
492         (free-specials (process-declarations-for-vars (cdr form) nil block)))
493    (setf (locally-free-specials block) free-specials)
494    (dolist (special free-specials)
495;;       (format t "p1-locally ~S is special~%" name)
496      (push special *visible-variables*))
497    (let ((*blocks* (cons block *blocks*)))
498      (setf (locally-form block)
499            (list* 'LOCALLY (p1-body (cdr form))))
500      block)))
501
502(defknown p1-m-v-b (t) t)
503(defun p1-m-v-b (form)
504  (when (= (length (cadr form)) 1)
505    (let ((new-form `(let* ((,(caadr form) ,(caddr form))) ,@(cdddr form))))
506      (return-from p1-m-v-b (p1-let/let* new-form))))
507  (let* ((*visible-variables* *visible-variables*)
508         (block (make-m-v-b-node))
509   (*block* block)
510         (varlist (cadr form))
511         ;; Process the values-form first. ("The scopes of the name binding and
512         ;; declarations do not include the values-form.")
513         (values-form (p1 (caddr form)))
514         (*blocks* (cons block *blocks*))
515         (body (cdddr form)))
516    (let ((vars ()))
517      (dolist (symbol varlist)
518        (let ((var (make-variable :name symbol :block block)))
519          (push var vars)
520          (push var *visible-variables*)
521          (push var *all-variables*)))
522      ;; Check for globally declared specials.
523      (dolist (variable vars)
524        (when (special-variable-p (variable-name variable))
525          (setf (variable-special-p variable) t
526                (m-v-b-environment-register block) t)))
527      (setf (m-v-b-free-specials block)
528            (process-declarations-for-vars body vars block))
529      (dolist (special (m-v-b-free-specials block))
530        (push special *visible-variables*))
531      (setf (m-v-b-vars block) (nreverse vars)))
532    (setf body (p1-body body))
533    (setf (m-v-b-form block)
534          (list* 'MULTIPLE-VALUE-BIND varlist values-form body))
535    block))
536
537(defun p1-block (form)
538  (let* ((block (make-block-node (cadr form)))
539   (*block* block)
540         (*blocks* (cons block *blocks*)))
541    (setf (cddr form) (p1-body (cddr form)))
542    (setf (block-form block) form)
543    (when (block-non-local-return-p block)
544      ;; Add a closure variable for RETURN-FROM to use
545      (push (setf (block-id-variable block)
546                  (make-variable :name (gensym)
547                                 :block block
548                                 :used-non-locally-p t))
549            *all-variables*))
550    block))
551
552(defun p1-catch (form)
553  (let* ((tag (p1 (cadr form)))
554         (body (cddr form))
555         (block (make-catch-node))
556   (*block* block)
557         ;; our subform processors need to know
558         ;; they're enclosed in a CATCH block
559         (*blocks* (cons block *blocks*))
560         (result '()))
561    (dolist (subform body)
562      (let ((op (and (consp subform) (%car subform))))
563        (push (p1 subform) result)
564        (when (memq op '(GO RETURN-FROM THROW))
565          (return))))
566    (setf result (nreverse result))
567    (when (and (null (cdr result))
568               (consp (car result))
569               (eq (caar result) 'GO))
570      (return-from p1-catch (car result)))
571    (push tag result)
572    (push 'CATCH result)
573    (setf (catch-form block) result)
574    block))
575
576(defun p1-threads-synchronized-on (form)
577  (let* ((synchronized-object (p1 (cadr form)))
578         (body (cddr form))
579         (block (make-synchronized-node))
580   (*block* block)
581         (*blocks* (cons block *blocks*))
582         result)
583    (dolist (subform body)
584      (let ((op (and (consp subform) (%car subform))))
585        (push (p1 subform) result)
586        (when (memq op '(GO RETURN-FROM THROW))
587          (return))))
588    (setf (synchronized-form block)
589          (list* 'threads:synchronized-on synchronized-object
590                 (nreverse result)))
591    block))
592
593(defun p1-unwind-protect (form)
594  (if (= (length form) 2)
595      (p1 (second form)) ; No cleanup forms: (unwind-protect (...)) => (...)
596
597      ;; in order to compile the cleanup forms twice (see
598      ;; p2-unwind-protect-node), we need to p1 them twice; p1 outcomes
599      ;; can be compiled (in the same compiland?) only once.
600      ;;
601      ;; However, p1 transforms the forms being processed, so, we
602      ;; need to copy the forms to create a second copy.
603      (let* ((block (make-unwind-protect-node))
604       (*block* block)
605             ;; a bit of jumping through hoops...
606             (unwinding-forms (p1-body (copy-tree (cddr form))))
607             (unprotected-forms (p1-body (cddr form)))
608             ;; ... because only the protected form is
609             ;; protected by the UNWIND-PROTECT block
610             (*blocks* (cons block *blocks*))
611             (protected-form (p1 (cadr form))))
612        (setf (unwind-protect-form block)
613              `(unwind-protect ,protected-form
614                 (progn ,@unwinding-forms)
615                 ,@unprotected-forms))
616        block)))
617
618(defknown p1-return-from (t) t)
619(defun p1-return-from (form)
620  (let* ((name (second form))
621         (block (find-block name))
622         non-local-p)
623    (when (null block)
624      (compiler-error "RETURN-FROM ~S: no block named ~S is currently visible."
625                      name name))
626    (dformat t "p1-return-from block = ~S~%" (block-name block))
627    (cond ((eq (block-compiland block) *current-compiland*)
628           ;; Local case. If the RETURN is nested inside an UNWIND-PROTECT
629           ;; which is inside the block we're returning from, we'll do a non-
630           ;; local return anyway so that UNWIND-PROTECT can catch it and run
631           ;; its cleanup forms.
632           ;;(dformat t "*blocks* = ~S~%" (mapcar #'node-name *blocks*))
633           (let ((protected (enclosed-by-protected-block-p block)))
634             (dformat t "p1-return-from protected = ~S~%" protected)
635             (if protected
636                 (setf (block-non-local-return-p block) t
637                       non-local-p t)
638                 ;; non-local GO's ensure environment restoration
639                 ;; find out about this local GO
640                 (when (null (block-needs-environment-restoration block))
641                   (setf (block-needs-environment-restoration block)
642                         (enclosed-by-environment-setting-block-p block))))))
643          (t
644           (setf (block-non-local-return-p block) t
645                 non-local-p t)))
646    (when (block-non-local-return-p block)
647      (dformat t "non-local return from block ~S~%" (block-name block)))
648    (let ((value-form (p1 (caddr form))))
649      (push value-form (block-return-value-forms block))
650      (make-jump-node (list 'RETURN-FROM name value-form)
651                      non-local-p block))))
652
653(defun p1-tagbody (form)
654  (let* ((block (make-tagbody-node))
655   (*block* block)
656         (*blocks* (cons block *blocks*))
657         (*visible-tags* *visible-tags*)
658         (local-tags '())
659         (body (cdr form)))
660    ;; Make all the tags visible before processing the body forms.
661    (dolist (subform body)
662      (when (or (symbolp subform) (integerp subform))
663        (let* ((tag (make-tag :name subform :label (gensym) :block block)))
664          (push tag local-tags)
665          (push tag *visible-tags*))))
666    (let ((new-body '())
667          (live t))
668      (dolist (subform body)
669        (cond ((or (symbolp subform) (integerp subform))
670               (push subform new-body)
671               (push (find subform local-tags :key #'tag-name :test #'eql)
672                     (tagbody-tags block))
673               (setf live t))
674              ((not live)
675               ;; Nothing to do.
676               )
677              (t
678               (when (and (consp subform)
679                          (memq (%car subform) '(GO RETURN-FROM THROW)))
680                 ;; Subsequent subforms are unreachable until we see another
681                 ;; tag.
682                 (setf live nil))
683               (push (p1 subform) new-body))))
684      (setf (tagbody-form block) (list* 'TAGBODY (nreverse new-body))))
685    (when (some #'tag-used-non-locally (tagbody-tags block))
686      (push (setf (tagbody-id-variable block)
687                  (make-variable :name (gensym)
688                                 :block block
689                                 :used-non-locally-p t))
690            *all-variables*))
691    block))
692
693(defknown p1-go (t) t)
694(defun p1-go (form)
695  (let* ((name (cadr form))
696         (tag (find-tag name)))
697    (unless tag
698      (error "p1-go: tag not found: ~S" name))
699    (setf (tag-used tag) t)
700    (let ((tag-block (tag-block tag))
701          non-local-p)
702      (cond ((eq (tag-compiland tag) *current-compiland*)
703             ;; Does the GO leave an enclosing UNWIND-PROTECT or CATCH?
704             (if (enclosed-by-protected-block-p tag-block)
705                 (setf (tagbody-non-local-go-p tag-block) t
706                       (tag-used-non-locally tag) t
707                       non-local-p t)
708                 ;; non-local GO's ensure environment restoration
709                 ;; find out about this local GO
710                 (when (null (tagbody-needs-environment-restoration tag-block))
711                   (setf (tagbody-needs-environment-restoration tag-block)
712                         (enclosed-by-environment-setting-block-p tag-block)))))
713            (t
714             (setf (tagbody-non-local-go-p tag-block) t
715                   (tag-used-non-locally tag) t
716                   non-local-p t)))
717      (make-jump-node form non-local-p tag-block tag))))
718
719(defun split-decls (forms specific-vars)
720  (let ((other-decls nil)
721        (specific-decls nil))
722    (dolist (form forms)
723      (unless (and (consp form) (eq (car form) 'DECLARE)) ; shouldn't happen
724        (return))
725      (dolist (decl (cdr form))
726        (case (car decl)
727          ((OPTIMIZE DECLARATION DYNAMIC-EXTENT FTYPE INLINE NOTINLINE)
728           (push (list 'DECLARE decl) other-decls))
729          (SPECIAL
730           (dolist (name (cdr decl))
731             (if (memq name specific-vars)
732                 (push `(DECLARE (SPECIAL ,name)) specific-decls)
733                 (push `(DECLARE (SPECIAL ,name)) other-decls))))
734          (TYPE
735           (dolist (name (cddr decl))
736             (if (memq name specific-vars)
737                 (push `(DECLARE (TYPE ,(cadr decl) ,name)) specific-decls)
738                 (push `(DECLARE (TYPE ,(cadr decl) ,name)) other-decls))))
739          (t
740           (dolist (name (cdr decl))
741             (if (memq name specific-vars)
742                 (push `(DECLARE (,(car decl) ,name)) specific-decls)
743                 (push `(DECLARE (,(car decl) ,name)) other-decls)))))))
744    (values (nreverse other-decls)
745            (nreverse specific-decls))))
746
747(defun rewrite-aux-vars (form)
748  (let* ((lambda-list (cadr form))
749         (aux-p (memq '&AUX lambda-list))
750         (lets (cdr aux-p))
751         aux-vars)
752    (unless aux-p
753      ;; no rewriting required
754      (return-from rewrite-aux-vars form))
755    (multiple-value-bind (body decls)
756        (parse-body (cddr form))
757      (dolist (form lets)
758        (cond ((consp form)
759               (push (car form) aux-vars))
760              (t
761               (push form aux-vars))))
762      (setf lambda-list (subseq lambda-list 0 (position '&AUX lambda-list)))
763      (multiple-value-bind (let-decls lambda-decls)
764          (split-decls decls (lambda-list-names lambda-list))
765        `(lambda ,lambda-list
766           ,@lambda-decls
767           (let* ,lets
768             ,@let-decls
769             ,@body))))))
770
771(defun rewrite-lambda (form)
772  (setf form (rewrite-aux-vars form))
773  (let* ((lambda-list (cadr form)))
774    (if (not (or (memq '&optional lambda-list)
775                 (memq '&key lambda-list)))
776        ;; no need to rewrite: no arguments with possible initforms anyway
777        form
778      (multiple-value-bind (body decls doc)
779          (parse-body (cddr form))
780        (let (state let-bindings new-lambda-list
781                    (non-constants 0))
782          (do* ((vars lambda-list (cdr vars))
783                (var (car vars) (car vars)))
784               ((endp vars))
785            (push (car vars) new-lambda-list)
786            (let ((replacement (gensym)))
787              (flet ((parse-compound-argument (arg)
788                       "Returns the values NAME, KEYWORD, INITFORM, INITFORM-P,
789   SUPPLIED-P and SUPPLIED-P-P assuming ARG is a compound argument."
790                       (destructuring-bind
791                             (name &optional (initform nil initform-supplied-p)
792                                   (supplied-p nil supplied-p-supplied-p))
793                           (if (listp arg) arg (list arg))
794                         (if (listp name)
795                             (values (cadr name) (car name)
796                                     initform initform-supplied-p
797                                     supplied-p supplied-p-supplied-p)
798                             (values name (make-keyword name)
799                                     initform initform-supplied-p
800                                     supplied-p supplied-p-supplied-p)))))
801                (case var
802                  (&optional (setf state :optional))
803                  (&key (setf state :key))
804                  ((&whole &environment &rest &body &allow-other-keys)
805                   ;; do nothing special
806                   )
807                  (t
808                   (cond
809                     ((atom var)
810                      (setf (car new-lambda-list)
811                            (if (eq state :key)
812                                (list (list (make-keyword var) replacement))
813                                replacement))
814                      (push (list var replacement) let-bindings))
815                     ((constantp (second var))
816                      ;; so, we must have a consp-type var we're looking at
817                      ;; and it has a constantp initform
818                      (multiple-value-bind
819                            (name keyword initform initform-supplied-p
820                                  supplied-p supplied-p-supplied-p)
821                          (parse-compound-argument var)
822                        (let ((var-form (if (eq state :key)
823                                            (list keyword replacement)
824                                            replacement))
825                              (supplied-p-replacement (gensym)))
826                          (setf (car new-lambda-list)
827                                (cond
828                                  ((not initform-supplied-p)
829                                   (list var-form))
830                                  ((not supplied-p-supplied-p)
831                                   (list var-form initform))
832                                  (t
833                                   (list var-form initform
834                                         supplied-p-replacement))))
835                          (push (list name replacement) let-bindings)
836                          ;; if there was a 'supplied-p' variable, it might
837                          ;; be used in the declarations. Since those will be
838                          ;; moved below the LET* block, we need to move the
839                          ;; supplied-p parameter too.
840                          (when supplied-p-supplied-p
841                            (push (list supplied-p supplied-p-replacement)
842                                  let-bindings)))))
843                     (t
844                      (incf non-constants)
845                      ;; this is either a keyword or an optional argument
846                      ;; with a non-constantp initform
847                      (multiple-value-bind
848                            (name keyword initform initform-supplied-p
849                                  supplied-p supplied-p-supplied-p)
850                          (parse-compound-argument var)
851                        (declare (ignore initform-supplied-p))
852                        (let ((var-form (if (eq state :key)
853                                            (list keyword replacement)
854                                            replacement))
855                              (supplied-p-replacement (gensym)))
856                          (setf (car new-lambda-list)
857                                (list var-form nil supplied-p-replacement))
858                          (push (list name `(if ,supplied-p-replacement
859                                                ,replacement ,initform))
860                                let-bindings)
861                          (when supplied-p-supplied-p
862                            (push (list supplied-p supplied-p-replacement)
863                                  let-bindings)))))))))))
864          (if (zerop non-constants)
865              ;; there was no reason to rewrite...
866              form
867              (let ((rv
868                     `(lambda ,(nreverse new-lambda-list)
869                        ,@(when doc (list doc))
870                        (let* ,(nreverse let-bindings)
871                          ,@decls ,@body))))
872                rv)))))))
873
874(defun validate-function-name (name)
875  (unless (or (symbolp name) (setf-function-name-p name))
876    (compiler-error "~S is not a valid function name." name))
877  name)
878
879(defun construct-flet/labels-function (definition)
880  (let* ((name (car definition))
881         (block-name (fdefinition-block-name (validate-function-name name)))
882         (lambda-list (cadr definition))
883         (compiland (make-compiland :name name :parent *current-compiland*))
884         (local-function (make-local-function :name name :compiland compiland)))
885    (push local-function (compiland-children *current-compiland*))
886    (multiple-value-bind
887          (body decls)
888        (parse-body (cddr definition))
889      (setf (local-function-definition local-function)
890            (copy-tree (cdr definition)))
891      (setf (compiland-lambda-expression compiland)
892            (rewrite-lambda `(lambda ,lambda-list
893                               ,@decls
894                               (block ,block-name
895                                 ,@body)))))
896    local-function))
897
898(defun p1-flet (form)
899  (let* ((local-functions
900          (mapcar #'(lambda (definition)
901                      (construct-flet/labels-function definition))
902                  (cadr form)))
903         (*local-functions* *local-functions*))
904    (dolist (local-function local-functions)
905      (p1-compiland (local-function-compiland local-function)))
906    (dolist (local-function local-functions)
907      (push local-function *local-functions*))
908    (with-saved-compiler-policy
909        (process-optimization-declarations (cddr form))
910      (let* ((block (make-flet-node))
911             (*block* block)
912             (*blocks* (cons block *blocks*))
913             (body (cddr form))
914             (*visible-variables* *visible-variables*))
915        (setf (flet-free-specials block)
916              (process-declarations-for-vars body nil block))
917        (dolist (special (flet-free-specials block))
918          (push special *visible-variables*))
919        (setf body (p1-body body) ;; affects the outcome of references-needed-p
920              (flet-form block)
921              (list* (car form)
922                     (remove-if #'(lambda (fn)
923                                    (and (inline-p (local-function-name fn))
924                                         (not (local-function-references-needed-p fn))))
925                                local-functions)
926                     body))
927        block))))
928
929
930(defun p1-labels (form)
931  (let* ((local-functions
932          (mapcar #'(lambda (definition)
933                      (construct-flet/labels-function definition))
934                  (cadr form)))
935         (*local-functions* *local-functions*)
936         (*visible-variables* *visible-variables*))
937    (dolist (local-function local-functions)
938      (push local-function *local-functions*))
939    (dolist (local-function local-functions)
940      (p1-compiland (local-function-compiland local-function)))
941    (let* ((block (make-labels-node))
942           (*block* block)
943           (*blocks* (cons block *blocks*))
944           (body (cddr form))
945           (*visible-variables* *visible-variables*))
946      (setf (labels-free-specials block)
947            (process-declarations-for-vars body nil block))
948      (dolist (special (labels-free-specials block))
949        (push special *visible-variables*))
950      (setf (labels-form block)
951            (list* (car form) local-functions (p1-body (cddr form))))
952      block)))
953
954(defknown p1-funcall (t) t)
955(defun p1-funcall (form)
956  (unless (> (length form) 1)
957    (compiler-warn "Wrong number of arguments for ~A." (car form))
958    (return-from p1-funcall form))
959  (let ((function-form (%cadr form)))
960    (when (and (consp function-form)
961               (eq (%car function-form) 'FUNCTION))
962      (let ((name (%cadr function-form)))
963;;         (format t "p1-funcall name = ~S~%" name)
964        (let ((source-transform (source-transform name)))
965          (when source-transform
966;;             (format t "found source transform for ~S~%" name)
967;;             (format t "old form = ~S~%" form)
968;;             (let ((new-form (expand-source-transform form)))
969;;               (when (neq new-form form)
970;;                 (format t "new form = ~S~%" new-form)
971;;                 (return-from p1-funcall (p1 new-form))))
972            (let ((new-form (expand-source-transform (list* name (cddr form)))))
973;;               (format t "new form = ~S~%" new-form)
974              (return-from p1-funcall (p1 new-form)))
975            )))))
976  ;; Otherwise...
977  (p1-function-call form))
978
979(defun p1-function (form)
980  (let ((form (copy-tree form))
981        local-function)
982    (cond ((and (consp (cadr form))
983                (or (eq (caadr form) 'LAMBDA)
984                    (eq (caadr form) 'NAMED-LAMBDA)))
985           (let* ((named-lambda-p (eq (caadr form) 'NAMED-LAMBDA))
986                  (named-lambda-form (when named-lambda-p
987                                       (cadr form)))
988                  (name (when named-lambda-p
989                          (cadr named-lambda-form)))
990                  (lambda-form (if named-lambda-p
991                                   (cons 'LAMBDA (cddr named-lambda-form))
992                                   (cadr form)))
993                  (lambda-list (cadr lambda-form))
994                  (body (cddr lambda-form))
995                  (compiland (make-compiland :name (if named-lambda-p
996                                                       name (gensym "ANONYMOUS-LAMBDA-"))
997                                             :lambda-expression lambda-form
998                                             :parent *current-compiland*))
999                  (local-function (make-local-function :compiland compiland)))
1000             (push local-function (compiland-children *current-compiland*))
1001             (multiple-value-bind (body decls)
1002                 (parse-body body)
1003               (setf (compiland-lambda-expression compiland)
1004                     ;; if there still was a doc-string present, remove it
1005                     (rewrite-lambda
1006                      `(lambda ,lambda-list ,@decls ,@body)))
1007               (let ((*visible-variables* *visible-variables*)
1008                     (*current-compiland* compiland))
1009                 (p1-compiland compiland)))
1010             (list 'FUNCTION local-function)))
1011          ((setf local-function (find-local-function (cadr form)))
1012           (dformat "p1-function local function ~S~%" (cadr form))
1013           ;;we found out that the function needs a reference
1014           (setf (local-function-references-needed-p local-function) t)
1015           form)
1016          (t
1017           form))))
1018
1019(defun p1-lambda (form)
1020  (setf form (rewrite-lambda form))
1021  (let* ((lambda-list (cadr form)))
1022    (when (or (memq '&optional lambda-list)
1023              (memq '&key lambda-list))
1024      (let ((state nil))
1025        (dolist (arg lambda-list)
1026          (cond ((memq arg lambda-list-keywords)
1027                 (setf state arg))
1028                ((memq state '(&optional &key))
1029                 (when (and (consp arg)
1030                            (not (constantp (second arg))))
1031                   (compiler-unsupported
1032                    "P1-LAMBDA: can't handle optional argument with non-constant initform.")))))))
1033    (p1-function (list 'FUNCTION form))))
1034
1035(defun p1-eval-when (form)
1036  (list* (car form) (cadr form) (mapcar #'p1 (cddr form))))
1037
1038(defknown p1-progv (t) t)
1039(defun p1-progv (form)
1040  ;; We've already checked argument count in PRECOMPILE-PROGV.
1041  (let* ((symbols-form (p1 (cadr form)))
1042         (values-form (p1 (caddr form)))
1043         (block (make-progv-node))
1044   (*block* block)
1045         (*blocks* (cons block *blocks*))
1046         (body (cdddr form)))
1047;;  The (commented out) block below means to detect compile-time
1048;;  enumeration of bindings to be created (a quoted form in the symbols
1049;;  position).
1050;;    (when (and (quoted-form-p symbols-form)
1051;;               (listp (second symbols-form)))
1052;;      (dolist (name (second symbols-form))
1053;;        (let ((variable (make-variable :name name :special-p t)))
1054;;          (push
1055    (setf (progv-environment-register block) t
1056          (progv-form block)
1057          `(progv ,symbols-form ,values-form ,@(p1-body body)))
1058    block))
1059
1060(defun p1-quote (form)
1061  (unless (= (length form) 2)
1062    (compiler-error "Wrong number of arguments for special operator ~A (expected 1, but received ~D)."
1063                    'QUOTE
1064                    (1- (length form))))
1065  (let ((arg (%cadr form)))
1066    (if (or (numberp arg) (characterp arg))
1067        arg
1068        form)))
1069
1070(defun p1-setq (form)
1071  (unless (= (length form) 3)
1072    (error "Too many arguments for SETQ."))
1073  (let ((arg1 (%cadr form))
1074        (arg2 (%caddr form)))
1075    (let ((variable (find-visible-variable arg1)))
1076      (if variable
1077          (progn
1078            (when (variable-ignore-p variable)
1079              (compiler-style-warn
1080               "Variable ~S is assigned even though it was declared to be ignored."
1081               (variable-name variable)))
1082            (incf (variable-writes variable))
1083            (cond ((eq (variable-compiland variable) *current-compiland*)
1084                   (dformat t "p1-setq: write ~S~%" arg1))
1085                  (t
1086                   (dformat t "p1-setq: non-local write ~S~%" arg1)
1087                   (setf (variable-used-non-locally-p variable) t))))
1088          (dformat t "p1-setq: unknown variable ~S~%" arg1)))
1089    (list 'SETQ arg1 (p1 arg2))))
1090
1091(defun p1-the (form)
1092  (unless (= (length form) 3)
1093    (compiler-error "Wrong number of arguments for special operator ~A (expected 2, but received ~D)."
1094                    'THE
1095                    (1- (length form))))
1096  (let ((type (%cadr form))
1097        (expr (%caddr form)))
1098    (cond ((and (listp type) (eq (car type) 'VALUES))
1099           ;; FIXME
1100           (p1 expr))
1101          ((= *safety* 3)
1102           (let* ((sym (gensym))
1103                  (new-expr `(let ((,sym ,expr))
1104                               (require-type ,sym ',type)
1105                               ,sym)))
1106             (p1 new-expr)))
1107          ((and (<= 1 *safety* 2) ;; at safety 1 or 2 check relatively
1108                (symbolp type))   ;; simple types (those specified by a single symbol)
1109           (let* ((sym (gensym))
1110                  (new-expr `(let ((,sym ,expr))
1111                               (require-type ,sym ',type)
1112                               ,sym)))
1113             (p1 new-expr)))
1114          (t
1115           (list 'THE type (p1 expr))))))
1116
1117(defun p1-truly-the (form)
1118  (unless (= (length form) 3)
1119    (compiler-error "Wrong number of arguments for special operator ~A (expected 2, but received ~D)."
1120                    'TRULY-THE
1121                    (1- (length form))))
1122  (list 'TRULY-THE (%cadr form) (p1 (%caddr form))))
1123
1124(defknown p1-throw (t) t)
1125(defun p1-throw (form)
1126  (list* 'THROW (mapcar #'p1 (cdr form))))
1127
1128(defknown rewrite-function-call (t) t)
1129(defun rewrite-function-call (form)
1130  (let ((op (car form)) (args (cdr form)))
1131    (cond
1132      ((and (eq op 'funcall) (listp (car args)) (eq (caar args) 'lambda))
1133       ;;(funcall (lambda (...) ...) ...)
1134       (let ((op (car args)) (args (cdr args)))
1135         (expand-function-call-inline form (cadr op) (copy-tree (cddr op))
1136                                      args)))
1137      ((and (listp op) (eq (car op) 'lambda))
1138       ;;((lambda (...) ...) ...)
1139       (expand-function-call-inline form (cadr op) (copy-tree (cddr op)) args))
1140      (t form))))
1141
1142(defknown p1-function-call (t) t)
1143(defun p1-function-call (form)
1144  (let ((new-form (rewrite-function-call form)))
1145    (when (neq new-form form)
1146      (return-from p1-function-call (p1 new-form))))
1147  (let* ((op (car form))
1148         (local-function (find-local-function op)))
1149    (when local-function
1150;;            (format t "p1 local call to ~S~%" op)
1151;;            (format t "inline-p = ~S~%" (inline-p op))
1152
1153      (when (and *enable-inline-expansion* (inline-p op)
1154                 (local-function-definition local-function))
1155        (let* ((definition (local-function-definition local-function))
1156               (lambda-list (car definition))
1157               (body (cdr definition))
1158               (expansion (generate-inline-expansion op lambda-list body
1159                                                     (cdr form))))
1160          (when expansion
1161            (let ((explain *explain*))
1162              (when (and explain (memq :calls explain))
1163                (format t ";   inlining call to local function ~S~%" op)))
1164            (return-from p1-function-call
1165                         (let ((*inline-declarations*
1166                                (remove op *inline-declarations* :key #'car :test #'equal)))
1167                           (p1 expansion))))))))
1168  (p1-default form))
1169
1170(defun %funcall (fn &rest args)
1171  "Dummy FUNCALL wrapper to force p1 not to optimize the call."
1172  (apply fn args))
1173
1174(defun p1-variable-reference (var)
1175  (let ((variable (find-visible-variable var)))
1176    (when (null variable)
1177      (unless (or (special-variable-p var)
1178                  (memq var *undefined-variables*))
1179        (compiler-style-warn
1180         "Undefined variable ~S assumed special" var)
1181        (push var *undefined-variables*))
1182      (setf variable (make-variable :name var :special-p t))
1183      (push variable *visible-variables*))
1184    (let ((ref (make-var-ref variable)))
1185      (unless (variable-special-p variable)
1186        (when (variable-ignore-p variable)
1187          (compiler-style-warn
1188           "Variable ~S is read even though it was declared to be ignored."
1189           (variable-name variable)))
1190        (push ref (variable-references variable))
1191        (incf (variable-reads variable))
1192        (cond
1193          ((eq (variable-compiland variable) *current-compiland*)
1194           (dformat t "p1: read ~S~%" var))
1195          (t
1196           (dformat t "p1: non-local read ~S variable-compiland = ~S current compiland = ~S~%"
1197                    var
1198                    (compiland-name (variable-compiland variable))
1199                    (compiland-name *current-compiland*))
1200           (setf (variable-used-non-locally-p variable) t))))
1201      ref)))
1202
1203(defknown p1 (t) t)
1204(defun p1 (form)
1205  (cond
1206    ((symbolp form)
1207     (let (value)
1208       (cond
1209         ((null form)
1210          form)
1211         ((eq form t)
1212          form)
1213         ((keywordp form)
1214          form)
1215         ((and (constantp form)
1216               (progn
1217                 (setf value (symbol-value form))
1218                 (or (numberp value)
1219                     (stringp value)
1220                     (pathnamep value))))
1221          (setf form value))
1222         (t
1223          (p1-variable-reference form)))))
1224    ((atom form)
1225     form)
1226    (t
1227     (let ((op (%car form))
1228           handler)
1229       (cond
1230         ((symbolp op)
1231          (when (find-local-function op)
1232            ;; local functions shadow macros and functions in
1233            ;; the global environment as well as compiler macros
1234            (return-from p1
1235              (p1-function-call form)))
1236          (when (compiler-macro-function op)
1237            (unless (notinline-p op)
1238              (multiple-value-bind (expansion expanded-p)
1239                  (compiler-macroexpand form)
1240                ;; Fall through if no change...
1241                (when expanded-p
1242                  (return-from p1 (p1 expansion))))))
1243          (cond
1244            ((setf handler (get op 'p1-handler))
1245             (funcall handler form))
1246            ((macro-function op *compile-file-environment*)
1247             (p1 (macroexpand form *compile-file-environment*)))
1248            ((special-operator-p op)
1249             (compiler-unsupported "P1: unsupported special operator ~S" op))
1250            (t
1251             (p1-function-call form))))
1252         ((and (consp op) (eq (%car op) 'LAMBDA))
1253          (let ((maybe-optimized-call (rewrite-function-call form)))
1254            (if (eq maybe-optimized-call form)
1255                (p1 `(%funcall (function ,op) ,@(cdr form)))
1256                (p1 maybe-optimized-call))))
1257         (t
1258          form))))))
1259
1260(defun install-p1-handler (symbol handler)
1261  (setf (get symbol 'p1-handler) handler))
1262
1263(defun initialize-p1-handlers ()
1264  (dolist (pair '((AND                  p1-default)
1265                  (BLOCK                p1-block)
1266                  (CATCH                p1-catch)
1267                  (DECLARE              identity)
1268                  (EVAL-WHEN            p1-eval-when)
1269                  (FLET                 p1-flet)
1270                  (FUNCALL              p1-funcall)
1271                  (FUNCTION             p1-function)
1272                  (GO                   p1-go)
1273                  (IF                   p1-default)
1274                  ;; used to be p1-if, which was used to rewrite the test
1275                  ;; form to a LET-binding; that's not necessary, because
1276                  ;; the test form doesn't lead to multiple operands on the
1277                  ;; operand stack
1278                  (LABELS               p1-labels)
1279                  (LAMBDA               p1-lambda)
1280                  (LET                  p1-let/let*)
1281                  (LET*                 p1-let/let*)
1282                  (LOAD-TIME-VALUE      identity)
1283                  (LOCALLY              p1-locally)
1284                  (MULTIPLE-VALUE-BIND  p1-m-v-b)
1285                  (MULTIPLE-VALUE-CALL  p1-default)
1286                  (MULTIPLE-VALUE-LIST  p1-default)
1287                  (MULTIPLE-VALUE-PROG1 p1-default)
1288                  (OR                   p1-default)
1289                  (PROGN                p1-default)
1290                  (PROGV                p1-progv)
1291                  (QUOTE                p1-quote)
1292                  (RETURN-FROM          p1-return-from)
1293                  (SETQ                 p1-setq)
1294                  (SYMBOL-MACROLET      identity)
1295                  (TAGBODY              p1-tagbody)
1296                  (THE                  p1-the)
1297                  (THROW                p1-throw)
1298                  (TRULY-THE            p1-truly-the)
1299                  (UNWIND-PROTECT       p1-unwind-protect)
1300                  (THREADS:SYNCHRONIZED-ON
1301                                        p1-threads-synchronized-on)
1302      (JVM::WITH-INLINE-CODE identity)))
1303    (install-p1-handler (%car pair) (%cadr pair))))
1304
1305(initialize-p1-handlers)
1306
1307(defun p1-compiland (compiland)
1308;;   (format t "p1-compiland name = ~S~%" (compiland-name compiland))
1309  (let ((*current-compiland* compiland)
1310        (*local-functions* *local-functions*)
1311        (*visible-variables* *visible-variables*)
1312        (form (compiland-lambda-expression compiland)))
1313    (aver (eq (car form) 'LAMBDA))
1314    (setf form (rewrite-lambda form))
1315    (with-saved-compiler-policy
1316      (process-optimization-declarations (cddr form))
1317
1318      (let* ((lambda-list (cadr form))
1319             (body (cddr form))
1320             (closure (make-closure `(lambda ,lambda-list nil) nil))
1321             (syms (sys::varlist closure))
1322             (vars nil)
1323             compiland-result)
1324        (dolist (sym syms)
1325          (let ((var (make-variable :name sym
1326                                    :special-p (special-variable-p sym))))
1327            (push var vars)
1328            (push var *all-variables*)
1329            (push var *visible-variables*)))
1330        (setf (compiland-arg-vars compiland) (nreverse vars))
1331        (let ((free-specials (process-declarations-for-vars body vars nil)))
1332          (setf (compiland-free-specials compiland) free-specials)
1333          (dolist (var free-specials)
1334            (push var *visible-variables*)))
1335        (setf compiland-result
1336              (list* 'LAMBDA lambda-list (p1-body body)))
1337        (setf (compiland-%single-valued-p compiland)
1338              (single-valued-p compiland-result))
1339        (setf (compiland-p1-result compiland)
1340              compiland-result)))))
1341
1342(provide "COMPILER-PASS1")
Note: See TracBrowser for help on using the repository browser.