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