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