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