[Vm-dev] VM Maker: VMMaker-dtl.275.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jun 23 18:11:08 UTC 2012


David T. Lewis uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-dtl.275.mcz

==================== Summary ====================

Name: VMMaker-dtl.275
Author: dtl
Time: 23 June 2012, 2:09:46.042 pm
UUID: ffa26536-19b5-42e3-896e-8eb0dd248215
Ancestors: VMMaker-dtl.274

VMMaker  Nothing more expected ->4.9.4

Relax restrictions on classes and methods that may be translated to C when browsing (SlangBrowser). Prevent a few of the more obvious runaway recursions for translating inlined C from a browser.

CCodeGenerator>>checkAbstractMethods now bypasses checks for methods in #uncheckedAbstractSelectors, attempting to do the right thing throughout a class hierarchy, e.g. an abstract method added to InterpreterPrimitives will produce a warning when translating Interpreter or StackInterpreter with either VMMaker or a slang browser, but no warning when translating InterpreterPrimitives in a slang browser. This allows C code for methods in an abstract class to be viewed in a browser, while unimplemented concrete methods produce warnings in VMMaker.

Limit loop count in CCodeGenerator>>doBasicInlining to prevent infinite recursion e.g. when translating Symbol>>asSymbol.

Provide TNotImplementedNode>>emitCCodeOn:level:generator: to write a comment on output stream so unimiplemented slang constructs produce readable output.

Prevent infinite recursion in TMethod>>renameVariablesUsing: when inlining a method with super send, e.g. WideString>>replaceFrom:to:with:startingAt:. Note, inlining super works in oscog, need to adopt that.

=============== Diff against VMMaker-dtl.274 ===============

Item was changed:
  Object subclass: #CCodeGenerator
+ 	instanceVariableNames: 'translationDict inlineList constants variables variableDeclarations scopeStack methods macros preparedMethodList variablesSetCache headerFiles globalVariableUsage useSymbolicConstants generateDeadCode doNotRemoveMethodList asArgumentTranslationDict receiverDict vmClass currentMethod logger declareMethodsStatic permitMethodPruning pools abstractDeclarations uncheckedAbstractMethods'
- 	instanceVariableNames: 'translationDict inlineList constants variables variableDeclarations scopeStack methods macros preparedMethodList variablesSetCache headerFiles globalVariableUsage useSymbolicConstants generateDeadCode doNotRemoveMethodList asArgumentTranslationDict receiverDict vmClass currentMethod logger declareMethodsStatic permitMethodPruning pools abstractDeclarations'
  	classVariableNames: 'UseRightShiftForDivide'
  	poolDictionaries: ''
  	category: 'VMMaker-Translation to C'!
  
  !CCodeGenerator commentStamp: 'tpr 5/2/2003 14:30' prior: 0!
  This class oversees the translation of a subset of Smalltalk to C, allowing the comforts of Smalltalk during development and the efficiency and portability of C for the resulting interpreter.  
  See VMMaker for more useful info!

Item was changed:
  ----- Method: CCodeGenerator>>checkAbstractMethods (in category 'error notification') -----
  checkAbstractMethods
  	"For each method that has been declared abstract, ensure that a concrete
  	implementation has been provided. This check should be performed prior to
  	inlining because methods may be removed during the inlining process."
  
  	| selectors |
+ 	selectors := methods keys, self uncheckedAbstractMethods.
- 	selectors := methods keys, self permittedAbstractMethods.
  	abstractDeclarations do: [:sel |
  		(selectors includes: sel)
  			ifFalse: [self notify: 'missing implementation for ', sel]]
  !

Item was changed:
  ----- Method: CCodeGenerator>>doBasicInlining: (in category 'inlining') -----
  doBasicInlining: inlineFlag
  	"Inline the bodies of all methods that are suitable for inlining.
  	This method does only the basic inlining suitable for both the core VM and plugins - no bytecode inlining etc"
  
+ 	| pass progress max |
- 	| pass progress |
  	inlineFlag ifFalse: [^self].
  	self collectInlineList.
  	pass := 0.
