Remove CODE completely
[jscl.git] / src / compiler.lisp
index 66844fb..0ce17c3 100644 (file)
@@ -1,6 +1,6 @@
 ;;; compiler.lisp ---
 
-;; copyright (C) 2012, 2013 David Vazquez
+;; Copyright (C) 2012, 2013 David Vazquez
 ;; Copyright (C) 2012 Raimon Grau
 
 ;; JSCL is free software: you can redistribute it and/or
@@ -26,7 +26,6 @@
 (define-js-macro bool (expr)
   `(if ,expr ,(ls-compile t) ,(ls-compile nil)))
 
-
 ;;; Translate the Lisp code to Javascript. It will compile the special
 ;;; forms. Some primitive functions are compiled as special forms
 ;;; too. The respective real functions are defined in the target (see
 
 
 (defvar *environment* (make-lexenv))
-
 (defvar *variable-counter* 0)
 
 (defun gvarname (symbol)
 ;;; evaluated. For this reason we define a valid macro-function for
 ;;; this symbol.
 (defvar *magic-unquote-marker* (gensym "MAGIC-UNQUOTE"))
+
 #-jscl
 (setf (macro-function *magic-unquote-marker*)
       (lambda (form &optional environment)
   (let ((head (butlast cons))
         (tail (last cons)))
     `(call |QIList|
-           ,@(mapcar (lambda (x) `(code ,(literal x t))) head)
-           (code ,(literal (car tail) t))
-           (code ,(literal (cdr tail) t)))))
+           ,@(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)))
-    (list-to-vector (mapcar (lambda (x) `(code ,(literal x)))
-                            elements))))
+    (list-to-vector (mapcar #'literal elements))))
 
 (defun dump-string (string)
   `(call |make_lisp_string| ,string))
 
 (defun literal (sexp &optional recursive)
   (cond
-    ((integerp sexp) (integer-to-string sexp))
-    ((floatp sexp) (float-to-string sexp))
-    ((characterp sexp) (js-escape-string (string sexp)))
+    ((integerp sexp) sexp)
+    ((floatp sexp) sexp)
+    ((characterp sexp)
+     ;; TODO: Remove selfcall after migration
+     `(selfcall (return ,(string sexp))))
     (t
      (or (cdr (assoc sexp *literal-table* :test #'eql))
          (let ((dumped (typecase sexp
            (if (and recursive (not (symbolp sexp)))
                dumped
                (let ((jsvar (genlit)))
-                 (push (cons sexp jsvar) *literal-table*)
-                 (toplevel-compilation `(code "var " ,jsvar " = " ,dumped))
+                 (push (cons sexp (make-symbol jsvar)) *literal-table*)
+                 (toplevel-compilation `(var (,(make-symbol jsvar) ,dumped)))
                  (when (keywordp sexp)
-                   (toplevel-compilation `(code ,jsvar ".value = " ,jsvar)))
-                 jsvar)))))))
+                   (toplevel-compilation `(= ,(get (make-symbol jsvar) "value") ,(make-symbol jsvar))))
+                 (make-symbol jsvar))))))))
 
 
 (define-compilation quote (sexp)
     ((symbolp x)
      (let ((b (lookup-in-lexenv x *environment* 'function)))
        (if b
-          (binding-value b)
+          (make-symbol (binding-value b))
           (ls-compile `(symbol-function ',x)))))))
 
-
 (defun make-function-binding (fname)
   (make-binding :name fname :type 'function :value (gvarname fname)))
 
   (let ((var (first binding))
         (value (second binding)))
     (if (special-variable-p var)
-        `(code ,(ls-compile `(setq ,var ,value)) ";" )
+        (ls-compile `(setq ,var ,value))
         (let* ((v (gvarname var))
                (b (make-binding :name var :type 'variable :value v)))
-          (prog1 `(code "var " ,v " = " ,(ls-compile value) ";" )
+          (prog1 `(var (,(make-symbol v) ,(ls-compile value)))
             (push-to-lexenv b *environment* 'variable))))))
 
 ;;; Wrap BODY to restore the symbol values of SYMBOLS after body. It
     (return-from let*-binding-wrapper body))
   (let ((store (mapcar (lambda (s) (cons s (gvarname s)))
                        (remove-if-not #'special-variable-p symbols))))
-    `(code
-      "try {"
-      (code
-       ,@(mapcar (lambda (b)
-                   (let ((s (ls-compile `(quote ,(car b)))))
-                     `(code "var " ,(cdr b) " = " ,s ".value;" )))
-                 store)
-       ,body)
-      "}"
-      "finally {"
-      (code
-       ,@(mapcar (lambda (b)
-                   (let ((s (ls-compile `(quote ,(car b)))))
-                     `(code ,s ".value" " = " ,(cdr b) ";" )))
-                 store))
-      "}" )))
+    `(progn
+       (try
+        ,@(mapcar (lambda (b)
+                    (let ((s (ls-compile `(quote ,(car b)))))
+                      `(var (,(make-symbol (cdr b)) (get ,s "value")))))
+                  store)
+        ,body)
+       (finally
+        ,@(mapcar (lambda (b)
+                    (let ((s (ls-compile `(quote ,(car b)))))
+                      `(= (get ,s "value") ,(make-symbol (cdr b)))))
+                  store)))))
 
 (define-compilation let* (bindings &rest body)
   (let ((bindings (mapcar #'ensure-list bindings))
         (*environment* (copy-lexenv *environment*)))
-    (js!selfcall
-      (let ((specials (remove-if-not #'special-variable-p (mapcar #'first bindings)))
-            (body `(code ,@(mapcar #'let*-initialize-value bindings)
-                         ,(ls-compile-block body t t))))
-        (let*-binding-wrapper specials body)))))
+    (let ((specials (remove-if-not #'special-variable-p (mapcar #'first bindings)))
+          (body `(progn
+                   ,@(mapcar #'let*-initialize-value bindings)
+                   ,(ls-compile-block body t t))))
+      `(selfcall ,(let*-binding-wrapper specials body)))))
 
 
 (define-compilation block (name &rest body)
     (let* ((*environment* (extend-lexenv (list b) *environment* 'block))
            (cbody (ls-compile-block body t)))
       (if (member 'used (binding-declarations b))
-          (js!selfcall
-            "try {"
-            "var " idvar " = [];"
-            `(code ,cbody)
-            "}"
-            "catch (cf){"
-            "    if (cf.type == 'block' && cf.id == " idvar ")"
-            (if *multiple-value-p*
-                "        return values.apply(this, forcemv(cf.values));"
-                "        return cf.values;")
-
-            "    else"
-            "        throw cf;"
-            "}" )
-          (js!selfcall cbody)))))
+          `(selfcall
+            (try
+             (var (,(make-symbol idvar) #()))
+             ,cbody)
+            (catch (cf)
+              (if (and (== (get cf "type") "block")
+                       (== (get cf "id") ,(make-symbol idvar)))
+                  ,(if *multiple-value-p*
+                       `(return (call (get |values| "apply") this (call |forcemv| (get cf "values"))))
+                       `(return (get cf "values")))
+                  (throw cf))))
+          ;; TODO: is selfcall necessary here?
+          `(selfcall ,cbody)))))
 
 (define-compilation return-from (name &optional value)
   (let* ((b (lookup-in-lexenv name *environment* 'block))
                                (if (go-tag-p form)
                                    (let ((b (lookup-in-lexenv form *environment* 'gotag)))
                                      (collect `(case ,(second (binding-value b)))))
-                                   (progn
-                                     (collect (ls-compile form))
-                                     ;; TEMPORAL!
-                                     (collect '(code ";"))))))
+                                   (collect (ls-compile form)))))
                           default
                           (break tbloop)))
                  (catch (jump)
   `(selfcall
     (var (args ,(ls-compile first-form *multiple-value-p*)))
     ;; TODO: Interleave is temporal
-    (progn ,@(interleave (mapcar #'ls-compile forms)
-                         '(code ";")
-                         t))
+    (progn ,@(mapcar #'ls-compile forms))
     (return args)))
 
 (define-transformation backquote (form)
      (values form nil))))
 
 (defun compile-funcall (function args)
-  (let* ((values-funcs (if *multiple-value-p* "values" "pv"))
-         (arglist `(code "(" ,@(interleave (list* values-funcs
-                                                  (integer-to-string (length args))
-                                                  (mapcar #'ls-compile args))
-                                           ", ")
-                         ")")))
+  (let* ((arglist (list* (if *multiple-value-p* '|values| '|pv|)
+                         (length args)
+                         (mapcar #'ls-compile args))))
     (unless (or (symbolp function)
                 (and (consp function)
                      (member (car function) '(lambda oget))))
       (error "Bad function designator `~S'" function))
     (cond
       ((translate-function function)
-       `(code ,(translate-function function) ,arglist))
+       `(call ,(make-symbol (translate-function function)) ,@arglist))
       ((and (symbolp function)
             #+jscl (eq (symbol-package function) (find-package "COMMON-LISP"))
             #-jscl t)
-       `(code ,(ls-compile `',function) ".fvalue" ,arglist))
+       `(call (get ,(ls-compile `',function) "fvalue") ,@arglist))
       #+jscl((symbolp function)
-       `(code ,(ls-compile `#',function) ,arglist))
+             `(call ,(ls-compile `#',function) ,@arglist))
       ((and (consp function) (eq (car function) 'lambda))
-       `(code ,(ls-compile `#',function) ,arglist))
+       `(call ,(ls-compile `#',function) ,@arglist))
       ((and (consp function) (eq (car function) 'oget))
-       `(code ,(ls-compile function) ,arglist))
+       `(call ,(ls-compile function) ,@arglist))
       (t
        (error "Bad function descriptor")))))
 
       (parse-body sexps :declarations decls-allowed-p)
     (declare (ignore decls))
     (if return-last-p
-        `(code ,(ls-compile-block (butlast sexps) nil decls-allowed-p)
-               "return " ,(ls-compile (car (last sexps)) *multiple-value-p*) ";")
-        `(code
-          ,@(interleave (mapcar #'ls-compile sexps) ";
-" *newline*)
-          ";" ,*newline*))))
+        `(progn
+           ,@(mapcar #'ls-compile (butlast sexps))
+           (return ,(ls-compile (car (last sexps)) *multiple-value-p*)))
+        `(progn ,@(mapcar #'ls-compile sexps)))))
 
 (defun ls-compile* (sexp &optional multiple-value-p)
   (multiple-value-bind (sexp expandedp) (!macroexpand-1 sexp)
          (let ((b (lookup-in-lexenv sexp *environment* 'variable)))
            (cond
              ((and b (not (member 'special (binding-declarations b))))
-              (binding-value b))
+              (make-symbol (binding-value b)))
              ((or (keywordp sexp)
                   (and b (member 'constant (binding-declarations b))))
               `(get ,(ls-compile `',sexp) "value"))
          (error "How should I compile `~S'?" sexp))))))
 
 (defun ls-compile (sexp &optional multiple-value-p)
-  `(code "(" ,(ls-compile* sexp multiple-value-p) ")"))
+  (ls-compile* sexp multiple-value-p))
 
 
 (defvar *compile-print-toplevels* nil)
          (let ((form-string (prin1-to-string sexp)))
            (format t "Compiling ~a..." (truncate-string form-string))))
        (let ((code (ls-compile sexp multiple-value-p)))
-         `(code
-           ,@(interleave (get-toplevel-compilations) ";
-" t)
-           ,(when code
-                  `(code ,code ";"))))))))
+         `(progn
+            ,@(get-toplevel-compilations)
+            (code ,code ";
+")))))))
 
 (defun ls-compile-toplevel (sexp &optional multiple-value-p)
   (with-output-to-string (*standard-output*)