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

commits at source.squeak.org commits at source.squeak.org
Sat Oct 17 22:42:27 UTC 2020


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

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

Name: VMMaker.oscog-eem.2846
Author: eem
Time: 17 October 2020, 3:42:17.887067 pm
UUID: e8cdd50a-a54c-4552-8787-6aa1e9441f9c
Ancestors: VMMaker.oscog-eem.2845

Slang: ix a regression in inlinability that broke users of InterpreterPlugin>>#positiveMachineIntegerFor: (marked <inline: #always>).

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

Item was changed:
  ----- Method: IA32ABIPlugin>>primStrlenThroughPointerAtIndex (in category 'primitives-accessing') -----
  primStrlenThroughPointerAtIndex
  	"Answer the number of non-null bytes starting at the byte addressed by
  	 the 4-byte pointer at index."
  	"<Alien> strlenThroughPointerAt: index <Integer> ^<Integer>
  		<primitive: 'primStrlenThroughPointerAtIndex' error: errorCode module: 'IA32ABI'>"
  	| byteOffset rcvr addr |
  	<export: true>
- 	<var: #ptr type: #'char *'>
  
  	byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.
  	rcvr := interpreterProxy stackObjectValue: 1.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	(self index: byteOffset length: interpreterProxy bytesPerOop inRange: rcvr) ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadIndex].
  	addr := (self startOfData: rcvr) + byteOffset.
  	^interpreterProxy methodReturnInteger: (self strlen: (self cCoerce: (self longAt: addr) to: #'char *'))!

Item was changed:
  ----- Method: TMethod>>isSubstitutableNode:intoMethod:in: (in category 'inlining') -----
  isSubstitutableNode: aNode intoMethod: targetMeth in: aCodeGen
  	"Answer true if the given parameter node is either a constant, a local variable, or a formal parameter of the receiver. Such parameter nodes may be substituted directly into the body of the method during inlining. 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."
  
  	| var |
  	aNode isConstant ifTrue: [ ^ true ].
  
  	aNode isVariable ifTrue: [
  		var := aNode name.
  		((locals includes: var) or: [args includes: var]) ifTrue: [ ^ true ].
  		(#(self true false nil) includes: var) ifTrue: [ ^ true ].
  		(targetMeth maySubstituteGlobal: var in: aCodeGen) ifTrue: [ ^ true ].
  	].
  
  	"For now allow literal blocks to be substituted.  They better be accessed only
  	 with value[:value:*] messages though!!"
  	aNode isStmtList ifTrue: [^true].
  
+ 	"Allow inlining of struct accesses and external functions;
+ 	 an external function won't appear in the code gen's set of methods."
  	(aNode isSend
  	 and: [aNode numArgs = 0
+ 	 and: [(aCodeGen isStructSend: aNode)
+ 		or: [(aCodeGen methodNamed: aNode selector) isNil]]]) ifTrue:
- 	 and: [aCodeGen isStructSend: aNode]]) ifTrue:
  		[^true].
  
  	"scan expression tree; must contain only constants, builtin ops, and inlineable vars"
  	aNode nodesDo: [ :node |
  		node isSend ifTrue: [
  			(node isBuiltinOperator
  			 or: [node numArgs = 0
  				 and: [aCodeGen isStructSend: node]]) ifFalse: [ ^false ].
  		].
  		node isVariable ifTrue: [
  			var := node name.
  			((locals includes: var) or:
  			 [(args includes: var) or:
  			 [(#(self true false nil) includes: var) or:
  			 [targetMeth maySubstituteGlobal: var in: aCodeGen]]]) ifFalse: [ ^ false ].
  		].
  		(node isConstant or: [node isVariable or: [node isSend]]) ifFalse: [ ^false ].
  	].
  
  	^ true!



More information about the Vm-dev mailing list