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