3 ;; copyright (C) 2012, 2013 David Vazquez
4 ;; Copyright (C) 2012 Raimon Grau
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.
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.
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/>.
21 (/debug "loading compiler.lisp!")
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.
28 (defun interleave (list element &optional after-last-p)
32 (dolist (x (cdr list))
38 (defun code (&rest args)
39 (mapconcat (lambda (arg)
42 ((integerp arg) (integer-to-string arg))
43 ((floatp arg) (float-to-string arg))
46 (with-output-to-string (*standard-output*)
50 ;;; Wrap X with a Javascript code to convert the result from
51 ;;; Javascript generalized booleans to T or NIL.
53 `(if ,x ,(ls-compile t) ,(ls-compile nil)))
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))))
63 (defmacro js!selfcall* (&body body)
64 ``(call (function nil ,,@body)))
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.
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
77 (defvar *multiple-value-p* nil)
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)))
101 (defun push-to-lexenv (binding lexenv 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)))))
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))))
114 (defvar *environment* (make-lexenv))
116 (defvar *variable-counter* 0)
118 (defun gvarname (symbol)
119 (declare (ignore symbol))
120 (incf *variable-counter*)
121 (concat "v" (integer-to-string *variable-counter*)))
123 (defun translate-variable (symbol)
124 (awhen (lookup-in-lexenv symbol *environment* 'variable)
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)))))
133 ;;; Toplevel compilations
134 (defvar *toplevel-compilations* nil)
136 (defun toplevel-compilation (string)
137 (push string *toplevel-compilations*))
139 (defun get-toplevel-compilations ()
140 (reverse *toplevel-compilations*))
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))
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)
154 (defun claimp (symbol namespace claim)
155 (let ((b (lookup-in-lexenv symbol *environment* namespace)))
156 (and b (member claim (binding-declarations b)))))
158 (defun !proclaim (decl)
161 (dolist (name (cdr decl))
162 (let ((b (global-binding name 'variable 'variable)))
163 (push 'special (binding-declarations b)))))
165 (dolist (name (cdr decl))
166 (let ((b (global-binding name 'function 'function)))
167 (push 'notinline (binding-declarations b)))))
169 (dolist (name (cdr decl))
170 (let ((b (global-binding name 'variable 'variable)))
171 (push 'constant (binding-declarations b)))))))
174 (fset 'proclaim #'!proclaim)
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)
182 (defmacro define-symbol-macro (name expansion)
183 `(%define-symbol-macro ',name ',expansion))
188 (defvar *compilations* nil)
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)))
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*)))
202 (defvar *ll-keywords* '(&optional &rest &key))
204 (defun list-until-keyword (list)
205 (if (or (null list) (member (car list) *ll-keywords*))
207 (cons (car list) (list-until-keyword (cdr list)))))
209 (defun ll-section (keyword ll)
210 (list-until-keyword (cdr (member keyword ll))))
212 (defun ll-required-arguments (ll)
213 (list-until-keyword ll))
215 (defun ll-optional-arguments-canonical (ll)
216 (mapcar #'ensure-list (ll-section '&optional ll)))
218 (defun ll-optional-arguments (ll)
219 (mapcar #'car (ll-optional-arguments-canonical ll)))
221 (defun ll-rest-argument (ll)
222 (let ((rest (ll-section '&rest ll)))
224 (error "Bad lambda-list `~S'." ll))
227 (defun ll-keyword-arguments-canonical (ll)
228 (flet ((canonicalize (keyarg)
229 ;; Build a canonical keyword argument descriptor, filling
230 ;; the optional fields. The result is a list of the form
231 ;; ((keyword-name var) init-form).
232 (let ((arg (ensure-list keyarg)))
233 (cons (if (listp (car arg))
235 (list (intern (symbol-name (car arg)) "KEYWORD") (car arg)))
237 (mapcar #'canonicalize (ll-section '&key ll))))
239 (defun ll-keyword-arguments (ll)
240 (mapcar (lambda (keyarg) (second (first keyarg)))
241 (ll-keyword-arguments-canonical ll)))
243 (defun ll-svars (lambda-list)
246 (ll-keyword-arguments-canonical lambda-list)
247 (ll-optional-arguments-canonical lambda-list))))
248 (remove nil (mapcar #'third args))))
250 (defun lambda-name/docstring-wrapper (name docstring code)
251 (if (or name docstring)
254 (when name `(= (get func "fname") ,name))
255 (when docstring `(= (get func "docstring") ,docstring))
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))))
266 ;; Special case: a positive exact number of arguments.
267 (when (and (< 0 min) (eql min max))
268 (return `(call |checkArgs| |nargs| ,min)))
271 ,(when (< 0 min) `(call |checkArgsAtLeast| |nargs| ,min))
272 ,(when (numberp max) `(call |checkArgsAtMost| |nargs| ,max))))))
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
281 (dotimes (idx n-optional-arguments)
282 (let ((arg (nth idx optional-arguments)))
283 (collect `(,(+ idx n-required-arguments)
284 (= ,(make-symbol (translate-variable (car arg)))
285 ,(ls-compile (cadr arg)))
287 `(= ,(make-symbol (translate-variable (third arg)))
288 ,(ls-compile nil)))))))
289 (collect `(default (break))))))))
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)))
296 (let ((js!rest (make-symbol (translate-variable rest-argument))))
298 (var (,js!rest ,(ls-compile nil)))
300 (for ((= i (- |nargs| 1))
301 (>= i ,(+ n-required-arguments n-optional-arguments))
303 (= ,js!rest (object "car" (property |arguments| (+ i 2))
304 "cdr" ,js!rest))))))))
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)))
312 (ll-keyword-arguments-canonical ll)))
315 ,@(mapcar (lambda (arg)
316 (let ((var (second (car arg))))
317 `(code "var " ,(translate-variable var) "; "
319 `(code "var " ,(translate-variable (third arg))
320 " = " ,(ls-compile nil)
324 ,(flet ((parse-keyword (keyarg)
325 ;; ((keyword-name var) init-form)
326 `(code "for (i=" ,(+ n-required-arguments n-optional-arguments)
328 "if (arguments[i+2] === " ,(ls-compile (caar keyarg)) "){"
329 ,(translate-variable (cadr (car keyarg)))
331 ,(let ((svar (third keyarg)))
333 `(code ,(translate-variable svar) " = " ,(ls-compile t) ";" )))
339 ,(translate-variable (cadr (car keyarg)))
341 ,(ls-compile (cadr keyarg))
344 (when keyword-arguments
346 ,@(mapcar #'parse-keyword keyword-arguments))))
347 ;; Check for unknown keywords
348 ,(when keyword-arguments
349 `(code "var start = " ,(+ n-required-arguments n-optional-arguments) ";"
350 "if ((nargs - start) % 2 == 1){"
351 "throw 'Odd number of keyword arguments';"
353 "for (i = start; i<nargs; i+=2){"
355 ,@(interleave (mapcar (lambda (x)
356 `(code "arguments[i+2] !== " ,(ls-compile (caar x))))
360 "throw 'Unknown keyword argument ' + xstring(arguments[i+2].name);"
363 (defun parse-lambda-list (ll)
364 (values (ll-required-arguments ll)
365 (ll-optional-arguments ll)
366 (ll-keyword-arguments ll)
367 (ll-rest-argument ll)))
369 ;;; Process BODY for declarations and/or docstrings. Return as
370 ;;; multiple values the BODY without docstrings or declarations, the
371 ;;; list of declaration forms and the docstring.
372 (defun parse-body (body &key declarations docstring)
373 (let ((value-declarations)
375 ;; Parse declarations
377 (do* ((rest body (cdr rest))
378 (form (car rest) (car rest)))
379 ((or (atom form) (not (eq (car form) 'declare)))
381 (push form value-declarations)))
385 (not (null (cdr body))))
386 (setq value-docstring (car body))
387 (setq body (cdr body)))
388 (values body value-declarations value-docstring)))
390 ;;; Compile a lambda function with lambda list LL and body BODY. If
391 ;;; NAME is given, it should be a constant string and it will become
392 ;;; the name of the function. If BLOCK is non-NIL, a named block is
393 ;;; created around the body. NOTE: No block (even anonymous) is
394 ;;; created if BLOCk is NIL.
395 (defun compile-lambda (ll body &key name block)
396 (multiple-value-bind (required-arguments
400 (parse-lambda-list ll)
401 (multiple-value-bind (body decls documentation)
402 (parse-body body :declarations t :docstring t)
403 (declare (ignore decls))
404 (let ((n-required-arguments (length required-arguments))
405 (n-optional-arguments (length optional-arguments))
406 (*environment* (extend-local-env
407 (append (ensure-list rest-argument)
412 (lambda-name/docstring-wrapper name documentation
413 `(function (|values| |nargs| ,@(mapcar (lambda (x)
414 (make-symbol (translate-variable x)))
415 (append required-arguments optional-arguments)))
416 ;; Check number of arguments
417 ,(lambda-check-argument-count n-required-arguments
419 (or rest-argument keyword-arguments))
420 ,(compile-lambda-optional ll)
421 ,(compile-lambda-rest ll)
423 ,(compile-lambda-parse-keywords ll))
425 ,(let ((*multiple-value-p* t))
427 (ls-compile-block `((block ,block ,@body)) t)
428 (ls-compile-block body t)))))))))
431 (defun setq-pair (var val)
432 (let ((b (lookup-in-lexenv var *environment* 'variable)))
435 (eq (binding-type b) 'variable)
436 (not (member 'special (binding-declarations b)))
437 (not (member 'constant (binding-declarations b))))
438 ;; TODO: Unnecesary make-symbol when codegen migration is
440 `(= ,(make-symbol (binding-value b)) ,(ls-compile val)))
441 ((and b (eq (binding-type b) 'macro))
442 (ls-compile `(setf ,var ,val)))
444 (ls-compile `(set ',var ,val))))))
447 (define-compilation setq (&rest pairs)
450 (return-from setq (ls-compile nil)))
456 (error "Odd pairs in SETQ"))
458 (push `,(setq-pair (car pairs) (cadr pairs)) result)
459 (setq pairs (cddr pairs)))))
460 `(progn ,@(reverse result))))
463 ;;; Compilation of literals an object dumping
465 ;;; BOOTSTRAP MAGIC: We record the macro definitions as lists during
466 ;;; the bootstrap. Once everything is compiled, we want to dump the
467 ;;; whole global environment to the output file to reproduce it in the
468 ;;; run-time. However, the environment must contain expander functions
469 ;;; rather than lists. We do not know how to dump function objects
470 ;;; itself, so we mark the list definitions with this object and the
471 ;;; compiler will be called when this object has to be dumped.
472 ;;; Backquote/unquote does a similar magic, but this use is exclusive.
474 ;;; Indeed, perhaps to compile the object other macros need to be
475 ;;; evaluated. For this reason we define a valid macro-function for
477 (defvar *magic-unquote-marker* (gensym "MAGIC-UNQUOTE"))
479 (setf (macro-function *magic-unquote-marker*)
480 (lambda (form &optional environment)
481 (declare (ignore environment))
484 (defvar *literal-table* nil)
485 (defvar *literal-counter* 0)
488 (incf *literal-counter*)
489 (concat "l" (integer-to-string *literal-counter*)))
491 (defun dump-symbol (symbol)
493 (let ((package (symbol-package symbol)))
494 (if (eq package (find-package "KEYWORD"))
495 `(new (call |Symbol| ,(dump-string (symbol-name symbol)) ,(dump-string (package-name package))))
496 `(new (call |Symbol| ,(dump-string (symbol-name symbol))))))
498 (let ((package (symbol-package symbol)))
500 `(new (call |Symbol| ,(dump-string (symbol-name symbol))))
501 (ls-compile `(intern ,(symbol-name symbol) ,(package-name package))))))
503 (defun dump-cons (cons)
504 (let ((head (butlast cons))
507 ,@(mapcar (lambda (x) `(code ,(literal x t))) head)
508 (code ,(literal (car tail) t))
509 (code ,(literal (cdr tail) t)))))
511 (defun dump-array (array)
512 (let ((elements (vector-to-list array)))
513 (list-to-vector (mapcar (lambda (x) `(code ,(literal x)))
516 (defun dump-string (string)
517 `(call |make_lisp_string| ,string))
519 (defun literal (sexp &optional recursive)
521 ((integerp sexp) (integer-to-string sexp))
522 ((floatp sexp) (float-to-string sexp))
523 ((characterp sexp) (js-escape-string (string sexp)))
525 (or (cdr (assoc sexp *literal-table* :test #'eql))
526 (let ((dumped (typecase sexp
527 (symbol (dump-symbol sexp))
528 (string (dump-string sexp))
530 ;; BOOTSTRAP MAGIC: See the root file
531 ;; jscl.lisp and the function
532 ;; `dump-global-environment' for futher
534 (if (eq (car sexp) *magic-unquote-marker*)
535 (ls-compile (second sexp))
537 (array (dump-array sexp)))))
538 (if (and recursive (not (symbolp sexp)))
540 (let ((jsvar (genlit)))
541 (push (cons sexp jsvar) *literal-table*)
542 (toplevel-compilation `(code "var " ,jsvar " = " ,dumped))
543 (when (keywordp sexp)
544 (toplevel-compilation `(code ,jsvar ".value = " ,jsvar)))
548 (define-compilation quote (sexp)
551 (define-compilation %while (pred &rest body)
553 `(while (!== ,(ls-compile pred) ,(ls-compile nil))
555 ; braces. Unnecesary when code
557 ,(ls-compile-block body))
558 `(return ,(ls-compile nil))))
560 (define-compilation function (x)
562 ((and (listp x) (eq (car x) 'lambda))
563 (compile-lambda (cadr x) (cddr x)))
564 ((and (listp x) (eq (car x) 'named-lambda))
565 (destructuring-bind (name ll &rest body) (cdr x)
566 (compile-lambda ll body
567 :name (symbol-name name)
570 (let ((b (lookup-in-lexenv x *environment* 'function)))
573 (ls-compile `(symbol-function ',x)))))))
576 (defun make-function-binding (fname)
577 (make-binding :name fname :type 'function :value (gvarname fname)))
579 (defun compile-function-definition (list)
580 (compile-lambda (car list) (cdr list)))
582 (defun translate-function (name)
583 (let ((b (lookup-in-lexenv name *environment* 'function)))
584 (and b (binding-value b))))
586 (define-compilation flet (definitions &rest body)
587 (let* ((fnames (mapcar #'car definitions))
588 (cfuncs (mapcar (lambda (def)
589 (compile-lambda (cadr def)
594 (extend-lexenv (mapcar #'make-function-binding fnames)
597 `(call (function ,(mapcar #'make-symbol (mapcar #'translate-function fnames))
598 ,(ls-compile-block body t))
601 (define-compilation labels (definitions &rest body)
602 (let* ((fnames (mapcar #'car definitions))
604 (extend-lexenv (mapcar #'make-function-binding fnames)
609 ,@(mapcar (lambda (func)
610 `(var (,(make-symbol (translate-function (car func)))
611 ,(compile-lambda (cadr func)
612 `((block ,(car func) ,@(cddr func)))))))
614 (ls-compile-block body t))))
617 (defvar *compiling-file* nil)
618 (define-compilation eval-when-compile (&rest body)
621 (eval (cons 'progn body))
623 (ls-compile `(progn ,@body))))
625 (defmacro define-transformation (name args form)
626 `(define-compilation ,name ,args
629 (define-compilation progn (&rest body)
630 (if (null (cdr body))
631 (ls-compile (car body) *multiple-value-p*)
633 ,@(append (mapcar #'ls-compile (butlast body))
634 (list (ls-compile (car (last body)) t))))))
636 (define-compilation macrolet (definitions &rest body)
637 (let ((*environment* (copy-lexenv *environment*)))
638 (dolist (def definitions)
639 (destructuring-bind (name lambda-list &body body) def
640 (let ((binding (make-binding :name name :type 'macro :value
641 (let ((g!form (gensym)))
643 (destructuring-bind ,lambda-list ,g!form
645 (push-to-lexenv binding *environment* 'function))))
646 (ls-compile `(progn ,@body) *multiple-value-p*)))
649 (defun special-variable-p (x)
650 (and (claimp x 'variable 'special) t))
652 ;;; Wrap CODE to restore the symbol values of the dynamic
653 ;;; bindings. BINDINGS is a list of pairs of the form
654 ;;; (SYMBOL . PLACE), where PLACE is a Javascript variable
655 ;;; name to initialize the symbol value and where to stored
657 (defun let-binding-wrapper (bindings body)
658 (when (null bindings)
659 (return-from let-binding-wrapper body))
664 (let ((s (ls-compile `',(car b))))
665 (collect `(= tmp (get ,s "value")))
666 (collect `(= (get ,s "value") ,(cdr b)))
667 (collect `(= ,(cdr b) tmp)))))
672 (let ((s (ls-compile `(quote ,(car b)))))
673 (collect `(= (get ,s "value") ,(cdr b)))))))))
675 (define-compilation let (bindings &rest body)
676 (let* ((bindings (mapcar #'ensure-list bindings))
677 (variables (mapcar #'first bindings))
678 (cvalues (mapcar #'ls-compile (mapcar #'second bindings)))
679 (*environment* (extend-local-env (remove-if #'special-variable-p variables)))
681 `(call (function ,(mapcar (lambda (x)
682 (if (special-variable-p x)
683 (let ((v (gvarname x)))
684 (push (cons x (make-symbol v)) dynamic-bindings)
686 (make-symbol (translate-variable x))))
688 ,(let ((body (ls-compile-block body t t)))
689 `,(let-binding-wrapper dynamic-bindings body)))
693 ;;; Return the code to initialize BINDING, and push it extending the
694 ;;; current lexical environment if the variable is not special.
695 (defun let*-initialize-value (binding)
696 (let ((var (first binding))
697 (value (second binding)))
698 (if (special-variable-p var)
699 `(code ,(ls-compile `(setq ,var ,value)) ";" )
700 (let* ((v (gvarname var))
701 (b (make-binding :name var :type 'variable :value v)))
702 (prog1 `(code "var " ,v " = " ,(ls-compile value) ";" )
703 (push-to-lexenv b *environment* 'variable))))))
705 ;;; Wrap BODY to restore the symbol values of SYMBOLS after body. It
706 ;;; DOES NOT generate code to initialize the value of the symbols,
707 ;;; unlike let-binding-wrapper.
708 (defun let*-binding-wrapper (symbols body)
710 (return-from let*-binding-wrapper body))
711 (let ((store (mapcar (lambda (s) (cons s (gvarname s)))
712 (remove-if-not #'special-variable-p symbols))))
716 ,@(mapcar (lambda (b)
717 (let ((s (ls-compile `(quote ,(car b)))))
718 `(code "var " ,(cdr b) " = " ,s ".value;" )))
724 ,@(mapcar (lambda (b)
725 (let ((s (ls-compile `(quote ,(car b)))))
726 `(code ,s ".value" " = " ,(cdr b) ";" )))
730 (define-compilation let* (bindings &rest body)
731 (let ((bindings (mapcar #'ensure-list bindings))
732 (*environment* (copy-lexenv *environment*)))
734 (let ((specials (remove-if-not #'special-variable-p (mapcar #'first bindings)))
735 (body `(code ,@(mapcar #'let*-initialize-value bindings)
736 ,(ls-compile-block body t t))))
737 (let*-binding-wrapper specials body)))))
740 (define-compilation block (name &rest body)
741 ;; We use Javascript exceptions to implement non local control
742 ;; transfer. Exceptions has dynamic scoping, so we use a uniquely
743 ;; generated object to identify the block. The instance of a empty
744 ;; array is used to distinguish between nested dynamic Javascript
745 ;; exceptions. See https://github.com/davazp/jscl/issues/64 for
747 (let* ((idvar (gvarname name))
748 (b (make-binding :name name :type 'block :value idvar)))
749 (when *multiple-value-p*
750 (push 'multiple-value (binding-declarations b)))
751 (let* ((*environment* (extend-lexenv (list b) *environment* 'block))
752 (cbody (ls-compile-block body t)))
753 (if (member 'used (binding-declarations b))
756 "var " idvar " = [];"
760 " if (cf.type == 'block' && cf.id == " idvar ")"
761 (if *multiple-value-p*
762 " return values.apply(this, forcemv(cf.values));"
763 " return cf.values;")
768 (js!selfcall cbody)))))
770 (define-compilation return-from (name &optional value)
771 (let* ((b (lookup-in-lexenv name *environment* 'block))
772 (multiple-value-p (member 'multiple-value (binding-declarations b))))
774 (error "Return from unknown block `~S'." (symbol-name name)))
775 (push 'used (binding-declarations b))
776 ;; The binding value is the name of a variable, whose value is the
777 ;; unique identifier of the block as exception. We can't use the
778 ;; variable name itself, because it could not to be unique, so we
779 ;; capture it in a closure.
781 (when multiple-value-p `(code "var values = mv;" ))
784 "id: " (binding-value b) ", "
785 "values: " (ls-compile value multiple-value-p) ", "
786 "message: 'Return from unknown block " (symbol-name name) ".'"
789 (define-compilation catch (id &rest body)
791 `(var (|id| ,(ls-compile id)))
793 ,(ls-compile-block body t))
795 (if (and (== (get |cf| "type") "catch")
796 (== (get |cf| "id") |id|))
797 ,(if *multiple-value-p*
798 `(return (call (get |values| "apply")
800 (call |forcemv| (get |cf| "values"))))
801 `(return (call (get |pv| "apply")
803 (call |forcemv| (get |cf| "values")))))
806 (define-compilation throw (id value)
808 `(var (|values| |mv|))
811 |id| ,(ls-compile id)
812 |values| ,(ls-compile value t)
813 |message| "Throw uncatched."))))
816 (or (integerp x) (symbolp x)))
818 (defun declare-tagbody-tags (tbidx body)
819 (let* ((go-tag-counter 0)
821 (mapcar (lambda (label)
822 (let ((tagidx (integer-to-string (incf go-tag-counter))))
823 (make-binding :name label :type 'gotag :value (list tbidx tagidx))))
824 (remove-if-not #'go-tag-p body))))
825 (extend-lexenv bindings *environment* 'gotag)))
827 (define-compilation tagbody (&rest body)
828 ;; Ignore the tagbody if it does not contain any go-tag. We do this
829 ;; because 1) it is easy and 2) many built-in forms expand to a
830 ;; implicit tagbody, so we save some space.
831 (unless (some #'go-tag-p body)
832 (return-from tagbody (ls-compile `(progn ,@body nil))))
833 ;; The translation assumes the first form in BODY is a label
834 (unless (go-tag-p (car body))
835 (push (gensym "START") body))
836 ;; Tagbody compilation
837 (let ((branch (gvarname 'branch))
838 (tbidx (gvarname 'tbidx)))
839 (let ((*environment* (declare-tagbody-tags tbidx body))
841 (let ((b (lookup-in-lexenv (first body) *environment* 'gotag)))
842 (setq initag (second (binding-value b))))
844 ;; TAGBODY branch to take
845 "var " branch " = " initag ";"
846 "var " tbidx " = [];"
850 ,(let ((content nil))
851 `(code "switch(" ,branch "){"
853 ,@(dolist (form (cdr body) (reverse content))
854 (push (if (not (go-tag-p form))
855 `(code ,(ls-compile form) ";" )
856 (let ((b (lookup-in-lexenv form *environment* 'gotag)))
857 `(code "case " ,(second (binding-value b)) ":" )))
864 " if (jump.type == 'tagbody' && jump.id == " ,tbidx ")"
865 " " ,branch " = jump.label;"
870 "return " (ls-compile nil) ";" ))))
872 (define-compilation go (label)
873 (let ((b (lookup-in-lexenv label *environment* 'gotag))
875 ((symbolp label) (symbol-name label))
876 ((integerp label) (integer-to-string label)))))
878 (error "Unknown tag `~S'" label))
882 "id: " (first (binding-value b)) ", "
883 "label: " (second (binding-value b)) ", "
884 "message: 'Attempt to GO to non-existing tag " n "'"
887 (define-compilation unwind-protect (form &rest clean-up)
889 `(var (|ret| ,(ls-compile nil)))
891 (= |ret| ,(ls-compile form)))
893 ,(ls-compile-block clean-up))
896 (define-compilation multiple-value-call (func-form &rest forms)
898 "var func = " (ls-compile func-form) ";"
899 "var args = [" (if *multiple-value-p* "values" "pv") ", 0];"
905 ,@(mapcar (lambda (form)
906 `(code "vs = " ,(ls-compile form t) ";"
907 "if (typeof vs === 'object' && 'multiple-value' in vs)"
908 (code " args = args.concat(vs);" )
910 (code "args.push(vs);" )))
912 "args[1] = args.length-2;"
913 "return func.apply(window, args);" ) ";" ))
915 (define-compilation multiple-value-prog1 (first-form &rest forms)
917 "var args = " (ls-compile first-form *multiple-value-p*) ";"
918 (ls-compile-block forms)
921 (define-transformation backquote (form)
922 (bq-completely-process form))
927 (defvar *builtins* nil)
929 (defmacro define-raw-builtin (name args &body body)
930 ;; Creates a new primitive function `name' with parameters args and
931 ;; @body. The body can access to the local environment through the
932 ;; variable *ENVIRONMENT*.
933 `(push (list ',name (lambda ,args (block ,name ,@body)))
936 (defmacro define-builtin (name args &body body)
937 `(define-raw-builtin ,name ,args
938 (let ,(mapcar (lambda (arg) `(,arg (ls-compile ,arg))) args)
941 ;;; DECLS is a list of (JSVARNAME TYPE LISPFORM) declarations.
942 (defmacro type-check (decls &body body)
944 ,@(mapcar (lambda (decl)
945 `(let ((name ,(first decl))
946 (value ,(third decl)))
947 `(code "var " ,name " = " ,value ";" )))
949 ,@(mapcar (lambda (decl)
950 `(let ((name ,(first decl))
951 (type ,(second decl)))
952 `(code "if (typeof " ,name " != '" ,type "')"
953 (code "throw 'The value ' + "
955 " + ' is not a type "
960 `(code "return " ,,@body ";" )))
962 ;;; VARIABLE-ARITY compiles variable arity operations. ARGS stands for
963 ;;; a variable which holds a list of forms. It will compile them and
964 ;;; store the result in some Javascript variables. BODY is evaluated
965 ;;; with ARGS bound to the list of these variables to generate the
966 ;;; code which performs the transformation on these variables.
968 (defun variable-arity-call (args function)
970 (error "ARGS must be a non-empty list"))
976 ((or (floatp x) (numberp x)) (push x fargs))
977 (t (let ((v (make-symbol (code "x" (incf counter)))))
979 (push `(code "var " ,v " = " ,(ls-compile x) ";"
980 "if (typeof " ,v " !== 'number') throw 'Not a number!';")
983 `(code ,@(reverse prelude))
984 (funcall function (reverse fargs)))))
987 (defmacro variable-arity (args &body body)
988 (unless (symbolp args)
989 (error "`~S' is not a symbol." args))
990 `(variable-arity-call ,args
992 `(code "return " ,,@body ";" ))))
994 (defun num-op-num (x op y)
995 (type-check (("x" "number" x) ("y" "number" y))
996 `(code "x" ,op "y")))
998 (define-raw-builtin + (&rest numbers)
1001 (variable-arity numbers
1004 (define-raw-builtin - (x &rest others)
1005 (let ((args (cons x others)))
1006 (variable-arity args `(- ,@args))))
1008 (define-raw-builtin * (&rest numbers)
1011 (variable-arity numbers `(* ,@numbers))))
1013 (define-raw-builtin / (x &rest others)
1014 (let ((args (cons x others)))
1015 (variable-arity args
1018 (reduce (lambda (x y) `(/ ,x ,y))
1021 (define-builtin mod (x y) (num-op-num x "%" y))
1024 (defun comparison-conjuntion (vars op)
1029 `(,op ,(car vars) ,(cadr vars)))
1031 `(and (,op ,(car vars) ,(cadr vars))
1032 ,(comparison-conjuntion (cdr vars) op)))))
1034 (defmacro define-builtin-comparison (op sym)
1035 `(define-raw-builtin ,op (x &rest args)
1036 (let ((args (cons x args)))
1037 (variable-arity args
1038 (js!bool (comparison-conjuntion args ',sym))))))
1040 (define-builtin-comparison > >)
1041 (define-builtin-comparison < <)
1042 (define-builtin-comparison >= >=)
1043 (define-builtin-comparison <= <=)
1044 (define-builtin-comparison = ==)
1045 (define-builtin-comparison /= !=)
1047 (define-builtin numberp (x)
1048 (js!bool `(== (typeof ,x) "number")))
1050 (define-builtin floor (x)
1051 (type-check (("x" "number" x))
1054 (define-builtin expt (x y)
1055 (type-check (("x" "number" x)
1059 (define-builtin float-to-string (x)
1060 (type-check (("x" "number" x))
1061 "make_lisp_string(x.toString())"))
1063 (define-builtin cons (x y)
1064 `(object "car" ,x "cdr" ,y))
1066 (define-builtin consp (x)
1070 "return (typeof tmp == 'object' && 'car' in tmp);" )))
1072 (define-builtin car (x)
1075 `(return (if (=== tmp ,(ls-compile nil))
1079 (define-builtin cdr (x)
1082 `(return (if (=== tmp ,(ls-compile nil))
1086 (define-builtin rplaca (x new)
1087 (type-check (("x" "object" x))
1088 `(code "(x.car = " ,new ", x)")))
1090 (define-builtin rplacd (x new)
1091 (type-check (("x" "object" x))
1092 `(code "(x.cdr = " ,new ", x)")))
1094 (define-builtin symbolp (x)
1095 (js!bool `(instanceof ,x |Symbol|)))
1097 (define-builtin make-symbol (name)
1098 `(new (call |Symbol| ,name)))
1100 (define-builtin symbol-name (x)
1103 (define-builtin set (symbol value)
1104 `(= (get ,symbol "value") ,value))
1106 (define-builtin fset (symbol value)
1107 `(= (get ,symbol "fvalue") ,value))
1109 (define-builtin boundp (x)
1110 (js!bool `(!== (get ,x "value") undefined)))
1112 (define-builtin fboundp (x)
1113 (js!bool `(!== (get ,x "fvalue") undefined)))
1115 (define-builtin symbol-value (x)
1118 (value (get symbol "value")))
1119 `(if (=== value undefined)
1120 (throw (+ "Variable `" (call |xstring| (get symbol "name")) "' is unbound.")))
1123 (define-builtin symbol-function (x)
1126 (func (get symbol "fvalue")))
1127 `(if (=== func undefined)
1128 (throw (+ "Function `" (call |xstring| (get symbol "name")) "' is undefined.")))
1131 (define-builtin symbol-plist (x)
1132 `(or (get ,x "plist") ,(ls-compile nil)))
1134 (define-builtin lambda-code (x)
1135 `(call |make_lisp_string| (call (get ,x "toString"))))
1137 (define-builtin eq (x y)
1138 (js!bool `(=== ,x ,y)))
1140 (define-builtin char-code (x)
1141 (type-check (("x" "string" x))
1142 "char_to_codepoint(x)"))
1144 (define-builtin code-char (x)
1145 (type-check (("x" "number" x))
1146 "char_from_codepoint(x)"))
1148 (define-builtin characterp (x)
1152 `(return (and (== (typeof x) "string")
1153 (or (== (get x "length") 1)
1154 (== (get x "length") 2)))))))
1156 (define-builtin char-upcase (x)
1157 `(call |safe_char_upcase| ,x))
1159 (define-builtin char-downcase (x)
1160 `(call |safe_char_downcase| ,x))
1162 (define-builtin stringp (x)
1166 `(return (and (and (===(typeof x) "object")
1168 (== (get x "stringp") 1))))))
1170 (define-raw-builtin funcall (func &rest args)
1172 `(var (f ,(ls-compile func)))
1173 `(return (call (if (=== (typeof f) "function")
1176 ,@(list* (if *multiple-value-p* '|values| '|pv|)
1178 (mapcar #'ls-compile args))))))
1180 (define-raw-builtin apply (func &rest args)
1182 `(code "(" ,(ls-compile func) ")()")
1183 (let ((args (butlast args))
1184 (last (car (last args))))
1186 "var f = " (ls-compile func) ";"
1187 "var args = [" `(code
1188 ,@(interleave (list* (if *multiple-value-p* "values" "pv")
1189 (integer-to-string (length args))
1190 (mapcar #'ls-compile args))
1193 "var tail = (" (ls-compile last) ");"
1194 "while (tail != " (ls-compile nil) "){"
1195 " args.push(tail.car);"
1199 "return (typeof f === 'function'? f : f.fvalue).apply(this, args);" ))))
1201 (define-builtin js-eval (string)
1202 (if *multiple-value-p*
1204 `(var (v (call |globalEval| (call |xstring| ,string))))
1205 `(return (call (get |values| "apply") this (call |forcemv| v))))
1206 `(call |globalEval| (call |xstring| ,string))))
1208 (define-builtin %throw (string)
1209 (js!selfcall* `(throw ,string)))
1211 (define-builtin functionp (x)
1212 (js!bool `(=== (typeof ,x) "function")))
1214 (define-builtin %write-string (x)
1215 `(call (get |lisp| "write") ,x))
1217 (define-builtin /debug (x)
1218 `(call (get |console| "log") (call |xstring| ,x)))
1221 ;;; Storage vectors. They are used to implement arrays and (in the
1222 ;;; future) structures.
1224 (define-builtin storage-vector-p (x)
1228 `(return (and (=== (typeof x) "object") (in "length" x))))))
1230 (define-builtin make-storage-vector (n)
1233 `(= (get r "length") ,n)
1236 (define-builtin storage-vector-size (x)
1239 (define-builtin resize-storage-vector (vector new-size)
1240 `(= (get ,vector "length") ,new-size))
1242 (define-builtin storage-vector-ref (vector n)
1244 `(var (x (property ,vector ,n)))
1245 `(if (=== x undefined) (throw "Out of range."))
1248 (define-builtin storage-vector-set (vector n value)
1252 `(if (or (< i 0) (>= i (get x "length")))
1253 (throw "Out of range."))
1254 `(return (= (property x i) ,value))))
1256 (define-builtin concatenate-storage-vector (sv1 sv2)
1259 `(var (r (call (get sv1 "concat") ,sv2)))
1260 `(= (get r "type") (get sv1 "type"))
1261 `(= (get r "stringp") (get sv1 "stringp"))
1264 (define-builtin get-internal-real-time ()
1265 `(call (get (new (call |Date|)) "getTime")))
1267 (define-builtin values-array (array)
1268 (if *multiple-value-p*
1269 `(call (get |values| "apply") this ,array)
1270 `(call (get |pv| "apply") this ,array)))
1272 (define-raw-builtin values (&rest args)
1273 (if *multiple-value-p*
1274 `(call |values| ,@(mapcar #'ls-compile args))
1275 `(call |pv| ,@(mapcar #'ls-compile args))))
1279 (define-builtin new ()
1282 (define-raw-builtin oget* (object key &rest keys)
1285 (var (tmp (property ,(ls-compile object) (call |xstring| ,(ls-compile key)))))
1286 ,@(mapcar (lambda (key)
1288 (if (=== tmp undefined) (return ,(ls-compile nil)))
1289 (= tmp (property tmp (call |xstring| ,(ls-compile key))))))
1291 `(return (if (=== tmp undefined) ,(ls-compile nil) tmp))))
1293 (define-raw-builtin oset* (value object key &rest keys)
1294 (let ((keys (cons key keys)))
1297 (var (obj ,(ls-compile object)))
1298 ,@(mapcar (lambda (key)
1300 (= obj (property obj (call |xstring| ,(ls-compile key))))
1301 (if (=== object undefined)
1302 (throw "Impossible to set object property."))))
1305 (= (property obj (call |xstring| ,(ls-compile (car (last keys)))))
1306 ,(ls-compile value))))
1307 (return (if (=== tmp undefined)
1311 (define-raw-builtin oget (object key &rest keys)
1312 `(call |js_to_lisp| ,(ls-compile `(oget* ,object ,key ,@keys))))
1314 (define-raw-builtin oset (value object key &rest keys)
1315 (ls-compile `(oset* (lisp-to-js ,value) ,object ,key ,@keys)))
1317 (define-builtin objectp (x)
1318 (js!bool `(=== (typeof ,x) "object")))
1320 (define-builtin lisp-to-js (x) `(call |lisp_to_js| ,x))
1321 (define-builtin js-to-lisp (x) `(call |js_to_lisp| ,x))
1324 (define-builtin in (key object)
1325 (js!bool `(in (call |xstring| ,key) ,object)))
1327 (define-builtin map-for-in (function object)
1330 (g (if (=== (typeof f) "function") f (get f "fvalue")))
1333 (call g ,(if *multiple-value-p* '|values| '|pv|) 1 (get o "key")))
1334 `(return ,(ls-compile nil))))
1336 (define-compilation %js-vref (var)
1337 `(call |js_to_lisp| ,(make-symbol var)))
1339 (define-compilation %js-vset (var val)
1340 `(= ,(make-symbol var) (call |lisp_to_js| ,(ls-compile val))))
1342 (define-setf-expander %js-vref (var)
1343 (let ((new-value (gensym)))
1344 (unless (stringp var)
1345 (error "`~S' is not a string." var))
1349 `(%js-vset ,var ,new-value)
1354 (defvar *macroexpander-cache*
1355 (make-hash-table :test #'eq))
1357 (defun !macro-function (symbol)
1358 (unless (symbolp symbol)
1359 (error "`~S' is not a symbol." symbol))
1360 (let ((b (lookup-in-lexenv symbol *environment* 'function)))
1361 (if (and b (eq (binding-type b) 'macro))
1362 (let ((expander (binding-value b)))
1365 ((gethash b *macroexpander-cache*)
1366 (setq expander (gethash b *macroexpander-cache*)))
1368 (let ((compiled (eval expander)))
1369 ;; The list representation are useful while
1370 ;; bootstrapping, as we can dump the definition of the
1371 ;; macros easily, but they are slow because we have to
1372 ;; evaluate them and compile them now and again. So, let
1373 ;; us replace the list representation version of the
1374 ;; function with the compiled one.
1376 #+jscl (setf (binding-value b) compiled)
1377 #-jscl (setf (gethash b *macroexpander-cache*) compiled)
1378 (setq expander compiled))))
1382 (defun !macroexpand-1 (form)
1385 (let ((b (lookup-in-lexenv form *environment* 'variable)))
1386 (if (and b (eq (binding-type b) 'macro))
1387 (values (binding-value b) t)
1388 (values form nil))))
1389 ((and (consp form) (symbolp (car form)))
1390 (let ((macrofun (!macro-function (car form))))
1392 (values (funcall macrofun (cdr form)) t)
1393 (values form nil))))
1395 (values form nil))))
1397 (defun compile-funcall (function args)
1398 (let* ((values-funcs (if *multiple-value-p* "values" "pv"))
1399 (arglist `(code "(" ,@(interleave (list* values-funcs
1400 (integer-to-string (length args))
1401 (mapcar #'ls-compile args))
1404 (unless (or (symbolp function)
1405 (and (consp function)
1406 (member (car function) '(lambda oget))))
1407 (error "Bad function designator `~S'" function))
1409 ((translate-function function)
1410 `(code ,(translate-function function) ,arglist))
1411 ((and (symbolp function)
1412 #+jscl (eq (symbol-package function) (find-package "COMMON-LISP"))
1414 `(code ,(ls-compile `',function) ".fvalue" ,arglist))
1415 #+jscl((symbolp function)
1416 `(code ,(ls-compile `#',function) ,arglist))
1417 ((and (consp function) (eq (car function) 'lambda))
1418 `(code ,(ls-compile `#',function) ,arglist))
1419 ((and (consp function) (eq (car function) 'oget))
1420 `(code ,(ls-compile function) ,arglist))
1422 (error "Bad function descriptor")))))
1424 (defun ls-compile-block (sexps &optional return-last-p decls-allowed-p)
1425 (multiple-value-bind (sexps decls)
1426 (parse-body sexps :declarations decls-allowed-p)
1427 (declare (ignore decls))
1429 `(code ,(ls-compile-block (butlast sexps) nil decls-allowed-p)
1430 "return " ,(ls-compile (car (last sexps)) *multiple-value-p*) ";")
1432 ,@(interleave (mapcar #'ls-compile sexps) ";
1436 (defun ls-compile* (sexp &optional multiple-value-p)
1437 (multiple-value-bind (sexp expandedp) (!macroexpand-1 sexp)
1439 (return-from ls-compile* (ls-compile sexp multiple-value-p)))
1440 ;; The expression has been macroexpanded. Now compile it!
1441 (let ((*multiple-value-p* multiple-value-p))
1444 (let ((b (lookup-in-lexenv sexp *environment* 'variable)))
1446 ((and b (not (member 'special (binding-declarations b))))
1448 ((or (keywordp sexp)
1449 (and b (member 'constant (binding-declarations b))))
1450 `(code ,(ls-compile `',sexp) ".value"))
1452 (ls-compile `(symbol-value ',sexp))))))
1453 ((or (integerp sexp) (floatp sexp) (characterp sexp) (stringp sexp) (arrayp sexp))
1456 (let ((name (car sexp))
1460 ((assoc name *compilations*)
1461 (let ((comp (second (assoc name *compilations*))))
1463 ;; Built-in functions
1464 ((and (assoc name *builtins*)
1465 (not (claimp name 'function 'notinline)))
1466 (let ((comp (second (assoc name *builtins*))))
1469 (compile-funcall name args)))))
1471 (error "How should I compile `~S'?" sexp))))))
1473 (defun ls-compile (sexp &optional multiple-value-p)
1474 `(code "(" ,(ls-compile* sexp multiple-value-p) ")"))
1477 (defvar *compile-print-toplevels* nil)
1479 (defun truncate-string (string &optional (width 60))
1480 (let ((n (or (position #\newline string)
1481 (min width (length string)))))
1482 (subseq string 0 n)))
1484 (defun convert-toplevel (sexp &optional multiple-value-p)
1485 (let ((*toplevel-compilations* nil))
1487 ;; Non-empty toplevel progn
1489 (eq (car sexp) 'progn)
1492 ,@(mapcar (lambda (s) (convert-toplevel s t))
1495 (when *compile-print-toplevels*
1496 (let ((form-string (prin1-to-string sexp)))
1497 (format t "Compiling ~a..." (truncate-string form-string))))
1498 (let ((code (ls-compile sexp multiple-value-p)))
1500 ,@(interleave (get-toplevel-compilations) ";
1503 `(code ,code ";"))))))))
1505 (defun ls-compile-toplevel (sexp &optional multiple-value-p)
1506 (with-output-to-string (*standard-output*)
1507 (js (convert-toplevel sexp multiple-value-p))))