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