New special form: labels
[jscl.git] / ecmalisp.lisp
index c7097c6..62fe386 100644 (file)
 (progn
   (eval-when-compile
     (%compile-defmacro 'defmacro
 (progn
   (eval-when-compile
     (%compile-defmacro 'defmacro
-                       '(lambda (name args &rest body)
-                         `(eval-when-compile
-                            (%compile-defmacro ',name
-                                               '(lambda ,(mapcar (lambda (x)
-                                                                   (if (eq x '&body)
-                                                                       '&rest
-                                                                       x))
-                                                                 args)
-                                                 ,@body))))))
+                       '(function
+                         (lambda (name args &rest body)
+                          `(eval-when-compile
+                             (%compile-defmacro ',name
+                                                '(function
+                                                  (lambda ,(mapcar #'(lambda (x)
+                                                                       (if (eq x '&body)
+                                                                           '&rest
+                                                                           x))
+                                                                   args)
+                                                   ,@body))))))))
 
   (defmacro declaim (&rest decls)
     `(eval-when-compile
 
   (defmacro declaim (&rest decls)
     `(eval-when-compile
 
   (declaim (constant nil t) (special t nil))
   (setq nil 'nil)
 
   (declaim (constant nil t) (special t nil))
   (setq nil 'nil)
+  (js-vset "nil" nil)
   (setq t 't)
 
   (setq t 't)
 
+  (defmacro lambda (args &body body)
+    `(function (lambda ,args ,@body)))
+
   (defmacro when (condition &body body)
     `(if ,condition (progn ,@body) nil))
 
   (defmacro when (condition &body body)
     `(if ,condition (progn ,@body) nil))
 
@@ -71,7 +77,6 @@
 
   (defmacro defun (name args &rest body)
     `(progn
 
   (defmacro defun (name args &rest body)
     `(progn
-       (declaim (non-overridable ,name))
        (fset ',name
              (named-lambda ,(symbol-name name) ,args
                ,@(if (and (stringp (car body)) (not (null (cdr body))))
        (fset ',name
              (named-lambda ,(symbol-name name) ,args
                ,@(if (and (stringp (car body)) (not (null (cdr body))))
   (defun second (x) (cadr x))
   (defun third (x) (caddr x))
   (defun fourth (x) (cadddr x))
   (defun second (x) (cadr x))
   (defun third (x) (caddr x))
   (defun fourth (x) (cadddr x))
+  (defun rest (x) (cdr x))
 
   (defun list (&rest args) args)
   (defun atom (x)
 
   (defun list (&rest args) args)
   (defun atom (x)
   (defun reverse (list)
     (revappend list '()))
 
   (defun reverse (list)
     (revappend list '()))
 
+  (defmacro psetq (&rest pairs)
+    (let ( ;; For each pair, we store here a list of the form
+         ;; (VARIABLE GENSYM VALUE).
+         (assignments '()))
+      (while t
+       (cond
+         ((null pairs) (return))
+         ((null (cdr pairs))
+          (error "Odd paris in PSETQ"))
+         (t
+          (let ((variable (car pairs))
+                (value (cadr pairs)))
+            (push `(,variable ,(gensym) ,value)  assignments)
+            (setq pairs (cddr pairs))))))
+      (setq assignments (reverse assignments))
+      ;;
+      `(let ,(mapcar #'cdr assignments)
+        (setq ,@(!reduce #'append (mapcar #'butlast assignments) '())))))
+
+  (defmacro do (varlist endlist &body body)
+    `(block nil
+       (let ,(mapcar (lambda (x) (list (first x) (second x))) varlist)
+        (while t
+          (when ,(car endlist)
+            (return (progn ,(cdr endlist))))
+          (tagbody ,@body)
+          (psetq
+           ,@(apply #'append
+                    (mapcar (lambda (v)
+                              (and (consp (cddr v))
+                                   (list (first v) (third v))))
+                            varlist)))))))
+
+  (defmacro do* (varlist endlist &body body)
+    `(block nil
+       (let* ,(mapcar (lambda (x) (list (first x) (second x))) varlist)
+        (while t
+          (when ,(car endlist)
+            (return (progn ,(cdr endlist))))
+          (tagbody ,@body)
+          (setq
+           ,@(apply #'append
+                    (mapcar (lambda (v)
+                              (and (consp (cddr v))
+                                   (list (first v) (third v))))
+                            varlist)))))))
+
   (defun list-length (list)
     (let ((l 0))
       (while (not (null list))
   (defun list-length (list)
     (let ((l 0))
       (while (not (null list))
       (t
        (error "Unsupported argument."))))
 
       (t
        (error "Unsupported argument."))))
 
-  (defun parse-integer (string)
-    (let ((value 0)
-          (index 0)
-          (size (length string)))
-      (while (< index size)
-        (setq value (+ (* value 10) (digit-char-p (char string index))))
-        (incf index))
-      value))
-
   (defun some (function seq)
     (cond
       ((stringp seq)
   (defun some (function seq)
     (cond
       ((stringp seq)
          (error "Wrong argument type! it should be a symbol"))
        (oget x "vardoc"))))
 
          (error "Wrong argument type! it should be a symbol"))
        (oget x "vardoc"))))
 
+  (defmacro multiple-value-bind (variables value-from &body body)
+    `(multiple-value-call (lambda (&optional ,@variables &rest ,(gensym))
+                            ,@body)
+       ,value-from))
+
+  (defmacro multiple-value-list (value-from)
+    `(multiple-value-call #'list ,value-from))
+
   ;; Packages
 
   (defvar *package-list* nil)
   ;; Packages
 
   (defvar *package-list* nil)
   ;; This function is used internally to initialize the CL package
   ;; with the symbols built during bootstrap.
   (defun %intern-symbol (symbol)
   ;; This function is used internally to initialize the CL package
   ;; with the symbols built during bootstrap.
   (defun %intern-symbol (symbol)
-    (let ((symbols (%package-symbols *common-lisp-package*)))
-      (oset symbol "package" *common-lisp-package*)
+    (let* ((package
+            (if (in "package" symbol)
+                (find-package-or-fail (oget symbol "package"))
+                *common-lisp-package*))
+           (symbols (%package-symbols package)))
+      (oset symbol "package" package)
+      (when (eq package *keyword-package*)
+        (oset symbol "value" symbol))
       (oset symbols (symbol-name symbol) symbol)))
 
       (oset symbols (symbol-name symbol) symbol)))
 
-  (defun %find-symbol (name package)
-    (let ((package (find-package-or-fail package)))
-      (let ((symbols (%package-symbols package)))
-        (if (in name symbols)
-            (cons (oget symbols name) t)
-            (dolist (used (package-use-list package) (cons nil nil))
-              (let ((exports (%package-external-symbols used)))
-                (when (in name exports)
-                  (return-from %find-symbol
-                    (cons (oget exports name) t)))))))))
-
   (defun find-symbol (name &optional (package *package*))
   (defun find-symbol (name &optional (package *package*))
-    (car (%find-symbol name package)))
+    (let* ((package (find-package-or-fail package))
+           (externals (%package-external-symbols package))
+           (symbols (%package-symbols package)))
+      (cond
+        ((in name externals)
+         (values (oget externals name) :external))
+        ((in name symbols)
+         (values (oget symbols name) :internal))
+        (t
+         (dolist (used (package-use-list package) (values nil nil))
+           (let ((exports (%package-external-symbols used)))
+             (when (in name exports)
+               (return (values (oget exports name) :inherit)))))))))
 
   (defun intern (name &optional (package *package*))
     (let ((package (find-package-or-fail package)))
 
   (defun intern (name &optional (package *package*))
     (let ((package (find-package-or-fail package)))
-      (let ((result (%find-symbol name package)))
-        (if (cdr result)
-            (car result)
+      (multiple-value-bind (symbol foundp)
+          (find-symbol name package)
+        (if foundp
+            (values symbol foundp)
             (let ((symbols (%package-symbols package)))
               (oget symbols name)
               (let ((symbol (make-symbol name)))
             (let ((symbols (%package-symbols package)))
               (oget symbols name)
               (let ((symbol (make-symbol name)))
                 (when (eq package *keyword-package*)
                   (oset symbol "value" symbol)
                   (export (list symbol) package))
                 (when (eq package *keyword-package*)
                   (oset symbol "value" symbol)
                   (export (list symbol) package))
-                (oset symbols name symbol)))))))
+                (oset symbols name symbol)
+                (values symbol nil)))))))
 
   (defun symbol-package (symbol)
     (unless (symbolp symbol)
 
   (defun symbol-package (symbol)
     (unless (symbolp symbol)
   (defun export (symbols &optional (package *package*))
     (let ((exports (%package-external-symbols package)))
       (dolist (symb symbols t)
   (defun export (symbols &optional (package *package*))
     (let ((exports (%package-external-symbols package)))
       (dolist (symb symbols t)
-        (oset exports (symbol-name symb) symb)))))
+        (oset exports (symbol-name symb) symb))))
+
+  (defun get-universal-time ()
+    (+ (get-unix-time) 2208988800)))
 
 
 ;;; The compiler offers some primitives and special forms which are
 
 
 ;;; The compiler offers some primitives and special forms which are
   (defun concat-two (s1 s2)
     (concatenate 'string s1 s2))
 
   (defun concat-two (s1 s2)
     (concatenate 'string s1 s2))
 
-  (defun setcar (cons new)
-    (setf (car cons) new))
-  (defun setcdr (cons new)
-    (setf (cdr cons) new))
-
   (defun aset (array idx value)
     (setf (aref array idx) value)))
 
   (defun aset (array idx value)
     (setf (aref array idx) value)))
 
       (aset v i x)
       (incf i))))
 
       (aset v i x)
       (incf i))))
 
+#+ecmalisp
+(progn
+  (defun values-list (list)
+    (values-array (list-to-vector list)))
+
+  (defun values (&rest args)
+    (values-list args)))
+
+
 ;;; Like CONCAT, but prefix each line with four spaces. Two versions
 ;;; of this function are available, because the Ecmalisp version is
 ;;; very slow and bootstraping was annoying.
 ;;; Like CONCAT, but prefix each line with four spaces. Two versions
 ;;; of this function are available, because the Ecmalisp version is
 ;;; very slow and bootstraping was annoying.
   (defun prin1-to-string (form)
     (cond
       ((symbolp form)
   (defun prin1-to-string (form)
     (cond
       ((symbolp form)
-       (if (cdr (%find-symbol (symbol-name form) *package*))
-           (symbol-name form)
-           (let ((package (symbol-package form))
-                 (name (symbol-name form)))
-             (concat (if (eq package (find-package "KEYWORD"))
-                         ""
-                         (package-name package))
-                     ":" name))))
+       (multiple-value-bind (symbol foundp)
+           (find-symbol (symbol-name form) *package*)
+         (if (and foundp (eq symbol form))
+             (symbol-name form)
+             (let ((package (symbol-package form))
+                   (name (symbol-name form)))
+               (concat (cond
+                         ((null package) "#")
+                         ((eq package (find-package "KEYWORD")) "")
+                         (t (package-name package)))
+                       ":" name)))))
       ((integerp form) (integer-to-string form))
       ((stringp form) (concat "\"" (escape-string form) "\""))
       ((functionp form)
       ((integerp form) (integer-to-string form))
       ((stringp form) (concat "\"" (escape-string form) "\""))
       ((functionp form)
 (defun %read-char (stream)
   (and (< (cdr stream) (length (car stream)))
        (prog1 (char (car stream) (cdr stream))
 (defun %read-char (stream)
   (and (< (cdr stream) (length (car stream)))
        (prog1 (char (car stream) (cdr stream))
-         (setcdr stream (1+ (cdr stream))))))
+         (rplacd stream (1+ (cdr stream))))))
 
 (defun whitespacep (ch)
   (or (char= ch #\space) (char= ch #\newline) (char= ch #\tab)))
 
 (defun whitespacep (ch)
   (or (char= ch #\space) (char= ch #\newline) (char= ch #\tab)))
   (ecase (%read-char stream)
     (#\'
      (list 'function (ls-read stream)))
   (ecase (%read-char stream)
     (#\'
      (list 'function (ls-read stream)))
+    (#\( (list-to-vector (%read-list stream)))
+    (#\: (make-symbol (string-upcase (read-until stream #'terminalp))))
     (#\\
      (let ((cname
             (concat (string (%read-char stream))
     (#\\
      (let ((cname
             (concat (string (%read-char stream))
         (intern name package)
         (find-symbol name package))))
 
         (intern name package)
         (find-symbol name package))))
 
+
+(defun !parse-integer (string junk-allow)
+  (block nil
+    (let ((value 0)
+         (index 0)
+         (size (length string))
+         (sign 1))
+      (when (zerop size) (return (values nil 0)))
+      ;; Optional sign
+      (case (char string 0)
+       (#\+ (incf index))
+       (#\- (setq sign -1)
+            (incf index)))
+      ;; First digit
+      (unless (and (< index size)
+                  (setq value (digit-char-p (char string index))))
+       (return (values nil index)))
+      (incf index)
+      ;; Other digits
+      (while (< index size)
+       (let ((digit (digit-char-p (char string index))))
+         (unless digit (return))
+         (setq value (+ (* value 10) digit))
+         (incf index)))
+      (if (or junk-allow
+             (= index size)
+             (char= (char string index) #\space))
+         (values (* sign value) index)
+         (values nil index)))))
+
+#+ecmalisp
+(defun parse-integer (string)
+  (!parse-integer string nil))
+
 (defvar *eof* (gensym))
 (defun ls-read (stream)
   (skip-whitespaces-and-comments stream)
 (defvar *eof* (gensym))
 (defun ls-read (stream)
   (skip-whitespaces-and-comments stream)
        (read-sharp stream))
       (t
        (let ((string (read-until stream #'terminalp)))
        (read-sharp stream))
       (t
        (let ((string (read-until stream #'terminalp)))
-         (if (every #'digit-char-p string)
-             (parse-integer string)
-             (read-symbol string)))))))
+        (or (values (!parse-integer string nil))
+            (read-symbol string)))))))
 
 (defun ls-read-from-string (string)
   (ls-read (make-string-stream string)))
 
 (defun ls-read-from-string (string)
   (ls-read (make-string-stream string)))
 ;;; too. The respective real functions are defined in the target (see
 ;;; the beginning of this file) as well as some primitive functions.
 
 ;;; too. The respective real functions are defined in the target (see
 ;;; the beginning of this file) as well as some primitive functions.
 
-(defvar *compilation-unit-checks* '())
+;;; A Form can return a multiple values object calling VALUES, like
+;;; values(arg1, arg2, ...). It will work in any context, as well as
+;;; returning an individual object. However, if the special variable
+;;; `*multiple-value-p*' is NIL, is granted that only the primary
+;;; value will be used, so we can optimize to avoid the VALUES
+;;; function call.
+(defvar *multiple-value-p* nil)
+
 
 (defun make-binding (name type value &optional declarations)
   (list name type value declarations))
 
 (defun make-binding (name type value &optional declarations)
   (list name type value declarations))
 (defun binding-declarations (b) (fourth b))
 
 (defun set-binding-value (b value)
 (defun binding-declarations (b) (fourth b))
 
 (defun set-binding-value (b value)
-  (setcar (cddr b) value))
+  (rplaca (cddr b) value))
 
 (defun set-binding-declarations (b value)
 
 (defun set-binding-declarations (b value)
-  (setcar (cdddr b) value))
+  (rplaca (cdddr b) value))
 
 (defun push-binding-declaration (decl b)
   (set-binding-declarations b (cons decl (binding-declarations b))))
 
 (defun push-binding-declaration (decl b)
   (set-binding-declarations b (cons decl (binding-declarations b))))
 
 (defun push-to-lexenv (binding lexenv namespace)
   (ecase namespace
 
 (defun push-to-lexenv (binding lexenv namespace)
   (ecase namespace
-    (variable   (setcar        lexenv  (cons binding (car lexenv))))
-    (function   (setcar   (cdr lexenv) (cons binding (cadr lexenv))))
-    (block      (setcar  (cddr lexenv) (cons binding (caddr lexenv))))
-    (gotag      (setcar (cdddr lexenv) (cons binding (cadddr lexenv))))))
+    (variable   (rplaca        lexenv  (cons binding (car lexenv))))
+    (function   (rplaca   (cdr lexenv) (cons binding (cadr lexenv))))
+    (block      (rplaca  (cddr lexenv) (cons binding (caddr lexenv))))
+    (gotag      (rplaca (cdddr lexenv) (cons binding (cadddr lexenv))))))
 
 (defun extend-lexenv (bindings lexenv namespace)
   (let ((env (copy-lexenv lexenv)))
 
 (defun extend-lexenv (bindings lexenv namespace)
   (let ((env (copy-lexenv lexenv)))
 (defun extend-local-env (args)
   (let ((new (copy-lexenv *environment*)))
     (dolist (symbol args new)
 (defun extend-local-env (args)
   (let ((new (copy-lexenv *environment*)))
     (dolist (symbol args new)
-      (let ((b (make-binding symbol 'lexical-variable (gvarname symbol))))
+      (let ((b (make-binding symbol 'variable (gvarname symbol))))
         (push-to-lexenv b new 'variable)))))
 
 ;;; Toplevel compilations
         (push-to-lexenv b new 'variable)))))
 
 ;;; Toplevel compilations
 
 (defun %compile-defmacro (name lambda)
   (toplevel-compilation (ls-compile `',name))
 
 (defun %compile-defmacro (name lambda)
   (toplevel-compilation (ls-compile `',name))
-  (push-to-lexenv (make-binding name 'macro lambda) *environment* 'function))
+  (push-to-lexenv (make-binding name 'macro lambda) *environment* 'function)
+  name)
 
 (defun global-binding (name type namespace)
   (or (lookup-in-lexenv name *environment* namespace)
 
 (defun global-binding (name type namespace)
   (or (lookup-in-lexenv name *environment* namespace)
     (constant
      (dolist (name (cdr decl))
        (let ((b (global-binding name 'variable 'variable)))
     (constant
      (dolist (name (cdr decl))
        (let ((b (global-binding name 'variable 'variable)))
-         (push-binding-declaration 'constant b))))
-    (non-overridable
-     (dolist (name (cdr decl))
-       (let ((b (global-binding name 'function 'function)))
-         (push-binding-declaration 'non-overridable b))))))
+         (push-binding-declaration 'constant b))))))
 
 #+ecmalisp
 (fset 'proclaim #'!proclaim)
 
 #+ecmalisp
 (fset 'proclaim #'!proclaim)
 
 (define-compilation if (condition true false)
   (concat "(" (ls-compile condition) " !== " (ls-compile nil)
 
 (define-compilation if (condition true false)
   (concat "(" (ls-compile condition) " !== " (ls-compile nil)
-          " ? " (ls-compile true)
-          " : " (ls-compile false)
+          " ? " (ls-compile true *multiple-value-p*)
+          " : " (ls-compile false *multiple-value-p*)
           ")"))
 
 (defvar *lambda-list-keywords* '(&optional &rest))
           ")"))
 
 (defvar *lambda-list-keywords* '(&optional &rest))
       (error "Bad lambda-list"))
     (car rest)))
 
       (error "Bad lambda-list"))
     (car rest)))
 
-
 (defun lambda-docstring-wrapper (docstring &rest strs)
   (if docstring
       (js!selfcall
 (defun lambda-docstring-wrapper (docstring &rest strs)
   (if docstring
       (js!selfcall
         "return func;" *newline*)
       (join strs)))
 
         "return func;" *newline*)
       (join strs)))
 
-(define-compilation lambda (lambda-list &rest body)
+(defun lambda-check-argument-count
+    (n-required-arguments n-optional-arguments rest-p)
+  ;; Note: Remember that we assume that the number of arguments of a
+  ;; call is at least 1 (the values argument).
+  (let ((min (1+ n-required-arguments))
+        (max (if rest-p 'n/a (+ 1 n-required-arguments n-optional-arguments))))
+    (block nil
+      ;; Special case: a positive exact number of arguments.
+      (when (and (< 1 min) (eql min max))
+        (return (concat "checkArgs(arguments, " (integer-to-string min) ");" *newline*)))
+      ;; General case:
+      (concat
+       (if (< 1 min)
+           (concat "checkArgsAtLeast(arguments, " (integer-to-string min) ");" *newline*)
+           "")
+       (if (numberp max)
+           (concat "checkArgsAtMost(arguments, " (integer-to-string max) ");" *newline*)
+           "")))))
+
+(defun compile-lambda (lambda-list body)
   (let ((required-arguments (lambda-list-required-arguments lambda-list))
         (optional-arguments (lambda-list-optional-arguments lambda-list))
         (rest-argument (lambda-list-rest-argument lambda-list))
   (let ((required-arguments (lambda-list-required-arguments lambda-list))
         (optional-arguments (lambda-list-optional-arguments lambda-list))
         (rest-argument (lambda-list-rest-argument lambda-list))
       (lambda-docstring-wrapper
        documentation
        "(function ("
       (lambda-docstring-wrapper
        documentation
        "(function ("
-       (join (mapcar #'translate-variable
-                     (append required-arguments optional-arguments))
+       (join (cons "values"
+                   (mapcar #'translate-variable
+                           (append required-arguments optional-arguments)))
              ",")
        "){" *newline*
              ",")
        "){" *newline*
-       ;; Check number of arguments
        (indent
        (indent
-        (if required-arguments
-            (concat "if (arguments.length < " (integer-to-string n-required-arguments)
-                    ") throw 'too few arguments';" *newline*)
-            "")
-        (if (not rest-argument)
-            (concat "if (arguments.length > "
-                    (integer-to-string (+ n-required-arguments n-optional-arguments))
-                    ") throw 'too many arguments';" *newline*)
-            "")
+        ;; Check number of arguments
+        (lambda-check-argument-count n-required-arguments
+                                     n-optional-arguments
+                                     rest-argument)
         ;; Optional arguments
         (if optional-arguments
         ;; Optional arguments
         (if optional-arguments
-            (concat "switch(arguments.length){" *newline*
+            (concat "switch(arguments.length-1){" *newline*
                     (let ((optional-and-defaults
                            (lambda-list-optional-arguments-with-default lambda-list))
                           (cases nil)
                     (let ((optional-and-defaults
                            (lambda-list-optional-arguments-with-default lambda-list))
                           (cases nil)
             (let ((js!rest (translate-variable rest-argument)))
               (concat "var " js!rest "= " (ls-compile nil) ";" *newline*
                       "for (var i = arguments.length-1; i>="
             (let ((js!rest (translate-variable rest-argument)))
               (concat "var " js!rest "= " (ls-compile nil) ";" *newline*
                       "for (var i = arguments.length-1; i>="
-                      (integer-to-string (+ n-required-arguments n-optional-arguments))
+                      (integer-to-string (+ 1 n-required-arguments n-optional-arguments))
                       "; i--)" *newline*
                       (indent js!rest " = "
                               "{car: arguments[i], cdr: ") js!rest "};"
                       *newline*))
             "")
         ;; Body
                       "; i--)" *newline*
                       (indent js!rest " = "
                               "{car: arguments[i], cdr: ") js!rest "};"
                       *newline*))
             "")
         ;; Body
-        (ls-compile-block body t)) *newline*
+        (let ((*multiple-value-p* t)) (ls-compile-block body t)))
        "})"))))
 
        "})"))))
 
-(define-compilation setq (var val)
+
+(defun setq-pair (var val)
   (let ((b (lookup-in-lexenv var *environment* 'variable)))
   (let ((b (lookup-in-lexenv var *environment* 'variable)))
-    (if (eq (binding-type b) 'lexical-variable)
+    (if (and (eq (binding-type b) 'variable)
+             (not (member 'special (binding-declarations b)))
+             (not (member 'constant (binding-declarations b))))
         (concat (binding-value b) " = " (ls-compile val))
         (ls-compile `(set ',var ,val)))))
 
         (concat (binding-value b) " = " (ls-compile val))
         (ls-compile `(set ',var ,val)))))
 
+(define-compilation setq (&rest pairs)
+  (let ((result ""))
+    (while t
+      (cond
+       ((null pairs) (return))
+       ((null (cdr pairs))
+        (error "Odd paris in SETQ"))
+       (t
+        (concatf result
+          (concat (setq-pair (car pairs) (cadr pairs))
+                  (if (null (cddr pairs)) "" ", ")))
+        (setq pairs (cddr pairs)))))
+    (concat "(" result ")")))
+
 ;;; FFI Variable accessors
 (define-compilation js-vref (var)
   var)
 ;;; FFI Variable accessors
 (define-compilation js-vref (var)
   var)
   (concat "(" var " = " (ls-compile val) ")"))
 
 
   (concat "(" var " = " (ls-compile val) ")"))
 
 
+
 ;;; Literals
 (defun escape-string (string)
   (let ((output "")
 ;;; Literals
 (defun escape-string (string)
   (let ((output "")
     ((symbolp sexp)
      (or (cdr (assoc sexp *literal-symbols*))
         (let ((v (genlit))
     ((symbolp sexp)
      (or (cdr (assoc sexp *literal-symbols*))
         (let ((v (genlit))
-              (s #+common-lisp (concat "{name: \"" (escape-string (symbol-name sexp)) "\"}")
-                 #+ecmalisp (ls-compile
-                              `(intern ,(symbol-name sexp)
-                                       ,(package-name (symbol-package sexp))))))
+              (s #+common-lisp
+                 (let ((package (symbol-package sexp)))
+                   (if (eq package (find-package "KEYWORD"))
+                       (concat "{name: \"" (escape-string (symbol-name sexp))
+                               "\", 'package': '" (package-name package) "'}")
+                       (concat "{name: \"" (escape-string (symbol-name sexp)) "\"}")))
+                 #+ecmalisp
+                 (let ((package (symbol-package sexp)))
+                   (if (null package)
+                       (concat "{name: \"" (escape-string (symbol-name sexp)) "\"}")
+                       (ls-compile `(intern ,(symbol-name sexp) ,(package-name package)))))))
           (push (cons sexp v) *literal-symbols*)
           (toplevel-compilation (concat "var " v " = " s))
           v)))
     ((consp sexp)
           (push (cons sexp v) *literal-symbols*)
           (toplevel-compilation (concat "var " v " = " s))
           v)))
     ((consp sexp)
-     (let ((c (concat "{car: " (literal (car sexp) t) ", "
-                     "cdr: " (literal (cdr sexp) t) "}")))
+     (let* ((head (butlast sexp))
+            (tail (last sexp))
+            (c (concat "QIList("
+                       (join-trailing (mapcar (lambda (x) (literal x t)) head) ",")
+                       (literal (car tail) t)
+                       ","
+                       (literal (cdr tail) t)
+                       ")")))
        (if recursive
           c
           (let ((v (genlit)))
        (if recursive
           c
           (let ((v (genlit)))
-            (toplevel-compilation (concat "var " v " = " c))
-            v))))
+             (toplevel-compilation (concat "var " v " = " c))
+             v))))
     ((arrayp sexp)
      (let ((elements (vector-to-list sexp)))
        (let ((c (concat "[" (join (mapcar #'literal elements) ", ") "]")))
     ((arrayp sexp)
      (let ((elements (vector-to-list sexp)))
        (let ((c (concat "[" (join (mapcar #'literal elements) ", ") "]")))
 (define-compilation function (x)
   (cond
     ((and (listp x) (eq (car x) 'lambda))
 (define-compilation function (x)
   (cond
     ((and (listp x) (eq (car x) 'lambda))
-     (ls-compile x))
+     (compile-lambda (cadr x) (cddr x)))
     ((symbolp x)
      (ls-compile `(symbol-function ',x)))))
 
     ((symbolp x)
      (ls-compile `(symbol-function ',x)))))
 
+
+(defun make-function-binding (fname)
+  (make-binding fname 'function (gvarname fname)))
+
+(defun compile-function-definition (list)
+  (compile-lambda (car list) (cdr list)))
+
+(defun translate-function (name)
+  (let ((b (lookup-in-lexenv name *environment* 'function)))
+    (binding-value b)))
+
+(define-compilation flet (definitions &rest body)
+  (let* ((fnames (mapcar #'car definitions))
+         (fbody  (mapcar #'cdr definitions))
+         (cfuncs (mapcar #'compile-function-definition fbody))
+         (*environment*
+          (extend-lexenv (mapcar #'make-function-binding fnames)
+                         *environment*
+                         'function)))
+    (concat "(function("
+            (join (mapcar #'translate-function fnames) ",")
+            "){" *newline*
+            (let ((body (ls-compile-block body t)))
+              (indent body))
+            "})(" (join cfuncs ",") ")")))
+
+(define-compilation labels (definitions &rest body)
+  (let* ((fnames (mapcar #'car definitions))
+         (fbody  (mapcar #'cdr definitions))
+        (*environment*
+          (extend-lexenv (mapcar #'make-function-binding fnames)
+                         *environment*
+                         'function))
+         (cfuncs (mapcar #'compile-function-definition fbody)))
+    (concat "(function(){" *newline*
+           (join (mapcar (lambda (func)
+                           ())
+                         definitions))
+            (let ((body (ls-compile-block body t)))
+              (indent body))
+            "})")))
+
+
+
+(defvar *compiling-file* nil)
 (define-compilation eval-when-compile (&rest body)
 (define-compilation eval-when-compile (&rest body)
-  (eval (cons 'progn body))
-  nil)
+  (if *compiling-file*
+      (progn
+        (eval (cons 'progn body))
+        nil)
+      (ls-compile `(progn ,@body))))
 
 (defmacro define-transformation (name args form)
   `(define-compilation ,name ,args
      (ls-compile ,form)))
 
 (define-compilation progn (&rest body)
 
 (defmacro define-transformation (name args form)
   `(define-compilation ,name ,args
      (ls-compile ,form)))
 
 (define-compilation progn (&rest body)
-  (js!selfcall (ls-compile-block body t)))
+  (if (null (cdr body))
+      (ls-compile (car body) *multiple-value-p*)
+      (js!selfcall (ls-compile-block body t))))
 
 (defun special-variable-p (x)
 
 (defun special-variable-p (x)
-  (claimp x 'variable 'special))
+  (and (claimp x 'variable 'special) t))
 
 ;;; Wrap CODE to restore the symbol values of the dynamic
 ;;; bindings. BINDINGS is a list of pairs of the form
 
 ;;; Wrap CODE to restore the symbol values of the dynamic
 ;;; bindings. BINDINGS is a list of pairs of the form
    "}" *newline*))
 
 (define-compilation let (bindings &rest body)
    "}" *newline*))
 
 (define-compilation let (bindings &rest body)
-  (let ((bindings (mapcar #'ensure-list bindings)))
-    (let ((variables (mapcar #'first bindings)))
-      (let ((cvalues (mapcar #'ls-compile (mapcar #'second bindings)))
-            (*environment* (extend-local-env (remove-if #'special-variable-p variables)))
-            (dynamic-bindings))
-        (concat "(function("
-                (join (mapcar (lambda (x)
-                                (if (special-variable-p x)
-                                    (let ((v (gvarname x)))
-                                      (push (cons x v) dynamic-bindings)
-                                      v)
-                                    (translate-variable x)))
-                              variables)
-                      ",")
-                "){" *newline*
-                (let ((body (ls-compile-block body t)))
-                  (indent (let-binding-wrapper dynamic-bindings body)))
-                "})(" (join cvalues ",") ")")))))
+  (let* ((bindings (mapcar #'ensure-list bindings))
+         (variables (mapcar #'first bindings))
+         (cvalues (mapcar #'ls-compile (mapcar #'second bindings)))
+         (*environment* (extend-local-env (remove-if #'special-variable-p variables)))
+         (dynamic-bindings))
+    (concat "(function("
+            (join (mapcar (lambda (x)
+                            (if (special-variable-p x)
+                                (let ((v (gvarname x)))
+                                  (push (cons x v) dynamic-bindings)
+                                  v)
+                                (translate-variable x)))
+                          variables)
+                  ",")
+            "){" *newline*
+            (let ((body (ls-compile-block body t)))
+              (indent (let-binding-wrapper dynamic-bindings body)))
+            "})(" (join cvalues ",") ")")))
 
 
 ;;; Return the code to initialize BINDING, and push it extending the
 
 
 ;;; Return the code to initialize BINDING, and push it extending the
-;;; current lexical environment if the variable is special.
+;;; current lexical environment if the variable is not special.
 (defun let*-initialize-value (binding)
   (let ((var (first binding))
         (value (second binding)))
     (if (special-variable-p var)
         (concat (ls-compile `(setq ,var ,value)) ";" *newline*)
 (defun let*-initialize-value (binding)
   (let ((var (first binding))
         (value (second binding)))
     (if (special-variable-p var)
         (concat (ls-compile `(setq ,var ,value)) ";" *newline*)
-        (let ((v (gvarname var)))
-          (let ((b (make-binding var 'variable v)))
-            (prog1 (concat "var " v " = " (ls-compile value) ";" *newline*)
-              (push-to-lexenv b *environment* 'variable)))))))
+        (let* ((v (gvarname var))
+               (b (make-binding var 'variable v)))
+          (prog1 (concat "var " v " = " (ls-compile value) ";" *newline*)
+            (push-to-lexenv b *environment* 'variable))))))
 
 ;;; Wrap BODY to restore the symbol values of SYMBOLS after body. It
 ;;; DOES NOT generate code to initialize the value of the symbols,
 
 ;;; Wrap BODY to restore the symbol values of SYMBOLS after body. It
 ;;; DOES NOT generate code to initialize the value of the symbols,
                  store))
      "}" *newline*)))
 
                  store))
      "}" *newline*)))
 
-
 (define-compilation let* (bindings &rest body)
   (let ((bindings (mapcar #'ensure-list bindings))
         (*environment* (copy-lexenv *environment*)))
 (define-compilation let* (bindings &rest body)
   (let ((bindings (mapcar #'ensure-list bindings))
         (*environment* (copy-lexenv *environment*)))
 (defvar *block-counter* 0)
 
 (define-compilation block (name &rest body)
 (defvar *block-counter* 0)
 
 (define-compilation block (name &rest body)
-  (let ((tr (integer-to-string (incf *block-counter*))))
-    (let ((b (make-binding name 'block tr)))
-      (js!selfcall
-        "try {" *newline*
-        (let ((*environment* (extend-lexenv (list b) *environment* 'block)))
-          (indent "return " (ls-compile `(progn ,@body)) ";" *newline*))
-        "}" *newline*
-        "catch (cf){" *newline*
-        "    if (cf.type == 'block' && cf.id == " tr ")" *newline*
-        "        return cf.value;" *newline*
-        "    else" *newline*
-        "        throw cf;" *newline*
-        "}" *newline*))))
+  (let* ((tr (integer-to-string (incf *block-counter*)))
+         (b (make-binding name 'block tr)))
+    (when *multiple-value-p*
+      (push-binding-declaration 'multiple-value b))
+    (let* ((*environment* (extend-lexenv (list b) *environment* 'block))
+           (cbody (ls-compile-block body t)))
+      (if (member 'used (binding-declarations b))
+          (js!selfcall
+            "try {" *newline*
+            (indent cbody)
+            "}" *newline*
+            "catch (cf){" *newline*
+            "    if (cf.type == 'block' && cf.id == " tr ")" *newline*
+            (if *multiple-value-p*
+                "        return values.apply(this, forcemv(cf.values));"
+                "        return cf.values;")
+            *newline*
+            "    else" *newline*
+            "        throw cf;" *newline*
+            "}" *newline*)
+          (js!selfcall cbody)))))
 
 (define-compilation return-from (name &optional value)
 
 (define-compilation return-from (name &optional value)
-  (let ((b (lookup-in-lexenv name *environment* 'block)))
-    (if b
-        (js!selfcall
-          "throw ({"
-          "type: 'block', "
-          "id: " (binding-value b) ", "
-          "value: " (ls-compile value) ", "
-          "message: 'Return from unknown block " (symbol-name name) ".'"
-          "})")
-        (error (concat "Unknown block `" (symbol-name name) "'.")))))
-
+  (let* ((b (lookup-in-lexenv name *environment* 'block))
+         (multiple-value-p (member 'multiple-value (binding-declarations b))))
+    (when (null b)
+      (error (concat "Unknown block `" (symbol-name name) "'.")))
+    (push-binding-declaration 'used b)
+    (js!selfcall
+      (if multiple-value-p
+          (concat "var values = mv;" *newline*)
+          "")
+      "throw ({"
+      "type: 'block', "
+      "id: " (binding-value b) ", "
+      "values: " (ls-compile value multiple-value-p) ", "
+      "message: 'Return from unknown block " (symbol-name name) ".'"
+      "})")))
 
 (define-compilation catch (id &rest body)
   (js!selfcall
     "var id = " (ls-compile id) ";" *newline*
     "try {" *newline*
 
 (define-compilation catch (id &rest body)
   (js!selfcall
     "var id = " (ls-compile id) ";" *newline*
     "try {" *newline*
-    (indent "return " (ls-compile `(progn ,@body))
-            ";" *newline*)
+    (indent (ls-compile-block body t)) *newline*
     "}" *newline*
     "catch (cf){" *newline*
     "    if (cf.type == 'catch' && cf.id == id)" *newline*
     "}" *newline*
     "catch (cf){" *newline*
     "    if (cf.type == 'catch' && cf.id == id)" *newline*
-    "        return cf.value;" *newline*
+    (if *multiple-value-p*
+        "        return values.apply(this, forcemv(cf.values));"
+        "        return pv.apply(this, forcemv(cf.values));")
+    *newline*
     "    else" *newline*
     "        throw cf;" *newline*
     "}" *newline*))
 
 (define-compilation throw (id value)
   (js!selfcall
     "    else" *newline*
     "        throw cf;" *newline*
     "}" *newline*))
 
 (define-compilation throw (id value)
   (js!selfcall
+    "var values = mv;" *newline*
     "throw ({"
     "type: 'catch', "
     "id: " (ls-compile id) ", "
     "throw ({"
     "type: 'catch', "
     "id: " (ls-compile id) ", "
-    "value: " (ls-compile value) ", "
+    "values: " (ls-compile value t) ", "
     "message: 'Throw uncatched.'"
     "})"))
 
     "message: 'Throw uncatched.'"
     "})"))
 
           "})" *newline*)
         (error (concat "Unknown tag `" n "'.")))))
 
           "})" *newline*)
         (error (concat "Unknown tag `" n "'.")))))
 
-
 (define-compilation unwind-protect (form &rest clean-up)
   (js!selfcall
     "var ret = " (ls-compile nil) ";" *newline*
 (define-compilation unwind-protect (form &rest clean-up)
   (js!selfcall
     "var ret = " (ls-compile nil) ";" *newline*
     "}" *newline*
     "return ret;" *newline*))
 
     "}" *newline*
     "return ret;" *newline*))
 
+(define-compilation multiple-value-call (func-form &rest forms)
+  (js!selfcall
+    "var func = " (ls-compile func-form) ";" *newline*
+    "var args = [" (if *multiple-value-p* "values" "pv") "];" *newline*
+    "return "
+    (js!selfcall
+      "var values = mv;" *newline*
+      "var vs;" *newline*
+      (mapconcat (lambda (form)
+                   (concat "vs = " (ls-compile form t) ";" *newline*
+                           "if (typeof vs === 'object' && 'multiple-value' in vs)" *newline*
+                           (indent "args = args.concat(vs);" *newline*)
+                           "else" *newline*
+                           (indent "args.push(vs);" *newline*)))
+                 forms)
+      "return func.apply(window, args);" *newline*) ";" *newline*))
+
+(define-compilation multiple-value-prog1 (first-form &rest forms)
+  (js!selfcall
+    "var args = " (ls-compile first-form *multiple-value-p*) ";" *newline*
+    (ls-compile-block forms)
+    "return args;" *newline*))
+
+
 
 ;;; A little backquote implementation without optimizations of any
 ;;; kind for ecmalisp.
 
 ;;; A little backquote implementation without optimizations of any
 ;;; kind for ecmalisp.
 
 (defmacro variable-arity (args &body body)
   (unless (symbolp args)
 
 (defmacro variable-arity (args &body body)
   (unless (symbolp args)
-    (error "Bad usage of VARIABLE-ARITY, yo must pass a symbol"))
+    (error "Bad usage of VARIABLE-ARITY, you must pass a symbol"))
   `(variable-arity-call ,args
                         (lambda (,args)
                           (concat "return " ,@body ";" *newline*))))
 
   `(variable-arity-call ,args
                         (lambda (,args)
                           (concat "return " ,@body ";" *newline*))))
 
-
 (defun num-op-num (x op y)
   (type-check (("x" "number" x) ("y" "number" y))
     (concat "x" op "y")))
 (defun num-op-num (x op y)
   (type-check (("x" "number" x) ("y" "number" y))
     (concat "x" op "y")))
          (concat "-" (car args))
          (join args "-")))))
 
          (concat "-" (car args))
          (join args "-")))))
 
+(define-raw-builtin * (&rest numbers)
+  (if (null numbers)
+      "1"
+      (variable-arity numbers
+       (join numbers "*"))))
 
 
-(define-builtin * (x y) (num-op-num x "*" y))
-(define-builtin / (x y) (num-op-num x "/" y))
+(define-raw-builtin / (x &rest others)
+  (let ((args (cons x others)))
+    (variable-arity args
+      (if (null others)
+         (concat "1 /" (car args))
+         (join args "/")))))
 
 (define-builtin mod (x y) (num-op-num x "%" y))
 
 
 (define-builtin mod (x y) (num-op-num x "%" y))
 
-(define-builtin < (x y)  (js!bool (num-op-num x "<" y)))
-(define-builtin > (x y)  (js!bool (num-op-num x ">" y)))
-(define-builtin = (x y)  (js!bool (num-op-num x "==" y)))
-(define-builtin <= (x y) (js!bool (num-op-num x "<=" y)))
-(define-builtin >= (x y) (js!bool (num-op-num x ">=" y)))
+
+(defun comparison-conjuntion (vars op)
+  (cond
+    ((null (cdr vars))
+     "true")
+    ((null (cddr vars))
+     (concat (car vars) op (cadr vars)))
+    (t
+     (concat (car vars) op (cadr vars)
+            " && "
+            (comparison-conjuntion (cdr vars) op)))))
+
+(defmacro define-builtin-comparison (op sym)
+  `(define-raw-builtin ,op (x &rest args)
+     (let ((args (cons x args)))
+       (variable-arity args
+        (js!bool (comparison-conjuntion args ,sym))))))
+
+(define-builtin-comparison > ">")
+(define-builtin-comparison < "<")
+(define-builtin-comparison >= ">=")
+(define-builtin-comparison <= "<=")
+(define-builtin-comparison = "==")
 
 (define-builtin numberp (x)
   (js!bool (concat "(typeof (" x ") == \"number\")")))
 
 (define-builtin numberp (x)
   (js!bool (concat "(typeof (" x ") == \"number\")")))
     (ls-compile nil)
     ": tmp.cdr;" *newline*))
 
     (ls-compile nil)
     ": tmp.cdr;" *newline*))
 
-(define-builtin setcar (x new)
+(define-builtin rplaca (x new)
   (type-check (("x" "object" x))
   (type-check (("x" "object" x))
-    (concat "(x.car = " new ")")))
+    (concat "(x.car = " new ", x)")))
 
 
-(define-builtin setcdr (x new)
+(define-builtin rplacd (x new)
   (type-check (("x" "object" x))
   (type-check (("x" "object" x))
-    (concat "(x.cdr = " new ")")))
+    (concat "(x.cdr = " new ", x)")))
 
 (define-builtin symbolp (x)
   (js!bool
 
 (define-builtin symbolp (x)
   (js!bool
   (concat "(" symbol ").value = " value))
 
 (define-builtin fset (symbol value)
   (concat "(" symbol ").value = " value))
 
 (define-builtin fset (symbol value)
-  (concat "(" symbol ").function = " value))
+  (concat "(" symbol ").fvalue = " value))
 
 (define-builtin boundp (x)
   (js!bool (concat "(" x ".value !== undefined)")))
 
 (define-builtin boundp (x)
   (js!bool (concat "(" x ".value !== undefined)")))
 (define-builtin symbol-function (x)
   (js!selfcall
     "var symbol = " x ";" *newline*
 (define-builtin symbol-function (x)
   (js!selfcall
     "var symbol = " x ";" *newline*
-    "var func = symbol.function;" *newline*
+    "var func = symbol.fvalue;" *newline*
     "if (func === undefined) throw \"Function `\" + symbol.name + \"' is undefined.\";" *newline*
     "return func;" *newline*))
 
     "if (func === undefined) throw \"Function `\" + symbol.name + \"' is undefined.\";" *newline*
     "return func;" *newline*))
 
 (define-builtin lambda-code (x)
   (concat "(" x ").toString()"))
 
 (define-builtin lambda-code (x)
   (concat "(" x ").toString()"))
 
-
 (define-builtin eq    (x y) (js!bool (concat "(" x " === " y ")")))
 (define-builtin equal (x y) (js!bool (concat "(" x  " == " y ")")))
 
 (define-builtin eq    (x y) (js!bool (concat "(" x " === " y ")")))
 (define-builtin equal (x y) (js!bool (concat "(" x  " == " y ")")))
 
 
 (define-raw-builtin funcall (func &rest args)
   (concat "(" (ls-compile func) ")("
 
 (define-raw-builtin funcall (func &rest args)
   (concat "(" (ls-compile func) ")("
-          (join (mapcar #'ls-compile args)
+          (join (cons (if *multiple-value-p* "values" "pv")
+                      (mapcar #'ls-compile args))
                 ", ")
           ")"))
 
                 ", ")
           ")"))
 
             (last (car (last args))))
         (js!selfcall
           "var f = " (ls-compile func) ";" *newline*
             (last (car (last args))))
         (js!selfcall
           "var f = " (ls-compile func) ";" *newline*
-          "var args = [" (join (mapcar #'ls-compile args)
+          "var args = [" (join (cons (if *multiple-value-p* "values" "pv")
+                                     (mapcar #'ls-compile args))
                                ", ")
           "];" *newline*
           "var tail = (" (ls-compile last) ");" *newline*
                                ", ")
           "];" *newline*
           "var tail = (" (ls-compile last) ");" *newline*
 
 (define-builtin js-eval (string)
   (type-check (("string" "string" string))
 
 (define-builtin js-eval (string)
   (type-check (("string" "string" string))
-    "eval.apply(window, [string])"))
+    (if *multiple-value-p*
+        (js!selfcall
+          "var v = eval.apply(window, [string]);" *newline*
+          "if (typeof v !== 'object' || !('multiple-value' in v)){" *newline*
+          (indent "v = [v];" *newline*
+                  "v['multiple-value'] = true;" *newline*)
+          "}" *newline*
+          "return values.apply(this, v);" *newline*)
+        "eval.apply(window, [string])")))
 
 (define-builtin error (string)
   (js!selfcall "throw " string ";" *newline*))
 
 (define-builtin error (string)
   (js!selfcall "throw " string ";" *newline*))
      "return typeof x === 'object' && 'length' in x;")))
 
 (define-builtin aref (array n)
      "return typeof x === 'object' && 'length' in x;")))
 
 (define-builtin aref (array n)
-  (concat "(" array ")[" n "]"))
+  (js!selfcall
+    "var x = " "(" array ")[" n "];" *newline*
+    "if (x === undefined) throw 'Out of range';" *newline*
+    "return x;" *newline*))
 
 (define-builtin aset (array n value)
 
 (define-builtin aset (array n value)
-  (concat "(" array ")[" n "] = " value))
+  (js!selfcall
+    "var x = " array ";" *newline*
+    "var i = " n ";" *newline*
+    "if (i < 0 || i >= x.length) throw 'Out of range';" *newline*
+    "return x[i] = " value ";" *newline*))
+
+(define-builtin get-unix-time ()
+  (concat "(Math.round(new Date() / 1000))"))
 
 
+(define-builtin values-array (array)
+  (if *multiple-value-p*
+      (concat "values.apply(this, " array ")")
+      (concat "pv.apply(this, " array ")")))
+
+(define-raw-builtin values (&rest args)
+  (if *multiple-value-p*
+      (concat "values(" (join (mapcar #'ls-compile args) ", ") ")")
+      (concat "pv(" (join (mapcar #'ls-compile args) ", ") ")")))
 
 (defun macro (x)
   (and (symbolp x)
 
 (defun macro (x)
   (and (symbolp x)
         form)))
 
 (defun compile-funcall (function args)
         form)))
 
 (defun compile-funcall (function args)
-  (if (and (symbolp function)
-           (claimp function 'function 'non-overridable))
-      (concat (ls-compile `',function) ".function("
-              (join (mapcar #'ls-compile args)
-                    ", ")
-              ")")
-      (concat (ls-compile `#',function) "("
-              (join (mapcar #'ls-compile args)
-                    ", ")
-              ")")))
+  (let* ((values-funcs (if *multiple-value-p* "values" "pv"))
+         (arglist (concat "(" (join (cons values-funcs (mapcar #'ls-compile args)) ", ") ")")))
+    (cond
+      ((translate-function function)
+       (concat (translate-function function) arglist))
+      ((and (symbolp function)
+            #+ecmalisp (eq (symbol-package function) (find-package "COMMON-LISP"))
+            #+common-lisp t)
+       (concat (ls-compile `',function) ".fvalue" arglist))
+      (t
+       (concat (ls-compile `#',function) arglist)))))
 
 (defun ls-compile-block (sexps &optional return-last-p)
   (if return-last-p
       (concat (ls-compile-block (butlast sexps))
 
 (defun ls-compile-block (sexps &optional return-last-p)
   (if return-last-p
       (concat (ls-compile-block (butlast sexps))
-              "return " (ls-compile (car (last sexps))) ";")
+              "return " (ls-compile (car (last sexps)) *multiple-value-p*) ";")
       (join-trailing
        (remove-if #'null-or-empty-p (mapcar #'ls-compile sexps))
        (concat ";" *newline*))))
 
       (join-trailing
        (remove-if #'null-or-empty-p (mapcar #'ls-compile sexps))
        (concat ";" *newline*))))
 
-(defun ls-compile (sexp)
-  (cond
-    ((symbolp sexp)
-     (let ((b (lookup-in-lexenv sexp *environment* 'variable)))
-       (cond
-         ((and b (not (member 'special (binding-declarations b))))
-          (binding-value b))
-         ((or (keywordp sexp)
-              (member 'constant (binding-declarations b)))
-          (concat (ls-compile `',sexp) ".value"))
-         (t
-          (ls-compile `(symbol-value ',sexp))))))
-    ((integerp sexp) (integer-to-string sexp))
-    ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
-    ((arrayp sexp) (literal sexp))
-    ((listp sexp)
-     (let ((name (car sexp))
-           (args (cdr sexp)))
-       (cond
-         ;; Special forms
-         ((assoc name *compilations*)
-          (let ((comp (second (assoc name *compilations*))))
-            (apply comp args)))
-         ;; Built-in functions
-         ((and (assoc name *builtins*)
-               (not (claimp name 'function 'notinline)))
-          (let ((comp (second (assoc name *builtins*))))
-            (apply comp args)))
-         (t
-          (if (macro name)
-              (ls-compile (ls-macroexpand-1 sexp))
-              (compile-funcall name args))))))
-    (t
-     (error "How should I compile this?"))))
+(defun ls-compile (sexp &optional multiple-value-p)
+  (let ((*multiple-value-p* multiple-value-p))
+    (cond
+      ((symbolp sexp)
+       (let ((b (lookup-in-lexenv sexp *environment* 'variable)))
+         (cond
+           ((and b (not (member 'special (binding-declarations b))))
+            (binding-value b))
+           ((or (keywordp sexp)
+                (member 'constant (binding-declarations b)))
+            (concat (ls-compile `',sexp) ".value"))
+           (t
+            (ls-compile `(symbol-value ',sexp))))))
+      ((integerp sexp) (integer-to-string sexp))
+      ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
+      ((arrayp sexp) (literal sexp))
+      ((listp sexp)
+       (let ((name (car sexp))
+             (args (cdr sexp)))
+         (cond
+           ;; Special forms
+           ((assoc name *compilations*)
+            (let ((comp (second (assoc name *compilations*))))
+              (apply comp args)))
+           ;; Built-in functions
+           ((and (assoc name *builtins*)
+                 (not (claimp name 'function 'notinline)))
+            (let ((comp (second (assoc name *builtins*))))
+              (apply comp args)))
+           (t
+            (if (macro name)
+                (ls-compile (ls-macroexpand-1 sexp) multiple-value-p)
+                (compile-funcall name args))))))
+      (t
+       (error "How should I compile this?")))))
 
 
-(defun ls-compile-toplevel (sexp)
+(defun ls-compile-toplevel (sexp &optional multiple-value-p)
   (let ((*toplevel-compilations* nil))
     (cond
       ((and (consp sexp) (eq (car sexp) 'progn))
   (let ((*toplevel-compilations* nil))
     (cond
       ((and (consp sexp) (eq (car sexp) 'progn))
-       (let ((subs (mapcar #'ls-compile-toplevel (cdr sexp))))
+       (let ((subs (mapcar (lambda (s)
+                             (ls-compile-toplevel s t))
+                           (cdr sexp))))
          (join (remove-if #'null-or-empty-p subs))))
       (t
          (join (remove-if #'null-or-empty-p subs))))
       (t
-       (let ((code (ls-compile sexp)))
+       (let ((code (ls-compile sexp multiple-value-p)))
          (concat (join-trailing (get-toplevel-compilations)
                                 (concat ";" *newline*))
                  (if code
          (concat (join-trailing (get-toplevel-compilations)
                                 (concat ";" *newline*))
                  (if code
 
 #+ecmalisp
 (progn
 
 #+ecmalisp
 (progn
-  (defmacro with-compilation-unit (&body body)
-    `(prog1
-         (progn
-           (setq *compilation-unit-checks* nil)
-           ,@body)
-       (dolist (check *compilation-unit-checks*)
-         (funcall check))))
-
   (defun eval (x)
   (defun eval (x)
-    (let ((code
-           (with-compilation-unit
-               (ls-compile-toplevel x))))
-      (js-eval code)))
+    (js-eval (ls-compile-toplevel x t)))
 
   (export '(&rest &optional &body * *gensym-counter* *package* + - / 1+ 1- < <= =
 
   (export '(&rest &optional &body * *gensym-counter* *package* + - / 1+ 1- < <= =
-           = > >= and append apply aref arrayp aset assoc atom block boundp
-           boundp butlast caar cadddr caddr cadr car car case catch cdar cdddr
-           cddr cdr cdr char char-code char= code-char cond cons consp copy-list
-           decf declaim defparameter defun defvar digit-char-p disassemble
-           documentation dolist dotimes ecase eq eql equal error eval every
-           export fdefinition find-package find-symbol first fourth fset funcall
-           function functionp gensym go identity if in-package incf integerp
-           integerp intern keywordp lambda last length let let* list-all-packages
-           list listp make-array make-package make-symbol mapcar member minusp
-           mod nil not nth nthcdr null numberp or package-name package-use-list
-           packagep plusp prin1-to-string print proclaim prog1 prog2 pron push
-           quote remove remove-if remove-if-not return return-from revappend
-           reverse second set setq some string-upcase string string= stringp
-           subseq symbol-function symbol-name symbol-package symbol-plist
-           symbol-value symbolp t tagbody third throw truncate unless
-           unwind-protect variable warn when write-line write-string zerop))
+            = > >= and append apply aref arrayp aset assoc atom block boundp
+            boundp butlast caar cadddr caddr cadr car car case catch cdar cdddr
+            cddr cdr cdr char char-code char= code-char cond cons consp copy-list
+            decf declaim defparameter defun defmacro defvar digit-char-p
+            disassemble do do* documentation dolist dotimes ecase eq eql equal
+           error eval every export fdefinition find-package find-symbol first
+           flet fourth fset funcall function functionp gensym get-universal-time
+            go identity if in-package incf integerp integerp intern keywordp lambda
+           last length let let* list-all-packages list listp make-array
+           make-package make-symbol mapcar member minusp mod multiple-value-bind
+            multiple-value-call multiple-value-list multiple-value-prog1 nil not
+            nth nthcdr null numberp or package-name package-use-list packagep
+            parse-integer plusp prin1-to-string print proclaim prog1 prog2 progn
+           psetq push quote remove remove-if remove-if-not return return-from
+           revappend reverse rplaca rplacd second set setq some string-upcase
+           string string= stringp subseq symbol-function symbol-name symbol-package
+            symbol-plist symbol-value symbolp t tagbody third throw truncate
+            unless unwind-protect values values-list variable warn when write-line
+            write-string zerop))
 
   (setq *package* *user-package*)
 
 
   (setq *package* *user-package*)
 
   (js-vset "lisp.read" #'ls-read-from-string)
   (js-vset "lisp.print" #'prin1-to-string)
   (js-vset "lisp.eval" #'eval)
   (js-vset "lisp.read" #'ls-read-from-string)
   (js-vset "lisp.print" #'prin1-to-string)
   (js-vset "lisp.eval" #'eval)
-  (js-vset "lisp.compile" #'ls-compile-toplevel)
+  (js-vset "lisp.compile" (lambda (s) (ls-compile-toplevel s t)))
   (js-vset "lisp.evalString" (lambda (str) (eval (ls-read-from-string str))))
   (js-vset "lisp.evalString" (lambda (str) (eval (ls-read-from-string str))))
-  (js-vset "lisp.compileString" (lambda (str) (ls-compile-toplevel (ls-read-from-string str))))
+  (js-vset "lisp.compileString" (lambda (str) (ls-compile-toplevel (ls-read-from-string str) t)))
 
   ;; Set the initial global environment to be equal to the host global
   ;; environment at this point of the compilation.
 
   ;; Set the initial global environment to be equal to the host global
   ;; environment at this point of the compilation.
         seq)))
 
   (defun ls-compile-file (filename output)
         seq)))
 
   (defun ls-compile-file (filename output)
-    (setq *compilation-unit-checks* nil)
-    (with-open-file (out output :direction :output :if-exists :supersede)
-      (let* ((source (read-whole-file filename))
-             (in (make-string-stream source)))
-        (loop
-           for x = (ls-read in)
-           until (eq x *eof*)
-           for compilation = (ls-compile-toplevel x)
-           when (plusp (length compilation))
-           do (write-string compilation out))
-        (dolist (check *compilation-unit-checks*)
-          (funcall check))
-        (setq *compilation-unit-checks* nil))))
+    (let ((*compiling-file* t))
+      (with-open-file (out output :direction :output :if-exists :supersede)
+        (write-string (read-whole-file "prelude.js") out)
+        (let* ((source (read-whole-file filename))
+               (in (make-string-stream source)))
+          (loop
+             for x = (ls-read in)
+             until (eq x *eof*)
+             for compilation = (ls-compile-toplevel x)
+             when (plusp (length compilation))
+             do (write-string compilation out))))))
 
   (defun bootstrap ()
     (setq *environment* (make-lexenv))
 
   (defun bootstrap ()
     (setq *environment* (make-lexenv))