Use destructuring-bind
[jscl.git] / src / compiler.lisp
index 4510427..10783e9 100644 (file)
 
 (defun gvarname (symbol)
   (declare (ignore symbol))
-  (code "v" (incf *variable-counter*)))
+  (incf *variable-counter*)
+  (concat "v" (integer-to-string *variable-counter*)))
 
 (defun translate-variable (symbol)
   (awhen (lookup-in-lexenv symbol *environment* 'variable)
   (if (or name docstring)
       (js!selfcall*
         `(var (func ,code))
-        (when name      `(= (get func |fname|) ,name))
-        (when docstring `(= (get func |docstring|) ,docstring))
+        (when name      `(= (get func "fname") ,name))
+        (when docstring `(= (get func "docstring") ,docstring))
         `(return func))
-      `(code ,code)))
+      code))
 
 (defun lambda-check-argument-count
     (n-required-arguments n-optional-arguments rest-p)
             (eq (binding-type b) 'variable)
             (not (member 'special (binding-declarations b)))
             (not (member 'constant (binding-declarations b))))
-       `(code ,(binding-value b) " = " ,(ls-compile val)))
+       ;; TODO: Unnecesary make-symbol when codegen migration is
+       ;; finished.
+       `(= ,(make-symbol (binding-value b)) ,(ls-compile val)))
       ((and b (eq (binding-type b) 'macro))
        (ls-compile `(setf ,var ,val)))
       (t
        ((null (cdr pairs))
         (error "Odd pairs in SETQ"))
        (t
-         (push `(code ,(setq-pair (car pairs) (cadr pairs))
-                      ,(if (null (cddr pairs)) "" ", "))
-               result)
+         (push `,(setq-pair (car pairs) (cadr pairs)) result)
         (setq pairs (cddr pairs)))))