+ 	max := 12. "More than this is probably due to infinite recursion" 
  	progress := true.
  	[progress] whileTrue: [
  		"repeatedly attempt to inline methods until no further progress is made"
  		progress := false.
+ 		pass > max
+ 			ifTrue: [self notify: 'too many inlining steps, inlining terminated']
+ 			ifFalse: [('Inlining pass ', (pass := pass + 1) printString, '...')
+ 						displayProgressAt: Sensor cursorPoint
+ 						from: 0 to: methods size
+ 						during: [:bar |
+ 							(self sortMethods: methods) doWithIndex: [:m :i |
+ 								bar value: i.
+ 								currentMethod := m.
+ 								(m tryToInlineMethodsIn: self)
+ 									ifTrue: [progress := true]]]]].
- 		('Inlining pass ', (pass := pass + 1) printString, '...')
- 			displayProgressAt: Sensor cursorPoint
- 			from: 0 to: methods size
- 			during: [:bar |
- 				(self sortMethods: methods) doWithIndex: [:m :i |
- 					bar value: i.
- 					currentMethod := m.
- 					(m tryToInlineMethodsIn: self)
- 						ifTrue: [progress := true]]]].
  
  !

Item was changed:
  ----- Method: CCodeGenerator>>initialize (in category 'public') -----
  initialize
  	translationDict := Dictionary new.
  	inlineList := Array new.
  	constants := Dictionary new: 100.
  	variables := OrderedCollection new: 100.
  	variableDeclarations := Dictionary new: 100.
  	methods := Dictionary new: 500.
  	macros := Dictionary new.
  	self initializeCTranslationDictionary.
  	receiverDict := Dictionary new.
  	headerFiles := OrderedCollection new.
  	globalVariableUsage := Dictionary new.
  	useSymbolicConstants := true.
  	generateDeadCode := true.
  	scopeStack := OrderedCollection new.
  	logger := (ProvideAnswerNotification new tag: #logger; signal) ifNil: [Transcript].
  	pools := IdentitySet new.
+ 	abstractDeclarations := IdentitySet new.
+ 	uncheckedAbstractMethods := OrderedCollection new.
+ !
- 	abstractDeclarations := IdentitySet new.!

Item was removed:
- ----- Method: CCodeGenerator>>permittedAbstractMethods (in category 'error notification') -----
- permittedAbstractMethods
- 	"Methods generated directly by the code generator require concrete implementations
- 	only in simulation. These may safely be declared abstract in order to ensure that
- 	implemenations are provided in the simulator classes."
- 
- 	^ #(
- 			bytesPerWord.
- 			baseHeaderSize.
- 			byteAt:.
- 			anAbstractMethod	"for unit test"
- 		).
- !

Item was added:
+ ----- Method: CCodeGenerator>>uncheckedAbstractMethods (in category 'accessing') -----
+ uncheckedAbstractMethods
+ 	"Answer the selectors for methods that should not be checked to ensure existence
+ 	of concrete implementations, such as methods that are generated directly by the
+ 	code generator itself."
+ 
+ 	^uncheckedAbstractMethods
+ 
+ !

Item was added:
+ ----- Method: Object class>>abstractSelectors (in category '*VMMaker-translation') -----
+ abstractSelectors
+ 	"Selectors for abstract methods in this class"
+ 	^ self selectors
+ 		select: [:sel | (self compiledMethodAt: sel) requiresConcreteImplementation]!

Item was added:
+ ----- Method: Object class>>buildCodeGenerator (in category '*VMMaker-translation') -----
+ buildCodeGenerator
+ 	"Build a CCodeGenerator for this class. By default, generate only the
+ 	the methods for aClass."
+ 	 | cg |
+ 	cg := self codeGeneratorClass new initialize.
+ 	cg declareModuleName: self name.
+ 	cg addClass: self.
+ 	cg declareMethodsStatic: true.
+ 	cg permitMethodPruning: false.
+ 	^cg
+ !

