[Vm-dev] VM Maker: VMMaker.oscog-eem.1067.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Feb 16 19:27:27 UTC 2015


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.1067.mcz

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

Name: VMMaker.oscog-eem.1067
Author: eem
Time: 16 February 2015, 11:26:13.727 am
UUID: a5db4c60-0a4d-4375-8e2b-9a1ece21e34c
Ancestors: VMMaker.oscog-eem.1066

Back out of the wrong-headed attempt to fix the
symptoms of bad inlining rather than the cause by
hacking comparison generation.

Insist on signedness of actual expressions matching
the signedness of formals to inline an expression,
otherwise assign the expression to the inlined formal.

Add support for type inferrence of simple arithmetic
(+,-,*,/) but *not* >> << et al, so that inlining is still
done for e.g. pointer arithmetic expressions.

Refactor the inlining breakpoint machinery so one can
break only at the point of inline as well as only at the
point of testing for inlinability.

Fix a bug in TMethod>>typeFor:in: which was causing
the failure to find the types of global variables.

=============== Diff against VMMaker.oscog-eem.1066 ===============

Item was changed:
  Object subclass: #CCodeGenerator
+ 	instanceVariableNames: 'vmClass structClasses translationDict asArgumentTranslationDict inlineList constants variables variableDeclarations scopeStack methods macros apiMethods kernelReturnTypes currentMethod headerFiles globalVariableUsage useSymbolicConstants generateDeadCode requiredSelectors logger suppressAsmLabels asmLabelCounts pools selectorTranslations optionsDictionary breakSrcInlineSelector breakDestInlineSelector breakOnInline vmMaker'
- 	instanceVariableNames: 'vmClass structClasses translationDict asArgumentTranslationDict inlineList constants variables variableDeclarations scopeStack methods macros apiMethods kernelReturnTypes currentMethod headerFiles globalVariableUsage useSymbolicConstants generateDeadCode requiredSelectors logger suppressAsmLabels asmLabelCounts pools selectorTranslations optionsDictionary breakSrcInlineSelector breakDestInlineSelector vmMaker'
  	classVariableNames: 'NoRegParmsInAssertVMs'
  	poolDictionaries: 'VMBasicConstants'
  	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 removed:
- ----- Method: CCodeGenerator>>breakDestInlineSelector (in category 'accessing') -----
- breakDestInlineSelector
- 	^breakDestInlineSelector!

Item was added:
+ ----- Method: CCodeGenerator>>breakOnInline: (in category 'accessing') -----
+ breakOnInline: aBooleanOrNil
+ 	breakOnInline := aBooleanOrNil!

Item was removed:
- ----- Method: CCodeGenerator>>breakSrcInlineSelector (in category 'accessing') -----
- breakSrcInlineSelector
- 	^breakSrcInlineSelector!

