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