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