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