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