-    `(code "(" ,@(reverse result) ")")))
+    `(progn ,@(reverse result))))
 
 
 ;;; Compilation of literals an object dumping
 (defvar *literal-counter* 0)
 
 (defun genlit ()
-  (code "l" (incf *literal-counter*)))
+  (incf *literal-counter*)
+  (concat "l" (integer-to-string *literal-counter*)))
 
 (defun dump-symbol (symbol)
   #-jscl
 (defun dump-cons (cons)
   (let ((head (butlast cons))
         (tail (last cons)))
-    `(code "QIList("
-           ,@(interleave (mapcar (lambda (x) (literal x t)) head) "," t)
-           ,(literal (car tail) t)
-           ","
-           ,(literal (cdr tail) t)
-           ")")))
+    `(call |QIList|
+           ,@(mapcar (lambda (x) `(code ,(literal x t))) head)
+           (code ,(literal (car tail) t))
+           (code ,(literal (cdr tail) t)))))
 
 (defun dump-array (array)
   (let ((elements (vector-to-list array)))
        0                                ; TODO: Force
                                         ; braces. Unnecesary when code
                                         ; is gone
-       (code ,(ls-compile-block body)))
+       ,(ls-compile-block body))
    `(return ,(ls-compile nil))))
 
 (define-compilation function (x)
     ((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)))
+     (destructuring-bind (name ll &rest body) (cdr x)
        (compile-lambda ll body
                        :name (symbol-name name)
                        :block name)))
 (define-compilation progn (&rest body)
   (if (null (cdr body))
       (ls-compile (car body) *multiple-value-p*)
-      `(code "("
-             ,@(interleave
-                (append (mapcar #'ls-compile (butlast body))
-                        (list (ls-compile (car (last body)) t)))
-                ",")
-             ")")))
+      `(progn
+         ,@(append (mapcar #'ls-compile (butlast body))
+                   (list (ls-compile (car (last body)) t))))))
 
 (define-compilation macrolet (definitions &rest body)
   (let ((*environment* (copy-lexenv *environment*)))
       "})")))
 
 (define-compilation catch (id &rest body)
-  (js!selfcall
-    "var id = " (ls-compile id) ";"
-    "try {"
-    `(code ,(ls-compile-block body t))
-    "}"
-    "catch (cf){"
-    "    if (cf.type == 'catch' && cf.id == id)"
-    (if *multiple-value-p*
-        "        return values.apply(this, forcemv(cf.values));"
-        "        return pv.apply(this, forcemv(cf.values));")
-
-    "    else"
-    "        throw cf;"
-    "}" ))
+  (js!selfcall*
+    `(var (|id| ,(ls-compile id)))
+    `(try
+      ,(ls-compile-block body t))
+    `(catch (|cf|)
+       (if (and (== (get |cf| "type") "catch")
+                (== (get |cf| "id") |id|))
+           ,(if *multiple-value-p*
+                `(return (call (get |values| "apply")
+                               this
+                               (call |forcemv| (get |cf| "values"))))
+                `(return (call (get |pv| "apply")
+                               this
+                               (call |forcemv| (get |cf| "values")))))
+           (throw |cf|)))))
 
 (define-compilation throw (id value)
-  (js!selfcall
-    "var values = mv;"
-    "throw ({"
-    "type: 'catch', "
-    "id: " (ls-compile id) ", "
-    "values: " (ls-compile value t) ", "
-    "message: 'Throw uncatched.'"
-    "})"))
+  (js!selfcall*
+    `(var (|values| |mv|))
+    `(throw (object
+             |type| "catch"
+             |id| ,(ls-compile id)
+             |values| ,(ls-compile value t)
+             |message| "Throw uncatched."))))
 
 (defun go-tag-p (x)
   (or (integerp x) (symbolp x)))
       "})" )))
 
 (define-compilation unwind-protect (form &rest clean-up)
-  (js!selfcall
-    "var ret = " (ls-compile nil) ";"
-    "try {"
-    `(code "ret = " ,(ls-compile form) ";" )
-    "} finally {"
-    `(code ,(ls-compile-block clean-up))
-    "}"
-    "return ret;" ))
+  (js!selfcall*
+    `(var (|ret| ,(ls-compile nil)))
+    `(try
+       (= |ret| ,(ls-compile form)))
+    `(finally
+      ,(ls-compile-block clean-up))
+    `(return |ret|)))
 
 (define-compilation multiple-value-call (func-form &rest forms)
   (js!selfcall
         (prelude '()))
     (dolist (x args)
       (cond
-        ((floatp x) (push (float-to-string x) fargs))
-        ((numberp x) (push (integer-to-string x) fargs))
-        (t (let ((v (code "x" (incf counter))))
+        ((or (floatp x) (numberp x)) (push x fargs))
+        (t (let ((v (make-symbol (code "x" (incf counter)))))
              (push v fargs)
              (push `(code "var " ,v " = " ,(ls-compile x) ";"
                           "if (typeof " ,v " !== 'number') throw 'Not a number!';")
 
 (define-raw-builtin + (&rest numbers)
   (if (null numbers)
-      "0"
+      0
       (variable-arity numbers
-        `(code ,@(interleave numbers "+")))))
+        `(+ ,@numbers))))
 
 (define-raw-builtin - (x &rest others)
   (let ((args (cons x others)))
-    (variable-arity args
-      (if (null others)
-         `(code "-" ,(car args))
-         `(code ,@(interleave args "-"))))))
+    (variable-arity args `(- ,@args))))
 
 (define-raw-builtin * (&rest numbers)
   (if (null numbers)
-      "1"
-      (variable-arity numbers
-       `(code ,@(interleave numbers "*")))))
+      1
+      (variable-arity numbers `(* ,@numbers))))
 
 (define-raw-builtin / (x &rest others)
   (let ((args (cons x others)))
     (variable-arity args
       (if (null others)
-          `(code "1 /" ,(car args))
-         `(code ,@(interleave args "/"))))))
+          `(/ 1 ,(car args))
+          (reduce (lambda (x y) `(/ ,x ,y))
+                  args)))))
 
 (define-builtin mod (x y) (num-op-num x "%" y))
 
 (defun comparison-conjuntion (vars op)
   (cond
     ((null (cdr vars))
-     "true")
+     'true)
     ((null (cddr vars))
-     `(code ,(car vars) ,op ,(cadr vars)))
+     `(,op ,(car vars) ,(cadr vars)))
     (t
-     `(code ,(car vars) ,op ,(cadr vars)
-            " && "
-            ,(comparison-conjuntion (cdr vars) op)))))
+     `(and (,op ,(car vars) ,(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))))))
+        (js!bool (comparison-conjuntion args ',sym))))))
 
-(define-builtin-comparison > ">")
-(define-builtin-comparison < "<")
-(define-builtin-comparison >= ">=")
-(define-builtin-comparison <= "<=")
-(define-builtin-comparison = "==")
-(define-builtin-comparison /= "!=")
+(define-builtin-comparison > >)
+(define-builtin-comparison < <)
+(define-builtin-comparison >= >=)
+(define-builtin-comparison <= <=)
+(define-builtin-comparison = ==)
+(define-builtin-comparison /= !=)
 
 (define-builtin numberp (x)
-  (js!bool `(code "(typeof (" ,x ") == \"number\")")))
+  (js!bool `(== (typeof ,x) "number")))
 
 (define-builtin floor (x)
   (type-check (("x" "number" x))
     "make_lisp_string(x.toString())"))
 
 (define-builtin cons (x y)
-  `(code "({car: " ,x ", cdr: " ,y "})"))
+  `(object "car" ,x "cdr" ,y))
 
 (define-builtin consp (x)
   (js!bool
      "return (typeof tmp == 'object' && 'car' in tmp);" )))
 
 (define-builtin car (x)
-  (js!selfcall
-    "var tmp = " x ";"
-    "return tmp === " (ls-compile nil)
-    "? " (ls-compile nil)
-    ": tmp.car;" ))
+  (js!selfcall*
+    `(var (tmp ,x))
+    `(return (if (=== tmp ,(ls-compile nil))
+                 ,(ls-compile nil)
+                 (get tmp "car")))))
 
 (define-builtin cdr (x)
-  (js!selfcall
-    "var tmp = " x ";"
-    "return tmp === " (ls-compile nil) "? "
-    (ls-compile nil)
-    ": tmp.cdr;" ))
+  (js!selfcall*
+    `(var (tmp ,x))
+    `(return (if (=== tmp ,(ls-compile nil))
+                 ,(ls-compile nil)
+                 (get tmp "cdr")))))
 
 (define-builtin rplaca (x new)
   (type-check (("x" "object" x))
     `(code "(x.cdr = " ,new ", x)")))
 
 (define-builtin symbolp (x)
-  (js!bool `(code "(" ,x " instanceof Symbol)")))
+  (js!bool `(instanceof ,x |Symbol|)))
 
 (define-builtin make-symbol (name)
-  `(code "(new Symbol(" ,name "))"))
+  `(new (call |Symbol| ,name)))
 
 (define-builtin symbol-name (x)
-  `(code "(" ,x ").name"))
+  `(get ,x "name"))
 
 (define-builtin set (symbol value)
-  `(code "(" ,symbol ").value = " ,value))
+  `(= (get ,symbol "value") ,value))
 
 (define-builtin fset (symbol value)
-  `(code "(" ,symbol ").fvalue = " ,value))
+  `(= (get ,symbol "fvalue") ,value))
 
 (define-builtin boundp (x)
-  (js!bool `(code "(" ,x ".value !== undefined)")))
+  (js!bool `(!== (get ,x "value") undefined)))
 
 (define-builtin fboundp (x)
-  (js!bool `(code "(" ,x ".fvalue !== undefined)")))
+  (js!bool `(!== (get ,x "fvalue") undefined)))
 
 (define-builtin symbol-value (x)
-  (js!selfcall
-    "var symbol = " x ";"
-    "var value = symbol.value;"
-    "if (value === undefined) throw \"Variable `\" + xstring(symbol.name) + \"' is unbound.\";"
-    "return value;" ))
+  (js!selfcall*
+    `(var (symbol ,x)
+          (value (get symbol "value")))
+    `(if (=== value undefined)
+         (throw (+ "Variable `" (call |xstring| (get symbol "name")) "' is unbound.")))
+    `(return value)))
 
 (define-builtin symbol-function (x)
-  (js!selfcall
-    "var symbol = " x ";"
-    "var func = symbol.fvalue;"
-    "if (func === undefined) throw \"Function `\" + xstring(symbol.name) + \"' is undefined.\";"
-    "return func;" ))
+  (js!selfcall*
+    `(var (symbol ,x)
+          (func (get symbol "fvalue")))
+    `(if (=== func undefined)
+         (throw (+ "Function `" (call |xstring| (get symbol "name")) "' is undefined.")))
+    `(return func)))
 
 (define-builtin symbol-plist (x)
-  `(code "((" ,x ").plist || " ,(ls-compile nil) ")"))
+  `(or (get ,x "plist") ,(ls-compile nil)))
 
 (define-builtin lambda-code (x)
-  `(code "make_lisp_string((" ,x ").toString())"))
+  `(call |make_lisp_string| (call (get ,x "toString"))))
 
 (define-builtin eq (x y)
-  (js!bool `(code "(" ,x " === " ,y ")")))
+  (js!bool `(=== ,x ,y)))
 
 (define-builtin char-code (x)
   (type-check (("x" "string" x))
 
 (define-builtin characterp (x)
   (js!bool
-   (js!selfcall
-     "var x = " x ";"
-     "return (typeof(" x ") == \"string\") && (x.length == 1 || x.length == 2);")))
+   (js!selfcall*
+     `(var (x ,x))
+     `(return (and (== (typeof x) "string")
+                   (or (== (get x "length") 1)
+                       (== (get x "length") 2)))))))
 
 (define-builtin char-upcase (x)
-  `(code "safe_char_upcase(" ,x ")"))
+  `(call |safe_char_upcase| ,x))
 
 (define-builtin char-downcase (x)
-  `(code "safe_char_downcase(" ,x ")"))
+  `(call |safe_char_downcase| ,x))
 
 (define-builtin stringp (x)
   (js!bool
-   (js!selfcall
-     "var x = " x ";"
-     "return typeof(x) == 'object' && 'length' in x && x.stringp == 1;")))
+   (js!selfcall*
+     `(var (x ,x))
+     `(return (and (and (===(typeof x) "object")
+                        (in "length" x))
+                   (== (get x "stringp") 1))))))
 
 (define-raw-builtin funcall (func &rest args)
-  (js!selfcall
-    "var f = " (ls-compile func) ";"
-    "return (typeof f === 'function'? f: f.fvalue)("
-    `(code
-     ,@(interleave (list* (if *multiple-value-p* "values" "pv")
-                          (integer-to-string (length args))
-                          (mapcar #'ls-compile args))
-                   ", "))
-    ")"))
+  (js!selfcall*
+    `(var (f ,(ls-compile func)))
+    `(return (call (if (=== (typeof f) "function")
+                       f
+                       (get f "fvalue"))
+                   ,@(list* (if *multiple-value-p* '|values| '|pv|)
+                            (length args)
+                            (mapcar #'ls-compile args))))))
 
 (define-raw-builtin apply (func &rest args)
   (if (null args)
 
 (define-builtin js-eval (string)
   (if *multiple-value-p*
-      (js!selfcall
-        "var v = globalEval(xstring(" string "));"
-        "return values.apply(this, forcemv(v));" )
-      `(code "globalEval(xstring(" ,string "))")))
+      (js!selfcall*
+        `(var (v (call |globalEval| (call |xstring| ,string))))
+        `(return (call (get |values| "apply") this (call |forcemv| v))))
+      `(call |globalEval| (call |xstring| ,string))))
 
 (define-builtin %throw (string)
-  (js!selfcall "throw " string ";" ))
+  (js!selfcall* `(throw ,string)))
 
 (define-builtin functionp (x)
-  (js!bool `(code "(typeof " ,x " == 'function')")))
+  (js!bool `(=== (typeof ,x) "function")))
 
 (define-builtin %write-string (x)
-  `(code "lisp.write(" ,x ")"))
+  `(call (get |lisp| "write") ,x))
 
 (define-builtin /debug (x)
-  `(code "console.log(xstring(" ,x "))"))
+  `(call (get |console| "log") (call |xstring| ,x)))
 
 
 ;;; Storage vectors. They are used to implement arrays and (in the
 
 (define-builtin storage-vector-p (x)
   (js!bool
-   (js!selfcall
-     "var x = " x ";"
-     "return typeof x === 'object' && 'length' in x;")))
+   (js!selfcall*
+     `(var (x ,x))
+     `(return (and (=== (typeof x) "object") (in "length" x))))))
 
 (define-builtin make-storage-vector (n)
-  (js!selfcall
-    "var r = [];"
-    "r.length = " n ";"
-    "return r;" ))
+  (js!selfcall*
+    `(var (r #()))
+    `(= (get r "length") ,n)
+    `(return r)))
 
 (define-builtin storage-vector-size (x)
-  `(code ,x ".length"))
+  `(get ,x "length"))
 
 (define-builtin resize-storage-vector (vector new-size)
-  `(code "(" ,vector ".length = " ,new-size ")"))
+  `(= (get ,vector "length") ,new-size))
 
 (define-builtin storage-vector-ref (vector n)
-  (js!selfcall
-    "var x = " "(" vector ")[" n "];"
-    "if (x === undefined) throw 'Out of range';"
-    "return x;" ))
+  (js!selfcall*
+    `(var (x (property ,vector ,n)))
+    `(if (=== x undefined) (throw "Out of range."))
+    `(return x)))
 
 (define-builtin storage-vector-set (vector n value)
-  (js!selfcall
-    "var x = " vector ";"
-    "var i = " n ";"
-    "if (i < 0 || i >= x.length) throw 'Out of range';"
-    "return x[i] = " value ";" ))
+  (js!selfcall*
+    `(var (x ,vector))
+    `(var (i ,n))
+    `(if (or (< i 0) (>= i (get x "length")))
+         (throw "Out of range."))
+    `(return (= (property x i) ,value))))
 
 (define-builtin concatenate-storage-vector (sv1 sv2)
-  (js!selfcall
-    "var sv1 = " sv1 ";"
-    "var r = sv1.concat(" sv2 ");"
-    "r.type = sv1.type;"
-    "r.stringp = sv1.stringp;"
-    "return r;" ))
+  (js!selfcall*
+    `(var (sv1 ,sv1))
+    `(var (r (call (get sv1 "concat") ,sv2)))
+    `(= (get r "type") (get sv1 "type"))
+    `(= (get r "stringp") (get sv1 "stringp"))
+    `(return r)))
 
 (define-builtin get-internal-real-time ()
-  "(new Date()).getTime()")
+  `(call (get (new (call |Date|)) "getTime")))
 
 (define-builtin values-array (array)
   (if *multiple-value-p*
-      `(code "values.apply(this, " ,array ")")
-      `(code "pv.apply(this, " ,array ")")))
+      `(call (get |values| "apply") this ,array)
+      `(call (get |pv| "apply") this ,array)))
 
 (define-raw-builtin values (&rest args)
   (if *multiple-value-p*
-      `(code "values(" ,@(interleave (mapcar #'ls-compile args) ",") ")")
-      `(code "pv(" ,@(interleave (mapcar #'ls-compile args) ", ") ")")))
-
+      `(call |values| ,@(mapcar #'ls-compile args))
+      `(call |pv| ,@(mapcar #'ls-compile args))))
 
 ;;; Javascript FFI
 
-(define-builtin new () "{}")
+(define-builtin new ()
+  '(object))
 
 (define-raw-builtin oget* (object key &rest keys)
-  (js!selfcall
-    "var tmp = (" (ls-compile object) ")[xstring(" (ls-compile key) ")];"
-    `(code
-      ,@(mapcar (lambda (key)
-                  `(code "if (tmp === undefined) return " ,(ls-compile nil) ";"
-                         "tmp = tmp[xstring(" ,(ls-compile key) ")];" ))
-                keys))
-    "return tmp === undefined? " (ls-compile nil) " : tmp;" ))
+  (js!selfcall*
+    `(progn
+       (var (tmp (property ,(ls-compile object) (call |xstring| ,(ls-compile key)))))
+       ,@(mapcar (lambda (key)
+                   `(progn
+                      (if (=== tmp undefined) (return ,(ls-compile nil)))
+                      (= tmp (property tmp (call |xstring| ,(ls-compile key))))))
+                 keys))
+    `(return (if (=== tmp undefined) ,(ls-compile nil) tmp))))
 
 (define-raw-builtin oset* (value object key &rest keys)
   (let ((keys (cons key keys)))
-    (js!selfcall
-      "var obj = " (ls-compile object) ";"
-      `(code ,@(mapcar (lambda (key)
-                         `(code "obj = obj[xstring(" ,(ls-compile key) ")];"
-                                "if (obj === undefined) throw 'Impossible to set Javascript property.';" ))
-                       (butlast keys)))
-      "var tmp = obj[xstring(" (ls-compile (car (last keys))) ")] = " (ls-compile value) ";"
-      "return tmp === undefined? " (ls-compile nil) " : tmp;" )))
+    (js!selfcall*
+      `(progn
+         (var (obj ,(ls-compile object)))
+         ,@(mapcar (lambda (key)
+                     `(progn
+                        (= obj (property obj (call |xstring| ,(ls-compile key))))
+                        (if (=== object undefined)
+                            (throw "Impossible to set object property."))))
+                   (butlast keys))
+         (var (tmp
+               (= (property obj (call |xstring| ,(ls-compile (car (last keys)))))
+                  ,(ls-compile value))))
+         (return (if (=== tmp undefined)
+                     ,(ls-compile nil)
+                     tmp))))))
 
 (define-raw-builtin oget (object key &rest keys)
   `(call |js_to_lisp| ,(ls-compile `(oget* ,object ,key ,@keys))))
   (js!bool `(in (call |xstring| ,key) ,object)))
 
 (define-builtin map-for-in (function object)
-  (js!selfcall
-   "var f = " function ";"
-   "var g = (typeof f === 'function' ? f : f.fvalue);"
-   "var o = " object ";"
-   "for (var key in o){"
-   `(code "g(" ,(if *multiple-value-p* "values" "pv") ", 1, o[key]);" )
-   "}"
-   " return " (ls-compile nil) ";" ))
+  (js!selfcall*
+    `(var (f ,function)
+          (g (if (=== (typeof f) "function") f (get f "fvalue")))
+          (o ,object))
+    `(for-in (key o)
+       (call g ,(if *multiple-value-p* '|values| '|pv|) 1 (get o "key")))
+    `(return ,(ls-compile nil))))
 
 (define-compilation %js-vref (var)
-  `(code "js_to_lisp(" ,var ")"))
+  `(call |js_to_lisp| ,(make-symbol var)))
 
 (define-compilation %js-vset (var val)
-  `(code "(" ,var " = lisp_to_js(" ,(ls-compile val) "))"))
+  `(= ,(make-symbol var) (call |lisp_to_js| ,(ls-compile val))))
 
 (define-setf-expander %js-vref (var)
   (let ((new-value (gensym)))