Changed let to not introduce any extra variables (for parallel
[clinton/parenscript.git] / src / special-forms.lisp
CommitLineData
18dd299a
VS
1(in-package :parenscript)
2
3;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
4;;; literals
5(defmacro defpsliteral (name string)
4577df1c
TC
6 `(progn
7 (add-ps-literal ',name)
8 (define-ps-special-form ,name (expecting)
9 (declare (ignore expecting))
10 (list 'js-literal ,string))))
18dd299a
VS
11
12(defpsliteral this "this")
13(defpsliteral t "true")
14(defpsliteral true "true")
15(defpsliteral false "false")
16(defpsliteral f "false")
17(defpsliteral nil "null")
18(defpsliteral undefined "undefined")
19
c452748e
TC
20(macrolet ((def-for-literal (name printer)
21 `(progn
4577df1c 22 (add-ps-literal ',name)
c452748e
TC
23 (define-ps-special-form ,name (expecting &optional label)
24 (declare (ignore expecting))
25 (list ',printer label)))))
26 (def-for-literal break js-break)
27 (def-for-literal continue js-continue))
18dd299a
VS
28
29;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
30;;; unary operators
6a46e1ef
TC
31(macrolet ((def-unary-ops (&rest ops)
32 `(progn ,@(mapcar (lambda (op)
33 (let ((op (if (listp op) (car op) op))
34 (spacep (if (listp op) (second op) nil)))
35 `(define-ps-special-form ,op (expecting x)
36 (declare (ignore expecting))
37 (list 'unary-operator ',op
38 (compile-parenscript-form x :expecting :expression)
39 :prefix t :space ,spacep))))
40 ops))))
41 (def-unary-ops ~ ! (new t) (delete t) (void t) (typeof t)))
18dd299a 42
6a46e1ef
TC
43;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
44;;; statements
18dd299a
VS
45(define-ps-special-form return (expecting &optional value)
46 (declare (ignore expecting))
47 (list 'js-return (compile-parenscript-form value :expecting :expression)))
48
6a46e1ef
TC
49(define-ps-special-form throw (expecting value)
50 (declare (ignore expecting))
51 (list 'js-throw (compile-parenscript-form value :expecting :expression)))
52
18dd299a
VS
53;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
54;;; arrays
55(define-ps-special-form array (expecting &rest values)
56 (declare (ignore expecting))
57 (cons 'array-literal (mapcar (lambda (form) (compile-parenscript-form form :expecting :expression))
58 values)))
59
60(define-ps-special-form aref (expecting array &rest coords)
61 (declare (ignore expecting))
62 (list 'js-aref (compile-parenscript-form array :expecting :expression)
63 (mapcar (lambda (form)
64 (compile-parenscript-form form :expecting :expression))
65 coords)))
66
18dd299a
VS
67(defpsmacro list (&rest values)
68 `(array ,@values))
69
79630c82
VS
70(defpsmacro make-array (&rest initial-values)
71 `(new (*array ,@initial-values)))
18dd299a
VS
72
73;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
74;;; operators
75(define-ps-special-form incf (expecting x &optional (delta 1))
76 (declare (ignore expecting))
77 (if (equal delta 1)
6a46e1ef 78 (list 'unary-operator '++ (compile-parenscript-form x :expecting :expression) :prefix t)
18dd299a
VS
79 (list 'operator '+= (list (compile-parenscript-form x :expecting :expression)
80 (compile-parenscript-form delta :expecting :expression)))))
81
82(define-ps-special-form decf (expecting x &optional (delta 1))
83 (declare (ignore expecting))
84 (if (equal delta 1)
6a46e1ef 85 (list 'unary-operator '-- (compile-parenscript-form x :expecting :expression) :prefix t)
18dd299a
VS
86 (list 'operator '-= (list (compile-parenscript-form x :expecting :expression)
87 (compile-parenscript-form delta :expecting :expression)))))
88
89(define-ps-special-form - (expecting first &rest rest)
90 (declare (ignore expecting))
91 (if (null rest)
6a46e1ef 92 (list 'unary-operator '- (compile-parenscript-form first :expecting :expression) :prefix t)
18dd299a
VS
93 (list 'operator '- (mapcar (lambda (val) (compile-parenscript-form val :expecting :expression))
94 (cons first rest)))))
95
96(define-ps-special-form not (expecting x)
97 (declare (ignore expecting))
98 (let ((form (compile-parenscript-form x :expecting :expression))
99 (not-op nil))
100 (if (and (eql (first form) 'operator)
b508414b 101 (= (length (third form)) 2)
18dd299a
VS
102 (setf not-op (case (second form)
103 (== '!=)
104 (< '>=)
105 (> '<=)
106 (<= '>)
107 (>= '<)
108 (!= '==)
109 (=== '!==)
110 (!== '===)
111 (t nil))))
112 (list 'operator not-op (third form))
6a46e1ef 113 (list 'unary-operator '! form :prefix t))))
18dd299a 114
18dd299a
VS
115;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
116;;; control structures
117(defun flatten-blocks (body)
118 (when body
119 (if (and (listp (car body))
120 (eql 'js-block (caar body)))
121 (append (third (car body)) (flatten-blocks (cdr body)))
122 (cons (car body) (flatten-blocks (cdr body))))))
123
124(defun constant-literal-form-p (form)
125 (or (numberp form)
126 (stringp form)
127 (and (listp form)
128 (eql 'js-literal (car form)))))
129
130(define-ps-special-form progn (expecting &rest body)
131 (if (and (eql expecting :expression) (= 1 (length body)))
132 (compile-parenscript-form (car body) :expecting :expression)
133 (list 'js-block
134 expecting
135 (let* ((block (mapcar (lambda (form)
136 (compile-parenscript-form form :expecting expecting))
137 body))
138 (clean-block (remove nil block))
139 (flat-block (flatten-blocks clean-block))
140 (reachable-block (append (remove-if #'constant-literal-form-p (butlast flat-block))
141 (last flat-block))))
142 reachable-block))))
143
144(define-ps-special-form cond (expecting &rest clauses)
145 (ecase expecting
146 (:statement (list 'js-cond-statement
147 (mapcar (lambda (clause)
148 (destructuring-bind (test &rest body)
149 clause
150 (list (compile-parenscript-form test :expecting :expression)
151 (compile-parenscript-form `(progn ,@body) :expecting :statement))))
152 clauses)))
153 (:expression (make-cond-clauses-into-nested-ifs clauses))))
154
155(defun make-cond-clauses-into-nested-ifs (clauses)
156 (if clauses
157 (destructuring-bind (test &rest body)
158 (car clauses)
159 (if (eq t test)
160 (compile-parenscript-form `(progn ,@body) :expecting :expression)
161 (list 'js-expression-if (compile-parenscript-form test :expecting :expression)
162 (compile-parenscript-form `(progn ,@body) :expecting :expression)
163 (make-cond-clauses-into-nested-ifs (cdr clauses)))))
164 (compile-parenscript-form nil :expecting :expression)))
165
166(define-ps-special-form if (expecting test then &optional else)
167 (ecase expecting
168 (:statement (list 'js-statement-if (compile-parenscript-form test :expecting :expression)
169 (compile-parenscript-form `(progn ,then))
170 (when else (compile-parenscript-form `(progn ,else)))))
171 (:expression (list 'js-expression-if (compile-parenscript-form test :expecting :expression)
172 (compile-parenscript-form then :expecting :expression)
173 (compile-parenscript-form else :expecting :expression)))))
174
175(define-ps-special-form switch (expecting test-expr &rest clauses)
176 (declare (ignore expecting))
177 (let ((clauses (mapcar (lambda (clause)
b508414b
TC
178 (let ((val (car clause))
179 (body (cdr clause)))
675edae3
TC
180 (cons (if (and (symbolp val)
181 (eq (ensure-ps-symbol val) 'default))
b508414b
TC
182 'default
183 (compile-parenscript-form val :expecting :expression))
18dd299a
VS
184 (mapcar (lambda (statement) (compile-parenscript-form statement :expecting :statement))
185 body))))
b508414b
TC
186 clauses))
187 (expr (compile-parenscript-form test-expr :expecting :expression)))
18dd299a
VS
188 (list 'js-switch expr clauses)))
189
190(defpsmacro case (value &rest clauses)
191 (labels ((make-clause (val body more)
587f3aa0 192 (cond ((and (listp val) (not (eq (car val) 'quote)))
18dd299a
VS
193 (append (mapcar #'list (butlast val))
194 (make-clause (first (last val)) body more)))
195 ((member val '(t otherwise))
196 (make-clause 'default body more))
197 (more `((,val ,@body break)))
198 (t `((,val ,@body))))))
199 `(switch ,value ,@(mapcon (lambda (clause)
200 (make-clause (car (first clause))
201 (cdr (first clause))
202 (rest clause)))
203 clauses))))
204
205(defpsmacro when (test &rest body)
206 `(if ,test (progn ,@body)))
207
208(defpsmacro unless (test &rest body)
209 `(if (not ,test) (progn ,@body)))
210
211;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
212;;; function definition
213(defun compile-function-definition (args body)
214 (list (mapcar (lambda (arg) (compile-parenscript-form arg :expecting :symbol)) args)
215 (let ((*enclosing-lexical-block-declarations* ()))
216 ;; the first compilation will produce a list of variables we need to declare in the function body
217 (compile-parenscript-form `(progn ,@body) :expecting :statement)
218 ;; now declare and compile
58c4ef4f 219 (compile-parenscript-form `(progn ,@(loop for var in *enclosing-lexical-block-declarations* collect `(var ,var))
18dd299a
VS
220 ,@body) :expecting :statement))))
221
222(define-ps-special-form %js-lambda (expecting args &rest body)
223 (declare (ignore expecting))
224 (cons 'js-lambda (compile-function-definition args body)))
225
226(define-ps-special-form %js-defun (expecting name args &rest body)
227 (declare (ignore expecting))
228 (append (list 'js-defun name) (compile-function-definition args body)))
229
230(defun parse-function-body (body)
231 (let* ((docstring
232 (when (stringp (first body))
233 (first body)))
234 (body-forms (if docstring (rest body) body)))
235 (values body-forms docstring)))
236
237(defun parse-key-spec (key-spec)
238 "parses an &key parameter. Returns 4 values:
239var, init-form, keyword-name, supplied-p-var, init-form-supplied-p.
240
241Syntax of key spec:
242[&key {var | ({var | (keyword-name var)} [init-form [supplied-p-parameter]])}*
243"
244 (let* ((var (cond ((symbolp key-spec) key-spec)
245 ((and (listp key-spec) (symbolp (first key-spec))) (first key-spec))
246 ((and (listp key-spec) (listp (first key-spec))) (second key-spec))))
247 (keyword-name (if (and (listp key-spec) (listp (first key-spec)))
248 (first (first key-spec))
249 (intern (string var) :keyword)))
250 (init-form (if (listp key-spec) (second key-spec) nil))
251 (init-form-supplied-p (if (listp key-spec) t nil))
252 (supplied-p-var (if (listp key-spec) (third key-spec) nil)))
253 (values var init-form keyword-name supplied-p-var init-form-supplied-p)))
254
255(defun parse-optional-spec (spec)
256 "Parses an &optional parameter. Returns 3 values: var, init-form, supplied-p-var.
257[&optional {var | (var [init-form [supplied-p-parameter]])}*] "
258 (let* ((var (cond ((symbolp spec) spec)
259 ((and (listp spec) (first spec)))))
260 (init-form (if (listp spec) (second spec)))
261 (supplied-p-var (if (listp spec) (third spec))))
262 (values var init-form supplied-p-var)))
263
264(defun parse-aux-spec (spec)
265 "Returns two values: variable and init-form"
266 ;; [&aux {var | (var [init-form])}*])
267 (values (if (symbolp spec) spec (first spec))
268 (when (listp spec) (second spec))))
269
270(defpsmacro defaultf (place value)
0e198f66
TC
271 `(when (=== ,place undefined)
272 (setf ,place ,value)))
18dd299a
VS
273
274(defun parse-extended-function (lambda-list body &optional name)
275 "Returns two values: the effective arguments and body for a function with
276the given lambda-list and body."
277
278 ;; The lambda list is transformed as follows, since a javascript lambda list is just a
279 ;; list of variable names, and you have access to the arguments variable inside the function:
280 ;; * standard variables are the mapped directly into the js-lambda list
281 ;; * optional variables' variable names are mapped directly into the lambda list,
282 ;; and for each optional variable with name v and default value d, a form is produced
283 ;; (defaultf v d)
284 ;; * when any keyword variables are in the lambda list, a single 'optional-args' variable is
285 ;; appended to the js-lambda list as the last argument. WITH-SLOTS is used for all
286 ;; the variables with inside the body of the function,
287 ;; a (with-slots ((var-name key-name)) optional-args ...)
288 (declare (ignore name))
289 (multiple-value-bind (requireds optionals rest? rest keys? keys allow? aux? aux
290 more? more-context more-count key-object)
291 (parse-lambda-list lambda-list)
292 (declare (ignore allow? aux? aux more? more-context more-count))
293 (let* ((options-var (or key-object (ps-gensym)))
294 ;; optionals are of form (var default-value)
295 (effective-args
296 (remove-if
297 #'null
298 (append requireds
299 (mapcar #'parse-optional-spec optionals)
300 (when keys (list options-var)))))
301 ;; an alist of arg -> default val
302 (initform-pairs
303 (remove
304 nil
305 (append
306 ;; optional arguments first
307 (mapcar #'(lambda (opt-spec)
308 (multiple-value-bind (var val) (parse-optional-spec opt-spec)
309 (cons var val)))
310 optionals)
311 (if keys? (list (cons options-var '(create))))
312 (mapcar #'(lambda (key-spec)
313 (multiple-value-bind (var val x y specified?) (parse-key-spec key-spec)
314 (declare (ignore x y))
315 (when specified? (cons var val))))
316 keys))))
45c9f9c2 317 (body-paren-forms (parse-function-body body)) ; remove documentation
18dd299a
VS
318 (initform-forms
319 (mapcar #'(lambda (default-pair)
320 `(defaultf ,(car default-pair) ,(cdr default-pair)))
321 initform-pairs))
322 (rest-form
323 (if rest?
324 (with-ps-gensyms (i)
f326f929 325 `(progn (var ,rest (array))
18dd299a
VS
326 (dotimes (,i (- arguments.length ,(length effective-args)))
327 (setf (aref ,rest ,i) (aref arguments (+ ,i ,(length effective-args)))))))
328 `(progn)))
329 (effective-body (append initform-forms (list rest-form) body-paren-forms))
330 (effective-body
331 (if keys?
332 (list `(with-slots ,(mapcar #'(lambda (key-spec)
333 (multiple-value-bind (var x key-name)
334 (parse-key-spec key-spec)
335 (declare (ignore x))
336 (list var key-name)))
337 keys)
338 ,options-var
339 ,@effective-body))
340 effective-body)))
341 (values effective-args effective-body))))
342
343(defpsmacro defun (name lambda-list &body body)
344 "An extended defun macro that allows cool things like keyword arguments.
345lambda-list::=
346 (var*
347 [&optional {var | (var [init-form [supplied-p-parameter]])}*]
348 [&rest var]
349 [&key {var | ({var | (keyword-name var)} [init-form [supplied-p-parameter]])}* [&allow-other-keys]]
350 [&aux {var | (var [init-form])}*])"
351 (if (symbolp name)
352 `(defun-function ,name ,lambda-list ,@body)
675edae3 353 (progn (assert (and (= (length name) 2) (eq 'setf (ensure-ps-symbol (car name)))) ()
18dd299a
VS
354 "(defun ~s ~s ...) needs to have a symbol or (setf symbol) for a name." name lambda-list)
355 `(defun-setf ,name ,lambda-list ,@body))))
356
357(defpsmacro defun-function (name lambda-list &body body)
358 (multiple-value-bind (effective-args effective-body)
359 (parse-extended-function lambda-list body name)
360 `(%js-defun ,name ,effective-args
361 ,@effective-body)))
362
363(defvar *defun-setf-name-prefix* "__setf_")
364
365(defpsmacro defun-setf (setf-name lambda-list &body body)
366 (let ((mangled-function-name (intern (concatenate 'string *defun-setf-name-prefix* (symbol-name (second setf-name)))
367 (symbol-package (second setf-name))))
368 (function-args (cdr (ordered-set-difference lambda-list lambda-list-keywords))))
369 `(progn (defsetf ,(second setf-name) ,(cdr lambda-list) (store-var)
370 `(,',mangled-function-name ,store-var ,@(list ,@function-args)))
371 (defun ,mangled-function-name ,lambda-list ,@body))))
372
373(defpsmacro lambda (lambda-list &body body)
374 "An extended defun macro that allows cool things like keyword arguments.
375lambda-list::=
376 (var*
377 [&optional {var | (var [init-form [supplied-p-parameter]])}*]
378 [&rest var]
379 [&key {var | ({var | (keyword-name var)} [init-form [supplied-p-parameter]])}* [&allow-other-keys]]
380 [&aux {var | (var [init-form])}*])"
381 (multiple-value-bind (effective-args effective-body)
382 (parse-extended-function lambda-list body)
383 `(%js-lambda ,effective-args
384 ,@effective-body)))
385
386(defpsmacro defsetf-long (access-fn lambda-list (store-var) form)
462ca010 387 (setf (get-macro-spec access-fn *ps-setf-expanders*)
18dd299a
VS
388 (compile nil
389 (let ((var-bindings (ordered-set-difference lambda-list lambda-list-keywords)))
390 `(lambda (access-fn-args store-form)
391 (destructuring-bind ,lambda-list
392 access-fn-args
393 (let* ((,store-var (ps-gensym))
394 (gensymed-names (loop repeat ,(length var-bindings) collecting (ps-gensym)))
395 (gensymed-arg-bindings (mapcar #'list gensymed-names (list ,@var-bindings))))
396 (destructuring-bind ,var-bindings
397 gensymed-names
58c4ef4f
VS
398 `(let* (,@gensymed-arg-bindings
399 (,,store-var ,store-form))
18dd299a
VS
400 ,,form))))))))
401 nil)
402
403(defpsmacro defsetf-short (access-fn update-fn &optional docstring)
404 (declare (ignore docstring))
462ca010 405 (setf (get-macro-spec access-fn *ps-setf-expanders*)
18dd299a
VS
406 (lambda (access-fn-args store-form)
407 `(,update-fn ,@access-fn-args ,store-form)))
408 nil)
409
410(defpsmacro defsetf (access-fn &rest args)
411 `(,(if (= (length args) 3) 'defsetf-long 'defsetf-short) ,access-fn ,@args))
412
413;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
414;;; macros
415(defmacro with-temp-macro-environment ((var) &body body)
416 `(let* ((,var (make-macro-env-dictionary))
462ca010 417 (*ps-macro-env* (cons ,var *ps-macro-env*)))
18dd299a
VS
418 ,@body))
419
420(define-ps-special-form macrolet (expecting macros &body body)
421 (declare (ignore expecting))
422 (with-temp-macro-environment (macro-env-dict)
423 (dolist (macro macros)
424 (destructuring-bind (name arglist &body body)
425 macro
b508414b 426 (setf (get-macro-spec name macro-env-dict)
8cfc6fe9 427 (cons nil (eval (make-ps-macro-function arglist body))))))
18dd299a
VS
428 (compile-parenscript-form `(progn ,@body))))
429
430(define-ps-special-form symbol-macrolet (expecting symbol-macros &body body)
431 (declare (ignore expecting))
432 (with-temp-macro-environment (macro-env-dict)
433 (dolist (macro symbol-macros)
434 (destructuring-bind (name expansion)
435 macro
b508414b 436 (setf (get-macro-spec name macro-env-dict)
8cfc6fe9 437 (cons t (lambda () expansion)))))
18dd299a
VS
438 (compile-parenscript-form `(progn ,@body))))
439
440(define-ps-special-form defmacro (expecting name args &body body)
441 (declare (ignore expecting))
8cfc6fe9 442 (eval `(defpsmacro ,name ,args ,@body))
18dd299a
VS
443 nil)
444
445(define-ps-special-form define-symbol-macro (expecting name expansion)
446 (declare (ignore expecting))
8cfc6fe9 447 (eval `(define-ps-symbol-macro ,name ,expansion))
18dd299a
VS
448 nil)
449
450;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
451;;; objects
79630c82
VS
452(add-ps-literal '{})
453(define-ps-symbol-macro {} (create))
454
455(define-ps-special-form create (expecting &rest arrows)
18dd299a 456 (declare (ignore expecting))
79630c82
VS
457 (list 'js-object (loop for (key-expr val-expr) on arrows by #'cddr collecting
458 (let ((key (compile-parenscript-form key-expr :expecting :expression)))
459 (when (keywordp key)
460 (setf key (list 'js-variable key)))
461 (assert (or (stringp key)
462 (numberp key)
463 (and (listp key)
464 (or (eq 'js-variable (car key))
465 (eq 'ps-quote (car key)))))
18dd299a 466 ()
79630c82
VS
467 "Slot key ~s is not one of js-variable, keyword, string or number." key)
468 (cons key (compile-parenscript-form val-expr :expecting :expression))))))
18dd299a
VS
469
470(define-ps-special-form %js-slot-value (expecting obj slot)
471 (declare (ignore expecting))
472 (if (ps::ps-macroexpand slot)
473 (list 'js-slot-value (compile-parenscript-form obj :expecting :expression) (compile-parenscript-form slot))
474 (compile-parenscript-form obj :expecting :expression)))
475
476(define-ps-special-form instanceof (expecting value type)
477 (declare (ignore expecting))
478 (list 'js-instanceof (compile-parenscript-form value :expecting :expression)
479 (compile-parenscript-form type :expecting :expression)))
480
481(defpsmacro slot-value (obj &rest slots)
482 (if (null (rest slots))
483 `(%js-slot-value ,obj ,(first slots))
484 `(slot-value (slot-value ,obj ,(first slots)) ,@(rest slots))))
485
486(defpsmacro with-slots (slots object &rest body)
487 (flet ((slot-var (slot) (if (listp slot) (first slot) slot))
b508414b 488 (slot-symbol (slot) (if (listp slot) (second slot) slot)))
18dd299a 489 `(symbol-macrolet ,(mapcar #'(lambda (slot)
b508414b
TC
490 `(,(slot-var slot) (slot-value ,object ',(slot-symbol slot))))
491 slots)
18dd299a
VS
492 ,@body)))
493
494;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
495;;; assignment and binding
496(defun assignment-op (op)
497 (case op
498 (+ '+=)
499 (~ '~=)
500 (\& '\&=)
501 (\| '\|=)
502 (- '-=)
503 (* '*=)
504 (% '%=)
505 (>> '>>=)
506 (^ '^=)
507 (<< '<<=)
508 (>>> '>>>=)
509 (/ '/=)
510 (t nil)))
511
512(defun smart-setf (lhs rhs)
513 (if (and (listp rhs)
514 (eql 'operator (car rhs))
b508414b 515 (member lhs (third rhs) :test #'equalp))
d89456ee 516 (let ((args-without-first (remove lhs (third rhs) :count 1 :end 1 :test #'equalp)))
b508414b
TC
517 (cond ((and (assignment-op (second rhs))
518 (member (second rhs) '(+ *))
18dd299a 519 (equalp lhs (first (third rhs))))
b508414b 520 (list 'operator (assignment-op (second rhs))
18dd299a 521 (list lhs (list 'operator (second rhs) args-without-first))))
b508414b 522 (t (list 'js-assign lhs rhs))))
18dd299a
VS
523 (list 'js-assign lhs rhs)))
524
525(define-ps-special-form setf1% (expecting lhs rhs)
526 (declare (ignore expecting))
527 (smart-setf (compile-parenscript-form lhs :expecting :expression) (compile-parenscript-form rhs :expecting :expression)))
528
529(defpsmacro setf (&rest args)
530 (flet ((process-setf-clause (place value-form)
462ca010
TC
531 (if (and (listp place) (get-macro-spec (car place) *ps-setf-expanders*))
532 (funcall (get-macro-spec (car place) *ps-setf-expanders*) (cdr place) value-form)
18dd299a 533 (let ((exp-place (ps-macroexpand place)))
462ca010
TC
534 (if (and (listp exp-place) (get-macro-spec (car exp-place) *ps-setf-expanders*))
535 (funcall (get-macro-spec (car exp-place) *ps-setf-expanders*) (cdr exp-place) value-form)
18dd299a
VS
536 `(setf1% ,exp-place ,value-form))))))
537 (assert (evenp (length args)) ()
538 "~s does not have an even number of arguments." (cons 'setf args))
539 `(progn ,@(loop for (place value) on args by #'cddr collect (process-setf-clause place value)))))
540
1fe28ee1
TC
541(defpsmacro psetf (&rest args)
542 (let ((vars (loop for x in args by #'cddr collect x))
543 (vals (loop for x in (cdr args) by #'cddr collect x)))
544 (let ((gensyms (mapcar (lambda (x) (declare (ignore x)) (ps-gensym)) vars)))
545 `(simple-let* ,(mapcar #'list gensyms vals)
546 (setf ,@(mapcan #'list vars gensyms))))))
547
ec227186
TC
548(defun check-setq-args (args)
549 (let ((vars (loop for x in args by #'cddr collect x)))
550 (let ((non-var (find-if (complement #'symbolp) vars)))
551 (when non-var
552 (error 'type-error :datum non-var :expected-type 'symbol)))))
553
554(defpsmacro setq (&rest args)
555 (check-setq-args args)
556 `(setf ,@args))
557
558(defpsmacro psetq (&rest args)
559 (check-setq-args args)
560 `(psetf ,@args))
561
58c4ef4f 562(define-ps-special-form var (expecting name &rest value)
18dd299a 563 (declare (ignore expecting))
58c4ef4f 564 (append (list 'js-var name)
18dd299a 565 (when value
58c4ef4f
VS
566 (assert (= (length value) 1) () "Wrong number of arguments to var: ~s" `(var ,name ,@value))
567 (list (compile-parenscript-form (car value) :expecting :expression)))))
18dd299a 568
58c4ef4f
VS
569(defpsmacro defvar (name &rest value)
570 "Note: this must be used as a top-level form, otherwise the result will be undefined behavior."
571 (pushnew name *ps-special-variables*)
572 (assert (or (null value) (= (length value) 1)) () "Wrong number of arguments to defvar: ~s" `(defvar ,name ,@value))
573 `(var ,name ,@value))
574
3530f5e1
TC
575(defun make-let-vars (bindings)
576 (mapcar (lambda (x) (if (listp x) (car x) x)) bindings))
577
578(defun make-let-vals (bindings)
579 (mapcar (lambda (x) (if (or (atom x) (endp (cdr x))) nil (second x))) bindings))
580
58c4ef4f 581(defpsmacro lexical-let* (bindings &body body)
241c2c5b
TC
582 `((lambda ()
583 (let* ,bindings
584 ,@body))))
58c4ef4f 585
3530f5e1
TC
586(defpsmacro lexical-let (bindings &body body)
587 `((lambda ,(make-let-vars bindings)
588 ,@body)
589 ,@(make-let-vals bindings)))
590
b5cf9e71 591(defpsmacro simple-let* (bindings &body body)
58c4ef4f
VS
592 (if bindings
593 (let ((var (if (listp (car bindings)) (caar bindings) (car bindings))))
594 `(,(if (member var *ps-special-variables*) 'let1-dynamic 'let1) ,(car bindings)
b5cf9e71 595 (simple-let* ,(cdr bindings) ,@body)))
58c4ef4f
VS
596 `(progn ,@body)))
597
ca25a40e
TC
598(defpsmacro simple-let (bindings &body body)
599 (let ((vars (mapcar (lambda (x) (if (atom x) x (first x))) bindings))
600 (vals (mapcar (lambda (x) (if (or (atom x) (endp (cdr x))) nil (second x))) bindings)))
601 (let ((gensyms (mapcar (lambda (x) (ps-gensym (format nil "_js_~a" x))) vars)))
602 `(simple-let* ,(mapcar #'list gensyms vals)
603 (simple-let* ,(mapcar #'list vars gensyms)
604 ,@(mapcar (lambda (x) `(delete ,x)) gensyms)
605 ,@body)))))
606
b5cf9e71
TC
607(defpsmacro let* (bindings &body body)
608 `(simple-let* ,bindings ,@body))
609
da7ec1c0 610(defpsmacro let (bindings &body body)
93296a3d 611 `(,(if (= 1 (length bindings)) 'simple-let* 'simple-let) ,bindings ,@body))
58c4ef4f
VS
612
613(define-ps-special-form let1 (expecting binding &rest body)
18dd299a
VS
614 (ecase expecting
615 (:statement
58c4ef4f 616 (compile-parenscript-form `(progn ,(if (atom binding) `(var ,binding) `(var ,@binding)) ,@body) :expecting :statement))
18dd299a 617 (:expression
58c4ef4f
VS
618 (let ((var (if (atom binding) binding (car binding)))
619 (variable-assignment (when (listp binding) (cons 'setf binding))))
620 (push var *enclosing-lexical-block-declarations*)
621 (compile-parenscript-form `(progn ,variable-assignment ,@body) :expecting :expression)))))
622
623(defpsmacro let1-dynamic ((var value) &rest body)
624 (with-ps-gensyms (temp-stack-var)
625 `(progn (var ,temp-stack-var)
626 (try (progn (setf ,temp-stack-var ,var)
627 (setf ,var ,value)
628 ,@body)
915342fb
TC
629 (:finally
630 (setf ,var ,temp-stack-var)
631 (delete ,temp-stack-var))))))
18dd299a
VS
632
633;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
634;;; iteration
6a2ce72d
TC
635(defun make-for-vars/inits (init-forms)
636 (mapcar (lambda (x)
637 (cons (compile-parenscript-form (if (atom x) x (first x)) :expecting :symbol)
638 (compile-parenscript-form (if (atom x) nil (second x)))))
639 init-forms))
18dd299a 640
6a2ce72d
TC
641(define-ps-special-form labeled-for (expecting label init-forms cond-forms step-forms &rest body)
642 (declare (ignore expecting))
643 (let ((vars (make-for-vars/inits init-forms))
644 (steps (mapcar (lambda (x) (compile-parenscript-form x :expecting :expression)) step-forms))
645 (tests (mapcar (lambda (x) (compile-parenscript-form x :expecting :expression)) cond-forms))
646 (body (compile-parenscript-form `(progn ,@body))))
647 (list 'js-for label vars tests steps body)))
648
649(defpsmacro for (init-forms cond-forms step-forms &body body)
650 `(labeled-for nil ,init-forms ,cond-forms ,step-forms ,@body))
651
652(defun do-make-let-bindings (decls)
653 (mapcar (lambda (x)
654 (if (atom x) x
655 (if (endp (cdr x)) (list (car x))
656 (subseq x 0 2))))
657 decls))
658
659(defun do-make-init-vars (decls)
660 (mapcar (lambda (x) (if (atom x) x (first x))) decls))
661
662(defun do-make-init-vals (decls)
663 (mapcar (lambda (x) (if (or (atom x) (endp (cdr x))) nil (second x))) decls))
664
665(defun do-make-for-vars/init (decls)
666 (mapcar (lambda (x)
667 (if (atom x) x
668 (if (endp (cdr x)) x
669 (subseq x 0 2))))
670 decls))
671
672(defun do-make-for-steps (decls)
673 (mapcar (lambda (x)
674 `(setf ,(first x) ,(third x)))
675 (remove-if (lambda (x) (or (atom x) (< (length x) 3))) decls)))
676
677(defun do-make-iter-psteps (decls)
678 `(psetq
679 ,@(mapcan (lambda (x) (list (first x) (third x)))
680 (remove-if (lambda (x) (or (atom x) (< (length x) 3))) decls))))
681
682(defpsmacro do* (decls (termination &optional (result nil result?)) &body body)
683 (if result?
684 `((lambda ()
685 (for ,(do-make-for-vars/init decls) ((not ,termination)) ,(do-make-for-steps decls)
686 ,@body)
687 (return ,result)))
688 `(progn
689 (for ,(do-make-for-vars/init decls) ((not ,termination)) ,(do-make-for-steps decls)
690 ,@body))))
691
692(defpsmacro do (decls (termination &optional (result nil result?)) &body body)
693 (if result?
694 `((lambda ,(do-make-init-vars decls)
695 (for () ((not ,termination)) ()
696 ,@body
697 ,(do-make-iter-psteps decls))
698 (return ,result))
699 ,@(do-make-init-vals decls))
700 `(let ,(do-make-let-bindings decls)
701 (for () ((not ,termination)) ()
702 ,@body
703 ,(do-make-iter-psteps decls)))))
704
705(define-ps-special-form for-in (expecting decl &rest body)
18dd299a 706 (declare (ignore expecting))
6a2ce72d
TC
707 (list 'js-for-in
708 (compile-parenscript-form (first decl) :expecting :expression)
18dd299a 709 (compile-parenscript-form (second decl) :expecting :expression)
b508414b 710 (compile-parenscript-form `(progn ,@body))))
18dd299a 711
6a2ce72d
TC
712(defpsmacro doeach ((var array &optional (result (values) result?)) &body body)
713 "Iterates over `array'. If `var' is a symbol, binds `var' to each
714element key. If `var' is a list, it must be a list of two
715symbols, (key value), which will be bound to each successive key/value
716pair in `array'."
717 (if result?
718 (if (consp var)
719 (destructuring-bind (key val) var
720 `((lambda ()
721 (let* (,val)
722 (for-in ((var ,key) ,array)
723 (setf ,val (aref ,array ,key))
724 ,@body)
725 (return ,result)))))
726 `((lambda ()
727 (for-in ((var ,var) ,array)
728 ,@body)
729 (return ,result))))
730 (if (consp var)
731 (destructuring-bind (key val) var
732 `(progn
733 (let* (,val)
734 (for-in ((var ,key) ,array)
735 (setf ,val (aref ,array ,key))
736 ,@body))))
737 `(progn
738 (for-in ((var ,var) ,array) ,@body)))))
739
18dd299a
VS
740(define-ps-special-form while (expecting test &rest body)
741 (declare (ignore expecting))
742 (list 'js-while (compile-parenscript-form test :expecting :expression)
743 (compile-parenscript-form `(progn ,@body))))
744
6a2ce72d
TC
745(defpsmacro dotimes ((var count &optional (result nil result?)) &rest body)
746 `(do* ((,var 0 (1+ ,var)))
747 ((>= ,var ,count) ,@(when result? (list result)))
748 ,@body))
749
750(defpsmacro dolist ((var array &optional (result nil result?)) &body body)
751 (let ((idx (ps-gensym "_js_idx"))
752 (arrvar (ps-gensym "_js_arrvar")))
753 `(do* (,var
754 (,arrvar ,array)
755 (,idx 0 (1+ ,idx)))
756 ((>= ,idx (slot-value ,arrvar 'length))
757 ,@(when result? (list result)))
758 (setq ,var (aref ,arrvar ,idx))
759 ,@body)))
18dd299a
VS
760
761;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
762;;; misc
763(define-ps-special-form with (expecting expression &rest body)
764 (declare (ignore expecting))
765 (list 'js-with (compile-parenscript-form expression :expecting :expression)
b508414b 766 (compile-parenscript-form `(progn ,@body))))
18dd299a
VS
767
768(define-ps-special-form try (expecting form &rest clauses)
769 (declare (ignore expecting))
770 (let ((catch (cdr (assoc :catch clauses)))
771 (finally (cdr (assoc :finally clauses))))
772 (assert (not (cdar catch)) nil "Sorry, currently only simple catch forms are supported.")
773 (assert (or catch finally) ()
774 "Try form should have either a catch or a finally clause or both.")
775 (list 'js-try (compile-parenscript-form `(progn ,form))
776 :catch (when catch (list (compile-parenscript-form (caar catch) :expecting :symbol)
777 (compile-parenscript-form `(progn ,@(cdr catch)))))
778 :finally (when finally (compile-parenscript-form `(progn ,@finally))))))
779
780(define-ps-special-form cc-if (expecting test &rest body)
781 (declare (ignore expecting))
782 (list 'cc-if test (mapcar #'compile-parenscript-form body)))
783
784(define-ps-special-form regex (expecting regex)
785 (declare (ignore expecting))
786 (list 'js-regex (string regex)))
787
cb8f8e58
VS
788(define-ps-special-form lisp (expecting lisp-form)
789 ;; (ps (foo (lisp bar))) is in effect equivalent to (ps* `(foo ,bar))
790 ;; when called from inside of ps*, lisp-form has access only to the dynamic environment (like for eval)
791 (declare (ignore expecting))
792 (list 'js-escape lisp-form))