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