3 ;;; Code generator for effective methods
5 ;;; (c) 2009 Straylight/Edgeware
8 ;;;----- Licensing notice ---------------------------------------------------
10 ;;; This file is part of the Simple Object Definition system.
12 ;;; SOD is free software; you can redistribute it and/or modify
13 ;;; it under the terms of the GNU General Public License as published by
14 ;;; the Free Software Foundation; either version 2 of the License, or
15 ;;; (at your option) any later version.
17 ;;; SOD is distributed in the hope that it will be useful,
18 ;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
19 ;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
20 ;;; GNU General Public License for more details.
22 ;;; You should have received a copy of the GNU General Public License
23 ;;; along with SOD; if not, write to the Free Software Foundation,
24 ;;; Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
28 ;;;--------------------------------------------------------------------------
31 (defclass temporary-name ()
32 ((tag :initarg :tag :reader temp-tag))
34 "Base class for temporary variable and argument names."))
36 (defclass temporary-argument (temporary-name) ())
37 (defclass temporary-function (temporary-name) ())
39 (defclass temporary-variable (temporary-name)
40 ((in-use-p :initarg :in-use-p :initform nil
41 :type boolean :accessor var-in-use-p)))
43 (defmethod var-in-use-p ((var t))
44 "Non-temporary variables are always in use."
47 (defmethod commentify-argument-name ((name temporary-name))
50 (defparameter *temporary-index* 0
51 "Index for temporary name generation.
53 This is automatically reset to zero before the output functions are
54 invoked to write a file. This way, we can ensure that the same output
55 file is always produced from the same input.")
57 (defun temporary-function ()
58 "Return a temporary function name."
59 (make-instance 'temporary-function
60 :tag (prog1 *temporary-index* (incf *temporary-index*))))
62 (defgeneric format-temporary-name (var stream)
63 (:method ((var temporary-name) stream)
64 (format stream "~A" (temp-tag var)))
65 (:method ((var temporary-argument) stream)
66 (format stream "sod__a~A" (temp-tag var)))
67 (:method ((var temporary-variable) stream)
68 (format stream "sod__v~A" (temp-tag var)))
69 (:method ((var temporary-function) stream)
70 (format stream "sod__f~A" (temp-tag var))))
72 (defmethod print-object ((var temporary-name) stream)
74 (print-unreadable-object (var stream :type t)
75 (prin1 (temp-tag var) stream))
76 (format-temporary-name var stream)))
78 (defparameter *sod-ap*
79 (make-instance 'temporary-name :tag "sod__ap"))
80 (defparameter *sod-master-ap*
81 (make-instance 'temporary-name :tag "sod__master_ap"))
83 ;;;--------------------------------------------------------------------------
88 "A base class for instructions.
90 An `instruction' is anything which might be useful to string into a code
91 generator. Both statements and expressions map can be represented by
92 trees of instructions. The DEFINST macro is a convenient way of defining
95 The only important protocol for instructions is output, which is achieved
96 by calling PRINT-OBJECT with *PRINT-ESCAPE* nil.
98 This doesn't really do very much, but it acts as a handy marker for
99 instruction subclasses."))
101 (defgeneric inst-metric (inst)
103 "Returns a `metric' describing how complicated INST is.
105 The default metric of an inst node is simply 1; INST subclasses generated
106 by DEFINST (q.v.) have an automatically generated method which returns one
107 plus the sum of the metrics of the node's children.
109 This isn't intended to be a particularly rigorous definition. Its purpose
110 is to allow code generators to make decisions about inlining or calling
111 code fairly simply.")
114 (defmacro definst (code (streamvar) args &body body)
115 "Define an instruction type and describe how to output it.
117 An INST can represent any structured piece of output syntax: a statement,
118 expression or declaration, for example. This macro defines the following
121 * A class CODE-INST to represent the instruction.
123 * Instance slots named after the ARGS, with matching keyword initargs,
124 and INST-ARG readers.
126 * A constructor MAKE-CODE-INST which accepts the ARGS (in order, not
127 with keywords) as arguments and returns a fresh instance.
129 * A print method, which prints a diagnostic dump if *PRINT-ESCAPE* is
130 set, or invokes the BODY (with STREAMVAR bound to the output stream)
131 otherwise. The BODY is expected to produce target code at this
134 (let ((inst-var (gensym "INST"))
135 (class-name (symbolicate code '-inst))
136 (keys (mapcar (lambda (arg) (intern (symbol-name arg) :keyword))
139 (defclass ,class-name (inst)
140 ,(mapcar (lambda (arg key)
141 `(,arg :initarg ,key :reader ,(symbolicate 'inst- arg)))
143 (defun ,(symbolicate 'make- code '-inst) (,@args)
144 (make-instance ',class-name ,@(mappend #'list keys args)))
145 (defmethod inst-metric ((,inst-var ,class-name))
146 (with-slots (,@args) ,inst-var
147 (+ 1 ,@(mapcar (lambda (arg) `(inst-metric ,arg)) args))))
148 (defmethod print-object ((,inst-var ,class-name) ,streamvar)
149 (with-slots (,@args) ,inst-var
151 (print-unreadable-object (,inst-var ,streamvar :type t)
152 (format stream "~@<~@{~S ~@_~S~^ ~_~}~:>"
153 ,@(mappend #'list keys args)))
156 (defun format-compound-statement* (stream child morep thunk)
157 "Underlying function for FORMAT-COMPOUND-STATEMENT."
158 (cond ((typep child 'block-inst)
159 (funcall thunk stream)
160 (write-char #\space stream)
162 (when morep (write-char #\space stream)))
164 (pprint-logical-block (stream nil)
165 (funcall thunk stream)
166 (write-char #\space stream)
167 (pprint-indent :block 2 stream)
168 (pprint-newline :linear stream)
170 (pprint-indent :block 0 stream)
173 (write-char #\space stream)
174 (pprint-newline :linear stream))
176 (pprint-newline :mandatory stream)))))))
178 (defmacro format-compound-statement
179 ((stream child &optional morep) &body body)
180 "Format a compound statement to STREAM.
182 The introductory material is printed by BODY. The CHILD is formatted
183 properly according to whether it's a BLOCK-INST. If MOREP is true, then
184 allow for more stuff following the child."
185 `(format-compound-statement* ,stream ,child ,morep
186 (lambda (,stream) ,@body)))
188 ;;;--------------------------------------------------------------------------
189 ;;; Instruction types.
191 ;; Compound statements.
193 (definst block (stream) (decls body)
194 (format stream "{~:@_~@< ~2I~@[~{~A;~:@_~}~:@_~]~{~A~^~:@_~}~:>~:@_}"
197 (definst if (stream) (condition consequent alternative)
198 (format-compound-statement (stream consequent alternative)
199 (format stream "if (~A)" condition))
201 (format-compound-statement (stream alternative)
202 (write-string "else" stream))))
204 (definst while (stream) (condition body)
205 (format-compound-statement (stream body)
206 (format stream "while (~A)" condition)))
208 (definst do-while (stream) (body condition)
209 (format-compound-statement (stream body :space)
210 (write-string "do" stream))
211 (format stream "while (~A);" condition))
213 ;; Simple statements.
215 (definst set (stream) (var expr)
216 (format stream "~@<~A = ~@_~2I~A;~:>" var expr))
218 (definst return (stream) (expr)
219 (format stream "return~@[ (~A)~];" expr))
221 (definst expr (stream) (expr)
222 (format stream "~A;" expr))
224 ;; Special varargs hacks.
226 (definst va-start (stream) (ap arg)
227 (format stream "va_start(~@<~A, ~_~A~:>);" ap arg))
229 (definst va-copy (stream) (to from)
230 (format stream "va_copy(~@<~A, ~_~A~:>);" to from))
232 (definst va-end (stream) (ap)
233 (format stream "va_end(~A);" ap))
235 ;; Declarations. These should appear at the heads of BLOCK-INSTs.
237 (definst var (stream) (name type init)
238 (pprint-c-type type stream name)
240 (format stream " = ~A" init)))
244 (definst call (stream) (func args)
245 (format stream "~A(~@<~{~A~^, ~_~}~:>)" func args))
249 (definst function (stream) (name type body)
250 (pprint-logical-block (stream nil)
251 (princ "static " stream)
252 (pprint-c-type type stream name)
253 (format stream "~:@_~A~:@_~:@_" body)))
255 ;;;--------------------------------------------------------------------------
256 ;;; Code generator objects.
258 (defclass basic-codegen ()
259 ((vars :initarg :vars :initform nil :type list :accessor codegen-vars)
260 (insts :initarg :insts :initform nil :type list :accessor codegen-insts)
261 (temp-index :initarg :temp-index :initform 0
262 :type fixnum :accessor codegen-temp-index))
264 "Base class for code generator state.
266 This contains the bare essentials for supporting the EMIT-INST and
267 ENSURE-VAR protocols; see the documentation for those generic functions
270 This class isn't abstract. A full CODEGEN object uses instances of this
271 to keep track of pending functions which haven't been completed yet.
273 Just in case that wasn't clear enough: this is nothing to do with the
276 (defgeneric emit-inst (codegen inst)
278 "Add INST to the end of CODEGEN's list of instructions.")
279 (:method ((codegen basic-codegen) inst)
280 (push inst (codegen-insts codegen))))
282 (defgeneric emit-insts (codegen insts)
284 "Add a list of INSTS to the end of CODEGEN's list of instructions.")
285 (:method ((codegen basic-codegen) insts)
286 (setf (codegen-insts codegen)
287 (revappend insts (codegen-insts codegen)))))
289 (defgeneric ensure-var (codegen name type &optional init)
291 "Add a variable to CODEGEN's list.
293 The variable is called NAME (which should be comparable using EQUAL and
294 print to an identifier) and has the given TYPE. If INIT is present and
295 non-nil it is an expression INST used to provide the variable with an
297 (:method ((codegen basic-codegen) name type &optional init)
298 (let* ((vars (codegen-vars codegen))
299 (var (find name vars :key #'inst-name :test #'equal)))
301 (setf (codegen-vars codegen)
302 (cons (make-var-inst name type init) vars)))
303 ((not (c-type-equal-p type (inst-type var)))
304 (error "(Internal) Redefining type for variable ~A." name)))
307 (defclass codegen (basic-codegen)
308 ((functions :initform nil :type list :accessor codegen-functions)
309 (stack :initform nil :type list :accessor codegen-stack))
311 "A full-fat code generator which can generate and track functions.
313 This is the real deal. Subclasses may which to attach additional state
314 for convenience's sake, but this class is self-contained. It supports the
315 CODEGEN-PUSH, CODEGEN-POP and CODEGEN-POP-FUNCTION protocols."))
317 (defgeneric codegen-push (codegen)
319 "Pushes the current code generation state onto a stack.
321 The state consists of the accumulated variables and instructions, i.e.,
322 what is representable by a BASIC-CODEGEN.")
323 (:method ((codegen codegen))
324 (with-slots (vars insts temp-index stack) codegen
325 (push (make-instance 'basic-codegen
328 :temp-index temp-index)
330 (setf vars nil insts nil temp-index 0))))
332 (defgeneric codegen-pop (codegen)
334 "Pops a saved state off of the CODEGEN's stack.
336 Returns the newly accumulated variables and instructions as lists, as
338 (:method ((codegen codegen))
339 (with-slots (vars insts temp-index stack) codegen
340 (multiple-value-prog1
341 (values (nreverse vars) (nreverse insts))
342 (let ((sub (pop stack)))
343 (setf vars (codegen-vars sub)
344 insts (codegen-insts sub)
345 temp-index (codegen-temp-index sub)))))))
347 (defgeneric codegen-add-function (codegen function)
349 "Adds a function to CODEGEN's list.
351 Actually, we're not picky: FUNCTION can be any kind of object that you're
352 willing to find in the list returned by CODEGEN-FUNCTIONS.")
353 (:method ((codegen codegen) function)
354 (with-slots (functions) codegen
355 (setf functions (nconc functions (list function))))))
357 (defun codegen-build-function (codegen name type vars insts)
358 "Build a function and add it to CODEGEN's list.
360 Returns the function's name."
361 (codegen-add-function codegen
362 (make-function-inst name type
363 (make-block-inst vars insts)))
366 (defgeneric codegen-pop-function (codegen name type)
368 "Makes a function out of the completed code in CODEGEN.
370 The NAME can be any object you like. The TYPE should be a function type
371 object which includes argument names. The return value is the NAME.")
372 (:method ((codegen codegen) name type)
373 (multiple-value-bind (vars insts) (codegen-pop codegen)
374 (codegen-build-function codegen name type vars insts))))
376 (defgeneric temporary-var (codegen type)
378 "Return the name of a temporary variable.
380 The temporary variable will have the given TYPE, and will be marked
381 in-use. You should clear the in-use flag explicitly when you've finished
382 with the variable -- or, better, use WITH-TEMPORARY-VAR to do the cleanup
385 (defmethod temporary-var ((codegen basic-codegen) type)
386 (with-slots (vars temp-index) codegen
387 (or (find-if (lambda (var)
388 (and (not (var-in-use-p (inst-name var)))
389 (c-type-equal-p type (inst-type var))))
391 (let* ((name (make-instance 'temporary-variable
392 :tag (prog1 temp-index
393 (incf temp-index)))))
394 (push (make-var-inst name type nil) vars)
397 (defmacro with-temporary-var ((codegen var type) &body body)
398 "Evaluate BODY with VAR bound to a temporary variable name.
400 During BODY, VAR will be marked in-use; when BODY ends, VAR will be marked
401 available for re-use."
402 `(let ((,var (temporary-var ,codegen ,type)))
405 (setf (var-in-use-p ,var) nil))))
407 ;;;--------------------------------------------------------------------------
408 ;;; Code generation idioms.
410 (defun deliver-expr (codegen target expr)
411 "Emit code to deliver the value of EXPR to the TARGET.
413 The TARGET may be one of the following.
415 * :VOID, indicating that the value is to be discarded. The expression
416 will still be evaluated.
418 * :VOID-RETURN, indicating that the value is to be discarded (as for
419 :VOID) and furthermore a `return' from the current function should be
420 forced after computing the value.
422 * :RETURN, indicating that the value is to be returned from the current
425 * A variable name, indicating that the value is to be stored in the
428 In the cases of :RETURN, :VOID and :VOID-RETURN targets, it is valid for
429 EXPR to be nil; this signifies that no computation needs to be performed.
430 Variable-name targets require an expression."
433 (:return (emit-inst codegen (make-return-inst expr)))
434 (:void (when expr (emit-inst codegen (make-expr-inst expr))))
435 (:void-return (when expr (emit-inst codegen (make-expr-inst expr)))
436 (emit-inst codegen (make-return-inst nil)))
437 (t (emit-inst codegen (make-set-inst target expr)))))
439 (defun convert-stmts (codegen target type func)
440 "Invoke FUNC to deliver a value to a non-:RETURN target.
442 FUNC is a function which accepts a single argument, a non-:RETURN target,
443 and generates statements which deliver a value (see DELIVER-EXPR) of the
444 specified TYPE to this target. In general, the generated code will have
447 setup instructions...
448 (DELIVER-EXPR CODEGEN TARGET (compute value...))
449 cleanup instructions...
451 where the cleanup instructions are essential to the proper working of the
454 CONVERT-STMTS will call FUNC to generate code, and arrange that its value
455 is correctly delivered to TARGET, regardless of what the TARGET is --
456 i.e., it lifts the restriction to non-:RETURN targets. It does this by
457 inventing a new temporary variable."
460 (:return (with-temporary-var (codegen var type)
462 (deliver-expr codegen target var)))
463 (:void-return (funcall func :void)
464 (emit-inst codegen (make-return-inst nil)))
465 (t (funcall func target))))
467 ;;;----- That's all, folks --------------------------------------------------