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