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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 7 01:32:56 UTC 2022


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

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

Name: VMMaker.oscog-eem.3278
Author: eem
Time: 6 December 2022, 5:32:36.728733 pm
UUID: 32f9ddc1-7a68-4cf4-b64f-fc9005104bcf
Ancestors: VMMaker.oscog-eem.3277

Fix Slang analysis of macro/constant methods in the wake of Compiler-eem.483, which doesn't add implicit literals to the literal frame.

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

Item was changed:
  ----- Method: BlockNode>>isPotentialCCaseLabel:in: (in category '*VMMaker-C translation') -----
  isPotentialCCaseLabel: stmt in: aTMethod
  	(stmt isVariableNode
  	 or: [stmt isLiteralNode
  		and: [stmt isConstantNumber or: [stmt literalValue isSymbol]]]) ifTrue:
  		[^true].
  	stmt isMessageNode ifTrue:
  		[| selector implementingClass method |
  		 selector := stmt selector key.
  		 (#(* + -) includes: selector) ifTrue:
  			[^(self isPotentialCCaseLabel: stmt receiver in: aTMethod)
  			   and: [self isPotentialCCaseLabel: stmt arguments first in: aTMethod]].
  
  		 (selector = #asSymbol
  		  and: [stmt receiver isLiteralNode
  		  and: [stmt receiver literalValue isSymbol]]) ifTrue:
  			[^true].
  
  		 (stmt arguments isEmpty
  		  and: [implementingClass := aTMethod definingClass whichClassIncludesSelector: selector.
  			   implementingClass ifNil:
  				[implementingClass := aTMethod definingClass objectMemoryClass whichClassIncludesSelector: selector].
  			   method := implementingClass >> selector.
  			   (method isQuick
+ 				or: [method numLiterals <= 3 and: [method allLiterals first value isInteger]])
- 				or: [(method literalAt: 1) isInteger
- 					and: [method numLiterals = 3]])
  		   and: [(implementingClass basicNew perform: selector) isInteger]]) ifTrue:
  				[^true]].
  	^false!

Item was changed:
  ----- Method: CCodeGenerator>>addMethodFor:selector: (in category 'utilities') -----
  addMethodFor: aClass selector: selector
  	"Add the given method to the code base and answer its translation
  	 or nil if it shouldn't be translated."
  
  	| method tmethod |
  	method := aClass compiledMethodAt: selector.
  	(method pragmaAt: #doNotGenerate) ifNotNil:
  		["only remove a previous method if this one overrides it, i.e. this is a subclass method.
  		 If the existing method is in a different hierarchy this method must be merely a redeirect."
  		 (methods at: selector ifAbsent: []) ifNotNil:
  			[:tm|
  			(aClass includesBehavior: tm definingClass) ifTrue:
  				[self removeMethodForSelector: selector]].
  		 ^nil].
  	method isSubclassResponsibility ifTrue:
  		[^nil].
  	(self shouldIncludeMethodFor: aClass selector: selector) ifFalse:
  		[^nil].
  	tmethod := self compileToTMethodSelector: selector in: aClass.
  	"Even though we exclude initialize methods, we must consider their
  	 global variable usage, otherwise globals may be incorrectly localized."
  	selector == #initialize ifTrue:
  		[self checkForGlobalUsage: (tmethod allReferencedVariablesUsing: self) in: tmethod.
  		 ^nil].
  	self addMethod: tmethod.
  	"If the method has a macro then add the macro.  But keep the method
  	 for analysis purposes (e.g. its variable accesses)."
  	(method pragmaAt: #cmacro:) ifNotNil:
  		[:pragma|
  		self addMacro: (pragma argumentAt: 1) for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	(method pragmaAt: #cmacro) ifNotNil:
  		[:pragma| | literal | "Method should be just foo ^const"
  		self assert: (self isValidMacroMethod: method).
+ 		literal := method decompile quickMethodReturnLiteral.
- 		literal := (method isQuick or: [method numArgs = 1])
- 					ifTrue: [method decompile quickMethodReturnLiteral]
- 					ifFalse: [method literalAt: 1].
  		self addMacro: (method numArgs = 1 "foo: arg ^const is a useful exception"
  								ifTrue: ['(x) ']
  								ifFalse: ['() ']),
  						(method isReturnField
  								ifTrue: [literal]
  								ifFalse: [self cLiteralFor: literal value name: method selector]) for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	^tmethod!

Item was changed:
  ----- Method: CCodeGenerator>>isValidMacroMethod: (in category 'utilities') -----
  isValidMacroMethod: method
  	| statements value |
+ 	^(method isQuick and: [method primitive ~= 256 "^self"])
+ 	 "foo: arg ^constant is a useful exception"
+ 	 or: [(statements := method methodNode block statements) size = 1
+ 		 and: [statements first isReturn
+ 		 and: [(value := statements first expr) isLiteralNode
+ 			or: [(value isVariableNode
+ 				and: [#('true' 'false' 'nil') includes: value key])
+ 			or: [value isLiteralVariableNode
+ 				and: [value key value isInteger
+ 					or: [#(true false nil) includes: value key value]]]]]]]!
- 	method numArgs = 0 ifTrue:
- 		[^method numLiterals = 3 "the value, the pragma and the methodClass" or: [method isQuick]].
- 	"foo: arg ^constant is a useful exception"
- 	^(statements := method methodNode block statements) size = 1
- 	 and: [statements first isReturn
- 	 and: [(value := statements first expr) isLiteralNode
- 		or: [value isVariableNode
- 			and: [#('true' 'false' 'nil') includes: value key]]]]!



More information about the Vm-dev mailing list