"Answer whether VAR is currently being used. See `with-temporary-var'.")
(:method (var)
"Non-temporary variables are always in use."
+ (declare (ignore var))
t))
(defgeneric (setf var-in-use-p) (value var)
(:documentation
;; Root class.
-(export 'temporary-name)
+(export '(temporary-name temp-tag))
(defclass temporary-name ()
((tag :initarg :tag :reader temp-tag))
(:documentation
"Base class for temporary variable and argument names."))
-;; Important variables.
-
-(defparameter *temporary-index* 0
- "Index for temporary name generation.
-
- This is automatically reset to zero before the output functions are
- invoked to write a file. This way, we can ensure that the same output
- file is always produced from the same input."
- ;; FIXME: this is currently a lie. Need some protocol to ensure that this
- ;; happens.
-)
-
;; Important temporary names.
(export '(*sod-ap* *sod-master-ap*))
(make-instance 'temporary-name :tag "sod__ap"))
(defparameter *sod-master-ap*
(make-instance 'temporary-name :tag "sod__master_ap"))
+(defparameter *sod-tmp-ap*
+ (make-instance 'temporary-name :tag "sod__tmp_ap"))
;;;--------------------------------------------------------------------------
;;; Instructions.
"A base class for instructions.
An `instruction' is anything which might be useful to string into a code
- generator. Both statements and expressions map can be represented by
- trees of instructions. The `definst' macro is a convenient way of
- defining new instructions.
+ generator. Both statements and expressions can be represented by trees of
+ instructions. The `definst' macro is a convenient way of defining new
+ instructions.
The only important protocol for instructions is output, which is achieved
by calling `print-object' with `*print-escape*' nil.
This isn't intended to be a particularly rigorous definition. Its purpose
is to allow code generators to make decisions about inlining or calling
code fairly simply.")
- (:method (inst) 1))
+ (:method ((inst t))
+ (declare (ignore inst))
+ 1)
+ (:method ((inst null))
+ (declare (ignore inst))
+ 1)
+ (:method ((inst list))
+ (reduce #'+ inst :key #'inst-metric)))
;; Instruction definition.
(export 'definst)
-(defmacro definst (code (streamvar) args &body body)
+(defmacro definst (code (streamvar &key export) args &body body)
"Define an instruction type and describe how to output it.
An `inst' can represent any structured piece of output syntax: a
* A print method, which prints a diagnostic dump if `*print-escape*' is
set, or invokes the BODY (with STREAMVAR bound to the output stream)
otherwise. The BODY is expected to produce target code at this
- point."
+ point.
+
+ If EXPORT is non-nil, then export the `CODE-inst' and `make-CODE-inst'
+ symbols."
(let ((inst-var (gensym "INST"))
(class-name (symbolicate code '-inst))
+ (constructor-name (symbolicate 'make- code '-inst))
(keys (mapcar (lambda (arg) (intern (symbol-name arg) :keyword))
args)))
`(progn
,(mapcar (lambda (arg key)
`(,arg :initarg ,key :reader ,(symbolicate 'inst- arg)))
args keys))
- (defun ,(symbolicate 'make- code '-inst) (,@args)
+ (defun ,constructor-name (,@args)
(make-instance ',class-name ,@(mappend #'list keys args)))
(defmethod inst-metric ((,inst-var ,class-name))
(with-slots (,@args) ,inst-var
(print-unreadable-object (,inst-var ,streamvar :type t)
(format stream "~@<~@{~S ~@_~S~^ ~_~}~:>"
,@(mappend #'list keys args)))
- (progn ,@body)))))))
+ (progn ,@body))))
+ ,@(and export `((export '(,class-name ,constructor-name
+ ,@(mapcar (lambda (arg)
+ (symbolicate 'inst- arg))
+ args)))))
+ ',code)))
;; Important instruction classes.
-(export '(block-inst make-block-inst var-inst make-var-inst
- function-inst make-function-inst set-inst make-set-inst
- return-inst make-return-inst expr-inst make-expr-inst
- inst-decls inst-body inst-name inst-type inst-init inst-var
- inst-expr))
+;; HACK: use a gensym for the `expr' and `type' slots to avoid leaking the
+;; slot names, since the symbol `expr' is exported from our package and
+;; `type' belongs to the `common-lisp' package.
-(definst var (stream) (name type init)
- (pprint-c-type type stream name)
+(definst var (stream :export t) (name #1=#:type init)
+ (pprint-c-type #1# stream name)
(when init
- (format stream " = ~A" init)))
-(definst set (stream) (var expr)
- (format stream "~@<~A = ~@_~2I~A;~:>" var expr))
-(definst return (stream) (expr)
- (format stream "return~@[ (~A)~];" expr))
-(definst expr (stream) (expr)
- (format stream "~A;" expr))
-(definst block (stream) (decls body)
- (format stream "{~:@_~@< ~2I~@[~{~A;~:@_~}~:@_~]~{~A~^~:@_~}~:>~:@_}"
+ (format stream " = ~A" init))
+ (write-char #\; stream))
+(definst set (stream :export t) (var #1=#:expr)
+ (format stream "~@<~A = ~@_~2I~A;~:>" var #1#))
+(definst update (stream :export t) (var op #1=#:expr)
+ (format stream "~@<~A ~A= ~@_~2I~A;~:>" var op #1#))
+(definst return (stream :export t) (#1=#:expr)
+ (format stream "return~@[ (~A)~];" #1#))
+(definst break (stream :export t) ()
+ (format stream "break;"))
+(definst continue (stream :export t) ()
+ (format stream "continue;"))
+(definst expr (stream :export t) (#1=#:expr)
+ (format stream "~A;" #1#))
+(definst block (stream :export t) (decls body)
+ (format stream "{~:@_~@< ~2I~@[~{~A~:@_~}~:@_~]~{~A~^~:@_~}~:>~:@_}"
decls body))
-(definst function (stream) (name type body)
+(definst function (stream :export t) (name #1=#:type body)
(pprint-logical-block (stream nil)
(princ "static " stream)
- (pprint-c-type type stream name)
+ (pprint-c-type #1# stream name)
(format stream "~:@_~A~:@_~:@_" body)))
;; Formatting utilities.
(:method (codegen insts)
(dolist (inst insts) (emit-inst codegen inst))))
+(export '(emit-decl emit-decls))
+(defgeneric emit-decl (codegen inst)
+ (:documentation
+ "Add INST to the end of CODEGEN's list of declarations."))
+(defgeneric emit-decls (codegen insts)
+ (:documentation
+ "Add a list of INSTS to the end of CODEGEN's list of declarations."))
+
(export 'codegen-push)
(defgeneric codegen-push (codegen)
(:documentation
"Evaluate BODY with VAR bound to a temporary variable name.
During BODY, VAR will be marked in-use; when BODY ends, VAR will be marked
- available for re-use."
+ available for re-use."
`(let ((,var (temporary-var ,codegen ,type)))
(unwind-protect
(progn ,@body)