Item was added:
+ ----- Method: Object class>>buildCodeGeneratorInlined: (in category '*VMMaker-translation') -----
+ buildCodeGeneratorInlined: doInlining
+ 	"Build a CCodeGenerator for this class. By default, generate only the
+ 	the methods for aClass. Classes that are normally translated along with
+ 	other collaborating classes, such as an object memory and its interpreter,
+ 	may include the collaborating classes when doInlining is true, allowing methods
+ 	in those classes to be included in the inlining process."
+ 
+ 	 ^self buildCodeGenerator
+ !

Item was added:
+ ----- Method: Object class>>buildCodeGeneratorUpTo: (in category '*VMMaker-translation') -----
+ buildCodeGeneratorUpTo: aClass
+ 	"Build a CCodeGenerator for this class. By default, generate only the
+ 	the methods for aClass."
+ 	 | cg |
+ 	cg := self codeGeneratorClass new initialize.
+ 	cg declareModuleName: self name.
+ 	cg addClass: aClass.
+ 	^cg
+ !

Item was changed:
  ----- Method: Object class>>initializeCodeGenerator: (in category '*VMMaker-translation') -----
  initializeCodeGenerator: cg
  	"Load a code generator with classes in a manner suitable for generating
  	code for this class."
  
  	| cls |
  	cls := self.
  	[cls == Object]
  		whileFalse:
  			[cg addClass: cls.
  			cls := cls superclass].
+ 	cg uncheckedAbstractMethods addAll: self uncheckedAbstractSelectors.
  	^cg
  !

Item was added:
+ ----- Method: Object class>>uncheckedAbstractSelectors (in category '*VMMaker-translation') -----
+ uncheckedAbstractSelectors
+ 	"Selectors for abstract methods that are not required to have concrete
+ 	implementations in a code generator for this class. These may be methods
+ 	in this class that send #subclassResponsibility, methods with implementations
+ 	supplied directly by the code generator, or methods implemented in the support
+ 	code. A code generator for translating this class in a browser should not raise
+ 	warnings about missing implementations for these selectors."
+ 
+ 	| codeGeneratorMethods |
+ 	"methods with implementations provide by the code generator or platform sources and macros"
+ 	codeGeneratorMethods := #(
+ 			bytesPerWord.
+ 			baseHeaderSize.
+ 			byteAt:.
+ 			anAbstractMethod	"for unit test"
+ 		).
+ 	"abstract methods in this class are presumed to have implementations in subclasses"
+ 	^ codeGeneratorMethods,  self abstractSelectors!

Item was removed:
- ----- Method: Object>>buildCodeGenerator (in category '*VMMaker-translation support') -----
- buildCodeGenerator
- 	"Build a CCodeGenerator for this class. By default, generate only the
- 	the methods for aClass."
- 	 | cg |
- 	cg := self codeGeneratorClass new initialize.
- 	cg declareModuleName: self name.
- 	cg addClass: self.
- 	cg declareMethodsStatic: true.
- 	cg permitMethodPruning: false.
- 	^cg
- !

Item was removed:
- ----- Method: Object>>buildCodeGeneratorInlined: (in category '*VMMaker-translation support') -----
- buildCodeGeneratorInlined: doInlining
- 	"Build a CCodeGenerator for this class. By default, generate only the
- 	the methods for aClass. Classes that are normally translated along with
- 	other collaborating classes, such as an object memory and its interpreter,
- 	may include the collaborating classes when doInlining is true, allowing methods
- 	in those classes to be included in the inlining process."
- 
- 	 ^self buildCodeGenerator
- !

Item was removed:
- ----- Method: Object>>buildCodeGeneratorUpTo: (in category '*VMMaker-translation support') -----
- buildCodeGeneratorUpTo: aClass
- 	"Build a CCodeGenerator for this class. By default, generate only the
- 	the methods for aClass."
- 	 | cg |
- 	cg := self codeGeneratorClass new initialize.
- 	cg declareModuleName: self name.
- 	cg addClass: aClass.
- 	^cg
- !

Item was changed:
  ----- Method: ObjectMemory class>>buildCodeGeneratorInlined: (in category 'translation') -----
  buildCodeGeneratorInlined: doInlining
  	"Build a CCodeGenerator for this class. By default, generate only the
  	the methods for aClass. Classes that are normally translated along with
  	other collaborating classes, such as an object memory and its interpreter,
  	may include the collaborating classes when doInlining is true, allowing methods
  	in those classes to be included in the inlining process."
  
  	 | cg |
  	cg := VMMaker new createCodeGenerator.
  	cg declareMethodsStatic: false.
  	cg permitMethodPruning: true.
