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