ls-compile-toplevel emits a semicolon after the compiled toplevel instructions
[jscl.git] / ecmalisp.lisp
1 ;;; ecmalisp.lisp ---
2
3 ;; Copyright (C) 2012, 2013 David Vazquez
4 ;; Copyright (C) 2012 Raimon Grau
5
6 ;; This program is free software: you can redistribute it and/or
7 ;; modify it under the terms of the GNU General Public License as
8 ;; published by the Free Software Foundation, either version 3 of the
9 ;; License, or (at your option) any later version.
10 ;;
11 ;; This program is distributed in the hope that it will be useful, but
12 ;; WITHOUT ANY WARRANTY; without even the implied warranty of
13 ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
14 ;; General Public License for more details.
15 ;;
16 ;; You should have received a copy of the GNU General Public License
17 ;; along with this program.  If not, see <http://www.gnu.org/licenses/>.
18
19 ;;; This code is executed when ecmalisp compiles this file
20 ;;; itself. The compiler provides compilation of some special forms,
21 ;;; as well as funcalls and macroexpansion, but no functions. So, we
22 ;;; define the Lisp world from scratch. This code has to define enough
23 ;;; language to the compiler to be able to run.
24
25 #+ecmalisp
26 (progn
27   (eval-when-compile
28     (%compile-defmacro 'defmacro
29                        '(lambda (name args &rest body)
30                          `(eval-when-compile
31                             (%compile-defmacro ',name
32                                                '(lambda ,(mapcar (lambda (x)
33                                                                    (if (eq x '&body)
34                                                                        '&rest
35                                                                        x))
36                                                                  args)
37                                                  ,@body))))))
38
39   (defmacro %defvar (name value)
40     `(progn
41        (eval-when-compile
42          (%compile-defvar ',name))
43        (setq ,name ,value)))
44
45   (defmacro defvar (name &optional value)
46     `(%defvar ,name ,value))
47
48   (defmacro named-lambda (name args &rest body)
49     (let ((x (gensym "FN")))
50       `(let ((,x (lambda ,args ,@body)))
51          (oset ,x "fname" ,name)
52          ,x)))
53
54   (defmacro %defun (name args &rest body)
55     `(progn
56        (eval-when-compile
57          (%compile-defun ',name))
58        (fsetq ,name (named-lambda ,(symbol-name name) ,args
59                       (block ,name ,@body)))))
60
61   (defmacro defun (name args &rest body)
62     `(%defun ,name ,args ,@body))
63
64   (defvar *package* (new))
65
66   (defvar nil 'nil)
67   (defvar t 't)
68
69   (defun null (x)
70     (eq x nil))
71
72   (defmacro return (&optional value)
73     `(return-from nil ,value))
74
75   (defmacro while (condition &body body)
76     `(block nil (%while ,condition ,@body)))
77
78   (defun internp (name)
79     (in name *package*))
80
81   (defun intern (name)
82     (if (internp name)
83         (oget *package* name)
84         (oset *package* name (make-symbol name))))
85
86   (defun find-symbol (name)
87     (oget *package* name))
88
89   (defvar *gensym-counter* 0)
90   (defun gensym (&optional (prefix "G"))
91     (setq *gensym-counter* (+ *gensym-counter* 1))
92     (make-symbol (concat-two prefix (integer-to-string *gensym-counter*))))
93
94   ;; Basic functions
95   (defun = (x y) (= x y))
96   (defun + (x y) (+ x y))
97   (defun - (x y) (- x y))
98   (defun * (x y) (* x y))
99   (defun / (x y) (/ x y))
100   (defun 1+ (x) (+ x 1))
101   (defun 1- (x) (- x 1))
102   (defun zerop (x) (= x 0))
103   (defun truncate (x y) (floor (/ x y)))
104
105   (defun eql (x y) (eq x y))
106
107   (defun not (x) (if x nil t))
108
109   (defun cons (x y ) (cons x y))
110   (defun consp (x) (consp x))
111   (defun car (x) (car x))
112   (defun cdr (x) (cdr x))
113   (defun caar (x) (car (car x)))
114   (defun cadr (x) (car (cdr x)))
115   (defun cdar (x) (cdr (car x)))
116   (defun cddr (x) (cdr (cdr x)))
117   (defun caddr (x) (car (cdr (cdr x))))
118   (defun cdddr (x) (cdr (cdr (cdr x))))
119   (defun cadddr (x) (car (cdr (cdr (cdr x)))))
120   (defun first (x) (car x))
121   (defun second (x) (cadr x))
122   (defun third (x) (caddr x))
123   (defun fourth (x) (cadddr x))
124
125   (defun list (&rest args) args)
126   (defun atom (x)
127     (not (consp x)))
128
129   ;; Basic macros
130
131   (defmacro incf (x &optional (delta 1))
132     `(setq ,x (+ ,x ,delta)))
133
134   (defmacro decf (x &optional (delta 1))
135     `(setq ,x (- ,x ,delta)))
136
137   (defmacro push (x place)
138     `(setq ,place (cons ,x ,place)))
139
140   (defmacro when (condition &body body)
141     `(if ,condition (progn ,@body) nil))
142
143   (defmacro unless (condition &body body)
144     `(if ,condition nil (progn ,@body)))
145
146   (defmacro dolist (iter &body body)
147     (let ((var (first iter))
148           (g!list (gensym)))
149       `(block nil
150          (let ((,g!list ,(second iter))
151                (,var nil))
152            (%while ,g!list
153                    (setq ,var (car ,g!list))
154                    (tagbody ,@body)
155                    (setq ,g!list (cdr ,g!list)))
156            ,(third iter)))))
157
158   (defmacro dotimes (iter &body body)
159     (let ((g!to (gensym))
160           (var (first iter))
161           (to (second iter))
162           (result (third iter)))
163       `(block nil
164          (let ((,var 0)
165                (,g!to ,to))
166            (%while (< ,var ,g!to)
167                    (tagbody ,@body)
168                    (incf ,var))
169            ,result))))
170
171   (defmacro cond (&rest clausules)
172     (if (null clausules)
173         nil
174         (if (eq (caar clausules) t)
175             `(progn ,@(cdar clausules))
176             `(if ,(caar clausules)
177                  (progn ,@(cdar clausules))
178                  (cond ,@(cdr clausules))))))
179
180   (defmacro case (form &rest clausules)
181     (let ((!form (gensym)))
182       `(let ((,!form ,form))
183          (cond
184            ,@(mapcar (lambda (clausule)
185                        (if (eq (car clausule) t)
186                            clausule
187                            `((eql ,!form ',(car clausule))
188                              ,@(cdr clausule))))
189                      clausules)))))
190
191   (defmacro ecase (form &rest clausules)
192     `(case ,form
193        ,@(append
194           clausules
195           `((t
196              (error "ECASE expression failed."))))))
197
198   (defmacro and (&rest forms)
199     (cond
200       ((null forms)
201        t)
202       ((null (cdr forms))
203        (car forms))
204       (t
205        `(if ,(car forms)
206             (and ,@(cdr forms))
207             nil))))
208
209   (defmacro or (&rest forms)
210     (cond
211       ((null forms)
212        nil)
213       ((null (cdr forms))
214        (car forms))
215       (t
216        (let ((g (gensym)))
217          `(let ((,g ,(car forms)))
218             (if ,g ,g (or ,@(cdr forms))))))))
219
220   (defmacro prog1 (form &body body)
221     (let ((value (gensym)))
222       `(let ((,value ,form))
223          ,@body
224          ,value)))
225
226   (defmacro prog2 (form1 result &body body)
227     `(prog1 (progn ,form1 ,result) ,@body))
228
229
230
231 )
232
233 ;;; This couple of helper functions will be defined in both Common
234 ;;; Lisp and in Ecmalisp.
235 (defun ensure-list (x)
236   (if (listp x)
237       x
238       (list x)))
239
240 (defun !reduce (func list initial)
241   (if (null list)
242       initial
243       (!reduce func
244                (cdr list)
245                (funcall func initial (car list)))))
246
247 ;;; Go on growing the Lisp language in Ecmalisp, with more high
248 ;;; level utilities as well as correct versions of other
249 ;;; constructions.
250 #+ecmalisp
251 (progn
252   (defmacro defun (name args &body body)
253     `(progn
254        (%defun ,name ,args ,@body)
255        ',name))
256
257   (defmacro defvar (name &optional value)
258     `(progn
259        (%defvar ,name ,value)
260        ',name))
261
262   (defun append-two (list1 list2)
263     (if (null list1)
264         list2
265         (cons (car list1)
266               (append (cdr list1) list2))))
267
268   (defun append (&rest lists)
269     (!reduce #'append-two lists '()))
270
271   (defun revappend (list1 list2)
272     (while list1
273       (push (car list1) list2)
274       (setq list1 (cdr list1)))
275     list2)
276
277   (defun reverse (list)
278     (revappend list '()))
279
280   (defun list-length (list)
281     (let ((l 0))
282       (while (not (null list))
283         (incf l)
284         (setq list (cdr list)))
285       l))
286
287   (defun length (seq)
288     (if (stringp seq)
289         (string-length seq)
290         (list-length seq)))
291
292   (defun concat-two (s1 s2)
293     (concat-two s1 s2))
294
295   (defun mapcar (func list)
296     (if (null list)
297         '()
298         (cons (funcall func (car list))
299               (mapcar func (cdr list)))))
300
301   (defun identity (x) x)
302
303   (defun copy-list (x)
304     (mapcar #'identity x))
305
306   (defun code-char (x) x)
307   (defun char-code (x) x)
308   (defun char= (x y) (= x y))
309
310   (defun integerp (x)
311     (and (numberp x) (= (floor x) x)))
312
313   (defun plusp (x) (< 0 x))
314   (defun minusp (x) (< x 0))
315
316   (defun listp (x)
317     (or (consp x) (null x)))
318
319   (defun nthcdr (n list)
320     (while (and (plusp n) list)
321       (setq n (1- n))
322       (setq list (cdr list)))
323     list)
324
325   (defun nth (n list)
326     (car (nthcdr n list)))
327
328   (defun last (x)
329     (while (consp (cdr x))
330       (setq x (cdr x)))
331     x)
332
333   (defun butlast (x)
334     (and (consp (cdr x))
335          (cons (car x) (butlast (cdr x)))))
336
337   (defun member (x list)
338     (while list
339       (when (eql x (car list))
340         (return list))
341       (setq list (cdr list))))
342
343   (defun remove (x list)
344     (cond
345       ((null list)
346        nil)
347       ((eql x (car list))
348        (remove x (cdr list)))
349       (t
350        (cons (car list) (remove x (cdr list))))))
351
352   (defun remove-if (func list)
353     (cond
354       ((null list)
355        nil)
356       ((funcall func (car list))
357        (remove-if func (cdr list)))
358       (t
359        (cons (car list) (remove-if func (cdr list))))))
360
361   (defun remove-if-not (func list)
362     (cond
363       ((null list)
364        nil)
365       ((funcall func (car list))
366        (cons (car list) (remove-if-not func (cdr list))))
367       (t
368        (remove-if-not func (cdr list)))))
369
370   (defun digit-char-p (x)
371     (if (and (<= #\0 x) (<= x #\9))
372         (- x #\0)
373         nil))
374
375   (defun subseq (seq a &optional b)
376     (cond
377       ((stringp seq)
378        (if b
379            (slice seq a b)
380            (slice seq a)))
381       (t
382        (error "Unsupported argument."))))
383
384   (defun parse-integer (string)
385     (let ((value 0)
386           (index 0)
387           (size (length string)))
388       (while (< index size)
389         (setq value (+ (* value 10) (digit-char-p (char string index))))
390         (incf index))
391       value))
392
393   (defun some (function seq)
394     (cond
395       ((stringp seq)
396        (let ((index 0)
397              (size (length seq)))
398          (while (< index size)
399            (when (funcall function (char seq index))
400              (return-from some t))
401            (incf index))
402          nil))
403       ((listp seq)
404        (dolist (x seq nil)
405          (when (funcall function x)
406            (return t))))
407       (t
408        (error "Unknown sequence."))))
409
410   (defun every (function seq)
411     (cond
412       ((stringp seq)
413        (let ((index 0)
414              (size (length seq)))
415          (while (< index size)
416            (unless (funcall function (char seq index))
417              (return-from every nil))
418            (incf index))
419          t))
420       ((listp seq)
421        (dolist (x seq t)
422          (unless (funcall function x)
423            (return))))
424       (t
425        (error "Unknown sequence."))))
426
427   (defun assoc (x alist)
428     (while alist
429       (if (eql x (caar alist))
430           (return)
431           (setq alist (cdr alist))))
432     (car alist))
433
434   (defun string= (s1 s2)
435     (equal s1 s2)))
436
437
438 ;;; The compiler offers some primitives and special forms which are
439 ;;; not found in Common Lisp, for instance, while. So, we grow Common
440 ;;; Lisp a bit to it can execute the rest of the file.
441 #+common-lisp
442 (progn
443   (defmacro while (condition &body body)
444     `(do ()
445          ((not ,condition))
446        ,@body))
447
448   (defmacro eval-when-compile (&body body)
449     `(eval-when (:compile-toplevel :load-toplevel :execute)
450        ,@body))
451
452   (defun concat-two (s1 s2)
453     (concatenate 'string s1 s2))
454
455   (defun setcar (cons new)
456     (setf (car cons) new))
457   (defun setcdr (cons new)
458     (setf (cdr cons) new)))
459
460 ;;; At this point, no matter if Common Lisp or ecmalisp is compiling
461 ;;; from here, this code will compile on both. We define some helper
462 ;;; functions now for string manipulation and so on. They will be
463 ;;; useful in the compiler, mostly.
464
465 (defvar *newline* (string (code-char 10)))
466
467 (defun concat (&rest strs)
468   (!reduce #'concat-two strs ""))
469
470 (defmacro concatf (variable &body form)
471   `(setq ,variable (concat ,variable (progn ,@form))))
472
473 ;;; Concatenate a list of strings, with a separator
474 (defun join (list &optional (separator ""))
475   (cond
476     ((null list)
477      "")
478     ((null (cdr list))
479      (car list))
480     (t
481      (concat (car list)
482              separator
483              (join (cdr list) separator)))))
484
485 (defun join-trailing (list &optional (separator ""))
486   (if (null list)
487       ""
488       (concat (car list) separator (join-trailing (cdr list) separator))))
489
490 (defun mapconcat (func list)
491   (join (mapcar func list)))
492
493 ;;; Like CONCAT, but prefix each line with four spaces. Two versions
494 ;;; of this function are available, because the Ecmalisp version is
495 ;;; very slow and bootstraping was annoying.
496
497 #+ecmalisp
498 (defun indent (&rest string)
499   (let ((input (join string)))
500     (let ((output "")
501           (index 0)
502           (size (length input)))
503       (when (plusp (length input)) (concatf output "    "))
504       (while (< index size)
505         (let ((str
506                (if (and (char= (char input index) #\newline)
507                         (< index (1- size))
508                         (not (char= (char input (1+ index)) #\newline)))
509                    (concat (string #\newline) "    ")
510                    (string (char input index)))))
511           (concatf output str))
512         (incf index))
513       output)))
514
515 #+common-lisp
516 (defun indent (&rest string)
517   (with-output-to-string (*standard-output*)
518     (with-input-from-string (input (join string))
519       (loop
520          for line = (read-line input nil)
521          while line
522          do (write-string "    ")
523          do (write-line line)))))
524
525
526 (defun integer-to-string (x)
527   (cond
528     ((zerop x)
529      "0")
530     ((minusp x)
531      (concat "-" (integer-to-string (- 0 x))))
532     (t
533      (let ((digits nil))
534        (while (not (zerop x))
535          (push (mod x 10) digits)
536          (setq x (truncate x 10)))
537        (join (mapcar (lambda (d) (string (char "0123456789" d)))
538                      digits))))))
539
540
541 ;;; Wrap X with a Javascript code to convert the result from
542 ;;; Javascript generalized booleans to T or NIL.
543 (defun js!bool (x)
544   (concat "(" x "?" (ls-compile t) ": " (ls-compile nil) ")"))
545
546 ;;; Concatenate the arguments and wrap them with a self-calling
547 ;;; Javascript anonymous function. It is used to make some Javascript
548 ;;; statements valid expressions and provide a private scope as well.
549 ;;; It could be defined as function, but we could do some
550 ;;; preprocessing in the future.
551 (defmacro js!selfcall (&body body)
552   `(concat "(function(){" *newline* (indent ,@body) "})()"))
553
554
555 ;;; Printer
556
557 #+ecmalisp
558 (progn
559   (defun prin1-to-string (form)
560     (cond
561       ((symbolp form) (symbol-name form))
562       ((integerp form) (integer-to-string form))
563       ((stringp form) (concat "\"" (escape-string form) "\""))
564       ((functionp form)
565        (let ((name (oget form "fname")))
566          (if name
567              (concat "#<FUNCTION " name ">")
568              (concat "#<FUNCTION>"))))
569       ((listp form)
570        (concat "("
571                (join-trailing (mapcar #'prin1-to-string (butlast form)) " ")
572                (let ((last (last form)))
573                  (if (null (cdr last))
574                      (prin1-to-string (car last))
575                      (concat (prin1-to-string (car last)) " . " (prin1-to-string (cdr last)))))
576                ")"))))
577
578   (defun write-line (x)
579     (write-string x)
580     (write-string *newline*)
581     x)
582
583   (defun print (x)
584     (write-line (prin1-to-string x))
585     x))
586
587
588 ;;;; Reader
589
590 ;;; The Lisp reader, parse strings and return Lisp objects. The main
591 ;;; entry points are `ls-read' and `ls-read-from-string'.
592
593 (defun make-string-stream (string)
594   (cons string 0))
595
596 (defun %peek-char (stream)
597   (and (< (cdr stream) (length (car stream)))
598        (char (car stream) (cdr stream))))
599
600 (defun %read-char (stream)
601   (and (< (cdr stream) (length (car stream)))
602        (prog1 (char (car stream) (cdr stream))
603          (setcdr stream (1+ (cdr stream))))))
604
605 (defun whitespacep (ch)
606   (or (char= ch #\space) (char= ch #\newline) (char= ch #\tab)))
607
608 (defun skip-whitespaces (stream)
609   (let (ch)
610     (setq ch (%peek-char stream))
611     (while (and ch (whitespacep ch))
612       (%read-char stream)
613       (setq ch (%peek-char stream)))))
614
615 (defun terminalp (ch)
616   (or (null ch) (whitespacep ch) (char= #\) ch) (char= #\( ch)))
617
618 (defun read-until (stream func)
619   (let ((string "")
620         (ch))
621     (setq ch (%peek-char stream))
622     (while (and ch (not (funcall func ch)))
623       (setq string (concat string (string ch)))
624       (%read-char stream)
625       (setq ch (%peek-char stream)))
626     string))
627
628 (defun skip-whitespaces-and-comments (stream)
629   (let (ch)
630     (skip-whitespaces stream)
631     (setq ch (%peek-char stream))
632     (while (and ch (char= ch #\;))
633       (read-until stream (lambda (x) (char= x #\newline)))
634       (skip-whitespaces stream)
635       (setq ch (%peek-char stream)))))
636
637 (defun %read-list (stream)
638   (skip-whitespaces-and-comments stream)
639   (let ((ch (%peek-char stream)))
640     (cond
641       ((null ch)
642        (error "Unspected EOF"))
643       ((char= ch #\))
644        (%read-char stream)
645        nil)
646       ((char= ch #\.)
647        (%read-char stream)
648        (prog1 (ls-read stream)
649          (skip-whitespaces-and-comments stream)
650          (unless (char= (%read-char stream) #\))
651            (error "')' was expected."))))
652       (t
653        (cons (ls-read stream) (%read-list stream))))))
654
655 (defun read-string (stream)
656   (let ((string "")
657         (ch nil))
658     (setq ch (%read-char stream))
659     (while (not (eql ch #\"))
660       (when (null ch)
661         (error "Unexpected EOF"))
662       (when (eql ch #\\)
663         (setq ch (%read-char stream)))
664       (setq string (concat string (string ch)))
665       (setq ch (%read-char stream)))
666     string))
667
668 (defun read-sharp (stream)
669   (%read-char stream)
670   (ecase (%read-char stream)
671     (#\'
672      (list 'function (ls-read stream)))
673     (#\\
674      (let ((cname
675             (concat (string (%read-char stream))
676                     (read-until stream #'terminalp))))
677        (cond
678          ((string= cname "space") (char-code #\space))
679          ((string= cname "tab") (char-code #\tab))
680          ((string= cname "newline") (char-code #\newline))
681          (t (char-code (char cname 0))))))
682     (#\+
683      (let ((feature (read-until stream #'terminalp)))
684        (cond
685          ((string= feature "common-lisp")
686           (ls-read stream)              ;ignore
687           (ls-read stream))
688          ((string= feature "ecmalisp")
689           (ls-read stream))
690          (t
691           (error "Unknown reader form.")))))))
692
693 (defvar *eof* (make-symbol "EOF"))
694 (defun ls-read (stream)
695   (skip-whitespaces-and-comments stream)
696   (let ((ch (%peek-char stream)))
697     (cond
698       ((null ch)
699        *eof*)
700       ((char= ch #\()
701        (%read-char stream)
702        (%read-list stream))
703       ((char= ch #\')
704        (%read-char stream)
705        (list 'quote (ls-read stream)))
706       ((char= ch #\`)
707        (%read-char stream)
708        (list 'backquote (ls-read stream)))
709       ((char= ch #\")
710        (%read-char stream)
711        (read-string stream))
712       ((char= ch #\,)
713        (%read-char stream)
714        (if (eql (%peek-char stream) #\@)
715            (progn (%read-char stream) (list 'unquote-splicing (ls-read stream)))
716            (list 'unquote (ls-read stream))))
717       ((char= ch #\#)
718        (read-sharp stream))
719       (t
720        (let ((string (read-until stream #'terminalp)))
721          (if (every #'digit-char-p string)
722              (parse-integer string)
723              (intern (string-upcase string))))))))
724
725 (defun ls-read-from-string (string)
726   (ls-read (make-string-stream string)))
727
728
729 ;;;; Compiler
730
731 ;;; Translate the Lisp code to Javascript. It will compile the special
732 ;;; forms. Some primitive functions are compiled as special forms
733 ;;; too. The respective real functions are defined in the target (see
734 ;;; the beginning of this file) as well as some primitive functions.
735
736 (defvar *compilation-unit-checks* '())
737
738 (defun make-binding (name type translation declared)
739   (list name type translation declared))
740
741 (defun binding-name (b) (first b))
742 (defun binding-type (b) (second b))
743 (defun binding-translation (b) (third b))
744 (defun binding-declared (b)
745   (and b (fourth b)))
746 (defun mark-binding-as-declared (b)
747   (setcar (cdddr b) t))
748
749 (defun make-lexenv ()
750   (list nil nil nil nil))
751
752 (defun copy-lexenv (lexenv)
753   (copy-list lexenv))
754
755 (defun push-to-lexenv (binding lexenv namespace)
756   (ecase namespace
757     (variable
758      (setcar lexenv (cons binding (car lexenv))))
759     (function
760      (setcar (cdr lexenv) (cons binding (cadr lexenv))))
761     (block
762      (setcar (cddr lexenv) (cons binding (caddr lexenv))))
763     (gotag
764      (setcar (cdddr lexenv) (cons binding (cadddr lexenv))))))
765
766 (defun extend-lexenv (bindings lexenv namespace)
767   (let ((env (copy-lexenv lexenv)))
768     (dolist (binding (reverse bindings) env)
769       (push-to-lexenv binding env namespace))))
770
771 (defun lookup-in-lexenv (name lexenv namespace)
772   (assoc name (ecase namespace
773                 (variable (first lexenv))
774                 (function (second lexenv))
775                 (block (third lexenv))
776                 (gotag (fourth lexenv)))))
777
778 (defvar *environment* (make-lexenv))
779
780 (defun clear-undeclared-global-bindings ()
781   (setq *environment*
782         (mapcar (lambda (namespace)
783                   (remove-if-not #'binding-declared namespace))
784                 *environment*)))
785
786
787 (defvar *variable-counter* 0)
788 (defun gvarname (symbol)
789   (concat "v" (integer-to-string (incf *variable-counter*))))
790
791 (defun lookup-variable (symbol env)
792   (or (lookup-in-lexenv symbol env 'variable)
793       (lookup-in-lexenv symbol *environment* 'variable)
794       (let ((name (symbol-name symbol))
795             (binding (make-binding symbol 'special-variable (gvarname symbol) nil)))
796         (push-to-lexenv binding *environment* 'variable)
797         (push (lambda ()
798                 (let ((b (lookup-in-lexenv symbol *environment* 'variable)))
799                   (unless (binding-declared b)
800                       (error (concat "Undefined variable `" name "'")))))
801               *compilation-unit-checks*)
802         binding)))
803
804 (defun lookup-variable-translation (symbol env)
805   (binding-translation (lookup-variable symbol env)))
806
807 (defun extend-local-env (args env)
808   (let ((new (copy-lexenv env)))
809     (dolist (symbol args new)
810       (let ((b (make-binding symbol 'lexical-variable (gvarname symbol) t)))
811         (push-to-lexenv b new 'variable)))))
812
813 (defvar *function-counter* 0)
814 (defun lookup-function (symbol env)
815   (or (lookup-in-lexenv symbol env 'function)
816       (lookup-in-lexenv symbol *environment* 'function)
817       (let ((name (symbol-name symbol))
818             (binding
819              (make-binding symbol
820                            'function
821                            (concat "f" (integer-to-string (incf *function-counter*)))
822                            nil)))
823         (push-to-lexenv binding *environment* 'function)
824         (push (lambda ()
825                 (let ((b (lookup-in-lexenv symbol *environment* 'function)))
826                   (unless (binding-declared b)
827                     (error (concat "Undefined function `" name "'")))))
828               *compilation-unit-checks*)
829         binding)))
830
831 (defun lookup-function-translation (symbol env)
832   (binding-translation (lookup-function symbol env)))
833
834 (defvar *toplevel-compilations* nil)
835
836 (defun %compile-defvar (name)
837   (let ((b (lookup-variable name *environment*)))
838     (mark-binding-as-declared b)
839     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
840
841 (defun %compile-defun (name)
842   (let ((b (lookup-function name *environment*)))
843     (mark-binding-as-declared b)
844     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
845
846 (defun %compile-defmacro (name lambda)
847   (push-to-lexenv (make-binding name 'macro lambda t) *environment* 'function))
848
849 (defvar *compilations* nil)
850
851 (defun ls-compile-block (sexps env)
852   (join-trailing
853    (remove-if #'null
854               (mapcar (lambda (x) (ls-compile x env))  sexps))
855    (concat ";" *newline*)))
856
857 (defmacro define-compilation (name args &body body)
858   ;; Creates a new primitive `name' with parameters args and
859   ;; @body. The body can access to the local environment through the
860   ;; variable ENV.
861   `(push (list ',name (lambda (env ,@args) (block ,name ,@body)))
862          *compilations*))
863
864 (define-compilation if (condition true false)
865   (concat "("
866           (ls-compile condition env) " !== " (ls-compile nil)
867           " ? "
868           (ls-compile true env)
869           " : "
870           (ls-compile false env)
871           ")"))
872
873
874 (defvar *lambda-list-keywords* '(&optional &rest))
875
876 (defun list-until-keyword (list)
877   (if (or (null list) (member (car list) *lambda-list-keywords*))
878       nil
879       (cons (car list) (list-until-keyword (cdr list)))))
880
881 (defun lambda-list-required-arguments (lambda-list)
882   (list-until-keyword lambda-list))
883
884 (defun lambda-list-optional-arguments-with-default (lambda-list)
885   (mapcar #'ensure-list (list-until-keyword (cdr (member '&optional lambda-list)))))
886
887 (defun lambda-list-optional-arguments (lambda-list)
888   (mapcar #'car (lambda-list-optional-arguments-with-default lambda-list)))
889
890 (defun lambda-list-rest-argument (lambda-list)
891   (let ((rest (list-until-keyword (cdr (member '&rest lambda-list)))))
892     (when (cdr rest)
893       (error "Bad lambda-list"))
894     (car rest)))
895
896 (define-compilation lambda (lambda-list &rest body)
897   (let ((required-arguments (lambda-list-required-arguments lambda-list))
898         (optional-arguments (lambda-list-optional-arguments lambda-list))
899         (rest-argument (lambda-list-rest-argument lambda-list)))
900     (let ((n-required-arguments (length required-arguments))
901           (n-optional-arguments (length optional-arguments))
902           (new-env (extend-local-env
903                     (append (ensure-list rest-argument)
904                             required-arguments
905                             optional-arguments)
906                     env)))
907       (concat "(function ("
908               (join (mapcar (lambda (x)
909                               (lookup-variable-translation x new-env))
910                             (append required-arguments optional-arguments))
911                     ",")
912               "){" *newline*
913               ;; Check number of arguments
914               (indent
915                (if required-arguments
916                    (concat "if (arguments.length < " (integer-to-string n-required-arguments)
917                            ") throw 'too few arguments';" *newline*)
918                    "")
919                (if (not rest-argument)
920                    (concat "if (arguments.length > "
921                            (integer-to-string (+ n-required-arguments n-optional-arguments))
922                            ") throw 'too many arguments';" *newline*)
923                    "")
924                ;; Optional arguments
925                (if optional-arguments
926                    (concat "switch(arguments.length){" *newline*
927                            (let ((optional-and-defaults
928                                   (lambda-list-optional-arguments-with-default lambda-list))
929                                  (cases nil)
930                                  (idx 0))
931                              (progn
932                                (while (< idx n-optional-arguments)
933                                  (let ((arg (nth idx optional-and-defaults)))
934                                    (push (concat "case "
935                                                  (integer-to-string (+ idx n-required-arguments)) ":" *newline*
936                                                  (lookup-variable-translation (car arg) new-env)
937                                                  "="
938                                                  (ls-compile (cadr arg) new-env)
939                                                  ";" *newline*)
940                                          cases)
941                                    (incf idx)))
942                                     (push (concat "default: break;" *newline*) cases)
943                                     (join (reverse cases))))
944                            "}" *newline*)
945                    "")
946                ;; &rest/&body argument
947                (if rest-argument
948                    (let ((js!rest (lookup-variable-translation rest-argument new-env)))
949                      (concat "var " js!rest "= " (ls-compile nil) ";" *newline*
950                              "for (var i = arguments.length-1; i>="
951                              (integer-to-string (+ n-required-arguments n-optional-arguments))
952                              "; i--)" *newline*
953                              (indent js!rest " = "
954                                      "{car: arguments[i], cdr: ") js!rest "};"
955                                      *newline*))
956                    "")
957                ;; Body
958                (concat (ls-compile-block (butlast body) new-env)
959                        "return " (ls-compile (car (last body)) new-env) ";")) *newline*
960               "})"))))
961
962 (define-compilation fsetq (var val)
963   (concat (lookup-function-translation var env)
964           " = "
965           (ls-compile val env)))
966
967 (define-compilation setq (var val)
968   (let ((b (lookup-variable var env)))
969     (ecase (binding-type b)
970       (lexical-variable (concat (binding-translation b) " = " (ls-compile val env)))
971       (special-variable (ls-compile `(set ',var ,val) env)))))
972
973 ;;; FFI Variable accessors
974 (define-compilation js-vref (var)
975   var)
976 (define-compilation js-vset (var val)
977   (concat "(" var " = " (ls-compile val env) ")"))
978
979
980 ;;; Literals
981 (defun escape-string (string)
982   (let ((output "")
983         (index 0)
984         (size (length string)))
985     (while (< index size)
986       (let ((ch (char string index)))
987         (when (or (char= ch #\") (char= ch #\\))
988           (setq output (concat output "\\")))
989         (when (or (char= ch #\newline))
990           (setq output (concat output "\\"))
991           (setq ch #\n))
992         (setq output (concat output (string ch))))
993       (incf index))
994     output))
995
996
997 (defvar *literal-symbols* nil)
998 (defvar *literal-counter* 0)
999
1000 (defun genlit ()
1001   (concat "l" (integer-to-string (incf *literal-counter*))))
1002
1003 (defun literal (sexp &optional recursive)
1004   (cond
1005     ((integerp sexp) (integer-to-string sexp))
1006     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
1007     ((symbolp sexp)
1008      #+common-lisp
1009      (or (cdr (assoc sexp *literal-symbols*))
1010          (let ((v (genlit))
1011                (s (concat "{name: \"" (escape-string (symbol-name sexp)) "\"}")))
1012            (push (cons sexp v) *literal-symbols*)
1013            (push (concat "var " v " = " s) *toplevel-compilations*)
1014            v))
1015      #+ecmalisp
1016      (let ((v (genlit)))
1017        (push (concat "var " v " = " (ls-compile `(intern ,(symbol-name sexp))))
1018              *toplevel-compilations*)
1019        v))
1020     ((consp sexp)
1021      (let ((c (concat "{car: " (literal (car sexp) t) ", "
1022                       "cdr: " (literal (cdr sexp) t) "}")))
1023        (if recursive
1024            c
1025            (let ((v (genlit)))
1026              (push (concat "var " v " = " c) *toplevel-compilations*)
1027              v))))))
1028
1029 (define-compilation quote (sexp)
1030   (literal sexp))
1031
1032
1033 (define-compilation %while (pred &rest body)
1034   (js!selfcall
1035     "while(" (ls-compile pred env) " !== " (ls-compile nil) "){" *newline*
1036     (indent (ls-compile-block body env))
1037     "}"
1038     "return " (ls-compile nil) ";" *newline*))
1039
1040 (define-compilation function (x)
1041   (cond
1042     ((and (listp x) (eq (car x) 'lambda))
1043      (ls-compile x env))
1044     ((symbolp x)
1045      (lookup-function-translation x env))))
1046
1047 (define-compilation eval-when-compile (&rest body)
1048   (eval (cons 'progn body))
1049   nil)
1050
1051 (defmacro define-transformation (name args form)
1052   `(define-compilation ,name ,args
1053      (ls-compile ,form env)))
1054
1055 (define-compilation progn (&rest body)
1056   (js!selfcall
1057     (ls-compile-block (butlast body) env)
1058     "return " (ls-compile (car (last body)) env) ";" *newline*))
1059
1060 (define-compilation let (bindings &rest body)
1061   (let ((bindings (mapcar #'ensure-list bindings)))
1062     (let ((variables (mapcar #'first bindings))
1063           (values    (mapcar #'second bindings)))
1064       (let ((new-env (extend-local-env variables env)))
1065         (concat "(function("
1066                 (join (mapcar (lambda (x)
1067                                 (lookup-variable-translation x new-env))
1068                               variables)
1069                       ",")
1070                 "){" *newline*
1071                 (indent (ls-compile-block (butlast body) new-env)
1072                         "return " (ls-compile (car (last body)) new-env)
1073                         ";" *newline*)
1074                 "})(" (join (mapcar (lambda (x) (ls-compile x env))
1075                                     values)
1076                             ",")
1077                 ")")))))
1078
1079
1080 (defvar *block-counter* 0)
1081
1082 (define-compilation block (name &rest body)
1083   (let ((tr (integer-to-string (incf *block-counter*))))
1084     (let ((b (make-binding name 'block tr t)))
1085       (js!selfcall
1086         "try {" *newline*
1087         (indent "return " (ls-compile `(progn ,@body)
1088                                       (extend-lexenv (list b) env 'block))
1089                 ";" *newline*)
1090         "}" *newline*
1091         "catch (cf){" *newline*
1092         "    if (cf.type == 'block' && cf.id == " tr ")" *newline*
1093         "        return cf.value;" *newline*
1094         "    else" *newline*
1095         "        throw cf;" *newline*
1096         "}" *newline*))))
1097
1098 (define-compilation return-from (name &optional value)
1099   (let ((b (lookup-in-lexenv name env 'block)))
1100     (if b
1101         (js!selfcall
1102           "throw ({"
1103           "type: 'block', "
1104           "id: " (binding-translation b) ", "
1105           "value: " (ls-compile value env) ", "
1106           "message: 'Return from unknown block " (symbol-name name) ".'"
1107           "})")
1108         (error (concat "Unknown block `" (symbol-name name) "'.")))))
1109
1110
1111 (define-compilation catch (id &rest body)
1112   (js!selfcall
1113     "var id = " (ls-compile id env) ";" *newline*
1114     "try {" *newline*
1115     (indent "return " (ls-compile `(progn ,@body))
1116             ";" *newline*)
1117     "}" *newline*
1118     "catch (cf){" *newline*
1119     "    if (cf.type == 'catch' && cf.id == id)" *newline*
1120     "        return cf.value;" *newline*
1121     "    else" *newline*
1122     "        throw cf;" *newline*
1123     "}" *newline*))
1124
1125 (define-compilation throw (id &optional value)
1126   (js!selfcall
1127     "throw ({"
1128     "type: 'catch', "
1129     "id: " (ls-compile id env) ", "
1130     "value: " (ls-compile value env) ", "
1131     "message: 'Throw uncatched.'"
1132     "})"))
1133
1134
1135 (defvar *tagbody-counter* 0)
1136 (defvar *go-tag-counter* 0)
1137
1138 (defun go-tag-p (x)
1139   (or (integerp x) (symbolp x)))
1140
1141 (defun declare-tagbody-tags (env tbidx body)
1142   (let ((bindings
1143          (mapcar (lambda (label)
1144                    (let ((tagidx (integer-to-string (incf *go-tag-counter*))))
1145                      (make-binding label 'gotag (list tbidx tagidx) t)))
1146                  (remove-if-not #'go-tag-p body))))
1147     (extend-lexenv bindings env 'gotag)))
1148
1149 (define-compilation tagbody (&rest body)
1150   ;; Ignore the tagbody if it does not contain any go-tag. We do this
1151   ;; because 1) it is easy and 2) many built-in forms expand to a
1152   ;; implicit tagbody, so we save some space.
1153   (unless (some #'go-tag-p body)
1154     (return-from tagbody (ls-compile `(progn ,@body nil) env)))
1155   ;; The translation assumes the first form in BODY is a label
1156   (unless (go-tag-p (car body))
1157     (push (gensym "START") body))
1158   ;; Tagbody compilation
1159   (let ((tbidx (integer-to-string *tagbody-counter*)))
1160     (let ((env (declare-tagbody-tags env tbidx body))
1161           initag)
1162       (let ((b (lookup-in-lexenv (first body) env 'gotag)))
1163         (setq initag (second (binding-translation b))))
1164       (js!selfcall
1165         "var tagbody_" tbidx " = " initag ";" *newline*
1166         "tbloop:" *newline*
1167         "while (true) {" *newline*
1168         (indent "try {" *newline*
1169                 (indent (let ((content ""))
1170                           (concat "switch(tagbody_" tbidx "){" *newline*
1171                                   "case " initag ":" *newline*
1172                                   (dolist (form (cdr body) content)
1173                                     (concatf content
1174                                       (if (not (go-tag-p form))
1175                                           (indent (ls-compile form env) ";" *newline*)
1176                                           (let ((b (lookup-in-lexenv form env 'gotag)))
1177                                             (concat "case " (second (binding-translation b)) ":" *newline*)))))
1178                                   "default:" *newline*
1179                                   "    break tbloop;" *newline*
1180                                   "}" *newline*)))
1181                 "}" *newline*
1182                 "catch (jump) {" *newline*
1183                 "    if (jump.type == 'tagbody' && jump.id == " tbidx ")" *newline*
1184                 "        tagbody_" tbidx " = jump.label;" *newline*
1185                 "    else" *newline*
1186                 "        throw(jump);" *newline*
1187                 "}" *newline*)
1188         "}" *newline*
1189         "return " (ls-compile nil) ";" *newline*))))
1190
1191 (define-compilation go (label)
1192   (let ((b (lookup-in-lexenv label env 'gotag))
1193         (n (cond
1194              ((symbolp label) (symbol-name label))
1195              ((integerp label) (integer-to-string label)))))
1196     (if b
1197         (js!selfcall
1198           "throw ({"
1199           "type: 'tagbody', "
1200           "id: " (first (binding-translation b)) ", "
1201           "label: " (second (binding-translation b)) ", "
1202           "message: 'Attempt to GO to non-existing tag " n "'"
1203           "})" *newline*)
1204         (error (concat "Unknown tag `" n "'.")))))
1205
1206
1207 (define-compilation unwind-protect (form &rest clean-up)
1208   (js!selfcall
1209     "var ret = " (ls-compile nil) ";" *newline*
1210     "try {" *newline*
1211     (indent "ret = " (ls-compile form env) ";" *newline*)
1212     "} finally {" *newline*
1213     (indent (ls-compile-block clean-up env))
1214     "}" *newline*
1215     "return ret;" *newline*))
1216
1217
1218 ;;; A little backquote implementation without optimizations of any
1219 ;;; kind for ecmalisp.
1220 (defun backquote-expand-1 (form)
1221   (cond
1222     ((symbolp form)
1223      (list 'quote form))
1224     ((atom form)
1225      form)
1226     ((eq (car form) 'unquote)
1227      (car form))
1228     ((eq (car form) 'backquote)
1229      (backquote-expand-1 (backquote-expand-1 (cadr form))))
1230     (t
1231      (cons 'append
1232            (mapcar (lambda (s)
1233                      (cond
1234                        ((and (listp s) (eq (car s) 'unquote))
1235                         (list 'list (cadr s)))
1236                        ((and (listp s) (eq (car s) 'unquote-splicing))
1237                         (cadr s))
1238                        (t
1239                         (list 'list (backquote-expand-1 s)))))
1240                    form)))))
1241
1242 (defun backquote-expand (form)
1243   (if (and (listp form) (eq (car form) 'backquote))
1244       (backquote-expand-1 (cadr form))
1245       form))
1246
1247 (defmacro backquote (form)
1248   (backquote-expand-1 form))
1249
1250 (define-transformation backquote (form)
1251   (backquote-expand-1 form))
1252
1253 ;;; Primitives
1254
1255 (defmacro define-builtin (name args &body body)
1256   `(define-compilation ,name ,args
1257      (let ,(mapcar (lambda (arg) `(,arg (ls-compile ,arg env))) args)
1258        ,@body)))
1259
1260 ;;; DECLS is a list of (JSVARNAME TYPE LISPFORM) declarations.
1261 (defmacro type-check (decls &body body)
1262   `(js!selfcall
1263      ,@(mapcar (lambda (decl)
1264                    `(concat "var " ,(first decl) " = " ,(third decl) ";" *newline*))
1265                  decls)
1266      ,@(mapcar (lambda (decl)
1267                  `(concat "if (typeof " ,(first decl) " != '" ,(second decl) "')" *newline*
1268                           (indent "throw 'The value ' + "
1269                                   ,(first decl)
1270                                   " + ' is not a type "
1271                                   ,(second decl)
1272                                   ".';"
1273                                   *newline*)))
1274                decls)
1275      (concat "return " (progn ,@body) ";" *newline*)))
1276
1277 (defun num-op-num (x op y)
1278   (type-check (("x" "number" x) ("y" "number" y))
1279     (concat "x" op "y")))
1280
1281 (define-builtin + (x y) (num-op-num x "+" y))
1282 (define-builtin - (x y) (num-op-num x "-" y))
1283 (define-builtin * (x y) (num-op-num x "*" y))
1284 (define-builtin / (x y) (num-op-num x "/" y))
1285
1286 (define-builtin mod (x y) (num-op-num x "%" y))
1287
1288 (define-builtin < (x y)  (js!bool (num-op-num x "<" y)))
1289 (define-builtin > (x y)  (js!bool (num-op-num x ">" y)))
1290 (define-builtin = (x y)  (js!bool (num-op-num x "==" y)))
1291 (define-builtin <= (x y) (js!bool (num-op-num x "<=" y)))
1292 (define-builtin >= (x y) (js!bool (num-op-num x ">=" y)))
1293
1294 (define-builtin numberp (x)
1295   (js!bool (concat "(typeof (" x ") == \"number\")")))
1296
1297 (define-builtin floor (x)
1298   (type-check (("x" "number" x))
1299     "Math.floor(x)"))
1300
1301 (define-builtin cons (x y)
1302   (concat "({car: " x ", cdr: " y "})"))
1303
1304 (define-builtin consp (x)
1305   (js!bool
1306    (js!selfcall
1307      "var tmp = " x ";" *newline*
1308      "return (typeof tmp == 'object' && 'car' in tmp);" *newline*)))
1309
1310 (define-builtin car (x)
1311   (js!selfcall
1312     "var tmp = " x ";" *newline*
1313     "return tmp === " (ls-compile nil)
1314     "? " (ls-compile nil)
1315     ": tmp.car;" *newline*))
1316
1317 (define-builtin cdr (x)
1318   (js!selfcall
1319     "var tmp = " x ";" *newline*
1320     "return tmp === " (ls-compile nil) "? "
1321     (ls-compile nil)
1322     ": tmp.cdr;" *newline*))
1323
1324 (define-builtin setcar (x new)
1325   (type-check (("x" "object" x))
1326     (concat "(x.car = " new ")")))
1327
1328 (define-builtin setcdr (x new)
1329   (type-check (("x" "object" x))
1330     (concat "(x.cdr = " new ")")))
1331
1332 (define-builtin symbolp (x)
1333   (js!bool
1334    (js!selfcall
1335      "var tmp = " x ";" *newline*
1336      "return (typeof tmp == 'object' && 'name' in tmp);" *newline*)))
1337
1338 (define-builtin make-symbol (name)
1339   (type-check (("name" "string" name))
1340     "({name: name})"))
1341
1342 (define-builtin symbol-name (x)
1343   (concat "(" x ").name"))
1344
1345 (define-builtin set (symbol value)
1346   (concat "(" symbol ").value =" value))
1347
1348 (define-builtin symbol-value (x)
1349   (concat "(" x ").value"))
1350
1351 (define-builtin symbol-function (x)
1352   (concat "(" x ").function"))
1353
1354 (define-builtin eq    (x y) (js!bool (concat "(" x " === " y ")")))
1355 (define-builtin equal (x y) (js!bool (concat "(" x  " == " y ")")))
1356
1357 (define-builtin string (x)
1358   (type-check (("x" "number" x))
1359     "String.fromCharCode(x)"))
1360
1361 (define-builtin stringp (x)
1362   (js!bool (concat "(typeof(" x ") == \"string\")")))
1363
1364 (define-builtin string-upcase (x)
1365   (type-check (("x" "string" x))
1366     "x.toUpperCase()"))
1367
1368 (define-builtin string-length (x)
1369   (type-check (("x" "string" x))
1370     "x.length"))
1371
1372 (define-compilation slice (string a &optional b)
1373   (js!selfcall
1374     "var str = " (ls-compile string env) ";" *newline*
1375     "var a = " (ls-compile a env) ";" *newline*
1376     "var b;" *newline*
1377     (if b
1378         (concat "b = " (ls-compile b env) ";" *newline*)
1379         "")
1380     "return str.slice(a,b);" *newline*))
1381
1382 (define-builtin char (string index)
1383   (type-check (("string" "string" string)
1384                ("index" "number" index))
1385     "string.charCodeAt(index)"))
1386
1387 (define-builtin concat-two (string1 string2)
1388   (type-check (("string1" "string" string1)
1389                ("string2" "string" string2))
1390     "string1.concat(string2)"))
1391
1392 (define-compilation funcall (func &rest args)
1393   (concat "(" (ls-compile func env) ")("
1394           (join (mapcar (lambda (x)
1395                           (ls-compile x env))
1396                         args)
1397                 ", ")
1398           ")"))
1399
1400 (define-compilation apply (func &rest args)
1401   (if (null args)
1402       (concat "(" (ls-compile func env) ")()")
1403       (let ((args (butlast args))
1404             (last (car (last args))))
1405         (js!selfcall
1406           "var f = " (ls-compile func env) ";" *newline*
1407           "var args = [" (join (mapcar (lambda (x)
1408                                          (ls-compile x env))
1409                                        args)
1410                                ", ")
1411           "];" *newline*
1412           "var tail = (" (ls-compile last env) ");" *newline*
1413           "while (tail != " (ls-compile nil) "){" *newline*
1414           "    args.push(tail.car);" *newline*
1415           "    tail = tail.cdr;" *newline*
1416           "}" *newline*
1417           "return f.apply(this, args);" *newline*))))
1418
1419 (define-builtin js-eval (string)
1420   (type-check (("string" "string" string))
1421     "eval.apply(window, [string])"))
1422
1423 (define-builtin error (string)
1424   (js!selfcall "throw " string ";" *newline*))
1425
1426 (define-builtin new () "{}")
1427
1428 (define-builtin oget (object key)
1429   (js!selfcall
1430     "var tmp = " "(" object ")[" key "];" *newline*
1431     "return tmp == undefined? " (ls-compile nil) ": tmp ;" *newline*))
1432
1433 (define-builtin oset (object key value)
1434   (concat "((" object ")[" key "] = " value ")"))
1435
1436 (define-builtin in (key object)
1437   (js!bool (concat "((" key ") in (" object "))")))
1438
1439 (define-builtin functionp (x)
1440   (js!bool (concat "(typeof " x " == 'function')")))
1441
1442 (define-builtin write-string (x)
1443   (type-check (("x" "string" x))
1444     "lisp.write(x)"))
1445
1446 (defun macrop (x)
1447   (and (symbolp x) (eq (binding-type (lookup-function x *environment*)) 'macro)))
1448
1449 (defun ls-macroexpand-1 (form env)
1450   (if (macrop (car form))
1451       (let ((binding (lookup-function (car form) *environment*)))
1452         (if (eq (binding-type binding) 'macro)
1453             (apply (eval (binding-translation binding)) (cdr form))
1454             form))
1455       form))
1456
1457 (defun compile-funcall (function args env)
1458   (cond
1459     ((symbolp function)
1460      (concat (lookup-function-translation function env)
1461              "("
1462              (join (mapcar (lambda (x) (ls-compile x env)) args)
1463                    ", ")
1464              ")"))
1465     ((and (listp function) (eq (car function) 'lambda))
1466      (concat "(" (ls-compile function env) ")("
1467              (join (mapcar (lambda (x) (ls-compile x env)) args)
1468                    ", ")
1469              ")"))
1470     (t
1471      (error (concat "Invalid function designator " (symbol-name function))))))
1472
1473 (defun ls-compile (sexp &optional (env (make-lexenv)))
1474   (cond
1475     ((symbolp sexp)
1476      (let ((b (lookup-variable sexp env)))
1477        (ecase (binding-type b)
1478          (lexical-variable
1479           (binding-translation b))
1480          (special-variable
1481           (ls-compile `(symbol-value ',sexp) env)))))
1482     ((integerp sexp) (integer-to-string sexp))
1483     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
1484     ((listp sexp)
1485      (if (assoc (car sexp) *compilations*)
1486          (let ((comp (second (assoc (car sexp) *compilations*))))
1487            (apply comp env (cdr sexp)))
1488          (if (macrop (car sexp))
1489              (ls-compile (ls-macroexpand-1 sexp env) env)
1490              (compile-funcall (car sexp) (cdr sexp) env))))))
1491
1492 (defun null-or-empty-p (x)
1493   (zerop (length x)))
1494
1495 (defun ls-compile-toplevel (sexp)
1496   (setq *toplevel-compilations* nil)
1497   (cond
1498     ((and (consp sexp) (eq (car sexp) 'progn))
1499      (let ((subs (mapcar #'ls-compile-toplevel (cdr sexp))))
1500        (join (remove-if #'null-or-empty-p subs))))
1501     (t
1502      (let ((code (ls-compile sexp)))
1503        (prog1
1504            (concat (join-trailing (remove-if #'null-or-empty-p *toplevel-compilations*)
1505                                   (concat ";" *newline*))
1506                    (if code
1507                        (concat code ";" *newline*)
1508                        ""))
1509          (setq *toplevel-compilations* nil))))))
1510
1511
1512 ;;; Once we have the compiler, we define the runtime environment and
1513 ;;; interactive development (eval), which works calling the compiler
1514 ;;; and evaluating the Javascript result globally.
1515
1516 #+ecmalisp
1517 (progn
1518   (defmacro with-compilation-unit (&body body)
1519     `(prog1
1520          (progn
1521            (setq *compilation-unit-checks* nil)
1522            (clear-undeclared-global-bindings)
1523            ,@body)
1524        (dolist (check *compilation-unit-checks*)
1525          (funcall check))))
1526
1527   (defun eval (x)
1528     (let ((code
1529            (with-compilation-unit
1530                (ls-compile-toplevel x))))
1531       (js-eval code)))
1532
1533   (js-eval "var lisp")
1534   (js-vset "lisp" (new))
1535   (js-vset "lisp.read" #'ls-read-from-string)
1536   (js-vset "lisp.print" #'prin1-to-string)
1537   (js-vset "lisp.eval" #'eval)
1538   (js-vset "lisp.compile" #'ls-compile-toplevel)
1539   (js-vset "lisp.evalString" (lambda (str) (eval (ls-read-from-string str))))
1540   (js-vset "lisp.compileString" (lambda (str) (ls-compile-toplevel (ls-read-from-string str))))
1541
1542   ;; Set the initial global environment to be equal to the host global
1543   ;; environment at this point of the compilation.
1544   (eval-when-compile
1545     (let ((tmp (ls-compile
1546                 `(progn
1547                    ,@(mapcar (lambda (s)
1548                                `(oset *package* ,(symbol-name (car s))
1549                                       (js-vref ,(cdr s))))
1550                              *literal-symbols*)
1551                    (setq *environment* ',*environment*)
1552                    (setq *variable-counter* ',*variable-counter*)
1553                    (setq *function-counter* ',*function-counter*)
1554                    (setq *gensym-counter* ',*gensym-counter*)
1555                    (setq *block-counter* ',*block-counter*)))))
1556       (setq *toplevel-compilations*
1557             (append *toplevel-compilations* (list tmp))))))
1558
1559
1560 ;;; Finally, we provide a couple of functions to easily bootstrap
1561 ;;; this. It just calls the compiler with this file as input.
1562
1563 #+common-lisp
1564 (progn
1565   (defun read-whole-file (filename)
1566     (with-open-file (in filename)
1567       (let ((seq (make-array (file-length in) :element-type 'character)))
1568         (read-sequence seq in)
1569         seq)))
1570
1571   (defun ls-compile-file (filename output)
1572     (setq *compilation-unit-checks* nil)
1573     (with-open-file (out output :direction :output :if-exists :supersede)
1574       (let* ((source (read-whole-file filename))
1575              (in (make-string-stream source)))
1576         (loop
1577            for x = (ls-read in)
1578            until (eq x *eof*)
1579            for compilation = (ls-compile-toplevel x)
1580            when (plusp (length compilation))
1581            do (write-string compilation out))
1582         (dolist (check *compilation-unit-checks*)
1583           (funcall check))
1584         (setq *compilation-unit-checks* nil))))
1585
1586   (defun bootstrap ()
1587     (setq *environment* (make-lexenv))
1588     (setq *literal-symbols* nil)
1589     (setq *variable-counter* 0
1590           *gensym-counter* 0
1591           *function-counter* 0
1592           *literal-counter* 0
1593           *block-counter* 0)
1594     (ls-compile-file "ecmalisp.lisp" "ecmalisp.js")))