4d1cdbd92b5363b5e04a12ed62f66af57beb8534
[jscl.git] / src / compiler.lisp
1 ;;; compiler.lisp --- 
2
3 ;; copyright (C) 2012, 2013 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 ;;;; Compiler
20
21 ;;; Translate the Lisp code to Javascript. It will compile the special
22 ;;; forms. Some primitive functions are compiled as special forms
23 ;;; too. The respective real functions are defined in the target (see
24 ;;; the beginning of this file) as well as some primitive functions.
25
26 (defun code (&rest args)
27   (mapconcat (lambda (arg)
28                (cond
29                  ((null arg) "")
30                  ((integerp arg) (integer-to-string arg))
31                  ((floatp arg) (float-to-string arg))
32                  ((stringp arg) arg)
33                  (t (error "Unknown argument."))))
34              args))
35
36 ;;; Wrap X with a Javascript code to convert the result from
37 ;;; Javascript generalized booleans to T or NIL.
38 (defun js!bool (x)
39   (code "(" x "?" (ls-compile t) ": " (ls-compile nil) ")"))
40
41 ;;; Concatenate the arguments and wrap them with a self-calling
42 ;;; Javascript anonymous function. It is used to make some Javascript
43 ;;; statements valid expressions and provide a private scope as well.
44 ;;; It could be defined as function, but we could do some
45 ;;; preprocessing in the future.
46 (defmacro js!selfcall (&body body)
47   `(code "(function(){" *newline* (indent ,@body) "})()"))
48
49 ;;; Like CODE, but prefix each line with four spaces. Two versions
50 ;;; of this function are available, because the Ecmalisp version is
51 ;;; very slow and bootstraping was annoying.
52
53 #+jscl
54 (defun indent (&rest string)
55   (let ((input (apply #'code string)))
56     (let ((output "")
57           (index 0)
58           (size (length input)))
59       (when (plusp (length input)) (concatf output "    "))
60       (while (< index size)
61         (let ((str
62                (if (and (char= (char input index) #\newline)
63                         (< index (1- size))
64                         (not (char= (char input (1+ index)) #\newline)))
65                    (concat (string #\newline) "    ")
66                    (string (char input index)))))
67           (concatf output str))
68         (incf index))
69       output)))
70
71 #+common-lisp
72 (defun indent (&rest string)
73   (with-output-to-string (*standard-output*)
74     (with-input-from-string (input (apply #'code string))
75       (loop
76          for line = (read-line input nil)
77          while line
78          do (write-string "    ")
79          do (write-line line)))))
80
81
82 ;;; A Form can return a multiple values object calling VALUES, like
83 ;;; values(arg1, arg2, ...). It will work in any context, as well as
84 ;;; returning an individual object. However, if the special variable
85 ;;; `*multiple-value-p*' is NIL, is granted that only the primary
86 ;;; value will be used, so we can optimize to avoid the VALUES
87 ;;; function call.
88 (defvar *multiple-value-p* nil)
89
90 ;; A very simple defstruct built on lists. It supports just slot with
91 ;; an optional default initform, and it will create a constructor,
92 ;; predicate and accessors for you.
93 (defmacro def!struct (name &rest slots)
94   (unless (symbolp name)
95     (error "It is not a full defstruct implementation."))
96   (let* ((name-string (symbol-name name))
97          (slot-descriptions
98           (mapcar (lambda (sd)
99                     (cond
100                       ((symbolp sd)
101                        (list sd))
102                       ((and (listp sd) (car sd) (cddr sd))
103                        sd)
104                       (t
105                        (error "Bad slot accessor."))))
106                   slots))
107          (predicate (intern (concat name-string "-P"))))
108     `(progn
109        ;; Constructor
110        (defun ,(intern (concat "MAKE-" name-string)) (&key ,@slot-descriptions)
111          (list ',name ,@(mapcar #'car slot-descriptions)))
112        ;; Predicate
113        (defun ,predicate (x)
114          (and (consp x) (eq (car x) ',name)))
115        ;; Copier
116        (defun ,(intern (concat "COPY-" name-string)) (x)
117          (copy-list x))
118        ;; Slot accessors
119        ,@(with-collect
120           (let ((index 1))
121             (dolist (slot slot-descriptions)
122               (let* ((name (car slot))
123                      (accessor-name (intern (concat name-string "-" (string name)))))
124                 (collect
125                     `(defun ,accessor-name (x)
126                        (unless (,predicate x)
127                          (error ,(concat "The object is not a type " name-string)))
128                        (nth ,index x)))
129                 ;; TODO: Implement this with a higher level
130                 ;; abstraction like defsetf or (defun (setf ..))
131                 (collect
132                     `(define-setf-expander ,accessor-name (x)
133                        (let ((object (gensym))
134                              (new-value (gensym)))
135                          (values (list object)
136                                  (list x)
137                                  (list new-value)
138                                  `(progn
139                                     (rplaca (nthcdr ,',index ,object) ,new-value) 
140                                     ,new-value)
141                                  `(,',accessor-name ,object)))))
142                 (incf index)))))
143        ',name)))
144
145
146 ;;; Environment
147
148 (def!struct binding
149   name
150   type
151   value
152   declarations)
153
154 (def!struct lexenv
155   variable
156   function
157   block
158   gotag)
159
160 (defun lookup-in-lexenv (name lexenv namespace)
161   (find name (ecase namespace
162                 (variable (lexenv-variable lexenv))
163                 (function (lexenv-function lexenv))
164                 (block    (lexenv-block    lexenv))
165                 (gotag    (lexenv-gotag    lexenv)))
166         :key #'binding-name))
167
168 (defun push-to-lexenv (binding lexenv namespace)
169   (ecase namespace
170     (variable (push binding (lexenv-variable lexenv)))
171     (function (push binding (lexenv-function lexenv)))
172     (block    (push binding (lexenv-block    lexenv)))
173     (gotag    (push binding (lexenv-gotag    lexenv)))))
174
175 (defun extend-lexenv (bindings lexenv namespace)
176   (let ((env (copy-lexenv lexenv)))
177     (dolist (binding (reverse bindings) env)
178       (push-to-lexenv binding env namespace))))
179
180
181 (defvar *environment* (make-lexenv))
182
183 (defvar *variable-counter* 0)
184
185 (defun gvarname (symbol)
186   (code "v" (incf *variable-counter*)))
187
188 (defun translate-variable (symbol)
189   (awhen (lookup-in-lexenv symbol *environment* 'variable)
190     (binding-value it)))
191
192 (defun extend-local-env (args)
193   (let ((new (copy-lexenv *environment*)))
194     (dolist (symbol args new)
195       (let ((b (make-binding :name symbol :type 'variable :value (gvarname symbol))))
196         (push-to-lexenv b new 'variable)))))
197
198 ;;; Toplevel compilations
199 (defvar *toplevel-compilations* nil)
200
201 (defun toplevel-compilation (string)
202   (push string *toplevel-compilations*))
203
204 (defun null-or-empty-p (x)
205   (zerop (length x)))
206
207 (defun get-toplevel-compilations ()
208   (reverse (remove-if #'null-or-empty-p *toplevel-compilations*)))
209
210 (defun %compile-defmacro (name lambda)
211   (toplevel-compilation (ls-compile `',name))
212   (let ((binding (make-binding :name name :type 'macro :value lambda)))
213     (push-to-lexenv binding  *environment* 'function))
214   name)
215
216 (defun global-binding (name type namespace)
217   (or (lookup-in-lexenv name *environment* namespace)
218       (let ((b (make-binding :name name :type type :value nil)))
219         (push-to-lexenv b *environment* namespace)
220         b)))
221
222 (defun claimp (symbol namespace claim)
223   (let ((b (lookup-in-lexenv symbol *environment* namespace)))
224     (and b (member claim (binding-declarations b)))))
225
226 (defun !proclaim (decl)
227   (case (car decl)
228     (special
229      (dolist (name (cdr decl))
230        (let ((b (global-binding name 'variable 'variable)))
231          (push 'special (binding-declarations b)))))
232     (notinline
233      (dolist (name (cdr decl))
234        (let ((b (global-binding name 'function 'function)))
235          (push 'notinline (binding-declarations b)))))
236     (constant
237      (dolist (name (cdr decl))
238        (let ((b (global-binding name 'variable 'variable)))
239          (push 'constant (binding-declarations b)))))))
240
241 #+jscl
242 (fset 'proclaim #'!proclaim)
243
244 (defun %define-symbol-macro (name expansion)
245   (let ((b (make-binding :name name :type 'macro :value expansion)))
246     (push-to-lexenv b *environment* 'variable)
247     name))
248
249 #+jscl
250 (defmacro define-symbol-macro (name expansion)
251   `(%define-symbol-macro ',name ',expansion))
252
253
254 ;;; Special forms
255
256 (defvar *compilations* nil)
257
258 (defmacro define-compilation (name args &body body)
259   ;; Creates a new primitive `name' with parameters args and
260   ;; @body. The body can access to the local environment through the
261   ;; variable *ENVIRONMENT*.
262   `(push (list ',name (lambda ,args (block ,name ,@body)))
263          *compilations*))
264
265 (define-compilation if (condition true false)
266   (code "(" (ls-compile condition) " !== " (ls-compile nil)
267         " ? " (ls-compile true *multiple-value-p*)
268         " : " (ls-compile false *multiple-value-p*)
269         ")"))
270
271 (defvar *ll-keywords* '(&optional &rest &key))
272
273 (defun list-until-keyword (list)
274   (if (or (null list) (member (car list) *ll-keywords*))
275       nil
276       (cons (car list) (list-until-keyword (cdr list)))))
277
278 (defun ll-section (keyword ll)
279   (list-until-keyword (cdr (member keyword ll))))
280
281 (defun ll-required-arguments (ll)
282   (list-until-keyword ll))
283
284 (defun ll-optional-arguments-canonical (ll)
285   (mapcar #'ensure-list (ll-section '&optional ll)))
286
287 (defun ll-optional-arguments (ll)
288   (mapcar #'car (ll-optional-arguments-canonical ll)))
289
290 (defun ll-rest-argument (ll)
291   (let ((rest (ll-section '&rest ll)))
292     (when (cdr rest)
293       (error "Bad lambda-list"))
294     (car rest)))
295
296 (defun ll-keyword-arguments-canonical (ll)
297   (flet ((canonicalize (keyarg)
298            ;; Build a canonical keyword argument descriptor, filling
299            ;; the optional fields. The result is a list of the form
300            ;; ((keyword-name var) init-form).
301            (let ((arg (ensure-list keyarg)))
302              (cons (if (listp (car arg))
303                        (car arg)
304                        (list (intern (symbol-name (car arg)) "KEYWORD") (car arg)))
305                    (cdr arg)))))
306     (mapcar #'canonicalize (ll-section '&key ll))))
307
308 (defun ll-keyword-arguments (ll)
309   (mapcar (lambda (keyarg) (second (first keyarg)))
310           (ll-keyword-arguments-canonical ll)))
311
312 (defun ll-svars (lambda-list)
313   (let ((args
314          (append
315           (ll-keyword-arguments-canonical lambda-list)
316           (ll-optional-arguments-canonical lambda-list))))
317     (remove nil (mapcar #'third args))))
318
319 (defun lambda-docstring-wrapper (docstring &rest strs)
320   (if docstring
321       (js!selfcall
322         "var func = " (join strs) ";" *newline*
323         "func.docstring = '" docstring "';" *newline*
324         "return func;" *newline*)
325       (apply #'code strs)))
326
327 (defun lambda-check-argument-count
328     (n-required-arguments n-optional-arguments rest-p)
329   ;; Note: Remember that we assume that the number of arguments of a
330   ;; call is at least 1 (the values argument).
331   (let ((min (1+ n-required-arguments))
332         (max (if rest-p 'n/a (+ 1 n-required-arguments n-optional-arguments))))
333     (block nil
334       ;; Special case: a positive exact number of arguments.
335       (when (and (< 1 min) (eql min max))
336         (return (code "checkArgs(arguments, " min ");" *newline*)))
337       ;; General case:
338       (code
339        (when (< 1 min)
340          (code "checkArgsAtLeast(arguments, " min ");" *newline*))
341        (when (numberp max)
342          (code "checkArgsAtMost(arguments, " max ");" *newline*))))))
343
344 (defun compile-lambda-optional (ll)
345   (let* ((optional-arguments (ll-optional-arguments-canonical ll))
346          (n-required-arguments (length (ll-required-arguments ll)))
347          (n-optional-arguments (length optional-arguments)))
348     (when optional-arguments
349       (code (mapconcat (lambda (arg)
350                          (code "var " (translate-variable (first arg)) "; " *newline*
351                                (when (third arg)
352                                  (code "var " (translate-variable (third arg))
353                                        " = " (ls-compile t)
354                                        "; " *newline*))))
355                        optional-arguments)
356             "switch(arguments.length-1){" *newline*
357             (let ((cases nil)
358                   (idx 0))
359               (progn
360                 (while (< idx n-optional-arguments)
361                   (let ((arg (nth idx optional-arguments)))
362                     (push (code "case " (+ idx n-required-arguments) ":" *newline*
363                                 (indent (translate-variable (car arg))
364                                         "="
365                                         (ls-compile (cadr arg)) ";" *newline*)
366                                 (when (third arg)
367                                   (indent (translate-variable (third arg))
368                                           "="
369                                           (ls-compile nil)
370                                           ";" *newline*)))
371                           cases)
372                     (incf idx)))
373                 (push (code "default: break;" *newline*) cases)
374                 (join (reverse cases))))
375             "}" *newline*))))
376
377 (defun compile-lambda-rest (ll)
378   (let ((n-required-arguments (length (ll-required-arguments ll)))
379         (n-optional-arguments (length (ll-optional-arguments ll)))
380         (rest-argument (ll-rest-argument ll)))
381     (when rest-argument
382       (let ((js!rest (translate-variable rest-argument)))
383         (code "var " js!rest "= " (ls-compile nil) ";" *newline*
384               "for (var i = arguments.length-1; i>="
385               (+ 1 n-required-arguments n-optional-arguments)
386               "; i--)" *newline*
387               (indent js!rest " = {car: arguments[i], cdr: ") js!rest "};"
388               *newline*)))))
389
390 (defun compile-lambda-parse-keywords (ll)
391   (let ((n-required-arguments
392          (length (ll-required-arguments ll)))
393         (n-optional-arguments
394          (length (ll-optional-arguments ll)))
395         (keyword-arguments
396          (ll-keyword-arguments-canonical ll)))
397     (code
398      ;; Declare variables
399      (mapconcat (lambda (arg)
400                   (let ((var (second (car arg))))
401                     (code "var " (translate-variable var) "; " *newline*
402                           (when (third arg)
403                             (code "var " (translate-variable (third arg))
404                                   " = " (ls-compile nil)
405                                   ";" *newline*)))))
406                 keyword-arguments)
407      ;; Parse keywords
408      (flet ((parse-keyword (keyarg)
409               ;; ((keyword-name var) init-form)
410               (code "for (i=" (+ 1 n-required-arguments n-optional-arguments)
411                     "; i<arguments.length; i+=2){" *newline*
412                     (indent
413                      "if (arguments[i] === " (ls-compile (caar keyarg)) "){" *newline*
414                      (indent (translate-variable (cadr (car keyarg)))
415                              " = arguments[i+1];"
416                              *newline*
417                              (let ((svar (third keyarg)))
418                                (when svar
419                                  (code (translate-variable svar) " = " (ls-compile t) ";" *newline*)))
420                              "break;" *newline*)
421                      "}" *newline*)
422                     "}" *newline*
423                     ;; Default value
424                     "if (i == arguments.length){" *newline*
425                     (indent (translate-variable (cadr (car keyarg))) " = " (ls-compile (cadr keyarg)) ";" *newline*)
426                     "}" *newline*)))
427        (when keyword-arguments
428          (code "var i;" *newline*
429                (mapconcat #'parse-keyword keyword-arguments))))
430      ;; Check for unknown keywords
431      (when keyword-arguments
432        (code "for (i=" (+ 1 n-required-arguments n-optional-arguments)
433              "; i<arguments.length; i+=2){" *newline*
434              (indent "if ("
435                      (join (mapcar (lambda (x)
436                                      (concat "arguments[i] !== " (ls-compile (caar x))))
437                                    keyword-arguments)
438                            " && ")
439                      ")" *newline*
440                      (indent
441                       "throw 'Unknown keyword argument ' + arguments[i].name;" *newline*))
442              "}" *newline*)))))
443
444 (defun compile-lambda (ll body)
445   (let ((required-arguments (ll-required-arguments ll))
446         (optional-arguments (ll-optional-arguments ll))
447         (keyword-arguments  (ll-keyword-arguments  ll))
448         (rest-argument      (ll-rest-argument      ll))
449         documentation)
450     ;; Get the documentation string for the lambda function
451     (when (and (stringp (car body))
452                (not (null (cdr body))))
453       (setq documentation (car body))
454       (setq body (cdr body)))
455     (let ((n-required-arguments (length required-arguments))
456           (n-optional-arguments (length optional-arguments))
457           (*environment* (extend-local-env
458                           (append (ensure-list rest-argument)
459                                   required-arguments
460                                   optional-arguments
461                                   keyword-arguments
462                                   (ll-svars ll)))))
463       (lambda-docstring-wrapper
464        documentation
465        "(function ("
466        (join (cons "values"
467                    (mapcar #'translate-variable
468                            (append required-arguments optional-arguments)))
469              ",")
470        "){" *newline*
471        (indent
472         ;; Check number of arguments
473         (lambda-check-argument-count n-required-arguments
474                                      n-optional-arguments
475                                      (or rest-argument keyword-arguments))
476         (compile-lambda-optional ll)
477         (compile-lambda-rest ll)
478         (compile-lambda-parse-keywords ll)
479         (let ((*multiple-value-p* t))
480           (ls-compile-block body t)))
481        "})"))))
482
483
484 (defun setq-pair (var val)
485   (let ((b (lookup-in-lexenv var *environment* 'variable)))
486     (cond
487       ((and b
488             (eq (binding-type b) 'variable)
489             (not (member 'special (binding-declarations b)))
490             (not (member 'constant (binding-declarations b))))
491        (code (binding-value b) " = " (ls-compile val)))
492       ((and b (eq (binding-type b) 'macro))
493        (ls-compile `(setf ,var ,val)))
494       (t
495        (ls-compile `(set ',var ,val))))))
496
497
498 (define-compilation setq (&rest pairs)
499   (let ((result ""))
500     (while t
501       (cond
502         ((null pairs) (return))
503         ((null (cdr pairs))
504          (error "Odd paris in SETQ"))
505         (t
506          (concatf result
507            (concat (setq-pair (car pairs) (cadr pairs))
508                    (if (null (cddr pairs)) "" ", ")))
509          (setq pairs (cddr pairs)))))
510     (code "(" result ")")))
511
512
513 ;;; Literals
514 (defun escape-string (string)
515   (let ((output "")
516         (index 0)
517         (size (length string)))
518     (while (< index size)
519       (let ((ch (char string index)))
520         (when (or (char= ch #\") (char= ch #\\))
521           (setq output (concat output "\\")))
522         (when (or (char= ch #\newline))
523           (setq output (concat output "\\"))
524           (setq ch #\n))
525         (setq output (concat output (string ch))))
526       (incf index))
527     output))
528
529
530 (defvar *literal-table* nil)
531 (defvar *literal-counter* 0)
532
533 (defun genlit ()
534   (code "l" (incf *literal-counter*)))
535
536 (defun literal (sexp &optional recursive)
537   (cond
538     ((integerp sexp) (integer-to-string sexp))
539     ((floatp sexp) (float-to-string sexp))
540     ((stringp sexp) (code "\"" (escape-string sexp) "\""))
541     ((symbolp sexp)
542      (or (cdr (assoc sexp *literal-symbols*))
543          (let ((v (genlit))
544                (s #+common-lisp
545                  (let ((package (symbol-package sexp)))
546                    (if (eq package (find-package "KEYWORD"))
547                        (code "{name: \"" (escape-string (symbol-name sexp))
548                              "\", 'package': '" (package-name package) "'}")
549                        (code "{name: \"" (escape-string (symbol-name sexp)) "\"}")))
550                  #+jscl
551                  (let ((package (symbol-package sexp)))
552                    (if (null package)
553                        (code "{name: \"" (escape-string (symbol-name sexp)) "\"}")
554                        (ls-compile `(intern ,(symbol-name sexp) ,(package-name package)))))))
555            (push (cons sexp v) *literal-symbols*)
556            (toplevel-compilation (code "var " v " = " s))
557            v)))
558     ((consp sexp)
559      (let* ((head (butlast sexp))
560             (tail (last sexp))
561             (c (code "QIList("
562                      (join-trailing (mapcar (lambda (x) (literal x t)) head) ",")
563                      (literal (car tail) t)
564                      ","
565                      (literal (cdr tail) t)
566                      ")")))
567        (if recursive
568            c
569            (let ((v (genlit)))
570              (toplevel-compilation (code "var " v " = " c))
571              v))))
572     ((arrayp sexp)
573      (let ((elements (vector-to-list sexp)))
574        (let ((c (concat "[" (join (mapcar #'literal elements) ", ") "]")))
575          (if recursive
576              c
577              (let ((v (genlit)))
578                (toplevel-compilation (code "var " v " = " c))
579                v)))))))
580
581 (define-compilation quote (sexp)
582   (literal sexp))
583
584 (define-compilation %while (pred &rest body)
585   (js!selfcall
586     "while(" (ls-compile pred) " !== " (ls-compile nil) "){" *newline*
587     (indent (ls-compile-block body))
588     "}"
589     "return " (ls-compile nil) ";" *newline*))
590
591 (define-compilation function (x)
592   (cond
593     ((and (listp x) (eq (car x) 'lambda))
594      (compile-lambda (cadr x) (cddr x)))
595     ((symbolp x)
596      (let ((b (lookup-in-lexenv x *environment* 'function)))
597        (if b
598            (binding-value b)
599            (ls-compile `(symbol-function ',x)))))))
600
601
602 (defun make-function-binding (fname)
603   (make-binding :name fname :type 'function :value (gvarname fname)))
604
605 (defun compile-function-definition (list)
606   (compile-lambda (car list) (cdr list)))
607
608 (defun translate-function (name)
609   (let ((b (lookup-in-lexenv name *environment* 'function)))
610     (and b (binding-value b))))
611
612 (define-compilation flet (definitions &rest body)
613   (let* ((fnames (mapcar #'car definitions))
614          (fbody  (mapcar #'cdr definitions))
615          (cfuncs (mapcar #'compile-function-definition fbody))
616          (*environment*
617           (extend-lexenv (mapcar #'make-function-binding fnames)
618                          *environment*
619                          'function)))
620     (code "(function("
621           (join (mapcar #'translate-function fnames) ",")
622           "){" *newline*
623           (let ((body (ls-compile-block body t)))
624             (indent body))
625           "})(" (join cfuncs ",") ")")))
626
627 (define-compilation labels (definitions &rest body)
628   (let* ((fnames (mapcar #'car definitions))
629          (*environment*
630           (extend-lexenv (mapcar #'make-function-binding fnames)
631                          *environment*
632                          'function)))
633     (js!selfcall
634       (mapconcat (lambda (func)
635                    (code "var " (translate-function (car func))
636                          " = " (compile-lambda (cadr func) (cddr func))
637                          ";" *newline*))
638                  definitions)
639       (ls-compile-block body t))))
640
641
642 (defvar *compiling-file* nil)
643 (define-compilation eval-when-compile (&rest body)
644   (if *compiling-file*
645       (progn
646         (eval (cons 'progn body))
647         nil)
648       (ls-compile `(progn ,@body))))
649
650 (defmacro define-transformation (name args form)
651   `(define-compilation ,name ,args
652      (ls-compile ,form)))
653
654 (define-compilation progn (&rest body)
655   (if (null (cdr body))
656       (ls-compile (car body) *multiple-value-p*)
657       (js!selfcall (ls-compile-block body t))))
658
659 (defun special-variable-p (x)
660   (and (claimp x 'variable 'special) t))
661
662 ;;; Wrap CODE to restore the symbol values of the dynamic
663 ;;; bindings. BINDINGS is a list of pairs of the form
664 ;;; (SYMBOL . PLACE),  where PLACE is a Javascript variable
665 ;;; name to initialize the symbol value and where to stored
666 ;;; the old value.
667 (defun let-binding-wrapper (bindings body)
668   (when (null bindings)
669     (return-from let-binding-wrapper body))
670   (code
671    "try {" *newline*
672    (indent "var tmp;" *newline*
673            (mapconcat
674             (lambda (b)
675               (let ((s (ls-compile `(quote ,(car b)))))
676                 (code "tmp = " s ".value;" *newline*
677                       s ".value = " (cdr b) ";" *newline*
678                       (cdr b) " = tmp;" *newline*)))
679             bindings)
680            body *newline*)
681    "}" *newline*
682    "finally {"  *newline*
683    (indent
684     (mapconcat (lambda (b)
685                  (let ((s (ls-compile `(quote ,(car b)))))
686                    (code s ".value" " = " (cdr b) ";" *newline*)))
687                bindings))
688    "}" *newline*))
689
690 (define-compilation let (bindings &rest body)
691   (let* ((bindings (mapcar #'ensure-list bindings))
692          (variables (mapcar #'first bindings))
693          (cvalues (mapcar #'ls-compile (mapcar #'second bindings)))
694          (*environment* (extend-local-env (remove-if #'special-variable-p variables)))
695          (dynamic-bindings))
696     (code "(function("
697           (join (mapcar (lambda (x)
698                           (if (special-variable-p x)
699                               (let ((v (gvarname x)))
700                                 (push (cons x v) dynamic-bindings)
701                                 v)
702                               (translate-variable x)))
703                         variables)
704                 ",")
705           "){" *newline*
706           (let ((body (ls-compile-block body t)))
707             (indent (let-binding-wrapper dynamic-bindings body)))
708           "})(" (join cvalues ",") ")")))
709
710
711 ;;; Return the code to initialize BINDING, and push it extending the
712 ;;; current lexical environment if the variable is not special.
713 (defun let*-initialize-value (binding)
714   (let ((var (first binding))
715         (value (second binding)))
716     (if (special-variable-p var)
717         (code (ls-compile `(setq ,var ,value)) ";" *newline*)
718         (let* ((v (gvarname var))
719                (b (make-binding :name var :type 'variable :value v)))
720           (prog1 (code "var " v " = " (ls-compile value) ";" *newline*)
721             (push-to-lexenv b *environment* 'variable))))))
722
723 ;;; Wrap BODY to restore the symbol values of SYMBOLS after body. It
724 ;;; DOES NOT generate code to initialize the value of the symbols,
725 ;;; unlike let-binding-wrapper.
726 (defun let*-binding-wrapper (symbols body)
727   (when (null symbols)
728     (return-from let*-binding-wrapper body))
729   (let ((store (mapcar (lambda (s) (cons s (gvarname s)))
730                        (remove-if-not #'special-variable-p symbols))))
731     (code
732      "try {" *newline*
733      (indent
734       (mapconcat (lambda (b)
735                    (let ((s (ls-compile `(quote ,(car b)))))
736                      (code "var " (cdr b) " = " s ".value;" *newline*)))
737                  store)
738       body)
739      "}" *newline*
740      "finally {" *newline*
741      (indent
742       (mapconcat (lambda (b)
743                    (let ((s (ls-compile `(quote ,(car b)))))
744                      (code s ".value" " = " (cdr b) ";" *newline*)))
745                  store))
746      "}" *newline*)))
747
748 (define-compilation let* (bindings &rest body)
749   (let ((bindings (mapcar #'ensure-list bindings))
750         (*environment* (copy-lexenv *environment*)))
751     (js!selfcall
752       (let ((specials (remove-if-not #'special-variable-p (mapcar #'first bindings)))
753             (body (concat (mapconcat #'let*-initialize-value bindings)
754                           (ls-compile-block body t))))
755         (let*-binding-wrapper specials body)))))
756
757
758 (defvar *block-counter* 0)
759
760 (define-compilation block (name &rest body)
761   (let* ((tr (incf *block-counter*))
762          (b (make-binding :name name :type 'block :value tr)))
763     (when *multiple-value-p*
764       (push 'multiple-value (binding-declarations b)))
765     (let* ((*environment* (extend-lexenv (list b) *environment* 'block))
766            (cbody (ls-compile-block body t)))
767       (if (member 'used (binding-declarations b))
768           (js!selfcall
769             "try {" *newline*
770             (indent cbody)
771             "}" *newline*
772             "catch (cf){" *newline*
773             "    if (cf.type == 'block' && cf.id == " tr ")" *newline*
774             (if *multiple-value-p*
775                 "        return values.apply(this, forcemv(cf.values));"
776                 "        return cf.values;")
777             *newline*
778             "    else" *newline*
779             "        throw cf;" *newline*
780             "}" *newline*)
781           (js!selfcall cbody)))))
782
783 (define-compilation return-from (name &optional value)
784   (let* ((b (lookup-in-lexenv name *environment* 'block))
785          (multiple-value-p (member 'multiple-value (binding-declarations b))))
786     (when (null b)
787       (error (concat "Unknown block `" (symbol-name name) "'.")))
788     (push 'used (binding-declarations b))
789     (js!selfcall
790       (when multiple-value-p (code "var values = mv;" *newline*))
791       "throw ({"
792       "type: 'block', "
793       "id: " (binding-value b) ", "
794       "values: " (ls-compile value multiple-value-p) ", "
795       "message: 'Return from unknown block " (symbol-name name) ".'"
796       "})")))
797
798 (define-compilation catch (id &rest body)
799   (js!selfcall
800     "var id = " (ls-compile id) ";" *newline*
801     "try {" *newline*
802     (indent (ls-compile-block body t)) *newline*
803     "}" *newline*
804     "catch (cf){" *newline*
805     "    if (cf.type == 'catch' && cf.id == id)" *newline*
806     (if *multiple-value-p*
807         "        return values.apply(this, forcemv(cf.values));"
808         "        return pv.apply(this, forcemv(cf.values));")
809     *newline*
810     "    else" *newline*
811     "        throw cf;" *newline*
812     "}" *newline*))
813
814 (define-compilation throw (id value)
815   (js!selfcall
816     "var values = mv;" *newline*
817     "throw ({"
818     "type: 'catch', "
819     "id: " (ls-compile id) ", "
820     "values: " (ls-compile value t) ", "
821     "message: 'Throw uncatched.'"
822     "})"))
823
824
825 (defvar *tagbody-counter* 0)
826 (defvar *go-tag-counter* 0)
827
828 (defun go-tag-p (x)
829   (or (integerp x) (symbolp x)))
830
831 (defun declare-tagbody-tags (tbidx body)
832   (let ((bindings
833          (mapcar (lambda (label)
834                    (let ((tagidx (integer-to-string (incf *go-tag-counter*))))
835                      (make-binding :name label :type 'gotag :value (list tbidx tagidx))))
836                  (remove-if-not #'go-tag-p body))))
837     (extend-lexenv bindings *environment* 'gotag)))
838
839 (define-compilation tagbody (&rest body)
840   ;; Ignore the tagbody if it does not contain any go-tag. We do this
841   ;; because 1) it is easy and 2) many built-in forms expand to a
842   ;; implicit tagbody, so we save some space.
843   (unless (some #'go-tag-p body)
844     (return-from tagbody (ls-compile `(progn ,@body nil))))
845   ;; The translation assumes the first form in BODY is a label
846   (unless (go-tag-p (car body))
847     (push (gensym "START") body))
848   ;; Tagbody compilation
849   (let ((tbidx *tagbody-counter*))
850     (let ((*environment* (declare-tagbody-tags tbidx body))
851           initag)
852       (let ((b (lookup-in-lexenv (first body) *environment* 'gotag)))
853         (setq initag (second (binding-value b))))
854       (js!selfcall
855         "var tagbody_" tbidx " = " initag ";" *newline*
856         "tbloop:" *newline*
857         "while (true) {" *newline*
858         (indent "try {" *newline*
859                 (indent (let ((content ""))
860                           (code "switch(tagbody_" tbidx "){" *newline*
861                                 "case " initag ":" *newline*
862                                 (dolist (form (cdr body) content)
863                                   (concatf content
864                                     (if (not (go-tag-p form))
865                                         (indent (ls-compile form) ";" *newline*)
866                                         (let ((b (lookup-in-lexenv form *environment* 'gotag)))
867                                           (code "case " (second (binding-value b)) ":" *newline*)))))
868                                 "default:" *newline*
869                                 "    break tbloop;" *newline*
870                                 "}" *newline*)))
871                 "}" *newline*
872                 "catch (jump) {" *newline*
873                 "    if (jump.type == 'tagbody' && jump.id == " tbidx ")" *newline*
874                 "        tagbody_" tbidx " = jump.label;" *newline*
875                 "    else" *newline*
876                 "        throw(jump);" *newline*
877                 "}" *newline*)
878         "}" *newline*
879         "return " (ls-compile nil) ";" *newline*))))
880
881 (define-compilation go (label)
882   (let ((b (lookup-in-lexenv label *environment* 'gotag))
883         (n (cond
884              ((symbolp label) (symbol-name label))
885              ((integerp label) (integer-to-string label)))))
886     (when (null b)
887       (error (concat "Unknown tag `" n "'.")))
888     (js!selfcall
889       "throw ({"
890       "type: 'tagbody', "
891       "id: " (first (binding-value b)) ", "
892       "label: " (second (binding-value b)) ", "
893       "message: 'Attempt to GO to non-existing tag " n "'"
894       "})" *newline*)))
895
896 (define-compilation unwind-protect (form &rest clean-up)
897   (js!selfcall
898     "var ret = " (ls-compile nil) ";" *newline*
899     "try {" *newline*
900     (indent "ret = " (ls-compile form) ";" *newline*)
901     "} finally {" *newline*
902     (indent (ls-compile-block clean-up))
903     "}" *newline*
904     "return ret;" *newline*))
905
906 (define-compilation multiple-value-call (func-form &rest forms)
907   (js!selfcall
908     "var func = " (ls-compile func-form) ";" *newline*
909     "var args = [" (if *multiple-value-p* "values" "pv") "];" *newline*
910     "return "
911     (js!selfcall
912       "var values = mv;" *newline*
913       "var vs;" *newline*
914       (mapconcat (lambda (form)
915                    (code "vs = " (ls-compile form t) ";" *newline*
916                          "if (typeof vs === 'object' && 'multiple-value' in vs)" *newline*
917                          (indent "args = args.concat(vs);" *newline*)
918                          "else" *newline*
919                          (indent "args.push(vs);" *newline*)))
920                  forms)
921       "return func.apply(window, args);" *newline*) ";" *newline*))
922
923 (define-compilation multiple-value-prog1 (first-form &rest forms)
924   (js!selfcall
925     "var args = " (ls-compile first-form *multiple-value-p*) ";" *newline*
926     (ls-compile-block forms)
927     "return args;" *newline*))
928
929
930 ;;; Javascript FFI
931
932 (define-compilation %js-vref (var) var)
933
934 (define-compilation %js-vset (var val)
935   (code "(" var " = " (ls-compile val) ")"))
936
937 (define-setf-expander %js-vref (var)
938   (let ((new-value (gensym)))
939     (unless (stringp var)
940       (error "a string was expected"))
941     (values nil
942             (list var)
943             (list new-value)
944             `(%js-vset ,var ,new-value)
945             `(%js-vref ,var))))
946
947
948 ;;; Backquote implementation.
949 ;;;
950 ;;;    Author: Guy L. Steele Jr.     Date: 27 December 1985
951 ;;;    Tested under Symbolics Common Lisp and Lucid Common Lisp.
952 ;;;    This software is in the public domain.
953
954 ;;;    The following are unique tokens used during processing.
955 ;;;    They need not be symbols; they need not even be atoms.
956 (defvar *comma* 'unquote)
957 (defvar *comma-atsign* 'unquote-splicing)
958
959 (defvar *bq-list* (make-symbol "BQ-LIST"))
960 (defvar *bq-append* (make-symbol "BQ-APPEND"))
961 (defvar *bq-list** (make-symbol "BQ-LIST*"))
962 (defvar *bq-nconc* (make-symbol "BQ-NCONC"))
963 (defvar *bq-clobberable* (make-symbol "BQ-CLOBBERABLE"))
964 (defvar *bq-quote* (make-symbol "BQ-QUOTE"))
965 (defvar *bq-quote-nil* (list *bq-quote* nil))
966
967 ;;; BACKQUOTE is an ordinary macro (not a read-macro) that processes
968 ;;; the expression foo, looking for occurrences of #:COMMA,
969 ;;; #:COMMA-ATSIGN, and #:COMMA-DOT.  It constructs code in strict
970 ;;; accordance with the rules on pages 349-350 of the first edition
971 ;;; (pages 528-529 of this second edition).  It then optionally
972 ;;; applies a code simplifier.
973
974 ;;; If the value of *BQ-SIMPLIFY* is non-NIL, then BACKQUOTE
975 ;;; processing applies the code simplifier.  If the value is NIL,
976 ;;; then the code resulting from BACKQUOTE is exactly that
977 ;;; specified by the official rules.
978 (defparameter *bq-simplify* t)
979
980 (defmacro backquote (x)
981   (bq-completely-process x))
982
983 ;;; Backquote processing proceeds in three stages:
984 ;;;
985 ;;; (1) BQ-PROCESS applies the rules to remove occurrences of
986 ;;; #:COMMA, #:COMMA-ATSIGN, and #:COMMA-DOT corresponding to
987 ;;; this level of BACKQUOTE.  (It also causes embedded calls to
988 ;;; BACKQUOTE to be expanded so that nesting is properly handled.)
989 ;;; Code is produced that is expressed in terms of functions
990 ;;; #:BQ-LIST, #:BQ-APPEND, and #:BQ-CLOBBERABLE.  This is done
991 ;;; so that the simplifier will simplify only list construction
992 ;;; functions actually generated by BACKQUOTE and will not involve
993 ;;; any user code in the simplification.  #:BQ-LIST means LIST,
994 ;;; #:BQ-APPEND means APPEND, and #:BQ-CLOBBERABLE means IDENTITY
995 ;;; but indicates places where "%." was used and where NCONC may
996 ;;; therefore be introduced by the simplifier for efficiency.
997 ;;;
998 ;;; (2) BQ-SIMPLIFY, if used, rewrites the code produced by
999 ;;; BQ-PROCESS to produce equivalent but faster code.  The
1000 ;;; additional functions #:BQ-LIST* and #:BQ-NCONC may be
1001 ;;; introduced into the code.
1002 ;;;
1003 ;;; (3) BQ-REMOVE-TOKENS goes through the code and replaces
1004 ;;; #:BQ-LIST with LIST, #:BQ-APPEND with APPEND, and so on.
1005 ;;; #:BQ-CLOBBERABLE is simply eliminated (a call to it being
1006 ;;; replaced by its argument).  #:BQ-LIST* is replaced by either
1007 ;;; LIST* or CONS (the latter is used in the two-argument case,
1008 ;;; purely to make the resulting code a tad more readable).
1009
1010 (defun bq-completely-process (x)
1011   (let ((raw-result (bq-process x)))
1012     (bq-remove-tokens (if *bq-simplify*
1013                           (bq-simplify raw-result)
1014                           raw-result))))
1015
1016 (defun bq-process (x)
1017   (cond ((atom x)
1018          (list *bq-quote* x))
1019         ((eq (car x) 'backquote)
1020          (bq-process (bq-completely-process (cadr x))))
1021         ((eq (car x) *comma*) (cadr x))
1022         ((eq (car x) *comma-atsign*)
1023          ;; (error ",@~S after `" (cadr x))
1024          (error "ill-formed"))
1025         ;; ((eq (car x) *comma-dot*)
1026         ;;  ;; (error ",.~S after `" (cadr x))
1027         ;;  (error "ill-formed"))
1028         (t (do ((p x (cdr p))
1029                 (q '() (cons (bracket (car p)) q)))
1030                ((atom p)
1031                 (cons *bq-append*
1032                       (nreconc q (list (list *bq-quote* p)))))
1033              (when (eq (car p) *comma*)
1034                (unless (null (cddr p))
1035                  ;; (error "Malformed ,~S" p)
1036                  (error "Malformed"))
1037                (return (cons *bq-append*
1038                              (nreconc q (list (cadr p))))))
1039              (when (eq (car p) *comma-atsign*)
1040                ;; (error "Dotted ,@~S" p)
1041                (error "Dotted"))
1042              ;; (when (eq (car p) *comma-dot*)
1043              ;;   ;; (error "Dotted ,.~S" p)
1044              ;;   (error "Dotted"))
1045              ))))
1046
1047 ;;; This implements the bracket operator of the formal rules.
1048 (defun bracket (x)
1049   (cond ((atom x)
1050          (list *bq-list* (bq-process x)))
1051         ((eq (car x) *comma*)
1052          (list *bq-list* (cadr x)))
1053         ((eq (car x) *comma-atsign*)
1054          (cadr x))
1055         ;; ((eq (car x) *comma-dot*)
1056         ;;  (list *bq-clobberable* (cadr x)))
1057         (t (list *bq-list* (bq-process x)))))
1058
1059 ;;; This auxiliary function is like MAPCAR but has two extra
1060 ;;; purposes: (1) it handles dotted lists; (2) it tries to make
1061 ;;; the result share with the argument x as much as possible.
1062 (defun maptree (fn x)
1063   (if (atom x)
1064       (funcall fn x)
1065       (let ((a (funcall fn (car x)))
1066             (d (maptree fn (cdr x))))
1067         (if (and (eql a (car x)) (eql d (cdr x)))
1068             x
1069             (cons a d)))))
1070
1071 ;;; This predicate is true of a form that when read looked
1072 ;;; like %@foo or %.foo.
1073 (defun bq-splicing-frob (x)
1074   (and (consp x)
1075        (or (eq (car x) *comma-atsign*)
1076            ;; (eq (car x) *comma-dot*)
1077            )))
1078
1079 ;;; This predicate is true of a form that when read
1080 ;;; looked like %@foo or %.foo or just plain %foo.
1081 (defun bq-frob (x)
1082   (and (consp x)
1083        (or (eq (car x) *comma*)
1084            (eq (car x) *comma-atsign*)
1085            ;; (eq (car x) *comma-dot*)
1086            )))
1087
1088 ;;; The simplifier essentially looks for calls to #:BQ-APPEND and
1089 ;;; tries to simplify them.  The arguments to #:BQ-APPEND are
1090 ;;; processed from right to left, building up a replacement form.
1091 ;;; At each step a number of special cases are handled that,
1092 ;;; loosely speaking, look like this:
1093 ;;;
1094 ;;;  (APPEND (LIST a b c) foo) => (LIST* a b c foo)
1095 ;;;       provided a, b, c are not splicing frobs
1096 ;;;  (APPEND (LIST* a b c) foo) => (LIST* a b (APPEND c foo))
1097 ;;;       provided a, b, c are not splicing frobs
1098 ;;;  (APPEND (QUOTE (x)) foo) => (LIST* (QUOTE x) foo)
1099 ;;;  (APPEND (CLOBBERABLE x) foo) => (NCONC x foo)
1100 (defun bq-simplify (x)
1101   (if (atom x)
1102       x
1103       (let ((x (if (eq (car x) *bq-quote*)
1104                    x
1105                    (maptree #'bq-simplify x))))
1106         (if (not (eq (car x) *bq-append*))
1107             x
1108             (bq-simplify-args x)))))
1109
1110 (defun bq-simplify-args (x)
1111   (do ((args (reverse (cdr x)) (cdr args))
1112        (result
1113          nil
1114          (cond ((atom (car args))
1115                 (bq-attach-append *bq-append* (car args) result))
1116                ((and (eq (caar args) *bq-list*)
1117                      (notany #'bq-splicing-frob (cdar args)))
1118                 (bq-attach-conses (cdar args) result))
1119                ((and (eq (caar args) *bq-list**)
1120                      (notany #'bq-splicing-frob (cdar args)))
1121                 (bq-attach-conses
1122                   (reverse (cdr (reverse (cdar args))))
1123                   (bq-attach-append *bq-append*
1124                                     (car (last (car args)))
1125                                     result)))
1126                ((and (eq (caar args) *bq-quote*)
1127                      (consp (cadar args))
1128                      (not (bq-frob (cadar args)))
1129                      (null (cddar args)))
1130                 (bq-attach-conses (list (list *bq-quote*
1131                                               (caadar args)))
1132                                   result))
1133                ((eq (caar args) *bq-clobberable*)
1134                 (bq-attach-append *bq-nconc* (cadar args) result))
1135                (t (bq-attach-append *bq-append*
1136                                     (car args)
1137                                     result)))))
1138       ((null args) result)))
1139
1140 (defun null-or-quoted (x)
1141   (or (null x) (and (consp x) (eq (car x) *bq-quote*))))
1142
1143 ;;; When BQ-ATTACH-APPEND is called, the OP should be #:BQ-APPEND
1144 ;;; or #:BQ-NCONC.  This produces a form (op item result) but
1145 ;;; some simplifications are done on the fly:
1146 ;;;
1147 ;;;  (op '(a b c) '(d e f g)) => '(a b c d e f g)
1148 ;;;  (op item 'nil) => item, provided item is not a splicable frob
1149 ;;;  (op item 'nil) => (op item), if item is a splicable frob
1150 ;;;  (op item (op a b c)) => (op item a b c)
1151 (defun bq-attach-append (op item result)
1152   (cond ((and (null-or-quoted item) (null-or-quoted result))
1153          (list *bq-quote* (append (cadr item) (cadr result))))
1154         ((or (null result) (equal result *bq-quote-nil*))
1155          (if (bq-splicing-frob item) (list op item) item))
1156         ((and (consp result) (eq (car result) op))
1157          (list* (car result) item (cdr result)))
1158         (t (list op item result))))
1159
1160 ;;; The effect of BQ-ATTACH-CONSES is to produce a form as if by
1161 ;;; `(LIST* ,@items ,result) but some simplifications are done
1162 ;;; on the fly.
1163 ;;;
1164 ;;;  (LIST* 'a 'b 'c 'd) => '(a b c . d)
1165 ;;;  (LIST* a b c 'nil) => (LIST a b c)
1166 ;;;  (LIST* a b c (LIST* d e f g)) => (LIST* a b c d e f g)
1167 ;;;  (LIST* a b c (LIST d e f g)) => (LIST a b c d e f g)
1168 (defun bq-attach-conses (items result)
1169   (cond ((and (every #'null-or-quoted items)
1170               (null-or-quoted result))
1171          (list *bq-quote*
1172                (append (mapcar #'cadr items) (cadr result))))
1173         ((or (null result) (equal result *bq-quote-nil*))
1174          (cons *bq-list* items))
1175         ((and (consp result)
1176               (or (eq (car result) *bq-list*)
1177                   (eq (car result) *bq-list**)))
1178          (cons (car result) (append items (cdr result))))
1179         (t (cons *bq-list** (append items (list result))))))
1180
1181 ;;; Removes funny tokens and changes (#:BQ-LIST* a b) into
1182 ;;; (CONS a b) instead of (LIST* a b), purely for readability.
1183 (defun bq-remove-tokens (x)
1184   (cond ((eq x *bq-list*) 'list)
1185         ((eq x *bq-append*) 'append)
1186         ((eq x *bq-nconc*) 'nconc)
1187         ((eq x *bq-list**) 'list*)
1188         ((eq x *bq-quote*) 'quote)
1189         ((atom x) x)
1190         ((eq (car x) *bq-clobberable*)
1191          (bq-remove-tokens (cadr x)))
1192         ((and (eq (car x) *bq-list**)
1193               (consp (cddr x))
1194               (null (cdddr x)))
1195          (cons 'cons (maptree #'bq-remove-tokens (cdr x))))
1196         (t (maptree #'bq-remove-tokens x))))
1197
1198 (define-transformation backquote (form)
1199   (bq-completely-process form))
1200
1201
1202 ;;; Primitives
1203
1204 (defvar *builtins* nil)
1205
1206 (defmacro define-raw-builtin (name args &body body)
1207   ;; Creates a new primitive function `name' with parameters args and
1208   ;; @body. The body can access to the local environment through the
1209   ;; variable *ENVIRONMENT*.
1210   `(push (list ',name (lambda ,args (block ,name ,@body)))
1211          *builtins*))
1212
1213 (defmacro define-builtin (name args &body body)
1214   `(define-raw-builtin ,name ,args
1215      (let ,(mapcar (lambda (arg) `(,arg (ls-compile ,arg))) args)
1216        ,@body)))
1217
1218 ;;; DECLS is a list of (JSVARNAME TYPE LISPFORM) declarations.
1219 (defmacro type-check (decls &body body)
1220   `(js!selfcall
1221      ,@(mapcar (lambda (decl)
1222                  `(code "var " ,(first decl) " = " ,(third decl) ";" *newline*))
1223                decls)
1224      ,@(mapcar (lambda (decl)
1225                  `(code "if (typeof " ,(first decl) " != '" ,(second decl) "')" *newline*
1226                         (indent "throw 'The value ' + "
1227                                 ,(first decl)
1228                                 " + ' is not a type "
1229                                 ,(second decl)
1230                                 ".';"
1231                                 *newline*)))
1232                decls)
1233      (code "return " (progn ,@body) ";" *newline*)))
1234
1235 ;;; VARIABLE-ARITY compiles variable arity operations. ARGS stands for
1236 ;;; a variable which holds a list of forms. It will compile them and
1237 ;;; store the result in some Javascript variables. BODY is evaluated
1238 ;;; with ARGS bound to the list of these variables to generate the
1239 ;;; code which performs the transformation on these variables.
1240
1241 (defun variable-arity-call (args function)
1242   (unless (consp args)
1243     (error "ARGS must be a non-empty list"))
1244   (let ((counter 0)
1245         (fargs '())
1246         (prelude ""))
1247     (dolist (x args)
1248       (cond
1249         ((floatp x) (push (float-to-string x) fargs))
1250         ((numberp x) (push (integer-to-string x) fargs))
1251         (t (let ((v (code "x" (incf counter))))
1252              (push v fargs)
1253              (concatf prelude
1254                (code "var " v " = " (ls-compile x) ";" *newline*
1255                      "if (typeof " v " !== 'number') throw 'Not a number!';"
1256                      *newline*))))))
1257     (js!selfcall prelude (funcall function (reverse fargs)))))
1258
1259
1260 (defmacro variable-arity (args &body body)
1261   (unless (symbolp args)
1262     (error "Bad usage of VARIABLE-ARITY, you must pass a symbol"))
1263   `(variable-arity-call ,args
1264                         (lambda (,args)
1265                           (code "return " ,@body ";" *newline*))))
1266
1267 (defun num-op-num (x op y)
1268   (type-check (("x" "number" x) ("y" "number" y))
1269     (code "x" op "y")))
1270
1271 (define-raw-builtin + (&rest numbers)
1272   (if (null numbers)
1273       "0"
1274       (variable-arity numbers
1275         (join numbers "+"))))
1276
1277 (define-raw-builtin - (x &rest others)
1278   (let ((args (cons x others)))
1279     (variable-arity args
1280       (if (null others)
1281           (concat "-" (car args))
1282           (join args "-")))))
1283
1284 (define-raw-builtin * (&rest numbers)
1285   (if (null numbers)
1286       "1"
1287       (variable-arity numbers
1288         (join numbers "*"))))
1289
1290 (define-raw-builtin / (x &rest others)
1291   (let ((args (cons x others)))
1292     (variable-arity args
1293       (if (null others)
1294           (concat "1 /" (car args))
1295           (join args "/")))))
1296
1297 (define-builtin mod (x y) (num-op-num x "%" y))
1298
1299
1300 (defun comparison-conjuntion (vars op)
1301   (cond
1302     ((null (cdr vars))
1303      "true")
1304     ((null (cddr vars))
1305      (concat (car vars) op (cadr vars)))
1306     (t
1307      (concat (car vars) op (cadr vars)
1308              " && "
1309              (comparison-conjuntion (cdr vars) op)))))
1310
1311 (defmacro define-builtin-comparison (op sym)
1312   `(define-raw-builtin ,op (x &rest args)
1313      (let ((args (cons x args)))
1314        (variable-arity args
1315          (js!bool (comparison-conjuntion args ,sym))))))
1316
1317 (define-builtin-comparison > ">")
1318 (define-builtin-comparison < "<")
1319 (define-builtin-comparison >= ">=")
1320 (define-builtin-comparison <= "<=")
1321 (define-builtin-comparison = "==")
1322
1323 (define-builtin numberp (x)
1324   (js!bool (code "(typeof (" x ") == \"number\")")))
1325
1326 (define-builtin floor (x)
1327   (type-check (("x" "number" x))
1328     "Math.floor(x)"))
1329
1330 (define-builtin expt (x y)
1331   (type-check (("x" "number" x)
1332                ("y" "number" y))
1333     "Math.pow(x, y)"))
1334
1335 (define-builtin float-to-string (x)
1336   (type-check (("x" "number" x))
1337     "x.toString()"))
1338
1339 (define-builtin cons (x y)
1340   (code "({car: " x ", cdr: " y "})"))
1341
1342 (define-builtin consp (x)
1343   (js!bool
1344    (js!selfcall
1345      "var tmp = " x ";" *newline*
1346      "return (typeof tmp == 'object' && 'car' in tmp);" *newline*)))
1347
1348 (define-builtin car (x)
1349   (js!selfcall
1350     "var tmp = " x ";" *newline*
1351     "return tmp === " (ls-compile nil)
1352     "? " (ls-compile nil)
1353     ": tmp.car;" *newline*))
1354
1355 (define-builtin cdr (x)
1356   (js!selfcall
1357     "var tmp = " x ";" *newline*
1358     "return tmp === " (ls-compile nil) "? "
1359     (ls-compile nil)
1360     ": tmp.cdr;" *newline*))
1361
1362 (define-builtin rplaca (x new)
1363   (type-check (("x" "object" x))
1364     (code "(x.car = " new ", x)")))
1365
1366 (define-builtin rplacd (x new)
1367   (type-check (("x" "object" x))
1368     (code "(x.cdr = " new ", x)")))
1369
1370 (define-builtin symbolp (x)
1371   (js!bool
1372    (js!selfcall
1373      "var tmp = " x ";" *newline*
1374      "return (typeof tmp == 'object' && 'name' in tmp);" *newline*)))
1375
1376 (define-builtin make-symbol (name)
1377   (type-check (("name" "string" name))
1378     "({name: name})"))
1379
1380 (define-builtin symbol-name (x)
1381   (code "(" x ").name"))
1382
1383 (define-builtin set (symbol value)
1384   (code "(" symbol ").value = " value))
1385
1386 (define-builtin fset (symbol value)
1387   (code "(" symbol ").fvalue = " value))
1388
1389 (define-builtin boundp (x)
1390   (js!bool (code "(" x ".value !== undefined)")))
1391
1392 (define-builtin symbol-value (x)
1393   (js!selfcall
1394     "var symbol = " x ";" *newline*
1395     "var value = symbol.value;" *newline*
1396     "if (value === undefined) throw \"Variable `\" + symbol.name + \"' is unbound.\";" *newline*
1397     "return value;" *newline*))
1398
1399 (define-builtin symbol-function (x)
1400   (js!selfcall
1401     "var symbol = " x ";" *newline*
1402     "var func = symbol.fvalue;" *newline*
1403     "if (func === undefined) throw \"Function `\" + symbol.name + \"' is undefined.\";" *newline*
1404     "return func;" *newline*))
1405
1406 (define-builtin symbol-plist (x)
1407   (code "((" x ").plist || " (ls-compile nil) ")"))
1408
1409 (define-builtin lambda-code (x)
1410   (code "(" x ").toString()"))
1411
1412 (define-builtin eq    (x y) (js!bool (code "(" x " === " y ")")))
1413 (define-builtin equal (x y) (js!bool (code "(" x  " == " y ")")))
1414
1415 (define-builtin char-to-string (x)
1416   (type-check (("x" "number" x))
1417     "String.fromCharCode(x)"))
1418
1419 (define-builtin stringp (x)
1420   (js!bool (code "(typeof(" x ") == \"string\")")))
1421
1422 (define-builtin string-upcase (x)
1423   (type-check (("x" "string" x))
1424     "x.toUpperCase()"))
1425
1426 (define-builtin string-length (x)
1427   (type-check (("x" "string" x))
1428     "x.length"))
1429
1430 (define-raw-builtin slice (string a &optional b)
1431   (js!selfcall
1432     "var str = " (ls-compile string) ";" *newline*
1433     "var a = " (ls-compile a) ";" *newline*
1434     "var b;" *newline*
1435     (when b (code "b = " (ls-compile b) ";" *newline*))
1436     "return str.slice(a,b);" *newline*))
1437
1438 (define-builtin char (string index)
1439   (type-check (("string" "string" string)
1440                ("index" "number" index))
1441     "string.charCodeAt(index)"))
1442
1443 (define-builtin concat-two (string1 string2)
1444   (type-check (("string1" "string" string1)
1445                ("string2" "string" string2))
1446     "string1.concat(string2)"))
1447
1448 (define-raw-builtin funcall (func &rest args)
1449   (js!selfcall
1450     "var f = " (ls-compile func) ";" *newline*
1451     "return (typeof f === 'function'? f: f.fvalue)("
1452     (join (cons (if *multiple-value-p* "values" "pv")
1453                 (mapcar #'ls-compile args))
1454           ", ")
1455     ")"))
1456
1457 (define-raw-builtin apply (func &rest args)
1458   (if (null args)
1459       (code "(" (ls-compile func) ")()")
1460       (let ((args (butlast args))
1461             (last (car (last args))))
1462         (js!selfcall
1463           "var f = " (ls-compile func) ";" *newline*
1464           "var args = [" (join (cons (if *multiple-value-p* "values" "pv")
1465                                      (mapcar #'ls-compile args))
1466                                ", ")
1467           "];" *newline*
1468           "var tail = (" (ls-compile last) ");" *newline*
1469           "while (tail != " (ls-compile nil) "){" *newline*
1470           "    args.push(tail.car);" *newline*
1471           "    tail = tail.cdr;" *newline*
1472           "}" *newline*
1473           "return (typeof f === 'function'? f : f.fvalue).apply(this, args);" *newline*))))
1474
1475 (define-builtin js-eval (string)
1476   (type-check (("string" "string" string))
1477     (if *multiple-value-p*
1478         (js!selfcall
1479           "var v = globalEval(string);" *newline*
1480           "if (typeof v !== 'object' || !('multiple-value' in v)){" *newline*
1481           (indent "v = [v];" *newline*
1482                   "v['multiple-value'] = true;" *newline*)
1483           "}" *newline*
1484           "return values.apply(this, v);" *newline*)
1485         "globalEval(string)")))
1486
1487 (define-builtin error (string)
1488   (js!selfcall "throw " string ";" *newline*))
1489
1490 (define-builtin new () "{}")
1491
1492 (define-builtin objectp (x)
1493   (js!bool (code "(typeof (" x ") === 'object')")))
1494
1495 (define-builtin oget (object key)
1496   (js!selfcall
1497     "var tmp = " "(" object ")[" key "];" *newline*
1498     "return tmp == undefined? " (ls-compile nil) ": tmp ;" *newline*))
1499
1500 (define-builtin oset (object key value)
1501   (code "((" object ")[" key "] = " value ")"))
1502
1503 (define-builtin in (key object)
1504   (js!bool (code "((" key ") in (" object "))")))
1505
1506 (define-builtin functionp (x)
1507   (js!bool (code "(typeof " x " == 'function')")))
1508
1509 (define-builtin write-string (x)
1510   (type-check (("x" "string" x))
1511     "lisp.write(x)"))
1512
1513 (define-builtin make-array (n)
1514   (js!selfcall
1515     "var r = [];" *newline*
1516     "for (var i = 0; i < " n "; i++)" *newline*
1517     (indent "r.push(" (ls-compile nil) ");" *newline*)
1518     "return r;" *newline*))
1519
1520 (define-builtin arrayp (x)
1521   (js!bool
1522    (js!selfcall
1523      "var x = " x ";" *newline*
1524      "return typeof x === 'object' && 'length' in x;")))
1525
1526 (define-builtin aref (array n)
1527   (js!selfcall
1528     "var x = " "(" array ")[" n "];" *newline*
1529     "if (x === undefined) throw 'Out of range';" *newline*
1530     "return x;" *newline*))
1531
1532 (define-builtin aset (array n value)
1533   (js!selfcall
1534     "var x = " array ";" *newline*
1535     "var i = " n ";" *newline*
1536     "if (i < 0 || i >= x.length) throw 'Out of range';" *newline*
1537     "return x[i] = " value ";" *newline*))
1538
1539 (define-builtin get-internal-real-time ()
1540   "(new Date()).getTime()")
1541
1542 (define-builtin values-array (array)
1543   (if *multiple-value-p*
1544       (code "values.apply(this, " array ")")
1545       (code "pv.apply(this, " array ")")))
1546
1547 (define-raw-builtin values (&rest args)
1548   (if *multiple-value-p*
1549       (code "values(" (join (mapcar #'ls-compile args) ", ") ")")
1550       (code "pv(" (join (mapcar #'ls-compile args) ", ") ")")))
1551
1552 ;; Receives the JS function as first argument as a literal string. The
1553 ;; second argument is compiled and should evaluate to a vector of
1554 ;; values to apply to the the function. The result returned.
1555 (define-builtin %js-call (fun args)
1556   (code fun ".apply(this, " args ")"))
1557
1558 (defun macro (x)
1559   (and (symbolp x)
1560        (let ((b (lookup-in-lexenv x *environment* 'function)))
1561          (if (and b (eq (binding-type b) 'macro))
1562              b
1563              nil))))
1564
1565 #+common-lisp
1566 (defvar *macroexpander-cache*
1567   (make-hash-table :test #'eq))
1568
1569 (defun ls-macroexpand-1 (form)
1570   (cond
1571     ((symbolp form)
1572      (let ((b (lookup-in-lexenv form *environment* 'variable)))
1573        (if (and b (eq (binding-type b) 'macro))
1574            (values (binding-value b) t)
1575            (values form nil))))
1576     ((consp form)
1577      (let ((macro-binding (macro (car form))))
1578        (if macro-binding
1579            (let ((expander (binding-value macro-binding)))
1580              (cond
1581                #+common-lisp
1582                ((gethash macro-binding *macroexpander-cache*)
1583                 (setq expander (gethash macro-binding *macroexpander-cache*)))
1584                ((listp expander)
1585                 (let ((compiled (eval expander)))
1586                   ;; The list representation are useful while
1587                   ;; bootstrapping, as we can dump the definition of the
1588                   ;; macros easily, but they are slow because we have to
1589                   ;; evaluate them and compile them now and again. So, let
1590                   ;; us replace the list representation version of the
1591                   ;; function with the compiled one.
1592                   ;;
1593                   #+jscl (setf (binding-value macro-binding) compiled)
1594                   #+common-lisp (setf (gethash macro-binding *macroexpander-cache*) compiled)
1595                   (setq expander compiled))))
1596              (values (apply expander (cdr form)) t))
1597            (values form nil))))
1598     (t
1599      (values form nil))))
1600
1601 (defun compile-funcall (function args)
1602   (let* ((values-funcs (if *multiple-value-p* "values" "pv"))
1603          (arglist (concat "(" (join (cons values-funcs (mapcar #'ls-compile args)) ", ") ")")))
1604     (unless (or (symbolp function)
1605                 (and (consp function)
1606                      (eq (car function) 'lambda)))
1607       (error "Bad function"))
1608     (cond
1609       ((translate-function function)
1610        (concat (translate-function function) arglist))
1611       ((and (symbolp function)
1612             #+jscl (eq (symbol-package function) (find-package "COMMON-LISP"))
1613             #+common-lisp t)
1614        (code (ls-compile `',function) ".fvalue" arglist))
1615       (t
1616        (code (ls-compile `#',function) arglist)))))
1617
1618 (defun ls-compile-block (sexps &optional return-last-p)
1619   (if return-last-p
1620       (code (ls-compile-block (butlast sexps))
1621             "return " (ls-compile (car (last sexps)) *multiple-value-p*) ";")
1622       (join-trailing
1623        (remove-if #'null-or-empty-p (mapcar #'ls-compile sexps))
1624        (concat ";" *newline*))))
1625
1626 (defun ls-compile (sexp &optional multiple-value-p)
1627   (multiple-value-bind (sexp expandedp) (ls-macroexpand-1 sexp)
1628     (when expandedp
1629       (return-from ls-compile (ls-compile sexp multiple-value-p)))
1630     ;; The expression has been macroexpanded. Now compile it!
1631     (let ((*multiple-value-p* multiple-value-p))
1632       (cond
1633         ((symbolp sexp)
1634          (let ((b (lookup-in-lexenv sexp *environment* 'variable)))
1635            (cond
1636              ((and b (not (member 'special (binding-declarations b))))
1637               (binding-value b))
1638              ((or (keywordp sexp)
1639                   (and b (member 'constant (binding-declarations b))))
1640               (code (ls-compile `',sexp) ".value"))
1641              (t
1642               (ls-compile `(symbol-value ',sexp))))))
1643         ((integerp sexp) (integer-to-string sexp))
1644         ((floatp sexp) (float-to-string sexp))
1645         ((stringp sexp) (code "\"" (escape-string sexp) "\""))
1646         ((arrayp sexp) (literal sexp))
1647         ((listp sexp)
1648          (let ((name (car sexp))
1649                (args (cdr sexp)))
1650            (cond
1651              ;; Special forms
1652              ((assoc name *compilations*)
1653               (let ((comp (second (assoc name *compilations*))))
1654                 (apply comp args)))
1655              ;; Built-in functions
1656              ((and (assoc name *builtins*)
1657                    (not (claimp name 'function 'notinline)))
1658               (let ((comp (second (assoc name *builtins*))))
1659                 (apply comp args)))
1660              (t
1661               (compile-funcall name args)))))
1662         (t
1663          (error (concat "How should I compile " (prin1-to-string sexp) "?")))))))
1664
1665
1666 (defvar *compile-print-toplevels* nil)
1667
1668 (defun truncate-string (string &optional (width 60))
1669   (let ((n (or (position #\newline string)
1670                (min width (length string)))))
1671     (subseq string 0 n)))
1672
1673 (defun ls-compile-toplevel (sexp &optional multiple-value-p)
1674   (let ((*toplevel-compilations* nil))
1675     (cond
1676       ((and (consp sexp) (eq (car sexp) 'progn))
1677        (let ((subs (mapcar (lambda (s)
1678                              (ls-compile-toplevel s t))
1679                            (cdr sexp))))
1680          (join (remove-if #'null-or-empty-p subs))))
1681       (t
1682        (when *compile-print-toplevels*
1683          (let ((form-string (prin1-to-string sexp)))
1684            (write-string "Compiling ")
1685            (write-string (truncate-string form-string))
1686            (write-line "...")))
1687
1688        (let ((code (ls-compile sexp multiple-value-p)))
1689          (code (join-trailing (get-toplevel-compilations)
1690                               (code ";" *newline*))
1691                (when code
1692                  (code code ";" *newline*))))))))