[ENH] Include Smalltalk comments in generated C code

Henrik Gedenryd Henrik.Gedenryd at lucs.lu.se
Mon Aug 14 16:50:36 UTC 2000


A surprisingly small number of changes to include (most?) Smalltalk comments
in generated C code. Places method comments before the generated function.
Doesn't handle inlining very well, but hey...

This proved to be very useful in the C debugger, at least for those who
don't know the generated code by heart. I think it will be valuable for
anyone who begins to look at the VM & plugin underworks.

Tip: when debugging, generate code without inlining. Not only because of
what I wrote above...

Testing: verified that the whole interpreter still translates without
problems.

Henrik

-------------- next part --------------
'From Squeak2.9alpha of 8 July 2000 [latest update: #2447] on 14 August 2000 at 6:38:15 pm'!
"Change Set:		emitComments-hg
Date:			14 August 2000
Author:			Henrik Gedenryd

A surprisingly small number of changes to include (most?) Smalltalk comments in generated C code. Places method comments before the generated function. 
Doesn't handle inlining very well, but hey..."!

Object subclass: #TMethod
	instanceVariableNames: 'selector returnType args locals declarations primitive parseTree labels possibleSideEffectsCache complete export static comment '
	classVariableNames: 'CaseStatements '
	poolDictionaries: ''
	category: 'VMConstruction-Translation to C'!
Object subclass: #TParseNode
	instanceVariableNames: 'comment '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMConstruction-Translation to C'!
TParseNode subclass: #TLabeledCommentNode
	instanceVariableNames: 'label '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMConstruction-Translation to C'!

!AssignmentNode methodsFor: 'C translation' stamp: 'hg 8/14/2000 15:33'!
asTranslatorNode
	^TAssignmentNode new
		setVariable: variable asTranslatorNode
		expression: value asTranslatorNode;
		comment: comment! !


!BlockNode methodsFor: 'C translation' stamp: 'hg 8/14/2000 15:33'!
asTranslatorNode
	| statementList newS |
	statementList _ OrderedCollection new.
	statements do: [ :s |
		newS _ s asTranslatorNode.
		newS isStmtList ifTrue: [
			"inline the statement list returned when a CascadeNode is translated"
			statementList addAll: newS statements.
		] ifFalse: [
			statementList add: newS.
		].
	].
	^TStmtListNode new
		setArguments: (arguments asArray collect: [ :arg | arg key ])
		statements: statementList;
		comment: comment! !


!CascadeNode methodsFor: 'C translation' stamp: 'hg 8/14/2000 15:33'!
asTranslatorNode
	^TStmtListNode new
		setArguments: #()
		statements: (messages collect:
			[ :msg | msg asTranslatorNode receiver: receiver asTranslatorNode ]);
		comment: comment! !


!MethodNode methodsFor: 'C translation' stamp: 'hg 8/14/2000 15:56'!
asTranslationMethodOfClass: aClass
 
	^ aClass new
		setSelector: selectorOrFalse
		args: arguments
		locals: encoder tempsAndBlockArgs
		block: block
		primitive: primitive;
		comment: comment
! !


!ReturnNode methodsFor: 'C translation' stamp: 'hg 8/14/2000 15:34'!
asTranslatorNode
	^TReturnNode new 
		setExpression: expr asTranslatorNode;
		comment: comment! !


!TMethod methodsFor: 'accessing' stamp: 'hg 8/14/2000 15:57'!
comment: aComment

	comment _ aComment ! !

!TMethod methodsFor: 'C code generation' stamp: 'hg 8/14/2000 15:41'!
emitCCodeOn: aStream generator: aCodeGen
	"Emit C code for this method onto the given stream. All calls to inlined methods should already have been expanded."

	self emitCCommentOn: aStream.	"place method comment before function"

	self emitCHeaderOn: aStream generator: aCodeGen.
	parseTree emitCCodeOn: aStream level: 1 generator: aCodeGen.
	aStream nextPutAll: '}'; cr.! !

!TMethod methodsFor: 'C code generation' stamp: 'hg 8/14/2000 16:09'!
emitCCommentOn: aStream
	"Emit the transferred Smalltalk comments as C comments."

	comment ifNotNil: [
		aStream cr;cr.
		1 to: comment size do: [:index | 
			aStream 
				nextPutAll: '/*'; tab;
				nextPutAll: (comment at: index);
				nextPutAll: ' */';
				cr]]! !


!TParseNode methodsFor: 'emit comments' stamp: 'hg 8/14/2000 15:32'!
comment: aComment

	comment _ aComment ! !

!TParseNode methodsFor: 'emit comments' stamp: 'hg 8/14/2000 16:13'!
emitCCommentOn: aStream level: level
	"Emit the transferred Smalltalk comments as C comments."

	comment ifNotNil: [
		comment isString ifTrue: [^self].	"safety catch"
		aStream cr.
		1 to: comment size do: [:index | 
			aStream 
				tab: level;
				nextPutAll: '/* ';
				nextPutAll: (comment at: index);
				nextPutAll: ' */';
				cr].
		aStream cr]! !


!TStmtListNode methodsFor: 'as yet unclassified' stamp: 'hg 8/14/2000 15:29'!
emitCCodeOn: aStream level: level generator: aCodeGen

	statements do: [:s |
		s emitCCommentOn: aStream level: level.
		aStream tab: level.
		s emitCCodeOn: aStream level: level generator: aCodeGen.
		((self endsWithCloseBracket: aStream) or:
		 [s isComment])
			ifFalse: [aStream nextPut: $;].
		aStream cr].
! !



More information about the Squeak-dev mailing list