1ea525981c25ec057bc46dd82093c5e52eb1179c
[jscl.git] / src / compiler / compiler.lisp
1 ;;; compiler.lisp ---
2
3 ;; Copyright (C) 2012, 2013 David Vazquez
4 ;; Copyright (C) 2012 Raimon Grau
5
6 ;; JSCL is free software: you can redistribute it and/or
7 ;; modify it under the terms of the GNU General Public License as
8 ;; published by the Free Software Foundation, either version 3 of the
9 ;; License, or (at your option) any later version.
10 ;;
11 ;; JSCL is distributed in the hope that it will be useful, but
12 ;; WITHOUT ANY WARRANTY; without even the implied warranty of
13 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
14 ;; General Public License for more details.
15 ;;
16 ;; You should have received a copy of the GNU General Public License
17 ;; along with JSCL.  If not, see <http://www.gnu.org/licenses/>.
18
19 ;;;; Compiler
20
21 (/debug "loading compiler.lisp!")
22
23 ;;; Translate the Lisp code to Javascript. It will compile the special
24 ;;; forms. Some primitive functions are compiled as special forms
25 ;;; too. The respective real functions are defined in the target (see
26 ;;; the beginning of this file) as well as some primitive functions.
27
28 (define-js-macro selfcall (&body body)
29   `(call (function () ,@body)))
30
31 (define-js-macro bool (expr)
32   `(if ,expr ,(convert t) ,(convert nil)))
33
34 (define-js-macro method-call (x method &rest args)
35   `(call (get ,x ,method) ,@args))
36
37 ;;; A Form can return a multiple values object calling VALUES, like
38 ;;; values(arg1, arg2, ...). It will work in any context, as well as
39 ;;; returning an individual object. However, if the special variable
40 ;;; `*multiple-value-p*' is NIL, is granted that only the primary
41 ;;; value will be used, so we can optimize to avoid the VALUES
42 ;;; function call.
43 (defvar *multiple-value-p* nil)
44
45 ;;; It is bound dinamically to the number of nested calls to
46 ;;; `convert'. Therefore, a form is being compiled as toplevel if it
47 ;;; is zero.
48 (defvar *convert-level* -1)
49
50
51 ;;; Environment
52
53 (def!struct binding
54   name
55   type
56   value
57   declarations)
58
59 (def!struct lexenv
60   variable
61   function
62   block
63   gotag)
64
65 (defun lookup-in-lexenv (name lexenv namespace)
66   (find name (ecase namespace
67                 (variable (lexenv-variable lexenv))
68                 (function (lexenv-function lexenv))
69                 (block    (lexenv-block    lexenv))
70                 (gotag    (lexenv-gotag    lexenv)))
71         :key #'binding-name))
72
73 (defun push-to-lexenv (binding lexenv namespace)
74   (ecase namespace
75     (variable (push binding (lexenv-variable lexenv)))
76     (function (push binding (lexenv-function lexenv)))
77     (block    (push binding (lexenv-block    lexenv)))
78     (gotag    (push binding (lexenv-gotag    lexenv)))))
79
80 (defun extend-lexenv (bindings lexenv namespace)
81   (let ((env (copy-lexenv lexenv)))
82     (dolist (binding (reverse bindings) env)
83       (push-to-lexenv binding env namespace))))
84
85
86 (defvar *environment* (make-lexenv))
87 (defvar *variable-counter* 0)
88
89 (defun gvarname (symbol)
90   (declare (ignore symbol))
91   (incf *variable-counter*)
92   (make-symbol (concat "v" (integer-to-string *variable-counter*))))
93
94 (defun translate-variable (symbol)
95   (awhen (lookup-in-lexenv symbol *environment* 'variable)
96     (binding-value it)))
97
98 (defun extend-local-env (args)
99   (let ((new (copy-lexenv *environment*)))
100     (dolist (symbol args new)
101       (let ((b (make-binding :name symbol :type 'variable :value (gvarname symbol))))
102         (push-to-lexenv b new 'variable)))))
103
104 ;;; Toplevel compilations
105 (defvar *toplevel-compilations* nil)
106
107 (defun toplevel-compilation (string)
108   (push string *toplevel-compilations*))
109
110 (defun get-toplevel-compilations ()
111   (reverse *toplevel-compilations*))
112
113 (defun %compile-defmacro (name lambda)
114   (toplevel-compilation (convert `',name))
115   (let ((binding (make-binding :name name :type 'macro :value lambda)))
116     (push-to-lexenv binding  *environment* 'function))
117   name)
118
119 (defun global-binding (name type namespace)
120   (or (lookup-in-lexenv name *environment* namespace)
121       (let ((b (make-binding :name name :type type :value nil)))
122         (push-to-lexenv b *environment* namespace)
123         b)))
124
125 (defun claimp (symbol namespace claim)
126   (let ((b (lookup-in-lexenv symbol *environment* namespace)))
127     (and b (member claim (binding-declarations b)))))
128
129 (defun !proclaim (decl)
130   (case (car decl)
131     (special
132      (dolist (name (cdr decl))
133        (let ((b (global-binding name 'variable 'variable)))
134          (push 'special (binding-declarations b)))))
135     (notinline
136      (dolist (name (cdr decl))
137        (let ((b (global-binding name 'function 'function)))
138          (push 'notinline (binding-declarations b)))))
139     (constant
140      (dolist (name (cdr decl))
141        (let ((b (global-binding name 'variable 'variable)))
142          (push 'constant (binding-declarations b)))))))
143
144 #+jscl
145 (fset 'proclaim #'!proclaim)
146
147 (defun %define-symbol-macro (name expansion)
148   (let ((b (make-binding :name name :type 'macro :value expansion)))
149     (push-to-lexenv b *environment* 'variable)
150     name))
151
152 #+jscl
153 (defmacro define-symbol-macro (name expansion)
154   `(%define-symbol-macro ',name ',expansion))
155
156
157 ;;; Special forms
158
159 (defvar *compilations* nil)
160
161 (defmacro define-compilation (name args &body body)
162   ;; Creates a new primitive `name' with parameters args and
163   ;; @body. The body can access to the local environment through the
164   ;; variable *ENVIRONMENT*.
165   `(push (list ',name (lambda ,args (block ,name ,@body)))
166          *compilations*))
167
168 (define-compilation if (condition true &optional false)
169   `(if (!== ,(convert condition) ,(convert nil))
170        ,(convert true *multiple-value-p*)
171        ,(convert false *multiple-value-p*)))
172
173 (defvar *ll-keywords* '(&optional &rest &key))
174
175 (defun list-until-keyword (list)
176   (if (or (null list) (member (car list) *ll-keywords*))
177       nil
178       (cons (car list) (list-until-keyword (cdr list)))))
179
180 (defun ll-section (keyword ll)
181   (list-until-keyword (cdr (member keyword ll))))
182
183 (defun ll-required-arguments (ll)
184   (list-until-keyword ll))
185
186 (defun ll-optional-arguments-canonical (ll)
187   (mapcar #'ensure-list (ll-section '&optional ll)))
188
189 (defun ll-optional-arguments (ll)
190   (mapcar #'car (ll-optional-arguments-canonical ll)))
191
192 (defun ll-rest-argument (ll)
193   (let ((rest (ll-section '&rest ll)))
194     (when (cdr rest)
195       (error "Bad lambda-list `~S'." ll))
196     (car rest)))
197
198 (defun ll-keyword-arguments-canonical (ll)
199   (flet ((canonicalize (keyarg)
200            ;; Build a canonical keyword argument descriptor, filling
201            ;; the optional fields. The result is a list of the form
202            ;; ((keyword-name var) init-form svar).
203            (let ((arg (ensure-list keyarg)))
204              (cons (if (listp (car arg))
205                        (car arg)
206                        (list (intern (symbol-name (car arg)) "KEYWORD") (car arg)))
207                    (cdr arg)))))
208     (mapcar #'canonicalize (ll-section '&key ll))))
209
210 (defun ll-keyword-arguments (ll)
211   (mapcar (lambda (keyarg) (second (first keyarg)))
212           (ll-keyword-arguments-canonical ll)))
213
214 (defun ll-svars (lambda-list)
215   (let ((args
216          (append
217           (ll-keyword-arguments-canonical lambda-list)
218           (ll-optional-arguments-canonical lambda-list))))
219     (remove nil (mapcar #'third args))))
220
221 (defun lambda-name/docstring-wrapper (name docstring code)
222   (if (or name docstring)
223       `(selfcall
224         (var (func ,code))
225         ,(when name `(= (get func "fname") ,name))
226         ,(when docstring `(= (get func "docstring") ,docstring))
227         (return func))
228       code))
229
230 (defun lambda-check-argument-count
231     (n-required-arguments n-optional-arguments rest-p)
232   ;; Note: Remember that we assume that the number of arguments of a
233   ;; call is at least 1 (the values argument).
234   (let ((min n-required-arguments)
235         (max (if rest-p 'n/a (+ n-required-arguments n-optional-arguments))))
236     (block nil
237       ;; Special case: a positive exact number of arguments.
238       (when (and (< 0 min) (eql min max))
239         (return `(call |checkArgs| |nargs| ,min)))
240       ;; General case:
241       `(progn
242          ,(when (< 0 min)     `(call |checkArgsAtLeast| |nargs| ,min))
243          ,(when (numberp max) `(call |checkArgsAtMost|  |nargs| ,max))))))
244
245 (defun compile-lambda-optional (ll)
246   (let* ((optional-arguments (ll-optional-arguments-canonical ll))
247          (n-required-arguments (length (ll-required-arguments ll)))
248          (n-optional-arguments (length optional-arguments)))
249     (when optional-arguments
250       `(switch |nargs|
251                ,@(with-collect
252                   (dotimes (idx n-optional-arguments)
253                     (let ((arg (nth idx optional-arguments)))
254                       (collect `(case ,(+ idx n-required-arguments)))
255                       (collect `(= ,(translate-variable (car arg))
256                                    ,(convert (cadr arg))))
257                       (collect (when (third arg)
258                                  `(= ,(translate-variable (third arg))
259                                      ,(convert nil))))))
260                   (collect 'default)
261                   (collect '(break)))))))
262
263 (defun compile-lambda-rest (ll)
264   (let ((n-required-arguments (length (ll-required-arguments ll)))
265         (n-optional-arguments (length (ll-optional-arguments ll)))
266         (rest-argument (ll-rest-argument ll)))
267     (when rest-argument
268       (let ((js!rest (translate-variable rest-argument)))
269         `(progn
270            (var (,js!rest ,(convert nil)))
271            (var i)
272            (for ((= i (- |nargs| 1))
273                  (>= i ,(+ n-required-arguments n-optional-arguments))
274                  (post-- i))
275                 (= ,js!rest (object "car" (property |arguments| (+ i 2))
276                                     "cdr" ,js!rest))))))))
277
278 (defun compile-lambda-parse-keywords (ll)
279   (let ((n-required-arguments
280          (length (ll-required-arguments ll)))
281         (n-optional-arguments
282          (length (ll-optional-arguments ll)))
283         (keyword-arguments
284          (ll-keyword-arguments-canonical ll)))
285     `(progn
286        ;; Declare variables
287        ,@(with-collect
288           (dolist (keyword-argument keyword-arguments)
289             (destructuring-bind ((keyword-name var) &optional initform svar)
290                 keyword-argument
291               (declare (ignore keyword-name initform))
292               (collect `(var ,(translate-variable var)))
293               (when svar
294                 (collect
295                     `(var (,(translate-variable svar)
296                             ,(convert nil))))))))
297
298        ;; Parse keywords
299        ,(flet ((parse-keyword (keyarg)
300                 (destructuring-bind ((keyword-name var) &optional initform svar) keyarg
301                   ;; ((keyword-name var) init-form svar)
302                   `(progn
303                      (for ((= i ,(+ n-required-arguments n-optional-arguments))
304                            (< i |nargs|)
305                            (+= i 2))
306                           ;; ....
307                           (if (=== (property |arguments| (+ i 2))
308                                    ,(convert keyword-name))
309                               (progn
310                                 (= ,(translate-variable var)
311                                    (property |arguments| (+ i 3)))
312                                 ,(when svar `(= ,(translate-variable svar)
313                                                 ,(convert t)))
314                                 (break))))
315                      (if (== i |nargs|)
316                          (= ,(translate-variable var) ,(convert initform)))))))
317          (when keyword-arguments
318            `(progn
319               (var i)
320               ,@(mapcar #'parse-keyword keyword-arguments))))
321
322        ;; Check for unknown keywords
323        ,(when keyword-arguments
324          `(progn
325             (var (start ,(+ n-required-arguments n-optional-arguments)))
326             (if (== (% (- |nargs| start) 2) 1)
327                 (throw "Odd number of keyword arguments."))
328             (for ((= i start) (< i |nargs|) (+= i 2))
329                  (if (and ,@(mapcar (lambda (keyword-argument)
330                                  (destructuring-bind ((keyword-name var) &optional initform svar)
331                                      keyword-argument
332                                    (declare (ignore var initform svar))
333                                    `(!== (property |arguments| (+ i 2)) ,(convert keyword-name))))
334                                keyword-arguments))
335                      (throw (+ "Unknown keyword argument "
336                                (call |xstring|
337                                      (property
338                                       (property |arguments| (+ i 2))
339                                       "name")))))))))))
340
341 (defun parse-lambda-list (ll)
342   (values (ll-required-arguments ll)
343           (ll-optional-arguments ll)
344           (ll-keyword-arguments  ll)
345           (ll-rest-argument      ll)))
346
347 ;;; Process BODY for declarations and/or docstrings. Return as
348 ;;; multiple values the BODY without docstrings or declarations, the
349 ;;; list of declaration forms and the docstring.
350 (defun parse-body (body &key declarations docstring)
351   (let ((value-declarations)
352         (value-docstring))
353     ;; Parse declarations
354     (when declarations
355       (do* ((rest body (cdr rest))
356             (form (car rest) (car rest)))
357            ((or (atom form) (not (eq (car form) 'declare)))
358             (setf body rest))
359         (push form value-declarations)))
360     ;; Parse docstring
361     (when (and docstring
362                (stringp (car body))
363                (not (null (cdr body))))
364       (setq value-docstring (car body))
365       (setq body (cdr body)))
366     (values body value-declarations value-docstring)))
367
368 ;;; Compile a lambda function with lambda list LL and body BODY. If
369 ;;; NAME is given, it should be a constant string and it will become
370 ;;; the name of the function. If BLOCK is non-NIL, a named block is
371 ;;; created around the body. NOTE: No block (even anonymous) is
372 ;;; created if BLOCk is NIL.
373 (defun compile-lambda (ll body &key name block)
374   (multiple-value-bind (required-arguments
375                         optional-arguments
376                         keyword-arguments
377                         rest-argument)
378       (parse-lambda-list ll)
379     (multiple-value-bind (body decls documentation)
380         (parse-body body :declarations t :docstring t)
381       (declare (ignore decls))
382       (let ((n-required-arguments (length required-arguments))
383             (n-optional-arguments (length optional-arguments))
384             (*environment* (extend-local-env
385                             (append (ensure-list rest-argument)
386                                     required-arguments
387                                     optional-arguments
388                                     keyword-arguments
389                                     (ll-svars ll)))))
390         (lambda-name/docstring-wrapper name documentation
391          `(function (|values| |nargs| ,@(mapcar (lambda (x)
392                                                   (translate-variable x))
393                                                 (append required-arguments optional-arguments)))
394                      ;; Check number of arguments
395                     ,(lambda-check-argument-count n-required-arguments
396                                                   n-optional-arguments
397                                                   (or rest-argument keyword-arguments))
398                     ,(compile-lambda-optional ll)
399                     ,(compile-lambda-rest ll)
400                     ,(compile-lambda-parse-keywords ll)
401
402                     ,(let ((*multiple-value-p* t))
403                           (if block
404                               (convert-block `((block ,block ,@body)) t)
405                               (convert-block body t)))))))))
406
407
408 (defun setq-pair (var val)
409   (let ((b (lookup-in-lexenv var *environment* 'variable)))
410     (cond
411       ((and b
412             (eq (binding-type b) 'variable)
413             (not (member 'special (binding-declarations b)))
414             (not (member 'constant (binding-declarations b))))
415        `(= ,(binding-value b) ,(convert val)))
416       ((and b (eq (binding-type b) 'macro))
417        (convert `(setf ,var ,val)))
418       (t
419        (convert `(set ',var ,val))))))
420
421
422 (define-compilation setq (&rest pairs)
423   (let ((result nil))
424     (when (null pairs)
425       (return-from setq (convert nil)))
426     (while t
427       (cond
428         ((null pairs)
429          (return))
430         ((null (cdr pairs))
431          (error "Odd pairs in SETQ"))
432         (t
433          (push `,(setq-pair (car pairs) (cadr pairs)) result)
434          (setq pairs (cddr pairs)))))
435     `(progn ,@(reverse result))))
436
437
438 ;;; Compilation of literals an object dumping
439
440 ;;; BOOTSTRAP MAGIC: We record the macro definitions as lists during
441 ;;; the bootstrap. Once everything is compiled, we want to dump the
442 ;;; whole global environment to the output file to reproduce it in the
443 ;;; run-time. However, the environment must contain expander functions
444 ;;; rather than lists. We do not know how to dump function objects
445 ;;; itself, so we mark the list definitions with this object and the
446 ;;; compiler will be called when this object has to be dumped.
447 ;;; Backquote/unquote does a similar magic, but this use is exclusive.
448 ;;;
449 ;;; Indeed, perhaps to compile the object other macros need to be
450 ;;; evaluated. For this reason we define a valid macro-function for
451 ;;; this symbol.
452 (defvar *magic-unquote-marker* (gensym "MAGIC-UNQUOTE"))
453
454 #-jscl
455 (setf (macro-function *magic-unquote-marker*)
456       (lambda (form &optional environment)
457         (declare (ignore environment))
458         (second form)))
459
460 (defvar *literal-table* nil)
461 (defvar *literal-counter* 0)
462
463 (defun genlit ()
464   (incf *literal-counter*)
465   (make-symbol (concat "l" (integer-to-string *literal-counter*))))
466
467 (defun dump-symbol (symbol)
468   #-jscl
469   (let ((package (symbol-package symbol)))
470     (if (eq package (find-package "KEYWORD"))
471         `(new (call |Symbol| ,(dump-string (symbol-name symbol)) ,(dump-string (package-name package))))
472         `(new (call |Symbol| ,(dump-string (symbol-name symbol))))))
473   #+jscl
474   (let ((package (symbol-package symbol)))
475     (if (null package)
476         `(new (call |Symbol| ,(dump-string (symbol-name symbol))))
477         (convert `(intern ,(symbol-name symbol) ,(package-name package))))))
478
479 (defun dump-cons (cons)
480   (let ((head (butlast cons))
481         (tail (last cons)))
482     `(call |QIList|
483            ,@(mapcar (lambda (x) (literal x t)) head)
484            ,(literal (car tail) t)
485            ,(literal (cdr tail) t))))
486
487 (defun dump-array (array)
488   (let ((elements (vector-to-list array)))
489     (list-to-vector (mapcar #'literal elements))))
490
491 (defun dump-string (string)
492   `(call |make_lisp_string| ,string))
493
494 (defun literal (sexp &optional recursive)
495   (cond
496     ((integerp sexp) sexp)
497     ((floatp sexp) sexp)
498     ((characterp sexp) (string sexp))
499     (t
500      (or (cdr (assoc sexp *literal-table* :test #'eql))
501          (let ((dumped (typecase sexp
502                          (symbol (dump-symbol sexp))
503                          (string (dump-string sexp))
504                          (cons
505                           ;; BOOTSTRAP MAGIC: See the root file
506                           ;; jscl.lisp and the function
507                           ;; `dump-global-environment' for futher
508                           ;; information.
509                           (if (eq (car sexp) *magic-unquote-marker*)
510                               (convert (second sexp))
511                               (dump-cons sexp)))
512                          (array (dump-array sexp)))))
513            (if (and recursive (not (symbolp sexp)))
514                dumped
515                (let ((jsvar (genlit)))
516                  (push (cons sexp jsvar) *literal-table*)
517                  (toplevel-compilation `(var (,jsvar ,dumped)))
518                  (when (keywordp sexp)
519                    (toplevel-compilation `(= (get ,jsvar "value") ,jsvar)))
520                  jsvar)))))))
521
522
523 (define-compilation quote (sexp)
524   (literal sexp))
525
526 (define-compilation %while (pred &rest body)
527   `(selfcall
528     (while (!== ,(convert pred) ,(convert nil))
529       ,(convert-block body))
530     (return ,(convert nil))))
531
532 (define-compilation function (x)
533   (cond
534     ((and (listp x) (eq (car x) 'lambda))
535      (compile-lambda (cadr x) (cddr x)))
536     ((and (listp x) (eq (car x) 'named-lambda))
537      (destructuring-bind (name ll &rest body) (cdr x)
538        (compile-lambda ll body
539                        :name (symbol-name name)
540                        :block name)))
541     ((symbolp x)
542      (let ((b (lookup-in-lexenv x *environment* 'function)))
543        (if b
544            (binding-value b)
545            (convert `(symbol-function ',x)))))))
546
547 (defun make-function-binding (fname)
548   (make-binding :name fname :type 'function :value (gvarname fname)))
549
550 (defun compile-function-definition (list)
551   (compile-lambda (car list) (cdr list)))
552
553 (defun translate-function (name)
554   (let ((b (lookup-in-lexenv name *environment* 'function)))
555     (and b (binding-value b))))
556
557 (define-compilation flet (definitions &rest body)
558   (let* ((fnames (mapcar #'car definitions))
559          (cfuncs (mapcar (lambda (def)
560                            (compile-lambda (cadr def)
561                                            `((block ,(car def)
562                                                ,@(cddr def)))))
563                          definitions))
564          (*environment*
565           (extend-lexenv (mapcar #'make-function-binding fnames)
566                          *environment*
567                          'function)))
568     `(call (function ,(mapcar #'translate-function fnames)
569                 ,(convert-block body t))
570            ,@cfuncs)))
571
572 (define-compilation labels (definitions &rest body)
573   (let* ((fnames (mapcar #'car definitions))
574          (*environment*
575           (extend-lexenv (mapcar #'make-function-binding fnames)
576                          *environment*
577                          'function)))
578     `(selfcall
579       ,@(mapcar (lambda (func)
580                   `(var (,(translate-function (car func))
581                           ,(compile-lambda (cadr func)
582                                            `((block ,(car func) ,@(cddr func)))))))
583                 definitions)
584       ,(convert-block body t))))
585
586
587 ;;; Was the compiler invoked from !compile-file?
588 (defvar *compiling-file* nil)
589
590 ;;; NOTE: It is probably wrong in many cases but we will not use this
591 ;;; heavily. Please, do not rely on wrong cases of this
592 ;;; implementation.
593 (define-compilation eval-when (situations &rest body)
594   ;; TODO: Error checking
595   (cond
596     ;; Toplevel form compiled by !compile-file.
597     ((and *compiling-file* (zerop *convert-level*))
598      ;; If the situation `compile-toplevel' is given. The form is
599      ;; evaluated at compilation-time.
600      (when (find :compile-toplevel situations)
601        (eval (cons 'progn body)))
602      ;; `load-toplevel' is given, then just compile the subforms as usual.
603      (when (find :load-toplevel situations)
604        (convert-toplevel `(progn ,@body) *multiple-value-p*)))
605     ((find :execute situations)
606      (convert `(progn ,@body) *multiple-value-p*))
607     (t
608      (convert nil))))
609
610 (defmacro define-transformation (name args form)
611   `(define-compilation ,name ,args
612      (convert ,form)))
613
614 (define-compilation progn (&rest body)
615   (if (null (cdr body))
616       (convert (car body) *multiple-value-p*)
617       `(progn
618          ,@(append (mapcar #'convert (butlast body))
619                    (list (convert (car (last body)) t))))))
620
621 (define-compilation macrolet (definitions &rest body)
622   (let ((*environment* (copy-lexenv *environment*)))
623     (dolist (def definitions)
624       (destructuring-bind (name lambda-list &body body) def
625         (let ((binding (make-binding :name name :type 'macro :value
626                                      (let ((g!form (gensym)))
627                                        `(lambda (,g!form)
628                                           (destructuring-bind ,lambda-list ,g!form
629                                             ,@body))))))
630           (push-to-lexenv binding  *environment* 'function))))
631     (convert `(progn ,@body) *multiple-value-p*)))
632
633
634 (defun special-variable-p (x)
635   (and (claimp x 'variable 'special) t))
636
637 ;;; Wrap CODE to restore the symbol values of the dynamic
638 ;;; bindings. BINDINGS is a list of pairs of the form
639 ;;; (SYMBOL . PLACE),  where PLACE is a Javascript variable
640 ;;; name to initialize the symbol value and where to stored
641 ;;; the old value.
642 (defun let-binding-wrapper (bindings body)
643   (when (null bindings)
644     (return-from let-binding-wrapper body))
645   `(progn
646      (try (var tmp)
647           ,@(with-collect
648              (dolist (b bindings)
649                (let ((s (convert `',(car b))))
650                  (collect `(= tmp (get ,s "value")))
651                  (collect `(= (get ,s "value") ,(cdr b)))
652                  (collect `(= ,(cdr b) tmp)))))
653           ,body)
654      (finally
655       ,@(with-collect
656          (dolist (b bindings)
657            (let ((s (convert `(quote ,(car b)))))
658              (collect `(= (get ,s "value") ,(cdr b)))))))))
659
660 (define-compilation let (bindings &rest body)
661   (let* ((bindings (mapcar #'ensure-list bindings))
662          (variables (mapcar #'first bindings))
663          (cvalues (mapcar #'convert (mapcar #'second bindings)))
664          (*environment* (extend-local-env (remove-if #'special-variable-p variables)))
665          (dynamic-bindings))
666     `(call (function ,(mapcar (lambda (x)
667                                 (if (special-variable-p x)
668                                     (let ((v (gvarname x)))
669                                       (push (cons x v) dynamic-bindings)
670                                       v)
671                                     (translate-variable x)))
672                               variables)
673                      ,(let ((body (convert-block body t t)))
674                            `,(let-binding-wrapper dynamic-bindings body)))
675            ,@cvalues)))
676
677
678 ;;; Return the code to initialize BINDING, and push it extending the
679 ;;; current lexical environment if the variable is not special.
680 (defun let*-initialize-value (binding)
681   (let ((var (first binding))
682         (value (second binding)))
683     (if (special-variable-p var)
684         (convert `(setq ,var ,value))
685         (let* ((v (gvarname var))
686                (b (make-binding :name var :type 'variable :value v)))
687           (prog1 `(var (,v ,(convert value)))
688             (push-to-lexenv b *environment* 'variable))))))
689
690 ;;; Wrap BODY to restore the symbol values of SYMBOLS after body. It
691 ;;; DOES NOT generate code to initialize the value of the symbols,
692 ;;; unlike let-binding-wrapper.
693 (defun let*-binding-wrapper (symbols body)
694   (when (null symbols)
695     (return-from let*-binding-wrapper body))
696   (let ((store (mapcar (lambda (s) (cons s (gvarname s)))
697                        (remove-if-not #'special-variable-p symbols))))
698     `(progn
699        (try
700         ,@(mapcar (lambda (b)
701                     (let ((s (convert `(quote ,(car b)))))
702                       `(var (,(cdr b) (get ,s "value")))))
703                   store)
704         ,body)
705        (finally
706         ,@(mapcar (lambda (b)
707                     (let ((s (convert `(quote ,(car b)))))
708                       `(= (get ,s "value") ,(cdr b))))
709                   store)))))
710
711 (define-compilation let* (bindings &rest body)
712   (let ((bindings (mapcar #'ensure-list bindings))
713         (*environment* (copy-lexenv *environment*)))
714     (let ((specials (remove-if-not #'special-variable-p (mapcar #'first bindings)))
715           (body `(progn
716                    ,@(mapcar #'let*-initialize-value bindings)
717                    ,(convert-block body t t))))
718       `(selfcall ,(let*-binding-wrapper specials body)))))
719
720
721 (define-compilation block (name &rest body)
722   ;; We use Javascript exceptions to implement non local control
723   ;; transfer. Exceptions has dynamic scoping, so we use a uniquely
724   ;; generated object to identify the block. The instance of a empty
725   ;; array is used to distinguish between nested dynamic Javascript
726   ;; exceptions. See https://github.com/davazp/jscl/issues/64 for
727   ;; futher details.
728   (let* ((idvar (gvarname name))
729          (b (make-binding :name name :type 'block :value idvar)))
730     (when *multiple-value-p*
731       (push 'multiple-value (binding-declarations b)))
732     (let* ((*environment* (extend-lexenv (list b) *environment* 'block))
733            (cbody (convert-block body t)))
734       (if (member 'used (binding-declarations b))
735           `(selfcall
736             (try
737              (var (,idvar #()))
738              ,cbody)
739             (catch (cf)
740               (if (and (== (get cf "type") "block")
741                        (== (get cf "id") ,idvar))
742                   ,(if *multiple-value-p*
743                        `(return (method-call |values| "apply" this (call |forcemv| (get cf "values"))))
744                        `(return (get cf "values")))
745                   (throw cf))))
746           `(selfcall ,cbody)))))
747
748 (define-compilation return-from (name &optional value)
749   (let* ((b (lookup-in-lexenv name *environment* 'block))
750          (multiple-value-p (member 'multiple-value (binding-declarations b))))
751     (when (null b)
752       (error "Return from unknown block `~S'." (symbol-name name)))
753     (push 'used (binding-declarations b))
754     ;; The binding value is the name of a variable, whose value is the
755     ;; unique identifier of the block as exception. We can't use the
756     ;; variable name itself, because it could not to be unique, so we
757     ;; capture it in a closure.
758     `(selfcall
759       ,(when multiple-value-p `(var (|values| |mv|)))
760       (throw
761           (object
762            "type" "block"
763            "id" ,(binding-value b)
764            "values" ,(convert value multiple-value-p)
765            "message" ,(concat "Return from unknown block '" (symbol-name name) "'."))))))
766
767 (define-compilation catch (id &rest body)
768   `(selfcall
769     (var (id ,(convert id)))
770     (try
771      ,(convert-block body t))
772     (catch (|cf|)
773       (if (and (== (get |cf| "type") "catch")
774                (== (get |cf| "id") id))
775           ,(if *multiple-value-p*
776                `(return (method-call |values| "apply" this (call |forcemv| (get |cf| "values"))))
777                `(return (method-call |pv|     "apply" this (call |forcemv| (get |cf| "values")))))
778           (throw |cf|)))))
779
780 (define-compilation throw (id value)
781   `(selfcall
782     (var (|values| |mv|))
783     (throw (object
784             "type" "catch"
785             "id" ,(convert id)
786             "values" ,(convert value t)
787             "message" "Throw uncatched."))))
788
789 (defun go-tag-p (x)
790   (or (integerp x) (symbolp x)))
791
792 (defun declare-tagbody-tags (tbidx body)
793   (let* ((go-tag-counter 0)
794          (bindings
795           (mapcar (lambda (label)
796                     (let ((tagidx (incf go-tag-counter)))
797                       (make-binding :name label :type 'gotag :value (list tbidx tagidx))))
798                   (remove-if-not #'go-tag-p body))))
799     (extend-lexenv bindings *environment* 'gotag)))
800
801 (define-compilation tagbody (&rest body)
802   ;; Ignore the tagbody if it does not contain any go-tag. We do this
803   ;; because 1) it is easy and 2) many built-in forms expand to a
804   ;; implicit tagbody, so we save some space.
805   (unless (some #'go-tag-p body)
806     (return-from tagbody (convert `(progn ,@body nil))))
807   ;; The translation assumes the first form in BODY is a label
808   (unless (go-tag-p (car body))
809     (push (gensym "START") body))
810   ;; Tagbody compilation
811   (let ((branch (gvarname 'branch))
812         (tbidx (gvarname 'tbidx)))
813     (let ((*environment* (declare-tagbody-tags tbidx body))
814           initag)
815       (let ((b (lookup-in-lexenv (first body) *environment* 'gotag)))
816         (setq initag (second (binding-value b))))
817       `(selfcall
818         ;; TAGBODY branch to take
819         (var (,branch ,initag))
820         (var (,tbidx #()))
821         (label tbloop
822                (while true
823                  (try
824                   (switch ,branch
825                           ,@(with-collect
826                              (collect `(case ,initag))
827                              (dolist (form (cdr body))
828                                (if (go-tag-p form)
829                                    (let ((b (lookup-in-lexenv form *environment* 'gotag)))
830                                      (collect `(case ,(second (binding-value b)))))
831                                    (collect (convert form)))))
832                           default
833                           (break tbloop)))
834                  (catch (jump)
835                    (if (and (== (get jump "type") "tagbody")
836                             (== (get jump "id") ,tbidx))
837                        (= ,branch (get jump "label"))
838                        (throw jump)))))
839         (return ,(convert nil))))))
840
841 (define-compilation go (label)
842   (let ((b (lookup-in-lexenv label *environment* 'gotag))
843         (n (cond
844              ((symbolp label) (symbol-name label))
845              ((integerp label) (integer-to-string label)))))
846     (when (null b)
847       (error "Unknown tag `~S'" label))
848     `(selfcall
849       (throw
850           (object
851            "type" "tagbody"
852            "id" ,(first (binding-value b))
853            "label" ,(second (binding-value b))
854            "message" ,(concat "Attempt to GO to non-existing tag " n))))))
855
856 (define-compilation unwind-protect (form &rest clean-up)
857   `(selfcall
858     (var (ret ,(convert nil)))
859     (try
860      (= ret ,(convert form)))
861     (finally
862      ,(convert-block clean-up))
863     (return ret)))
864
865 (define-compilation multiple-value-call (func-form &rest forms)
866   `(selfcall
867     (var (func ,(convert func-form)))
868     (var (args ,(vector (if *multiple-value-p* '|values| '|pv|) 0)))
869     (return
870       (selfcall
871        (var (|values| |mv|))
872        (var vs)
873        (progn
874          ,@(with-collect
875             (dolist (form forms)
876               (collect `(= vs ,(convert form t)))
877               (collect `(if (and (=== (typeof vs) "object")
878                                  (in "multiple-value" vs))
879                             (= args (method-call args "concat" vs))
880                             (method-call args "push" vs))))))
881        (= (property args 1) (- (property args "length") 2))
882        (return (method-call func "apply" |window| args))))))
883
884 (define-compilation multiple-value-prog1 (first-form &rest forms)
885   `(selfcall
886     (var (args ,(convert first-form *multiple-value-p*)))
887     (progn ,@(mapcar #'convert forms))
888     (return args)))
889
890 (define-transformation backquote (form)
891   (bq-completely-process form))
892
893
894 ;;; Primitives
895
896 (defvar *builtins* nil)
897
898 (defmacro define-raw-builtin (name args &body body)
899   ;; Creates a new primitive function `name' with parameters args and
900   ;; @body. The body can access to the local environment through the
901   ;; variable *ENVIRONMENT*.
902   `(push (list ',name (lambda ,args (block ,name ,@body)))
903          *builtins*))
904
905 (defmacro define-builtin (name args &body body)
906   `(define-raw-builtin ,name ,args
907      (let ,(mapcar (lambda (arg) `(,arg (convert ,arg))) args)
908        ,@body)))
909
910 ;;; VARIABLE-ARITY compiles variable arity operations. ARGS stands for
911 ;;; a variable which holds a list of forms. It will compile them and
912 ;;; store the result in some Javascript variables. BODY is evaluated
913 ;;; with ARGS bound to the list of these variables to generate the
914 ;;; code which performs the transformation on these variables.
915 (defun variable-arity-call (args function)
916   (unless (consp args)
917     (error "ARGS must be a non-empty list"))
918   (let ((counter 0)
919         (fargs '())
920         (prelude '()))
921     (dolist (x args)
922       (if (or (floatp x) (numberp x))
923           (push x fargs)
924           (let ((v (make-symbol (concat "x" (integer-to-string (incf counter))))))
925             (push v fargs)
926             (push `(var (,v ,(convert x)))
927                   prelude)
928             (push `(if (!= (typeof ,v) "number")
929                        (throw "Not a number!"))
930                   prelude))))
931     `(selfcall
932       (progn ,@(reverse prelude))
933       ,(funcall function (reverse fargs)))))
934
935
936 (defmacro variable-arity (args &body body)
937   (unless (symbolp args)
938     (error "`~S' is not a symbol." args))
939   `(variable-arity-call ,args (lambda (,args) `(return  ,,@body))))
940
941 (define-raw-builtin + (&rest numbers)
942   (if (null numbers)
943       0
944       (variable-arity numbers
945         `(+ ,@numbers))))
946
947 (define-raw-builtin - (x &rest others)
948   (let ((args (cons x others)))
949     (variable-arity args `(- ,@args))))
950
951 (define-raw-builtin * (&rest numbers)
952   (if (null numbers)
953       1
954       (variable-arity numbers `(* ,@numbers))))
955
956 (define-raw-builtin / (x &rest others)
957   (let ((args (cons x others)))
958     (variable-arity args
959       (if (null others)
960           `(/ 1 ,(car args))
961           (reduce (lambda (x y) `(/ ,x ,y))
962                   args)))))
963
964 (define-builtin mod (x y)
965   `(% ,x ,y))
966
967
968 (defun comparison-conjuntion (vars op)
969   (cond
970     ((null (cdr vars))
971      'true)
972     ((null (cddr vars))
973      `(,op ,(car vars) ,(cadr vars)))
974     (t
975      `(and (,op ,(car vars) ,(cadr vars))
976            ,(comparison-conjuntion (cdr vars) op)))))
977
978 (defmacro define-builtin-comparison (op sym)
979   `(define-raw-builtin ,op (x &rest args)
980      (let ((args (cons x args)))
981        (variable-arity args
982          `(bool ,(comparison-conjuntion args ',sym))))))
983
984 (define-builtin-comparison > >)
985 (define-builtin-comparison < <)
986 (define-builtin-comparison >= >=)
987 (define-builtin-comparison <= <=)
988 (define-builtin-comparison = ==)
989 (define-builtin-comparison /= !=)
990
991 (define-builtin numberp (x)
992   `(bool (== (typeof ,x) "number")))
993
994 (define-builtin floor (x)
995   `(method-call |Math| "floor" ,x))
996
997 (define-builtin expt (x y)
998   `(method-call |Math| "pow" ,x ,y))
999
1000 (define-builtin float-to-string (x)
1001   `(call |make_lisp_string| (method-call ,x |toString|)))
1002
1003 (define-builtin cons (x y)
1004   `(object "car" ,x "cdr" ,y))
1005
1006 (define-builtin consp (x)
1007   `(selfcall
1008     (var (tmp ,x))
1009     (return (bool (and (== (typeof tmp) "object")
1010                        (in "car" tmp))))))
1011
1012 (define-builtin car (x)
1013   `(selfcall
1014     (var (tmp ,x))
1015     (return (if (=== tmp ,(convert nil))
1016                 ,(convert nil)
1017                 (get tmp "car")))))
1018
1019 (define-builtin cdr (x)
1020   `(selfcall
1021     (var (tmp ,x))
1022     (return (if (=== tmp ,(convert nil))
1023                 ,(convert nil)
1024                 (get tmp "cdr")))))
1025
1026 (define-builtin rplaca (x new)
1027   `(selfcall
1028      (var (tmp ,x))
1029      (= (get tmp "car") ,new)
1030      (return tmp)))
1031
1032 (define-builtin rplacd (x new)
1033   `(selfcall
1034      (var (tmp ,x))
1035      (= (get tmp "cdr") ,new)
1036      (return tmp)))
1037
1038 (define-builtin symbolp (x)
1039   `(bool (instanceof ,x |Symbol|)))
1040
1041 (define-builtin make-symbol (name)
1042   `(new (call |Symbol| ,name)))
1043
1044 (define-builtin symbol-name (x)
1045   `(get ,x "name"))
1046
1047 (define-builtin set (symbol value)
1048   `(= (get ,symbol "value") ,value))
1049
1050 (define-builtin fset (symbol value)
1051   `(= (get ,symbol "fvalue") ,value))
1052
1053 (define-builtin boundp (x)
1054   `(bool (!== (get ,x "value") undefined)))
1055
1056 (define-builtin fboundp (x)
1057   `(bool (!== (get ,x "fvalue") undefined)))
1058
1059 (define-builtin symbol-value (x)
1060   `(selfcall
1061     (var (symbol ,x)
1062          (value (get symbol "value")))
1063     (if (=== value undefined)
1064         (throw (+ "Variable `" (call |xstring| (get symbol "name")) "' is unbound.")))
1065     (return value)))
1066
1067 (define-builtin symbol-function (x)
1068   `(selfcall
1069     (var (symbol ,x)
1070          (func (get symbol "fvalue")))
1071     (if (=== func undefined)
1072         (throw (+ "Function `" (call |xstring| (get symbol "name")) "' is undefined.")))
1073     (return func)))
1074
1075 (define-builtin symbol-plist (x)
1076   `(or (get ,x "plist") ,(convert nil)))
1077
1078 (define-builtin lambda-code (x)
1079   `(call |make_lisp_string| (method-call ,x "toString")))
1080
1081 (define-builtin eq (x y)
1082   `(bool (=== ,x ,y)))
1083
1084 (define-builtin char-code (x)
1085   `(call |char_to_codepoint| ,x))
1086
1087 (define-builtin code-char (x)
1088   `(call |char_from_codepoint| ,x))
1089
1090 (define-builtin characterp (x)
1091   `(selfcall
1092     (var (x ,x))
1093     (return (bool
1094              (and (== (typeof x) "string")
1095                   (or (== (get x "length") 1)
1096                       (== (get x "length") 2)))))))
1097
1098 (define-builtin char-upcase (x)
1099   `(call |safe_char_upcase| ,x))
1100
1101 (define-builtin char-downcase (x)
1102   `(call |safe_char_downcase| ,x))
1103
1104 (define-builtin stringp (x)
1105   `(selfcall
1106     (var (x ,x))
1107     (return (bool
1108              (and (and (===(typeof x) "object")
1109                        (in "length" x))
1110                   (== (get x "stringp") 1))))))
1111
1112 (define-raw-builtin funcall (func &rest args)
1113   `(selfcall
1114     (var (f ,(convert func)))
1115     (return (call (if (=== (typeof f) "function")
1116                       f
1117                       (get f "fvalue"))
1118                   ,@(list* (if *multiple-value-p* '|values| '|pv|)
1119                            (length args)
1120                            (mapcar #'convert args))))))
1121
1122 (define-raw-builtin apply (func &rest args)
1123   (if (null args)
1124       (convert func)
1125       (let ((args (butlast args))
1126             (last (car (last args))))
1127         `(selfcall
1128            (var (f ,(convert func)))
1129            (var (args ,(list-to-vector
1130                         (list* (if *multiple-value-p* '|values| '|pv|)
1131                                (length args)
1132                                (mapcar #'convert args)))))
1133            (var (tail ,(convert last)))
1134            (while (!= tail ,(convert nil))
1135              (method-call args "push" (get tail "car"))
1136              (post++ (property args 1))
1137              (= tail (get tail "cdr")))
1138            (return (method-call (if (=== (typeof f) "function")
1139                                     f
1140                                     (get f "fvalue"))
1141                                 "apply"
1142                                 this
1143                                 args))))))
1144
1145 (define-builtin js-eval (string)
1146   (if *multiple-value-p*
1147       `(selfcall
1148         (var (v (call |globalEval| (call |xstring| ,string))))
1149         (return (method-call |values| "apply" this (call |forcemv| v))))
1150       `(call |globalEval| (call |xstring| ,string))))
1151
1152 (define-builtin %throw (string)
1153   `(selfcall (throw ,string)))
1154
1155 (define-builtin functionp (x)
1156   `(bool (=== (typeof ,x) "function")))
1157
1158 (define-builtin %write-string (x)
1159   `(method-call |lisp| "write" ,x))
1160
1161 (define-builtin /debug (x)
1162   `(method-call |console| "log" (call |xstring| ,x)))
1163
1164
1165 ;;; Storage vectors. They are used to implement arrays and (in the
1166 ;;; future) structures.
1167
1168 (define-builtin storage-vector-p (x)
1169   `(selfcall
1170     (var (x ,x))
1171     (return (bool (and (=== (typeof x) "object") (in "length" x))))))
1172
1173 (define-builtin make-storage-vector (n)
1174   `(selfcall
1175     (var (r #()))
1176     (= (get r "length") ,n)
1177     (return r)))
1178
1179 (define-builtin storage-vector-size (x)
1180   `(get ,x "length"))
1181
1182 (define-builtin resize-storage-vector (vector new-size)
1183   `(= (get ,vector "length") ,new-size))
1184
1185 (define-builtin storage-vector-ref (vector n)
1186   `(selfcall
1187     (var (x (property ,vector ,n)))
1188     (if (=== x undefined) (throw "Out of range."))
1189     (return x)))
1190
1191 (define-builtin storage-vector-set (vector n value)
1192   `(selfcall
1193     (var (x ,vector))
1194     (var (i ,n))
1195     (if (or (< i 0) (>= i (get x "length")))
1196         (throw "Out of range."))
1197     (return (= (property x i) ,value))))
1198
1199 (define-builtin concatenate-storage-vector (sv1 sv2)
1200   `(selfcall
1201      (var (sv1 ,sv1))
1202      (var (r (method-call sv1 "concat" ,sv2)))
1203      (= (get r "type") (get sv1 "type"))
1204      (= (get r "stringp") (get sv1 "stringp"))
1205      (return r)))
1206
1207 (define-builtin get-internal-real-time ()
1208   `(method-call (new (call |Date|)) "getTime"))
1209
1210 (define-builtin values-array (array)
1211   (if *multiple-value-p*
1212       `(method-call |values| "apply" this ,array)
1213       `(method-call |pv| "apply" this ,array)))
1214
1215 (define-raw-builtin values (&rest args)
1216   (if *multiple-value-p*
1217       `(call |values| ,@(mapcar #'convert args))
1218       `(call |pv| ,@(mapcar #'convert args))))
1219
1220 ;;; Javascript FFI
1221
1222 (define-builtin new ()
1223   '(object))
1224
1225 (define-raw-builtin oget* (object key &rest keys)
1226   `(selfcall
1227     (progn
1228       (var (tmp (property ,(convert object) (call |xstring| ,(convert key)))))
1229       ,@(mapcar (lambda (key)
1230                   `(progn
1231                      (if (=== tmp undefined) (return ,(convert nil)))
1232                      (= tmp (property tmp (call |xstring| ,(convert key))))))
1233                 keys))
1234     (return (if (=== tmp undefined) ,(convert nil) tmp))))
1235
1236 (define-raw-builtin oset* (value object key &rest keys)
1237   (let ((keys (cons key keys)))
1238     `(selfcall
1239       (progn
1240         (var (obj ,(convert object)))
1241         ,@(mapcar (lambda (key)
1242                     `(progn
1243                        (= obj (property obj (call |xstring| ,(convert key))))
1244                        (if (=== obj undefined)
1245                            (throw "Impossible to set object property."))))
1246                   (butlast keys))
1247         (var (tmp
1248               (= (property obj (call |xstring| ,(convert (car (last keys)))))
1249                  ,(convert value))))
1250         (return (if (=== tmp undefined)
1251                     ,(convert nil)
1252                     tmp))))))
1253
1254 (define-raw-builtin oget (object key &rest keys)
1255   `(call |js_to_lisp| ,(convert `(oget* ,object ,key ,@keys))))
1256
1257 (define-raw-builtin oset (value object key &rest keys)
1258   (convert `(oset* (lisp-to-js ,value) ,object ,key ,@keys)))
1259
1260 (define-builtin objectp (x)
1261   `(bool (=== (typeof ,x) "object")))
1262
1263 (define-builtin lisp-to-js (x) `(call |lisp_to_js| ,x))
1264 (define-builtin js-to-lisp (x) `(call |js_to_lisp| ,x))
1265
1266
1267 (define-builtin in (key object)
1268   `(bool (in (call |xstring| ,key) ,object)))
1269
1270 (define-builtin delete-property (key object)
1271   `(selfcall
1272     (delete (property ,object (call |xstring| ,key)))))
1273
1274 (define-builtin map-for-in (function object)
1275   `(selfcall
1276     (var (f ,function)
1277          (g (if (=== (typeof f) "function") f (get f "fvalue")))
1278          (o ,object))
1279     (for-in (key o)
1280             (call g ,(if *multiple-value-p* '|values| '|pv|) 1 (property o key)))
1281     (return ,(convert nil))))
1282
1283 (define-compilation %js-vref (var)
1284   `(call |js_to_lisp| ,(make-symbol var)))
1285
1286 (define-compilation %js-vset (var val)
1287   `(= ,(make-symbol var) (call |lisp_to_js| ,(convert val))))
1288
1289 (define-setf-expander %js-vref (var)
1290   (let ((new-value (gensym)))
1291     (unless (stringp var)
1292       (error "`~S' is not a string." var))
1293     (values nil
1294             (list var)
1295             (list new-value)
1296             `(%js-vset ,var ,new-value)
1297             `(%js-vref ,var))))
1298
1299
1300 #-jscl
1301 (defvar *macroexpander-cache*
1302   (make-hash-table :test #'eq))
1303
1304 (defun !macro-function (symbol)
1305   (unless (symbolp symbol)
1306     (error "`~S' is not a symbol." symbol))
1307   (let ((b (lookup-in-lexenv symbol *environment* 'function)))
1308     (if (and b (eq (binding-type b) 'macro))
1309         (let ((expander (binding-value b)))
1310           (cond
1311             #-jscl
1312             ((gethash b *macroexpander-cache*)
1313              (setq expander (gethash b *macroexpander-cache*)))
1314             ((listp expander)
1315              (let ((compiled (eval expander)))
1316                ;; The list representation are useful while
1317                ;; bootstrapping, as we can dump the definition of the
1318                ;; macros easily, but they are slow because we have to
1319                ;; evaluate them and compile them now and again. So, let
1320                ;; us replace the list representation version of the
1321                ;; function with the compiled one.
1322                ;;
1323                #+jscl (setf (binding-value b) compiled)
1324                #-jscl (setf (gethash b *macroexpander-cache*) compiled)
1325                (setq expander compiled))))
1326           expander)
1327         nil)))
1328
1329 (defun !macroexpand-1 (form)
1330   (cond
1331     ((symbolp form)
1332      (let ((b (lookup-in-lexenv form *environment* 'variable)))
1333        (if (and b (eq (binding-type b) 'macro))
1334            (values (binding-value b) t)
1335            (values form nil))))
1336     ((and (consp form) (symbolp (car form)))
1337      (let ((macrofun (!macro-function (car form))))
1338        (if macrofun
1339            (values (funcall macrofun (cdr form)) t)
1340            (values form nil))))
1341     (t
1342      (values form nil))))
1343
1344 (defun compile-funcall (function args)
1345   (let* ((arglist (list* (if *multiple-value-p* '|values| '|pv|)
1346                          (length args)
1347                          (mapcar #'convert args))))
1348     (unless (or (symbolp function)
1349                 (and (consp function)
1350                      (member (car function) '(lambda oget))))
1351       (error "Bad function designator `~S'" function))
1352     (cond
1353       ((translate-function function)
1354        `(call ,(translate-function function) ,@arglist))
1355       ((and (symbolp function)
1356             #+jscl (eq (symbol-package function) (find-package "COMMON-LISP"))
1357             #-jscl t)
1358        `(method-call ,(convert `',function) "fvalue" ,@arglist))
1359       #+jscl((symbolp function)
1360              `(call ,(convert `#',function) ,@arglist))
1361       ((and (consp function) (eq (car function) 'lambda))
1362        `(call ,(convert `(function ,function)) ,@arglist))
1363       ((and (consp function) (eq (car function) 'oget))
1364        `(call |js_to_lisp|
1365               (call ,(reduce (lambda (obj p)
1366                                `(property ,obj (call |xstring| ,p)))
1367                              (mapcar #'convert (cdr function)))
1368                     ,@(mapcar (lambda (s)
1369                                 `(call |lisp_to_js| ,(convert s)))
1370                               args))))
1371       (t
1372        (error "Bad function descriptor")))))
1373
1374 (defun convert-block (sexps &optional return-last-p decls-allowed-p)
1375   (multiple-value-bind (sexps decls)
1376       (parse-body sexps :declarations decls-allowed-p)
1377     (declare (ignore decls))
1378     (if return-last-p
1379         `(progn
1380            ,@(mapcar #'convert (butlast sexps))
1381            (return ,(convert (car (last sexps)) *multiple-value-p*)))
1382         `(progn ,@(mapcar #'convert sexps)))))
1383
1384 (defun convert (sexp &optional multiple-value-p)
1385   (multiple-value-bind (sexp expandedp) (!macroexpand-1 sexp)
1386     (when expandedp
1387       (return-from convert (convert sexp multiple-value-p)))
1388     ;; The expression has been macroexpanded. Now compile it!
1389     (let ((*multiple-value-p* multiple-value-p)
1390           (*convert-level* (1+ *convert-level*)))
1391       (cond
1392         ((symbolp sexp)
1393          (let ((b (lookup-in-lexenv sexp *environment* 'variable)))
1394            (cond
1395              ((and b (not (member 'special (binding-declarations b))))
1396               (binding-value b))
1397              ((or (keywordp sexp)
1398                   (and b (member 'constant (binding-declarations b))))
1399               `(get ,(convert `',sexp) "value"))
1400              (t
1401               (convert `(symbol-value ',sexp))))))
1402         ((or (integerp sexp) (floatp sexp) (characterp sexp) (stringp sexp) (arrayp sexp))
1403          (literal sexp))
1404         ((listp sexp)
1405          (let ((name (car sexp))
1406                (args (cdr sexp)))
1407            (cond
1408              ;; Special forms
1409              ((assoc name *compilations*)
1410               (let ((comp (second (assoc name *compilations*))))
1411                 (apply comp args)))
1412              ;; Built-in functions
1413              ((and (assoc name *builtins*)
1414                    (not (claimp name 'function 'notinline)))
1415               (let ((comp (second (assoc name *builtins*))))
1416                 (apply comp args)))
1417              (t
1418               (compile-funcall name args)))))
1419         (t
1420          (error "How should I compile `~S'?" sexp))))))
1421
1422
1423 (defvar *compile-print-toplevels* nil)
1424
1425 (defun truncate-string (string &optional (width 60))
1426   (let ((n (or (position #\newline string)
1427                (min width (length string)))))
1428     (subseq string 0 n)))
1429
1430 (defun convert-toplevel (sexp &optional multiple-value-p)
1431   ;; Macroexpand sexp as much as possible
1432   (multiple-value-bind (sexp expandedp) (!macroexpand-1 sexp)
1433     (when expandedp
1434       (return-from convert-toplevel (convert-toplevel sexp multiple-value-p))))
1435   ;; Process as toplevel
1436   (let ((*convert-level* -1)
1437         (*toplevel-compilations* nil))
1438     (cond
1439       ;; Non-empty toplevel progn
1440       ((and (consp sexp)
1441             (eq (car sexp) 'progn)
1442             (cdr sexp))
1443        `(progn
1444           ,@(mapcar (lambda (s) (convert-toplevel s t))
1445                     (cdr sexp))))
1446       (t
1447        (when *compile-print-toplevels*
1448          (let ((form-string (prin1-to-string sexp)))
1449            (format t "Compiling ~a..." (truncate-string form-string))))
1450        (let ((code (convert sexp multiple-value-p)))
1451          `(progn
1452             ,@(get-toplevel-compilations)
1453             ,code))))))
1454
1455 (defun compile-toplevel (sexp &optional multiple-value-p)
1456   (with-output-to-string (*standard-output*)
1457     (js (convert-toplevel sexp multiple-value-p))))