Call JOIN without a separator in some callers
[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   (cond
411     ((zerop x)
412      "0")
413     ((minusp x)
414      (concat "-" (integer-to-string (- 0 x))))
415     (t
416      (let ((digits nil))
417        (while (not (zerop x))
418          (push (mod x 10) digits)
419          (setq x (truncate x 10)))
420        (join (mapcar (lambda (d) (string (char "0123456789" d)))
421                      digits))))))
422
423 (defun print-to-string (form)
424   (cond
425     ((symbolp form) (symbol-name form))
426     ((integerp form) (integer-to-string form))
427     ((stringp form) (concat "\"" (escape-string form) "\""))
428     ((functionp form) (concat "#<FUNCTION>"))
429     ((listp form)
430      (concat "("
431              (join (mapcar #'print-to-string form)
432                    " ")
433              ")"))))
434
435 ;;;; Reader
436
437 ;;; The Lisp reader, parse strings and return Lisp objects. The main
438 ;;; entry points are `ls-read' and `ls-read-from-string'.
439
440 (defun make-string-stream (string)
441   (cons string 0))
442
443 (defun %peek-char (stream)
444   (and (< (cdr stream) (length (car stream)))
445        (char (car stream) (cdr stream))))
446
447 (defun %read-char (stream)
448   (and (< (cdr stream) (length (car stream)))
449        (prog1 (char (car stream) (cdr stream))
450          (setcdr stream (1+ (cdr stream))))))
451
452 (defun whitespacep (ch)
453   (or (char= ch #\space) (char= ch #\newline) (char= ch #\tab)))
454
455 (defun skip-whitespaces (stream)
456   (let (ch)
457     (setq ch (%peek-char stream))
458     (while (and ch (whitespacep ch))
459       (%read-char stream)
460       (setq ch (%peek-char stream)))))
461
462 (defun terminalp (ch)
463   (or (null ch) (whitespacep ch) (char= #\) ch) (char= #\( ch)))
464
465 (defun read-until (stream func)
466   (let ((string "")
467         (ch))
468     (setq ch (%peek-char stream))
469     (while (not (funcall func ch))
470       (setq string (concat string (string ch)))
471       (%read-char stream)
472       (setq ch (%peek-char stream)))
473     string))
474
475 (defun skip-whitespaces-and-comments (stream)
476   (let (ch)
477     (skip-whitespaces stream)
478     (setq ch (%peek-char stream))
479     (while (and ch (char= ch #\;))
480       (read-until stream (lambda (x) (char= x #\newline)))
481       (skip-whitespaces stream)
482       (setq ch (%peek-char stream)))))
483
484 (defun %read-list (stream)
485   (skip-whitespaces-and-comments stream)
486   (let ((ch (%peek-char stream)))
487     (cond
488       ((null ch)
489        (error "Unspected EOF"))
490       ((char= ch #\))
491        (%read-char stream)
492        nil)
493       ((char= ch #\.)
494        (%read-char stream)
495        (prog1 (ls-read stream)
496          (skip-whitespaces-and-comments stream)
497          (unless (char= (%read-char stream) #\))
498            (error "')' was expected."))))
499       (t
500        (cons (ls-read stream) (%read-list stream))))))
501
502 (defun read-string (stream)
503   (let ((string "")
504         (ch nil))
505     (setq ch (%read-char stream))
506     (while (not (eql ch #\"))
507       (when (null ch)
508         (error "Unexpected EOF"))
509       (when (eql ch #\\)
510         (setq ch (%read-char stream)))
511       (setq string (concat string (string ch)))
512       (setq ch (%read-char stream)))
513     string))
514
515 (defun read-sharp (stream)
516   (%read-char stream)
517   (ecase (%read-char stream)
518     (#\'
519      (list 'function (ls-read stream)))
520     (#\\
521      (let ((cname
522             (concat (string (%read-char stream))
523                     (read-until stream #'terminalp))))
524        (cond
525          ((string= cname "space") (char-code #\space))
526          ((string= cname "tab") (char-code #\tab))
527          ((string= cname "newline") (char-code #\newline))
528          (t (char-code (char cname 0))))))
529     (#\+
530      (let ((feature (read-until stream #'terminalp)))
531        (cond
532          ((string= feature "common-lisp")
533           (ls-read stream)              ;ignore
534           (ls-read stream))
535          ((string= feature "lispstrack")
536           (ls-read stream))
537          (t
538           (error "Unknown reader form.")))))))
539
540 (defvar *eof* (make-symbol "EOF"))
541 (defun ls-read (stream)
542   (skip-whitespaces-and-comments stream)
543   (let ((ch (%peek-char stream)))
544     (cond
545       ((null ch)
546        *eof*)
547       ((char= ch #\()
548        (%read-char stream)
549        (%read-list stream))
550       ((char= ch #\')
551        (%read-char stream)
552        (list 'quote (ls-read stream)))
553       ((char= ch #\`)
554        (%read-char stream)
555        (list 'backquote (ls-read stream)))
556       ((char= ch #\")
557        (%read-char stream)
558        (read-string stream))
559       ((char= ch #\,)
560        (%read-char stream)
561        (if (eql (%peek-char stream) #\@)
562            (progn (%read-char stream) (list 'unquote-splicing (ls-read stream)))
563            (list 'unquote (ls-read stream))))
564       ((char= ch #\#)
565        (read-sharp stream))
566       (t
567        (let ((string (read-until stream #'terminalp)))
568          (if (every #'digit-char-p string)
569              (parse-integer string)
570              (intern (string-upcase string))))))))
571
572 (defun ls-read-from-string (string)
573   (ls-read (make-string-stream string)))
574
575
576 ;;;; Compiler
577
578 ;;; Translate the Lisp code to Javascript. It will compile the special
579 ;;; forms. Some primitive functions are compiled as special forms
580 ;;; too. The respective real functions are defined in the target (see
581 ;;; the beginning of this file) as well as some primitive functions.
582
583 (defvar *compilation-unit-checks* '())
584
585 (defvar *env* '())
586 (defvar *fenv* '())
587
588 (defun make-binding (name type js declared)
589   (list name type js declared))
590
591 (defun binding-name (b) (first b))
592 (defun binding-type (b) (second b))
593 (defun binding-translation (b) (third b))
594 (defun binding-declared (b)
595   (and b (fourth b)))
596 (defun mark-binding-as-declared (b)
597   (setcar (cdddr b) t))
598
599 (defvar *variable-counter* 0)
600 (defun gvarname (symbol)
601   (concat "v" (integer-to-string (incf *variable-counter*))))
602
603 (defun lookup-variable (symbol env)
604   (or (assoc symbol env)
605       (assoc symbol *env*)
606       (let ((name (symbol-name symbol))
607             (binding (make-binding symbol 'variable (gvarname symbol) nil)))
608         (push binding *env*)
609         (push (lambda ()
610                 (unless (binding-declared (assoc symbol *env*))
611                   (error (concat "Undefined variable `" name "'"))))
612               *compilation-unit-checks*)
613         binding)))
614
615 (defun lookup-variable-translation (symbol env)
616   (binding-translation (lookup-variable symbol env)))
617
618 (defun extend-local-env (args env)
619   (append (mapcar (lambda (symbol)
620                     (make-binding symbol 'variable (gvarname symbol) t))
621                   args)
622           env))
623
624 (defvar *function-counter* 0)
625 (defun lookup-function (symbol env)
626   (or (assoc symbol env)
627       (assoc symbol *fenv*)
628       (let ((name (symbol-name symbol))
629             (binding
630              (make-binding symbol
631                            'function
632                            (concat "f" (integer-to-string (incf *function-counter*)))
633                            nil)))
634         (push binding *fenv*)
635         (push (lambda ()
636                 (unless (binding-declared (assoc symbol *fenv*))
637                   (error (concat "Undefined function `" name "'"))))
638               *compilation-unit-checks*)
639         binding)))
640
641 (defun lookup-function-translation (symbol env)
642   (binding-translation (lookup-function symbol env)))
643
644 (defvar *toplevel-compilations* nil)
645
646 (defun %compile-defvar (name)
647   (let ((b (lookup-variable name *env*)))
648     (mark-binding-as-declared b)
649     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
650
651 (defun %compile-defun (name)
652   (let ((b (lookup-function name *env*)))
653     (mark-binding-as-declared b)
654     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
655
656 (defun %compile-defmacro (name lambda)
657   (push (make-binding name 'macro lambda t) *fenv*))
658
659 (defvar *compilations* nil)
660
661 (defun ls-compile-block (sexps env fenv)
662   (join-trailing
663    (remove-if (lambda (x)
664                 (or (null x)
665                     (and (stringp x)
666                          (zerop (length x)))))
667               (mapcar (lambda (x) (ls-compile x env fenv))  sexps))
668    (concat ";" *newline*)))
669
670 (defmacro define-compilation (name args &rest body)
671   ;; Creates a new primitive `name' with parameters args and
672   ;; @body. The body can access to the local environment through the
673   ;; variable ENV.
674   `(push (list ',name (lambda (env fenv ,@args) ,@body))
675          *compilations*))
676
677 (define-compilation if (condition true false)
678   (concat "("
679           (ls-compile condition env fenv) " !== " (ls-compile nil nil nil)
680           " ? "
681           (ls-compile true env fenv)
682           " : "
683           (ls-compile false env fenv)
684           ")"))
685
686
687 (defvar *lambda-list-keywords* '(&optional &rest))
688
689 (defun list-until-keyword (list)
690   (if (or (null list) (member (car list) *lambda-list-keywords*))
691       nil
692       (cons (car list) (list-until-keyword (cdr list)))))
693
694 (defun lambda-list-required-arguments (lambda-list)
695   (list-until-keyword lambda-list))
696
697 (defun lambda-list-optional-arguments-with-default (lambda-list)
698   (mapcar #'ensure-list (list-until-keyword (cdr (member '&optional lambda-list)))))
699
700 (defun lambda-list-optional-arguments (lambda-list)
701   (mapcar #'car (lambda-list-optional-arguments-with-default lambda-list)))
702
703 (defun lambda-list-rest-argument (lambda-list)
704   (let ((rest (list-until-keyword (cdr (member '&rest lambda-list)))))
705     (when (cdr rest)
706       (error "Bad lambda-list"))
707     (car rest)))
708
709 (define-compilation lambda (lambda-list &rest body)
710   (let ((required-arguments (lambda-list-required-arguments lambda-list))
711         (optional-arguments (lambda-list-optional-arguments lambda-list))
712         (rest-argument (lambda-list-rest-argument lambda-list)))
713     (let ((n-required-arguments (length required-arguments))
714           (n-optional-arguments (length optional-arguments))
715           (new-env (extend-local-env
716                     (append (ensure-list rest-argument)
717                             required-arguments
718                             optional-arguments)
719                     env)))
720       (concat "(function ("
721               (join (mapcar (lambda (x)
722                               (lookup-variable-translation x new-env))
723                             (append required-arguments optional-arguments))
724                     ",")
725               "){" *newline*
726               ;; Check number of arguments
727               (if required-arguments
728                   (concat "if (arguments.length < " (integer-to-string n-required-arguments)
729                           ") throw 'too few arguments';" *newline*)
730                   "")
731               (if (not rest-argument)
732                   (concat "if (arguments.length > "
733                           (integer-to-string (+ n-required-arguments n-optional-arguments))
734                           ") throw 'too many arguments';" *newline*)
735                   "")
736               ;; Optional arguments
737               (if optional-arguments
738                   (concat "switch(arguments.length){" *newline*
739                           (let ((optional-and-defaults
740                                  (lambda-list-optional-arguments-with-default lambda-list))
741                                 (cases nil)
742                                 (idx 0))
743                             (progn (while (< idx n-optional-arguments)
744                                      (let ((arg (nth idx optional-and-defaults)))
745                                        (push (concat "case "
746                                                      (integer-to-string (+ idx n-required-arguments)) ":" *newline*
747                                                      (lookup-variable-translation (car arg) new-env)
748                                                      "="
749                                                      (ls-compile (cadr arg) new-env fenv)
750                                                      ";" *newline*)
751                                              cases)
752                                        (incf idx)))
753                                    (push (concat "default: break;" *newline*) cases)
754                                    (join (reverse cases))))
755                           "}" *newline*)
756                   "")
757               ;; &rest argument
758               (if rest-argument
759                   (let ((js!rest (lookup-variable-translation rest-argument new-env)))
760                     (concat "var " js!rest "= " (ls-compile nil env fenv) ";" *newline*
761                             "for (var i = arguments.length-1; i>="
762                             (integer-to-string (+ n-required-arguments n-optional-arguments))
763                             "; i--)" *newline*
764                             js!rest " = "
765                             "{car: arguments[i], cdr: " js!rest "};"
766                             *newline*))
767                   "")
768               ;; Body
769               (concat (ls-compile-block (butlast body) new-env fenv)
770                       "return " (ls-compile (car (last body)) new-env fenv) ";")
771               *newline* "})"))))
772
773 (define-compilation fsetq (var val)
774   (concat (lookup-function-translation var fenv)
775           " = "
776           (ls-compile val env fenv)))
777
778 (define-compilation setq (var val)
779   (concat (lookup-variable-translation var env)
780           " = "
781            (ls-compile val env fenv)))
782
783 ;;; Literals
784 (defun escape-string (string)
785   (let ((output "")
786         (index 0)
787         (size (length string)))
788     (while (< index size)
789       (let ((ch (char string index)))
790         (when (or (char= ch #\") (char= ch #\\))
791           (setq output (concat output "\\")))
792         (when (or (char= ch #\newline))
793           (setq output (concat output "\\"))
794           (setq ch #\n))
795         (setq output (concat output (string ch))))
796       (incf index))
797     output))
798
799 (defun literal->js (sexp)
800   (cond
801     ((integerp sexp) (integer-to-string sexp))
802     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
803     ((symbolp sexp) (ls-compile `(intern ,(escape-string (symbol-name sexp))) *env* *fenv*))
804     ((consp sexp) (concat "{car: "
805                           (literal->js (car sexp))
806                           ", cdr: "
807                           (literal->js (cdr sexp)) "}"))))
808
809 (defvar *literal-counter* 0)
810 (defun literal (form)
811   (let ((var (concat "l" (integer-to-string (incf *literal-counter*)))))
812     (push (concat "var " var " = " (literal->js form)) *toplevel-compilations*)
813     var))
814
815 (define-compilation quote (sexp)
816   (literal sexp))
817
818 (define-compilation debug (form)
819   (concat "console.log(" (ls-compile form env fenv) ")"))
820
821 (define-compilation while (pred &rest body)
822   (concat "(function(){ while("
823           (ls-compile pred env fenv) " !== " (ls-compile nil nil nil)
824           "){"
825           (ls-compile-block body env fenv)
826           "}})()"))
827
828 (define-compilation function (x)
829   (cond
830     ((and (listp x) (eq (car x) 'lambda))
831      (ls-compile x env fenv))
832     ((symbolp x)
833      (lookup-function-translation x fenv))))
834
835 (define-compilation eval-when-compile (&rest body)
836   (eval (cons 'progn body))
837   "")
838
839 (defmacro define-transformation (name args form)
840   `(define-compilation ,name ,args
841      (ls-compile ,form env fenv)))
842
843 (define-compilation progn (&rest body)
844   (concat "(function(){" *newline*
845           (ls-compile-block (butlast body) env fenv)
846           "return " (ls-compile (car (last body)) env fenv) ";"
847           "})()" *newline*))
848
849 (define-transformation let (bindings &rest body)
850   (let ((bindings (mapcar #'ensure-list bindings)))
851     `((lambda ,(mapcar #'car bindings) ,@body)
852       ,@(mapcar #'cadr bindings))))
853
854 ;;; A little backquote implementation without optimizations of any
855 ;;; kind for lispstrack.
856 (defun backquote-expand-1 (form)
857   (cond
858     ((symbolp form)
859      (list 'quote form))
860     ((atom form)
861      form)
862     ((eq (car form) 'unquote)
863      (car form))
864     ((eq (car form) 'backquote)
865      (backquote-expand-1 (backquote-expand-1 (cadr form))))
866     (t
867      (cons 'append
868            (mapcar (lambda (s)
869                      (cond
870                        ((and (listp s) (eq (car s) 'unquote))
871                         (list 'list (cadr s)))
872                        ((and (listp s) (eq (car s) 'unquote-splicing))
873                         (cadr s))
874                        (t
875                         (list 'list (backquote-expand-1 s)))))
876                    form)))))
877
878 (defun backquote-expand (form)
879   (if (and (listp form) (eq (car form) 'backquote))
880       (backquote-expand-1 (cadr form))
881       form))
882
883 (defmacro backquote (form)
884   (backquote-expand-1 form))
885
886 (define-transformation backquote (form)
887   (backquote-expand-1 form))
888
889 ;;; Primitives
890
891 (defun compile-bool (x)
892   (concat "(" x "?" (ls-compile t nil nil) ": " (ls-compile nil nil nil) ")"))
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   (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 = (x y)
910   (compile-bool (concat "((" (ls-compile x env fenv) ") == (" (ls-compile y env fenv) "))")))
911
912 (define-compilation numberp (x)
913   (compile-bool (concat "(typeof (" (ls-compile x env fenv) ") == \"number\")")))
914
915
916 (define-compilation mod (x y)
917   (concat "((" (ls-compile x env fenv) ") % (" (ls-compile y env fenv) "))"))
918
919 (define-compilation floor (x)
920   (concat "(Math.floor(" (ls-compile x env fenv) "))"))
921
922 (define-compilation null (x)
923   (compile-bool (concat "(" (ls-compile x env fenv) "===" (ls-compile nil env fenv) ")")))
924
925 (define-compilation cons (x y)
926   (concat "({car: " (ls-compile x env fenv) ", cdr: " (ls-compile y env fenv) "})"))
927
928 (define-compilation consp (x)
929   (compile-bool
930    (concat "(function(){ var tmp = "
931            (ls-compile x env fenv)
932            "; return (typeof tmp == 'object' && 'car' in tmp);})()")))
933
934 (define-compilation car (x)
935   (concat "(function () { var tmp = " (ls-compile x env fenv)
936           "; return tmp === " (ls-compile nil nil nil) "? "
937           (ls-compile nil nil nil)
938           ": tmp.car; })()"))
939
940 (define-compilation cdr (x)
941   (concat "(function () { var tmp = " (ls-compile x env fenv)
942           "; return tmp === " (ls-compile nil nil nil) "? "
943           (ls-compile nil nil nil)
944           ": tmp.cdr; })()"))
945
946 (define-compilation setcar (x new)
947   (concat "((" (ls-compile x env fenv) ").car = " (ls-compile new env fenv) ")"))
948
949 (define-compilation setcdr (x new)
950   (concat "((" (ls-compile x env fenv) ").cdr = " (ls-compile new env fenv) ")"))
951
952 (define-compilation symbolp (x)
953   (compile-bool
954    (concat "(function(){ var tmp = "
955            (ls-compile x env fenv)
956            "; return (typeof tmp == 'object' && 'name' in tmp); })()")))
957
958 (define-compilation make-symbol (name)
959   (concat "({name: " (ls-compile name env fenv) "})"))
960
961 (define-compilation symbol-name (x)
962   (concat "(" (ls-compile x env fenv) ").name"))
963
964 (define-compilation eq (x y)
965   (compile-bool
966    (concat "(" (ls-compile x env fenv) " === " (ls-compile y env fenv) ")")))
967
968 (define-compilation equal (x y)
969   (compile-bool
970    (concat "(" (ls-compile x env fenv) " == " (ls-compile y env fenv) ")")))
971
972 (define-compilation string (x)
973   (concat "String.fromCharCode(" (ls-compile x env fenv) ")"))
974
975 (define-compilation stringp (x)
976   (compile-bool
977    (concat "(typeof(" (ls-compile x env fenv) ") == \"string\")")))
978
979 (define-compilation string-upcase (x)
980   (concat "(" (ls-compile x env fenv) ").toUpperCase()"))
981
982 (define-compilation string-length (x)
983   (concat "(" (ls-compile x env fenv) ").length"))
984
985 (define-compilation char (string index)
986   (concat "("
987           (ls-compile string env fenv)
988           ").charCodeAt("
989           (ls-compile index env fenv)
990           ")"))
991
992 (define-compilation concat-two (string1 string2)
993   (concat "("
994           (ls-compile string1 env fenv)
995           ").concat("
996           (ls-compile string2 env fenv)
997           ")"))
998
999 (define-compilation funcall (func &rest args)
1000   (concat "("
1001           (ls-compile func env fenv)
1002           ")("
1003           (join (mapcar (lambda (x)
1004                           (ls-compile x env fenv))
1005                         args)
1006                 ", ")
1007           ")"))
1008
1009 (define-compilation apply (func &rest args)
1010   (if (null args)
1011       (concat "(" (ls-compile func env fenv) ")()")
1012       (let ((args (butlast args))
1013             (last (car (last args))))
1014         (concat "(function(){" *newline*
1015                 "var f = " (ls-compile func env fenv) ";" *newline*
1016                 "var args = [" (join (mapcar (lambda (x)
1017                                                (ls-compile x env fenv))
1018                                              args)
1019                                      ", ")
1020                 "];" *newline*
1021                 "var tail = (" (ls-compile last env fenv) ");" *newline*
1022                 "while (tail != " (ls-compile nil env fenv) "){" *newline*
1023                 "    args.push(tail.car);" *newline*
1024                 "    tail = tail.cdr;" *newline*
1025                 "}" *newline*
1026                 "return f.apply(this, args);" *newline*
1027                 "})()" *newline*))))
1028
1029 (define-compilation js-eval (string)
1030   (concat "eval.apply(window, [" (ls-compile string env fenv)  "])"))
1031
1032
1033 (define-compilation error (string)
1034   (concat "(function (){ throw " (ls-compile string env fenv) ";" "return 0;})()"))
1035
1036 (define-compilation new ()
1037   "{}")
1038
1039 (define-compilation get (object key)
1040   (concat "(function(){ var tmp = "
1041           "(" (ls-compile object env fenv) ")[" (ls-compile key env fenv) "]"
1042           ";"
1043           "return tmp == undefined? " (ls-compile nil nil nil) ": tmp ;"
1044           "})()"))
1045
1046 (define-compilation set (object key value)
1047   (concat "(("
1048           (ls-compile object env fenv)
1049           ")["
1050           (ls-compile key env fenv) "]"
1051           " = " (ls-compile value env fenv) ")"))
1052
1053 (define-compilation in (key object)
1054   (compile-bool
1055    (concat "(" (ls-compile key env fenv) " in " (ls-compile object env fenv) ")")))
1056
1057 (define-compilation functionp (x)
1058   (compile-bool
1059    (concat "(typeof " (ls-compile x env fenv) " == 'function')")))
1060
1061
1062 (defun macrop (x)
1063   (and (symbolp x) (eq (binding-type (lookup-function x *fenv*)) 'macro)))
1064
1065 (defun ls-macroexpand-1 (form env fenv)
1066   (if (macrop (car form))
1067       (let ((binding (lookup-function (car form) *env*)))
1068         (if (eq (binding-type binding) 'macro)
1069             (apply (eval (binding-translation binding)) (cdr form))
1070             form))
1071       form))
1072
1073 (defun compile-funcall (function args env fenv)
1074   (cond
1075     ((symbolp function)
1076      (concat (lookup-function-translation function fenv)
1077              "("
1078              (join (mapcar (lambda (x) (ls-compile x env fenv)) args)
1079                    ", ")
1080              ")"))
1081     ((and (listp function) (eq (car function) 'lambda))
1082      (concat "(" (ls-compile function env fenv) ")("
1083              (join (mapcar (lambda (x) (ls-compile x env fenv)) args)
1084                    ", ")
1085              ")"))
1086     (t
1087      (error (concat "Invalid function designator " (symbol-name function))))))
1088
1089 (defun ls-compile (sexp env fenv)
1090   (cond
1091     ((symbolp sexp) (lookup-variable-translation sexp env))
1092     ((integerp sexp) (integer-to-string sexp))
1093     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
1094     ((listp sexp)
1095      (if (assoc (car sexp) *compilations*)
1096          (let ((comp (second (assoc (car sexp) *compilations*))))
1097            (apply comp env fenv (cdr sexp)))
1098          (if (macrop (car sexp))
1099              (ls-compile (ls-macroexpand-1 sexp env fenv) env fenv)
1100              (compile-funcall (car sexp) (cdr sexp) env fenv))))))
1101
1102 (defun ls-compile-toplevel (sexp)
1103   (setq *toplevel-compilations* nil)
1104   (let ((code (ls-compile sexp nil nil)))
1105     (prog1
1106         (concat (join (mapcar (lambda (x) (concat x ";" *newline*))
1107                               *toplevel-compilations*))
1108                 code)
1109       (setq *toplevel-compilations* nil))))
1110
1111
1112 ;;; Once we have the compiler, we define the runtime environment and
1113 ;;; interactive development (eval), which works calling the compiler
1114 ;;; and evaluating the Javascript result globally.
1115
1116 #+lispstrack
1117 (progn
1118  (defmacro with-compilation-unit (&rest body)
1119    `(prog1
1120         (progn
1121           (setq *compilation-unit-checks* nil)
1122           (setq *env* (remove-if-not #'binding-declared *env*))
1123           (setq *fenv* (remove-if-not #'binding-declared *fenv*))
1124           ,@body)
1125       (dolist (check *compilation-unit-checks*)
1126         (funcall check))))
1127
1128  (defun eval (x)
1129    (let ((code
1130           (with-compilation-unit
1131               (ls-compile-toplevel x))))
1132      (js-eval code)))
1133
1134  ;; Set the initial global environment to be equal to the host global
1135  ;; environment at this point of the compilation.
1136  (eval-when-compile
1137    (let ((c1 (ls-compile `(setq *fenv* ',*fenv*) nil nil))
1138          (c2 (ls-compile `(setq *env* ',*env*) nil nil))
1139          (c3 (ls-compile `(setq *variable-counter* ',*variable-counter*) nil nil))
1140          (c4 (ls-compile `(setq *function-counter* ',*function-counter*) nil nil))
1141          (c5 (ls-compile `(setq *literal-counter* ',*literal-counter*) nil nil)))
1142      (setq *toplevel-compilations*
1143            (append *toplevel-compilations* (list c1 c2 c3 c4 c5)))))
1144
1145  (js-eval
1146   (concat "var lisp = {};"
1147           "lisp.read = " (lookup-function-translation 'ls-read-from-string nil) ";" *newline*
1148           "lisp.print = " (lookup-function-translation 'print-to-string nil) ";" *newline*
1149           "lisp.eval = " (lookup-function-translation 'eval nil) ";" *newline*
1150           "lisp.compile = " (lookup-function-translation 'ls-compile-toplevel nil) ";" *newline*
1151           "lisp.evalString = function(str){" *newline*
1152           "   return lisp.eval(lisp.read(str));" *newline*
1153           "}" *newline*
1154           "lisp.compileString = function(str){" *newline*
1155           "   return lisp.compile(lisp.read(str));" *newline*
1156           "}" *newline*)))
1157
1158
1159 ;;; Finally, we provide a couple of functions to easily bootstrap
1160 ;;; this. It just calls the compiler with this file as input.
1161
1162 #+common-lisp
1163 (progn
1164   (defun read-whole-file (filename)
1165     (with-open-file (in filename)
1166       (let ((seq (make-array (file-length in) :element-type 'character)))
1167         (read-sequence seq in)
1168         seq)))
1169
1170   (defun ls-compile-file (filename output)
1171     (setq *env* nil *fenv* nil)
1172     (setq *compilation-unit-checks* nil)
1173     (with-open-file (out output :direction :output :if-exists :supersede)
1174       (let* ((source (read-whole-file filename))
1175              (in (make-string-stream source)))
1176         (loop
1177            for x = (ls-read in)
1178            until (eq x *eof*)
1179            for compilation = (ls-compile-toplevel x)
1180            when (plusp (length compilation))
1181            do (write-line (concat compilation "; ") out))
1182         (dolist (check *compilation-unit-checks*)
1183           (funcall check))
1184         (setq *compilation-unit-checks* nil))))
1185
1186   (defun bootstrap ()
1187     (ls-compile-file "lispstrack.lisp" "lispstrack.js")))