Some string conversions in error reporting
[jscl.git] / src / compiler.lisp
index ee4514c..94e77ce 100644 (file)
@@ -3,18 +3,18 @@
 ;; copyright (C) 2012, 2013 David Vazquez
 ;; Copyright (C) 2012 Raimon Grau
 
-;; This program is free software: you can redistribute it and/or
+;; JSCL is free software: you can redistribute it and/or
 ;; modify it under the terms of the GNU General Public License as
 ;; published by the Free Software Foundation, either version 3 of the
 ;; License, or (at your option) any later version.
 ;;
-;; This program is distributed in the hope that it will be useful, but
+;; JSCL is distributed in the hope that it will be useful, but
 ;; WITHOUT ANY WARRANTY; without even the implied warranty of
 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
 ;; General Public License for more details.
 ;;
 ;; You should have received a copy of the GNU General Public License
-;; along with this program.  If not, see <http://www.gnu.org/licenses/>.
+;; along with JSCL.  If not, see <http://www.gnu.org/licenses/>.
 
 ;;;; Compiler
 
@@ -30,7 +30,7 @@
                  ((integerp arg) (integer-to-string arg))
                  ((floatp arg) (float-to-string arg))
                  ((stringp arg) arg)
-                 (t (error "Unknown argument."))))
+                 (t (error "Unknown argument `~S'." arg))))
              args))
 
 ;;; Wrap X with a Javascript code to convert the result from
                       ((and (listp sd) (car sd) (cddr sd))
                        sd)
                       (t
-                       (error "Bad slot accessor."))))
+                       (error "Bad slot description `~S'." sd))))
                   slots))
          (predicate (intern (concat name-string "-P"))))
     `(progn
                 (collect
                     `(defun ,accessor-name (x)
                        (unless (,predicate x)
-                         (error ,(concat "The object is not a type " name-string)))
+                         (error "The object `~S' is not of type `~S'" x ,name-string))
                        (nth ,index x)))
                 ;; TODO: Implement this with a higher level
                 ;; abstraction like defsetf or (defun (setf ..))
 (defvar *variable-counter* 0)
 
 (defun gvarname (symbol)
+  (declare (ignore symbol))
   (code "v" (incf *variable-counter*)))
 
 (defun translate-variable (symbol)
 (defun ll-rest-argument (ll)
   (let ((rest (ll-section '&rest ll)))
     (when (cdr rest)
-      (error "Bad lambda-list"))
+      (error "Bad lambda-list `~S'." ll))
     (car rest)))
 
 (defun ll-keyword-arguments-canonical (ll)
           (ll-optional-arguments-canonical lambda-list))))
     (remove nil (mapcar #'third args))))
 
-(defun lambda-docstring-wrapper (docstring &rest strs)
-  (if docstring
+(defun lambda-name/docstring-wrapper (name docstring &rest strs)
+  (if (or name docstring)
       (js!selfcall
         "var func = " (join strs) ";" *newline*
-        "func.docstring = '" docstring "';" *newline*
+        (when name
+          (code "func.fname = '" (escape-string name) "';" *newline*))
+        (when docstring
+          (code "func.docstring = '" (escape-string docstring) "';" *newline*))
         "return func;" *newline*)
       (apply #'code strs)))
 
     (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))))
+  (let ((min n-required-arguments)
+        (max (if rest-p 'n/a (+ n-required-arguments n-optional-arguments))))
     (block nil
       ;; Special case: a positive exact number of arguments.
-      (when (and (< 1 min) (eql min max))
-        (return (code "checkArgs(arguments, " min ");" *newline*)))
+      (when (and (< 0 min) (eql min max))
+        (return (code "checkArgs(nargs, " min ");" *newline*)))
       ;; General case:
       (code
-       (when (< 1 min)
-         (code "checkArgsAtLeast(arguments, " min ");" *newline*))
+       (when (< 0 min)
+         (code "checkArgsAtLeast(nargs, " min ");" *newline*))
        (when (numberp max)
-         (code "checkArgsAtMost(arguments, " max ");" *newline*))))))
+         (code "checkArgsAtMost(nargs, " max ");" *newline*))))))
 
 (defun compile-lambda-optional (ll)
   (let* ((optional-arguments (ll-optional-arguments-canonical ll))
         (n-required-arguments (length (ll-required-arguments ll)))
         (n-optional-arguments (length optional-arguments)))
     (when optional-arguments
-      (code (mapconcat (lambda (arg)
-                         (code "var " (translate-variable (first arg)) "; " *newline*
-                               (when (third arg)
-                                 (code "var " (translate-variable (third arg))
-                                       " = " (ls-compile t)
-                                       "; " *newline*))))
-                       optional-arguments)
-            "switch(arguments.length-1){" *newline*
+      (code "switch(nargs){" *newline*
             (let ((cases nil)
                   (idx 0))
               (progn
     (when rest-argument
       (let ((js!rest (translate-variable rest-argument)))
         (code "var " js!rest "= " (ls-compile nil) ";" *newline*
-              "for (var i = arguments.length-1; i>="
-              (+ 1 n-required-arguments n-optional-arguments)
+              "for (var i = nargs-1; i>=" (+ n-required-arguments n-optional-arguments)
               "; i--)" *newline*
-              (indent js!rest " = {car: arguments[i], cdr: ") js!rest "};"
-              *newline*)))))
+              (indent js!rest " = {car: arguments[i+2], cdr: " js!rest "};" *newline*))))))
 
 (defun compile-lambda-parse-keywords (ll)
   (let ((n-required-arguments
      ;; Parse keywords
      (flet ((parse-keyword (keyarg)
              ;; ((keyword-name var) init-form)
-             (code "for (i=" (+ 1 n-required-arguments n-optional-arguments)
-                    "; i<arguments.length; i+=2){" *newline*
+             (code "for (i=" (+ n-required-arguments n-optional-arguments)
+                    "; i<nargs; i+=2){" *newline*
                     (indent
-                     "if (arguments[i] === " (ls-compile (caar keyarg)) "){" *newline*
+                     "if (arguments[i+2] === " (ls-compile (caar keyarg)) "){" *newline*
                      (indent (translate-variable (cadr (car keyarg)))
-                             " = arguments[i+1];"
+                             " = arguments[i+3];"
                              *newline*
                              (let ((svar (third keyarg)))
                                (when svar
                      "}" *newline*)
                     "}" *newline*
                     ;; Default value
-                    "if (i == arguments.length){" *newline*
+                    "if (i == nargs){" *newline*
                     (indent (translate-variable (cadr (car keyarg))) " = " (ls-compile (cadr keyarg)) ";" *newline*)
                     "}" *newline*)))
        (when keyword-arguments
                (mapconcat #'parse-keyword keyword-arguments))))
      ;; Check for unknown keywords
      (when keyword-arguments
-       (code "for (i=" (+ 1 n-required-arguments n-optional-arguments)
-             "; i<arguments.length; i+=2){" *newline*
+       (code "for (i=" (+ n-required-arguments n-optional-arguments)
+             "; i<nargs; i+=2){" *newline*
              (indent "if ("
                      (join (mapcar (lambda (x)
-                                     (concat "arguments[i] !== " (ls-compile (caar x))))
+                                     (concat "arguments[i+2] !== " (ls-compile (caar x))))
                                    keyword-arguments)
                            " && ")
                      ")" *newline*
                      (indent
-                      "throw 'Unknown keyword argument ' + arguments[i].name;" *newline*))
+                      "throw 'Unknown keyword argument ' + xstring(arguments[i].name);" *newline*))
              "}" *newline*)))))
 
-(defun compile-lambda (ll body)
-  (let ((required-arguments (ll-required-arguments ll))
-        (optional-arguments (ll-optional-arguments ll))
-       (keyword-arguments  (ll-keyword-arguments  ll))
-        (rest-argument      (ll-rest-argument      ll))
-        documentation)
-    ;; Get the documentation string for the lambda function
-    (when (and (stringp (car body))
+(defun parse-lambda-list (ll)
+  (values (ll-required-arguments ll)
+          (ll-optional-arguments ll)
+          (ll-keyword-arguments  ll)
+          (ll-rest-argument      ll)))
+
+;;; Process BODY for declarations and/or docstrings. Return as
+;;; multiple values the BODY without docstrings or declarations, the
+;;; list of declaration forms and the docstring.
+(defun parse-body (body &key declarations docstring)
+  (let ((value-declarations)
+        (value-docstring))
+    ;; Parse declarations
+    (when declarations
+      (do* ((rest body (cdr rest))
+            (form (car rest) (car rest)))
+           ((or (atom form) (not (eq (car form) 'declare)))
+            (setf body rest))
+        (push form value-declarations)))
+    ;; Parse docstring
+    (when (and docstring
+               (stringp (car body))
                (not (null (cdr body))))
-      (setq documentation (car body))
+      (setq value-docstring (car body))
       (setq body (cdr body)))
-    (let ((n-required-arguments (length required-arguments))
-          (n-optional-arguments (length optional-arguments))
-          (*environment* (extend-local-env
-                          (append (ensure-list rest-argument)
-                                  required-arguments
-                                  optional-arguments
-                                 keyword-arguments
-                                  (ll-svars ll)))))
-      (lambda-docstring-wrapper
-       documentation
-       "(function ("
-       (join (cons "values"
-                   (mapcar #'translate-variable
-                           (append required-arguments optional-arguments)))
-             ",")
-       "){" *newline*
-       (indent
-        ;; Check number of arguments
-        (lambda-check-argument-count n-required-arguments
-                                     n-optional-arguments
-                                     (or rest-argument keyword-arguments))
-       (compile-lambda-optional ll)
-       (compile-lambda-rest ll)
-       (compile-lambda-parse-keywords ll)
-        (let ((*multiple-value-p* t))
-         (ls-compile-block body t)))
-       "})"))))
+    (values body value-declarations value-docstring)))
+
+;;; Compile a lambda function with lambda list LL and body BODY. If
+;;; NAME is given, it should be a constant string and it will become
+;;; the name of the function. If BLOCK is non-NIL, a named block is
+;;; created around the body. NOTE: No block (even anonymous) is
+;;; created if BLOCk is NIL.
+(defun compile-lambda (ll body &key name block)
+  (multiple-value-bind (required-arguments
+                        optional-arguments
+                        keyword-arguments
+                        rest-argument)
+      (parse-lambda-list ll)
+    (multiple-value-bind (body decls documentation)
+        (parse-body body :declarations t :docstring t)
+      (declare (ignore decls))
+      (let ((n-required-arguments (length required-arguments))
+            (n-optional-arguments (length optional-arguments))
+            (*environment* (extend-local-env
+                            (append (ensure-list rest-argument)
+                                    required-arguments
+                                    optional-arguments
+                                    keyword-arguments
+                                    (ll-svars ll)))))
+        (lambda-name/docstring-wrapper name documentation
+         "(function ("
+         (join (list* "values"
+                      "nargs"
+                      (mapcar #'translate-variable
+                              (append required-arguments optional-arguments)))
+               ",")
+         "){" *newline*
+         (indent
+          ;; Check number of arguments
+          (lambda-check-argument-count n-required-arguments
+                                       n-optional-arguments
+                                       (or rest-argument keyword-arguments))
+                                        (compile-lambda-optional ll)
+                                        (compile-lambda-rest ll)
+                                        (compile-lambda-parse-keywords ll)
+                                        (let ((*multiple-value-p* t))
+                                          (if block
+                                              (ls-compile-block `((block ,block ,@body)) t)
+                                              (ls-compile-block body t))))
+         "})")))))
 
 
 (defun setq-pair (var val)
       (cond
        ((null pairs) (return))
        ((null (cdr pairs))
-        (error "Odd paris in SETQ"))
+        (error "Odd pairs in SETQ"))
        (t
         (concatf result
           (concat (setq-pair (car pairs) (cadr pairs))
     output))
 
 
-(defvar *literal-symbols* nil)
+(defvar *literal-table* nil)
 (defvar *literal-counter* 0)
 
 (defun genlit ()
   (code "l" (incf *literal-counter*)))
 
+(defun dump-symbol (symbol)
+  #+common-lisp
+  (let ((package (symbol-package symbol)))
+    (if (eq package (find-package "KEYWORD"))
+        (code "{name: " (dump-string (symbol-name symbol))
+              ", 'package': " (dump-string (package-name package)) "}")
+        (code "{name: " (dump-string (symbol-name symbol)) "}")))
+  #+jscl
+  (let ((package (symbol-package symbol)))
+    (if (null package)
+        (code "{name: " (dump-symbol (symbol-name symbol)) "}")
+        (ls-compile `(intern ,(symbol-name symbol) ,(package-name package))))))
+
+(defun dump-cons (cons)
+  (let ((head (butlast cons))
+        (tail (last cons)))
+    (code "QIList("
+          (join-trailing (mapcar (lambda (x) (literal x t)) head) ",")
+          (literal (car tail) t)
+          ","
+          (literal (cdr tail) t)
+          ")")))
+
+(defun dump-array (array)
+  (let ((elements (vector-to-list array)))
+    (concat "[" (join (mapcar #'literal elements) ", ") "]")))
+
+(defun dump-string (string)
+  (code "make_lisp_string(\"" (escape-string string) "\")"))
+
 (defun literal (sexp &optional recursive)
   (cond
     ((integerp sexp) (integer-to-string sexp))
     ((floatp sexp) (float-to-string sexp))
-    ((stringp sexp) (code "\"" (escape-string sexp) "\""))
-    ((symbolp sexp)
-     (or (cdr (assoc sexp *literal-symbols*))
-        (let ((v (genlit))
-              (s #+common-lisp
-                 (let ((package (symbol-package sexp)))
-                   (if (eq package (find-package "KEYWORD"))
-                       (code "{name: \"" (escape-string (symbol-name sexp))
-                             "\", 'package': '" (package-name package) "'}")
-                       (code "{name: \"" (escape-string (symbol-name sexp)) "\"}")))
-                 #+jscl
-                 (let ((package (symbol-package sexp)))
-                   (if (null package)
-                       (code "{name: \"" (escape-string (symbol-name sexp)) "\"}")
-                       (ls-compile `(intern ,(symbol-name sexp) ,(package-name package)))))))
-          (push (cons sexp v) *literal-symbols*)
-          (toplevel-compilation (code "var " v " = " s))
-          v)))
-    ((consp sexp)
-     (let* ((head (butlast sexp))
-            (tail (last sexp))
-            (c (code "QIList("
-                     (join-trailing (mapcar (lambda (x) (literal x t)) head) ",")
-                     (literal (car tail) t)
-                     ","
-                     (literal (cdr tail) t)
-                     ")")))
-       (if recursive
-          c
-          (let ((v (genlit)))
-             (toplevel-compilation (code "var " v " = " c))
-             v))))
-    ((arrayp sexp)
-     (let ((elements (vector-to-list sexp)))
-       (let ((c (concat "[" (join (mapcar #'literal elements) ", ") "]")))
-        (if recursive
-            c
-            (let ((v (genlit)))
-              (toplevel-compilation (code "var " v " = " c))
-              v)))))))
-
+    ((characterp sexp) (code "\"" (escape-string (string sexp)) "\""))
+    (t
+     (or (cdr (assoc sexp *literal-table* :test #'equal))
+         (let ((dumped (typecase sexp
+                         (symbol (dump-symbol sexp))
+                         (cons (dump-cons sexp))
+                         (string (dump-string sexp))
+                         (array (dump-array sexp)))))
+           (if (and recursive (not (symbolp sexp)))
+               dumped
+               (let ((jsvar (genlit)))
+                 (push (cons sexp jsvar) *literal-table*)
+                 (toplevel-compilation (code "var " jsvar " = " dumped))
+                 jsvar)))))))
 
 (define-compilation quote (sexp)
   (literal sexp))
   (cond
     ((and (listp x) (eq (car x) 'lambda))
      (compile-lambda (cadr x) (cddr x)))
+    ((and (listp x) (eq (car x) 'named-lambda))
+     ;; TODO: destructuring-bind now! Do error checking manually is
+     ;; very annoying.
+     (let ((name (cadr x))
+           (ll (caddr x))
+           (body (cdddr x)))
+       (compile-lambda ll body
+                       :name (symbol-name name)
+                       :block name)))
     ((symbolp x)
      (let ((b (lookup-in-lexenv x *environment* 'function)))
        (if b
 
 (define-compilation flet (definitions &rest body)
   (let* ((fnames (mapcar #'car definitions))
-         (fbody  (mapcar #'cdr definitions))
-         (cfuncs (mapcar #'compile-function-definition fbody))
+         (cfuncs (mapcar (lambda (def)
+                           (compile-lambda (cadr def)
+                                           `((block ,(car def)
+                                               ,@(cddr def)))))
+                         definitions))
          (*environment*
           (extend-lexenv (mapcar #'make-function-binding fnames)
                          *environment*
     (js!selfcall
       (mapconcat (lambda (func)
                   (code "var " (translate-function (car func))
-                         " = " (compile-lambda (cadr func) (cddr func))
+                         " = " (compile-lambda (cadr func)
+                                               `((block ,(car func) ,@(cddr func))))
                          ";" *newline*))
                 definitions)
       (ls-compile-block body t))))
         (let*-binding-wrapper specials body)))))
 
 
-(defvar *block-counter* 0)
-
 (define-compilation block (name &rest body)
-  (let* ((tr (incf *block-counter*))
-         (b (make-binding :name name :type 'block :value tr)))
+  ;; We use Javascript exceptions to implement non local control
+  ;; transfer. Exceptions has dynamic scoping, so we use a uniquely
+  ;; generated object to identify the block. The instance of a empty
+  ;; array is used to distinguish between nested dynamic Javascript
+  ;; exceptions. See https://github.com/davazp/jscl/issues/64 for
+  ;; futher details.
+  (let* ((idvar (gvarname name))
+         (b (make-binding :name name :type 'block :value idvar)))
     (when *multiple-value-p*
       (push 'multiple-value (binding-declarations b)))
     (let* ((*environment* (extend-lexenv (list b) *environment* 'block))
       (if (member 'used (binding-declarations b))
           (js!selfcall
             "try {" *newline*
+            "var " idvar " = [];" *newline*
             (indent cbody)
             "}" *newline*
             "catch (cf){" *newline*
-            "    if (cf.type == 'block' && cf.id == " tr ")" *newline*
+            "    if (cf.type == 'block' && cf.id == " idvar ")" *newline*
             (if *multiple-value-p*
                 "        return values.apply(this, forcemv(cf.values));"
                 "        return cf.values;")
   (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) "'.")))
+      (error "Return from unknown block `~S'." (symbol-name name)))
     (push 'used (binding-declarations b))
+    ;; The binding value is the name of a variable, whose value is the
+    ;; unique identifier of the block as exception. We can't use the
+    ;; variable name itself, because it could not to be unique, so we
+    ;; capture it in a closure.
     (js!selfcall
       (when multiple-value-p (code "var values = mv;" *newline*))
       "throw ({"
     "message: 'Throw uncatched.'"
     "})"))
 
-
-(defvar *tagbody-counter* 0)
-(defvar *go-tag-counter* 0)
-
 (defun go-tag-p (x)
   (or (integerp x) (symbolp x)))
 
 (defun declare-tagbody-tags (tbidx body)
-  (let ((bindings
-         (mapcar (lambda (label)
-                   (let ((tagidx (integer-to-string (incf *go-tag-counter*))))
-                     (make-binding :name label :type 'gotag :value (list tbidx tagidx))))
-                 (remove-if-not #'go-tag-p body))))
+  (let* ((go-tag-counter 0)
+         (bindings
+          (mapcar (lambda (label)
+                    (let ((tagidx (integer-to-string (incf go-tag-counter))))
+                      (make-binding :name label :type 'gotag :value (list tbidx tagidx))))
+                  (remove-if-not #'go-tag-p body))))
     (extend-lexenv bindings *environment* 'gotag)))
 
 (define-compilation tagbody (&rest body)
   (unless (go-tag-p (car body))
     (push (gensym "START") body))
   ;; Tagbody compilation
-  (let ((tbidx *tagbody-counter*))
+  (let ((branch (gvarname 'branch))
+        (tbidx (gvarname 'tbidx)))
     (let ((*environment* (declare-tagbody-tags tbidx body))
           initag)
       (let ((b (lookup-in-lexenv (first body) *environment* 'gotag)))
         (setq initag (second (binding-value b))))
       (js!selfcall
-        "var tagbody_" tbidx " = " initag ";" *newline*
+        ;; TAGBODY branch to take
+        "var " branch " = " initag ";" *newline*
+        "var " tbidx " = [];" *newline*
         "tbloop:" *newline*
         "while (true) {" *newline*
         (indent "try {" *newline*
                 (indent (let ((content ""))
-                          (code "switch(tagbody_" tbidx "){" *newline*
+                          (code "switch(" branch "){" *newline*
                                 "case " initag ":" *newline*
                                 (dolist (form (cdr body) content)
                                   (concatf content
                 "}" *newline*
                 "catch (jump) {" *newline*
                 "    if (jump.type == 'tagbody' && jump.id == " tbidx ")" *newline*
-                "        tagbody_" tbidx " = jump.label;" *newline*
+                "        " branch " = jump.label;" *newline*
                 "    else" *newline*
                 "        throw(jump);" *newline*
                 "}" *newline*)
              ((symbolp label) (symbol-name label))
              ((integerp label) (integer-to-string label)))))
     (when (null b)
-      (error (concat "Unknown tag `" n "'.")))
+      (error "Unknown tag `~S'" label))
     (js!selfcall
       "throw ({"
       "type: 'tagbody', "
 (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*
+    "var args = [" (if *multiple-value-p* "values" "pv") ", 0];" *newline*
     "return "
     (js!selfcall
       "var values = mv;" *newline*
                          "else" *newline*
                          (indent "args.push(vs);" *newline*)))
                  forms)
+      "args[1] = args.length-2;" *newline*
       "return func.apply(window, args);" *newline*) ";" *newline*))
 
 (define-compilation multiple-value-prog1 (first-form &rest forms)
 (define-setf-expander %js-vref (var)
   (let ((new-value (gensym)))
     (unless (stringp var)
-      (error "a string was expected"))
+      (error "`~S' is not a string." var))
     (values nil
             (list var)
             (list new-value)
          (bq-process (bq-completely-process (cadr x))))
         ((eq (car x) *comma*) (cadr x))
         ((eq (car x) *comma-atsign*)
-         ;; (error ",@~S after `" (cadr x))
-         (error "ill-formed"))
+         (error ",@~S after `" (cadr x)))
         ;; ((eq (car x) *comma-dot*)
         ;;  ;; (error ",.~S after `" (cadr x))
         ;;  (error "ill-formed"))
                       (nreconc q (list (list *bq-quote* p)))))
              (when (eq (car p) *comma*)
                (unless (null (cddr p))
-                 ;; (error "Malformed ,~S" p)
-                 (error "Malformed"))
+                 (error "Malformed ,~S" p))
                (return (cons *bq-append*
                              (nreconc q (list (cadr p))))))
              (when (eq (car p) *comma-atsign*)
-               ;; (error "Dotted ,@~S" p)
-               (error "Dotted"))
+               (error "Dotted ,@~S" p))
              ;; (when (eq (car p) *comma-dot*)
              ;;   ;; (error "Dotted ,.~S" p)
              ;;   (error "Dotted"))
 
 (defmacro variable-arity (args &body body)
   (unless (symbolp args)
-    (error "Bad usage of VARIABLE-ARITY, you must pass a symbol"))
+    (error "`~S' is not a symbol." args))
   `(variable-arity-call ,args
                         (lambda (,args)
                           (code "return " ,@body ";" *newline*))))
 
 (define-builtin float-to-string (x)
   (type-check (("x" "number" x))
-    "x.toString()"))
+    "make_lisp_string(x.toString())"))
 
 (define-builtin cons (x y)
   (code "({car: " x ", cdr: " y "})"))
      "return (typeof tmp == 'object' && 'name' in tmp);" *newline*)))
 
 (define-builtin make-symbol (name)
-  (type-check (("name" "string" name))
-    "({name: name})"))
+  (code "({name: " name "})"))
 
 (define-builtin symbol-name (x)
   (code "(" x ").name"))
   (js!selfcall
     "var symbol = " x ";" *newline*
     "var value = symbol.value;" *newline*
-    "if (value === undefined) throw \"Variable `\" + symbol.name + \"' is unbound.\";" *newline*
+    "if (value === undefined) throw \"Variable `\" + xstring(symbol.name) + \"' is unbound.\";" *newline*
     "return value;" *newline*))
 
 (define-builtin symbol-function (x)
   (js!selfcall
     "var symbol = " x ";" *newline*
     "var func = symbol.fvalue;" *newline*
-    "if (func === undefined) throw \"Function `\" + symbol.name + \"' is undefined.\";" *newline*
+    "if (func === undefined) throw \"Function `\" + xstring(symbol.name) + \"' is undefined.\";" *newline*
     "return func;" *newline*))
 
 (define-builtin symbol-plist (x)
   (code "((" x ").plist || " (ls-compile nil) ")"))
 
 (define-builtin lambda-code (x)
-  (code "(" x ").toString()"))
+  (code "make_lisp_string((" x ").toString())"))
 
-(define-builtin eq    (x y) (js!bool (code "(" x " === " y ")")))
-(define-builtin equal (x y) (js!bool (code "(" x  " == " y ")")))
+(define-builtin eq (x y)
+  (js!bool (code "(" x " === " y ")")))
 
-(define-builtin char-to-string (x)
+(define-builtin char-code (x)
+  (type-check (("x" "string" x))
+    "x.charCodeAt(0)"))
+
+(define-builtin code-char (x)
   (type-check (("x" "number" x))
     "String.fromCharCode(x)"))
 
+(define-builtin characterp (x)
+  (js!bool
+   (js!selfcall
+     "var x = " x ";" *newline*
+     "return (typeof(" x ") == \"string\") && x.length == 1;")))
+
+(define-builtin char-to-string (x)
+  (js!selfcall
+    "var r = [" x "];" *newline*
+    "r.type = 'character';"
+    "return r"))
+
 (define-builtin stringp (x)
-  (js!bool (code "(typeof(" x ") == \"string\")")))
+  (js!bool
+   (js!selfcall
+     "var x = " x ";" *newline*
+     "return typeof(x) == 'object' && 'length' in x && x.type == 'character';")))
 
 (define-builtin string-upcase (x)
-  (type-check (("x" "string" x))
-    "x.toUpperCase()"))
+  (code "make_lisp_string(xstring(" x ").toUpperCase())"))
 
 (define-builtin string-length (x)
-  (type-check (("x" "string" x))
-    "x.length"))
+  (code x ".length"))
 
-(define-raw-builtin slice (string a &optional b)
+(define-raw-builtin slice (vector a &optional b)
   (js!selfcall
-    "var str = " (ls-compile string) ";" *newline*
+    "var vector = " (ls-compile vector) ";" *newline*
     "var a = " (ls-compile a) ";" *newline*
     "var b;" *newline*
     (when b (code "b = " (ls-compile b) ";" *newline*))
-    "return str.slice(a,b);" *newline*))
+    "return vector.slice(a,b);" *newline*))
 
 (define-builtin char (string index)
-  (type-check (("string" "string" string)
-               ("index" "number" index))
-    "string.charCodeAt(index)"))
+  (code string "[" index "]"))
 
 (define-builtin concat-two (string1 string2)
-  (type-check (("string1" "string" string1)
-               ("string2" "string" string2))
-    "string1.concat(string2)"))
+  (js!selfcall
+    "var r = " string1 ".concat(" string2 ");" *newline*
+    "r.type = 'character';"
+    "return r;" *newline*))
 
 (define-raw-builtin funcall (func &rest args)
   (js!selfcall
     "var f = " (ls-compile func) ";" *newline*
     "return (typeof f === 'function'? f: f.fvalue)("
-    (join (cons (if *multiple-value-p* "values" "pv")
-                (mapcar #'ls-compile args))
+    (join (list* (if *multiple-value-p* "values" "pv")
+                 (integer-to-string (length args))
+                 (mapcar #'ls-compile args))
           ", ")
     ")"))
 
             (last (car (last args))))
         (js!selfcall
           "var f = " (ls-compile func) ";" *newline*
-          "var args = [" (join (cons (if *multiple-value-p* "values" "pv")
-                                     (mapcar #'ls-compile args))
+          "var args = [" (join (list* (if *multiple-value-p* "values" "pv")
+                                      (integer-to-string (length args))
+                                      (mapcar #'ls-compile args))
                                ", ")
           "];" *newline*
           "var tail = (" (ls-compile last) ");" *newline*
           "while (tail != " (ls-compile nil) "){" *newline*
           "    args.push(tail.car);" *newline*
+          "    args[1] += 1;" *newline*
           "    tail = tail.cdr;" *newline*
           "}" *newline*
           "return (typeof f === 'function'? f : f.fvalue).apply(this, args);" *newline*))))
 
 (define-builtin js-eval (string)
-  (type-check (("string" "string" string))
-    (if *multiple-value-p*
-        (js!selfcall
-          "var v = globalEval(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*)
-        "globalEval(string)")))
+  (if *multiple-value-p*
+      (js!selfcall
+        "var v = globalEval(xstring(" string "));" *newline*
+        "return values.apply(this, forcemv(v));" *newline*)
+      (code "globalEval(xstring(" string ")")))
 
-(define-builtin error (string)
+(define-builtin %throw (string)
   (js!selfcall "throw " string ";" *newline*))
 
 (define-builtin new () "{}")
 
 (define-builtin oget (object key)
   (js!selfcall
-    "var tmp = " "(" object ")[" key "];" *newline*
+    "var tmp = " "(" object ")[xstring(" key ")];" *newline*
     "return tmp == undefined? " (ls-compile nil) ": tmp ;" *newline*))
 
 (define-builtin oset (object key value)
-  (code "((" object ")[" key "] = " value ")"))
+  (code "((" object ")[xstring(" key ")] = " value ")"))
 
 (define-builtin in (key object)
-  (js!bool (code "((" key ") in (" object "))")))
+  (js!bool (code "(xstring(" key ") in (" object ")")))
 
 (define-builtin functionp (x)
   (js!bool (code "(typeof " x " == 'function')")))
 
 (define-builtin write-string (x)
-  (type-check (("x" "string" x))
-    "lisp.write(x)"))
+  (code "lisp.write(xstring(" x "))"))
 
 (define-builtin make-array (n)
   (js!selfcall
 
 (defun compile-funcall (function args)
   (let* ((values-funcs (if *multiple-value-p* "values" "pv"))
-         (arglist (concat "(" (join (cons values-funcs (mapcar #'ls-compile args)) ", ") ")")))
+         (arglist (concat "(" (join (list* values-funcs
+                                           (integer-to-string (length args))
+                                           (mapcar #'ls-compile args)) ", ") ")")))
     (unless (or (symbolp function)
                 (and (consp function)
                      (eq (car function) 'lambda)))
-      (error "Bad function"))
+      (error "Bad function designator `~S'" function))
     (cond
       ((translate-function function)
        (concat (translate-function function) arglist))
               (code (ls-compile `',sexp) ".value"))
              (t
               (ls-compile `(symbol-value ',sexp))))))
-        ((integerp sexp) (integer-to-string sexp))
-        ((floatp sexp) (float-to-string sexp))
-        ((stringp sexp) (code "\"" (escape-string sexp) "\""))
-        ((arrayp sexp) (literal sexp))
+        ((or (integerp sexp) (floatp sexp) (characterp sexp) (stringp sexp) (arrayp sexp))
+         (literal sexp))
         ((listp sexp)
          (let ((name (car sexp))
                (args (cdr sexp)))
              (t
               (compile-funcall name args)))))
         (t
-         (error (concat "How should I compile " (prin1-to-string sexp) "?")))))))
+         (error "How should I compile `~S'?" sexp))))))
 
 
 (defvar *compile-print-toplevels* nil)
       (t
        (when *compile-print-toplevels*
          (let ((form-string (prin1-to-string sexp)))
-           (write-string "Compiling ")
-           (write-string (truncate-string form-string))
-           (write-line "...")))
-
+           (format t "Compiling ~a..." (truncate-string form-string))))
        (let ((code (ls-compile sexp multiple-value-p)))
          (code (join-trailing (get-toplevel-compilations)
                               (code ";" *newline*))