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