Got rid of parenscript-symbol object; special forms and macros are now
[clinton/parenscript.git] / src / compiler.lisp
1 (in-package :parenscript)
2
3 ;;; reserved symbols/literals
4
5 (defvar *ps-reserved-symbol-names* ()) ;; symbol names reserved for PS/JS literals
6
7 (defun add-ps-literal (name)
8 (push (symbol-name name) *ps-reserved-symbol-names*))
9
10 (defun ps-literal-p (symbol)
11 (find (symbol-name symbol) *ps-reserved-symbol-names* :test #'equalp))
12
13 ;;; special forms
14
15 (defvar *ps-special-forms* (make-hash-table :test 'eq))
16
17 (defun get-ps-special-form (name)
18 (gethash name *ps-special-forms*))
19
20 (defmacro define-ps-special-form (name lambda-list &rest body)
21 "Define a special form NAME. The first argument given to the special
22 form is a keyword indicating whether the form is expected to produce
23 an :expression or a :statement. The resulting Parenscript language
24 types are appended to the ongoing javascript compilation."
25 (let ((arglist (gensym "ps-arglist-")))
26 `(setf (gethash ',name *ps-special-forms*)
27 (lambda (&rest ,arglist)
28 (destructuring-bind ,lambda-list
29 ,arglist
30 ,@body)))))
31
32 (defun undefine-ps-special-form (name)
33 (remhash name *ps-special-forms*))
34
35 (defun ps-special-form-p (form)
36 (and (consp form)
37 (symbolp (car form))
38 (gethash (car form) *ps-special-forms*)))
39
40 ;;; scoping
41
42 (defvar *enclosing-lexical-block-declarations* ()
43 "This special variable is expected to be bound to a fresh list by
44 special forms that introduce a new JavaScript lexical block (currently
45 function definitions and lambdas). Enclosed special forms are expected
46 to push variable declarations onto the list when the variables
47 declaration cannot be made by the enclosed form \(for example, a
48 \(x,y,z\) expression progn\). It is then the responsibility of the
49 enclosing special form to introduce the variable bindings in its
50 lexical block.")
51
52 (defvar *ps-special-variables* ())
53
54 ;;; form predicates
55
56 (defun op-form-p (form)
57 (and (listp form)
58 (not (ps-special-form-p form))
59 (not (null (op-precedence (first form))))))
60
61 (defun funcall-form-p (form)
62 (and (listp form)
63 (not (op-form-p form))
64 (not (ps-special-form-p form))))
65
66 (defun method-call-p (form)
67 (and (funcall-form-p form)
68 (symbolp (first form))
69 (eql (char (symbol-name (first form)) 0) #\.)))
70
71 ;;; macro expansion
72 (eval-when (:compile-toplevel :load-toplevel :execute)
73 (defun make-macro-env-dictionary ()
74 (make-hash-table :test 'eq))
75 (defvar *ps-macro-toplevel* (make-macro-env-dictionary)
76 "Toplevel macro environment dictionary. Key is the symbol name of
77 the macro, value is (symbol-macro-p . expansion-function).")
78 (defvar *ps-macro-env* (list *ps-macro-toplevel*)
79 "Current macro environment.")
80
81 (defvar *ps-setf-expanders* (make-macro-env-dictionary)
82 "Setf expander dictionary. Key is the symbol of the access
83 function of the place, value is an expansion function that takes the
84 arguments of the access functions as a first value and the form to be
85 stored as the second value.")
86
87 (defun get-macro-spec (name env-dict)
88 "Retrieves the macro spec of the given name with the given environment dictionary.
89 SPEC is of the form (symbol-macro-p . expansion-function)."
90 (gethash name env-dict))
91 (defsetf get-macro-spec (name env-dict)
92 (spec)
93 `(setf (gethash ,name ,env-dict) ,spec)))
94
95 (defun lookup-macro-spec (name &optional (environment *ps-macro-env*))
96 "Looks up the macro spec associated with NAME in the given environment. A
97 macro spec is of the form (symbol-macro-p . function). Returns two values:
98 the SPEC and the parent macro environment.
99
100 NAME must be a symbol."
101 (when (symbolp name)
102 (do ((env environment (cdr env)))
103 ((null env) nil)
104 (let ((val (get-macro-spec name (car env))))
105 (when val
106 (return-from lookup-macro-spec
107 (values val (or (cdr env)
108 (list *ps-macro-toplevel*)))))))))
109
110 (defun ps-symbol-macro-p (name &optional (environment *ps-macro-env*))
111 "True if there is a Parenscript symbol macro named by the symbol NAME."
112 (and (symbolp name) (car (lookup-macro-spec name environment))))
113
114 (defun ps-macro-p (name &optional (environment *ps-macro-env*))
115 "True if there is a Parenscript macro named by the symbol NAME."
116 (and (symbolp name)
117 (let ((macro-spec (lookup-macro-spec name environment)))
118 (and macro-spec (not (car macro-spec))))))
119
120 (defun lookup-macro-expansion-function (name &optional (environment *ps-macro-env*))
121 "Lookup NAME in the given macro expansion environment (which
122 defaults to the current macro environment). Returns the expansion
123 function and the parent macro environment of the macro."
124 (multiple-value-bind (macro-spec parent-env)
125 (lookup-macro-spec name environment)
126 (values (cdr macro-spec) parent-env)))
127
128 (eval-when (:compile-toplevel :load-toplevel :execute)
129 (defun make-ps-macro-function (args body)
130 (let* ((whole-var (when (eql '&whole (first args)) (second args)))
131 (effective-lambda-list (if whole-var (cddr args) args))
132 (form-arg (or whole-var (gensym "ps-macro-form-arg-")))
133 (body (if (and (cdr body) (stringp (first body))) (rest body) body))) ;; drop docstring
134 (compile nil `(lambda (,form-arg)
135 (destructuring-bind ,effective-lambda-list
136 (cdr ,form-arg)
137 ,@body)))))
138
139 (defun define-ps-macro% (name args body &key symbol-macro-p)
140 (undefine-ps-special-form name)
141 (setf (get-macro-spec name *ps-macro-toplevel*)
142 (cons symbol-macro-p (make-ps-macro-function args body)))
143 nil))
144
145 (defmacro defpsmacro (name args &body body)
146 "Define a ParenScript macro, and store it in the toplevel ParenScript
147 macro environment."
148 `(define-ps-macro% ',name ',args ',body :symbol-macro-p nil))
149
150 (defmacro define-ps-symbol-macro (name &body body)
151 "Define a ParenScript symbol macro, and store it in the toplevel ParenScript
152 macro environment. BODY is a Lisp form that should return a ParenScript form."
153 `(define-ps-macro% ',name () ',body :symbol-macro-p t))
154
155 (defun import-macros-from-lisp (&rest names)
156 "Import the named Lisp macros into the ParenScript macro
157 environment. When the imported macro is macroexpanded by ParenScript,
158 it is first fully macroexpanded in the Lisp macro environment, and
159 then that expansion is further expanded by ParenScript."
160 (dolist (name names)
161 (define-ps-macro% name '(&rest args)
162 (list `(common-lisp:macroexpand `(,',name ,@args)))
163 :symbol-macro-p nil)))
164
165 (defmacro defmacro/ps (name args &body body)
166 "Define a Lisp macro and import it into the ParenScript macro environment."
167 `(progn (defmacro ,name ,args ,@body)
168 (ps:import-macros-from-lisp ',name)))
169
170 (defmacro defmacro+ps (name args &body body)
171 "Define a Lisp macro and a ParenScript macro in their respective
172 macro environments. This function should be used when you want to use
173 the same macro in both Lisp and ParenScript, but the 'macroexpand' of
174 that macro in Lisp makes the Lisp macro unsuitable to be imported into
175 the ParenScript macro environment."
176 `(progn (defmacro ,name ,args ,@body)
177 (defpsmacro ,name ,args ,@body)))
178
179 (defun ps-macroexpand (form)
180 "Recursively macroexpands ParenScript macros and symbol-macros in
181 the given ParenScript form. Returns two values: the expanded form, and
182 whether any expansion was performed on the form or not."
183 (if (consp form)
184 (let ((op (car form))
185 (args (cdr form)))
186 (cond ((equal op 'quote) (values (if (equalp '(nil) args) nil form) ; leave quotes alone, unless it's a quoted nil
187 nil))
188 ((ps-macro-p op) (values (ps-macroexpand (funcall (lookup-macro-expansion-function op) form)) t))
189 (t (values form nil))))
190 (cond ((ps-symbol-macro-p form) (values (ps-macroexpand (funcall (lookup-macro-expansion-function form) (list form))) t))
191 (t (values form nil)))))
192
193 ;;;; compiler interface
194 (defgeneric compile-parenscript-form (form &key expecting)
195 (:documentation "Compiles a ParenScript form to the intermediate
196 ParenScript representation. :expecting determines whether the form is
197 compiled to an :expression (the default), a :statement, or a
198 :symbol."))
199
200 (defmethod compile-parenscript-form :around (form &key expecting)
201 (assert (if expecting (member expecting '(:expression :statement :symbol)) t))
202 (if (eql expecting :symbol)
203 (compile-to-symbol form)
204 (multiple-value-bind (expanded-form expanded-p)
205 (ps-macroexpand form)
206 (if expanded-p
207 (compile-parenscript-form expanded-form :expecting expecting)
208 (call-next-method)))))
209
210 (defun compile-to-symbol (form)
211 "Compiles the given Parenscript form and guarantees that the
212 resultant symbol has an associated script-package. Raises an error if
213 the form cannot be compiled to a symbol."
214 (let ((exp (compile-parenscript-form form)))
215 (when (or (eql (first exp) 'js-variable)
216 (eql (first exp) 'ps-quote))
217 (setf exp (second exp)))
218 (assert (symbolp exp) ()
219 "~a is expected to be a symbol, but compiles to ~a (the ParenScript output for ~a alone is \"~a\"). This could be due to ~a being a special form." form exp form (ps* form) form)
220 exp))
221
222 (defmethod compile-parenscript-form (form &key expecting)
223 (declare (ignore expecting))
224 (error "The object ~S cannot be compiled by ParenScript." form))
225
226 (defmethod compile-parenscript-form ((form number) &key expecting)
227 (declare (ignore expecting))
228 form)
229
230 (defmethod compile-parenscript-form ((form string) &key expecting)
231 (declare (ignore expecting))
232 form)
233
234 (defmethod compile-parenscript-form ((form character) &key expecting)
235 (declare (ignore expecting))
236 (compile-parenscript-form (string form)))
237
238 (defmethod compile-parenscript-form ((symbol symbol) &key expecting)
239 (declare (ignore expecting))
240 (cond ((ps-special-form-p (list symbol))
241 (if (ps-literal-p symbol)
242 (funcall (get-ps-special-form symbol) :symbol)
243 (error "Attempting to use Parenscript special form ~a as variable" symbol)))
244 (t (list 'js-variable symbol))))
245
246 (defun compile-function-argument-forms (arg-forms)
247 "Compiles a bunch of Parenscript forms from a funcall form to an effective set of
248 Javascript arguments. The only extra processing this does is makes :keyword arguments
249 into a single options argument via CREATE."
250 (flet ((keyword-arg (arg)
251 "If the given compiled expression is supposed to be a keyword argument, returns
252 the keyword for it."
253 (when (and (listp arg) (eql (first arg) 'ps-quote)) (second arg))))
254 (let ((compiled-args (mapcar (lambda (arg) (compile-parenscript-form arg :expecting :expression))
255 arg-forms)))
256 (do ((effective-expressions nil)
257 (expressions-subl compiled-args))
258 ((not expressions-subl) (reverse effective-expressions))
259 (let ((arg-expr (first expressions-subl)))
260 (if (keyword-arg arg-expr)
261 (progn (when (oddp (length expressions-subl))
262 (error "Odd number of keyword arguments: ~A." arg-forms))
263 (push (list 'js-object (loop for (name val) on expressions-subl by #'cddr
264 collect (list name val)))
265 effective-expressions)
266 (setf expressions-subl nil))
267 (progn (push arg-expr effective-expressions)
268 (setf expressions-subl (rest expressions-subl)))))))))
269
270 (defun ps-convert-op-name (op)
271 (case (ensure-ps-symbol op)
272 (and '\&\&)
273 (or '\|\|)
274 (not '!)
275 (eql '\=\=)
276 (= '\=\=)
277 (t op)))
278
279 (defmethod compile-parenscript-form ((form cons) &key (expecting :statement))
280 (let* ((name (car form))
281 (args (cdr form)))
282 (cond ((eql name 'quote)
283 (assert (= 1 (length args)) () "Wrong number of arguments to quote: ~s" args)
284 (list 'ps-quote (first args)))
285 ((ps-special-form-p form) (apply (get-ps-special-form name) (cons expecting args)))
286 ((op-form-p form)
287 (list 'operator
288 (ps-convert-op-name (compile-parenscript-form (first form) :expecting :symbol))
289 (mapcar (lambda (form) (compile-parenscript-form form :expecting :expression)) (rest form))))
290 ((method-call-p form)
291 (list 'js-method-call
292 (compile-parenscript-form name :expecting :symbol)
293 (compile-parenscript-form (first args) :expecting :expression)
294 (compile-function-argument-forms (rest args))))
295 ((funcall-form-p form)
296 (list 'js-funcall
297 (compile-parenscript-form name :expecting :expression)
298 (compile-function-argument-forms args)))
299 (t (error "Cannot compile ~S to a ParenScript form." form)))))
300
301 (defvar *ps-gensym-counter* 0)
302
303 (defun ps-gensym (&optional (prefix "_js"))
304 (make-symbol (format nil "~A~A" prefix (incf *ps-gensym-counter*))))
305
306 (defmacro with-ps-gensyms (symbols &body body)
307 "Evaluate BODY with SYMBOLS bound to unique ParenScript identifiers.
308
309 Each element of SYMBOLS is either a symbol or a list of (symbol
310 gensym-prefix-string)."
311 `(let* ,(mapcar (lambda (symbol)
312 (destructuring-bind (symbol &optional prefix)
313 (if (consp symbol)
314 symbol
315 (list symbol))
316 (if prefix
317 `(,symbol (ps-gensym ,prefix))
318 `(,symbol (ps-gensym ,(symbol-to-js-string symbol))))))
319 symbols)
320 ,@body))
321
322 (defun %check-once-only-vars (vars)
323 (let ((bad-var (find-if (lambda (x) (or (not (symbolp x)) (keywordp x))) vars)))
324 (when bad-var
325 (error "PS-ONLY-ONCE expected a non-keyword symbol but got ~s" bad-var))))
326
327 (defmacro ps-once-only ((&rest vars) &body body)
328 (%check-once-only-vars vars)
329 (let ((gensyms (mapcar (lambda (x) (ps-gensym (string x))) vars)))
330 `(let ,(mapcar (lambda (g v) `(,g (ps-gensym ,(string v)))) gensyms vars)
331 `(let* (,,@(mapcar (lambda (g v) ``(,,g ,,v)) gensyms vars))
332 ,(let ,(mapcar (lambda (g v) `(,v ,g)) gensyms vars)
333 ,@body)))))