Item was changed:
  ----- Method: CCodeGenerator>>collectInlineList: (in category 'inlining') -----
  collectInlineList: inlineFlagOrSymbol
  	"Make a list of methods that should be inlined.  If inlineFlagOrSymbol == #asSpecified
  	 only inline methods marked with <inline: true>."
  	"Details: The method must not include any inline C, since the
  	 translator cannot currently map variable names in inlined C code.
  	 Methods to be inlined must be small or called from only one place."
  
  	| selectorsOfMethodsNotToInline callsOf |
  	self assert: (#(true false asSpecified) includes: inlineFlagOrSymbol).
  	selectorsOfMethodsNotToInline := Set new: methods size.
  	selectorsOfMethodsNotToInline addAll: macros keys.
  	apiMethods ifNotNil:
  		[selectorsOfMethodsNotToInline addAll: apiMethods keys].
  	methods do:
  		[:m|
  		m isStructAccessor ifTrue:
  			[selectorsOfMethodsNotToInline add: m selector]].
  
  	"build dictionary to record the number of calls to each method"
  	callsOf := Dictionary new: methods size * 2.
  	methods keysAndValuesDo:
  		[:s :m|
  		(m isRealMethod
  		 and: [self shouldGenerateMethod: m]) ifTrue:
  			[callsOf at: s put: 0]].
  
  	"For each method, scan its parse tree once or twice to:
  		1. determine if the method contains unrenamable C code or declarations or has a C builtin
  		2. determine how many nodes it has
  		3. increment the sender counts of the methods it calls"
  	inlineList := Set new: methods size * 2.
  	(methods reject: [:m| selectorsOfMethodsNotToInline includes: m selector]) do:
  		[:m| | inlineIt hasUnrenamableCCode nodeCount |
+ 		(breakSrcInlineSelector = m selector
+ 		 and: [breakOnInline isNil]) ifTrue:
- 		breakSrcInlineSelector = m selector ifTrue:
  			[self halt].
  		inlineIt := #dontCare.
  		(translationDict includesKey: m selector)
  			ifTrue: [hasUnrenamableCCode := true]
  			ifFalse:
  				[hasUnrenamableCCode := m hasUnrenamableCCode.
  				 nodeCount := 0.
  				 m parseTree nodesDo:
  					[:node|
  					node isSend ifTrue:
  						[callsOf
  							at: node selector
  							ifPresent:
  								[:senderCount| callsOf at: node selector put: senderCount + 1]].
  					 nodeCount := nodeCount + 1].
  				inlineIt := m extractInlineDirective].  "may be true, false, or #dontCare"
  		(hasUnrenamableCCode or: [inlineIt == false])
  			ifTrue: "don't inline if method has C code or contains negative inline directive"
  				[inlineIt == true ifTrue:
  					[logger
  						ensureCr;
  						nextPutAll: 'failed to inline ';
  						nextPutAll: m selector;
  						nextPutAll: ' as it contains unrenamable C declarations or C code';
  						cr; flush].
  				selectorsOfMethodsNotToInline add: m selector]
  			ifFalse:
  				[(inlineFlagOrSymbol == #asSpecified
  					ifTrue: [inlineIt == true]
  					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]]].
  
  	inlineFlagOrSymbol ~~ #asSpecified ifTrue:
  		[callsOf associationsDo:
  			[:assoc|
  			(assoc value = 1
  			 and: [(selectorsOfMethodsNotToInline includes: assoc key) not]) ifTrue:
  				[inlineList add: assoc key]]]!

Item was removed:
- ----- Method: CCodeGenerator>>emitSignedComparison:for:on:indent: (in category 'C translation support') -----
- emitSignedComparison: operator for: msgNode on: aStream indent: level
- 	"Emit a signed comparison.
- 	 Make sure the receiver expression is signed if comparing against zero."
- 
- 	| arg rcvrType |
- 	((arg := msgNode args first) isConstant
- 	and: [arg value isInteger
- 	and: [arg value = 0
- 	and: [(self typeFor: msgNode receiver in: currentMethod)
- 			ifNil: [false]
- 			ifNotNil: [:t| (rcvrType := t) first = $u]]]]) ifTrue:
- 		[aStream nextPut: $(; nextPutAll: (self signedTypeForIntegralType: rcvrType); nextPut: $)].
- 	self emitCExpression: msgNode receiver on: aStream.
- 	aStream space; nextPutAll: operator; space.
- 	self emitCExpression: arg on: aStream!

Item was changed:
  ----- Method: CCodeGenerator>>generateGreaterThan:on:indent: (in category 'C translation') -----
  generateGreaterThan: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
+ 	self emitCExpression: msgNode receiver on: aStream.
+ 	aStream nextPutAll: ' > '.
+ 	self emitCExpression: msgNode args first on: aStream.!
- 	self emitSignedComparison: #> for: msgNode on: aStream indent: level!

Item was changed:
  ----- Method: CCodeGenerator>>generateGreaterThanOrEqual:on:indent: (in category 'C translation') -----
  generateGreaterThanOrEqual: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
+ 	self emitCExpression: msgNode receiver on: aStream.
+ 	aStream nextPutAll: ' >= '.
+ 	self emitCExpression: msgNode args first on: aStream.!
- 	self emitSignedComparison: #>= for: msgNode on: aStream indent: level!

Item was changed:
  ----- Method: CCodeGenerator>>generateLessThan:on:indent: (in category 'C translation') -----
  generateLessThan: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
+ 	self emitCExpression: msgNode receiver on: aStream.
+ 	aStream nextPutAll: ' < '.
+ 	self emitCExpression: msgNode args first on: aStream.!
- 	self emitSignedComparison: #< for: msgNode on: aStream indent: level!

Item was changed:
  ----- Method: CCodeGenerator>>generateLessThanOrEqual:on:indent: (in category 'C translation') -----
  generateLessThanOrEqual: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
+ 	self emitCExpression: msgNode receiver on: aStream.
+ 	aStream nextPutAll: ' <= '.
+ 	self emitCExpression: msgNode args first on: aStream.!
- 	self emitSignedComparison: #<= for: msgNode on: aStream indent: level!

Item was added:
+ ----- Method: CCodeGenerator>>isActualType:compatibleWithFormalType: (in category 'inlining') -----
+ isActualType: actualTypeOrNil compatibleWithFormalType: formalTypeOrNil 
+ 	| actualType formalType |
+ 	actualType := actualTypeOrNil ifNil: [#sqInt].
+ 	formalType := formalTypeOrNil ifNil: [#sqInt].
+ 	((self isIntegralCType: actualType)
+ 	 and: [self isIntegralCType: formalType]) ifFalse:
+ 		[^actualType = formalType].
+ 	"For now, insist that the signedness agrees."
+ 	^(actualType first = $u) = (formalType first = $u)
+ 	 or: [actualTypeOrNil isNil or: [formalTypeOrNil isNil]]!

Item was added:
+ ----- Method: CCodeGenerator>>maybeBreakForInlineOf:in: (in category 'inlining') -----
+ maybeBreakForInlineOf: aNode in: aTMethod
+ 	"convenient for debugging..."
+ 	(aNode isSend
+ 	and: [(breakSrcInlineSelector notNil or: [breakDestInlineSelector notNil])
+ 	and: [(breakSrcInlineSelector ifNil: [true] ifNotNil: [:srcSel| srcSel = aNode selector])
+ 	and: [breakDestInlineSelector ifNil: [true] ifNotNil: [:dstSel| dstSel = aTMethod selector
+ 	and: [breakOnInline ~~ false]]]]]) ifTrue:
+ 		[aTMethod halt: aTMethod selector, ' ', aNode selector]!

Item was added:
+ ----- Method: CCodeGenerator>>maybeBreakForTestToInline:in: (in category 'inlining') -----
+ maybeBreakForTestToInline: aNode in: aTMethod
+ 	"convenient for debugging..."
+ 	(aNode isSend
+ 	and: [(breakSrcInlineSelector notNil or: [breakDestInlineSelector notNil])
+ 	and: [(breakSrcInlineSelector ifNil: [true] ifNotNil: [:srcSel| srcSel = aNode selector])
+ 	and: [breakDestInlineSelector ifNil: [true] ifNotNil: [:dstSel| dstSel = aTMethod selector
+ 	and: [breakOnInline ~~ true]]]]]) ifTrue:
+ 		[aTMethod halt: aTMethod selector, ' ', aNode selector]!

Item was changed:
  ----- Method: CCodeGenerator>>returnTypeForSend:in: (in category 'type inference') -----
+ returnTypeForSend: sendNode in: aTMethod
- returnTypeForSend: aTSendNode in: aTMethod
  	"Answer the return type for a send.  Absent sends default to #sqInt.
  	 The bitwise operators answer unsigned versions of their argument types, at least in gcc
  	 although this author can't find that in the C99 spec.  If you can find this, please let me know."
  	| sel |
+ 	^(self anyMethodNamed: (sel := sendNode selector))
- 	^(self anyMethodNamed: (sel := aTSendNode selector))
  		ifNil: [kernelReturnTypes
  				at: sel
  				ifAbsent:
  					[^sel
  						caseOf: {
+ 						[#+]					->	[self typeForArithmetic: sendNode in: aTMethod].
+ 						[#-]						->	[self typeForArithmetic: sendNode in: aTMethod].
+ 						[#*]					->	[self typeForArithmetic: sendNode in: aTMethod].
+ 						[#/]						->	[self typeForArithmetic: sendNode in: aTMethod].
+ 						[#bitAnd:]				->	[self unsignedTypeForBitwiseSend: sendNode in: aTMethod].
+ 						[#bitOr:]				->	[self unsignedTypeForBitwiseSend: sendNode in: aTMethod].
+ 						[#bitXor:]				->	[self unsignedTypeForBitwiseSend: sendNode in: aTMethod].
- 						[#bitAnd:]				->	[self unsignedTypeForBitwiseSend: aTSendNode in: aTMethod].
- 						[#bitOr:]				->	[self unsignedTypeForBitwiseSend: aTSendNode in: aTMethod].
- 						[#bitXor:]				->	[self unsignedTypeForBitwiseSend: aTSendNode in: aTMethod].
  						[#asVoidPointer]		->	[#'void *'].
  						[#asVoidPointer]		->	[#'void *'].
  						[#asUnsignedInteger]	->	[#usqInt].
  						[#asLong]				->	[#long].
  						[#asUnsignedLong]		->	[#'unsigned long'].
  						[#signedIntToLong]		->	[#usqInt]. "c.f. generateSignedIntToLong:on:indent:"
  						[#signedIntToShort]	->	[#usqInt]. "c.f. generateSignedIntToShort:on:indent:"
+ 						[#cCoerce:to:]			->	[sendNode args last value].
+ 						[#cCoerceSimple:to:]	->	[sendNode args last value] }
- 						[#cCoerce:to:]			->	[aTSendNode args last value].
- 						[#cCoerceSimple:to:]	->	[aTSendNode args last value] }
  						otherwise: [#sqInt]]]
  		ifNotNil:
  			[:m|
  			m returnType ifNotNil:
  				[:type| "map fields to #usqInt"
  				((type beginsWith: 'unsigned')
  				 and: [(type includes: $:)
  				 and: [type last isDigit]])
  					ifTrue: [#usqInt]
  					ifFalse: [type]]]!

Item was added:
+ ----- Method: CCodeGenerator>>typeForArithmetic:in: (in category 'type inference') -----
+ typeForArithmetic: sendNode in: aTMethod
+ 	"Answer the return type for an arithmetic sendThis is so that the inliner can still
+ 	 inline simple expressions.  Deal with pointer arithmetic and floating point arithmetic"
+ 	(self typeFor: sendNode args first in: aTMethod) = #double ifTrue:
+ 		[^#double].
+ 	^self typeFor: sendNode receiver in: aTMethod!

Item was changed:
  ----- Method: CCodeGenerator>>typeOfVariable: (in category 'C code generator') -----
+ typeOfVariable: varName "<String>"
+ 	self assert: varName isString.
- typeOfVariable: varName "<String>" 
  	scopeStack reverseDo:
  		[:dict|
  		(dict includesKey: varName) ifTrue:
  			[^self
  				extractTypeFor: varName
  				fromDeclaration: (dict at: varName)]].
  	^self
  		extractTypeFor: varName
  		fromDeclaration: (variableDeclarations at: varName ifAbsent: [^nil])!

Item was changed:
  ----- Method: TMethod>>inlineGuardingConditional:in: (in category 'inlining') -----
  inlineGuardingConditional: aSendNode in: aCodeGen
  	"Inline
  		aSend ifTrue:/ifFalse: [statements]
  	 where aSend is inlineable and always answers booleans.  We convert
  	 the boolean returns in aSend to jumps."
  	| evaluateIfTrue replacementTree map lastNode evaluateLabel skipLabel method |
  	self assert: self == aCodeGen currentMethod.
  	self assert: (self isInlineableConditional: aSendNode in: aCodeGen).
+ 	aCodeGen maybeBreakForInlineOf: aSendNode in: self.
- 	self maybeBreakFor: aSendNode receiver in: aCodeGen.
  	evaluateIfTrue := aSendNode selector = #ifTrue:.
  	method := (aCodeGen methodNamed: aSendNode receiver selector) copy.
  	replacementTree := method inlineFunctionCall: aSendNode receiver in: aCodeGen.
  	map := Dictionary new.
  	(replacementTree statements last isReturn
  	 and: [replacementTree statements last expression value = evaluateIfTrue]) ifTrue:
  		[lastNode := replacementTree statements last].
  	skipLabel := TLabeledCommentNode new setLabel:
  					(self unusedLabelForInlining: method).
  	replacementTree nodesDo:
  		[:node| | expr |
  		 node isReturn ifTrue:
  			[expr := node expression.
  			 self assert: (expr isConstant and: [#(true false) includes: expr value]).
  			 map
  				at: node
  				put: (expr value ~~ evaluateIfTrue
  						ifTrue: [TGoToNode new setLabel: skipLabel label]
  						ifFalse:
  							[node == lastNode
  								ifTrue: [TLabeledCommentNode new setComment: 'end ', aSendNode receiver selector, '; fall through']
  								ifFalse:
  									[evaluateLabel ifNil:
  										[evaluateLabel := TLabeledCommentNode new setLabel:
  													(self unusedLabelForInlining: method)].
  									 TGoToNode new setLabel: evaluateLabel label]])]].
  	replacementTree replaceNodesIn: map.
  	replacementTree comment: {'inline ', aSendNode receiver selector}.
  	self addVarsDeclarationsAndLabelsOf: method except: method args.
  	^TStmtListNode new
  		setArguments: #()
  		statements:
  			(evaluateLabel
  				ifNil: [replacementTree statements, aSendNode args first statements, {skipLabel}]
  				ifNotNil:
  					[replacementTree statements, {evaluateLabel}, aSendNode args first statements, {skipLabel}])!

Item was changed:
  ----- Method: TMethod>>inlineReturningConditional:in: (in category 'inlining') -----
  inlineReturningConditional: aSendNode in: aCodeGen
  	"Inline
  		aSend ifTrue:/ifFalse: [^expr]
  	 where aSend is inlineable and always answers booleans.  We inline ^expr
  	 into aSend."
  	| returnIfTrue returnNode replacementTree map lastNode label method |
  	self assert: self == aCodeGen currentMethod.
  	self assert: (self isInlineableConditional: aSendNode in: aCodeGen).
+ 	aCodeGen maybeBreakForInlineOf: aSendNode receiver in: self.
- 	self maybeBreakFor: aSendNode receiver in: aCodeGen.
  	returnIfTrue := aSendNode selector = #ifTrue:.
  	returnNode := aSendNode args first.
  	method := (aCodeGen methodNamed: aSendNode receiver selector) copy.
  	replacementTree := method inlineFunctionCall: aSendNode receiver in: aCodeGen.
  	map := Dictionary new.
  	(replacementTree statements last isReturn
  	 and: [replacementTree statements last expression value = returnIfTrue not]) ifTrue:
  		[lastNode := replacementTree statements last].
  	replacementTree nodesDo:
  		[:node| | expr |
  		 node isReturn ifTrue:
  			[expr := node expression.
  			 self assert: (expr isConstant and: [#(true false) includes: expr value]).
  			 map
  				at: node
  				put: (expr value == returnIfTrue
  						ifTrue: [returnNode]
  						ifFalse:
  							[node == lastNode
  								ifTrue: [TLabeledCommentNode new setComment: 'end ', aSendNode receiver selector, '; fall through']
  								ifFalse:
  									[label ifNil:
  										[label := TLabeledCommentNode new setLabel:
  													(self unusedLabelForInlining: method)].
  									 TGoToNode new setLabel: label label]])]].
  	replacementTree replaceNodesIn: map.
  	self addVarsDeclarationsAndLabelsOf: method except: method args.
  	replacementTree comment: {'inline ', aSendNode receiver selector}.
  	^label
  		ifNil: [replacementTree]
  		ifNotNil:
  			[TStmtListNode new
  				setArguments: #()
  				statements: {replacementTree. label}]!

Item was changed:
  ----- Method: TMethod>>inlineSend:directReturn:exitVar:in: (in category 'inlining') -----
  inlineSend: aSendNode directReturn: directReturn exitVar: exitVar in: aCodeGen
  	"Answer a collection of statements to replace the given send.  directReturn indicates
  	 that the send is the expression in a return statement, so returns can be left in the
  	 body of the inlined method. If exitVar is nil, the value returned by the send is not
  	 used; thus, returns need not assign to the output variable.
  
  	 Types are propagated to as-yet-untyped variables when inlining a send that is assigned,
  	 otherwise the assignee variable type must match the return type of the inlinee.  Return
  	 types are not propagated."
  
  	| sel meth methArgs exitLabel inlineStmts label exitType |
  	sel := aSendNode selector.
  	meth := aCodeGen methodNamed: sel.
  	methArgs := meth args.
  	"convenient for debugging..."
+ 	aCodeGen maybeBreakForInlineOf: aSendNode in: self.
- 	self maybeBreakFor: aSendNode in: aCodeGen.
  	(methArgs notEmpty and: [methArgs first beginsWith: 'self_in_']) ifTrue:
  		[methArgs := methArgs allButFirst].
  	methArgs size = aSendNode args size ifFalse:
  		[^nil].
  	methArgs with: aSendNode args do:
  		[:formal :actual|
  		(actual isVariable
  		and: [(aCodeGen
  				variableOfType: (self typeFor: formal using: aCodeGen)
  				acceptsValueOfType: (self typeFor: actual name in: aCodeGen)) not]) ifTrue:
  			[aCodeGen logger
  				nextPutAll:
  					'type mismatch for formal ', formal, ' and actual ', actual name,
  					' when inlining ', sel, ' in ', selector, '. Use a cast.';
  				cr; flush]]. 
  	meth := meth copy.
  
  	"Propagate the return type of an inlined method"
  	(directReturn or:[exitVar notNil]) ifTrue:[
  		exitType := directReturn 
  			ifTrue:[returnType] 
  			ifFalse:[(self typeFor: exitVar in: aCodeGen) ifNil:[#sqInt]].
  		(exitType = #void or:[exitType = meth returnType]) 
  			ifFalse:[meth propagateReturnIn: aCodeGen]].
  
  	meth renameVarsForInliningInto: self except: #() in: aCodeGen.
  	meth renameLabelsForInliningInto: self.
  	self addVarsDeclarationsAndLabelsOf: meth except: #().
  	meth hasReturn ifTrue:[
  		directReturn ifFalse:[
  			exitLabel := self unusedLabelForInliningInto: self.
  			(meth exitVar: exitVar label: exitLabel) "is label used?"
  				ifTrue: [ labels add: exitLabel ]
  				ifFalse: [ exitLabel := nil ]]].
  	(inlineStmts := OrderedCollection new: 100)
  		add: (label := TLabeledCommentNode new setComment: 'begin ', sel);
  		addAll: (self argAssignmentsFor: meth send: aSendNode in: aCodeGen);
  		addAll: meth statements.  "method body"
  	(directReturn
  	 and: [meth endsWithReturn not]) ifTrue:
  		[inlineStmts add:
  			(TReturnNode new setExpression: (TVariableNode new setName: 'nil'))].
  	exitLabel ~= nil ifTrue:
  		[inlineStmts add:
  			(TLabeledCommentNode new setLabel:
  				exitLabel comment: 'end ', meth selector)].
  	^inlineStmts!

Item was changed:
  ----- Method: TMethod>>inlineableFunctionCall:in: (in category 'inlining') -----
  inlineableFunctionCall: aNode in: aCodeGen
  	"Answer true if the given send node is a call to a 'functional' method--a method whose body is a single return statement of some expression and whose actual parameters can all be directly substituted."
  
+ 	aCodeGen maybeBreakForTestToInline: aNode in: self.
- 	self maybeBreakFor: aNode in: aCodeGen.
  	aNode isSend ifFalse:
  		[^false].
  	^(aCodeGen methodNamed: aNode selector)
  		ifNil:
  			[aNode asTransformedConstantPerform
  				ifNil: [self isInlineableConditional: aNode in: aCodeGen]
  				ifNotNil: [:n| self inlineableFunctionCall: n in: aCodeGen]]
  		ifNotNil:
  			[:m|
  			 m ~~ self
  			 and: [m isFunctional
  			 and: [(aCodeGen mayInline: m selector)
  			 and: [aNode args allSatisfy: [ :a | self isSubstitutableNode: a intoMethod: m in: aCodeGen]]]]]!

Item was changed:
  ----- Method: TMethod>>inlineableSend:in: (in category 'inlining') -----
  inlineableSend: aNode in: aCodeGen
  	"Answer true if the given send node is a call to a method that can be inlined."
  
  	| m |
+ 	aCodeGen maybeBreakForTestToInline: aNode in: self.
- 	self maybeBreakFor: aNode in: aCodeGen.
  	aNode isSend ifFalse: [ ^false ].
  	m := aCodeGen methodNamed: aNode selector.  "nil if builtin or external function"
  	^m ~= nil and: [m ~~ self and: [m isComplete and: [aCodeGen mayInline: m selector]]]!

Item was changed:
  ----- Method: TMethod>>isNode:substitutableFor:inMethod:in: (in category 'inlining') -----
  isNode: aNode substitutableFor: argName inMethod: targetMeth in: aCodeGen
  	"Answer if the given parameter node may be substituted directly into the body of
  	 the method during inlining, instead of being bound to the actual parameter variable.
  	 We allow a constant, a local variable, or a formal parameter, or simple expressions
  	 involving only these to to be directly substituted. Note that global variables cannot
  	 be subsituted into methods with possible side effects (i.e., methods that may assign
  	 to global variables) because the inlined method might depend on having the value of
  	 the global variable captured when it is passed in as an argument."
  
  	| madeNonTrivialCall count constantExpression usageCount |
  	aNode isConstant ifTrue: [^true].
  
  	aNode isVariable ifTrue:
  		[((locals includes: aNode name)
  		 or: [(args includes: aNode name)
  		 or: [#('self' 'true' 'false' 'nil') includes: aNode name]]) ifTrue: [^true].
  		"We can substitute any variable provided it is only read in the method being inlined,
  		 and if it is not read after any non-trivial call (which may update the variable)."
  		madeNonTrivialCall := false.
  		(targetMeth isComplete
  		 and: [targetMeth parseTree
  				noneSatisfy:
  					[:node|
  					 (node isSend
  					  and: [(aCodeGen isBuiltinSelector: node selector) not]) ifTrue:
  						[madeNonTrivialCall := true].
  					 (madeNonTrivialCall and: [node isVariable and: [node name = argName]])
  					 or: [node isAssignment
  						  and: [node variable name = argName]]]
  				unless:
  					[:node|
  					node isSend and: [aCodeGen isAssertSelector: node selector]]]) ifTrue:
  			[^true].
  		^targetMeth maySubstituteGlobal: aNode name in: aCodeGen].
  
  	"For now allow literal blocks to be substituted.  They better be accessed only
  	 with value[:value:*] messages though!!"
  	aNode isStmtList ifTrue: [^true].
  
+ 	"Don't inline expressions unless type-compatible,"
+ 	aNode isSend ifTrue:
+ 		[(aCodeGen
+ 				isActualType: (aCodeGen returnTypeForSend: aNode in: self)
+ 				compatibleWithFormalType: (self typeFor: argName in: aCodeGen)) ifFalse:
+ 			[^false]].
+ 
  	count := 0.
  	constantExpression := true.
  	"scan expression tree; must contain only constants, builtin ops, and inlineable vars"
  	aNode nodesDo:
  		[:node|
  		node isConstant
  			ifTrue: [] ifFalse:
  		[node isSend
  			ifTrue:
  				[((VMBasicConstants mostBasicConstantSelectors includes: node selector)
  				  or: [node isBuiltinOperator]) ifFalse: [^false].
  				 count := count + 1] ifFalse:
  		[node isVariable ifTrue:
  			[(aCodeGen isNonArgumentImplicitReceiverVariableName: node name) ifFalse:
  				[constantExpression := false.
  				((locals includes: node name)
  				 or: [(args includes: node name)
  				 or: [(#('self' 'true' 'false' 'nil') includes: node name)
  				 or: [targetMeth maySubstituteGlobal: node name in: aCodeGen]]]) ifFalse: [^false]]] ifFalse:
  		[^false]]]].
  	"inline constant expressions"
  	constantExpression ifNil: [^true].
  
  	"scan target to find usage count"
  	usageCount := 0.
  	targetMeth parseTree nodesDo:
  		[:node|
  		(node isVariable and: [node name = argName]) ifTrue:
  			[usageCount := usageCount + 1]].
  	"(usageCount > 1 and: [count <= usageCount]) ifTrue:
  		[[UsageCounts := Dictionary new.
  		  self removeClassVarName: #UsageCounts].
  		 (UsageCounts at: usageCount ifAbsentPut: [Set new]) add: ({targetMeth. argName. aNode})]."
  	"Now only inline expressions if they are used only once or are simple
  	 w.r.t. the usage count, and the usage count is not large; a heuristic that seems to work well enough."
  	^usageCount = 1 or: [usageCount <= 7 and: [count <= usageCount]]!

Item was removed:
- ----- Method: TMethod>>maybeBreakFor:in: (in category 'inlining') -----
- maybeBreakFor: aNode in: aCodeGen
- 	"convenient for debugging..."
- 	(aNode isSend
- 	and: [(aCodeGen breakSrcInlineSelector notNil or: [aCodeGen breakDestInlineSelector notNil])
- 	and: [(aCodeGen breakSrcInlineSelector ifNil: [true] ifNotNil: [:srcSel| srcSel = aNode selector])
- 	and: [aCodeGen breakDestInlineSelector ifNil: [true] ifNotNil: [:dstSel| dstSel = selector]]]]) ifTrue:
- 		[self halt: selector]!

Item was changed:
  ----- Method: TMethod>>typeFor:in: (in category 'utilities') -----
  typeFor: aVariable in: aCodeGen
  	"Answer the type for aVariable, deferring to aCodeGen (which defers to the vmClass)
  	 if no type is found and the variable is global (not an arg or a local).  Expect the
  	 cCodeGen to answer nil for variables without types. nil for typelessness is required
  	 by the type propagation logic in inlineSend:directReturn:exitVar:in:."
  	^(declarations
  			at: aVariable asString
  			ifAbsent: [((locals includes: aVariable) or: [args includes: aVariable]) ifFalse:
+ 						[aCodeGen typeOfVariable: aVariable asString]]) ifNotNil:
- 						[aCodeGen typeOfVariable: aVariable]]) ifNotNil:
  		[:decl|
  		aCodeGen extractTypeFor: aVariable asString fromDeclaration: decl]!



More information about the Vm-dev mailing list