9a6dbab4297f2d95c75db07b6c35964273055594
[jscl.git] / test.lisp
1 ;;; Library
2
3 (eval-when-compile
4   (%compile-defmacro 'defmacro
5      (lambda (name args &rest body)
6        `(eval-when-compile
7           (%compile-defmacro ',name (lambda ,args ,@body))))))
8
9 (defmacro defvar (name value)
10   `(progn
11      (eval-when-compile
12        (%compile-defvar ',name))
13      (setq ,name ,value)))
14
15 (defmacro defun (name args &rest body)
16   `(progn
17      (eval-when-compile
18        (%compile-defun ',name))
19      (fsetq ,name (lambda ,args ,@body))))
20
21 (defvar *package* (new))
22
23 (defun intern (name)
24   (let ((s (get *package* name)))
25     (if s s (set *package* name (make-symbol name)))))
26
27 (defun find-symbol (name)
28   (get *package* name))
29
30 (defvar t 't)
31 (defvar nil 'nil)
32
33 (defmacro when (condition &rest body)
34   `(if ,condition (progn ,@body) nil))
35
36 (defmacro unless (condition &rest body)
37   `(if ,condition nil (progn ,@body)))
38
39 (defmacro dolist (iter &rest body)
40   (let ((var (first iter))
41         (g!list (make-symbol "LIST")))
42     `(let ((,g!list ,(second iter))
43            (,var nil))
44        (while ,g!list
45          (setq ,var (car ,g!list))
46          ,@body
47          (setq ,g!list (cdr ,g!list))))))
48
49 (defun = (x y) (= x y))
50 (defun + (x y) (+ x y))
51 (defun - (x y) (- x y))
52 (defun * (x y) (* x y))
53 (defun / (x y) (/ x y))
54 (defun 1+ (x) (+ x 1))
55 (defun 1- (x) (- x 1))
56 (defun zerop (x) (= x 0))
57 (defun not (x) (if x nil t))
58
59 (defun truncate (x y) (floor (/ x y)))
60
61 (defun cons (x y ) (cons x y))
62 (defun car (x) (car x))
63 (defun caar (x) (car (car x)))
64 (defun cadr (x) (car (cdr x)))
65 (defun caddr (x) (car (cdr x)))
66 (defun cadddr (x) (car (cdr x)))
67 (defun cdr (x) (cdr x))
68 (defun cdar (x) (cdr (car x)))
69 (defun cddr (x) (cdr (cdr x)))
70 (defun cdddr (x) (cdr (cdr x)))
71
72 (defun first (x) (car x))
73 (defun second (x) (cadr x))
74 (defun third (x) (caddr x))
75 (defun fourth (x) (cadddr x))
76
77 (defun list (&rest args)
78   args)
79
80 (defun atom (x)
81   (not (consp x)))
82
83 (defun ensure-list (x)
84   (if (listp x)
85       x
86       (list x)))
87
88 (defun append (list1 list2)
89   (if (null list1)
90       list2
91       (cons (car list1)
92             (append (cdr list1) list2))))
93
94 (defun reverse-aux (list acc)
95   (if (null list)
96       acc
97       (reverse-aux (cdr list) (cons (car list) acc))))
98
99 (defun reverse (list)
100   (reverse-aux list '()))
101
102 (defmacro incf (x)
103   `(setq ,x (1+ ,x)))
104
105 (defmacro decf (x)
106   `(setq ,x (1- ,x)))
107
108 (defun list-length (list)
109   (let ((l 0))
110     (while (not (null list))
111       (incf l)
112       (setq list (cdr list)))
113     l))
114
115 (defun length (seq)
116   (if (stringp seq)
117       (string-length seq)
118       (list-length seq)))
119
120 (defun mapcar (func list)
121   (if (null list)
122       '()
123       (cons (funcall func (car list))
124             (mapcar func (cdr list)))))
125
126 (defmacro push (x place)
127   `(setq ,place (cons ,x ,place)))
128
129 (defmacro cond (&rest clausules)
130   (if (null clausules)
131       nil
132       (if (eq (caar clausules) t)
133           `(progn ,@(cdar clausules))
134           `(if ,(caar clausules)
135                (progn ,@(cdar clausules))
136                (cond ,@(cdr clausules))))))
137
138
139 (defmacro case (form &rest clausules)
140   (let ((!form (make-symbol "FORM")))
141     `(let ((,!form ,form))
142        (cond
143          ,@(mapcar (lambda (clausule)
144                      (if (eq (car clausule) t)
145                          clausule
146                          `((eql ,!form ,(car clausule))
147                            ,@(cdr clausule))))
148                    clausules)))))
149
150 (defmacro ecase (form &rest clausules)
151   `(case ,form
152      ,@(append
153         clausules
154         `((t
155            (error "ECASE expression failed."))))))
156
157 (defun !reduce (func list initial)
158   (if (null list)
159       initial
160       (!reduce func
161                (cdr list)
162                (funcall func initial (car list)))))
163
164
165 (defun code-char (x) x)
166 (defun char-code (x) x)
167 (defvar *newline* (string (code-char 10)))
168
169 (defun concat (&rest strs)
170   (!reduce (lambda (s1 s2) (concat-two s1 s2))
171            strs
172            ""))
173
174 ;;; Concatenate a list of strings, with a separator
175 (defun join (list separator)
176   (cond
177     ((null list)
178      "")
179     ((null (cdr list))
180      (car list))
181     (t
182      (concat (car list)
183              separator
184              (join (cdr list) separator)))))
185
186 (defun join-trailing (list separator)
187   (if (null list)
188       ""
189       (concat (car list) separator (join-trailing (cdr list) separator))))
190
191 (defun integer-to-string (x)
192   (if (zerop x)
193       "0"
194       (let ((digits nil))
195         (while (not (zerop x 0))
196           (push (mod x 10) digits)
197           (setq x (truncate x 10)))
198         (join (mapcar (lambda (d) (string (char "0123456789" d)))
199                       digits)
200               ""))))
201
202 (defmacro and (&rest forms)
203   (cond
204     ((null forms)
205      t)
206     ((null (cdr forms))
207      (car forms))
208     (t
209      `(if ,(car forms)
210           (and ,@(cdr forms))
211           nil))))
212
213
214 (defmacro or (&rest forms)
215   (cond
216     ((null forms)
217      nil)
218     ((null (cdr forms))
219      (car forms))
220     (t
221      `(if ,(car forms)
222           t
223           (or ,@(cdr forms))))))
224
225
226 (defmacro prog1 (form &rest body)
227   (let ((value (make-symbol "VALUE")))
228     `(let ((,value ,form))
229        ,@body
230        ,value)))
231
232
233 (defun char= (x y) (= x y))
234
235 (defun <= (x y) (or (< x y) (= x y)))
236 (defun >= (x y) (not (< x y)))
237
238 (defun listp (x)
239   (or (consp x) (null x)))
240
241 (defun integerp (x)
242   (and (numberp x) (= (floor x) x)))
243
244 (defun last (x)
245   (if (null (cdr x))
246       x
247       (last (cdr x))))
248
249 (defun butlast (x)
250   (if (null (cdr x))
251       nil
252       (cons (car x) (butlast (cdr x)))))
253
254 (defun member (x list)
255   (cond
256     ((null list)
257      nil)
258     ((eql x (car list))
259      list)
260     (t
261      (member x (cdr list)))))
262
263 (defun remove (x list)
264   (cond
265     ((null list)
266      nil)
267     ((eql x (car list))
268      (remove x (cdr list)))
269     (t
270      (cons (car list) (remove x (cdr list))))))
271
272 (defun digit-char-p (x)
273   (if (and (<= #\0 x) (<= x #\9))
274       (- x #\0)
275       nil))
276
277 (defun parse-integer (string)
278   (let ((value 0)
279         (index 0)
280         (size (length string)))
281     (while (< index size)
282       (setq value (+ (* value 10) (digit-char-p (char string index))))
283       (incf index))
284     value))
285
286 (defun every (function seq)
287   ;; string
288   (let ((ret t)
289         (index 0)
290         (size (length seq)))
291     (while (and ret (< index size))
292       (unless (funcall function (char seq index))
293         (setq ret nil))
294       (incf index))
295     ret))
296
297 (defun eql (x y)
298   (eq x y))
299
300 (defun assoc (x alist)
301   (cond
302     ((null alist)
303      nil)
304     ((eql x (caar alist))
305      (car alist))
306     (t
307      (assoc x (cdr alist)))))
308
309 (defun string= (s1 s2)
310   (equal s1 s2))
311
312 ;;;; Reader
313
314 ;;; It is a basic Lisp reader. It does not use advanced stuff
315 ;;; intentionally, because we want to use it to bootstrap a simple
316 ;;; Lisp. The main entry point is the function `ls-read', which
317 ;;; accepts a strings as argument and return the Lisp expression.
318 (defun make-string-stream (string)
319   (cons string 0))
320
321 (defun %peek-char (stream)
322   (and (< (cdr stream) (length (car stream)))
323        (char (car stream) (cdr stream))))
324
325 (defun %read-char (stream)
326   (and (< (cdr stream) (length (car stream)))
327        (prog1 (char (car stream) (cdr stream))
328          (setcdr stream (1+ (cdr stream))))))
329
330 (defun whitespacep (ch)
331   (or (char= ch #\space) (char= ch #\newline) (char= ch #\tab)))
332
333 (defun skip-whitespaces (stream)
334   (let (ch)
335     (setq ch (%peek-char stream))
336     (while (and ch (whitespacep ch))
337       (%read-char stream)
338       (setq ch (%peek-char stream)))))
339
340 (defun terminalp (ch)
341   (or (null ch) (whitespacep ch) (char= #\) ch) (char= #\( ch)))
342
343 (defun read-until (stream func)
344   (let ((string "")
345         (ch))
346     (setq ch (%peek-char stream))
347     (while (not (funcall func ch))
348       (setq string (concat string (string ch)))
349       (%read-char stream)
350       (setq ch (%peek-char stream)))
351     string))
352
353 (defun skip-whitespaces-and-comments (stream)
354   (let (ch)
355     (skip-whitespaces stream)
356     (setq ch (%peek-char stream))
357     (while (and ch (char= ch #\;))
358       (read-until stream (lambda (x) (char= x #\newline)))
359       (skip-whitespaces stream)
360       (setq ch (%peek-char stream)))))
361
362 (defun %read-list (stream)
363   (skip-whitespaces-and-comments stream)
364   (let ((ch (%peek-char stream)))
365     (cond
366       ((char= ch #\))
367        (%read-char stream)
368        nil)
369       ((char= ch #\.)
370        (%read-char stream)
371        (skip-whitespaces-and-comments stream)
372        (prog1 (ls-read stream)
373          (unless (char= (%read-char stream) #\))
374            (error "')' was expected."))))
375       (t
376        (cons (ls-read stream) (%read-list stream))))))
377
378 (defun read-string (stream)
379   (let ((string "")
380         (ch nil))
381     (setq ch (%read-char stream))
382     (while (not (char= ch #\"))
383       (when (char= ch #\\)
384         (setq ch (%read-char stream)))
385       (setq string (concat string (string ch)))
386       (setq ch (%read-char stream)))
387     string))
388
389 (defvar *eof* (make-symbol "EOF"))
390 (defun ls-read (stream)
391   (skip-whitespaces-and-comments stream)
392   (let ((ch (%peek-char stream)))
393     (cond
394       ((null ch)
395        *eof*)
396       ((char= ch #\()
397        (%read-char stream)
398        (%read-list stream))
399       ((char= ch #\')
400        (%read-char stream)
401        (list 'quote (ls-read stream)))
402       ((char= ch #\`)
403        (%read-char stream)
404        (list 'backquote (ls-read stream)))
405       ((char= ch #\")
406        (%read-char stream)
407        (read-string stream))
408       ((char= ch #\,)
409        (%read-char stream)
410        (if (eql (%peek-char stream) #\@)
411            (progn (%read-char stream) (list 'unquote-splicing (ls-read stream)))
412            (list 'unquote (ls-read stream))))
413       ((char= ch #\#)
414        (%read-char stream)
415        (ecase (%read-char stream)
416          (#\'
417           (list 'function (ls-read stream)))
418          (#\\
419           (let ((cname
420                  (concat (string (%read-char stream))
421                          (read-until stream #'terminalp))))
422             (cond
423               ((string= cname "space") (char-code #\space))
424               ((string= cname "newline") (char-code #\newline))
425               (t (char-code (char cname 0))))))
426          (#\+
427           (let ((feature (read-until stream #'terminalp)))
428             (cond
429               ((string= feature "common-lisp")
430                (ls-read stream)         ;ignore
431                (ls-read stream))
432               ((string= feature "lispstrack")
433                (ls-read stream))
434               (t
435                (error "Unknown reader form.")))))))
436       (t
437        (let ((string (read-until stream #'terminalp)))
438          (if (every #'digit-char-p string)
439              (parse-integer string)
440              (intern (string-upcase string))))))))
441
442 (defun ls-read-from-string (string)
443   (ls-read (make-string-stream string)))
444
445
446 ;;;; Compiler
447
448 (defvar *compilation-unit-checks* '())
449
450 (defvar *env* '())
451 (defvar *fenv* '())
452
453 (defun make-binding (name type js declared)
454   (list name type js declared))
455
456 (defun binding-name (b) (first b))
457 (defun binding-type (b) (second b))
458 (defun binding-translation (b) (third b))
459 (defun binding-declared (b)
460   (and b (fourth b)))
461 (defun mark-binding-as-declared (b)
462   (setcar (cdddr b) t))
463
464 (let ((counter 0))
465   (defun gvarname (symbol)
466     (concat "v" (integer-to-string (incf counter))))
467
468   (defun lookup-variable (symbol env)
469     (or (assoc symbol env)
470         (assoc symbol *env*)
471         (let ((name (symbol-name symbol))
472               (binding (make-binding symbol 'variable (gvarname symbol) nil)))
473           (push binding *env*)
474           (push (lambda ()
475                   (unless (binding-declared (assoc symbol *env*))
476                     (error (concat "Undefined variable `" name "'"))))
477                 *compilation-unit-checks*)
478           binding)))
479
480   (defun lookup-variable-translation (symbol env)
481     (binding-translation (lookup-variable symbol env)))
482
483   (defun extend-local-env (args env)
484     (append (mapcar (lambda (symbol)
485                       (make-binding symbol 'variable (gvarname symbol) t))
486                     args)
487             env)))
488
489 (let ((counter 0))
490   (defun lookup-function (symbol env)
491     (or (assoc symbol env)
492         (assoc symbol *fenv*)
493         (let ((name (symbol-name symbol))
494               (binding
495                (make-binding symbol
496                              'function
497                              (concat "f" (integer-to-string (incf counter)))
498                              nil)))
499           (push binding *fenv*)
500           (push (lambda ()
501                   (unless (binding-declared (assoc symbol *fenv*))
502                     (error (concat "Undefined function `" name "'"))))
503                 *compilation-unit-checks*)
504           binding)))
505
506   (defun lookup-function-translation (symbol env)
507     (binding-translation (lookup-function symbol env))))
508
509
510 (defvar *toplevel-compilations* nil)
511
512 (defun %compile-defvar (name)
513   (let ((b (lookup-variable name *env*)))
514     (mark-binding-as-declared b)
515     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
516
517 (defun %compile-defun (name)
518   (let ((b (lookup-function name *env*)))
519     (mark-binding-as-declared b)
520     (push (concat "var " (binding-translation b)) *toplevel-compilations*)))
521
522 (defun %compile-defmacro (name lambda)
523   (push (make-binding name 'macro lambda t) *fenv*))
524
525
526 (defvar *compilations* nil)
527
528 (defun ls-compile-block (sexps env fenv)
529   (join-trailing
530    (remove nil (mapcar (lambda (x)
531                          (ls-compile x env fenv))
532                        sexps))
533                  ";
534 "))
535 (defmacro define-compilation (name args &rest body)
536   ;; Creates a new primitive `name' with parameters args and
537   ;; @body. The body can access to the local environment through the
538   ;; variable ENV.
539   `(push (list ',name (lambda (env fenv ,@args) ,@body))
540          *compilations*))
541
542 (define-compilation if (condition true false)
543   (concat "("
544           (ls-compile condition env fenv)
545           " ? "
546           (ls-compile true env fenv)
547           " : "
548           (ls-compile false env fenv)
549           ")"))
550
551 ;;; Return the required args of a lambda list
552 (defun lambda-list-required-argument (lambda-list)
553   (if (or (null lambda-list) (eq (car lambda-list) '&rest))
554       nil
555       (cons (car lambda-list) (lambda-list-required-argument (cdr lambda-list)))))
556
557 (defun lambda-list-rest-argument (lambda-list)
558   (second (member '&rest lambda-list)))
559
560 (define-compilation lambda (lambda-list &rest body)
561   (let ((required-arguments (lambda-list-required-argument lambda-list))
562         (rest-argument (lambda-list-rest-argument lambda-list)))
563     (let ((new-env (extend-local-env
564                     (append (and rest-argument (list rest-argument))
565                             required-arguments)
566                     env)))
567       (concat "(function ("
568               (join (mapcar (lambda (x)
569                               (lookup-variable-translation x new-env))
570                             required-arguments)
571                     ",")
572               "){"
573               *newline*
574               (if rest-argument
575                   (let ((js!rest (lookup-variable-translation rest-argument new-env)))
576                     (concat "var " js!rest "= false;" *newline*
577                             "for (var i = arguments.length-1; i>="
578                             (integer-to-string (length required-arguments))
579                             "; i--)" *newline*
580                             js!rest " = "
581                             "{car: arguments[i], cdr: " js!rest "};"
582                             *newline*))
583                   "")
584               (concat (ls-compile-block (butlast body) new-env fenv)
585                       "return " (ls-compile (car (last body)) new-env fenv) ";")
586               *newline*
587               "})"))))
588
589 (define-compilation fsetq (var val)
590   (concat (lookup-function-translation var fenv)
591           " = "
592           (ls-compile val env fenv)))
593
594 (define-compilation setq (var val)
595   (concat (lookup-variable-translation var env)
596           " = "
597            (ls-compile val env fenv)))
598
599 ;;; Literals
600
601 (defun escape-string (string)
602   (let ((output "")
603         (index 0)
604         (size (length string)))
605     (while (< index size)
606       (let ((ch (char string index)))
607         (when (or (char= ch #\") (char= ch #\\))
608           (setq output (concat output "\\")))
609         (when (or (char= ch #\newline))
610           (setq output (concat output "\\"))
611           (setq ch #\n))
612         (setq output (concat output (string ch))))
613       (incf index))
614     output))
615
616 (defun literal->js (sexp)
617   (cond
618     ((null sexp) "false")
619     ((integerp sexp) (integer-to-string sexp))
620     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
621     ((symbolp sexp) (ls-compile `(intern ,(escape-string (symbol-name sexp))) *env* *fenv*))
622     ((consp sexp) (concat "{car: "
623                           (literal->js (car sexp))
624                           ", cdr: "
625                           (literal->js (cdr sexp)) "}"))))
626
627 (let ((counter 0))
628   (defun literal (form)
629     (cond
630       ((null form)
631        (literal->js form))
632       (t
633        (let ((var (concat "l" (integer-to-string (incf counter)))))
634          (push (concat "var " var " = " (literal->js form)) *toplevel-compilations*)
635          var)))))
636
637 (define-compilation quote (sexp)
638   (literal sexp))
639
640 (define-compilation debug (form)
641   (concat "console.log(" (ls-compile form env fenv) ")"))
642
643 (define-compilation while (pred &rest body)
644   (concat "(function(){ while("
645           (ls-compile pred env fenv)
646           "){"
647           (ls-compile-block body env fenv)
648           "}})()"))
649
650 (define-compilation function (x)
651   (cond
652     ((and (listp x) (eq (car x) 'lambda))
653      (ls-compile x env fenv))
654     ((symbolp x)
655      (lookup-function-translation x fenv))))
656
657 #+common-lisp
658 (defmacro eval-when-compile (&body body)
659   `(eval-when (:compile-toplevel :load-toplevel :execute)
660      ,@body))
661
662 (define-compilation eval-when-compile (&rest body)
663   (eval (cons 'progn body))
664   nil)
665
666 (defmacro define-transformation (name args form)
667   `(define-compilation ,name ,args
668      (ls-compile ,form env fenv)))
669
670 (define-transformation progn (&rest body)
671   `((lambda () ,@body)))
672
673 (define-transformation let (bindings &rest body)
674   (let ((bindings (mapcar #'ensure-list bindings)))
675     `((lambda ,(mapcar 'car bindings) ,@body)
676       ,@(mapcar 'cadr bindings))))
677
678 ;;; A little backquote implementation without optimizations of any
679 ;;; kind for lispstrack.
680 (defun backquote-expand-1 (form)
681   (cond
682     ((symbolp form)
683      (list 'quote form))
684     ((atom form)
685      form)
686     ((eq (car form) 'unquote)
687      (car form))
688     ((eq (car form) 'backquote)
689      (backquote-expand-1 (backquote-expand-1 (cadr form))))
690     (t
691      (cons 'append
692            (mapcar (lambda (s)
693                      (cond
694                        ((and (listp s) (eq (car s) 'unquote))
695                         (list 'list (cadr s)))
696                        ((and (listp s) (eq (car s) 'unquote-splicing))
697                         (cadr s))
698                        (t
699                         (list 'list (backquote-expand-1 s)))))
700                    form)))))
701
702 (defun backquote-expand (form)
703   (if (and (listp form) (eq (car form) 'backquote))
704       (backquote-expand-1 (cadr form))
705       form))
706
707 (defmacro backquote (form)
708   (backquote-expand-1 form))
709
710 (define-transformation backquote (form)
711   (backquote-expand-1 form))
712
713 ;;; Primitives
714
715 (define-compilation + (x y)
716   (concat "((" (ls-compile x env fenv) ") + (" (ls-compile y env fenv) "))"))
717
718 (define-compilation - (x y)
719   (concat "((" (ls-compile x env fenv) ") - (" (ls-compile y env fenv) "))"))
720
721 (define-compilation * (x y)
722   (concat "((" (ls-compile x env fenv) ") * (" (ls-compile y env fenv) "))"))
723
724 (define-compilation / (x y)
725   (concat "((" (ls-compile x env fenv) ") / (" (ls-compile y env fenv) "))"))
726
727 (define-compilation < (x y)
728   (concat "((" (ls-compile x env fenv) ") < (" (ls-compile y env fenv) "))"))
729
730 (define-compilation = (x y)
731   (concat "((" (ls-compile x env fenv) ") == (" (ls-compile y env fenv) "))"))
732
733 (define-compilation numberp (x)
734   (concat "(typeof (" (ls-compile x env fenv) ") == \"number\")"))
735
736
737 (define-compilation mod (x y)
738   (concat "((" (ls-compile x env fenv) ") % (" (ls-compile y env fenv) "))"))
739
740 (define-compilation floor (x)
741   (concat "(Math.floor(" (ls-compile x env fenv) "))"))
742
743 (define-compilation null (x)
744   (concat "(" (ls-compile x env fenv) "== false)"))
745
746 (define-compilation cons (x y)
747   (concat "{car: " (ls-compile x env fenv) ", cdr: " (ls-compile y env fenv) "}"))
748
749 (define-compilation consp (x)
750   (concat "(function(){ var tmp = "
751           (ls-compile x env fenv)
752           "; return (typeof tmp == 'object' && 'car' in tmp);})()"))
753
754 (define-compilation car (x)
755   (concat "(" (ls-compile x env fenv) ").car"))
756
757 (define-compilation cdr (x)
758   (concat "(" (ls-compile x env fenv) ").cdr"))
759
760 (define-compilation setcar (x new)
761   (concat "((" (ls-compile x env fenv) ").car = " (ls-compile new env fenv) ")"))
762
763 (define-compilation setcdr (x new)
764   (concat "((" (ls-compile x env fenv) ").cdr = " (ls-compile new env fenv) ")"))
765
766 (define-compilation symbolp (x)
767   (concat "(function(){ var tmp = "
768           (ls-compile x env fenv)
769           "; return (typeof tmp == 'object' && 'name' in tmp); })()"))
770
771 (define-compilation make-symbol (name)
772   (concat "{name: " (ls-compile name env fenv) "}"))
773
774 (define-compilation symbol-name (x)
775   (concat "(" (ls-compile x env fenv) ").name"))
776
777 (define-compilation eq (x y)
778   (concat "(" (ls-compile x env fenv) " === " (ls-compile y env fenv) ")"))
779
780 (define-compilation equal (x y)
781   (concat "(" (ls-compile x env fenv) " == " (ls-compile y env fenv) ")"))
782
783 (define-compilation string (x)
784   (concat "String.fromCharCode(" (ls-compile x env fenv) ")"))
785
786 (define-compilation stringp (x)
787   (concat "(typeof(" (ls-compile x env fenv) ") == \"string\")"))
788
789 (define-compilation string-upcase (x)
790   (concat "(" (ls-compile x env fenv) ").toUpperCase()"))
791
792 (define-compilation string-length (x)
793   (concat "(" (ls-compile x env fenv) ").length"))
794
795 (define-compilation char (string index)
796   (concat "("
797           (ls-compile string env fenv)
798           ").charCodeAt("
799           (ls-compile index env fenv)
800           ")"))
801
802 (define-compilation concat-two (string1 string2)
803   (concat "("
804           (ls-compile string1 env fenv)
805           ").concat("
806           (ls-compile string2 env fenv)
807           ")"))
808
809 (define-compilation funcall (func &rest args)
810   (concat "("
811           (ls-compile func env fenv)
812           ")("
813           (join (mapcar (lambda (x)
814                           (ls-compile x env fenv))
815                         args)
816                 ", ")
817           ")"))
818
819 (define-compilation apply (func &rest args)
820   (if (null args)
821       (concat "(" (ls-compile func env fenv) ")()")
822       (let ((args (butlast args))
823             (last (car (last args))))
824         (concat "function(){" *newline*
825                 "var f = " (ls-compile func env fenv) ";" *newline*
826                 "var args = [" (join (mapcar (lambda (x)
827                                                (ls-compile x env fenv))
828                                              args)
829                                      ", ")
830                 "];" *newline*
831                 "var tail = (" (ls-compile last env fenv) ");" *newline*
832                 "while (tail != false){" *newline*
833                 "    args.push(tail[0]);" *newline*
834                 "    args = args.slice(1);" *newline*
835                 "}" *newline*
836                 "return f.apply(this, args);" *newline*
837                 "}" *newline*))))
838
839 (define-compilation js-eval (string)
840   (concat "eval(" (ls-compile string env fenv)  ")"))
841
842
843 (define-compilation error (string)
844   (concat "(function (){ throw " (ls-compile string env fenv) ";" "return 0;})()"))
845
846 (define-compilation new ()
847   "{}")
848
849 (define-compilation get (object key)
850   (concat "(" (ls-compile object env fenv) ")[" (ls-compile key env fenv) "]"))
851
852 (define-compilation set (object key value)
853   (concat "(("
854           (ls-compile object env fenv)
855           ")["
856           (ls-compile key env fenv) "]"
857           " = " (ls-compile value env fenv) ")"))
858
859 (defun macrop (x)
860   (and (symbolp x) (eq (binding-type (lookup-function x *fenv*)) 'macro)))
861
862 (defun ls-macroexpand-1 (form env fenv)
863   (when (macrop (car form))
864     (let ((binding (lookup-function (car form) *env*)))
865       (if (eq (binding-type binding) 'macro)
866           (apply (eval (binding-translation binding)) (cdr form))
867           form))))
868
869 (defun compile-funcall (function args env fenv)
870   (cond
871     ((symbolp function)
872      (concat (lookup-function-translation function fenv)
873              "("
874              (join (mapcar (lambda (x) (ls-compile x env fenv)) args)
875                    ", ")
876              ")"))
877     ((and (listp function) (eq (car function) 'lambda))
878      (concat "(" (ls-compile function env fenv) ")("
879              (join (mapcar (lambda (x) (ls-compile x env fenv)) args)
880                    ", ")
881              ")"))
882     (t
883      (error (concat "Invalid function designator " (symbol-name function))))))
884
885 (defun ls-compile (sexp env fenv)
886   (cond
887     ((symbolp sexp) (lookup-variable-translation sexp env))
888     ((integerp sexp) (integer-to-string sexp))
889     ((stringp sexp) (concat "\"" (escape-string sexp) "\""))
890     ((listp sexp)
891      (if (assoc (car sexp) *compilations*)
892          (let ((comp (second (assoc (car sexp) *compilations*))))
893            (apply comp env fenv (cdr sexp)))
894          (if (macrop (car sexp))
895              (ls-compile (ls-macroexpand-1 sexp env fenv) env fenv)
896              (compile-funcall (car sexp) (cdr sexp) env fenv))))))
897
898 (defun ls-compile-toplevel (sexp)
899   (setq *toplevel-compilations* nil)
900   (let ((code (ls-compile sexp nil nil)))
901     (prog1
902         (join (mapcar (lambda (x) (concat x ";" *newline*))
903                       *toplevel-compilations*)
904               "")
905       code
906       (setq *toplevel-compilations* nil))))
907
908
909 (defmacro with-compilation-unit (&rest body)
910   `(progn
911      (setq *compilation-unit-checks* nil)
912      ,@body
913      (dolist (check *compilation-unit-checks*)
914        (funcall check))
915      (setq *compilation-unit-checks* nil)))
916
917
918 #+common-lisp
919 (progn
920   (defun read-whole-file (filename)
921     (with-open-file (in filename)
922       (let ((seq (make-array (file-length in) :element-type 'character)))
923         (read-sequence seq in)
924         seq)))
925
926   (defun ls-compile-file (filename output)
927     (setq *env* nil *fenv* nil)
928     (setq *compilation-unit-checks* nil)
929     (with-open-file (out output :direction :output :if-exists :supersede)
930       (let* ((source (read-whole-file filename))
931              (in (make-string-stream source)))
932         (loop
933            for x = (ls-read in)
934            until (eq x *eof*)
935            for compilation = (ls-compile-toplevel x)
936            when (plusp (length compilation))
937            do (write-line (concat compilation "; ") out))
938         (dolist (check *compilation-unit-checks*)
939           (funcall check))
940         (setq *compilation-unit-checks* nil))))
941
942   (defun bootstrap ()
943     (ls-compile-file "lispstrack.lisp" "lispstrack.js")))
944
945
946
947 (defun eval (x)
948   (js-eval (ls-compile x nil nil)))
949
950
951 (debug (ls-compile '(+ 1 2) nil nil))