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