Change definition of T and NIL, as package is kept in host now
[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 test ()
527   (mapcar (lambda (x) (1+ x)) '(1 2 3 4)))
528
529 (defun integer-to-string (x)
530   (cond
531     ((zerop x)
532      "0")
533     ((minusp x)
534      (concat "-" (integer-to-string (- 0 x))))
535     (t
536      (let ((digits nil))
537        (while (not (zerop x))
538          (push (mod x 10) digits)
539          (setq x (truncate x 10)))
540        (join (mapcar (lambda (d) (string (char "0123456789" d)))
541                      digits))))))
542
543
544 ;;; Wrap X with a Javascript code to convert the result from
545 ;;; Javascript generalized booleans to T or NIL.
546 (defun js!bool (x)
547   (concat "(" x "?" (ls-compile t) ": " (ls-compile nil) ")"))
548
549 ;;; Concatenate the arguments and wrap them with a self-calling
550 ;;; Javascript anonymous function. It is used to make some Javascript
551 ;;; statements valid expressions and provide a private scope as well.
552 ;;; It could be defined as function, but we could do some
553 ;;; preprocessing in the future.
554 (defmacro js!selfcall (&body body)
555   `(concat "(function(){" *newline* (indent ,@body) "})()"))
556
557
558 ;;; Printer
559
560 #+ecmalisp
561 (progn
562   (defun prin1-to-string (form)
563     (cond
564       ((symbolp form) (symbol-name form))
565       ((integerp form) (integer-to-string form))
566       ((stringp form) (concat "\"" (escape-string form) "\""))
567       ((functionp form)
568        (let ((name (oget form "fname")))
569          (if name
570              (concat "#<FUNCTION " name ">")
571              (concat "#<FUNCTION>"))))
572       ((listp form)
573        (concat "("
574                (join-trailing (mapcar #'prin1-to-string (butlast form)) " ")
575                (let ((last (last form)))
576                  (if (null (cdr last))
577                      (prin1-to-string (car last))
578                      (concat (prin1-to-string (car last)) " . " (prin1-to-string (cdr last)))))
579                ")"))))
580
581   (defun write-line (x)
582     (write-string x)
583     (write-string *newline*)
584     x)
585
586   (defun print (x)
587     (write-line (prin1-to-string x))
588     x))
589
590
591 ;;;; Reader
592
593 ;;; The Lisp reader, parse strings and return Lisp objects. The main
594 ;;; entry points are `ls-read' and `ls-read-from-string'.
595
596 (defun make-string-stream (string)
597   (cons string 0))
598
599 (defun %peek-char (stream)
600   (and (< (cdr stream) (length (car stream)))
601        (char (car stream) (cdr stream))))
602
603 (defun %read-char (stream)
604   (and (< (cdr stream) (length (car stream)))
605        (prog1 (char (car stream) (cdr stream))
606          (setcdr stream (1+ (cdr stream))))))
607
608 (defun whitespacep (ch)
609   (or (char= ch #\space) (char= ch #\newline) (char= ch #\tab)))
610
611 (defun skip-whitespaces (stream)
612   (let (ch)
613     (setq ch (%peek-char stream))
614     (while (and ch (whitespacep ch))
615       (%read-char stream)
616       (setq ch (%peek-char stream)))))
617
618 (defun terminalp (ch)
619   (or (null ch) (whitespacep ch) (char= #\) ch) (char= #\( ch)))
620
621 (defun read-until (stream func)
622   (let ((string "")
623         (ch))
624     (setq ch (%peek-char stream))
625     (while (and ch (not (funcall func ch)))
626       (setq string (concat string (string ch)))
627       (%read-char stream)
628       (setq ch (%peek-char stream)))
629     string))
630
631 (defun skip-whitespaces-and-comments (stream)
632   (let (ch)
633     (skip-whitespaces stream)
634     (setq ch (%peek-char stream))
635     (while (and ch (char= ch #\;))
636       (read-until stream (lambda (x) (char= x #\newline)))
637       (skip-whitespaces stream)
638       (setq ch (%peek-char stream)))))
639
640 (defun %read-list (stream)
641   (skip-whitespaces-and-comments stream)
642   (let ((ch (%peek-char stream)))
643     (cond
644       ((null ch)
645        (error "Unspected EOF"))
646       ((char= ch #\))
647        (%read-char stream)
648        nil)
649       ((char= ch #\.)
650        (%read-char stream)
651        (prog1 (ls-read stream)
652          (skip-whitespaces-and-comments stream)
653          (unless (char= (%read-char stream) #\))
654            (error "')' was expected."))))
655       (t
656        (cons (ls-read stream) (%read-list stream))))))
657
658 (defun read-string (stream)
659   (let ((string "")
660         (ch nil))
661     (setq ch (%read-char stream))
662     (while (not (eql ch #\"))
663       (when (null ch)
664         (error "Unexpected EOF"))
665       (when (eql ch #\\)
666         (setq ch (%read-char stream)))
667       (setq string (concat string (string ch)))
668       (setq ch (%read-char stream)))
669     string))
670
671 (defun read-sharp (stream)
672   (%read-char stream)
673   (ecase (%read-char stream)
674     (#\'
675      (list 'function (ls-read stream)))
676     (#\\
677      (let ((cname
678             (concat (string (%read-char stream))
679                     (read-until stream #'terminalp))))
680        (cond
681          ((string= cname "space") (char-code #\space))
682          ((string= cname "tab") (char-code #\tab))
683          ((string= cname "newline") (char-code #\newline))
684          (t (char-code (char cname 0))))))
685     (#\+
686      (let ((feature (read-until stream #'terminalp)))
687        (cond
688          ((string= feature "common-lisp")
689           (ls-read stream)              ;ignore
690           (ls-read stream))
691          ((string= feature "ecmalisp")
692           (ls-read stream))
693          (t
694           (error "Unknown reader form.")))))))
695
696 (defvar *eof* (make-symbol "EOF"))
697 (defun ls-read (stream)
698   (skip-whitespaces-and-comments stream)
699   (let ((ch (%peek-char stream)))
700     (cond
701       ((null ch)
702        *eof*)
703       ((char= ch #\()
704        (%read-char stream)
705        (%read-list stream))
706       ((char= ch #\')
707        (%read-char stream)
708        (list 'quote (ls-read stream)))
709       ((char= ch #\`)
710        (%read-char stream)
711        (list 'backquote (ls-read stream)))
712       ((char= ch #\")
713        (%read-char stream)
714        (read-string stream))
715       ((char= ch #\,)
716        (%read-char stream)
717        (if (eql (%peek-char stream) #\@)
718            (progn (%read-char stream) (list 'unquote-splicing (ls-read stream)))
719            (list 'unquote (ls-read stream))))
720       ((char= ch #\#)
721        (read-sharp stream))
722       (t
723        (let ((string (read-until stream #'terminalp)))
724          (if (every #'digit-char-p string)
725              (parse-integer string)
726              (intern (string-upcase string))))))))
727
728 (defun ls-read-from-string (string)
729   (ls-read (make-string-stream string)))
730
731
732 ;;;; Compiler
733
734 ;;; Translate the Lisp code to Javascript. It will compile the special
735 ;;; forms. Some primitive functions are compiled as special forms
736 ;;; too. The respective real functions are defined in the target (see
737 ;;; the beginning of this file) as well as some primitive functions.
738
739 (defvar *compilation-unit-checks* '())
740
741 (defun make-binding (name type translation declared)
742   (list name type translation declared))
743
744 (defun binding-name (b) (first b))
745 (defun binding-type (b) (second b))
746 (defun binding-translation (b) (third b))
747 (defun binding-declared (b)
748   (and b (fourth b)))
749 (defun mark-binding-as-declared (b)
750   (setcar (cdddr b) t))
751
752 (defun make-lexenv ()
753   (list nil nil nil nil))
754
755 (defun copy-lexenv (lexenv)
756   (copy-list lexenv))
757
758 (defun push-to-lexenv (binding lexenv namespace)
759   (ecase namespace
760     (variable
761      (setcar lexenv (cons binding (car lexenv))))
762     (function
763      (setcar (cdr lexenv) (cons binding (cadr lexenv))))
764     (block
765      (setcar (cddr lexenv) (cons binding (caddr lexenv))))
766     (gotag
767      (setcar (cdddr lexenv) (cons binding (cadddr lexenv))))))
768
769 (defun extend-lexenv (bindings lexenv namespace)
770   (let ((env (copy-lexenv lexenv)))
771     (dolist (binding (reverse bindings) env)
772       (push-to-lexenv binding env namespace))))
773
774 (defun lookup-in-lexenv (name lexenv namespace)
775   (assoc name (ecase namespace
776                 (variable (first lexenv))
777                 (function (second lexenv))
778                 (block (third lexenv))
779                 (gotag (fourth lexenv)))))
780
781 (defvar *environment* (make-lexenv))
782
783 (defun clear-undeclared-global-bindings ()
784   (setq *environment*
785         (mapcar (lambda (namespace)
786                   (remove-if-not #'binding-declared namespace))
787                 *environment*)))
788
789
790 (defvar *variable-counter* 0)
791 (defun gvarname (symbol)
792   (concat "v" (integer-to-string (incf *variable-counter*))))
793
794 (defun lookup-variable (symbol env)
795   (or (lookup-in-lexenv symbol env 'variable)
796       (lookup-in-lexenv symbol *environment* 'variable)
797       (let ((name (symbol-name symbol))
798             (binding (make-binding symbol 'special-variable (gvarname symbol) nil)))
799         (push-to-lexenv binding *environment* 'variable)
800         (push (lambda ()
801                 (let ((b (lookup-in-lexenv symbol *environment* 'variable)))
802                   (unless (binding-declared b)
803                       (error (concat "Undefined variable `" name "'")))))
804               *compilation-unit-checks*)
805         binding)))
806
807 (defun lookup-variable-translation (symbol env)
808   (binding-translation (lookup-variable symbol env)))
809
810 (defun extend-local-env (args env)
811   (let ((new (copy-lexenv env)))
812     (dolist (symbol args new)
813       (let ((b (make-binding symbol 'lexical-variable (gvarname symbol) t)))
814         (push-to-lexenv b new 'variable)))))
815
816 (defvar *function-counter* 0)
817 (defun lookup-function (symbol env)
818   (or (lookup-in-lexenv symbol env 'function)
819       (lookup-in-lexenv symbol *environment* 'function)
820       (let ((name (symbol-name symbol))
821             (binding
822              (make-binding symbol
823                            'function
824                            (concat "f" (integer-to-string (incf *function-counter*)))
825                            nil)))
826         (push-to-lexenv binding *environment* 'function)
827         (push (lambda ()
828                 (let ((b (lookup-in-lexenv symbol *environment* 'function)))
829                   (unless (binding-declared b)
830                     (error (concat "Undefined function `" name "'")))))
831               *compilation-unit-checks*)
832         binding)))
833
834 (defun lookup-function-translation (symbol env)
835   (binding-translation (lookup-function symbol env)))
836
837 (defvar *toplevel-compilations* nil)
838
839 (defun %compile-defvar (name)
840   (let ((b (lookup-variable name *environment*)))
841     (mark-binding-as-declared b)
842     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
843
844 (defun %compile-defun (name)
845   (let ((b (lookup-function name *environment*)))
846     (mark-binding-as-declared b)
847     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
848
849 (defun %compile-defmacro (name lambda)
850   (push-to-lexenv (make-binding name 'macro lambda t) *environment* 'function))
851
852 (defvar *compilations* nil)
853
854 (defun ls-compile-block (sexps env)
855   (join-trailing
856    (remove-if (lambda (x)
857                 (or (null x)
858                     (and (stringp x)
859                          (zerop (length x)))))
860               (mapcar (lambda (x) (ls-compile x env))  sexps))
861    (concat ";" *newline*)))
862
863 (defmacro define-compilation (name args &body body)
864   ;; Creates a new primitive `name' with parameters args and
865   ;; @body. The body can access to the local environment through the
866   ;; variable ENV.
867   `(push (list ',name (lambda (env ,@args) (block ,name ,@body)))
868          *compilations*))
869
870 (define-compilation if (condition true false)
871   (concat "("
872           (ls-compile condition env) " !== " (ls-compile nil)
873           " ? "
874           (ls-compile true env)
875           " : "
876           (ls-compile false env)
877           ")"))
878
879
880 (defvar *lambda-list-keywords* '(&optional &rest))
881
882 (defun list-until-keyword (list)
883   (if (or (null list) (member (car list) *lambda-list-keywords*))
884       nil
885       (cons (car list) (list-until-keyword (cdr list)))))
886
887 (defun lambda-list-required-arguments (lambda-list)
888   (list-until-keyword lambda-list))
889
890 (defun lambda-list-optional-arguments-with-default (lambda-list)
891   (mapcar #'ensure-list (list-until-keyword (cdr (member '&optional lambda-list)))))
892
893 (defun lambda-list-optional-arguments (lambda-list)
894   (mapcar #'car (lambda-list-optional-arguments-with-default lambda-list)))
895
896 (defun lambda-list-rest-argument (lambda-list)
897   (let ((rest (list-until-keyword (cdr (member '&rest lambda-list)))))
898     (when (cdr rest)
899       (error "Bad lambda-list"))
900     (car rest)))
901
902 (define-compilation lambda (lambda-list &rest body)
903   (let ((required-arguments (lambda-list-required-arguments lambda-list))
904         (optional-arguments (lambda-list-optional-arguments lambda-list))
905         (rest-argument (lambda-list-rest-argument lambda-list)))
906     (let ((n-required-arguments (length required-arguments))
907           (n-optional-arguments (length optional-arguments))
908           (new-env (extend-local-env
909                     (append (ensure-list rest-argument)
910                             required-arguments
911                             optional-arguments)
912                     env)))
913       (concat "(function ("
914               (join (mapcar (lambda (x)
915                               (lookup-variable-translation x new-env))
916                             (append required-arguments optional-arguments))
917                     ",")
918               "){" *newline*
919               ;; Check number of arguments
920               (indent
921                (if required-arguments
922                    (concat "if (arguments.length < " (integer-to-string n-required-arguments)
923                            ") throw 'too few arguments';" *newline*)
924                    "")
925                (if (not rest-argument)
926                    (concat "if (arguments.length > "
927                            (integer-to-string (+ n-required-arguments n-optional-arguments))
928                            ") throw 'too many arguments';" *newline*)
929                    "")
930                ;; Optional arguments
931                (if optional-arguments
932                    (concat "switch(arguments.length){" *newline*
933                            (let ((optional-and-defaults
934                                   (lambda-list-optional-arguments-with-default lambda-list))
935                                  (cases nil)
936                                  (idx 0))
937                              (progn
938                                (while (< idx n-optional-arguments)
939                                  (let ((arg (nth idx optional-and-defaults)))
940                                    (push (concat "case "
941                                                  (integer-to-string (+ idx n-required-arguments)) ":" *newline*
942                                                  (lookup-variable-translation (car arg) new-env)
943                                                  "="
944                                                  (ls-compile (cadr arg) new-env)
945                                                  ";" *newline*)
946                                          cases)
947                                    (incf idx)))
948                                     (push (concat "default: break;" *newline*) cases)
949                                     (join (reverse cases))))
950                            "}" *newline*)
951                    "")
952                ;; &rest/&body argument
953                (if rest-argument
954                    (let ((js!rest (lookup-variable-translation rest-argument new-env)))
955                      (concat "var " js!rest "= " (ls-compile nil) ";" *newline*
956                              "for (var i = arguments.length-1; i>="
957                              (integer-to-string (+ n-required-arguments n-optional-arguments))
958                              "; i--)" *newline*
959                              (indent js!rest " = "
960                                      "{car: arguments[i], cdr: ") js!rest "};"
961                                      *newline*))
962                    "")
963                ;; Body
964                (concat (ls-compile-block (butlast body) new-env)
965                        "return " (ls-compile (car (last body)) new-env) ";")) *newline*
966               "})"))))
967
968 (define-compilation fsetq (var val)
969   (concat (lookup-function-translation var env)
970           " = "
971           (ls-compile val env)))
972
973 (define-compilation setq (var val)
974   (let ((b (lookup-variable var env)))
975     (ecase (binding-type b)
976       (lexical-variable (concat (binding-translation b) " = " (ls-compile val env)))
977       (special-variable (ls-compile `(set ',var ,val) env)))))
978
979 ;;; FFI Variable accessors
980 (define-compilation js-vref (var)
981   var)
982 (define-compilation js-vset (var val)
983   (concat "(" var " = " (ls-compile val env) ")"))
984
985
986 ;;; Literals
987 (defun escape-string (string)
988   (let ((output "")
989         (index 0)
990         (size (length string)))
991     (while (< index size)
992       (let ((ch (char string index)))
993         (when (or (char= ch #\") (char= ch #\\))
994           (setq output (concat output "\\")))
995         (when (or (char= ch #\newline))
996           (setq output (concat output "\\"))
997           (setq ch #\n))
998         (setq output (concat output (string ch))))
999       (incf index))
1000     output))
1001
1002
1003 (defvar *literal-symbols* nil)
1004 (defvar *literal-counter* 0)
1005
1006 (defun genlit ()
1007   (concat "l" (integer-to-string (incf *literal-counter*))))
1008
1009 (defun literal (sexp &optional recursive)
1010   (cond
1011     ((integerp sexp) (integer-to-string sexp))
1012     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
1013     ((symbolp sexp)
1014      (or (cdr (assoc sexp *literal-symbols*))
1015          (let ((v (genlit))
1016                (s (concat "{name: \"" (escape-string (symbol-name sexp)) "\"}")))
1017            (push (cons sexp v) *literal-symbols*)
1018            (push (concat "var " v " = " s) *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 #+common-lisp
1030 (define-compilation quote (sexp)
1031   (literal sexp))
1032
1033 #+ecmalisp
1034 (define-compilation quote (sexp)
1035   (let ((v (genlit)))
1036     (push (ls-compile `(js-vset ,v ,sexp) env)
1037           *toplevel-compilations*)
1038     v))
1039
1040
1041 (define-compilation %while (pred &rest body)
1042   (js!selfcall
1043     "while(" (ls-compile pred env) " !== " (ls-compile nil) "){" *newline*
1044     (indent (ls-compile-block body env))
1045     "}"
1046     "return " (ls-compile nil) ";" *newline*))
1047
1048 (define-compilation function (x)
1049   (cond
1050     ((and (listp x) (eq (car x) 'lambda))
1051      (ls-compile x env))
1052     ((symbolp x)
1053      (lookup-function-translation x env))))
1054
1055 (define-compilation eval-when-compile (&rest body)
1056   (eval (cons 'progn body))
1057   "")
1058
1059 (defmacro define-transformation (name args form)
1060   `(define-compilation ,name ,args
1061      (ls-compile ,form env)))
1062
1063 (define-compilation progn (&rest body)
1064   (js!selfcall
1065     (ls-compile-block (butlast body) env)
1066     "return " (ls-compile (car (last body)) env) ";" *newline*))
1067
1068 (define-compilation let (bindings &rest body)
1069   (let ((bindings (mapcar #'ensure-list bindings)))
1070     (let ((variables (mapcar #'first bindings))
1071           (values    (mapcar #'second bindings)))
1072       (let ((new-env (extend-local-env variables env)))
1073         (concat "(function("
1074                 (join (mapcar (lambda (x)
1075                                 (lookup-variable-translation x new-env))
1076                               variables)
1077                       ",")
1078                 "){" *newline*
1079                 (indent (ls-compile-block (butlast body) new-env)
1080                         "return " (ls-compile (car (last body)) new-env)
1081                         ";" *newline*)
1082                 "})(" (join (mapcar (lambda (x) (ls-compile x env))
1083                                     values)
1084                             ",")
1085                 ")")))))
1086
1087
1088 (defvar *block-counter* 0)
1089
1090 (define-compilation block (name &rest body)
1091   (let ((tr (integer-to-string (incf *block-counter*))))
1092     (let ((b (make-binding name 'block tr t)))
1093       (js!selfcall
1094         "try {" *newline*
1095         (indent "return " (ls-compile `(progn ,@body)
1096                                       (extend-lexenv (list b) env 'block))
1097                 ";" *newline*)
1098         "}" *newline*
1099         "catch (cf){" *newline*
1100         "    if (cf.type == 'block' && cf.id == " tr ")" *newline*
1101         "        return cf.value;" *newline*
1102         "    else" *newline*
1103         "        throw cf;" *newline*
1104         "}" *newline*))))
1105
1106 (define-compilation return-from (name &optional value)
1107   (let ((b (lookup-in-lexenv name env 'block)))
1108     (if b
1109         (js!selfcall
1110           "throw ({"
1111           "type: 'block', "
1112           "id: " (binding-translation b) ", "
1113           "value: " (ls-compile value env) ", "
1114           "message: 'Return from unknown block " (symbol-name name) ".'"
1115           "})")
1116         (error (concat "Unknown block `" (symbol-name name) "'.")))))
1117
1118
1119 (define-compilation catch (id &rest body)
1120   (js!selfcall
1121     "var id = " (ls-compile id env) ";" *newline*
1122     "try {" *newline*
1123     (indent "return " (ls-compile `(progn ,@body))
1124             ";" *newline*)
1125     "}" *newline*
1126     "catch (cf){" *newline*
1127     "    if (cf.type == 'catch' && cf.id == id)" *newline*
1128     "        return cf.value;" *newline*
1129     "    else" *newline*
1130     "        throw cf;" *newline*
1131     "}" *newline*))
1132
1133 (define-compilation throw (id &optional value)
1134   (js!selfcall
1135     "throw ({"
1136     "type: 'catch', "
1137     "id: " (ls-compile id env) ", "
1138     "value: " (ls-compile value env) ", "
1139     "message: 'Throw uncatched.'"
1140     "})"))
1141
1142
1143 (defvar *tagbody-counter* 0)
1144 (defvar *go-tag-counter* 0)
1145
1146 (defun go-tag-p (x)
1147   (or (integerp x) (symbolp x)))
1148
1149 (defun declare-tagbody-tags (env tbidx body)
1150   (let ((bindings
1151          (mapcar (lambda (label)
1152                    (let ((tagidx (integer-to-string (incf *go-tag-counter*))))
1153                      (make-binding label 'gotag (list tbidx tagidx) t)))
1154                  (remove-if-not #'go-tag-p body))))
1155     (extend-lexenv bindings env 'gotag)))
1156
1157 (define-compilation tagbody (&rest body)
1158   ;; Ignore the tagbody if it does not contain any go-tag. We do this
1159   ;; because 1) it is easy and 2) many built-in forms expand to a
1160   ;; implicit tagbody, so we save some space.
1161   (unless (some #'go-tag-p body)
1162     (return-from tagbody (ls-compile `(progn ,@body nil) env)))
1163   ;; The translation assumes the first form in BODY is a label
1164   (unless (go-tag-p (car body))
1165     (push (gensym "START") body))
1166   ;; Tagbody compilation
1167   (let ((tbidx (integer-to-string *tagbody-counter*)))
1168     (let ((env (declare-tagbody-tags env tbidx body))
1169           initag)
1170       (let ((b (lookup-in-lexenv (first body) env 'gotag)))
1171         (setq initag (second (binding-translation b))))
1172       (js!selfcall
1173         "var tagbody_" tbidx " = " initag ";" *newline*
1174         "tbloop:" *newline*
1175         "while (true) {" *newline*
1176         (indent "try {" *newline*
1177                 (indent (let ((content ""))
1178                           (concat "switch(tagbody_" tbidx "){" *newline*
1179                                   "case " initag ":" *newline*
1180                                   (dolist (form (cdr body) content)
1181                                     (concatf content
1182                                       (if (not (go-tag-p form))
1183                                           (indent (ls-compile form env) ";" *newline*)
1184                                           (let ((b (lookup-in-lexenv form env 'gotag)))
1185                                             (concat "case " (second (binding-translation b)) ":" *newline*)))))
1186                                   "default:" *newline*
1187                                   "    break tbloop;" *newline*
1188                                   "}" *newline*)))
1189                 "}" *newline*
1190                 "catch (jump) {" *newline*
1191                 "    if (jump.type == 'tagbody' && jump.id == " tbidx ")" *newline*
1192                 "        tagbody_" tbidx " = jump.label;" *newline*
1193                 "    else" *newline*
1194                 "        throw(jump);" *newline*
1195                 "}" *newline*)
1196         "}" *newline*
1197         "return " (ls-compile nil) ";" *newline*))))
1198
1199 (define-compilation go (label)
1200   (let ((b (lookup-in-lexenv label env 'gotag))
1201         (n (cond
1202              ((symbolp label) (symbol-name label))
1203              ((integerp label) (integer-to-string label)))))
1204     (if b
1205         (js!selfcall
1206           "throw ({"
1207           "type: 'tagbody', "
1208           "id: " (first (binding-translation b)) ", "
1209           "label: " (second (binding-translation b)) ", "
1210           "message: 'Attempt to GO to non-existing tag " n "'"
1211           "})" *newline*)
1212         (error (concat "Unknown tag `" n "'.")))))
1213
1214
1215 (define-compilation unwind-protect (form &rest clean-up)
1216   (js!selfcall
1217     "var ret = " (ls-compile nil) ";" *newline*
1218     "try {" *newline*
1219     (indent "ret = " (ls-compile form env) ";" *newline*)
1220     "} finally {" *newline*
1221     (indent (ls-compile-block clean-up env))
1222     "}" *newline*
1223     "return ret;" *newline*))
1224
1225
1226 ;;; A little backquote implementation without optimizations of any
1227 ;;; kind for ecmalisp.
1228 (defun backquote-expand-1 (form)
1229   (cond
1230     ((symbolp form)
1231      (list 'quote form))
1232     ((atom form)
1233      form)
1234     ((eq (car form) 'unquote)
1235      (car form))
1236     ((eq (car form) 'backquote)
1237      (backquote-expand-1 (backquote-expand-1 (cadr form))))
1238     (t
1239      (cons 'append
1240            (mapcar (lambda (s)
1241                      (cond
1242                        ((and (listp s) (eq (car s) 'unquote))
1243                         (list 'list (cadr s)))
1244                        ((and (listp s) (eq (car s) 'unquote-splicing))
1245                         (cadr s))
1246                        (t
1247                         (list 'list (backquote-expand-1 s)))))
1248                    form)))))
1249
1250 (defun backquote-expand (form)
1251   (if (and (listp form) (eq (car form) 'backquote))
1252       (backquote-expand-1 (cadr form))
1253       form))
1254
1255 (defmacro backquote (form)
1256   (backquote-expand-1 form))
1257
1258 (define-transformation backquote (form)
1259   (backquote-expand-1 form))
1260
1261 ;;; Primitives
1262
1263 (defmacro define-builtin (name args &body body)
1264   `(define-compilation ,name ,args
1265      (let ,(mapcar (lambda (arg) `(,arg (ls-compile ,arg env))) args)
1266        ,@body)))
1267
1268 ;;; DECLS is a list of (JSVARNAME TYPE LISPFORM) declarations.
1269 (defmacro type-check (decls &body body)
1270   `(js!selfcall
1271      ,@(mapcar (lambda (decl)
1272                    `(concat "var " ,(first decl) " = " ,(third decl) ";" *newline*))
1273                  decls)
1274      ,@(mapcar (lambda (decl)
1275                  `(concat "if (typeof " ,(first decl) " != '" ,(second decl) "')" *newline*
1276                           (indent "throw 'The value ' + "
1277                                   ,(first decl)
1278                                   " + ' is not a type "
1279                                   ,(second decl)
1280                                   ".';"
1281                                   *newline*)))
1282                decls)
1283      (concat "return " (progn ,@body) ";" *newline*)))
1284
1285 (defun num-op-num (x op y)
1286   (type-check (("x" "number" x) ("y" "number" y))
1287     (concat "x" op "y")))
1288
1289 (define-builtin + (x y) (num-op-num x "+" y))
1290 (define-builtin - (x y) (num-op-num x "-" y))
1291 (define-builtin * (x y) (num-op-num x "*" y))
1292 (define-builtin / (x y) (num-op-num x "/" y))
1293
1294 (define-builtin mod (x y) (num-op-num x "%" y))
1295
1296 (define-builtin < (x y)  (js!bool (num-op-num x "<" y)))
1297 (define-builtin > (x y)  (js!bool (num-op-num x ">" y)))
1298 (define-builtin = (x y)  (js!bool (num-op-num x "==" y)))
1299 (define-builtin <= (x y) (js!bool (num-op-num x "<=" y)))
1300 (define-builtin >= (x y) (js!bool (num-op-num x ">=" y)))
1301
1302 (define-builtin numberp (x)
1303   (js!bool (concat "(typeof (" x ") == \"number\")")))
1304
1305 (define-builtin floor (x)
1306   (type-check (("x" "number" x))
1307     "Math.floor(x)"))
1308
1309 (define-builtin cons (x y) (concat "({car: " x ", cdr: " y "})"))
1310 (define-builtin consp (x)
1311   (js!bool
1312    (js!selfcall
1313      "var tmp = " x ";" *newline*
1314      "return (typeof tmp == 'object' && 'car' in tmp);" *newline*)))
1315
1316 (define-builtin car (x)
1317   (js!selfcall
1318     "var tmp = " x ";" *newline*
1319     "return tmp === " (ls-compile nil)
1320     "? " (ls-compile nil)
1321     ": tmp.car;" *newline*))
1322
1323 (define-builtin cdr (x)
1324   (js!selfcall
1325     "var tmp = " x ";" *newline*
1326     "return tmp === " (ls-compile nil) "? "
1327     (ls-compile nil)
1328     ": tmp.cdr;" *newline*))
1329
1330 (define-builtin setcar (x new)
1331   (type-check (("x" "object" x))
1332     (concat "(x.car = " new ")")))
1333
1334 (define-builtin setcdr (x new)
1335   (type-check (("x" "object" x))
1336     (concat "(x.cdr = " new ")")))
1337
1338 (define-builtin symbolp (x)
1339   (js!bool
1340    (js!selfcall
1341      "var tmp = " x ";" *newline*
1342      "return (typeof tmp == 'object' && 'name' in tmp);" *newline*)))
1343
1344 (define-builtin make-symbol (name)
1345   (type-check (("name" "string" name))
1346     "({name: name})"))
1347
1348 (define-builtin symbol-name (x)
1349   (concat "(" x ").name"))
1350
1351 (define-builtin set (symbol value)
1352   (concat "(" symbol ").value =" value))
1353
1354 (define-builtin symbol-value (x)
1355   (concat "(" x ").value"))
1356
1357 (define-builtin symbol-function (x)
1358   (concat "(" x ").function"))
1359
1360 (define-builtin eq    (x y) (js!bool (concat "(" x " === " y ")")))
1361 (define-builtin equal (x y) (js!bool (concat "(" x  " == " y ")")))
1362
1363 (define-builtin string (x)
1364   (type-check (("x" "number" x))
1365     "String.fromCharCode(x)"))
1366
1367 (define-builtin stringp (x)
1368   (js!bool (concat "(typeof(" x ") == \"string\")")))
1369
1370 (define-builtin string-upcase (x)
1371   (type-check (("x" "string" x))
1372     "x.toUpperCase()"))
1373
1374 (define-builtin string-length (x)
1375   (type-check (("x" "string" x))
1376     "x.length"))
1377
1378 (define-compilation slice (string a &optional b)
1379   (js!selfcall
1380     "var str = " (ls-compile string env) ";" *newline*
1381     "var a = " (ls-compile a env) ";" *newline*
1382     "var b;" *newline*
1383     (if b
1384         (concat "b = " (ls-compile b env) ";" *newline*)
1385         "")
1386     "return str.slice(a,b);" *newline*))
1387
1388 (define-builtin char (string index)
1389   (type-check (("string" "string" string)
1390                ("index" "number" index))
1391     "string.charCodeAt(index)"))
1392
1393 (define-builtin concat-two (string1 string2)
1394   (type-check (("string1" "string" string1)
1395                ("string2" "string" string2))
1396     "string1.concat(string2)"))
1397
1398 (define-compilation funcall (func &rest args)
1399   (concat "(" (ls-compile func env) ")("
1400           (join (mapcar (lambda (x)
1401                           (ls-compile x env))
1402                         args)
1403                 ", ")
1404           ")"))
1405
1406 (define-compilation apply (func &rest args)
1407   (if (null args)
1408       (concat "(" (ls-compile func env) ")()")
1409       (let ((args (butlast args))
1410             (last (car (last args))))
1411         (js!selfcall
1412           "var f = " (ls-compile func env) ";" *newline*
1413           "var args = [" (join (mapcar (lambda (x)
1414                                          (ls-compile x env))
1415                                        args)
1416                                ", ")
1417           "];" *newline*
1418           "var tail = (" (ls-compile last env) ");" *newline*
1419           "while (tail != " (ls-compile nil) "){" *newline*
1420           "    args.push(tail.car);" *newline*
1421           "    tail = tail.cdr;" *newline*
1422           "}" *newline*
1423           "return f.apply(this, args);" *newline*))))
1424
1425 (define-builtin js-eval (string)
1426   (type-check (("string" "string" string))
1427     "eval.apply(window, [string])"))
1428
1429 (define-builtin error (string)
1430   (js!selfcall "throw " string ";" *newline*))
1431
1432 (define-builtin new () "{}")
1433
1434 (define-builtin oget (object key)
1435   (js!selfcall
1436     "var tmp = " "(" object ")[" key "];" *newline*
1437     "return tmp == undefined? " (ls-compile nil) ": tmp ;" *newline*))
1438
1439 (define-builtin oset (object key value)
1440   (concat "((" object ")[" key "] = " value ")"))
1441
1442 (define-builtin in (key object)
1443   (js!bool (concat "((" key ") in (" object "))")))
1444
1445 (define-builtin functionp (x)
1446   (js!bool (concat "(typeof " x " == 'function')")))
1447
1448 (define-builtin write-string (x)
1449   (type-check (("x" "string" x))
1450     "lisp.write(x)"))
1451
1452 (defun macrop (x)
1453   (and (symbolp x) (eq (binding-type (lookup-function x *environment*)) 'macro)))
1454
1455 (defun ls-macroexpand-1 (form env)
1456   (if (macrop (car form))
1457       (let ((binding (lookup-function (car form) *environment*)))
1458         (if (eq (binding-type binding) 'macro)
1459             (apply (eval (binding-translation binding)) (cdr form))
1460             form))
1461       form))
1462
1463 (defun compile-funcall (function args env)
1464   (cond
1465     ((symbolp function)
1466      (concat (lookup-function-translation function env)
1467              "("
1468              (join (mapcar (lambda (x) (ls-compile x env)) args)
1469                    ", ")
1470              ")"))
1471     ((and (listp function) (eq (car function) 'lambda))
1472      (concat "(" (ls-compile function env) ")("
1473              (join (mapcar (lambda (x) (ls-compile x env)) args)
1474                    ", ")
1475              ")"))
1476     (t
1477      (error (concat "Invalid function designator " (symbol-name function))))))
1478
1479 (defun ls-compile (sexp &optional (env (make-lexenv)))
1480   (cond
1481     ((symbolp sexp)
1482      (let ((b (lookup-variable sexp env)))
1483        (ecase (binding-type b)
1484          (lexical-variable
1485           (binding-translation b))
1486          (special-variable
1487           (ls-compile `(symbol-value ',sexp) env)))))
1488     ((integerp sexp) (integer-to-string sexp))
1489     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
1490     ((listp sexp)
1491      (if (assoc (car sexp) *compilations*)
1492          (let ((comp (second (assoc (car sexp) *compilations*))))
1493            (apply comp env (cdr sexp)))
1494          (if (macrop (car sexp))
1495              (ls-compile (ls-macroexpand-1 sexp env) env)
1496              (compile-funcall (car sexp) (cdr sexp) env))))))
1497
1498 (defun ls-compile-toplevel (sexp)
1499   (cond
1500     ((and (consp sexp) (eq (car sexp) 'progn))
1501      (let ((subs (mapcar 'ls-compile-toplevel (cdr sexp))))
1502        (join-trailing
1503         (remove-if (lambda (s) (or (null s) (equal s "")))
1504                    subs)
1505         (concat ";" *newline*))))
1506     (t
1507      (setq *toplevel-compilations* nil)
1508      (let ((code (ls-compile sexp)))
1509        (prog1
1510            (concat (join-trailing *toplevel-compilations*
1511                                   (concat ";" *newline*))
1512                    code)
1513          (setq *toplevel-compilations* nil))))))
1514
1515
1516 ;;; Once we have the compiler, we define the runtime environment and
1517 ;;; interactive development (eval), which works calling the compiler
1518 ;;; and evaluating the Javascript result globally.
1519
1520 #+ecmalisp
1521 (progn
1522   (defmacro with-compilation-unit (&body body)
1523     `(prog1
1524          (progn
1525            (setq *compilation-unit-checks* nil)
1526            (clear-undeclared-global-bindings)
1527            ,@body)
1528        (dolist (check *compilation-unit-checks*)
1529          (funcall check))))
1530
1531   (defun eval (x)
1532     (let ((code
1533            (with-compilation-unit
1534                (ls-compile-toplevel x))))
1535       (js-eval code)))
1536
1537   ;; Set the initial global environment to be equal to the host global
1538   ;; environment at this point of the compilation.
1539   (eval-when-compile
1540     (let ((tmp (ls-compile
1541                 `(progn
1542                    (setq *environment* ',*environment*)
1543                    (setq *variable-counter* ',*variable-counter*)
1544                    (setq *function-counter* ',*function-counter*)
1545                    (setq *literal-counter* ',*literal-counter*)
1546                    (setq *gensym-counter* ',*gensym-counter*)
1547                    (setq *block-counter* ',*block-counter*)
1548                    ,@(mapcar (lambda (s)
1549                                `(oset *package* ,(symbol-name (car s))
1550                                       (js-vref ,(cdr s))))
1551                              *literal-symbols*)))))
1552       (setq *toplevel-compilations*
1553             (append *toplevel-compilations* (list tmp)))))
1554
1555   (js-eval "var lisp")
1556   (js-vset "lisp" (new))
1557   (js-vset "lisp.read" #'ls-read-from-string)
1558   (js-vset "lisp.print" #'prin1-to-string)
1559   (js-vset "lisp.eval" #'eval)
1560   (js-vset "lisp.compile" #'ls-compile-toplevel)
1561   (js-vset "lisp.evalString" (lambda (str) (eval (ls-read-from-string str))))
1562   (js-vset "lisp.compileString" (lambda (str) (ls-compile-toplevel (ls-read-from-string str)))))
1563
1564
1565 ;;; Finally, we provide a couple of functions to easily bootstrap
1566 ;;; this. It just calls the compiler with this file as input.
1567
1568 #+common-lisp
1569 (progn
1570   (defun read-whole-file (filename)
1571     (with-open-file (in filename)
1572       (let ((seq (make-array (file-length in) :element-type 'character)))
1573         (read-sequence seq in)
1574         seq)))
1575
1576   (defun ls-compile-file (filename output)
1577     (setq *compilation-unit-checks* nil)
1578     (with-open-file (out output :direction :output :if-exists :supersede)
1579       (let* ((source (read-whole-file filename))
1580              (in (make-string-stream source)))
1581         (loop
1582            for x = (ls-read in)
1583            until (eq x *eof*)
1584            for compilation = (ls-compile-toplevel x)
1585            when (plusp (length compilation))
1586            do (write-line (concat compilation "; ") out))
1587         (dolist (check *compilation-unit-checks*)
1588           (funcall check))
1589         (setq *compilation-unit-checks* nil))))
1590
1591   (defun bootstrap ()
1592     (setq *environment* (make-lexenv))
1593     (setq *literal-symbols* nil)
1594     (setq *variable-counter* 0
1595           *gensym-counter* 0
1596           *function-counter* 0
1597           *literal-counter* 0
1598           *block-counter* 0)
1599     (ls-compile-file "ecmalisp.lisp" "ecmalisp.js")))