;;;----- Licensing notice ---------------------------------------------------
;;;
-;;; This file is part of the Sensble Object Design, an object system for C.
+;;; This file is part of the Sensible Object Design, an object system for C.
;;;
;;; SOD is free software; you can redistribute it and/or modify
;;; it under the terms of the GNU General Public License as published by
;; 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.")
-
-(define-clear-the-decks reset-codegen-index
- (setf *temporary-index* 0))
-
;; 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"))
+(defparameter *sod-tmp-val*
+ (make-instance 'temporary-name :tag "sod__t"))
;;;--------------------------------------------------------------------------
;;; Instructions.
* Instance slots named after the ARGS, with matching keyword initargs,
and `inst-ARG' readers.
- * A constructor `make-CODE-inst' which accepts the ARGS (in order, not
- with keywords) as arguments and returns a fresh instance.
+ * A constructor `make-CODE-inst' which accepts the ARGS (as an ordinary
+ BVL) as arguments and returns a fresh instance.
* A print method, which prints a diagnostic dump if `*print-escape*' is
set, or invokes the BODY (with STREAMVAR bound to the output stream)
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)))
+ (let* ((inst-var (gensym "INST"))
+ (class-name (symbolicate code '-inst))
+ (constructor-name (symbolicate 'make- code '-inst))
+ (slots (mapcan (lambda (arg)
+ (if (listp arg) (list (car arg))
+ (let ((name (symbol-name arg)))
+ (if (and (plusp (length name))
+ (char/= (char name 0) #\&))
+ (list arg)
+ nil))))
+ args))
+ (keys (mapcar (lambda (arg) (intern (symbol-name arg) :keyword))
+ slots)))
`(progn
(defclass ,class-name (inst)
- ,(mapcar (lambda (arg key)
- `(,arg :initarg ,key :reader ,(symbolicate 'inst- arg)))
- args keys))
+ ,(mapcar (lambda (slot key)
+ `(,slot :initarg ,key
+ :reader ,(symbolicate 'inst- slot)))
+ slots keys))
(defun ,constructor-name (,@args)
- (make-instance ',class-name ,@(mappend #'list keys args)))
+ (make-instance ',class-name ,@(mappend #'list keys slots)))
(defmethod inst-metric ((,inst-var ,class-name))
- (with-slots (,@args) ,inst-var
- (+ 1 ,@(mapcar (lambda (arg) `(inst-metric ,arg)) args))))
+ (with-slots (,@slots) ,inst-var
+ (+ 1 ,@(mapcar (lambda (slot) `(inst-metric ,slot)) slots))))
(defmethod print-object ((,inst-var ,class-name) ,streamvar)
- (with-slots (,@args) ,inst-var
+ (with-slots (,@slots) ,inst-var
(if *print-escape*
(print-unreadable-object (,inst-var ,streamvar :type t)
(format stream "~@<~@{~S ~@_~S~^ ~_~}~:>"
- ,@(mappend #'list keys args)))
- (progn ,@body))))
- ,@(and export `((export '(,class-name ,constructor-name))))
+ ,@(mappend #'list keys slots)))
+ (block ,code ,@body))))
+ ,@(and export `((export '(,class-name ,constructor-name
+ ,@(mapcar (lambda (slot)
+ (symbolicate 'inst- slot))
+ slots)))))
',code)))
-;; Important instruction classes.
-
-(definst var (stream :export t) (name type init)
- (pprint-c-type type stream name)
- (when init
- (format stream " = ~A" init))
- (write-char #\; stream))
-(definst set (stream :export t) (var expr)
- (format stream "~@<~A = ~@_~2I~A;~:>" var expr))
-(definst update (stream :export t) (var op expr)
- (format stream "~@<~A ~A= ~@_~2I~A;~:>" var op expr))
-(definst return (stream :export t) (expr)
- (format stream "return~@[ (~A)~];" expr))
-(definst break (stream :export t) ()
- (format stream "break;"))
-(definst continue (stream :export t) ()
- (format stream "continue;"))
-(definst expr (stream :export t) (expr)
- (format stream "~A;" expr))
-(definst block (stream :export t) (decls body)
- (format stream "{~:@_~@< ~2I~@[~{~A~:@_~}~:@_~]~{~A~^~:@_~}~:>~:@_}"
- decls body))
-(definst function (stream :export t) (name type body)
- (pprint-logical-block (stream nil)
- (princ "static " stream)
- (pprint-c-type type stream name)
- (format stream "~:@_~A~:@_~:@_" body)))
-
;; Formatting utilities.
(defun format-compound-statement* (stream child morep thunk)
`(format-compound-statement* ,stream ,child ,morep
(lambda (,stream) ,@body)))
+;; Important instruction classes.
+
+;; HACK: Some of the slot names we'd like to use are external symbols in our
+;; package or the `common-lisp' package. Use gensyms for these slot names to
+;; prevent them from leaking.
+
+(definst var (stream :export t) (name #1=#:type &optional init)
+ (pprint-c-type #1# stream name)
+ (when init
+ (format stream " = ~A" init))
+ (write-char #\; stream))
+
+(definst function (stream :export t) (name #1=#:type body)
+ (pprint-logical-block (stream nil)
+ (princ "static " stream)
+ (pprint-c-type #1# stream name)
+ (format stream "~:@_~A~:@_~:@_" body)))
+
+;; Expression statements.
+(definst expr (stream :export t) (#1=#:expr)
+ (format stream "~A;" #1#))
+(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#))
+
+;; Special kinds of expressions.
+(definst call (stream :export t) (#1=#:func &rest args)
+ (format stream "~A(~@<~{~A~^, ~_~}~:>)" #1# args))
+
+;; Simple statements.
+(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;"))
+
+;; Compound statements.
+
+(definst block (stream :export t) (decls body)
+ (format stream "{~:@_~@< ~2I~@[~{~A~:@_~}~:@_~]~{~A~^~:@_~}~:>~:@_}"
+ decls body))
+
+(definst if (stream :export t) (#1=#:cond conseq &optional alt)
+ (format-compound-statement (stream conseq alt)
+ (format stream "if (~A)" #1#))
+ (when alt
+ (format-compound-statement (stream alt)
+ (write-string "else" stream))))
+
+(definst while (stream :export t) (#1=#:cond body)
+ (format-compound-statement (stream body)
+ (format stream "while (~A)" #1#)))
+
+(definst do-while (stream :export t) (body #1=#:cond)
+ (format-compound-statement (stream body :space)
+ (write-string "do" stream))
+ (format stream "while (~A);" #1#))
+
;;;--------------------------------------------------------------------------
;;; Code generation.
During BODY, VAR will be marked in-use; when BODY ends, VAR will be marked
available for re-use."
- `(let ((,var (temporary-var ,codegen ,type)))
- (unwind-protect
- (progn ,@body)
- (setf (var-in-use-p ,var) nil))))
+ (multiple-value-bind (doc decls body) (parse-body body :docp nil)
+ (declare (ignore doc))
+ `(let ((,var (temporary-var ,codegen ,type)))
+ ,@decls
+ (unwind-protect
+ (progn ,@body)
+ (setf (var-in-use-p ,var) nil)))))
;;;--------------------------------------------------------------------------
;;; Code generation idioms.
(emit-inst codegen (make-return-inst nil)))
(t (funcall func target))))
+(export 'deliver-call)
+(defun deliver-call (codegen target func &rest args)
+ "Emit a statement to call FUNC with ARGS and deliver the result to TARGET."
+ (deliver-expr codegen target (apply #'make-call-inst func args)))
+
;;;----- That's all, folks --------------------------------------------------