Fix a bug related to SETQ which DO* uncovered
[jscl.git] / ecmalisp.lisp
index 53449f2..cb89dfc 100644 (file)
 ;;; language to the compiler to be able to run.
 
 #+ecmalisp
-(js-eval "function pv (x) { return x ; }")
-
-#+ecmalisp
-(js-eval "
-function mv(){
-     var r = [];
-     r['multiple-value'] = true;
-     for (var i=0; i<arguments.length; i++)
-         r.push(arguments[i]);
-     return r;
-}")
-
-;;; NOTE: Define VALUES to be MV for toplevel forms. It is because
-;;; `eval' compiles the forms and execute the Javascript code at
-;;; toplevel with `js-eval', so it is necessary to return multiple
-;;; values from the eval function.
-#+ecmalisp
-(js-eval "var values = mv;")
-
-#+ecmalisp
 (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
@@ -62,8 +44,12 @@ function mv(){
 
   (declaim (constant nil t) (special t nil))
   (setq nil 'nil)
+  (js-vset "nil" nil)
   (setq t 't)
 
+  (defmacro lambda (args &body body)
+    `(function (lambda ,args ,@body)))
+
   (defmacro when (condition &body body)
     `(if ,condition (progn ,@body) nil))
 
@@ -91,7 +77,6 @@ function mv(){
 
   (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))))
@@ -316,6 +301,34 @@ function mv(){
       `(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))
@@ -638,11 +651,6 @@ function mv(){
   (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)))
 
@@ -836,7 +844,7 @@ function mv(){
 (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)))
@@ -1007,12 +1015,14 @@ function mv(){
 ;;; too. The respective real functions are defined in the target (see
 ;;; the beginning of this file) as well as some primitive functions.
 
-;;; If the special variable `*multiple-value-p*' is NON-NIL, then the
-;;; compilation of the current form is allowed to return multiple
-;;; values, using the VALUES variable.
+;;; 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)
 
-(defvar *compilation-unit-checks* '())
 
 (defun make-binding (name type value &optional declarations)
   (list name type value declarations))
@@ -1023,10 +1033,10 @@ function mv(){
 (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)
-  (setcar (cdddr b) value))
+  (rplaca (cdddr b) value))
 
 (defun push-binding-declaration (decl b)
   (set-binding-declarations b (cons decl (binding-declarations b))))
@@ -1040,10 +1050,10 @@ function mv(){
 
 (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)))
@@ -1069,7 +1079,7 @@ function mv(){
 (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
@@ -1086,7 +1096,8 @@ function mv(){
 
 (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)
@@ -1111,11 +1122,7 @@ function mv(){
     (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)
@@ -1167,7 +1174,26 @@ function mv(){
         "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))
@@ -1191,17 +1217,11 @@ function mv(){
                            (append required-arguments optional-arguments)))
              ",")
        "){" *newline*
-       ;; Check number of arguments
        (indent
-        (if required-arguments
-            (concat "if (arguments.length < " (integer-to-string (1+ n-required-arguments))
-                    ") throw 'too few arguments';" *newline*)
-            "")
-        (if (not rest-argument)
-            (concat "if (arguments.length > "
-                    (integer-to-string (+ 1 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
             (concat "switch(arguments.length-1){" *newline*
@@ -1237,13 +1257,14 @@ function mv(){
             "")
         ;; Body
         (let ((*multiple-value-p* t)) (ls-compile-block body t)))
-       *newline*
        "})"))))
 
 
 (defun setq-pair (var val)
   (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)))))
 
@@ -1310,13 +1331,19 @@ function mv(){
           (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)))
-            (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) ", ") "]")))
@@ -1339,20 +1366,26 @@ function mv(){
 (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)))))
 
+(defvar *compiling-file* nil)
 (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)
-  (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)
   (and (claimp x 'variable 'special) t))
@@ -1407,7 +1440,7 @@ function mv(){
 
 
 ;;; 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)))
@@ -1456,52 +1489,68 @@ function mv(){
 (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) *multiple-value-p*) ";" *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)
-  (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*
-    (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*
-    "        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
+    "var values = mv;" *newline*
     "throw ({"
     "type: 'catch', "
     "id: " (ls-compile id) ", "
-    "value: " (ls-compile value) ", "
+    "values: " (ls-compile value t) ", "
     "message: 'Throw uncatched.'"
     "})"))
 
@@ -1611,6 +1660,7 @@ function mv(){
     "return args;" *newline*))
 
 
+
 ;;; A little backquote implementation without optimizations of any
 ;;; kind for ecmalisp.
 (defun backquote-expand-1 (form)
@@ -1795,13 +1845,13 @@ function mv(){
     (ls-compile nil)
     ": tmp.cdr;" *newline*))
 
-(define-builtin setcar (x new)
+(define-builtin rplaca (x new)
   (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))
-    (concat "(x.cdr = " new ")")))
+    (concat "(x.cdr = " new ", x)")))
 
 (define-builtin symbolp (x)
   (js!bool
@@ -2012,7 +2062,8 @@ function mv(){
 (defun compile-funcall (function args)
   (let ((values-funcs (if *multiple-value-p* "values" "pv")))
     (if (and (symbolp function)
-             (claimp function 'function 'non-overridable))
+             #+ecmalisp (eq (symbol-package function) (find-package "COMMON-LISP"))
+             #+common-lisp t)
         (concat (ls-compile `',function) ".fvalue("
                 (join (cons values-funcs (mapcar #'ls-compile args))
                       ", ")
@@ -2025,7 +2076,7 @@ function mv(){
 (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)) *multiple-value-p*) ";")
+              "return " (ls-compile (car (last sexps)) *multiple-value-p*) ";")
       (join-trailing
        (remove-if #'null-or-empty-p (mapcar #'ls-compile sexps))
        (concat ";" *newline*))))
@@ -2097,20 +2148,20 @@ function mv(){
             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 documentation dolist dotimes ecase eq eql equal error eval
-            every export fdefinition find-package find-symbol first 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
+            disassemble do do* documentation dolist dotimes ecase eq eql equal
+           error eval every export fdefinition find-package find-symbol first
+           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
             plusp prin1-to-string print proclaim prog1 prog2 progn psetq 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 values values-list variable warn when write-line
+            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*)
@@ -2156,19 +2207,17 @@ function mv(){
         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))