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

commits at source.squeak.org commits at source.squeak.org
Fri Sep 1 23:17:49 UTC 2017


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

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

Name: VMMaker.oscog-eem.2267
Author: eem
Time: 1 September 2017, 4:16:52.098824 pm
UUID: 9a398445-4694-49b8-a1d1-77e877f29295
Ancestors: VMMaker.oscog-eem.2266

Slang:
Allow plugins to use sends to access struct members.
To this end replace all sends of TSendNode>>isStructSendIn: with CCodeGenerator>>isStructSend:.

Plugins wanting to use this facility must override InterpreterPlugin>>#isStructType: to answer true for types denoting structs.

There's probably more work to be done (e.g. to TSendNode>>structTargetKindIn: which sends to VMStructType directly).  Biut this is enough for the FileAttributesPlugin.

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

Item was changed:
  ----- Method: CCodeGenerator>>generateIfNilAsArgument:on:indent: (in category 'C translation') -----
  generateIfNilAsArgument: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  
  	(self isNilConstantReceiverOf: msgNode)
  		ifFalse:
  			[aStream nextPutAll: '(!!('.
  			 msgNode receiver emitCCodeAsArgumentOn: aStream level: 0 generator: self.
  			 aStream nextPut: $); crtab: level + 1; nextPut: $?; space.
  			 msgNode args last emitCCodeAsArgumentOn: aStream level: level + 2 generator: self.
  			 aStream crtab: level + 1; nextPut: $:; space.
  			 msgNode receiver emitCCodeAsArgumentOn: aStream level: 0 generator: self.
  			 (msgNode receiver isLeaf
  			  or: [msgNode receiver isSend
+ 				  and: [(self isStructSend: msgNode receiver)
- 				  and: [(msgNode receiver isStructSendIn: self)
  				  and: [msgNode receiver receiver isLeaf]]]) ifFalse:
  				[logger cr; nextPutAll: 'sending ifNil: to non-leaf in '; nextPutAll: currentMethod selector].
  			 aStream nextPut: $)]
  		ifTrue:
  			[msgNode args first emitCCodeAsArgumentOn: aStream level: level generator: self]!

Item was added:
+ ----- Method: CCodeGenerator>>isStructSend: (in category 'utilities') -----
+ isStructSend: aTSendNode
+ 	"Answer if the argument aTSendNode is a send of a structure accessor.
+ 	 This is tricky.  We want
+ 		foo bar => foo->bar
+ 		foo bar => foo.bar
+ 		foo bar: expr => foo->bar = expr
+ 		foo bar: expr => foo.bar = expr
+ 	 depending on whether foo is a struct or a pointer to a struct,
+ 	 but only if both foo is a struct type and bar is a field accessor.
+ 	 The tricky cases are self-sends within struct class methods.  Here we need to
+ 	 distinguish between self-sends of ordinary methods from self sends of accessors."
+ 	^aTSendNode numArgs <= 1
+ 	   and: [(aTSendNode receiver structTargetKindIn: self) notNil
+ 	   and: [(self methodNamed: aTSendNode selector)
+ 				ifNil: [false]
+ 				ifNotNil: [:method| method isStructAccessor]]]!

Item was added:
+ ----- Method: CCodeGenerator>>structTargetKindForDeclaration: (in category 'C code generator') -----
+ structTargetKindForDeclaration: typeName "<String>"
+ 	^VMStructType structTargetKindForDeclaration: typeName!

Item was changed:
  ----- Method: CCodeGenerator>>structTargetKindForVariableName: (in category 'C code generator') -----
  structTargetKindForVariableName: varName "<String>"
+ 	^(self typeOfVariable: varName) ifNotNil:
+ 		[:declaration|
+ 		 self structTargetKindForDeclaration: declaration]!
- 	^VMStructType structTargetKindForDeclaration: (self typeOfVariable: varName)!

Item was added:
+ ----- Method: InterpreterPlugin class>>isStructType: (in category 'translation') -----
+ isStructType: typeName "<String>"
+ 	"Subclasses should override to answer trye for struct types they use."
+ 	^false!

Item was changed:
  ----- Method: TMethod>>computePossibleSideEffectsInto:visited:in: (in category 'inlining support') -----
  computePossibleSideEffectsInto: writtenToVars visited: visitedSelectors in: aCodeGen
  	"Add all variables written to by this method and its callees to writtenToVars.
  	 Avoid circularity via visitedSelectors"
  
  	(visitedSelectors includes: selector) ifTrue:
  		[^self].
  	visitedSelectors add: selector.
  	writtenToGlobalVarsCache ifNotNil:
  		[writtenToVars addAll: writtenToGlobalVarsCache.
  		 ^self].
  	parseTree nodesDo:
  		[ :node |
  			(node isAssignment
  			 and: [(locals includes: node variable name) not])
  				ifTrue:
  					[writtenToVars add: node variable name].
  			(node isSend
  			 and: [node isBuiltinOperator not
+ 			 and: [(aCodeGen isStructSend: node) not]]) ifTrue:
- 			 and: [(node isStructSendIn: aCodeGen) not]]) ifTrue:
  				[(aCodeGen methodNamed: node selector) ifNotNil:
  					[:method|
  					 method
  						computePossibleSideEffectsInto: writtenToVars
  						visited: visitedSelectors
  						in: aCodeGen]]].
  	writtenToGlobalVarsCache := writtenToVars copy!

