Implicit blocks for WHILE, DOTIMES, DOLIST and DEFUN
[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 (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     (let ((found nil))
397       (while (and alist (not found))
398         (if (eql x (caar alist))
399             (setq found t)
400             (setq alist (cdr alist))))
401       (car alist)))
402
403   (defun string= (s1 s2)
404     (equal s1 s2)))
405
406
407 ;;; The compiler offers some primitives and special forms which are
408 ;;; not found in Common Lisp, for instance, while. So, we grow Common
409 ;;; Lisp a bit to it can execute the rest of the file.
410 #+common-lisp
411 (progn
412   (defmacro while (condition &body body)
413     `(do ()
414          ((not ,condition))
415        ,@body))
416
417   (defmacro eval-when-compile (&body body)
418     `(eval-when (:compile-toplevel :load-toplevel :execute)
419        ,@body))
420
421   (defun concat-two (s1 s2)
422     (concatenate 'string s1 s2))
423
424   (defun setcar (cons new)
425     (setf (car cons) new))
426   (defun setcdr (cons new)
427     (setf (cdr cons) new)))
428
429 ;;; At this point, no matter if Common Lisp or ecmalisp is compiling
430 ;;; from here, this code will compile on both. We define some helper
431 ;;; functions now for string manipulation and so on. They will be
432 ;;; useful in the compiler, mostly.
433
434 (defvar *newline* (string (code-char 10)))
435
436 (defun concat (&rest strs)
437   (!reduce #'concat-two strs ""))
438
439 ;;; Concatenate a list of strings, with a separator
440 (defun join (list &optional (separator ""))
441   (cond
442     ((null list)
443      "")
444     ((null (cdr list))
445      (car list))
446     (t
447      (concat (car list)
448              separator
449              (join (cdr list) separator)))))
450
451 (defun join-trailing (list &optional (separator ""))
452   (if (null list)
453       ""
454       (concat (car list) separator (join-trailing (cdr list) separator))))
455
456 ;;; Like CONCAT, but prefix each line with four spaces.
457 (defun indent (&rest string)
458   (let ((input (join string)))
459     (let ((output "")
460           (index 0)
461           (size (length input)))
462       (when (plusp size)
463         (setq output "    "))
464       (while (< index size)
465         (setq output
466               (concat output
467                       (if (and (char= (char input index) #\newline)
468                                (< index (1- size))
469                                (not (char= (char input (1+ index)) #\newline)))
470                           (concat (string #\newline) "    ")
471                           (subseq input index (1+ index)))))
472         (incf index))
473       output)))
474
475 (defun integer-to-string (x)
476   (cond
477     ((zerop x)
478      "0")
479     ((minusp x)
480      (concat "-" (integer-to-string (- 0 x))))
481     (t
482      (let ((digits nil))
483        (while (not (zerop x))
484          (push (mod x 10) digits)
485          (setq x (truncate x 10)))
486        (join (mapcar (lambda (d) (string (char "0123456789" d)))
487                      digits))))))
488
489 ;;; Printer
490
491 #+ecmalisp
492 (progn
493   (defun print-to-string (form)
494     (cond
495       ((symbolp form) (symbol-name form))
496       ((integerp form) (integer-to-string form))
497       ((stringp form) (concat "\"" (escape-string form) "\""))
498       ((functionp form)
499        (let ((name (get form "fname")))
500          (if name
501              (concat "#<FUNCTION " name ">")
502              (concat "#<FUNCTION>"))))
503       ((listp form)
504        (concat "("
505                (join-trailing (mapcar #'print-to-string (butlast form)) " ")
506                (let ((last (last form)))
507                  (if (null (cdr last))
508                      (print-to-string (car last))
509                      (concat (print-to-string (car last)) " . " (print-to-string (cdr last)))))
510                ")"))))
511
512   (defun write-line (x)
513     (write-string x)
514     (write-string *newline*)
515     x)
516
517   (defun print (x)
518     (write-line (print-to-string x))
519     x))
520
521
522 ;;;; Reader
523
524 ;;; The Lisp reader, parse strings and return Lisp objects. The main
525 ;;; entry points are `ls-read' and `ls-read-from-string'.
526
527 (defun make-string-stream (string)
528   (cons string 0))
529
530 (defun %peek-char (stream)
531   (and (< (cdr stream) (length (car stream)))
532        (char (car stream) (cdr stream))))
533
534 (defun %read-char (stream)
535   (and (< (cdr stream) (length (car stream)))
536        (prog1 (char (car stream) (cdr stream))
537          (setcdr stream (1+ (cdr stream))))))
538
539 (defun whitespacep (ch)
540   (or (char= ch #\space) (char= ch #\newline) (char= ch #\tab)))
541
542 (defun skip-whitespaces (stream)
543   (let (ch)
544     (setq ch (%peek-char stream))
545     (while (and ch (whitespacep ch))
546       (%read-char stream)
547       (setq ch (%peek-char stream)))))
548
549 (defun terminalp (ch)
550   (or (null ch) (whitespacep ch) (char= #\) ch) (char= #\( ch)))
551
552 (defun read-until (stream func)
553   (let ((string "")
554         (ch))
555     (setq ch (%peek-char stream))
556     (while (and ch (not (funcall func ch)))
557       (setq string (concat string (string ch)))
558       (%read-char stream)
559       (setq ch (%peek-char stream)))
560     string))
561
562 (defun skip-whitespaces-and-comments (stream)
563   (let (ch)
564     (skip-whitespaces stream)
565     (setq ch (%peek-char stream))
566     (while (and ch (char= ch #\;))
567       (read-until stream (lambda (x) (char= x #\newline)))
568       (skip-whitespaces stream)
569       (setq ch (%peek-char stream)))))
570
571 (defun %read-list (stream)
572   (skip-whitespaces-and-comments stream)
573   (let ((ch (%peek-char stream)))
574     (cond
575       ((null ch)
576        (error "Unspected EOF"))
577       ((char= ch #\))
578        (%read-char stream)
579        nil)
580       ((char= ch #\.)
581        (%read-char stream)
582        (prog1 (ls-read stream)
583          (skip-whitespaces-and-comments stream)
584          (unless (char= (%read-char stream) #\))
585            (error "')' was expected."))))
586       (t
587        (cons (ls-read stream) (%read-list stream))))))
588
589 (defun read-string (stream)
590   (let ((string "")
591         (ch nil))
592     (setq ch (%read-char stream))
593     (while (not (eql ch #\"))
594       (when (null ch)
595         (error "Unexpected EOF"))
596       (when (eql ch #\\)
597         (setq ch (%read-char stream)))
598       (setq string (concat string (string ch)))
599       (setq ch (%read-char stream)))
600     string))
601
602 (defun read-sharp (stream)
603   (%read-char stream)
604   (ecase (%read-char stream)
605     (#\'
606      (list 'function (ls-read stream)))
607     (#\\
608      (let ((cname
609             (concat (string (%read-char stream))
610                     (read-until stream #'terminalp))))
611        (cond
612          ((string= cname "space") (char-code #\space))
613          ((string= cname "tab") (char-code #\tab))
614          ((string= cname "newline") (char-code #\newline))
615          (t (char-code (char cname 0))))))
616     (#\+
617      (let ((feature (read-until stream #'terminalp)))
618        (cond
619          ((string= feature "common-lisp")
620           (ls-read stream)              ;ignore
621           (ls-read stream))
622          ((string= feature "ecmalisp")
623           (ls-read stream))
624          (t
625           (error "Unknown reader form.")))))))
626
627 (defvar *eof* (make-symbol "EOF"))
628 (defun ls-read (stream)
629   (skip-whitespaces-and-comments stream)
630   (let ((ch (%peek-char stream)))
631     (cond
632       ((null ch)
633        *eof*)
634       ((char= ch #\()
635        (%read-char stream)
636        (%read-list stream))
637       ((char= ch #\')
638        (%read-char stream)
639        (list 'quote (ls-read stream)))
640       ((char= ch #\`)
641        (%read-char stream)
642        (list 'backquote (ls-read stream)))
643       ((char= ch #\")
644        (%read-char stream)
645        (read-string stream))
646       ((char= ch #\,)
647        (%read-char stream)
648        (if (eql (%peek-char stream) #\@)
649            (progn (%read-char stream) (list 'unquote-splicing (ls-read stream)))
650            (list 'unquote (ls-read stream))))
651       ((char= ch #\#)
652        (read-sharp stream))
653       (t
654        (let ((string (read-until stream #'terminalp)))
655          (if (every #'digit-char-p string)
656              (parse-integer string)
657              (intern (string-upcase string))))))))
658
659 (defun ls-read-from-string (string)
660   (ls-read (make-string-stream string)))
661
662
663 ;;;; Compiler
664
665 ;;; Translate the Lisp code to Javascript. It will compile the special
666 ;;; forms. Some primitive functions are compiled as special forms
667 ;;; too. The respective real functions are defined in the target (see
668 ;;; the beginning of this file) as well as some primitive functions.
669
670 (defvar *compilation-unit-checks* '())
671
672 (defun make-binding (name type js declared)
673   (list name type js declared))
674
675 (defun binding-name (b) (first b))
676 (defun binding-type (b) (second b))
677 (defun binding-translation (b) (third b))
678 (defun binding-declared (b)
679   (and b (fourth b)))
680 (defun mark-binding-as-declared (b)
681   (setcar (cdddr b) t))
682
683 (defun make-lexenv ()
684   (list nil nil nil))
685
686 (defun copy-lexenv (lexenv)
687   (copy-list lexenv))
688
689 (defun push-to-lexenv (binding lexenv namespace)
690   (ecase namespace
691     (variable
692      (setcar lexenv (cons binding (car lexenv))))
693     (function
694      (setcar (cdr lexenv) (cons binding (cadr lexenv))))
695     (block
696      (setcar (cddr lexenv) (cons binding (caddr lexenv))))))
697
698 (defun extend-lexenv (binding lexenv namespace)
699   (let ((env (copy-lexenv lexenv)))
700     (push-to-lexenv binding env namespace)
701     env))
702
703 (defun lookup-in-lexenv (name lexenv namespace)
704   (assoc name (ecase namespace
705                 (variable (first lexenv))
706                 (function (second lexenv))
707                 (block (third lexenv)))))
708
709 (defvar *environment* (make-lexenv))
710
711 (defun clear-undeclared-global-bindings ()
712   (let ((variables (first *environment*))
713         (functions (second *environment*)))
714     (setq *environment* (list variables functions (third *environment*)))))
715
716
717 (defvar *variable-counter* 0)
718 (defun gvarname (symbol)
719   (concat "v" (integer-to-string (incf *variable-counter*))))
720
721 (defun lookup-variable (symbol env)
722   (or (lookup-in-lexenv symbol env 'variable)
723       (lookup-in-lexenv symbol *environment* 'variable)
724       (let ((name (symbol-name symbol))
725             (binding (make-binding symbol 'variable (gvarname symbol) nil)))
726         (push-to-lexenv binding *environment* 'variable)
727         (push (lambda ()
728                 (unless (lookup-in-lexenv symbol *environment* 'variable)
729                   (error (concat "Undefined variable `" name "'"))))
730               *compilation-unit-checks*)
731         binding)))
732
733 (defun lookup-variable-translation (symbol env)
734   (binding-translation (lookup-variable symbol env)))
735
736 (defun extend-local-env (args env)
737   (let ((new (copy-lexenv env)))
738     (dolist (symbol args new)
739       (let ((b (make-binding symbol 'variable (gvarname symbol) t)))
740         (push-to-lexenv b new 'variable)))))
741
742 (defvar *function-counter* 0)
743 (defun lookup-function (symbol env)
744   (or (lookup-in-lexenv symbol env 'function)
745       (lookup-in-lexenv symbol *environment* 'function)
746       (let ((name (symbol-name symbol))
747             (binding
748              (make-binding symbol
749                            'function
750                            (concat "f" (integer-to-string (incf *function-counter*)))
751                            nil)))
752         (push-to-lexenv binding *environment* 'function)
753         (push (lambda ()
754                 (unless (binding-declared (lookup-in-lexenv symbol *environment* 'function))
755                   (error (concat "Undefined function `" name "'"))))
756               *compilation-unit-checks*)
757         binding)))
758
759 (defun lookup-function-translation (symbol env)
760   (binding-translation (lookup-function symbol env)))
761
762 (defvar *toplevel-compilations* nil)
763
764 (defun %compile-defvar (name)
765   (let ((b (lookup-variable name *environment*)))
766     (mark-binding-as-declared b)
767     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
768
769 (defun %compile-defun (name)
770   (let ((b (lookup-function name *environment*)))
771     (mark-binding-as-declared b)
772     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
773
774 (defun %compile-defmacro (name lambda)
775   (push-to-lexenv (make-binding name 'macro lambda t) *environment* 'function))
776
777 (defvar *compilations* nil)
778
779 (defun ls-compile-block (sexps env)
780   (join-trailing
781    (remove-if (lambda (x)
782                 (or (null x)
783                     (and (stringp x)
784                          (zerop (length x)))))
785               (mapcar (lambda (x) (ls-compile x env))  sexps))
786    (concat ";" *newline*)))
787
788 (defmacro define-compilation (name args &body body)
789   ;; Creates a new primitive `name' with parameters args and
790   ;; @body. The body can access to the local environment through the
791   ;; variable ENV.
792   `(push (list ',name (lambda (env ,@args) ,@body))
793          *compilations*))
794
795 (define-compilation if (condition true false)
796   (concat "("
797           (ls-compile condition env) " !== " (ls-compile nil)
798           " ? "
799           (ls-compile true env)
800           " : "
801           (ls-compile false env)
802           ")"))
803
804
805 (defvar *lambda-list-keywords* '(&optional &rest))
806
807 (defun list-until-keyword (list)
808   (if (or (null list) (member (car list) *lambda-list-keywords*))
809       nil
810       (cons (car list) (list-until-keyword (cdr list)))))
811
812 (defun lambda-list-required-arguments (lambda-list)
813   (list-until-keyword lambda-list))
814
815 (defun lambda-list-optional-arguments-with-default (lambda-list)
816   (mapcar #'ensure-list (list-until-keyword (cdr (member '&optional lambda-list)))))
817
818 (defun lambda-list-optional-arguments (lambda-list)
819   (mapcar #'car (lambda-list-optional-arguments-with-default lambda-list)))
820
821 (defun lambda-list-rest-argument (lambda-list)
822   (let ((rest (list-until-keyword (cdr (member '&rest lambda-list)))))
823     (when (cdr rest)
824       (error "Bad lambda-list"))
825     (car rest)))
826
827 (define-compilation lambda (lambda-list &rest body)
828   (let ((required-arguments (lambda-list-required-arguments lambda-list))
829         (optional-arguments (lambda-list-optional-arguments lambda-list))
830         (rest-argument (lambda-list-rest-argument lambda-list)))
831     (let ((n-required-arguments (length required-arguments))
832           (n-optional-arguments (length optional-arguments))
833           (new-env (extend-local-env
834                     (append (ensure-list rest-argument)
835                             required-arguments
836                             optional-arguments)
837                     env)))
838       (concat "(function ("
839               (join (mapcar (lambda (x)
840                               (lookup-variable-translation x new-env))
841                             (append required-arguments optional-arguments))
842                     ",")
843               "){" *newline*
844               ;; Check number of arguments
845               (indent
846                (if required-arguments
847                    (concat "if (arguments.length < " (integer-to-string n-required-arguments)
848                            ") throw 'too few arguments';" *newline*)
849                    "")
850                (if (not rest-argument)
851                    (concat "if (arguments.length > "
852                            (integer-to-string (+ n-required-arguments n-optional-arguments))
853                            ") throw 'too many arguments';" *newline*)
854                    "")
855                ;; Optional arguments
856                (if optional-arguments
857                    (concat "switch(arguments.length){" *newline*
858                            (let ((optional-and-defaults
859                                   (lambda-list-optional-arguments-with-default lambda-list))
860                                  (cases nil)
861                                  (idx 0))
862                              (progn
863                                (while (< idx n-optional-arguments)
864                                  (let ((arg (nth idx optional-and-defaults)))
865                                    (push (concat "case "
866                                                  (integer-to-string (+ idx n-required-arguments)) ":" *newline*
867                                                  (lookup-variable-translation (car arg) new-env)
868                                                  "="
869                                                  (ls-compile (cadr arg) new-env)
870                                                  ";" *newline*)
871                                          cases)
872                                    (incf idx)))
873                                     (push (concat "default: break;" *newline*) cases)
874                                     (join (reverse cases))))
875                            "}" *newline*)
876                    "")
877                ;; &rest/&body argument
878                (if rest-argument
879                    (let ((js!rest (lookup-variable-translation rest-argument new-env)))
880                      (concat "var " js!rest "= " (ls-compile nil) ";" *newline*
881                              "for (var i = arguments.length-1; i>="
882                              (integer-to-string (+ n-required-arguments n-optional-arguments))
883                              "; i--)" *newline*
884                              (indent js!rest " = "
885                                      "{car: arguments[i], cdr: ") js!rest "};"
886                                      *newline*))
887                    "")
888                ;; Body
889                (concat (ls-compile-block (butlast body) new-env)
890                        "return " (ls-compile (car (last body)) new-env) ";")) *newline*
891               "})"))))
892
893 (define-compilation fsetq (var val)
894   (concat (lookup-function-translation var env)
895           " = "
896           (ls-compile val env)))
897
898 (define-compilation setq (var val)
899   (concat (lookup-variable-translation var env)
900           " = "
901            (ls-compile val env)))
902
903 ;;; Literals
904 (defun escape-string (string)
905   (let ((output "")
906         (index 0)
907         (size (length string)))
908     (while (< index size)
909       (let ((ch (char string index)))
910         (when (or (char= ch #\") (char= ch #\\))
911           (setq output (concat output "\\")))
912         (when (or (char= ch #\newline))
913           (setq output (concat output "\\"))
914           (setq ch #\n))
915         (setq output (concat output (string ch))))
916       (incf index))
917     output))
918
919 (defun literal->js (sexp)
920   (cond
921     ((integerp sexp) (integer-to-string sexp))
922     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
923     ((symbolp sexp) (ls-compile `(intern ,(escape-string (symbol-name sexp))) *environment*))
924     ((consp sexp) (concat "{car: "
925                           (literal->js (car sexp))
926                           ", cdr: "
927                           (literal->js (cdr sexp)) "}"))))
928
929 (defvar *literal-counter* 0)
930 (defun literal (form)
931   (let ((var (concat "l" (integer-to-string (incf *literal-counter*)))))
932     (push (concat "var " var " = " (literal->js form)) *toplevel-compilations*)
933     var))
934
935 (define-compilation quote (sexp)
936   (literal sexp))
937
938 (define-compilation %while (pred &rest body)
939   (concat "(function(){" *newline*
940           (indent "while(" (ls-compile pred env) " !== " (ls-compile nil) "){" *newline*
941                   (indent (ls-compile-block body env))
942                   "}"
943                   "return " (ls-compile nil) ";" *newline*)
944           "})()"))
945
946 (define-compilation function (x)
947   (cond
948     ((and (listp x) (eq (car x) 'lambda))
949      (ls-compile x env))
950     ((symbolp x)
951      (lookup-function-translation x env))))
952
953 (define-compilation eval-when-compile (&rest body)
954   (eval (cons 'progn body))
955   "")
956
957 (defmacro define-transformation (name args form)
958   `(define-compilation ,name ,args
959      (ls-compile ,form env)))
960
961 (define-compilation progn (&rest body)
962   (concat "(function(){" *newline*
963           (indent (ls-compile-block (butlast body) env)
964                   "return " (ls-compile (car (last body)) env) ";" *newline*)
965           "})()"))
966
967 (define-compilation let (bindings &rest body)
968   (let ((bindings (mapcar #'ensure-list bindings)))
969     (let ((variables (mapcar #'first bindings))
970           (values    (mapcar #'second bindings)))
971       (let ((new-env (extend-local-env variables env)))
972         (concat "(function("
973                 (join (mapcar (lambda (x)
974                                 (lookup-variable-translation x new-env))
975                               variables)
976                       ",")
977                 "){" *newline*
978                 (indent (ls-compile-block (butlast body) new-env)
979                         "return " (ls-compile (car (last body)) new-env)
980                         ";" *newline*)
981                 "})(" (join (mapcar (lambda (x) (ls-compile x env))
982                                     values)
983                             ",")
984                 ")")))))
985
986
987 (defvar *block-counter* 0)
988
989 (define-compilation block (name &rest body)
990   (let ((tr (integer-to-string (incf *block-counter*))))
991     (let ((b (make-binding name 'block tr t)))
992       (concat "(function(){" *newline*
993               (indent "try {" *newline*
994                       (indent "return " (ls-compile `(progn ,@body)
995                                                     (extend-lexenv b env 'block))) ";" *newline*
996                       "}" *newline*
997                       "catch (cf){" *newline*
998                       "    if (cf.type == 'block' && cf.id == " tr ")" *newline*
999                       "        return cf.value;" *newline*
1000                       "    else" *newline*
1001                       "        throw cf;" *newline*
1002                       "}" *newline*)
1003               "})()"))))
1004
1005 (define-compilation return-from (name &optional value)
1006   (let ((b (lookup-in-lexenv name env 'block)))
1007     (if b
1008         (concat "(function(){ throw ({"
1009                 "type: 'block', "
1010                 "id: " (binding-translation b) ", "
1011                 "value: " (ls-compile value env) ", "
1012                 "message: 'Return from unknown block " (symbol-name name) ".'"
1013                 "})})()")
1014         (error (concat "Unknown block `" (symbol-name name) "'.")))))
1015
1016 ;;; A little backquote implementation without optimizations of any
1017 ;;; kind for ecmalisp.
1018 (defun backquote-expand-1 (form)
1019   (cond
1020     ((symbolp form)
1021      (list 'quote form))
1022     ((atom form)
1023      form)
1024     ((eq (car form) 'unquote)
1025      (car form))
1026     ((eq (car form) 'backquote)
1027      (backquote-expand-1 (backquote-expand-1 (cadr form))))
1028     (t
1029      (cons 'append
1030            (mapcar (lambda (s)
1031                      (cond
1032                        ((and (listp s) (eq (car s) 'unquote))
1033                         (list 'list (cadr s)))
1034                        ((and (listp s) (eq (car s) 'unquote-splicing))
1035                         (cadr s))
1036                        (t
1037                         (list 'list (backquote-expand-1 s)))))
1038                    form)))))
1039
1040 (defun backquote-expand (form)
1041   (if (and (listp form) (eq (car form) 'backquote))
1042       (backquote-expand-1 (cadr form))
1043       form))
1044
1045 (defmacro backquote (form)
1046   (backquote-expand-1 form))
1047
1048 (define-transformation backquote (form)
1049   (backquote-expand-1 form))
1050
1051 ;;; Primitives
1052
1053 (defmacro define-builtin (name args &body body)
1054   `(define-compilation ,name ,args
1055      (let ,(mapcar (lambda (arg) `(,arg (ls-compile ,arg env))) args)
1056        ,@body)))
1057
1058 (defun compile-bool (x)
1059   (concat "(" x "?" (ls-compile t) ": " (ls-compile nil) ")"))
1060
1061 ;;; DECLS is a list of (JSVARNAME TYPE LISPFORM) declarations.
1062 (defmacro type-check (decls &body body)
1063   `(concat "(function(){" *newline*
1064            (indent ,@(mapcar (lambda (decl)
1065                                `(concat "var " ,(first decl) " = " ,(third decl) ";" *newline*))
1066                              decls)
1067
1068                    ,@(mapcar (lambda (decl)
1069                                `(concat "if (typeof " ,(first decl) " != '" ,(second decl) "')" *newline*
1070                                         (indent "throw 'The value ' + "
1071                                                 ,(first decl)
1072                                                 " + ' is not a type "
1073                                                 ,(second decl)
1074                                                 ".';"
1075                                                 *newline*)))
1076                              decls)
1077                    (concat "return " (progn ,@body) ";" *newline*))
1078            "})()"))
1079
1080 (defun num-op-num (x op y)
1081   (type-check (("x" "number" x) ("y" "number" y))
1082     (concat "x" op "y")))
1083
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 (define-builtin / (x y) (num-op-num x "/" y))
1088
1089 (define-builtin mod (x y) (num-op-num x "%" y))
1090
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 (define-builtin >= (x y) (compile-bool (num-op-num x ">=" y)))
1096
1097 (define-builtin numberp (x)
1098   (compile-bool (concat "(typeof (" x ") == \"number\")")))
1099
1100 (define-builtin floor (x)
1101   (type-check (("x" "number" x))
1102     "Math.floor(x)"))
1103
1104 (define-builtin cons (x y) (concat "({car: " x ", cdr: " y "})"))
1105 (define-builtin consp (x)
1106   (compile-bool
1107    (concat "(function(){" *newline*
1108            (indent "var tmp = " x ";" *newline*
1109                    "return (typeof tmp == 'object' && 'car' in tmp);" *newline*)
1110            "})()")))
1111
1112 (define-builtin car (x)
1113   (concat "(function(){" *newline*
1114           (indent "var tmp = " x ";" *newline*
1115                   "return tmp === " (ls-compile nil)
1116                   "? " (ls-compile nil)
1117                   ": tmp.car;" *newline*)
1118           "})()"))
1119
1120 (define-builtin cdr (x)
1121   (concat "(function(){" *newline*
1122           (indent "var tmp = " x ";" *newline*
1123                   "return tmp === " (ls-compile nil) "? "
1124                   (ls-compile nil)
1125                   ": tmp.cdr;" *newline*)
1126           "})()"))
1127
1128 (define-builtin setcar (x new)
1129   (type-check (("x" "object" x))
1130     (concat "(x.car = " new ")")))
1131
1132 (define-builtin setcdr (x new)
1133   (type-check (("x" "object" x))
1134     (concat "(x.cdr = " new ")")))
1135
1136 (define-builtin symbolp (x)
1137   (compile-bool
1138    (concat "(function(){" *newline*
1139            (indent "var tmp = " x ";" *newline*
1140                    "return (typeof tmp == 'object' && 'name' in tmp);" *newline*)
1141            "})()")))
1142
1143 (define-builtin make-symbol (name)
1144   (type-check (("name" "string" name))
1145     "({name: name})"))
1146
1147 (define-builtin symbol-name (x)
1148   (concat "(" x ").name"))
1149
1150 (define-builtin eq    (x y) (compile-bool (concat "(" x " === " y ")")))
1151 (define-builtin equal (x y) (compile-bool (concat "(" x  " == " y ")")))
1152
1153 (define-builtin string (x)
1154   (type-check (("x" "number" x))
1155     "String.fromCharCode(x)"))
1156
1157 (define-builtin stringp (x)
1158   (compile-bool (concat "(typeof(" x ") == \"string\")")))
1159
1160 (define-builtin string-upcase (x)
1161   (type-check (("x" "string" x))
1162     "x.toUpperCase()"))
1163
1164 (define-builtin string-length (x)
1165   (type-check (("x" "string" x))
1166     "x.length"))
1167
1168 (define-compilation slice (string a &optional b)
1169   (concat "(function(){" *newline*
1170           (indent "var str = " (ls-compile string env) ";" *newline*
1171                   "var a = " (ls-compile a env) ";" *newline*
1172                   "var b;" *newline*
1173                   (if b
1174                       (concat "b = " (ls-compile b env) ";" *newline*)
1175                       "")
1176                   "return str.slice(a,b);" *newline*)
1177           "})()"))
1178
1179 (define-builtin char (string index)
1180   (type-check (("string" "string" string)
1181                ("index" "number" index))
1182     "string.charCodeAt(index)"))
1183
1184 (define-builtin concat-two (string1 string2)
1185   (type-check (("string1" "string" string1)
1186                ("string2" "string" string2))
1187     "string1.concat(string2)"))
1188
1189 (define-compilation funcall (func &rest args)
1190   (concat "(" (ls-compile func env) ")("
1191           (join (mapcar (lambda (x)
1192                           (ls-compile x env))
1193                         args)
1194                 ", ")
1195           ")"))
1196
1197 (define-compilation apply (func &rest args)
1198   (if (null args)
1199       (concat "(" (ls-compile func env) ")()")
1200       (let ((args (butlast args))
1201             (last (car (last args))))
1202         (concat "(function(){" *newline*
1203                 (indent "var f = " (ls-compile func env) ";" *newline*
1204                         "var args = [" (join (mapcar (lambda (x)
1205                                                        (ls-compile x env))
1206                                                      args)
1207                                              ", ")
1208                         "];" *newline*
1209                         "var tail = (" (ls-compile last env) ");" *newline*
1210                         (indent "while (tail != " (ls-compile nil) "){" *newline*
1211                                 "    args.push(tail.car);" *newline*
1212                                 "    tail = tail.cdr;" *newline*
1213                                 "}" *newline*
1214                                 "return f.apply(this, args);" *newline*)
1215                         "})()")))))
1216
1217 (define-builtin js-eval (string)
1218   (type-check (("string" "string" string))
1219     "eval.apply(window, [string])"))
1220
1221 (define-builtin error (string)
1222   (concat "(function (){ throw " string "; })()"))
1223
1224 (define-builtin new () "{}")
1225
1226 (define-builtin get (object key)
1227   (concat "(function(){" *newline*
1228           (indent "var tmp = " "(" object ")[" key "];" *newline*
1229                   "return tmp == undefined? " (ls-compile nil) ": tmp ;" *newline*)
1230           "})()"))
1231
1232 (define-builtin set (object key value)
1233   (concat "((" object ")[" key "] = " value ")"))
1234
1235 (define-builtin in (key object)
1236   (compile-bool (concat "((" key ") in (" object "))")))
1237
1238 (define-builtin functionp (x)
1239   (compile-bool (concat "(typeof " x " == 'function')")))
1240
1241 (define-builtin write-string (x)
1242   (type-check (("x" "string" x))
1243     "lisp.write(x)"))
1244
1245 (defun macrop (x)
1246   (and (symbolp x) (eq (binding-type (lookup-function x *environment*)) 'macro)))
1247
1248 (defun ls-macroexpand-1 (form env)
1249   (if (macrop (car form))
1250       (let ((binding (lookup-function (car form) *environment*)))
1251         (if (eq (binding-type binding) 'macro)
1252             (apply (eval (binding-translation binding)) (cdr form))
1253             form))
1254       form))
1255
1256 (defun compile-funcall (function args env)
1257   (cond
1258     ((symbolp function)
1259      (concat (lookup-function-translation function env)
1260              "("
1261              (join (mapcar (lambda (x) (ls-compile x env)) args)
1262                    ", ")
1263              ")"))
1264     ((and (listp function) (eq (car function) 'lambda))
1265      (concat "(" (ls-compile function env) ")("
1266              (join (mapcar (lambda (x) (ls-compile x env)) args)
1267                    ", ")
1268              ")"))
1269     (t
1270      (error (concat "Invalid function designator " (symbol-name function))))))
1271
1272 (defun ls-compile (sexp &optional (env (make-lexenv)))
1273   (cond
1274     ((symbolp sexp) (lookup-variable-translation sexp env))
1275     ((integerp sexp) (integer-to-string sexp))
1276     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
1277     ((listp sexp)
1278      (if (assoc (car sexp) *compilations*)
1279          (let ((comp (second (assoc (car sexp) *compilations*))))
1280            (apply comp env (cdr sexp)))
1281          (if (macrop (car sexp))
1282              (ls-compile (ls-macroexpand-1 sexp env) env)
1283              (compile-funcall (car sexp) (cdr sexp) env))))))
1284
1285 (defun ls-compile-toplevel (sexp)
1286   (setq *toplevel-compilations* nil)
1287   (let ((code (ls-compile sexp)))
1288     (prog1
1289         (concat (join (mapcar (lambda (x) (concat x ";" *newline*))
1290                               *toplevel-compilations*))
1291                 code)
1292       (setq *toplevel-compilations* nil))))
1293
1294
1295 ;;; Once we have the compiler, we define the runtime environment and
1296 ;;; interactive development (eval), which works calling the compiler
1297 ;;; and evaluating the Javascript result globally.
1298
1299 #+ecmalisp
1300 (progn
1301   (defmacro with-compilation-unit (&body body)
1302     `(prog1
1303          (progn
1304            (setq *compilation-unit-checks* nil)
1305            (clear-undeclared-global-bindings)
1306            ,@body)
1307        (dolist (check *compilation-unit-checks*)
1308          (funcall check))))
1309
1310   (defun eval (x)
1311     (let ((code
1312            (with-compilation-unit
1313                (ls-compile-toplevel x))))
1314       (js-eval code)))
1315
1316   ;; Set the initial global environment to be equal to the host global
1317   ;; environment at this point of the compilation.
1318   (eval-when-compile
1319     (let ((tmp (ls-compile
1320                 `(progn
1321                    (setq *environment* ',*environment*)
1322                    (setq *variable-counter* ',*variable-counter*)
1323                    (setq *function-counter* ',*function-counter*)
1324                    (setq *literal-counter* ',*literal-counter*)
1325                    (setq *gensym-counter* ',*gensym-counter*)
1326                    (setq *block-counter* ',*block-counter*)))))
1327       (setq *toplevel-compilations*
1328             (append *toplevel-compilations* (list tmp)))))
1329
1330   (js-eval
1331    (concat "var lisp = {};"
1332            "lisp.read = " (lookup-function-translation 'ls-read-from-string nil) ";" *newline*
1333            "lisp.print = " (lookup-function-translation 'print-to-string nil) ";" *newline*
1334            "lisp.eval = " (lookup-function-translation 'eval nil) ";" *newline*
1335            "lisp.compile = " (lookup-function-translation 'ls-compile-toplevel nil) ";" *newline*
1336            "lisp.evalString = function(str){" *newline*
1337            "   return lisp.eval(lisp.read(str));" *newline*
1338            "}" *newline*
1339            "lisp.compileString = function(str){" *newline*
1340            "   return lisp.compile(lisp.read(str));" *newline*
1341            "}" *newline*)))
1342
1343
1344 ;;; Finally, we provide a couple of functions to easily bootstrap
1345 ;;; this. It just calls the compiler with this file as input.
1346
1347 #+common-lisp
1348 (progn
1349   (defun read-whole-file (filename)
1350     (with-open-file (in filename)
1351       (let ((seq (make-array (file-length in) :element-type 'character)))
1352         (read-sequence seq in)
1353         seq)))
1354
1355   (defun ls-compile-file (filename output)
1356     (setq *compilation-unit-checks* nil)
1357     (with-open-file (out output :direction :output :if-exists :supersede)
1358       (let* ((source (read-whole-file filename))
1359              (in (make-string-stream source)))
1360         (loop
1361            for x = (ls-read in)
1362            until (eq x *eof*)
1363            for compilation = (ls-compile-toplevel x)
1364            when (plusp (length compilation))
1365            do (write-line (concat compilation "; ") out))
1366         (dolist (check *compilation-unit-checks*)
1367           (funcall check))
1368         (setq *compilation-unit-checks* nil))))
1369
1370   (defun bootstrap ()
1371     (setq *environment* (make-lexenv))
1372     (setq *variable-counter* 0
1373           *gensym-counter* 0
1374           *function-counter* 0
1375           *literal-counter* 0
1376           *block-counter* 0)
1377     (ls-compile-file "ecmalisp.lisp" "ecmalisp.js")))