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