Item was changed:
  ----- Method: TMethod>>ensureToByDoLoopLimitIsSafeAndEfficient:in: (in category 'transformations') -----
  ensureToByDoLoopLimitIsSafeAndEfficient: node in: aCodeGen
  	"For both safety and efficiency, make sure that to:[by:]do: loops
  	 with complex limits have a variable to hold the limit expression.
  	 In C the limit expression is evaluated each time round the loop
  	 so if the loop has side-effects (which it usually will), the C compiler
  	 may not be able to optimize the limit expression itself."
  	| limitExpr hasSideEffects |
  	 limitExpr := node args first.
  	 hasSideEffects := limitExpr anySatisfy:
  						[:subNode|
  						subNode isSend
  						and: [(aCodeGen isBuiltinSelector: subNode selector) not
+ 						and: [(aCodeGen isStructSend: subNode) not]]].
- 						and: [(subNode isStructSendIn: aCodeGen) not]]].
  	 node args size = 4
  		ifTrue:
  			[hasSideEffects
  				ifTrue: [locals add: node args last name]
  				ifFalse: [node arguments: node args allButLast]]
  		ifFalse: "If the expression is complex but as yet there is no limit variable, add it"
  			[hasSideEffects ifTrue:
  				[| var |
  				 var := self unusedNamePrefixedBy: 'toDoLimit' avoiding: locals. "N.B. adds it to locals!!!!"
  				 node arguments: node args, {TVariableNode new setName: var; yourself}.
  				 declarations
  					at: node args third args first
  					ifPresent: [:decl| self declarationAt: var put: (self typeFor: node args third args first in: aCodeGen), ' ', var]]]!

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].
  
  	(aNode isSend
  	 and: [aNode numArgs = 0
+ 	 and: [aCodeGen isStructSend: aNode]]) ifTrue:
- 	 and: [aNode isStructSendIn: aCodeGen]]) 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 ].
- 				 and: [node isStructSendIn: aCodeGen]]) 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!

Item was changed:
  ----- Method: TMethod>>tryToInlineMethodExpressionsIn: (in category 'inlining') -----
  tryToInlineMethodExpressionsIn: aCodeGen
  	"Expand any (complete) inline methods sent by this method as receivers or parameters.
  	 Answer if anything was inlined."
  
  	| sendsToInline |
  	sendsToInline := Dictionary new: 100.
+ 	aCodeGen
+ 		pushScope: declarations
+ 		while: [parseTree
+ 					nodesDo:
+ 						[:node|
+ 						(self inlineableFunctionCall: node in: aCodeGen) ifTrue:
+ 							[(self inlineFunctionCall: node in: aCodeGen) ifNotNil:
+ 								[:replacement|
+ 								 sendsToInline at: node put: replacement]]]
+ 					unless: "Don't inline the arguments to asserts to keep the asserts readable"
+ 						[:node|
+ 						node isSend
+ 						and: [node selector == #cCode:inSmalltalk:
+ 							or: [aCodeGen isAssertSelector: node selector]]]].
- 	parseTree
- 		nodesDo:
- 			[:node|
- 			(self inlineableFunctionCall: node in: aCodeGen) ifTrue:
- 				[(self inlineFunctionCall: node in: aCodeGen) ifNotNil:
- 					[:replacement|
- 					 sendsToInline at: node put: replacement]]]
- 		unless: "Don't inline the arguments to asserts to keep the asserts readable"
- 			[:node|
- 			node isSend
- 			and: [node selector == #cCode:inSmalltalk:
- 				or: [aCodeGen isAssertSelector: node selector]]].
  
  	sendsToInline isEmpty ifTrue:
  		[^false].
  	self replaceNodesIn: sendsToInline.
  	^true!

Item was changed:
  ----- Method: TSendNode>>emitCCodeAsFieldReferenceOn:level:generator: (in category 'C code generation') -----
  emitCCodeAsFieldReferenceOn: aStream level: level generator: aCodeGen
  	"If appropriate, translate this message send as a pointer dereference"
  
  	| parenCount |