+ 	cg uncheckedAbstractMethods addAll: self abstractSelectors.
  	doInlining
  		ifTrue: ["Include methods from associated classes so that inlining for each
  				method is performed as in normal interp.c generation"
  				^self interpreterClass initializeCodeGenerator: cg]
  		ifFalse: [^self initializeCodeGenerator: cg]
+ 
  !

Item was added:
+ ----- Method: SlangTestSupportInterpreter class>>uncheckedAbstractSelectors (in category 'translation') -----
+ uncheckedAbstractSelectors
+ 	^ super uncheckedAbstractSelectors, ObjectMemory uncheckedAbstractSelectors!

Item was added:
+ ----- Method: StackInterpreter class>>uncheckedAbstractSelectors (in category 'translation') -----
+ uncheckedAbstractSelectors
+ 	"Selectors for abstract methods that are not required to have concrete
+ 	implementations in a code generator for this class. These may be methods
+ 	in this class that send #subclassResponsibility, methods with implementations
+ 	supplied directly by the code generator, or methods implemented in the support
+ 	code. A code generator for translating this class in a browser should not raise
+ 	warnings about missing implementations for these selectors."
+ 
+ 	^super uncheckedAbstractSelectors, StackInterpreterPrimitives selectors!

Item was changed:
  ----- Method: TMethod>>renameVariablesUsing: (in category 'inlining support') -----
  renameVariablesUsing: aDictionary
  	"Rename all variables according to old->new mappings of the given dictionary."
  
  	| newDecls newKey newValue |
  	"map args and locals"
  	args := args collect: [ :arg |
  		(aDictionary includesKey: arg) ifTrue: [ aDictionary at: arg ] ifFalse: [ arg ].
  	].
  	locals := locals collect: [ :v |
  		(aDictionary includesKey: v) ifTrue: [ aDictionary at: v ] ifFalse: [ v ].
  	].
+ 	"prevent runaway recursion, e.g. inlining a method with super send"
+ 	locals size > 1000 ifTrue: [self error: 'recursive inlining in ', selector asString, ', too many locals'].
  
  	"map declarations"
  	newDecls := declarations species new.
  	declarations associationsDo: [ :assoc |
  		(aDictionary includesKey: assoc key)
  			ifTrue: [ newKey := aDictionary at: assoc key.
  					newValue := assoc value replaceLastOccurrence: assoc key with: newKey.
  					newDecls at: newKey put: newValue]
  			ifFalse: [ newDecls add: assoc ].
  	].
  	declarations := newDecls.
  
  	"map variable names in parse tree"
  	parseTree nodesDo: [ :node |
  		(node isVariable and:
  		 [aDictionary includesKey: node name]) ifTrue: [
  			node setName: (aDictionary at: node name).
  		].
  		(node isStmtList and: [node args size > 0]) ifTrue: [
  			node setArguments:
  				(node args collect: [ :arg |
  					(aDictionary includesKey: arg)
  						ifTrue: [ aDictionary at: arg ]
  						ifFalse: [ arg ].
  				]).
  		].
  	].!

Item was added:
+ ----- Method: TNotImplementedNode>>emitCCodeOn:level:generator: (in category 'C code generation') -----
+ emitCCodeOn: aStream level: level generator: aCodeGen
+ 	"Emit a comment only"
+ 
+ 	aStream cr; nextPutAll: '/*** ';
+ 		nextPutAll: self printString;
+ 		nextPutAll: ' cannot translate: '; cr;
+ 		nextPutAll: parseNode printString;
+ 		cr; nextPutAll: ' ***/'; cr
+ !

Item was changed:
  ----- Method: VMMaker class>>versionString (in category 'version testing') -----
  versionString
  
  	"VMMaker versionString"
  
+ 	^'4.9.4'!
- 	^'4.9.3'!



More information about the Vm-dev mailing list