Added JS* and JS-INLINE*.
[clinton/parenscript.git] / js.lisp
CommitLineData
8e198a08
MB
1(in-package :js)
2
3;;; ecmascript standard:
4;;; http://www.ecma-international.org/publications/standards/Ecma-262.htm
5
6;;; javascript name conversion
7
8(defparameter *special-chars*
9 '((#\! . "Bang")
10 (#\? . "What")
11 (#\# . "Hash")
12 (#\$ . "Dollar")
13 (#\@ . "At")
14 (#\% . "Percent")
15 (#\+ . "Plus")
16 (#\* . "Star")
17 (#\/ . "Slash")))
18
19(defun string-chars (string)
20 (coerce string 'list))
21
22(defun constant-string-p (string)
23 (let ((len (length string))
24 (constant-chars '(#\+ #\*)))
25 (and (> len 2)
26 (member (char string 0) constant-chars)
27 (member (char string (1- len)) constant-chars))))
28
29(defun first-uppercase-p (string)
30 (and (> (length string) 1)
31 (member (char string 0) '(#\+ #\*))))
32
33(defun symbol-to-js (symbol)
34 (when (symbolp symbol)
35 (setf symbol (symbol-name symbol)))
36 (let ((symbols (string-split symbol '(#\.))))
37 (cond ((null symbols) "")
38 ((= (length symbols) 1)
39 (let (res
40 (lowercase t)
41 (all-uppercase nil))
42 (cond ((constant-string-p symbol)
43 (setf all-uppercase t
44 symbol (subseq symbol 1 (1- (length symbol)))))
45 ((first-uppercase-p symbol)
46 (setf lowercase nil
47 symbol (subseq symbol 1))))
48 (flet ((reschar (c)
49 (push (if (and lowercase (not all-uppercase))
50 (char-downcase c)
51 (char-upcase c)) res)
52 (setf lowercase t)))
53 (dotimes (i (length symbol))
54 (let ((c (char symbol i)))
55 (cond
56 ((eql c #\-)
57 (setf lowercase (not lowercase)))
58 ((assoc c *special-chars*)
59 (dolist (i (coerce (cdr (assoc c *special-chars*)) 'list))
60 (reschar i)))
61 (t (reschar c))))))
62 (coerce (nreverse res) 'string)))
63 (t (string-join (mapcar #'symbol-to-js symbols) ".")))))
64
65;;; js language types
66
67(defgeneric js-equal (obj1 obj2))
68(defmethod js-equal ((obj1 list) (obj2 list))
69 (and (= (length obj1) (length obj2))
70 (every #'js-equal obj1 obj2)))
71(defmethod js-equal ((obj1 t) (obj2 t))
72 (equal obj1 obj2))
73
74(defmacro defjsclass (name superclasses slots &rest class-options)
75 (let ((slot-names (mapcar #'(lambda (slot) (if (atom slot) slot (first slot))) slots)))
76 `(progn
77 (defclass ,name ,superclasses
78 ,slots ,@class-options)
79 (defmethod js-equal ((obj1 ,name) (obj2 ,name))
80 (every #'(lambda (slot)
81 (js-equal (slot-value obj1 slot)
82 (slot-value obj2 slot)))
83 ',slot-names)))))
84
85(defjsclass statement ()
86 ((value :initarg :value :accessor value :initform nil)))
87
88(defjsclass expression (statement)
89 ((value)))
90
91;;; indenter
92
93(defun special-append-to-last (form elt)
94 (flet ((special-append (form elt)
95 (let ((len (length form)))
96 (if (and (> len 0)
97 (member (char form (1- len))
98 '(#\; #\, #\})))
99 form
100 (concatenate 'string form elt)))))
101 (cond ((stringp form)
102 (special-append form elt))
103 ((consp form)
104 (let ((last (last form)))
105 (if (stringp (car last))
106 (rplaca last (special-append (car last) elt))
107 (append-to-last (car last) elt))
108 form))
109 (t (error "unsupported form ~S" form)))))
110
111(defun dwim-join (value-string-lists max-length
112 &key start end
113 join-before join-after
114 white-space (separator " ")
115 (append-to-last #'append-to-last)
116 (collect t))
117 #+nil
118 (format t "value-string-lists: ~S~%" value-string-lists)
119
120 (unless start
121 (setf start ""))
122
123 (unless join-before
124 (setf join-before ""))
125
126 ;;; collect single value-string-lists until line full
127
128 (do* ((string-lists value-string-lists (cdr string-lists))
129 (string-list (car string-lists) (car string-lists))
130 (cur-elt start)
131 (cur-empty t)
132 (white-space (or white-space (make-string (length start) :initial-element #\Space)))
133 (res nil))
134 ((null string-lists)
135 (unless cur-empty
136 (push cur-elt res))
137 (if (null res)
138 (list (concatenate 'string start end))
139 (progn
140 (when end
141 (setf (first res)
142 (funcall append-to-last (first res) end)))
143 (nreverse res))))
144
145 #+nil
146 (format t "string-list: ~S~%" string-list)
147
148 (when join-after
149 (unless (null (cdr string-lists))
150 (funcall append-to-last string-list join-after)))
151
152 (if (and collect (= (length string-list) 1))
153 (progn
154 #+nil
155 (format t "cur-elt: ~S line-length ~D, max-length ~D, string: ~S~%"
156 cur-elt
157 (+ (length (first string-list))
158 (length cur-elt))
159 max-length
160 (first string-list))
161 (if (or cur-empty
162 (< (+ (length (first string-list))
163 (length cur-elt)) max-length))
164 (setf cur-elt
165 (concatenate 'string cur-elt
166 (if cur-empty "" (concatenate 'string separator join-before))
167 (first string-list))
168 cur-empty nil)
169 (progn
170 (push cur-elt res)
171 (setf cur-elt (concatenate 'string white-space
172 join-before (first string-list))
173 cur-empty nil))))
174
175 (progn
176 (unless cur-empty
177 (push cur-elt res)
178 (setf cur-elt white-space
179 cur-empty t))
180 (setf res (nconc (nreverse
181 (cons (concatenate 'string
182 cur-elt (if (null res)
183 "" join-before)
184 (first string-list))
185 (mapcar #'(lambda (x) (concatenate 'string white-space x))
186 (cdr string-list)))) res))
187 (setf cur-elt white-space cur-empty t)))))
188
189(defmethod js-to-strings ((expression expression) start-pos)
30b3e3eb 190 (declare (ignore start-pos))
8e198a08
MB
191 (list (princ-to-string (value expression))))
192
193(defmethod js-to-statement-strings ((expression expression) start-pos)
194 (js-to-strings expression start-pos))
195
196(defmethod js-to-statement-strings ((statement statement) start-pos)
30b3e3eb 197 (declare (ignore start-pos))
8e198a08
MB
198 (list (princ-to-string (value statement))))
199
200;;; compiler macros
201
202(eval-when (:compile-toplevel :load-toplevel :execute)
203 (defvar *js-compiler-macros* (make-hash-table)
204 "*JS-COMPILER-MACROS* is a hash-table containing the functions corresponding
205to javascript special forms, indexed by their name. Javascript special
206forms are compiler macros for JS expressions."))
207
208(defmacro define-js-compiler-macro (name lambda-list &rest body)
209 "Define a javascript compiler macro NAME. Arguments are destructured
210according to LAMBDA-LIST. The resulting JS language types are appended
211to the ongoing javascript compilation."
212 (let ((js-name (intern (concatenate 'string "JS-" (symbol-name name)) #.*package*)))
213 `(eval-when (:compile-toplevel :load-toplevel :execute)
214 (defun ,js-name ,lambda-list ,@body)
215 (setf (gethash ',name *js-compiler-macros*) #',js-name))))
216
217(defun js-compiler-macro-form-p (form)
218 (when (gethash (car form) *js-compiler-macros*)
219 t))
220
221(defun js-get-compiler-macro (name)
222 (gethash name *js-compiler-macros*))
223
224;;; macro expansion
225
226(eval-when (:compile-toplevel :load-toplevel :execute)
227 (defvar *js-macro-toplevel* (make-hash-table)
228 "Toplevel of macro expansion, holds all the toplevel javascript macros.")
229 (defvar *js-macro-env* (list *js-macro-toplevel*)
230 "Current macro environment."))
231
232(defun lookup-macro (name)
233 "Lookup the macro NAME in the current macro expansion
234environment. Returns the macro and the parent macro environment of
235this macro."
236 (do ((env *js-macro-env* (cdr env)))
237 ((null env) nil)
238 (let ((val (gethash name (car env))))
239 (when val
240 (return-from lookup-macro
241 (values val (or (cdr env)
242 (list *js-macro-toplevel*))))))))
243
244(defmacro defjsmacro (name args &rest body)
245 "Define a javascript macro, and store it in the toplevel macro environment."
246 (when (gethash name *js-compiler-macros*)
247 (warn "Redefining compiler macro ~S" name)
248 (remhash name *js-compiler-macros*))
249 (let ((lambda-list (gensym)))
250 `(setf (gethash ',name *js-macro-toplevel*)
251 #'(lambda (&rest ,lambda-list)
252 (destructuring-bind ,args ,lambda-list ,@body)))))
253
254(defun js-expand-form (expr)
255 "Expand a javascript form."
256 (cond ((atom expr)
257 (multiple-value-bind (js-macro macro-env)
258 (lookup-macro expr)
259 (if js-macro
260 (js-expand-form (let ((*js-macro-env* macro-env))
261 (funcall js-macro)))
262 expr)))
263
264 ((js-compiler-macro-form-p expr) expr)
265
266 ((equal (first expr) 'quote) expr)
267
268 (t (let ((js-macro (lookup-macro (car expr))))
269 (if js-macro
270 (js-expand-form (apply js-macro (cdr expr)))
271 expr)))))
272
273(defvar *var-counter* 0)
274
275(defun js-gensym (&optional (name "js"))
276 (intern (format nil "tmp-~A-~A" name (incf *var-counter*)) #.*package*))
277
278;;; literals
279
280(defmacro defjsliteral (name string)
281 "Define a Javascript literal that will expand to STRING."
282 `(define-js-compiler-macro ,name () (make-instance 'expression :value ,string)))
283
284(defjsliteral this "this")
285(defjsliteral t "true")
286(defjsliteral nil "null")
287(defjsliteral false "false")
288(defjsliteral undefined "undefined")
289
290(defmacro defjskeyword (name string)
291 "Define a Javascript keyword that will expand to STRING."
292 `(define-js-compiler-macro ,name () (make-instance 'statement :value ,string)))
293
294(defjskeyword break "break")
295(defjskeyword continue "continue")
296
297;;; array literals
298
299(defjsclass array-literal (expression)
300 ((values :initarg :values :accessor array-values)))
301
302(define-js-compiler-macro array (&rest values)
303 (make-instance 'array-literal
304 :values (mapcar #'js-compile-to-expression values)))
305
306(defjsmacro list (&rest values)
307 `(array ,@values))
308
309(defmethod js-to-strings ((array array-literal) start-pos)
310 (let ((value-string-lists
311 (mapcar #'(lambda (x) (js-to-strings x (+ start-pos 2)))
312 (array-values array)))
313 (max-length (- 80 start-pos 2)))
314 (dwim-join value-string-lists max-length
315 :start "[ " :end " ]"
316 :join-after ",")))
317
318(defjsclass js-aref (expression)
319 ((array :initarg :array
320 :accessor aref-array)
321 (index :initarg :index
322 :accessor aref-index)))
323
324(define-js-compiler-macro aref (array &rest coords)
325 (make-instance 'js-aref
326 :array (js-compile-to-expression array)
327 :index (mapcar #'js-compile-to-expression coords)))
328
329(defmethod js-to-strings ((aref js-aref) start-pos)
330 (dwim-join (cons (js-to-strings (aref-array aref) start-pos)
331 (mapcar #'(lambda (x) (dwim-join (list (js-to-strings x (+ start-pos 2)))
332 (- 80 start-pos 2)
333 :start "[" :end "]"))
334 (aref-index aref)))
335 (- 80 start-pos 2) :separator ""
336 :white-space " "))
337
338(defjsmacro make-array (&rest inits)
339 `(new (*array ,@inits)))
340
341;;; string literals
342
343(defjsclass string-literal (expression)
344 (value))
345
346(defmethod js-to-strings ((string string-literal) start-pos)
347 (declare (ignore start-pos))
02747605 348 (list (format nil "'~A'" (value string))))
8e198a08
MB
349
350;;; number literals
351
352(defjsclass number-literal (expression)
353 (value))
354
355;;; variables
356
357(defjsclass js-variable (expression)
358 (value))
359
360(defmethod js-to-strings ((v js-variable) start-form)
30b3e3eb 361 (declare (ignore start-form))
8e198a08
MB
362 (list (symbol-to-js (value v))))
363
364;;; arithmetic operators
365
366(eval-when (:compile-toplevel :load-toplevel :execute)
367
368 (defparameter *op-precedence-hash* (make-hash-table))
369
370 (defparameter *op-precedences*
371 '((aref)
372 (slot-value)
373 (! not ~)
374 (* / %)
375 (+ -)
376 (<< >>)
377 (>>>)
378 (< > <= >=)
379 (in if)
380 (eql == != =)
381 (=== !==)
382 (&)
383 (^)
384 (\|)
385 (\&\& and)
386 (\|\| or)
387 (setf *= /= %= += -= <<= >>= >>>= \&= ^= \|=)
388 (comma)))
389
390 ;;; generate the operator precedences from *OP-PRECEDENCES*
391 (let ((precedence 1))
392 (dolist (ops *op-precedences*)
393 (dolist (op ops)
394 (setf (gethash op *op-precedence-hash*) precedence))
395 (incf precedence))))
396
397(defun js-convert-op-name (op)
398 (case op
399 (and '\&\&)
400 (or '\|\|)
401 (not '!)
402 (eql '\=\=)
403 (= '\=\=)
404 (t op)))
405
406(defjsclass op-form (expression)
407 ((operator :initarg :operator :accessor operator)
408 (args :initarg :args :accessor op-args)))
409
410(defun op-form-p (form)
411 (and (listp form)
412 (not (js-compiler-macro-form-p form))
413 (not (null (gethash (first form) *op-precedence-hash*)))))
414
415(defun klammer (string-list)
416 (prepend-to-first string-list "(")
417 (append-to-last string-list ")")
418 string-list)
419
420(defmethod expression-precedence ((expression expression))
421 0)
422
423(defmethod expression-precedence ((form op-form))
424 (gethash (operator form) *op-precedence-hash*))
425
426(defmethod js-to-strings ((form op-form) start-pos)
427 (let* ((precedence (expression-precedence form))
428 (value-string-lists
429 (mapcar #'(lambda (x)
430 (let ((string-list (js-to-strings x (+ start-pos 2))))
431 (if (>= (expression-precedence x) precedence)
432 (klammer string-list)
433 string-list)))
434 (op-args form)))
435 (max-length (- 80 start-pos 2))
436 (op-string (format nil "~A " (operator form))))
437 (dwim-join value-string-lists max-length :join-before op-string)))
438
439(defjsmacro 1- (form)
440 `(- ,form 1))
441
442(defjsmacro 1+ (form)
443 `(+ ,form 1))
444
445(defjsclass one-op (expression)
446 ((pre-p :initarg :pre-p
447 :initform nil
448 :accessor one-op-pre-p)
449 (op :initarg :op
450 :accessor one-op)))
451
452(defmethod js-to-strings ((one-op one-op) start-pos)
453 (let* ((value (value one-op))
454 (value-strings (js-to-strings value start-pos)))
455 (when (typep value 'op-form)
456 (setf value-strings (klammer value-strings)))
457 (if (one-op-pre-p one-op)
458 (prepend-to-first value-strings
459 (one-op one-op))
460 (append-to-last value-strings
461 (one-op one-op)))))
462
463(define-js-compiler-macro incf (x)
464 (make-instance 'one-op :pre-p t :op "++"
465 :value (js-compile-to-expression x)))
466(define-js-compiler-macro ++ (x)
467 (make-instance 'one-op :pre-p nil :op "++"
468 :value (js-compile-to-expression x)))
469(define-js-compiler-macro decf (x)
470 (make-instance 'one-op :pre-p t :op "--"
471 :value (js-compile-to-expression x)))
472(define-js-compiler-macro -- (x)
473 (make-instance 'one-op :pre-p nil :op "--"
474 :value (js-compile-to-expression x)))
475
476
477(define-js-compiler-macro not (x)
478 (let ((value (js-compile-to-expression x)))
479 (if (and (typep value 'op-form)
480 (= (length (op-args value)) 2))
481 (let ((new-op (case (operator value)
482 (== '!=)
483 (< '>=)
484 (> '<=)
485 (<= '>)
486 (>= '<)
487 (!= '==)
488 (=== '!==)
489 (!== '===)
490 (t nil))))
491 (if new-op
492 (make-instance 'op-form :operator new-op
493 :args (op-args value))
494 (make-instance 'one-op :pre-p t :op "!"
495 :value value)))
496 (make-instance 'one-op :pre-p t :op "!"
497 :value value))))
498
499;;; function calls
500
501(defjsclass function-call (expression)
502 ((function :initarg :function :accessor f-function)
503 (args :initarg :args :accessor f-args)))
504
505(defun funcall-form-p (form)
506 (and (listp form)
507 (not (op-form-p form))
508 (not (js-compiler-macro-form-p form))))
509
510(defmethod js-to-strings ((form function-call) start-pos)
511 (let* ((value-string-lists
512 (mapcar #'(lambda (x) (js-to-strings x (+ start-pos 2)))
513 (f-args form)))
514 (max-length (- 80 start-pos 2))
515 (args (dwim-join value-string-lists max-length
516 :start "(" :end ")" :join-after ",")))
12ac1f25
MB
517 (dwim-join (typecase (f-function form)
518 (js-defun (list (list "(")
519 (js-to-strings (f-function form) (+ start-pos 2))
520 (list ")")
521 args))
522 (t (list (js-to-strings (f-function form) (+ start-pos 2))
523 args)))
8e198a08
MB
524 max-length
525 :separator "")))
526
527(defjsclass method-call (expression)
528 ((method :initarg :method :accessor m-method)
529 (object :initarg :object :accessor m-object)
530 (args :initarg :args :accessor m-args)))
531
532(defmethod js-to-strings ((form method-call) start-pos)
533 (let ((fname (dwim-join (list (js-to-strings (m-object form) (+ start-pos 2))
534 (list (symbol-to-js (m-method form))))
535 (- 80 start-pos 2)
536 :end "("
537 :separator "")))
538 (let ((butlast (butlast fname))
539 (last (car (last fname))))
540 (nconc butlast
541 (dwim-join (mapcar #'(lambda (x) (js-to-strings x (+ start-pos 2)))
542 (m-args form))
543 (- 80 start-pos 2)
544 :start last
545 :end ")"
546 :join-after ",")))))
547
548(defun method-call-p (form)
549 (and (funcall-form-p form)
550 (symbolp (first form))
551 (eql (char (symbol-name (first form)) 0) #\.)))
552
553;;; body forms
554
555(defjsclass js-body (expression)
556 ((stmts :initarg :stmts :accessor b-stmts)
557 (indent :initarg :indent :initform "" :accessor b-indent)))
558
559(define-js-compiler-macro progn (&rest body)
560 (make-instance 'js-body
561 :stmts (mapcar #'js-compile-to-statement body)))
562
563(defmethod initialize-instance :after ((body js-body) &rest initargs)
564 (declare (ignore initargs))
565 (let* ((stmts (b-stmts body))
566 (last (last stmts))
567 (last-stmt (car last)))
568 (when (typep last-stmt 'js-body)
569 (setf (b-stmts body)
570 (nconc (butlast stmts)
571 (b-stmts last-stmt))))))
572
573
574(defmethod js-to-statement-strings ((body js-body) start-pos)
575 (dwim-join (mapcar #'(lambda (x) (js-to-statement-strings x (+ start-pos 2)))
576 (b-stmts body))
577 (- 80 start-pos 2)
578 :join-after ";"
579 :append-to-last #'special-append-to-last
580 :start (b-indent body) :collect nil
581 :end ";"))
582
583(defmethod js-to-strings ((body js-body) start-pos)
584 (dwim-join (mapcar #'(lambda (x) (js-to-strings x (+ start-pos 2)))
585 (b-stmts body))
586 (- 80 start-pos 2)
587 :append-to-last #'special-append-to-last
588 :join-after ","
589 :start (b-indent body)))
590
591(defjsclass js-sub-body (js-body)
592 (stmts indent))
593
594(defmethod js-to-statement-strings ((body js-sub-body) start-pos)
30b3e3eb 595 (declare (ignore start-pos))
8e198a08
MB
596 (nconc (list "{") (call-next-method) (list "}")))
597
598(defmethod expression-precedence ((body js-body))
599 (if (= (length (b-stmts body)) 1)
600 (expression-precedence (first (b-stmts body)))
601 (gethash 'comma *op-precedence-hash*)))
602
603;;; function definition
604
605(defjsclass js-defun (expression)
606 ((name :initarg :name :accessor d-name)
607 (args :initarg :args :accessor d-args)
608 (body :initarg :body :accessor d-body)))
609
610(define-js-compiler-macro defun (name args &rest body)
611 (make-instance 'js-defun
612 :name (js-compile-to-symbol name)
613 :args (mapcar #'js-compile-to-symbol args)
614 :body (make-instance 'js-body
615 :indent " "
616 :stmts (mapcar #'js-compile-to-statement body))))
617
618(defmethod js-to-strings ((defun js-defun) start-pos)
619 (let ((fun-header (dwim-join (mapcar #'(lambda (x) (list (symbol-to-js x)))
620 (d-args defun))
621 (- 80 start-pos 2)
622 :start (format nil "function ~A("
623 (symbol-to-js (d-name defun)))
624 :end ") {" :join-after ","))
625 (fun-body (js-to-statement-strings (d-body defun) (+ start-pos 2))))
626 (nconc fun-header fun-body (list "}"))))
627
628(defmethod js-to-statement-strings ((defun js-defun) start-pos)
629 (js-to-strings defun start-pos))
630
631(defjsmacro lambda (args &rest body)
632 `(defun :|| ,args ,@body))
633
634;;; object creation
635
636(defjsclass js-object (expression)
637 ((slots :initarg :slots
638 :accessor o-slots)))
639
640(define-js-compiler-macro create (&rest args)
641 (make-instance 'js-object
642 :slots (loop for (name val) on args by #'cddr
643 collect (list (js-compile-to-symbol name)
644 (js-compile-to-expression val)))))
645
646(defmethod js-to-strings ((object js-object) start-pos)
647 (let ((value-string-lists
648 (mapcar #'(lambda (slot)
649 (dwim-join (list (js-to-strings (second slot) (+ start-pos 4)))
650 (- 80 start-pos 2)
651 :start (concatenate 'string (symbol-to-js (first slot)) " : ")
652 :white-space " ")) (o-slots object)))
653 (max-length (- 80 start-pos 2)))
654 (dwim-join value-string-lists max-length
655 :start "{ "
656 :end " }"
657 :join-after ", "
658 :white-space " "
659 :collect nil)))
660
661(defjsclass js-slot-value (expression)
662 ((object :initarg :object
663 :accessor sv-object)
664 (slot :initarg :slot
665 :accessor sv-slot)))
666
667(define-js-compiler-macro slot-value (obj slot)
668 (make-instance 'js-slot-value :object (js-compile-to-expression obj)
669 :slot (js-compile-to-symbol slot)))
670
671(defmethod js-to-strings ((sv js-slot-value) start-pos)
672 (append-to-last (js-to-strings (sv-object sv) start-pos)
673 (format nil ".~A" (symbol-to-js (sv-slot sv)))))
674
675(defjsmacro with-slots (slots object &rest body)
676 `(symbol-macrolet ,(mapcar #'(lambda (slot)
677 `(,slot '(slot-value ,object ',slot)))
678 slots)
679 ,@body))
680
681;;; macros
682
683(define-js-compiler-macro macrolet (macros &rest body)
684 (let* ((macro-env (make-hash-table))
685 (*js-macro-env* (cons macro-env *js-macro-env*)))
686 (dolist (macro macros)
687 (destructuring-bind (name arglist &rest body) macro
688 (setf (gethash name macro-env)
689 (compile nil `(lambda ,arglist ,@body)))))
690 (js-compile `(progn ,@body))))
691
692(defjsmacro symbol-macrolet (macros &rest body)
693 `(macrolet ,(mapcar #'(lambda (macro)
694 `(,(first macro) () ,@(rest macro))) macros)
695 ,@body))
696
697;;; lisp eval
698
699(defjsmacro lisp (&rest forms)
700 (eval (cons 'progn forms)))
701
702;;; if
703
704(defjsclass js-if (expression)
705 ((test :initarg :test
706 :accessor if-test)
707 (then :initarg :then
708 :accessor if-then)
709 (else :initarg :else
710 :accessor if-else)))
711
712(define-js-compiler-macro if (test then &optional else)
713 (make-instance 'js-if :test (js-compile-to-expression test)
714 :then (js-compile-to-body then :indent " ")
715 :else (when else
716 (js-compile-to-body else :indent " "))))
717
718(defmethod initialize-instance :after ((if js-if) &rest initargs)
719 (declare (ignore initargs))
720 (when (and (if-then if)
721 (typep (if-then if) 'js-sub-body))
722 (change-class (if-then if) 'js-body))
723 (when (and (if-else if)
724 (typep (if-else if) 'js-sub-body))
725 (change-class (if-else if) 'js-body)))
726
727(defmethod js-to-statement-strings ((if js-if) start-pos)
728 (let ((if-strings (dwim-join (list (js-to-strings (if-test if) 0))
729 (- 80 start-pos 2)
730 :start "if ("
731 :end ") {"))
732 (then-strings (js-to-statement-strings (if-then if) (+ start-pos 2)))
733 (else-strings (when (if-else if)
734 (js-to-statement-strings (if-else if)
735 (+ start-pos 2)))))
736 (nconc if-strings then-strings (if else-strings
737 (nconc (list "} else {") else-strings (list "}"))
738 (list "}")))))
739
740(defmethod expression-precedence ((if js-if))
741 (gethash 'if *op-precedence-hash*))
742
743(defmethod js-to-strings ((if js-if) start-pos)
744 (assert (typep (if-then if) 'expression))
745 (when (if-else if)
746 (assert (typep (if-else if) 'expression)))
747 (dwim-join (list (append-to-last (js-to-strings (if-test if) start-pos) " ?")
748 (let* ((new-then (make-instance 'js-body
749 :stmts (b-stmts (if-then if))
750 :indent ""))
751 (res (js-to-strings new-then start-pos)))
752 (if (>= (expression-precedence (if-then if))
753 (expression-precedence if))
754 (klammer res)
755 res))
756 (list ":")
757 (if (if-else if)
758 (let* ((new-else (make-instance 'js-body
759 :stmts (b-stmts (if-else if))
760 :indent ""))
761 (res (js-to-strings new-else start-pos)))
762 (if (>= (expression-precedence (if-else if))
763 (expression-precedence if))
764 (klammer res)
765 res))
766 (list "undefined")))
767 (- 80 start-pos 2)
768 :white-space " "))
769
770(defjsmacro when (test &rest body)
771 `(if ,test (progn ,@body)))
772
773(defjsmacro unless (test &rest body)
774 `(if (not ,test) (progn ,@body)))
775
776;;; single keyword expressions and statements
777
778(defmacro define-js-single-op (name &optional (superclass 'expression))
779 (let ((js-name (intern (concatenate 'string "JS-" (symbol-name name)) #.*package*)))
780 `(progn
781 (defjsclass ,js-name (,superclass)
782 (value))
783 (define-js-compiler-macro ,name (value)
784 (make-instance ',js-name :value (js-compile-to-expression value)))
785 (defmethod ,(if (eql superclass 'expression)
786 'js-to-strings
787 'js-to-statement-strings) ((,name ,js-name) start-pos)
788 (dwim-join (list (js-to-strings (value ,name) (+ start-pos 2)))
789 (- 80 start-pos 2)
790 :start ,(concatenate 'string (string-downcase (symbol-name name)) " ")
791 :white-space " ")))))
792
793
794(define-js-single-op return statement)
795(define-js-single-op throw statement)
796(define-js-single-op delete)
797(define-js-single-op void)
798(define-js-single-op typeof)
799(define-js-single-op instanceof)
800(define-js-single-op new)
801
802;;; assignment
803
804(defjsclass js-setf (expression)
805 ((lhs :initarg :lhs :accessor setf-lhs)
806 (rhsides :initarg :rhsides :accessor setf-rhsides)))
807
808(defun assignment-op (op)
809 (case op
810 (+ '+=)
811 (~ '~=)
812 (\& '\&=)
813 (\| '\|=)
814 (- '-=)
815 (* '*=)
816 (% '%=)
817 (>> '>>=)
818 (^ '^=)
819 (<< '<<=)
820 (>>> '>>>=)
821 (/ '/=)
822 (t nil)))
823
824(defun make-js-test (lhs rhs)
825 (if (and (typep rhs 'op-form)
826 (member lhs (op-args rhs) :test #'js-equal))
827 (let ((args-without (remove lhs (op-args rhs)
828 :count 1 :test #'js-equal))
829 (args-without-first (remove lhs (op-args rhs)
830 :count 1 :end 1
831 :test #'js-equal))
832 (one (list (make-instance 'number-literal :value 1))))
833 #+nil
834 (format t "OPERATOR: ~S, ARGS-WITHOUT: ~S, ARGS-WITHOUT-FIRST ~S~%"
835 (operator rhs)
836 args-without
837 args-without-first)
838 (cond ((and (js-equal args-without one)
839 (eql (operator rhs) '+))
840 (make-instance 'one-op :pre-p nil :op "++"
841 :value lhs))
842 ((and (js-equal args-without-first one)
843 (eql (operator rhs) '-))
844 (make-instance 'one-op :pre-p nil :op "--"
845 :value lhs))
846 ((and (assignment-op (operator rhs))
847 (member (operator rhs)
848 '(+ *)))
849 (make-instance 'op-form
850 :operator (assignment-op (operator rhs))
851 :args (list lhs (make-instance 'op-form
852 :operator (operator rhs)
853 :args args-without))))
854 ((and (assignment-op (operator rhs))
855 (js-equal (first (op-args rhs)) lhs))
856 (make-instance 'op-form
857 :operator (assignment-op (operator rhs))
858 :args (list lhs (make-instance 'op-form
859 :operator (operator rhs)
860 :args (cdr (op-args rhs))))))
861 (t (make-instance 'js-setf :lhs lhs :rhsides (list rhs)))))
862 (make-instance 'js-setf :lhs lhs :rhsides (list rhs))))
863
864(define-js-compiler-macro setf (&rest args)
865 (let ((assignments (loop for (lhs rhs) on args by #'cddr
866 for rexpr = (js-compile-to-expression rhs)
867 for lexpr = (js-compile-to-expression lhs)
868 collect (make-js-test lexpr rexpr))))
869 (if (= (length assignments) 1)
870 (first assignments)
871 (make-instance 'js-body :indent "" :stmts assignments))))
872
873(defmethod js-to-strings ((setf js-setf) start-pos)
874 (dwim-join (cons (js-to-strings (setf-lhs setf) start-pos)
875 (mapcar #'(lambda (x) (js-to-strings x start-pos)) (setf-rhsides setf)))
876 (- 80 start-pos 2)
877 :join-after " ="))
878
879(defmethod expression-precedence ((setf js-setf))
880 (gethash '= *op-precedence-hash*))
881
882;;; defvar
883
884(defjsclass js-defvar (statement)
885 ((names :initarg :names :accessor var-names)
886 (value :initarg :value :accessor var-value)))
887
888(define-js-compiler-macro defvar (name &optional value)
889 (make-instance 'js-defvar :names (list (js-compile-to-symbol name))
890 :value (when value (js-compile-to-expression value))))
891
892(defmethod js-to-statement-strings ((defvar js-defvar) start-pos)
893 (dwim-join (nconc (mapcar #'(lambda (x) (list (symbol-to-js x))) (var-names defvar))
894 (when (var-value defvar)
895 (list (js-to-strings (var-value defvar) start-pos))))
896 (- 80 start-pos 2)
897 :join-after " ="
898 :start "var " :end ";"))
899
900;;; let
901
902(define-js-compiler-macro let (decls &rest body)
903 (let ((single-defvar (make-instance 'js-defvar
904 :names (mapcar #'js-compile-to-symbol
905 (remove-if-not #'atom decls))
906 :value nil))
907 (defvars (mapcar #'(lambda (decl)
908 (let ((name (first decl))
909 (value (second decl)))
910 (make-instance 'js-defvar
911 :names (list (js-compile-to-symbol name))
912 :value (js-compile-to-expression value))))
913 (remove-if #'atom decls))))
914 (make-instance 'js-sub-body
915 :indent " "
916 :stmts (nconc (when (var-names single-defvar) (list single-defvar))
917 defvars
918 (mapcar #'js-compile-to-statement body)))))
919
920;;; iteration
921
922(defjsclass js-for (statement)
923 ((vars :initarg :vars :accessor for-vars)
924 (steps :initarg :steps :accessor for-steps)
925 (check :initarg :check :accessor for-check)
926 (body :initarg :body :accessor for-body)))
927
928(defun make-for-vars (decls)
929 (loop for decl in decls
930 for var = (if (atom decl) decl (first decl))
931 for init = (if (atom decl) nil (second decl))
932 collect (make-instance 'js-defvar :names (list (js-compile-to-symbol var))
933 :value (js-compile-to-expression init))))
934
935(defun make-for-steps (decls)
936 (loop for decl in decls
937 when (= (length decl) 3)
938 collect (js-compile-to-expression (third decl))))
939
940(define-js-compiler-macro do (decls termination &rest body)
941 (let ((vars (make-for-vars decls))
942 (steps (make-for-steps decls))
943 (check (js-compile-to-expression (list 'not (first termination))))
944 (body (js-compile-to-body (cons 'progn body) :indent " ")))
945 (make-instance 'js-for
946 :vars vars
947 :steps steps
948 :check check
949 :body body)))
950
951(defjsmacro dotimes (iter &rest body)
952 (let ((var (first iter))
953 (times (second iter)))
954 `(do ((,var 0 (++ ,var)))
955 ((= ,var ,times))
956 ,@body)))
957
958(defjsmacro dolist (i-array &rest body)
959 (let ((var (first i-array))
960 (array (second i-array))
961 (arrvar (js-gensym "arr"))
962 (idx (js-gensym "i")))
963 `(let ((,arrvar ,array))
964 (do ((,idx 0 (++ ,idx)))
965 ((>= ,idx (slot-value ,arrvar 'length)))
966 (let ((,var (aref ,arrvar ,idx)))
967 ,@body)))))
968
969(defmethod js-to-statement-strings ((for js-for) start-pos)
970 (let* ((init (dwim-join (mapcar #'(lambda (x)
971 (dwim-join (list (list (symbol-to-js (first (var-names x))))
972 (js-to-strings (var-value x)
973 (+ start-pos 2)))
974 (- 80 start-pos 2)
975 :join-after " ="))
976 (for-vars for))
977 (- 80 start-pos 2)
978 :start "var " :join-after ","))
979 (check (js-to-strings (for-check for) (+ start-pos 2)))
980 (steps (dwim-join (mapcar #'(lambda (x var)
981 (dwim-join
982 (list (list (symbol-to-js (first (var-names var))))
983 (js-to-strings x (- start-pos 2)))
984 (- 80 start-pos 2)
985 :join-after " ="))
986 (for-steps for)
987 (for-vars for))
988 (- 80 start-pos 2)
989 :join-after ","))
990 (header (dwim-join (list init check steps)
991 (- 80 start-pos 2)
992 :start "for (" :end ") {"
993 :join-after ";"))
994 (body (js-to-statement-strings (for-body for) (+ start-pos 2))))
995 (nconc header body (list "}"))))
996
997(defjsclass for-each (statement)
998 ((name :initarg :name :accessor fe-name)
999 (value :initarg :value :accessor fe-value)
1000 (body :initarg :body :accessor fe-body)))
1001
1002(define-js-compiler-macro doeach (decl &rest body)
1003 (make-instance 'for-each :name (js-compile-to-symbol (first decl))
1004 :value (js-compile-to-expression (second decl))
1005 :body (js-compile-to-body (cons 'progn body) :indent " ")))
1006
1007(defmethod js-to-statement-strings ((fe for-each) start-pos)
1008 (let ((header (dwim-join (list (list (symbol-to-js (fe-name fe)))
1009 (list "in")
1010 (js-to-strings (fe-value fe) (+ start-pos 2)))
1011 (- 80 start-pos 2)
1012 :start "for (var "
1013 :end ") {"))
1014 (body (js-to-statement-strings (fe-body fe) (+ start-pos 2))))
1015 (nconc header body (list "}"))))
1016
1017(defjsclass js-while (statement)
1018 ((check :initarg :check :accessor while-check)
1019 (body :initarg :body :accessor while-body)))
1020
1021(define-js-compiler-macro while (check &rest body)
1022 (make-instance 'js-while
1023 :check (js-compile-to-expression check)
1024 :body (js-compile-to-body (cons 'progn body) :indent " ")))
1025
1026(defmethod js-to-statement-strings ((while js-while) start-pos)
1027 (let ((header (dwim-join (list (js-to-strings (while-check while) (+ start-pos 2)))
1028 (- 80 start-pos 2)
1029 :start "while ("
1030 :end ") {"))
1031 (body (js-to-statement-strings (while-body while) (+ start-pos 2))))
1032 (nconc header body (list "}"))))
1033
1034;;; with
1035
1036(defjsclass js-with (statement)
1037 ((obj :initarg :obj :accessor with-obj)
1038 (body :initarg :body :accessor with-body)))
1039
1040(define-js-compiler-macro with (statement &rest body)
1041 (make-instance 'js-with
1042 :obj (js-compile-to-expression (first statement))
1043 :body (js-compile-to-body (cons 'progn body) :indent " ")))
1044
1045(defmethod js-to-statement-strings ((with js-with) start-pos)
1046 (nconc (dwim-join (list (js-to-strings (with-obj with) (+ start-pos 2)))
1047 (- 80 start-pos 2)
1048 :start "with (" :end ") {")
1049 (js-to-statement-strings (with-body with) (+ start-pos 2))
1050 (list "}")))
1051
1052;;; case
1053
1054(defjsclass js-case (statement)
1055 ((value :initarg :value :accessor case-value)
1056 (clauses :initarg :clauses :accessor case-clauses)))
1057
1058(define-js-compiler-macro case (value &rest clauses)
1059 (let ((clauses (mapcar #'(lambda (clause)
1060 (let ((val (first clause))
1061 (body (cdr clause)))
1062 (list (if (eql val 'default)
1063 'default
1064 (js-compile-to-expression val))
1065 (js-compile-to-body (cons 'progn body) :indent " "))))
1066 clauses))
1067 (check (js-compile-to-expression value)))
1068 (make-instance 'js-case :value check
1069 :clauses clauses)))
1070
1071(defmethod js-to-statement-strings ((case js-case) start-pos)
1072 (let ((body (mapcan #'(lambda (clause)
1073 (let ((val (car clause))
1074 (body (second clause)))
1075 (dwim-join (list (if (eql val 'default)
1076 (list "")
1077 (js-to-strings val (+ start-pos 2)))
1078 (js-to-statement-strings body (+ start-pos 2)))
1079 (- 80 start-pos 2)
1080 :start (if (eql val 'default) " default" " case ")
1081 :white-space " "
1082 :join-after ":"))) (case-clauses case))))
1083
1084 #+nil
1085 (format t "body: ~S~%" body)
1086 (nconc (dwim-join (list (js-to-strings (case-value case) (+ start-pos 2)))
1087 (- 80 start-pos 2)
1088 :start "switch (" :end ") {")
1089 body
1090 (list "}"))))
1091
1092;;; throw catch
1093
1094(defjsclass js-try (statement)
1095 ((body :initarg :body :accessor try-body)
1096 (catch :initarg :catch :accessor try-catch)
1097 (finally :initarg :finally :accessor try-finally)))
1098
1099(define-js-compiler-macro try (body &rest clauses)
1100 (let ((body (js-compile-to-body body :indent " "))
1101 (catch (cdr (assoc :catch clauses)))
1102 (finally (cdr (assoc :finally clauses))))
1103 (make-instance 'js-try
1104 :body body
1105 :catch (when catch (list (js-compile-to-symbol (caar catch))
1106 (js-compile-to-body (cons 'progn (cdr catch))
1107 :indent " ")))
1108 :finally (when finally (js-compile-to-body (cons 'progn finally)
1109 :indent " ")))))
1110
1111(defmethod js-to-statement-strings ((try js-try) start-pos)
1112 (let* ((catch (try-catch try))
1113 (finally (try-finally try))
1114 (catch-list (when catch
1115 (nconc
1116 (dwim-join (list (list (symbol-to-js (first catch))))
1117 (- 80 start-pos 2)
1118 :start "} catch ("
1119 :end ") {")
1120 (js-to-statement-strings (second catch) (+ start-pos 2)))))
1121 (finally-list (when finally
1122 (nconc (list "} finally {")
1123 (js-to-statement-strings finally (+ start-pos 2))))))
1124 (nconc (list "try {")
1125 (js-to-statement-strings (try-body try) (+ start-pos 2))
1126 catch-list
1127 finally-list
1128 (list "}"))))
1129
1130;;; regex
1131
1132(defjsclass regex (expression)
1133 (value))
1134
1135(define-js-compiler-macro regex (regex)
1136 (make-instance 'regex :value (string regex)))
1137
1138;;; conditional compilation
1139
1140(defjsclass cc-if ()
1141 ((test :initarg :test :accessor cc-if-test)
1142 (body :initarg :body :accessor cc-if-body)))
1143
1144(defmethod js-to-statement-strings ((cc cc-if) start-pos)
1145 (nconc (list (format nil "/*@if ~A" (cc-if-test cc)))
1146 (mapcan #'(lambda (x) (js-to-strings x start-pos)) (cc-if-body cc))
1147 (list "@end @*/")))
1148
1149(define-js-compiler-macro cc-if (test &rest body)
1150 (make-instance 'cc-if :test test
1151 :body (mapcar #'js-compile body)))
1152
1153;;; compiler
1154
1155(defun js-compile (form)
1156 (setf form (js-expand-form form))
1157 (cond ((stringp form)
1158 (make-instance 'string-literal :value form))
1159 ((numberp form)
1160 (make-instance 'number-literal :value form))
1161 ((symbolp form)
1162 (let ((c-macro (js-get-compiler-macro form)))
1163 (if c-macro
1164 (funcall c-macro)
1165 (make-instance 'js-variable :value form))))
1166 ((and (consp form)
1167 (eql (first form) 'quote))
1168 (second form))
1169 ((consp form)
1170 (js-compile-list form))
1171 (t (error "Unknown atomar expression ~S" form))))
1172
1173(defun js-compile-list (form)
1174 (let* ((name (car form))
1175 (args (cdr form))
1176 (js-form (js-get-compiler-macro name)))
1177 (cond (js-form
1178 (apply js-form args))
1179
1180 ((op-form-p form)
1181 (make-instance 'op-form
1182 :operator (js-convert-op-name (js-compile-to-symbol (first form)))
1183 :args (mapcar #'js-compile-to-expression (rest form))))
1184
1185 ((method-call-p form)
1186 (make-instance 'method-call
1187 :method (js-compile-to-symbol (first form))
1188 :object (js-compile-to-expression (second form))
1189 :args (mapcar #'js-compile-to-expression (cddr form))))
1190
1191 ((funcall-form-p form)
1192 (make-instance 'function-call
1193 :function (js-compile-to-expression (first form))
1194 :args (mapcar #'js-compile-to-expression (rest form))))
1195
1196 (t (error "Unknown form ~S" form)))))
1197
1198(defun js-compile-to-expression (form)
1199 (let ((res (js-compile form)))
1200 (assert (typep res 'expression))
1201 res))
1202
1203(defun js-compile-to-symbol (form)
1204 (let ((res (js-compile form)))
1205 (when (typep res 'js-variable )
1206 (setf res (value res)))
1207 (assert (symbolp res))
1208 res))
1209
1210(defun js-compile-to-statement (form)
1211 (let ((res (js-compile form)))
1212 (assert (typep res 'statement))
1213 res))
1214
1215(defun js-compile-to-body (form &key (indent ""))
1216 (let ((res (js-compile-to-statement form)))
1217 (if (typep res 'js-body)
1218 (progn (setf (b-indent res) indent)
1219 res)
1220 (make-instance 'js-body
1221 :indent indent
1222 :stmts (list res)))))
1223
1224;;; Math library
1225(defjsmacro floor (expr)
1226 `(*Math.floor ,expr))
1227
1228(defjsmacro random ()
1229 `(*Math.random))
1230
1231;;; helper macros
1232
1233(define-js-compiler-macro js (&rest body)
1234 (make-instance 'string-literal
1235 :value (string-join (js-to-statement-strings
1236 (js-compile (cons 'progn body)) 0) " ")))
1237
1238(define-js-compiler-macro js-inline (&rest body)
1239 (make-instance 'string-literal
1240 :value (concatenate
1241 'string
1242 "javascript:"
1243 (string-join (js-to-statement-strings
1244 (js-compile (cons 'progn body)) 0) " "))))
1245
1246
1247(defmacro js (&rest body)
1248 `(string-join
1249 (js-to-statement-strings (js-compile '(progn ,@body)) 0)
1250 (string #\Newline)))
1251
d006f536
MB
1252(defmacro js* (&rest body)
1253 "Just like JS except that BODY is evaluated before being
1254converted to javascript."
1255 `(string-join
1256 (js-to-statement-strings (js-compile (list 'progn ,@body)) 0)
1257 (string #\Newline)))
1258
8e198a08
MB
1259(defun js-to-string (expr)
1260 (string-join
1261 (js-to-statement-strings (js-compile expr) 0)
1262 (string #\Newline)))
1263
1264(defun js-to-line (expr)
1265 (string-join
1266 (js-to-statement-strings (js-compile expr) 0) " "))
1267
1268(defmacro js-file (&rest body)
1269 `(html
1270 (:princ
1271 (js ,@body))))
1272
1273(defmacro js-script (&rest body)
1274 `((:script :type "text/javascript")
1275 (:princ (format nil "~%// <![CDATA[~%"))
1276 (:princ (js ,@body))
1277 (:princ (format nil "~%// ]]>~%"))))
1278
1279(defmacro js-inline (&rest body)
1280 `(concatenate 'string "javascript:"
1281 (string-join (js-to-statement-strings (js-compile '(progn ,@body)) 0) " ")))
1282
d006f536
MB
1283(defmacro js-inline* (&rest body)
1284 "Just like JS-INLINE except that BODY is evaluated before being
1285converted to javascript."
1286 `(concatenate 'string "javascript:"
1287 (string-join (js-to-statement-strings (js-compile (list 'progn ,@body)) 0) " ")))
1288
1289