Console
[jscl.git] / lispstrack.lisp
index f3f01df..3b76ca4 100644 (file)
@@ -1,57 +1,7 @@
-#+lispstrack
-(progn
-  (eval-when-compile
-    (%compile-defmacro 'defmacro
-                       (lambda (name args &rest body)
-                         `(eval-when-compile
-                            (%compile-defmacro ',name (lambda ,args ,@body))))))
-
-  (defmacro defvar (name value)
-    `(progn
-       (eval-when-compile
-         (%compile-defvar ',name))
-       (setq ,name ,value)))
-
-  (defmacro defun (name args &rest body)
-    `(progn
-       (eval-when-compile
-         (%compile-defun ',name))
-       (fsetq ,name (lambda ,args ,@body))))
-
-  (defun = (x y) (= x y))
-  (defun + (x y) (+ x y))
-  (defun - (x y) (- x y))
-  (defun * (x y) (* x y))
-  (defun / (x y) (/ x y))
-  (defun 1+ (x) (+ x 1))
-  (defun 1- (x) (- x 1))
-  (defun cons (x y) (cons x y))
-  (defun car (x) (car x))
-  (defun cdr (x) (cdr x))
-
-  (defun append (list1 list2)
-    (if (null list1)
-        list2
-        (cons (car list1)
-              (append (cdr list1) list2))))
-
-  (defun reverse-aux (list acc)
-    (if (null list)
-        acc
-        (reverse-aux (cdr list) (cons (car list) acc))))
-
-  (defun reverse (list)
-    (reverse-aux list '()))
-
-  (defun mapcar (func list)
-    (if (null list)
-        '()
-        (cons (funcall func (car list))
-              (mapcar func (cdr list)))))
-
-  (defmacro push (x place)
-    `(setq ,place (cons ,x ,place))))
-
+(defun ensure-list (x)
+  (if (listp x)
+      x
+      (list x)))
 
 (defun !reduce (func list initial)
   (if (null list)
          ((not ,condition))
        ,@body))
 
-  #+common-lisp
   (defun concat-two (s1 s2)
-    (concatenate 'string s1 s2)))
+    (concatenate 'string s1 s2))
 
-(defvar *newline* "
-")
+  (defun setcar (cons new)
+    (setf (car cons) new))
+  (defun setcdr (cons new)
+    (setf (cdr cons) new)))
+
+(defvar *newline* (string (code-char 10)))
 
 (defun concat (&rest strs)
   (!reduce (lambda (s1 s2) (concat-two s1 s2))
              (join (cdr list) separator)))))
 
 (defun join-trailing (list separator)
-  (if (null list)
-      ""
-      (concat (car list) separator (join-trailing (cdr list) separator))))
+  (cond
+    ((null list)
+     "")
+    ((null (car list))
+     (join-trailing (cdr list) separator))
+    (t
+     (concat (car list) separator (join-trailing (cdr list) separator)))))
 
 (defun integer-to-string (x)
   (if (zerop x)
   (cons string 0))
 
 (defun %peek-char (stream)
-  (if (streamp stream)
-      (peek-char nil stream nil)
-      (and (< (cdr stream) (length (car stream)))
-           (char (car stream) (cdr stream)))))
+  (and (< (cdr stream) (length (car stream)))
+       (char (car stream) (cdr stream))))
 
 (defun %read-char (stream)
-  (if (streamp stream)
-      (read-char stream nil)
-      (and (< (cdr stream) (length (car stream)))
-           (prog1 (char (car stream) (cdr stream))
-             (incf (cdr stream))))))
+  (and (< (cdr stream) (length (car stream)))
+       (prog1 (char (car stream) (cdr stream))
+         (setcdr stream (1+ (cdr stream))))))
 
 (defun whitespacep (ch)
   (or (char= ch #\space) (char= ch #\newline) (char= ch #\tab)))
   (let (ch)
     (skip-whitespaces stream)
     (setq ch (%peek-char stream))
-    (while (and ch (eql ch #\;))
-      (read-until stream (lambda (x) (eql x #\newline)))
+    (while (and ch (char= ch #\;))
+      (read-until stream (lambda (x) (char= x #\newline)))
       (skip-whitespaces stream)
       (setq ch (%peek-char stream)))))
 
       (t
        (cons (ls-read stream) (%read-list stream))))))
 
+(defun read-string (stream)
+  (let ((string "")
+        (ch nil))
+    (setq ch (%read-char stream))
+    (while (not (char= ch #\"))
+      (when (char= ch #\\)
+        (setq ch (%read-char stream)))
+      (setq string (concat string (string ch)))
+      (setq ch (%read-char stream)))
+    string))
+
 (defvar *eof* (make-symbol "EOF"))
 (defun ls-read (stream)
   (skip-whitespaces-and-comments stream)
        (list 'backquote (ls-read stream)))
       ((char= ch #\")
        (%read-char stream)
-       (prog1 (read-until stream (lambda (ch) (char= ch #\")))
-         (%read-char stream)))
+       (read-string stream))
       ((char= ch #\,)
        (%read-char stream)
        (if (eql (%peek-char stream) #\@)
        (ecase (%read-char stream)
          (#\'
           (list 'function (ls-read stream)))
+         (#\\
+          (let ((cname
+                (concat (string (%read-char stream))
+                        (read-until stream #'terminalp))))
+            (cond
+              ((string= cname "space") (char-code #\space))
+              ((string= cname "tab") (char-code #\tab))
+              ((string= cname "newline") (char-code #\newline))
+              (t (char-code (char cname 0))))))
          (#\+
           (let ((feature (read-until stream #'terminalp)))
             (cond
               ((string= feature "common-lisp")
-               (ls-read stream);ignore
+               (ls-read stream)         ;ignore
                (ls-read stream))
               ((string= feature "lispstrack")
                (ls-read stream))
 
 ;;;; Compiler
 
-(let ((counter 0))
-  (defun make-var-binding (symbol)
-    (cons symbol (concat "v" (integer-to-string (incf counter))))))
+(defvar *compilation-unit-checks* '())
 
-(let ((counter 0))
-  (defun make-func-binding (symbol)
-    (cons symbol (concat "f" (integer-to-string (incf counter))))))
+(defvar *env* '())
+(defvar *fenv* '())
 
-(defvar *compilations* nil)
+(defun make-binding (name type js declared)
+  (list name type js declared))
 
-(defun ls-compile-block (sexps env fenv)
-  (join-trailing (mapcar (lambda (x)
-                           (ls-compile x env fenv))
-                         sexps)
-                 ";
-"))
+(defun binding-name (b) (first b))
+(defun binding-type (b) (second b))
+(defun binding-translation (b) (third b))
+(defun binding-declared (b)
+  (and b (fourth b)))
+(defun mark-binding-as-declared (b)
+  (setcar (cdddr b) t))
 
-(defun extend-env (args env)
-  (append (mapcar #'make-var-binding args) env))
+(defvar *variable-counter* 0)
+(defun gvarname (symbol)
+  (concat "v" (integer-to-string (incf *variable-counter*))))
 
-(defparameter *env* '())
-(defparameter *fenv* '())
+(defun lookup-variable (symbol env)
+  (or (assoc symbol env)
+      (assoc symbol *env*)
+      (let ((name (symbol-name symbol))
+            (binding (make-binding symbol 'variable (gvarname symbol) nil)))
+        (push binding *env*)
+        (push (lambda ()
+                (unless (binding-declared (assoc symbol *env*))
+                  (error (concat "Undefined variable `" name "'"))))
+              *compilation-unit-checks*)
+        binding)))
+
+(defun lookup-variable-translation (symbol env)
+  (binding-translation (lookup-variable symbol env)))
+
+(defun extend-local-env (args env)
+  (append (mapcar (lambda (symbol)
+                    (make-binding symbol 'variable (gvarname symbol) t))
+                  args)
+          env))
+
+(defvar *function-counter* 0)
+(defun lookup-function (symbol env)
+  (or (assoc symbol env)
+      (assoc symbol *fenv*)
+      (let ((name (symbol-name symbol))
+            (binding
+             (make-binding symbol
+                           'function
+                           (concat "f" (integer-to-string (incf *function-counter*)))
+                           nil)))
+        (push binding *fenv*)
+        (push (lambda ()
+                (unless (binding-declared (assoc symbol *fenv*))
+                  (error (concat "Undefined function `" name "'"))))
+              *compilation-unit-checks*)
+        binding)))
+
+(defun lookup-function-translation (symbol env)
+  (binding-translation (lookup-function symbol env)))
+
+
+(defvar *toplevel-compilations* nil)
 
-(defun ls-lookup (symbol env)
-  (let ((binding (assoc symbol env)))
-    (and binding (cdr binding))))
+(defun %compile-defvar (name)
+  (let ((b (lookup-variable name *env*)))
+    (mark-binding-as-declared b)
+    (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
 
-(defun lookup-variable (symbol env)
-  (or (ls-lookup symbol env)
-      (ls-lookup symbol *env*)
-      (error "Undefined variable `~a'"  symbol)))
+(defun %compile-defun (name)
+  (let ((b (lookup-function name *env*)))
+    (mark-binding-as-declared b)
+    (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
 
-(defun lookup-function (symbol env)
-  (or (ls-lookup symbol env)
-      (ls-lookup symbol *fenv*)
-      (error "Undefined function `~a'"  symbol)))
+(defun %compile-defmacro (name lambda)
+  (push (make-binding name 'macro lambda t) *fenv*))
+
+
+(defvar *compilations* nil)
 
-(defmacro define-compilation (name args &body body)
+(defun ls-compile-block (sexps env fenv)
+  (join-trailing
+   (remove nil (mapcar (lambda (x)
+                         (ls-compile x env fenv))
+                       sexps))
+                 ";
+"))
+(defmacro define-compilation (name args &rest body)
   ;; Creates a new primitive `name' with parameters args and
   ;; @body. The body can access to the local environment through the
   ;; variable ENV.
   `(push (list ',name (lambda (env fenv ,@args) ,@body))
          *compilations*))
 
-(defvar *toplevel-compilations*)
-
 (define-compilation if (condition true false)
   (concat "("
-          (ls-compile condition env fenv)
+          (ls-compile condition env fenv) " !== " (ls-compile nil nil nil)
           " ? "
           (ls-compile true env fenv)
           " : "
 (define-compilation lambda (lambda-list &rest body)
   (let ((required-arguments (lambda-list-required-argument lambda-list))
         (rest-argument (lambda-list-rest-argument lambda-list)))
-    (let ((new-env (extend-env (cons rest-argument required-arguments) env)))
+    (let ((new-env (extend-local-env
+                    (append (and rest-argument (list rest-argument))
+                            required-arguments)
+                    env)))
       (concat "(function ("
-              (join (mapcar (lambda (x) (lookup-variable x new-env))
+              (join (mapcar (lambda (x)
+                              (lookup-variable-translation x new-env))
                             required-arguments)
                     ",")
               "){"
               *newline*
               (if rest-argument
-                  (concat "var " (lookup-variable rest-argument new-env) ";" *newline*
-                          "for (var i = arguments.length-1; i>="
-                          (integer-to-string (length required-arguments))
-                          "; i--)" *newline*
-                          (lookup-variable rest-argument new-env) " = "
-                          "{car: arguments[i], cdr: " (lookup-variable rest-argument new-env) "};"
-                          *newline*)
+                  (let ((js!rest (lookup-variable-translation rest-argument new-env)))
+                    (concat "var " js!rest "= " (ls-compile nil env fenv) ";" *newline*
+                            "for (var i = arguments.length-1; i>="
+                            (integer-to-string (length required-arguments))
+                            "; i--)" *newline*
+                            js!rest " = "
+                            "{car: arguments[i], cdr: " js!rest "};"
+                            *newline*))
                   "")
               (concat (ls-compile-block (butlast body) new-env fenv)
                       "return " (ls-compile (car (last body)) new-env fenv) ";")
               "})"))))
 
 (define-compilation fsetq (var val)
-  (concat (lookup-function var fenv)
+  (concat (lookup-function-translation var fenv)
           " = "
           (ls-compile val env fenv)))
 
 (define-compilation setq (var val)
-  (concat (lookup-variable var env)
+  (concat (lookup-variable-translation var env)
           " = "
            (ls-compile val env fenv)))
 
-
 ;;; Literals
 
+(defun escape-string (string)
+  (let ((output "")
+        (index 0)
+        (size (length string)))
+    (while (< index size)
+      (let ((ch (char string index)))
+        (when (or (char= ch #\") (char= ch #\\))
+          (setq output (concat output "\\")))
+        (when (or (char= ch #\newline))
+          (setq output (concat output "\\"))
+          (setq ch #\n))
+        (setq output (concat output (string ch))))
+      (incf index))
+    output))
+
 (defun literal->js (sexp)
   (cond
-    ((null sexp) "undefined")
     ((integerp sexp) (integer-to-string sexp))
-    ((stringp sexp) (concat "\"" sexp "\""))
-    ((symbolp sexp) (concat "{name: \"" (symbol-name sexp) "\"}"))
+    ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
+    ((symbolp sexp) (ls-compile `(intern ,(escape-string (symbol-name sexp))) *env* *fenv*))
     ((consp sexp) (concat "{car: "
                           (literal->js (car sexp))
                           ", cdr: "
                          (literal->js (cdr sexp)) "}"))))
 
-(let ((counter 0))
-  (defun literal (form)
-    (let ((var (concat "l" (integer-to-string (incf counter)))))
-      (push (concat "var " var " = " (literal->js form)) *toplevel-compilations*)
-      var)))
+(defvar *literal-counter* 0)
+(defun literal (form)
+  (let ((var (concat "l" (integer-to-string (incf *literal-counter*)))))
+    (push (concat "var " var " = " (literal->js form)) *toplevel-compilations*)
+    var))
 
 (define-compilation quote (sexp)
   (literal sexp))
 
 (define-compilation while (pred &rest body)
   (concat "(function(){ while("
-          (ls-compile pred env fenv)
+          (ls-compile pred env fenv) " !== " (ls-compile nil nil nil)
           "){"
           (ls-compile-block body env fenv)
           "}})()"))
     ((and (listp x) (eq (car x) 'lambda))
      (ls-compile x env fenv))
     ((symbolp x)
-     (lookup-function x fenv))))
+     (lookup-function-translation x fenv))))
 
 #+common-lisp
 (defmacro eval-when-compile (&body body)
-  `(eval-when (:compile-toplevel :execute)
+  `(eval-when (:compile-toplevel :load-toplevel :execute)
      ,@body))
 
-(defvar *eval-when-compilations*)
 (define-compilation eval-when-compile (&rest body)
   (eval (cons 'progn body))
   nil)
   `((lambda () ,@body)))
 
 (define-transformation let (bindings &rest body)
-  `((lambda ,(mapcar 'car bindings) ,@body)
-    ,@(mapcar 'cadr bindings)))
+  (let ((bindings (mapcar #'ensure-list bindings)))
+    `((lambda ,(mapcar 'car bindings) ,@body)
+      ,@(mapcar 'cadr bindings))))
 
 ;;; A little backquote implementation without optimizations of any
 ;;; kind for lispstrack.
 
 ;;; Primitives
 
+(defun compile-bool (x)
+  (concat "(" x "?" (ls-compile t nil nil) ": " (ls-compile nil nil nil) ")"))
+
 (define-compilation + (x y)
   (concat "((" (ls-compile x env fenv) ") + (" (ls-compile y env fenv) "))"))
 
 (define-compilation / (x y)
   (concat "((" (ls-compile x env fenv) ") / (" (ls-compile y env fenv) "))"))
 
+(define-compilation < (x y)
+  (compile-bool (concat "((" (ls-compile x env fenv) ") < (" (ls-compile y env fenv) "))")))
+
 (define-compilation = (x y)
-  (concat "((" (ls-compile x env fenv) ") == (" (ls-compile y env fenv) "))"))
+  (compile-bool (concat "((" (ls-compile x env fenv) ") == (" (ls-compile y env fenv) "))")))
+
+(define-compilation numberp (x)
+  (compile-bool (concat "(typeof (" (ls-compile x env fenv) ") == \"number\")")))
+
+
+(define-compilation mod (x y)
+  (concat "((" (ls-compile x env fenv) ") % (" (ls-compile y env fenv) "))"))
+
+(define-compilation floor (x)
+  (concat "(Math.floor(" (ls-compile x env fenv) "))"))
 
 (define-compilation null (x)
-  (concat "(" (ls-compile x env fenv) "== undefined)"))
+  (compile-bool (concat "(" (ls-compile x env fenv) "===" (ls-compile nil env fenv) ")")))
 
 (define-compilation cons (x y)
   (concat "{car: " (ls-compile x env fenv) ", cdr: " (ls-compile y env fenv) "}"))
 
+(define-compilation consp (x)
+  (compile-bool
+   (concat "(function(){ var tmp = "
+           (ls-compile x env fenv)
+           "; return (typeof tmp == 'object' && 'car' in tmp);})()")))
+
 (define-compilation car (x)
-  (concat "(" (ls-compile x env fenv) ").car"))
+  (concat "(function () { var tmp = " (ls-compile x env fenv)
+          "; return tmp === " (ls-compile nil nil nil) "? "
+          (ls-compile nil nil nil)
+          ": tmp.car; })()"))
 
 (define-compilation cdr (x)
-  (concat "(" (ls-compile x env fenv) ").cdr"))
+  (concat "(function () { var tmp = " (ls-compile x env fenv)
+          "; return tmp === " (ls-compile nil nil nil) "? "
+          (ls-compile nil nil nil)
+          ": tmp.cdr; })()"))
+
+(define-compilation setcar (x new)
+  (concat "((" (ls-compile x env fenv) ").car = " (ls-compile new env fenv) ")"))
+
+(define-compilation setcdr (x new)
+  (concat "((" (ls-compile x env fenv) ").cdr = " (ls-compile new env fenv) ")"))
+
+(define-compilation symbolp (x)
+  (compile-bool
+   (concat "(function(){ var tmp = "
+           (ls-compile x env fenv)
+           "; return (typeof tmp == 'object' && 'name' in tmp); })()")))
+
+(define-compilation make-symbol (name)
+  (concat "{name: " (ls-compile name env fenv) "}"))
 
 (define-compilation symbol-name (x)
   (concat "(" (ls-compile x env fenv) ").name"))
 
 (define-compilation eq (x y)
-  (concat "(" (ls-compile x env fenv) " === " (ls-compile y env fenv) ")"))
+  (compile-bool
+   (concat "(" (ls-compile x env fenv) " === " (ls-compile y env fenv) ")")))
 
-(define-compilation eql (x y)
-  (concat "(" (ls-compile x env fenv) " == " (ls-compile y env fenv) ")"))
+(define-compilation equal (x y)
+  (compile-bool
+   (concat "(" (ls-compile x env fenv) " == " (ls-compile y env fenv) ")")))
 
-(define-compilation code-char (x)
-  (concat "String.fromCharCode( " (ls-compile x env fenv) ")"))
+(define-compilation string (x)
+  (concat "String.fromCharCode(" (ls-compile x env fenv) ")"))
+
+(define-compilation stringp (x)
+  (compile-bool
+   (concat "(typeof(" (ls-compile x env fenv) ") == \"string\")")))
+
+(define-compilation string-upcase (x)
+  (concat "(" (ls-compile x env fenv) ").toUpperCase()"))
+
+(define-compilation string-length (x)
+  (concat "(" (ls-compile x env fenv) ").length"))
 
 (define-compilation char (string index)
   (concat "("
                 ", ")
           ")"))
 
-(defun %compile-defvar (name)
-  (push (make-var-binding name) *env*)
-  (push (concat "var " (lookup-variable name *env*)) *toplevel-compilations*))
-
-(defun %compile-defun (name)
-  (push (make-func-binding name) *fenv*)
-  (push (concat "var " (lookup-variable name *fenv*)) *toplevel-compilations*))
-
-(defun %compile-defmacro (name lambda)
-  (push (cons name (cons 'macro lambda)) *fenv*))
-
-(defun ls-macroexpand-1 (form &optional env fenv)
-  (let ((function (cdr (assoc (car form) *fenv*))))
-    (if (and (listp function) (eq (car function) 'macro))
-        (apply (eval (cdr function)) (cdr form))
-        form)))
+(define-compilation apply (func &rest args)
+  (if (null args)
+      (concat "(" (ls-compile func env fenv) ")()")
+      (let ((args (butlast args))
+            (last (car (last args))))
+        (concat "(function(){" *newline*
+                "var f = " (ls-compile func env fenv) ";" *newline*
+                "var args = [" (join (mapcar (lambda (x)
+                                               (ls-compile x env fenv))
+                                             args)
+                                     ", ")
+                "];" *newline*
+                "var tail = (" (ls-compile last env fenv) ");" *newline*
+                "while (tail != " (ls-compile nil env fenv) "){" *newline*
+                "    args.push(tail.car);" *newline*
+                "    tail = tail.cdr;" *newline*
+                "}" *newline*
+                "return f.apply(this, args);" *newline*
+                "})()" *newline*))))
+
+(define-compilation js-eval (string)
+  (concat "eval(" (ls-compile string env fenv)  ")"))
+
+
+(define-compilation error (string)
+  (concat "(function (){ throw " (ls-compile string env fenv) ";" "return 0;})()"))
+
+(define-compilation new ()
+  "{}")
+
+(define-compilation get (object key)
+  (concat "(function(){ var tmp = "
+          "(" (ls-compile object env fenv) ")[" (ls-compile key env fenv) "]"
+          ";"
+          "return tmp == undefined? " (ls-compile nil nil nil) ": tmp ;"
+          "})()"))
+
+(define-compilation set (object key value)
+  (concat "(("
+          (ls-compile object env fenv)
+          ")["
+          (ls-compile key env fenv) "]"
+          " = " (ls-compile value env fenv) ")"))
+
+(define-compilation in (key object)
+  (compile-bool
+   (concat "(" (ls-compile key env fenv) " in " (ls-compile object env fenv) ")")))
+
+
+(defun macrop (x)
+  (and (symbolp x) (eq (binding-type (lookup-function x *fenv*)) 'macro)))
+
+(defun ls-macroexpand-1 (form env fenv)
+  (if (macrop (car form))
+      (let ((binding (lookup-function (car form) *env*)))
+        (if (eq (binding-type binding) 'macro)
+            (apply (eval (binding-translation binding)) (cdr form))
+            form))
+      form))
 
 (defun compile-funcall (function args env fenv)
   (cond
     ((symbolp function)
-     (concat (lookup-function function fenv)
+     (concat (lookup-function-translation function fenv)
              "("
              (join (mapcar (lambda (x) (ls-compile x env fenv)) args)
                    ", ")
                    ", ")
              ")"))
     (t
-     (error "Invalid function designator ~a." function))))
+     (error (concat "Invalid function designator " (symbol-name function))))))
 
-(defun ls-compile (sexp &optional env fenv)
+(defun ls-compile (sexp env fenv)
   (cond
-    ((symbolp sexp) (lookup-variable sexp env))
+    ((symbolp sexp) (lookup-variable-translation sexp env))
     ((integerp sexp) (integer-to-string sexp))
-    ((stringp sexp) (concat "\"" sexp "\""))
+    ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
     ((listp sexp)
-     (let ((sexp (ls-macroexpand-1 sexp env fenv)))
-       (let ((compiler-func (second (assoc (car sexp) *compilations*))))
-         (if compiler-func
-             (apply compiler-func env fenv (cdr sexp))
-             (compile-funcall (car sexp) (cdr sexp) env fenv)))))))
+     (if (assoc (car sexp) *compilations*)
+         (let ((comp (second (assoc (car sexp) *compilations*))))
+           (apply comp env fenv (cdr sexp)))
+         (if (macrop (car sexp))
+             (ls-compile (ls-macroexpand-1 sexp env fenv) env fenv)
+             (compile-funcall (car sexp) (cdr sexp) env fenv))))))
 
 (defun ls-compile-toplevel (sexp)
   (setq *toplevel-compilations* nil)
-  (let ((code (ls-compile sexp)))
+  (let ((code (ls-compile sexp nil nil)))
     (prog1
-        (concat (join (mapcar (lambda (x) (concat x ";" *newline*))
+        (concat #+common-lisp (concat "/* " (princ-to-string sexp) " */")
+                (join (mapcar (lambda (x) (concat x ";" *newline*))
                               *toplevel-compilations*)
-                      "")
+               "")
                 code)
       (setq *toplevel-compilations* nil))))
 
 #+common-lisp
 (progn
-  (defun ls-compile-file (filename output)
+  (defun read-whole-file (filename)
     (with-open-file (in filename)
-      (with-open-file (out output :direction :output :if-exists :supersede)
+      (let ((seq (make-array (file-length in) :element-type 'character)))
+        (read-sequence seq in)
+        seq)))
+
+  (defun ls-compile-file (filename output)
+    (setq *env* nil *fenv* nil)
+    (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 compilation do (write-line (concat compilation "; ") out)))))
+           when (plusp (length compilation))
+           do (write-line (concat compilation "; ") out))
+        (dolist (check *compilation-unit-checks*)
+          (funcall check))
+        (setq *compilation-unit-checks* nil))))
+
   (defun bootstrap ()
     (ls-compile-file "lispstrack.lisp" "lispstrack.js")))