source: trunk/abcl/src/org/armedbear/lisp/precompiler.lisp @ 14911

Last change on this file since 14911 was 14911, checked in by Mark Evenson, 7 years ago

precompiler: possibly beta reduce form with function position lambda (Alan Ruttenberg)

Case 1: If the lambda has a single form in it, let someone define a
transform using:

define-function-position-lambda-transform (body-function-name (arglist form args) &body body)

body-function-name is the car of the single form in the lambda
arglist is the arglist of the lambda
form is the single form within the lambda
args are the arguments to which the lambda will be defined.

The function should check whether it can do a transform, and do it if
so, otherwise return nil signalling it couldn't

Case 2: If case 1 is not successful then if the arglist is a simple
one (no &key, &rest, &optional) then do a standard beta-reduction
binding the args to arglist using let (https://wiki.haskell.org/Beta_reduction)

If not, return and do the usual thing.

An example is in contrib/jss/optimize-java-call.lisp

To see benefits, (compile-file contrib/jss/test-optimize-java-call.lisp)
and then load the compiled file. You should see something like the below
which reports the timings for the optimized and unoptimized version of
10000 calls of (#"compile" 'regex.pattern ".*")

--

With optimization: (INVOKE-RESTARGS-MACRO "compile" (QUOTE REGEX.PATTERN) (LIST ".*") NIL T)
Without optimization: ((LAMBDA (#:G85648 &REST #:G85649) (INVOKE-RESTARGS "compile" #:G85648 #:G85649 NIL)) (QUOTE REGEX.PATTERN) ".*")

JUST-LOOP
0.0 seconds real time
0 cons cells

OPTIMIZED-JSS
0.011 seconds real time
0 cons cells

UNOPTIMIZED-JSS
0.325 seconds real time
800156 cons cells

---
<> rdfs:seeAlso <https://mailman.common-lisp.net/pipermail/armedbear-devel/2016-October/003726.html>
<> rdfs:seeAlso <https://mailman.common-lisp.net/pipermail/armedbear-devel/2016-November/003733.html> .
<> :fixes <https://mailman.common-lisp.net/pipermail/armedbear-devel/2016-November/003736.html> .
<> :closes <https://github.com/armedbear/abcl/pull/11/files> .
<> :closes <http://abcl.org/trac/ticket/420> .

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 44.8 KB
Line 
1;;; precompiler.lisp
2;;;
3;;; Copyright (C) 2003-2008 Peter Graves <peter@armedbear.org>
4;;; $Id: precompiler.lisp 14911 2016-11-17 19:22:56Z mevenson $
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 "SYSTEM")
33
34
35(export '(process-optimization-declarations
36          inline-p notinline-p inline-expansion expand-inline
37          *defined-functions* *undefined-functions* note-name-defined))
38
39(declaim (ftype (function (t) t) process-optimization-declarations))
40(defun process-optimization-declarations (forms)
41  (dolist (form forms)
42    (unless (and (consp form) (eq (%car form) 'DECLARE))
43      (return))
44    (dolist (decl (%cdr form))
45      (case (car decl)
46        (OPTIMIZE
47         (dolist (spec (%cdr decl))
48           (let ((val 3)
49                 (quality spec))
50             (when (consp spec)
51               (setf quality (%car spec)
52                     val (cadr spec)))
53             (when (and (fixnump val)
54                        (<= 0 val 3))
55               (case quality
56                 (speed
57                  (setf *speed* val))
58                 (safety
59                  (setf *safety* val))
60                 (debug
61                  (setf *debug* val))
62                 (space
63                  (setf *space* val))
64                 (compilation-speed) ;; Ignored.
65                 (t
66                  (compiler-warn "Ignoring unknown optimization quality ~S in ~S." quality decl)))))))
67        ((INLINE NOTINLINE)
68         (dolist (symbol (%cdr decl))
69           (push (cons symbol (%car decl)) *inline-declarations*)))
70        (:explain
71         (dolist (spec (%cdr decl))
72           (let ((val t)
73                 (quality spec))
74             (when (consp spec)
75               (setf quality (%car spec))
76               (when (= (length spec) 2)
77                 (setf val (%cadr spec))))
78             (if val
79                 (pushnew quality *explain*)
80                 (setf *explain* (remove quality *explain*)))))))))
81  t)
82
83(declaim (ftype (function (t) t) inline-p))
84(defun inline-p (name)
85  (declare (optimize speed))
86  (let ((entry (assoc name *inline-declarations* :test #'equal)))
87    (if entry
88        (eq (cdr entry) 'INLINE)
89        (and (symbolp name) (eq (get name '%inline) 'INLINE)))))
90
91(declaim (ftype (function (t) t) notinline-p))
92(defun notinline-p (name)
93  (declare (optimize speed))
94  (let ((entry (assoc name *inline-declarations* :test #'equal)))
95    (if entry
96        (eq (cdr entry) 'NOTINLINE)
97        (and (symbolp name) (eq (get name '%inline) 'NOTINLINE)))))
98
99(defun expand-inline (form expansion)
100;;   (format t "expand-inline form = ~S~%" form)
101;;   (format t "expand-inline expansion = ~S~%" expansion)
102  (let* ((op (car form))
103         (proclaimed-ftype (proclaimed-ftype op))
104         (args (cdr form))
105         (vars (cadr expansion))
106         (varlist ())
107         new-form)
108;;     (format t "op = ~S proclaimed-ftype = ~S~%" op (proclaimed-ftype op))
109    (do ((vars vars (cdr vars))
110         (args args (cdr args)))
111        ((null vars))
112      (push (list (car vars) (car args)) varlist))
113    (setf new-form (list* 'LET (nreverse varlist)
114                          (copy-tree (cddr expansion))))
115    (when proclaimed-ftype
116      (let ((result-type (ftype-result-type proclaimed-ftype)))
117        (when (and result-type
118                   (neq result-type t)
119                   (neq result-type '*))
120          (setf new-form (list 'TRULY-THE result-type new-form)))))
121;;     (format t "expand-inline new form = ~S~%" new-form)
122    new-form))
123
124(define-compiler-macro assoc (&whole form &rest args)
125  (cond ((and (= (length args) 4)
126              (eq (third args) :test)
127              (or (equal (fourth args) '(quote eq))
128                  (equal (fourth args) '(function eq))))
129         `(assq ,(first args) ,(second args)))
130        ((= (length args) 2)
131         `(assql ,(first args) ,(second args)))
132        (t form)))
133
134(define-compiler-macro member (&whole form &rest args)
135  (let ((arg1 (first args))
136        (arg2 (second args)))
137    (case (length args)
138      (2
139       `(memql ,arg1 ,arg2))
140      (4
141       (let ((arg3 (third args))
142             (arg4 (fourth args)))
143         (cond ((and (eq arg3 :test)
144                     (or (equal arg4 '(quote eq))
145                         (equal arg4 '(function eq))))
146                `(memq ,arg1 ,arg2))
147               ((and (eq arg3 :test)
148                     (or (equal arg4 '(quote eql))
149                         (equal arg4 '(function eql))
150                         (equal arg4 '(quote char=))
151                         (equal arg4 '(function char=))))
152                `(memql ,arg1 ,arg2))
153               (t
154                form))))
155      (t
156       form))))
157
158(define-compiler-macro search (&whole form &rest args)
159  (if (= (length args) 2)
160      `(simple-search ,@args)
161      form))
162
163(define-compiler-macro identity (&whole form &rest args)
164  (if (= (length args) 1)
165      `(progn ,(car args))
166      form))
167
168(defun quoted-form-p (form)
169  (and (consp form) (eq (%car form) 'QUOTE) (= (length form) 2)))
170
171(define-compiler-macro eql (&whole form &rest args)
172  (let ((first (car args))
173        (second (cadr args)))
174    (if (or (and (quoted-form-p first) (symbolp (cadr first)))
175            (and (quoted-form-p second) (symbolp (cadr second))))
176        `(eq ,first ,second)
177        form)))
178
179(define-compiler-macro not (&whole form arg)
180  (if (atom arg)
181      form
182      (let ((op (case (car arg)
183                  (>= '<)
184                  (<  '>=)
185                  (<= '>)
186                  (>  '<=)
187                  (t  nil))))
188        (if (and op (= (length arg) 3))
189            (cons op (cdr arg))
190            form))))
191
192(defun predicate-for-type (type)
193  (cdr (assq type '((ARRAY             . arrayp)
194                    (ATOM              . atom)
195                    (BIT-VECTOR        . bit-vector-p)
196                    (CHARACTER         . characterp)
197                    (COMPLEX           . complexp)
198                    (CONS              . consp)
199                    (FIXNUM            . fixnump)
200                    (FLOAT             . floatp)
201                    (FUNCTION          . functionp)
202                    (HASH-TABLE        . hash-table-p)
203                    (INTEGER           . integerp)
204                    (LIST              . listp)
205                    (NULL              . null)
206                    (NUMBER            . numberp)
207                    (NUMBER            . numberp)
208                    (PACKAGE           . packagep)
209                    (RATIONAL          . rationalp)
210                    (REAL              . realp)
211                    (SIMPLE-BIT-VECTOR . simple-bit-vector-p)
212                    (SIMPLE-STRING     . simple-string-p)
213                    (SIMPLE-VECTOR     . simple-vector-p)
214                    (STREAM            . streamp)
215                    (STRING            . stringp)
216                    (SYMBOL            . symbolp)))))
217
218(define-compiler-macro typep (&whole form &rest args)
219  (if (= (length args) 2) ; no environment arg
220      (let* ((object (%car args))
221             (type-specifier (%cadr args))
222             (type (and (consp type-specifier)
223                        (eq (%car type-specifier) 'QUOTE)
224                        (%cadr type-specifier)))
225             (predicate (and type (predicate-for-type type))))
226        (if predicate
227            `(,predicate ,object)
228            `(%typep ,@args)))
229      form))
230
231(define-compiler-macro subtypep (&whole form &rest args)
232  (if (= (length args) 2)
233      `(%subtypep ,@args)
234      form))
235
236(define-compiler-macro funcall (&whole form
237                                &environment env &rest args)
238  (let ((callee (car args)))
239    (if (and (>= *speed* *debug*)
240             (consp callee)
241             (eq (%car callee) 'function)
242             (symbolp (cadr callee))
243             (not (special-operator-p (cadr callee)))
244             (not (macro-function (cadr callee) env))
245             (memq (symbol-package (cadr callee))
246                   (list (find-package "CL") (find-package "SYS"))))
247        `(,(cadr callee) ,@(cdr args))
248        form)))
249
250(define-compiler-macro byte (size position)
251  `(cons ,size ,position))
252
253(define-compiler-macro byte-size (bytespec)
254  `(car ,bytespec))
255
256(define-compiler-macro byte-position (bytespec)
257  `(cdr ,bytespec))
258
259(define-source-transform concatenate (&whole form result-type &rest sequences)
260  (if (equal result-type '(quote STRING))
261      `(sys::concatenate-to-string (list ,@sequences))
262      form))
263
264(define-source-transform ldb (&whole form bytespec integer)
265  (if (and (consp bytespec)
266           (eq (%car bytespec) 'byte)
267           (= (length bytespec) 3))
268      (let ((size (%cadr bytespec))
269            (position (%caddr bytespec)))
270        `(%ldb ,size ,position ,integer))
271      form))
272
273(define-source-transform find (&whole form item sequence &key from-end test test-not start end key)
274  (cond ((and (>= (length form) 3) (null start) (null end))
275         (cond ((and (stringp sequence)
276                     (null from-end)
277                     (member test '(#'eql #'char=) :test #'equal)
278                     (null test-not)
279                     (null key))
280                `(string-find ,item ,sequence))
281               (t
282                (let ((item-var (gensym))
283                      (seq-var (gensym)))
284                  `(let ((,item-var ,item)
285                         (,seq-var ,sequence))
286                     (if (listp ,seq-var)
287                         (list-find* ,item-var ,seq-var ,from-end ,test ,test-not 0 (length ,seq-var) ,key)
288                         (vector-find* ,item-var ,seq-var ,from-end ,test ,test-not 0 (length ,seq-var) ,key)))))))
289        (t
290         form)))
291
292(define-source-transform adjoin (&whole form &rest args)
293  (if (= (length args) 2)
294      `(adjoin-eql ,(first args) ,(second args))
295      form))
296
297(define-source-transform format (&whole form &rest args)
298  (if (stringp (second args))
299      `(format ,(pop args) (formatter ,(pop args)) ,@args)
300      form))
301
302(define-compiler-macro catch (&whole form tag &rest args)
303  (declare (ignore tag))
304  (if (and (null (cdr args))
305           (constantp (car args)))
306      (car args)
307      form))
308
309(define-compiler-macro string= (&whole form &rest args)
310  (if (= (length args) 2)
311      `(sys::%%string= ,@args)
312      form))
313
314(define-compiler-macro <= (&whole form &rest args)
315  (cond ((and (= (length args) 3)
316              (numberp (first args))
317              (numberp (third args))
318              (= (first args) (third args)))
319         `(= ,(second args) ,(first args)))
320        (t
321         form)))
322
323
324(in-package "PRECOMPILER")
325
326
327(export '(precompile-form precompile))
328
329
330;; No source-transforms and inlining in precompile-function-call
331;; No macro expansion in precompile-dolist and precompile-dotimes
332;; No macro expansion in precompile-do/do*
333;; No macro expansion in precompile-defun
334;; Special precompilation in precompile-case and precompile-cond
335;; Special precompilation in precompile-when and precompile-unless
336;; No precompilation in precompile-nth-value
337;; Special precompilation in precompile-return
338;;
339;; if *in-jvm-compile* is false
340
341(defvar *in-jvm-compile* nil)
342(defvar *precompile-env* nil)
343
344(declaim (inline expand-macro))
345(defun expand-macro (form)
346  (macroexpand-1 form *precompile-env*))
347
348
349(declaim (ftype (function (t) t) precompile1))
350(defun precompile1 (form)
351  (cond ((symbolp form)
352         (multiple-value-bind
353               (expansion expanded)
354             (expand-macro form)
355           (if expanded
356               (precompile1 expansion)
357               form)))
358        ((atom form)
359         form)
360        (t
361         (let ((op (%car form))
362               handler)
363           (when (symbolp op)
364             (cond ((setf handler (get op 'precompile-handler))
365                    (return-from precompile1 (funcall handler form)))
366                   ((macro-function op *precompile-env*)
367                    (return-from precompile1 (precompile1 (expand-macro form))))
368                   ((special-operator-p op)
369                    (error "PRECOMPILE1: unsupported special operator ~S." op))))
370           (precompile-function-call form)))))
371
372(defun precompile-identity (form)
373  (declare (optimize speed))
374  form)
375
376(declaim (ftype (function (t) cons) precompile-cons))
377(defun precompile-cons (form)
378  (cons (car form) (mapcar #'precompile1 (cdr form))))
379
380(declaim (ftype (function (t t) t) precompile-function-call))
381(defun precompile-function-call (form)
382  (let ((op (car form)))
383    (when (and (consp op) (eq (%car op) 'LAMBDA))
384      (return-from precompile-function-call
385  (or (precompile-function-position-lambda op (cdr form))
386      (cons (precompile-lambda op)
387      (mapcar #'precompile1 (cdr form))))))
388    (when (or (not *in-jvm-compile*) (notinline-p op))
389      (return-from precompile-function-call (precompile-cons form)))
390    (when (source-transform op)
391      (let ((new-form (expand-source-transform form)))
392        (when (neq new-form form)
393          (return-from precompile-function-call (precompile1 new-form)))))
394    (when *enable-inline-expansion*
395      (let ((expansion (inline-expansion op)))
396        (when expansion
397          (let ((explain *explain*))
398            (when (and explain (memq :calls explain))
399              (format t ";   inlining call to ~S~%" op)))
400          (return-from precompile-function-call (precompile1 (expand-inline form expansion))))))
401    (cons op (mapcar #'precompile1 (cdr form)))))
402
403(defun precompile-function-position-lambda (lambda args)
404  (let* ((arglist (second lambda))
405   (body (cddr lambda))
406   (simple-arglist? (not (or (memq '&KEY arglist) (memq '&OPTIONAL arglist) (memq '&REST arglist)))))
407    (or
408     ;;give a chance for someone to transform single-form function bodies
409     (and (= (length body) 1) (consp (car body)) (get (caar body) 'sys::function-position-lambda-transform)
410    (funcall (get (caar body) 'sys::function-position-lambda-transform) (caar body) (car body) (mapcar #'precompile1 args)))
411     (and simple-arglist?
412    (let ((arglist-length (if (memq '&aux arglist) (position '&aux arglist) (length arglist))))
413      (if (= (length args) arglist-length)
414    ;; simplest case - we have a simple arglist with as many
415    ;; arguments as call args. Transform to let.
416    (return-from precompile-function-position-lambda
417      `(let* ,(append
418          (loop for arg-name in arglist
419          for arg in (mapcar #'precompile1 args)
420          until (eq arg-name '&aux)
421          collect (list arg-name arg))
422          (subseq arglist (1+ arglist-length)))
423          ,@body))
424    (error "Argument mismatch for lambda in function position: ~a applied to ~a" `(lambda ,arglist body) args)))))))
425
426(defmacro define-function-position-lambda-transform (body-function-name (arglist form args) &body body)
427  `(put ',body-function-name 'sys::function-position-lambda-transform 
428  #'(lambda(,arglist ,form ,args)
429      ,@body)))
430
431(defun precompile-locally (form)
432  (let ((*inline-declarations* *inline-declarations*))
433    (process-optimization-declarations (cdr form))
434  (cons 'LOCALLY (mapcar #'precompile1 (cdr form)))))
435
436(defun precompile-block (form)
437  (let ((args (cdr form)))
438    (if (null (cdr args))
439        nil
440        (list* 'BLOCK (car args) (mapcar #'precompile1 (cdr args))))))
441
442(defun precompile-dolist (form)
443  (if *in-jvm-compile*
444      (precompile1 (macroexpand form *precompile-env*))
445      (cons 'DOLIST (cons (mapcar #'precompile1 (cadr form))
446                          (mapcar #'precompile1 (cddr form))))))
447
448(defun precompile-dotimes (form)
449  (if *in-jvm-compile*
450      (precompile1 (macroexpand form *precompile-env*))
451      (cons 'DOTIMES (cons (mapcar #'precompile1 (cadr form))
452                           (mapcar #'precompile1 (cddr form))))))
453
454(defun precompile-do/do*-vars (varlist)
455  (let ((result nil))
456    (dolist (varspec varlist)
457      (if (atom varspec)
458          (push varspec result)
459          (case (length varspec)
460            (1
461             (push (%car varspec) result))
462            (2
463             (let* ((var (%car varspec))
464                    (init-form (%cadr varspec)))
465               (unless (symbolp var)
466                 (error 'type-error))
467               (push (list var (precompile1 init-form))
468                     result)))
469            (3
470             (let* ((var (%car varspec))
471                    (init-form (%cadr varspec))
472                    (step-form (%caddr varspec)))
473               (unless (symbolp var)
474                 (error 'type-error))
475               (push (list var (precompile1 init-form) (precompile1 step-form))
476                     result))))))
477    (nreverse result)))
478
479(defun precompile-do/do*-end-form (end-form)
480  (let ((end-test-form (car end-form))
481        (result-forms (cdr end-form)))
482    (list* (precompile1 end-test-form) (mapcar #'precompile1 result-forms))))
483
484(defun precompile-do/do* (form)
485  (if *in-jvm-compile*
486      (precompile1 (macroexpand form *precompile-env*))
487      (list* (car form)
488             (precompile-do/do*-vars (cadr form))
489             (precompile-do/do*-end-form (caddr form))
490             (mapcar #'precompile1 (cdddr form)))))
491
492(defun precompile-do-symbols (form)
493  (list* (car form) (cadr form) (mapcar #'precompile1 (cddr form))))
494
495(defun precompile-load-time-value (form)
496  form)
497
498(defun precompile-progn (form)
499  (let ((body (cdr form)))
500    (if (eql (length body) 1)
501        (let ((res (precompile1 (%car body))))
502          ;; If the result turns out to be a bare symbol, leave it wrapped
503          ;; with PROGN so it won't be mistaken for a tag in an enclosing
504          ;; TAGBODY.
505          (if (symbolp res)
506              (list 'progn res)
507              res))
508        (cons 'PROGN (mapcar #'precompile1 body)))))
509
510(defun precompile-threads-synchronized-on (form)
511  (cons 'threads:synchronized-on (mapcar #'precompile1 (cdr form))))
512
513(defun precompile-progv (form)
514  (if (< (length form) 3)
515      (error "Not enough arguments for ~S." 'progv)
516      (list* 'PROGV (mapcar #'precompile1 (%cdr form)))))
517
518(defun precompile-setf (form)
519  (let ((place (second form)))
520    (cond ((and (consp place)
521                (eq (%car place) 'VALUES))
522     (setf form
523     (list* 'SETF
524      (list* 'VALUES
525             (mapcar #'precompile1 (%cdr place)))
526      (cddr form)))
527     (precompile1 (expand-macro form)))
528    ((symbolp place)
529           (multiple-value-bind
530                 (expansion expanded)
531               ;; Expand once in case the form expands
532               ;; into something that needs special
533               ;; SETF treatment
534               (macroexpand-1 place *precompile-env*)
535             (if expanded
536                 (precompile1 (list* 'SETF expansion
537                                     (cddr form)))
538                 (precompile1 (expand-macro form)))))
539          (t
540           (precompile1 (expand-macro form))))))
541
542(defun precompile-setq (form)
543  (let* ((args (cdr form))
544         (len (length args)))
545    (when (oddp len)
546      (error 'simple-program-error
547             :format-control "Odd number of arguments to SETQ."))
548    (if (= len 2)
549        (let* ((sym (%car args))
550               (val (%cadr args)))
551          (multiple-value-bind
552                (expansion expanded)
553              ;; Expand once in case the form expands
554              ;; into something that needs special
555              ;; SETF treatment
556              (macroexpand-1 sym *precompile-env*)
557            (if expanded
558                (precompile1 (list 'SETF expansion val))
559                (list 'SETQ sym (precompile1 val)))))
560        (let ((result ()))
561          (loop
562            (when (null args)
563              (return))
564            (push (precompile-setq (list 'SETQ (car args) (cadr args))) result)
565            (setq args (cddr args)))
566          (setq result (nreverse result))
567          (push 'PROGN result)
568          result))))
569
570(defun precompile-psetf (form)
571  (setf form
572        (list* 'PSETF
573               (mapcar #'precompile1 (cdr form))))
574  (precompile1 (expand-macro form)))
575
576(defun precompile-psetq (form)
577  ;; Make sure all the vars are symbols.
578  (do* ((rest (cdr form) (cddr rest))
579        (var (car rest)))
580       ((null rest))
581    (unless (symbolp var)
582      (error 'simple-error
583             :format-control "~S is not a symbol."
584             :format-arguments (list var))))
585  ;; Delegate to PRECOMPILE-PSETF so symbol macros are handled correctly.
586  (precompile-psetf form))
587
588
589(defun precompile-lambda-list (form)
590  (let (new aux-tail)
591    (dolist (arg form (nreverse new))
592       (if (or (atom arg) (> 2 (length arg)))
593           (progn
594             (when (eq arg '&aux)
595               (setf aux-tail t))
596             (push arg new))
597          ;; must be a cons of more than 1 cell
598          (let ((new-arg (copy-list arg)))
599            (unless (<= 1 (length arg) (if aux-tail 2 3))
600              ;; the aux-vars have a maximum length of 2 conses
601              ;; optional and key vars may have 3
602              (error 'program-error
603                     :format-control
604                     "The ~A binding specification ~S is invalid."
605                     :format-arguments (list (if aux-tail "&AUX"
606                                                 "&OPTIONAL/&KEY") arg)))
607             (setf (second new-arg)
608                   (precompile1 (second arg)))
609             (push new-arg new))))))
610
611(defun extract-lambda-vars (lambda-list)
612  (let ((state :required)
613        vars)
614    (dolist (var/key lambda-list vars)
615      (cond
616        ((eq '&aux var/key)       (setf state :aux))
617        ((eq '&key var/key)       (setf state :key))
618        ((eq '&optional var/key)  (setf state :optional))
619        ((eq '&rest var/key)      (setf state :rest))
620        ((symbolp var/key)        (unless (eq var/key '&allow-other-keys)
621                                    (push var/key vars)))
622        ((and (consp var/key)
623              (member state '(:optional :key)))
624         (setf var/key (car var/key))
625         (when (and (consp var/key) (eq state :key))
626           (setf var/key (second var/key)))
627         (if (symbolp var/key)
628             (push var/key vars)
629             (error 'program-error
630                    :format-control
631                    "Unexpected ~A variable specifier ~A."
632                    :format-arguments (list state var/key))))
633        ((and (consp var/key) (eq state :aux))
634         (if (symbolp (car var/key))
635             (push (car var/key) vars)
636             (error 'program-error
637                    :format-control "Unexpected &AUX format for ~A."
638                    :format-arguments (list var/key))))
639        (t
640         (error 'program-error
641                :format-control "Unexpected lambda-list format: ~A."
642                :format-arguments (list lambda-list)))))))
643
644(defun precompile-lambda (form)
645  (let ((body (cddr form))
646        (precompiled-lambda-list
647           (precompile-lambda-list (cadr form)))
648        (*inline-declarations* *inline-declarations*)
649        (*precompile-env* (make-environment *precompile-env*)))
650    (process-optimization-declarations body)
651    (dolist (var (extract-lambda-vars precompiled-lambda-list))
652      (environment-add-symbol-binding *precompile-env* var nil))
653    (list* 'LAMBDA precompiled-lambda-list
654           (mapcar #'precompile1 body))))
655
656(defun precompile-named-lambda (form)
657  (let ((lambda-form (list* 'LAMBDA (caddr form) (cdddr form))))
658    (let ((body (cddr lambda-form))
659          (precompiled-lambda-list
660           (precompile-lambda-list (cadr lambda-form)))
661          (*inline-declarations* *inline-declarations*)
662          (*precompile-env* (make-environment *precompile-env*)))
663      (process-optimization-declarations body)
664      (dolist (var (extract-lambda-vars precompiled-lambda-list))
665        (environment-add-symbol-binding *precompile-env* var nil))
666      (list* 'NAMED-LAMBDA (cadr form) precompiled-lambda-list
667             (mapcar #'precompile1 body)))))
668
669(defun precompile-defun (form)
670  (if *in-jvm-compile*
671      (precompile1 (expand-macro form))
672      form))
673
674(defun precompile-macrolet (form)
675  (let ((*precompile-env* (make-environment *precompile-env*)))
676    (dolist (definition (cadr form))
677      (environment-add-macro-definition
678       *precompile-env*
679       (car definition)
680       (make-macro (car definition)
681                   (make-closure
682                    (make-macro-expander definition)
683                    NIL))))
684    (multiple-value-bind (body decls)
685        (parse-body (cddr form) nil)
686      `(locally ,@decls ,@(mapcar #'precompile1 body)))))
687
688(defun precompile-symbol-macrolet (form)
689  (let ((*precompile-env* (make-environment *precompile-env*))
690        (defs (cadr form)))
691    (dolist (def defs)
692      (let ((sym (car def))
693            (expansion (cadr def)))
694        (when (special-variable-p sym)
695          (error 'program-error
696                 :format-control
697                 "Attempt to bind the special variable ~S with SYMBOL-MACROLET."
698                 :format-arguments (list sym)))
699        (environment-add-symbol-binding *precompile-env*
700                                        sym
701                                        (sys::make-symbol-macro expansion))))
702    (multiple-value-bind (body decls)
703        (parse-body (cddr form) nil)
704      (when decls
705        (let ((specials ()))
706          (dolist (decl decls)
707            (when (eq (car decl) 'DECLARE)
708              (dolist (declspec (cdr decl))
709                (when (eq (car declspec) 'SPECIAL)
710                  (setf specials (append specials (cdr declspec)))))))
711          (when specials
712            (let ((syms (mapcar #'car (cadr form))))
713              (dolist (special specials)
714                (when (memq special syms)
715                  (error 'program-error
716                         :format-control
717                         "~S is a symbol-macro and may not be declared special."
718                         :format-arguments (list special))))))))
719      `(locally ,@decls ,@(mapcar #'precompile1 body)))))
720
721(defun precompile-the (form)
722  (list 'THE
723        (second form)
724        (precompile1 (third form))))
725
726(defun precompile-truly-the (form)
727  (list 'TRULY-THE
728        (second form)
729        (precompile1 (third form))))
730
731(defun precompile-let/let*-vars (vars)
732  (let ((result nil))
733    (dolist (var vars)
734      (cond ((consp var)
735             (unless (<= 1 (length var) 2)
736               (error 'program-error
737                       :format-control
738                       "The LET/LET* binding specification ~S is invalid."
739                       :format-arguments (list var)))
740             (let ((v (%car var))
741                   (expr (cadr var)))
742               (unless (symbolp v)
743                 (error 'simple-type-error
744                        :format-control "The variable ~S is not a symbol."
745                        :format-arguments (list v)))
746               (push (list v (precompile1 expr)) result)
747               (environment-add-symbol-binding *precompile-env* v nil)))
748               ;; any value will do: we just need to shadow any symbol macros
749            (t
750             (push var result)
751             (environment-add-symbol-binding *precompile-env* var nil))))
752    (nreverse result)))
753
754(defun precompile-let (form)
755  (let ((*precompile-env* (make-environment *precompile-env*)))
756    (list* 'LET
757           (precompile-let/let*-vars (cadr form))
758           (mapcar #'precompile1 (cddr form)))))
759
760;; (LET* ((X 1)) (LET* ((Y 2)) (LET* ((Z 3)) (+ X Y Z)))) =>
761;; (LET* ((X 1) (Y 2) (Z 3)) (+ X Y Z))
762(defun maybe-fold-let* (form)
763  (if (and (= (length form) 3)
764           (consp (%caddr form))
765           (eq (%car (%caddr form)) 'LET*))
766      (let ((third (maybe-fold-let* (%caddr form))))
767        (list* 'LET* (append (%cadr form) (cadr third)) (cddr third)))
768      form))
769
770(defun precompile-let* (form)
771  (setf form (maybe-fold-let* form))
772  (let ((*precompile-env* (make-environment *precompile-env*)))
773    (list* 'LET*
774           (precompile-let/let*-vars (cadr form))
775           (mapcar #'precompile1 (cddr form)))))
776
777(defun precompile-case (form)
778  (if *in-jvm-compile*
779      (precompile1 (macroexpand form *precompile-env*))
780      (let* ((keyform (cadr form))
781             (clauses (cddr form))
782             (result (list (precompile1 keyform))))
783        (dolist (clause clauses)
784          (push (precompile-case-clause clause) result))
785        (cons (car form) (nreverse result)))))
786
787(defun precompile-case-clause (clause)
788  (let ((keys (car clause))
789        (forms (cdr clause)))
790    (cons keys (mapcar #'precompile1 forms))))
791
792(defun precompile-cond (form)
793  (if *in-jvm-compile*
794      (precompile1 (macroexpand form *precompile-env*))
795      (let ((clauses (cdr form))
796            (result nil))
797        (dolist (clause clauses)
798          (push (precompile-cond-clause clause) result))
799        (cons 'COND (nreverse result)))))
800
801(defun precompile-cond-clause (clause)
802  (let ((test (car clause))
803        (forms (cdr clause)))
804    (cons (precompile1 test) (mapcar #'precompile1 forms))))
805
806(defun precompile-local-function-def (def)
807  (let ((name (car def))
808        (body (cddr def)))
809    ;; Macro names are shadowed by local functions.
810    (environment-add-function-definition *precompile-env* name body)
811    (cdr (precompile-named-lambda (list* 'NAMED-LAMBDA def)))))
812
813(defun precompile-local-functions (defs)
814  (let ((result nil))
815    (dolist (def defs (nreverse result))
816      (push (precompile-local-function-def def) result))))
817
818(defun find-use (name expression)
819  (cond ((atom expression)
820         nil)
821        ((eq (%car expression) name)
822         t)
823        ((consp name)
824         t) ;; FIXME Recognize use of SETF functions!
825        (t
826         (or (find-use name (%car expression))
827             (find-use name (%cdr expression))))))
828
829(defun precompile-flet/labels (form)
830  (let* ((*precompile-env* (make-environment *precompile-env*))
831         (operator (car form))
832         (locals (cadr form))
833         precompiled-locals
834         applicable-locals
835         body)
836    (when (eq operator 'FLET)
837       ;; FLET functions *don't* shadow within their own FLET form
838       (setf precompiled-locals
839             (precompile-local-functions locals))
840       (setf applicable-locals precompiled-locals))
841    ;; augment the environment with the newly-defined local functions
842    ;; to shadow preexisting macro definitions with the same names
843    (dolist (local locals)
844      ;; we can use the non-precompiled locals, because the function body isn't used
845      (environment-add-function-definition *precompile-env*
846             (car local) (cddr local)))
847    (when (eq operator 'LABELS)
848       ;; LABELS functions *do* shadow within their own LABELS form
849       (setf precompiled-locals
850             (precompile-local-functions locals))
851       (setf applicable-locals precompiled-locals))
852    ;; then precompile (thus macro-expand) the body before inspecting it
853    ;; for the use of our locals and eliminating dead code
854    (setq body (mapcar #'precompile1 (cddr form)))
855    (dolist (local precompiled-locals)
856      (let* ((name (car local))
857             (used-p (find-use name body)))
858        (unless used-p
859          (when (eq operator 'LABELS)
860            (dolist (local precompiled-locals)
861              (when (neq name (car local))
862                (when (find-use name (cddr local))
863                  (setf used-p t)
864                  (return))
865                ;; Scope of defined function names includes
866                ;; &OPTIONAL, &KEY and &AUX parameters
867                ;; (LABELS.7B, LABELS.7C and LABELS.7D).
868                (let ((vars (or
869                             (cdr (memq '&optional (cadr local)))
870                             (cdr (memq '&key (cadr local)))
871                             (cdr (memq '&aux (cadr local))))))
872                  (when (and vars (find-use name vars))
873                    (setf used-p t)
874                    (return)))
875                ))))
876        (unless used-p
877          (format t "; Note: deleting unused local function ~A ~S~%"
878                  operator name)
879          (setf applicable-locals (remove local applicable-locals)))))
880    (if applicable-locals
881        (list* operator applicable-locals body)
882        (list* 'LOCALLY body))))
883
884(defun precompile-function (form)
885  (if (and (consp (cadr form)) (eq (caadr form) 'LAMBDA))
886      (list 'FUNCTION (precompile-lambda (%cadr form)))
887      form))
888
889(defun precompile-if (form)
890  (let ((args (cdr form)))
891    (case (length args)
892      (2
893       (let ((test (precompile1 (%car args))))
894         (cond ((null test)
895                nil)
896               (;;(constantp test)
897                (eq test t)
898                (precompile1 (%cadr args)))
899               (t
900                (list 'IF
901                      test
902                      (precompile1 (%cadr args)))))))
903      (3
904       (let ((test (precompile1 (%car args))))
905         (cond ((null test)
906                (precompile1 (%caddr args)))
907               (;;(constantp test)
908                (eq test t)
909                (precompile1 (%cadr args)))
910               (t
911                (list 'IF
912                      test
913                      (precompile1 (%cadr args))
914                      (precompile1 (%caddr args)))))))
915      (t
916       (error "wrong number of arguments for IF")))))
917
918(defun precompile-when (form)
919  (if *in-jvm-compile*
920      (precompile1 (macroexpand form *precompile-env*))
921      (precompile-cons form)))
922
923(defun precompile-unless (form)
924  (if *in-jvm-compile*
925      (precompile1 (macroexpand form *precompile-env*))
926      (precompile-cons form)))
927
928;; MULTIPLE-VALUE-BIND is handled explicitly by the JVM compiler.
929(defun precompile-multiple-value-bind (form)
930  (let ((vars (cadr form))
931        (values-form (caddr form))
932        (body (cdddr form))
933        (*precompile-env* (make-environment *precompile-env*)))
934    (dolist (var vars)
935      (environment-add-symbol-binding *precompile-env* var nil))
936    (list* 'MULTIPLE-VALUE-BIND
937           vars
938           (precompile1 values-form)
939           (mapcar #'precompile1 body))))
940
941;; MULTIPLE-VALUE-LIST is handled explicitly by the JVM compiler.
942(defun precompile-multiple-value-list (form)
943  (list 'MULTIPLE-VALUE-LIST (precompile1 (cadr form))))
944
945(defun precompile-nth-value (form)
946  (if *in-jvm-compile*
947      (precompile1 (macroexpand form *precompile-env*))
948      form))
949
950(defun precompile-return (form)
951  (if *in-jvm-compile*
952      (precompile1 (macroexpand form *precompile-env*))
953      (list 'RETURN (precompile1 (cadr form)))))
954
955(defun precompile-return-from (form)
956  (list 'RETURN-FROM (cadr form) (precompile1 (caddr form))))
957
958(defun precompile-tagbody (form)
959  (do ((body (cdr form) (cdr body))
960       (result ()))
961      ((null body) (cons 'TAGBODY (nreverse result)))
962    (if (atom (car body))
963        (push (car body) result)
964        (push (let* ((first-form (car body))
965                     (expanded (precompile1 first-form)))
966                (if (and (symbolp expanded)
967                         (neq expanded first-form))
968                    ;; Workaround:
969                    ;;  Since our expansion/compilation order
970                    ;;   is out of sync with the definition of
971                    ;;   TAGBODY (which requires the compiler
972                    ;;   to look for tags before expanding),
973                    ;;   we need to disguise anything which might
974                    ;;   look like a tag. We do this by wrapping
975                    ;;   it in a PROGN form.
976                    (list 'PROGN expanded)
977                    expanded)) result))))
978
979(defun precompile-eval-when (form)
980  (list* 'EVAL-WHEN (cadr form) (mapcar #'precompile1 (cddr form))))
981
982(defun precompile-unwind-protect (form)
983  (list* 'UNWIND-PROTECT
984         (precompile1 (cadr form))
985         (mapcar #'precompile1 (cddr form))))
986
987(declaim (ftype (function (t t) t) precompile-form))
988(defun precompile-form (form in-jvm-compile
989                        &optional precompile-env)
990  (let ((*in-jvm-compile* in-jvm-compile)
991        (*inline-declarations* *inline-declarations*)
992        (pre::*precompile-env* precompile-env))
993    (precompile1 form)))
994
995(defun install-handler (symbol &optional handler)
996  (declare (type symbol symbol))
997  (let ((handler (or handler
998                     (find-symbol (sys::%format nil "PRECOMPILE-~A"
999                                                (symbol-name symbol))
1000                                  'precompiler))))
1001    (unless (and handler (fboundp handler))
1002      (error "No handler for ~S." (let ((*package* (find-package :keyword)))
1003            (format nil "~S" symbol))))
1004    (setf (get symbol 'precompile-handler) handler)))
1005
1006(defun install-handlers ()
1007  (mapcar #'install-handler '(BLOCK
1008                              CASE
1009                              COND
1010                              DOLIST
1011                              DOTIMES
1012                              EVAL-WHEN
1013                              FUNCTION
1014                              IF
1015                              LAMBDA
1016                              MACROLET
1017                              MULTIPLE-VALUE-BIND
1018                              MULTIPLE-VALUE-LIST
1019                              NAMED-LAMBDA
1020                              NTH-VALUE
1021                              PROGN
1022                              PROGV
1023                              PSETF
1024                              PSETQ
1025                              RETURN
1026                              RETURN-FROM
1027                              SETF
1028                              SETQ
1029                              SYMBOL-MACROLET
1030                              TAGBODY
1031                              UNWIND-PROTECT
1032                              UNLESS
1033                              WHEN))
1034
1035  (dolist (pair '((ECASE                precompile-case)
1036
1037                  (AND                  precompile-cons)
1038                  (OR                   precompile-cons)
1039
1040                  (CATCH                precompile-cons)
1041                  (MULTIPLE-VALUE-CALL  precompile-cons)
1042                  (MULTIPLE-VALUE-PROG1 precompile-cons)
1043
1044                  (DO                   precompile-do/do*)
1045                  (DO*                  precompile-do/do*)
1046
1047                  (LET                  precompile-let)
1048                  (LET*                 precompile-let*)
1049
1050                  (LOCALLY              precompile-locally)
1051
1052                  (FLET                 precompile-flet/labels)
1053                  (LABELS               precompile-flet/labels)
1054
1055                  (LOAD-TIME-VALUE      precompile-load-time-value)
1056
1057                  (DECLARE              precompile-identity)
1058                  (DEFUN                precompile-defun)
1059                  (GO                   precompile-identity)
1060                  (QUOTE                precompile-identity)
1061                  (THE                  precompile-the)
1062                  (THROW                precompile-cons)
1063                  (TRULY-THE            precompile-truly-the)
1064
1065                  (THREADS:SYNCHRONIZED-ON
1066                                        precompile-threads-synchronized-on)
1067     
1068      (JVM::WITH-INLINE-CODE precompile-identity)))
1069    (install-handler (first pair) (second pair))))
1070
1071(install-handlers)
1072
1073(export '(precompile-form))
1074
1075(in-package #:ext)
1076
1077(export 'macroexpand-all)
1078
1079(defun macroexpand-all (form &optional env)
1080  (precompiler:precompile-form form t env))
1081
1082(in-package #:lisp)
1083
1084(export '(compiler-let))
1085
1086(defmacro compiler-let (bindings &body forms &environment env)
1087  (let ((bindings (mapcar #'(lambda (binding)
1088                              (if (atom binding) (list binding) binding))
1089                          bindings)))
1090    (progv (mapcar #'car bindings)
1091           (mapcar #'(lambda (binding)
1092                       (eval (cadr binding))) bindings)
1093      (macroexpand-all `(progn ,@forms) env))))
1094
1095(in-package #:system)
1096
1097(defun set-function-definition (name new old)
1098  (let ((*warn-on-redefinition* nil))
1099    (sys::%set-lambda-name new name)
1100    (sys:set-call-count new (sys:call-count old))
1101    (sys::%set-arglist new (sys::arglist old))
1102    (when (macro-function name)
1103      (setf new (make-macro name new)))
1104    (if (typep old 'mop:funcallable-standard-object)
1105        (mop:set-funcallable-instance-function old new)
1106        (setf (fdefinition name) new))))
1107
1108(defun precompile (name &optional definition)
1109  (unless definition
1110    (setq definition (or (and (symbolp name) (macro-function name))
1111                         (fdefinition name))))
1112  (let ((expr definition)
1113        env result
1114        (pre::*precompile-env* nil))
1115    (when (functionp definition)
1116      (multiple-value-bind (form closure-p)
1117          (function-lambda-expression definition)
1118        (unless form
1119          (return-from precompile (values nil t t)))
1120        (setq env closure-p)
1121        (setq expr form)))
1122    (unless (and (consp expr) (eq (car expr) 'lambda))
1123      (format t "Unable to precompile ~S.~%" name)
1124      (return-from precompile (values nil t t)))
1125    (setf result
1126          (sys:make-closure (precompiler:precompile-form expr nil env) env))
1127    (when (and name (functionp result))
1128      (sys::set-function-definition name result definition))
1129    (values (or name result) nil nil)))
1130
1131(defun precompile-package (pkg &key verbose)
1132  (dolist (sym (package-symbols pkg))
1133    (when (fboundp sym)
1134      (unless (special-operator-p sym)
1135        (let ((f (fdefinition sym)))
1136          (unless (compiled-function-p f)
1137            (when verbose
1138              (format t "Precompiling ~S~%" sym)
1139              (finish-output))
1140            (precompile sym))))))
1141  t)
1142
1143(defun %compile (name definition)
1144  (if (and name (fboundp name) (%typep (symbol-function name) 'generic-function))
1145      (values name nil nil)
1146      (precompile name definition)))
1147
1148;; ;; Redefine EVAL to precompile its argument.
1149;; (defun eval (form)
1150;;   (%eval (precompile-form form nil)))
1151
1152;; ;; Redefine DEFMACRO to precompile the expansion function on the fly.
1153;; (defmacro defmacro (name lambda-list &rest body)
1154;;   (let* ((form (gensym "WHOLE-"))
1155;;          (env (gensym "ENVIRONMENT-")))
1156;;     (multiple-value-bind (body decls)
1157;;         (parse-defmacro lambda-list form body name 'defmacro :environment env)
1158;;       (let ((expander `(lambda (,form ,env) ,@decls (block ,name ,body))))
1159;;         `(progn
1160;;            (let ((macro (make-macro ',name
1161;;                                     (or (precompile nil ,expander) ,expander))))
1162;;              ,@(if (special-operator-p name)
1163;;                    `((put ',name 'macroexpand-macro macro))
1164;;                    `((fset ',name macro)))
1165;;              (%set-arglist macro ',lambda-list)
1166;;              ',name))))))
1167
1168;; Make an exception just this one time...
1169(when (get 'defmacro 'macroexpand-macro)
1170  (fset 'defmacro (get 'defmacro 'macroexpand-macro))
1171  (remprop 'defmacro 'macroexpand-macro))
1172
1173(defvar *defined-functions*)
1174
1175(defvar *undefined-functions*)
1176
1177(defun note-name-defined (name)
1178  (when (boundp '*defined-functions*)
1179    (push name *defined-functions*))
1180  (when (and (boundp '*undefined-functions*) (not (null *undefined-functions*)))
1181    (setf *undefined-functions* (remove name *undefined-functions*))))
1182
1183;; Redefine DEFUN to precompile the definition on the fly.
1184(defmacro defun (name lambda-list &body body &environment env)
1185  (note-name-defined name)
1186  (multiple-value-bind (body decls doc)
1187      (parse-body body)
1188    (let* ((block-name (fdefinition-block-name name))
1189           (lambda-expression
1190            `(named-lambda ,name ,lambda-list
1191                           ,@decls
1192                           ,@(when doc `(,doc))
1193                           (block ,block-name ,@body))))
1194      (cond ((and (boundp 'jvm::*file-compilation*)
1195                  ;; when JVM.lisp isn't loaded yet, this variable isn't bound
1196                  ;; meaning that we're not trying to compile to a file:
1197                  ;; Both COMPILE and COMPILE-FILE bind this variable.
1198                  ;; This function is also triggered by MACROEXPAND, though
1199                  jvm::*file-compilation*)
1200             `(progn
1201                (fset ',name ,lambda-expression)
1202                ',name))
1203            (t
1204             (when (and env (empty-environment-p env))
1205               (setf env nil))
1206             (when (null env)
1207               (setf lambda-expression (precompiler:precompile-form lambda-expression nil)))
1208             `(prog1
1209                  (%defun ',name ,lambda-expression)
1210                ,@(when doc
1211                   `((%set-documentation ',name 'function ,doc)))))))))
1212
1213(export '(precompile))
1214
1215;;(provide "PRECOMPILER")
Note: See TracBrowser for help on using the repository browser.