+ 	(aCodeGen isStructSend: self) ifFalse:
- 	(self isStructSendIn: aCodeGen) ifFalse:
  		[^false].
  
  	parenCount := receiver isSend ifTrue: [2] ifFalse: [1].
  	aStream next: parenCount put: $(.
  	receiver  emitCCodeAsExpressionOn: aStream level: 0 generator: aCodeGen.
  	parenCount > 1 ifTrue:
  		[aStream nextPut: $)].
  	(receiver structTargetKindIn: aCodeGen) caseOf: {
  		[#pointer] -> [aStream nextPut: $-; nextPut: $>].
  		[#struct] -> [aStream nextPut: $.] }.
  	aStream nextPutAll: (aCodeGen cFunctionNameFor: selector).
  	arguments isEmpty ifFalse:
  		[self assert: arguments size = 1.
  		 aStream nextPutAll: ' = '.
  		 arguments first emitCCodeAsExpressionOn: aStream level: level generator: aCodeGen].
  	aStream nextPut: $).
  	^true!

Item was removed:
- ----- Method: TSendNode>>isStructSendIn: (in category 'testing') -----
- isStructSendIn: aCodeGen
- 	"Answer if the recever is a send of a structure accessor.
- 	 This is tricky.  We want
- 		foo bar => foo->bar
- 		foo bar => foo.bar
- 		foo bar: expr => foo->bar = expr
- 		foo bar: expr => foo.bar = expr
- 	 depending on whether foo is a struct or a pointer to a struct,
- 	 but only if both foo is a struct type and bar is a field accessor.
- 	 The tricky cases are self-sends within struct class methods.  Here we need to
- 	 distinguish between self-sends of ordinary methods from self sends of accessors."
- 	^arguments size <= 1
- 	   and: [(receiver structTargetKindIn: aCodeGen) notNil
- 	   and: [(aCodeGen methodNamed: selector)
- 				ifNil: [false]
- 				ifNotNil: [:method| method isStructAccessor]]]!

Item was changed:
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
  namesDefinedAtCompileTime
  	"Answer the set of names for variables that should be defined at compile time.
  	 Some of these get default values during simulation, and hence get defaulted in
  	 the various initializeMiscConstants methods.  But that they have values should
  	 /not/ cause the code generator to do dead code elimination based on their
  	 default values."
  	^#(	VMBIGENDIAN
  		IMMUTABILITY
  		STACKVM COGVM COGMTVM SPURVM
  		PharoVM								"Pharo vs Squeak"
  		TerfVM									"Terf vs Squeak"
  		EnforceAccessControl					"Newspeak"
  		CheckRememberedInTrampoline		"IMMUTABILITY"
+ 		LLDB									"As of lldb-370.0.42 Swift-3.1, passing funciton parameters to printOopsSuchThat fails with Internal error [IRForTarget]: Couldn't rewrite one of the arguments of a function call.  Turning off link time optimization with -fno-lto has no effect.  hence we define some debugging functions as being <option: LLDB>"
+ 		WIN32)!
- 		LLDB)									"As of lldb-370.0.42 Swift-3.1, passing funciton parameters to printOopsSuchThat fails with Internal error [IRForTarget]: Couldn't rewrite one of the arguments of a function call.  Turning off link time optimization with -fno-lto has no effect.  hence we define some debugging functions as being <option: LLDB>"!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>isStructSend: (in category 'utilities') -----
+ isStructSend: aTSendNode
+ 	"Answer if the argument aTSendNode is a send of a structure accessor.
+ 	 This is tricky.  We want
+ 		foo bar => foo->bar
+ 		foo bar => foo.bar
+ 		foo bar: expr => foo->bar = expr
+ 		foo bar: expr => foo.bar = expr
+ 	 depending on whether foo is a struct or a pointer to a struct,
+ 	 but only if both foo is a struct type and bar is a field accessor.
+ 	 The tricky cases are self-sends within struct class methods.  Here we need to
+ 	 distinguish between self-sends of ordinary methods from self sends of accessors.
+ 
+ 	Override to avoid requiring that there be a struct accessor method for the selector."
+ 	^aTSendNode numArgs <= 1
+ 	   and: [(aTSendNode receiver structTargetKindIn: self) notNil]!

Item was added:
+ ----- Method: VMPluginCodeGenerator>>structTargetKindForDeclaration: (in category 'C code generator') -----
+ structTargetKindForDeclaration: decl "<String>"
+ 	^(super structTargetKindForDeclaration: decl) ifNil:
+ 		[pluginClass ifNotNil:
+ 			[(pluginClass isStructType: (decl last = $*
+ 											ifTrue: [decl allButLast]
+ 											ifFalse: [decl]) withBlanksTrimmed) ifTrue:
+ 				[(decl indexOf: $*) > 0
+ 					ifTrue: [#pointer]
+ 					ifFalse: [#struct]]]]!



More information about the Vm-dev mailing list