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