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

commits at source.squeak.org commits at source.squeak.org
Fri Dec 30 21:58:29 UTC 2022


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

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

Name: VMMaker-dtl.437
Author: dtl
Time: 30 December 2022, 2:51:02.319 pm
UUID: 021734cc-f299-460b-833e-f547874175af
Ancestors: VMMaker-dtl.436

VMMaker 4.20.3
Document and fix an ancient bug in return type generation for inlined methods. Symptom was duplicate (float *) casts in generated KlattSynthesizerPlugin>>loadFrom: when code was generated from a Squeak 6 image (worked by accident in Squeak 4.6). Add unit test to document the bug and fix it in CCodeGenerator>>collectInlineList.

=============== Diff against VMMaker-dtl.436 ===============

Item was changed:
  ----- Method: CCodeGenerator>>collectInlineList (in category 'inlining') -----
  collectInlineList
  	"Make a list of methods that should be inlined."
  	"Details: The method must not include any inline C, since the translator cannot
  	currently map variable names in inlined C code. The #inline: directive may be
  	used to override this for cases in which the C code or declarations are harmless.
  	Methods to be inlined must be small or called from only one place."
  
  	| methodsNotToInline callsOf inlineIt hasCCode nodeCount senderCount
  sel returnTypesOf |
  	methodsNotToInline := Set new: methods size.
  
  	"build dictionary to record the number of calls to each method"
  	callsOf := Dictionary new: methods size * 2.
  	returnTypesOf := Dictionary new: methods size.
  	methods keys do: [ :s | callsOf at: s put: 0 ].
  	methods do: [ :m | returnTypesOf at: m selector put: m returnType ].
  
  	"For each method, scan its parse tree once to:
  		1. determine if the method contains C code or declarations
  		2. determine how many nodes it has
  		3. increment the sender counts of the methods it calls
  		4. determine if it includes any C declarations or code"
  	inlineList := Set new: methods size * 2.
  	inlineReturnTypes := Dictionary new: methods size.
  	methods do: [ :m |
  		inlineIt := #dontCare.
  		(translationDict includesKey: m selector) ifTrue: [
  			hasCCode := true.
  		] ifFalse: [
  			hasCCode := m declarations size > 0.
  			nodeCount := 0.
  			m parseTree nodesDo: [ :node |
  				node isSend ifTrue: [
  					sel := node selector.
  					(sel = #cCode: or: [sel = #cCode:inSmalltalk:])
  						ifTrue: [ hasCCode := true ].
  					senderCount := callsOf at: sel ifAbsent: [ nil ].
  					nil = senderCount ifFalse: [
  						callsOf at: sel put: senderCount + 1.
  					].
  				].
  				nodeCount := nodeCount + 1.
  			].
  			inlineIt := m extractInlineDirective.  "may be true, false, or
  #dontCare"
  		].
  		(inlineIt ~= true and: [hasCCode or: [inlineIt = false]]) ifTrue: [
  			"Don't inline if method has C code or if it contains a negative inline
  			directive. If it contains a positive inline directive, permit inlining even
  			if C code is present."
  			methodsNotToInline add: m selector.
  		] ifFalse: [
  			((nodeCount < 40) or: [inlineIt = true]) ifTrue: [
  				"inline if method has no C code and is either small or contains
  inline directive"
  				inlineList add: m selector.
+ "('CCoerce*' match: sel) ifTrue: [self halt]."
+ inlineReturnTypes at: m selector put: m returnType.
+ 
+ 
+ "				inlineReturnTypes at: sel put: m returnType."
- 				inlineReturnTypes at: sel put: m returnType.
  			].
  		].
  	].
  
  	callsOf associationsDo: [ :assoc |
  		((assoc value = 1) and: [(methodsNotToInline includes: assoc key)
  not]) ifTrue: [
  			inlineList add: assoc key.
  		].
  	].!

Item was added:
+ ----- Method: SlangTest>>testTwoInlinedCCoerceInOneMethod (in category 'testing variable declaration') -----
+ testTwoInlinedCCoerceInOneMethod
+ 	"Pattern appearing in KlattPlugin>>loadFrom:
+ 	Translated C code should have one type cast (not two)."
+ 
+ 	| stssi s |
+ 	stssi := SlangTestSupportPlugin inline: true.
+ 	s := stssi asCString: #testTwoInlinedCCoerceInOneMethod .
+ 	self should: ('*floatPointer = ((float *) (interpreterProxy->firstIndexableField(12345)));*' match: s).
+ 	self should: ('*shortPointer = ((short *) (interpreterProxy->firstIndexableField(789)));*' match: s).!

Item was changed:
  InterpreterPlugin subclass: #SlangTestSupportPlugin
+ 	instanceVariableNames: 'cg inlineFlag floatPointer shortPointer'
- 	instanceVariableNames: 'cg inlineFlag'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-Tests'!
  
  !SlangTestSupportPlugin commentStamp: 'dtl 9/19/2010 21:36' prior: 0!
  SlangTestSupport implements translatable methods for use in SlangTest unit tests.
  This is a subclass of InterpreterPlugin, which provides coverage of slang translation
  for base plugins.
  
  	"VMMaker clearCacheEntriesFor: SlangTestSupportPlugin.
  	SlangTestSupportPlugin asCString"!

Item was added:
+ ----- Method: SlangTestSupportPlugin class>>declareCVarsIn: (in category 'translation') -----
+ declareCVarsIn: cg 
+ 	cg var: #floatPointer type: #'float *'.
+ 	cg var: #shortPointer type: #'short *'.
+ !

Item was added:
+ ----- Method: SlangTestSupportPlugin>>checkedFloatPtrOf: (in category 'type declaration') -----
+ checkedFloatPtrOf: oop
+ 	"Originally implemented (ar) in FFTPlugin, also found in KlattPlugin, copied here for testing"
+ 	"Return the first indexable word of oop which is assumed to be variableWordSubclass"
+ 	<returnTypeC:'float *'>
+ 	interpreterProxy success: (interpreterProxy isWords: oop).
+ 	interpreterProxy failed ifTrue:[^0].
+ 	^self cCoerce: (interpreterProxy firstIndexableField: oop) to:'float *'!

Item was added:
+ ----- Method: SlangTestSupportPlugin>>checkedShortPtrOf: (in category 'type declaration') -----
+ checkedShortPtrOf: oop
+ 	"Originally implemented in FFTPlugin, also found in KlattPlugin, copied here for testing"
+ 	"Return the first indexable word of oop which is assumed to be variableWordSubclass"
+ 	<returnTypeC: 'short *'>
+ 	interpreterProxy success: (interpreterProxy isWords: oop).
+ 	interpreterProxy failed ifTrue:[^0].
+ 	^self cCoerce: (interpreterProxy firstIndexableField: oop) to:'short *'!

Item was added:
+ ----- Method: SlangTestSupportPlugin>>testTwoInlinedCCoerceInOneMethod (in category 'type declaration') -----
+ testTwoInlinedCCoerceInOneMethod
+ 	"Pattern appearing in KlattPlugin>>loadFrom:
+ 	Translated C code should have one type cast (not two)"
+ 
+ 	<export: true>
+ 	shortPointer := self checkedShortPtrOf: 789..
+ 	floatPointer := self checkedFloatPtrOf: 12345..
+ !

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



More information about the Vm-dev mailing list