Migrate GO
[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 svar).
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     `(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) `(code ,(literal x t))) head)
514            (code ,(literal (car tail) t))
515            (code ,(literal (cdr tail) t)))))
516
517 (defun dump-array (array)
518   (let ((elements (vector-to-list array)))
519     (list-to-vector (mapcar (lambda (x) `(code ,(literal x)))
520                             elements))))
521
522 (defun dump-string (string)
523   `(call |make_lisp_string| ,string))
524
525 (defun literal (sexp &optional recursive)
526   (cond
527     ((integerp sexp) (integer-to-string sexp))
528     ((floatp sexp) (float-to-string sexp))
529     ((characterp sexp) (js-escape-string (string sexp)))
530     (t
531      (or (cdr (assoc sexp *literal-table* :test #'eql))
532          (let ((dumped (typecase sexp
533                          (symbol (dump-symbol sexp))
534                          (string (dump-string sexp))
535                          (cons
536                           ;; BOOTSTRAP MAGIC: See the root file
537                           ;; jscl.lisp and the function
538                           ;; `dump-global-environment' for futher
539                           ;; information.
540                           (if (eq (car sexp) *magic-unquote-marker*)
541                               (ls-compile (second sexp))
542                               (dump-cons sexp)))
543                          (array (dump-array sexp)))))
544            (if (and recursive (not (symbolp sexp)))
545                dumped
546                (let ((jsvar (genlit)))
547                  (push (cons sexp jsvar) *literal-table*)
548                  (toplevel-compilation `(code "var " ,jsvar " = " ,dumped))
549                  (when (keywordp sexp)
550                    (toplevel-compilation `(code ,jsvar ".value = " ,jsvar)))
551                  jsvar)))))))
552
553
554 (define-compilation quote (sexp)
555   (literal sexp))
556
557 (define-compilation %while (pred &rest body)
558   (js!selfcall*
559     `(while (!== ,(ls-compile pred) ,(ls-compile nil))
560        0                                ; TODO: Force
561                                         ; braces. Unnecesary when code
562                                         ; is gone
563        ,(ls-compile-block body))
564    `(return ,(ls-compile nil))))
565
566 (define-compilation function (x)
567   (cond
568     ((and (listp x) (eq (car x) 'lambda))
569      (compile-lambda (cadr x) (cddr x)))
570     ((and (listp x) (eq (car x) 'named-lambda))
571      (destructuring-bind (name ll &rest body) (cdr x)
572        (compile-lambda ll body
573                        :name (symbol-name name)
574                        :block name)))
575     ((symbolp x)
576      (let ((b (lookup-in-lexenv x *environment* 'function)))
577        (if b
578            (binding-value b)
579            (ls-compile `(symbol-function ',x)))))))
580
581
582 (defun make-function-binding (fname)
583   (make-binding :name fname :type 'function :value (gvarname fname)))
584
585 (defun compile-function-definition (list)
586   (compile-lambda (car list) (cdr list)))
587
588 (defun translate-function (name)
589   (let ((b (lookup-in-lexenv name *environment* 'function)))
590     (and b (binding-value b))))
591
592 (define-compilation flet (definitions &rest body)
593   (let* ((fnames (mapcar #'car definitions))
594          (cfuncs (mapcar (lambda (def)
595                            (compile-lambda (cadr def)
596                                            `((block ,(car def)
597                                                ,@(cddr def)))))
598                          definitions))
599          (*environment*
600           (extend-lexenv (mapcar #'make-function-binding fnames)
601                          *environment*
602                          'function)))
603     `(call (function ,(mapcar #'make-symbol (mapcar #'translate-function fnames))
604                 ,(ls-compile-block body t))
605            ,@cfuncs)))
606
607 (define-compilation labels (definitions &rest body)
608   (let* ((fnames (mapcar #'car definitions))
609          (*environment*
610           (extend-lexenv (mapcar #'make-function-binding fnames)
611                          *environment*
612                          'function)))
613     (js!selfcall*
614       `(progn
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     (js!selfcall*
787       (when multiple-value-p
788         `(var (|values| |mv|)))
789       `(throw
790            (object
791             "type" "block"
792             "id" ,(make-symbol (binding-value b))
793             "values" ,(ls-compile value multiple-value-p)
794             "message" ,(concat "Return from unknown block '" (symbol-name name) "'."))))))
795
796 (define-compilation catch (id &rest body)
797   (js!selfcall*
798     `(var (|id| ,(ls-compile id)))
799     `(try
800       ,(ls-compile-block body t))
801     `(catch (|cf|)
802        (if (and (== (get |cf| "type") "catch")
803                 (== (get |cf| "id") |id|))
804            ,(if *multiple-value-p*
805                 `(return (call (get |values| "apply")
806                                this
807                                (call |forcemv| (get |cf| "values"))))
808                 `(return (call (get |pv| "apply")
809                                this
810                                (call |forcemv| (get |cf| "values")))))
811            (throw |cf|)))))
812
813 (define-compilation throw (id value)
814   (js!selfcall*
815     `(var (|values| |mv|))
816     `(throw (object
817              |type| "catch"
818              |id| ,(ls-compile id)
819              |values| ,(ls-compile value t)
820              |message| "Throw uncatched."))))
821
822 (defun go-tag-p (x)
823   (or (integerp x) (symbolp x)))
824
825 (defun declare-tagbody-tags (tbidx body)
826   (let* ((go-tag-counter 0)
827          (bindings
828           (mapcar (lambda (label)
829                     (let ((tagidx (incf go-tag-counter)))
830                       (make-binding :name label :type 'gotag :value (list tbidx tagidx))))
831                   (remove-if-not #'go-tag-p body))))
832     (extend-lexenv bindings *environment* 'gotag)))
833
834 (define-compilation tagbody (&rest body)
835   ;; Ignore the tagbody if it does not contain any go-tag. We do this
836   ;; because 1) it is easy and 2) many built-in forms expand to a
837   ;; implicit tagbody, so we save some space.
838   (unless (some #'go-tag-p body)
839     (return-from tagbody (ls-compile `(progn ,@body nil))))
840   ;; The translation assumes the first form in BODY is a label
841   (unless (go-tag-p (car body))
842     (push (gensym "START") body))
843   ;; Tagbody compilation
844   (let ((branch (gvarname 'branch))
845         (tbidx (gvarname 'tbidx)))
846     (let ((*environment* (declare-tagbody-tags tbidx body))
847           initag)
848       (let ((b (lookup-in-lexenv (first body) *environment* 'gotag)))
849         (setq initag (second (binding-value b))))
850       (js!selfcall
851         ;; TAGBODY branch to take
852         "var " branch " = " initag ";"
853         "var " tbidx " = [];"
854         "tbloop:"
855         "while (true) {"
856         `(code "try {"
857                ,(let ((content nil))
858                   `(code "switch(" ,branch "){"
859                         "case " ,initag ":"
860                         ,@(dolist (form (cdr body) (reverse content))
861                           (push (if (not (go-tag-p form))
862                                     `(code ,(ls-compile form) ";" )
863                                     (let ((b (lookup-in-lexenv form *environment* 'gotag)))
864                                       `(code "case " ,(second (binding-value b)) ":" )))
865                                 content))
866                            "default:"
867                            "    break tbloop;"
868                            "}" ))
869                "}"
870                "catch (jump) {"
871                "    if (jump.type == 'tagbody' && jump.id == " ,tbidx ")"
872                "        " ,branch " = jump.label;"
873                "    else"
874                "        throw(jump);"
875                "}" )
876         "}"
877         "return " (ls-compile nil) ";" ))))
878
879 (define-compilation go (label)
880   (let ((b (lookup-in-lexenv label *environment* 'gotag))
881         (n (cond
882              ((symbolp label) (symbol-name label))
883              ((integerp label) (integer-to-string label)))))
884     (when (null b)
885       (error "Unknown tag `~S'" label))
886     (js!selfcall*
887       `(throw
888            (object
889             "type" "tagbody"
890             "id" ,(make-symbol (first (binding-value b)))
891             "label" ,(second (binding-value b))
892             "message" ,(concat "Attempt to GO to non-existing tag " n))))))
893
894 (define-compilation unwind-protect (form &rest clean-up)
895   (js!selfcall*
896     `(var (|ret| ,(ls-compile nil)))
897     `(try
898        (= |ret| ,(ls-compile form)))
899     `(finally
900       ,(ls-compile-block clean-up))
901     `(return |ret|)))
902
903 (define-compilation multiple-value-call (func-form &rest forms)
904   (js!selfcall
905     "var func = " (ls-compile func-form) ";"
906     "var args = [" (if *multiple-value-p* "values" "pv") ", 0];"
907     "return "
908     (js!selfcall
909       "var values = mv;"
910       "var vs;"
911       `(code
912         ,@(mapcar (lambda (form)
913                     `(code "vs = " ,(ls-compile form t) ";"
914                            "if (typeof vs === 'object' && 'multiple-value' in vs)"
915                            (code " args = args.concat(vs);" )
916                            " else "
917                            (code "args.push(vs);" )))
918                   forms))
919       "args[1] = args.length-2;"
920       "return func.apply(window, args);" ) ";" ))
921
922 (define-compilation multiple-value-prog1 (first-form &rest forms)
923   (js!selfcall
924     "var args = " (ls-compile first-form *multiple-value-p*) ";"
925     (ls-compile-block forms)
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 ;;; DECLS is a list of (JSVARNAME TYPE LISPFORM) declarations.
949 (defmacro type-check (decls &body body)
950   `(js!selfcall
951      ,@(mapcar (lambda (decl)
952                  `(let ((name ,(first decl))
953                         (value ,(third decl)))
954                     `(code "var " ,name " = " ,value ";" )))
955                decls)
956      ,@(mapcar (lambda (decl)
957                  `(let ((name ,(first decl))
958                         (type ,(second decl)))
959                     `(code "if (typeof " ,name " != '" ,type "')"
960                            (code "throw 'The value ' + "
961                                  ,name
962                                  " + ' is not a type "
963                                  ,type
964                                  ".';"
965                                  ))))
966                decls)
967      `(code "return " ,,@body ";" )))
968
969 ;;; VARIABLE-ARITY compiles variable arity operations. ARGS stands for
970 ;;; a variable which holds a list of forms. It will compile them and
971 ;;; store the result in some Javascript variables. BODY is evaluated
972 ;;; with ARGS bound to the list of these variables to generate the
973 ;;; code which performs the transformation on these variables.
974
975 (defun variable-arity-call (args function)
976   (unless (consp args)
977     (error "ARGS must be a non-empty list"))
978   (let ((counter 0)
979         (fargs '())
980         (prelude '()))
981     (dolist (x args)
982       (cond
983         ((or (floatp x) (numberp x)) (push x fargs))
984         (t (let ((v (make-symbol (code "x" (incf counter)))))
985              (push v fargs)
986              (push `(code "var " ,v " = " ,(ls-compile x) ";"
987                           "if (typeof " ,v " !== 'number') throw 'Not a number!';")
988                    prelude)))))
989     (js!selfcall
990       `(code ,@(reverse prelude))
991       (funcall function (reverse fargs)))))
992
993
994 (defmacro variable-arity (args &body body)
995   (unless (symbolp args)
996     (error "`~S' is not a symbol." args))
997   `(variable-arity-call ,args
998                         (lambda (,args)
999                           `(code "return " ,,@body ";" ))))
1000
1001 (defun num-op-num (x op y)
1002   (type-check (("x" "number" x) ("y" "number" y))
1003     `(code "x" ,op "y")))
1004
1005 (define-raw-builtin + (&rest numbers)
1006   (if (null numbers)
1007       0
1008       (variable-arity numbers
1009         `(+ ,@numbers))))
1010
1011 (define-raw-builtin - (x &rest others)
1012   (let ((args (cons x others)))
1013     (variable-arity args `(- ,@args))))
1014
1015 (define-raw-builtin * (&rest numbers)
1016   (if (null numbers)
1017       1
1018       (variable-arity numbers `(* ,@numbers))))
1019
1020 (define-raw-builtin / (x &rest others)
1021   (let ((args (cons x others)))
1022     (variable-arity args
1023       (if (null others)
1024           `(/ 1 ,(car args))
1025           (reduce (lambda (x y) `(/ ,x ,y))
1026                   args)))))
1027
1028 (define-builtin mod (x y) (num-op-num x "%" y))
1029
1030
1031 (defun comparison-conjuntion (vars op)
1032   (cond
1033     ((null (cdr vars))
1034      'true)
1035     ((null (cddr vars))
1036      `(,op ,(car vars) ,(cadr vars)))
1037     (t
1038      `(and (,op ,(car vars) ,(cadr vars))
1039            ,(comparison-conjuntion (cdr vars) op)))))
1040
1041 (defmacro define-builtin-comparison (op sym)
1042   `(define-raw-builtin ,op (x &rest args)
1043      (let ((args (cons x args)))
1044        (variable-arity args
1045          (js!bool (comparison-conjuntion args ',sym))))))
1046
1047 (define-builtin-comparison > >)
1048 (define-builtin-comparison < <)
1049 (define-builtin-comparison >= >=)
1050 (define-builtin-comparison <= <=)
1051 (define-builtin-comparison = ==)
1052 (define-builtin-comparison /= !=)
1053
1054 (define-builtin numberp (x)
1055   (js!bool `(== (typeof ,x) "number")))
1056
1057 (define-builtin floor (x)
1058   (type-check (("x" "number" x))
1059     "Math.floor(x)"))
1060
1061 (define-builtin expt (x y)
1062   (type-check (("x" "number" x)
1063                ("y" "number" y))
1064     "Math.pow(x, y)"))
1065
1066 (define-builtin float-to-string (x)
1067   (type-check (("x" "number" x))
1068     "make_lisp_string(x.toString())"))
1069
1070 (define-builtin cons (x y)
1071   `(object "car" ,x "cdr" ,y))
1072
1073 (define-builtin consp (x)
1074   (js!bool
1075    (js!selfcall
1076      "var tmp = " x ";"
1077      "return (typeof tmp == 'object' && 'car' in tmp);" )))
1078
1079 (define-builtin car (x)
1080   (js!selfcall*
1081     `(var (tmp ,x))
1082     `(return (if (=== tmp ,(ls-compile nil))
1083                  ,(ls-compile nil)
1084                  (get tmp "car")))))
1085
1086 (define-builtin cdr (x)
1087   (js!selfcall*
1088     `(var (tmp ,x))
1089     `(return (if (=== tmp ,(ls-compile nil))
1090                  ,(ls-compile nil)
1091                  (get tmp "cdr")))))
1092
1093 (define-builtin rplaca (x new)
1094   (type-check (("x" "object" x))
1095     `(code "(x.car = " ,new ", x)")))
1096
1097 (define-builtin rplacd (x new)
1098   (type-check (("x" "object" x))
1099     `(code "(x.cdr = " ,new ", x)")))
1100
1101 (define-builtin symbolp (x)
1102   (js!bool `(instanceof ,x |Symbol|)))
1103
1104 (define-builtin make-symbol (name)
1105   `(new (call |Symbol| ,name)))
1106
1107 (define-builtin symbol-name (x)
1108   `(get ,x "name"))
1109
1110 (define-builtin set (symbol value)
1111   `(= (get ,symbol "value") ,value))
1112
1113 (define-builtin fset (symbol value)
1114   `(= (get ,symbol "fvalue") ,value))
1115
1116 (define-builtin boundp (x)
1117   (js!bool `(!== (get ,x "value") undefined)))
1118
1119 (define-builtin fboundp (x)
1120   (js!bool `(!== (get ,x "fvalue") undefined)))
1121
1122 (define-builtin symbol-value (x)
1123   (js!selfcall*
1124     `(var (symbol ,x)
1125           (value (get symbol "value")))
1126     `(if (=== value undefined)
1127          (throw (+ "Variable `" (call |xstring| (get symbol "name")) "' is unbound.")))
1128     `(return value)))
1129
1130 (define-builtin symbol-function (x)
1131   (js!selfcall*
1132     `(var (symbol ,x)
1133           (func (get symbol "fvalue")))
1134     `(if (=== func undefined)
1135          (throw (+ "Function `" (call |xstring| (get symbol "name")) "' is undefined.")))
1136     `(return func)))
1137
1138 (define-builtin symbol-plist (x)
1139   `(or (get ,x "plist") ,(ls-compile nil)))
1140
1141 (define-builtin lambda-code (x)
1142   `(call |make_lisp_string| (call (get ,x "toString"))))
1143
1144 (define-builtin eq (x y)
1145   (js!bool `(=== ,x ,y)))
1146
1147 (define-builtin char-code (x)
1148   (type-check (("x" "string" x))
1149     "char_to_codepoint(x)"))
1150
1151 (define-builtin code-char (x)
1152   (type-check (("x" "number" x))
1153     "char_from_codepoint(x)"))
1154
1155 (define-builtin characterp (x)
1156   (js!bool
1157    (js!selfcall*
1158      `(var (x ,x))
1159      `(return (and (== (typeof x) "string")
1160                    (or (== (get x "length") 1)
1161                        (== (get x "length") 2)))))))
1162
1163 (define-builtin char-upcase (x)
1164   `(call |safe_char_upcase| ,x))
1165
1166 (define-builtin char-downcase (x)
1167   `(call |safe_char_downcase| ,x))
1168
1169 (define-builtin stringp (x)
1170   (js!bool
1171    (js!selfcall*
1172      `(var (x ,x))
1173      `(return (and (and (===(typeof x) "object")
1174                         (in "length" x))
1175                    (== (get x "stringp") 1))))))
1176
1177 (define-raw-builtin funcall (func &rest args)
1178   (js!selfcall*
1179     `(var (f ,(ls-compile func)))
1180     `(return (call (if (=== (typeof f) "function")
1181                        f
1182                        (get f "fvalue"))
1183                    ,@(list* (if *multiple-value-p* '|values| '|pv|)
1184                             (length args)
1185                             (mapcar #'ls-compile args))))))
1186
1187 (define-raw-builtin apply (func &rest args)
1188   (if (null args)
1189       `(code "(" ,(ls-compile func) ")()")
1190       (let ((args (butlast args))
1191             (last (car (last args))))
1192         (js!selfcall
1193           "var f = " (ls-compile func) ";"
1194           "var args = [" `(code
1195                            ,@(interleave (list* (if *multiple-value-p* "values" "pv")
1196                                                 (integer-to-string (length args))
1197                                                 (mapcar #'ls-compile args))
1198                                          ", "))
1199           "];"
1200           "var tail = (" (ls-compile last) ");"
1201           "while (tail != " (ls-compile nil) "){"
1202           "    args.push(tail.car);"
1203           "    args[1] += 1;"
1204           "    tail = tail.cdr;"
1205           "}"
1206           "return (typeof f === 'function'? f : f.fvalue).apply(this, args);" ))))
1207
1208 (define-builtin js-eval (string)
1209   (if *multiple-value-p*
1210       (js!selfcall*
1211         `(var (v (call |globalEval| (call |xstring| ,string))))
1212         `(return (call (get |values| "apply") this (call |forcemv| v))))
1213       `(call |globalEval| (call |xstring| ,string))))
1214
1215 (define-builtin %throw (string)
1216   (js!selfcall* `(throw ,string)))
1217
1218 (define-builtin functionp (x)
1219   (js!bool `(=== (typeof ,x) "function")))
1220
1221 (define-builtin %write-string (x)
1222   `(call (get |lisp| "write") ,x))
1223
1224 (define-builtin /debug (x)
1225   `(call (get |console| "log") (call |xstring| ,x)))
1226
1227
1228 ;;; Storage vectors. They are used to implement arrays and (in the
1229 ;;; future) structures.
1230
1231 (define-builtin storage-vector-p (x)
1232   (js!bool
1233    (js!selfcall*
1234      `(var (x ,x))
1235      `(return (and (=== (typeof x) "object") (in "length" x))))))
1236
1237 (define-builtin make-storage-vector (n)
1238   (js!selfcall*
1239     `(var (r #()))
1240     `(= (get r "length") ,n)
1241     `(return r)))
1242
1243 (define-builtin storage-vector-size (x)
1244   `(get ,x "length"))
1245
1246 (define-builtin resize-storage-vector (vector new-size)
1247   `(= (get ,vector "length") ,new-size))
1248
1249 (define-builtin storage-vector-ref (vector n)
1250   (js!selfcall*
1251     `(var (x (property ,vector ,n)))
1252     `(if (=== x undefined) (throw "Out of range."))
1253     `(return x)))
1254
1255 (define-builtin storage-vector-set (vector n value)
1256   (js!selfcall*
1257     `(var (x ,vector))
1258     `(var (i ,n))
1259     `(if (or (< i 0) (>= i (get x "length")))
1260          (throw "Out of range."))
1261     `(return (= (property x i) ,value))))
1262
1263 (define-builtin concatenate-storage-vector (sv1 sv2)
1264   (js!selfcall*
1265     `(var (sv1 ,sv1))
1266     `(var (r (call (get sv1 "concat") ,sv2)))
1267     `(= (get r "type") (get sv1 "type"))
1268     `(= (get r "stringp") (get sv1 "stringp"))
1269     `(return r)))
1270
1271 (define-builtin get-internal-real-time ()
1272   `(call (get (new (call |Date|)) "getTime")))
1273
1274 (define-builtin values-array (array)
1275   (if *multiple-value-p*
1276       `(call (get |values| "apply") this ,array)
1277       `(call (get |pv| "apply") this ,array)))
1278
1279 (define-raw-builtin values (&rest args)
1280   (if *multiple-value-p*
1281       `(call |values| ,@(mapcar #'ls-compile args))
1282       `(call |pv| ,@(mapcar #'ls-compile args))))
1283
1284 ;;; Javascript FFI
1285
1286 (define-builtin new ()
1287   '(object))
1288
1289 (define-raw-builtin oget* (object key &rest keys)
1290   (js!selfcall*
1291     `(progn
1292        (var (tmp (property ,(ls-compile object) (call |xstring| ,(ls-compile key)))))
1293        ,@(mapcar (lambda (key)
1294                    `(progn
1295                       (if (=== tmp undefined) (return ,(ls-compile nil)))
1296                       (= tmp (property tmp (call |xstring| ,(ls-compile key))))))
1297                  keys))
1298     `(return (if (=== tmp undefined) ,(ls-compile nil) tmp))))
1299
1300 (define-raw-builtin oset* (value object key &rest keys)
1301   (let ((keys (cons key keys)))
1302     (js!selfcall*
1303       `(progn
1304          (var (obj ,(ls-compile object)))
1305          ,@(mapcar (lambda (key)
1306                      `(progn
1307                         (= obj (property obj (call |xstring| ,(ls-compile key))))
1308                         (if (=== object undefined)
1309                             (throw "Impossible to set object property."))))
1310                    (butlast keys))
1311          (var (tmp
1312                (= (property obj (call |xstring| ,(ls-compile (car (last keys)))))
1313                   ,(ls-compile value))))
1314          (return (if (=== tmp undefined)
1315                      ,(ls-compile nil)
1316                      tmp))))))
1317
1318 (define-raw-builtin oget (object key &rest keys)
1319   `(call |js_to_lisp| ,(ls-compile `(oget* ,object ,key ,@keys))))
1320
1321 (define-raw-builtin oset (value object key &rest keys)
1322   (ls-compile `(oset* (lisp-to-js ,value) ,object ,key ,@keys)))
1323
1324 (define-builtin objectp (x)
1325   (js!bool `(=== (typeof ,x) "object")))
1326
1327 (define-builtin lisp-to-js (x) `(call |lisp_to_js| ,x))
1328 (define-builtin js-to-lisp (x) `(call |js_to_lisp| ,x))
1329
1330
1331 (define-builtin in (key object)
1332   (js!bool `(in (call |xstring| ,key) ,object)))
1333
1334 (define-builtin map-for-in (function object)
1335   (js!selfcall*
1336     `(var (f ,function)
1337           (g (if (=== (typeof f) "function") f (get f "fvalue")))
1338           (o ,object))
1339     `(for-in (key o)
1340        (call g ,(if *multiple-value-p* '|values| '|pv|) 1 (get o "key")))
1341     `(return ,(ls-compile nil))))
1342
1343 (define-compilation %js-vref (var)
1344   `(call |js_to_lisp| ,(make-symbol var)))
1345
1346 (define-compilation %js-vset (var val)
1347   `(= ,(make-symbol var) (call |lisp_to_js| ,(ls-compile val))))
1348
1349 (define-setf-expander %js-vref (var)
1350   (let ((new-value (gensym)))
1351     (unless (stringp var)
1352       (error "`~S' is not a string." var))
1353     (values nil
1354             (list var)
1355             (list new-value)
1356             `(%js-vset ,var ,new-value)
1357             `(%js-vref ,var))))
1358
1359
1360 #-jscl
1361 (defvar *macroexpander-cache*
1362   (make-hash-table :test #'eq))
1363
1364 (defun !macro-function (symbol)
1365   (unless (symbolp symbol)
1366     (error "`~S' is not a symbol." symbol))
1367   (let ((b (lookup-in-lexenv symbol *environment* 'function)))
1368     (if (and b (eq (binding-type b) 'macro))
1369         (let ((expander (binding-value b)))
1370           (cond
1371             #-jscl
1372             ((gethash b *macroexpander-cache*)
1373              (setq expander (gethash b *macroexpander-cache*)))
1374             ((listp expander)
1375              (let ((compiled (eval expander)))
1376                ;; The list representation are useful while
1377                ;; bootstrapping, as we can dump the definition of the
1378                ;; macros easily, but they are slow because we have to
1379                ;; evaluate them and compile them now and again. So, let
1380                ;; us replace the list representation version of the
1381                ;; function with the compiled one.
1382                ;;
1383                #+jscl (setf (binding-value b) compiled)
1384                #-jscl (setf (gethash b *macroexpander-cache*) compiled)
1385                (setq expander compiled))))
1386           expander)
1387         nil)))
1388
1389 (defun !macroexpand-1 (form)
1390   (cond
1391     ((symbolp form)
1392      (let ((b (lookup-in-lexenv form *environment* 'variable)))
1393        (if (and b (eq (binding-type b) 'macro))
1394            (values (binding-value b) t)
1395            (values form nil))))
1396     ((and (consp form) (symbolp (car form)))
1397      (let ((macrofun (!macro-function (car form))))
1398        (if macrofun
1399            (values (funcall macrofun (cdr form)) t)
1400            (values form nil))))
1401     (t
1402      (values form nil))))
1403
1404 (defun compile-funcall (function args)
1405   (let* ((values-funcs (if *multiple-value-p* "values" "pv"))
1406          (arglist `(code "(" ,@(interleave (list* values-funcs
1407                                                   (integer-to-string (length args))
1408                                                   (mapcar #'ls-compile args))
1409                                            ", ")
1410                          ")")))
1411     (unless (or (symbolp function)
1412                 (and (consp function)
1413                      (member (car function) '(lambda oget))))
1414       (error "Bad function designator `~S'" function))
1415     (cond
1416       ((translate-function function)
1417        `(code ,(translate-function function) ,arglist))
1418       ((and (symbolp function)
1419             #+jscl (eq (symbol-package function) (find-package "COMMON-LISP"))
1420             #-jscl t)
1421        `(code ,(ls-compile `',function) ".fvalue" ,arglist))
1422       #+jscl((symbolp function)
1423        `(code ,(ls-compile `#',function) ,arglist))
1424       ((and (consp function) (eq (car function) 'lambda))
1425        `(code ,(ls-compile `#',function) ,arglist))
1426       ((and (consp function) (eq (car function) 'oget))
1427        `(code ,(ls-compile function) ,arglist))
1428       (t
1429        (error "Bad function descriptor")))))
1430
1431 (defun ls-compile-block (sexps &optional return-last-p decls-allowed-p)
1432   (multiple-value-bind (sexps decls)
1433       (parse-body sexps :declarations decls-allowed-p)
1434     (declare (ignore decls))
1435     (if return-last-p
1436         `(code ,(ls-compile-block (butlast sexps) nil decls-allowed-p)
1437                "return " ,(ls-compile (car (last sexps)) *multiple-value-p*) ";")
1438         `(code
1439           ,@(interleave (mapcar #'ls-compile sexps) ";
1440 " *newline*)
1441           ";" ,*newline*))))
1442
1443 (defun ls-compile* (sexp &optional multiple-value-p)
1444   (multiple-value-bind (sexp expandedp) (!macroexpand-1 sexp)
1445     (when expandedp
1446       (return-from ls-compile* (ls-compile sexp multiple-value-p)))
1447     ;; The expression has been macroexpanded. Now compile it!
1448     (let ((*multiple-value-p* multiple-value-p))
1449       (cond
1450         ((symbolp sexp)
1451          (let ((b (lookup-in-lexenv sexp *environment* 'variable)))
1452            (cond
1453              ((and b (not (member 'special (binding-declarations b))))
1454               (binding-value b))
1455              ((or (keywordp sexp)
1456                   (and b (member 'constant (binding-declarations b))))
1457               `(code ,(ls-compile `',sexp) ".value"))
1458              (t
1459               (ls-compile `(symbol-value ',sexp))))))
1460         ((or (integerp sexp) (floatp sexp) (characterp sexp) (stringp sexp) (arrayp sexp))
1461          (literal sexp))
1462         ((listp sexp)
1463          (let ((name (car sexp))
1464                (args (cdr sexp)))
1465            (cond
1466              ;; Special forms
1467              ((assoc name *compilations*)
1468               (let ((comp (second (assoc name *compilations*))))
1469                 (apply comp args)))
1470              ;; Built-in functions
1471              ((and (assoc name *builtins*)
1472                    (not (claimp name 'function 'notinline)))
1473               (let ((comp (second (assoc name *builtins*))))
1474                 (apply comp args)))
1475              (t
1476               (compile-funcall name args)))))
1477         (t
1478          (error "How should I compile `~S'?" sexp))))))
1479
1480 (defun ls-compile (sexp &optional multiple-value-p)
1481   `(code "(" ,(ls-compile* sexp multiple-value-p) ")"))
1482
1483
1484 (defvar *compile-print-toplevels* nil)
1485
1486 (defun truncate-string (string &optional (width 60))
1487   (let ((n (or (position #\newline string)
1488                (min width (length string)))))
1489     (subseq string 0 n)))
1490
1491 (defun convert-toplevel (sexp &optional multiple-value-p)
1492   (let ((*toplevel-compilations* nil))
1493     (cond
1494       ;; Non-empty toplevel progn
1495       ((and (consp sexp)
1496             (eq (car sexp) 'progn)
1497             (cdr sexp))
1498        `(progn
1499           ,@(mapcar (lambda (s) (convert-toplevel s t))
1500                     (cdr sexp))))
1501       (t
1502        (when *compile-print-toplevels*
1503          (let ((form-string (prin1-to-string sexp)))
1504            (format t "Compiling ~a..." (truncate-string form-string))))
1505        (let ((code (ls-compile sexp multiple-value-p)))
1506          `(code
1507            ,@(interleave (get-toplevel-compilations) ";
1508 " t)
1509            ,(when code
1510                   `(code ,code ";"))))))))
1511
1512 (defun ls-compile-toplevel (sexp &optional multiple-value-p)
1513   (with-output-to-string (*standard-output*)
1514     (js (convert-toplevel sexp multiple-value-p))))