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

commits at source.squeak.org commits at source.squeak.org
Fri Mar 11 01:31:02 UTC 2016


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

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

Name: VMMaker.oscog-eem.1722
Author: eem
Time: 10 March 2016, 5:29:23.250589 pm
UUID: e5c44d63-ba75-4cd1-bf4e-c92c4232bbfe
Ancestors: VMMaker.oscog-eem.1721

Revert the more flexible super expansion code.  It produces an as-yet-undiagnosed lockup in generating the NewspeakSpurCogVM.

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

Item was changed:
  ----- Method: MessageNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
  	"make a CCodeGenerator equivalent of me"
  	"selector is sometimes a Symbol, sometimes a SelectorNode!!
  	On top of this, numArgs is needed due to the (truly grody) use of
  	arguments as a place to store the extra expressions needed to generate
  	code for in-line to:by:do:, etc.  see below, where it is used."
+ 	| rcvrOrNil sel args ifNotNilBlock |
- 	| lastExpression rcvrOrNil sel args ifNotNilBlock |
  	rcvrOrNil := receiver ifNotNil: [receiver asTranslatorNodeIn: aTMethod].
  	(rcvrOrNil notNil
  	and: [rcvrOrNil isVariable
  	and: [rcvrOrNil name = 'super']]) ifTrue:
+ 		[^aTMethod superExpansionNodeFor: selector key args: arguments].
- 		[lastExpression := aTMethod parseTree statements last.
- 		 ^aTMethod
- 			superExpansionNodeFor: selector key
- 			args: arguments
- 			isResult: (lastExpression isReturn and: [lastExpression expr == self])].
  	sel := selector isSymbol ifTrue: [selector] ifFalse: [selector key].
  	((sel == #cCode:inSmalltalk: "extracting here rather than in translation allows inlining in the block."
  	  or: [sel == #cCode:])
  	 and: [arguments first isBlockNode]) ifTrue:
  		[| block |
  		 ^(block := arguments first asTranslatorNodeIn: aTMethod) statements size = 1
  			ifTrue: [block statements first]
  			ifFalse: [block]].
  	args := arguments
  				select: [:arg| arg notNil]
  				thenCollect: [:arg| arg asTranslatorNodeIn: aTMethod].
  	(sel = #to:by:do: and: [arguments size = 7 and: [(arguments at: 7) notNil]]) ifTrue:
  		["Restore limit expr that got moved by transformToDo:"
  		 args := {(arguments at: 7) value asTranslatorNodeIn: aTMethod. 
  				  args second.
  				  args third. "add the limit var as a hidden extra argument; we may need it later"
  				  TVariableNode new setName: arguments first key}].
  	(sel == #ifTrue:ifFalse: and: [arguments first isJust: NodeNil]) ifTrue:
  		[sel := #ifFalse:. args := {args last}].
  	(sel == #ifTrue:ifFalse: and: [arguments last isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args first}].
  	(sel == #ifFalse:ifTrue: and: [arguments first isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args last}].
  	(sel == #ifFalse:ifTrue: and: [arguments last isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args first}].
  	((sel == #ifFalse: or: [sel == #or:])
  	 and: [arguments size = 2 and: [(arguments at: 2) notNil]]) ifTrue:
  		["Restore argument block that got moved by transformOr: or transformIfFalse:"
  		 args := {(arguments at: 2) asTranslatorNodeIn: aTMethod}].
  	(args size > sel numArgs and: [sel ~~ #to:by:do:]) ifTrue: "to:by:do: has iLimiT hidden in last arg"
  		["prune the extra blocks left by ifTrue:, ifFalse:, and: & or:"
  		 self assert: args size - sel numArgs = 1.
  		 self assert: (args last isStmtList
  					  and: [args last statements size = 1
  					  and: [(args last statements first isVariable
  							or: [args last statements first isConstant])
  					  and: [#('nil' true false) includes: args last statements first nameOrValue]]]).
  		 args := args first: sel numArgs].
  	"For the benefit of later passes, e.g. value: inlining,
  	 transform e ifNotNil: [:v| ...] into  v := e. v ifNotNil: [...],
  	 which in fact means transforming (v := e) ifTrue: [:v|...] into v := e. v ifTrue: [...]."
  	((sel == #ifTrue: or: [sel == #ifFalse: or: [sel == #ifTrue:ifFalse: or: [sel == #ifFalse:ifTrue:]]])
  	 and: [receiver notNil
  	 and: [receiver isAssignmentEqualsEqualsNil
  	 and: [(ifNotNilBlock := args detect: [:arg| arg isStmtList and: [arg args size = 1]] ifNone: []) notNil]]]) ifTrue:
  		[ifNotNilBlock setArguments: #().
  		 ^TStmtListNode new
  			setArguments: #()
  			statements:
  				{	receiver receiver asTranslatorNodeIn: aTMethod.
  					TSendNode new
  						setSelector: sel
  						receiver: (TSendNode new
  									setSelector: #==
  									receiver: (receiver receiver variable asTranslatorNodeIn: aTMethod)
  									arguments: {receiver arguments first asTranslatorNodeIn: aTMethod})
  						arguments: args }].
  	^TSendNode new
  		setSelector: sel
  		receiver: rcvrOrNil
  		arguments: args!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>setHiddenRootsObj: (in category 'class table') -----
- setHiddenRootsObj: anOop
- 	"Override to check for and abort old format 64-bit Spur images in which the smallFloatTag is 3."
- 	super setHiddenRootsObj: anOop.
- 	(self bootstrapping not
- 	 and: [self smallFloatTag ~= (self rawHashBitsOf: (self fetchPointer: self smallFloatTag
- 															ofObject: classTableFirstPage))]) ifTrue:
- 		[self error: 'This is an old-format 64-bit Spur image with smallFloatTag = 3.  Aborting.']!

Item was removed:
- ----- Method: TMethod>>mapReturnsToGotos (in category 'transformations') -----
- mapReturnsToGotos
- 	"For super expansions inner returns must be mapped to gotos to prevent premature exit.
- 	 But this only works if no value is being returned.
- 	 Anything meaningful in the returned expression must be retained."
- 
- 	| map label |
- 	map := Dictionary new.
- 	parseTree nodesDo:
- 		[:node|
- 		node isReturn ifTrue:
- 			[(node expression isVariable and: [#('self' 'nil') includes: node expression name])
- 				ifTrue:
- 					[map at: node put: (TGoToNode new
- 											setLabel: (label ifNil: [label := self unusedLabelForInlining: self]);
- 											yourself)]
- 				ifFalse: [self error: 'Cannot expand super node with inner return that answers a value!!']]].
- 	label ifNotNil:
- 		[parseTree := parseTree replaceNodesIn: map.
- 		 parseTree setStatements: (parseTree statements asOrderedCollection
- 										addLast: (TLabeledCommentNode new
- 														setLabel: label;
- 														yourself);
- 										yourself)]!

Item was added:
+ ----- Method: TMethod>>superExpansionNodeFor:args: (in category 'inlining') -----
+ superExpansionNodeFor: aSelector args: argumentNodes
+ 	"Answer the expansion of a super send.  Merge the super expansion's
+ 	 locals, properties and comment into this method's properties."
+ 	(definingClass superclass lookupSelector: aSelector)
+ 		ifNil: [self error: 'superclass does not define super method']
+ 		ifNotNil:
+ 			[:superMethod| | superTMethod commonVars varMap |
+ 			superTMethod := superMethod methodNode asTranslationMethodOfClass: self class.
+ 			((argumentNodes allSatisfy: [:parseNode| parseNode isVariableNode])
+ 			and: [(argumentNodes asOrderedCollection collect: [:parseNode| parseNode key]) = superTMethod args]) ifFalse:
+ 				[self error: definingClass name, '>>',selector, ' args ~= ',
+ 							superTMethod definingClass name, '>>', aSelector,
+ 							(String with: $. with: Character cr),
+ 							'For super expansions to be translated correctly each argument must be a variable with the same name as the corresponding argument in the super method.'].
+ 			(commonVars := superTMethod locals intersection: self locals) notEmpty ifTrue:
+ 				[varMap := Dictionary new.
+ 				 commonVars do:
+ 					[:k| varMap at: k put: (superTMethod unusedNamePrefixedBy: k avoiding: self allLocals)].
+ 				 superTMethod renameVariablesUsing: varMap].
+ 			self mergePropertiesOfSuperMethod: superTMethod.
+ 			self assert: (superTMethod locals allSatisfy: [:var| (self locals includes: var) not]).
+ 			locals addAll: superTMethod locals.
+ 			superTMethod declarations keysAndValuesDo:
+ 				[:var :decl|
+ 				self declarationAt: var put: decl].
+ 			superTMethod comment ifNotNil:
+ 				[:superComment|
+ 				comment := comment
+ 								ifNil: [superComment]
+ 								ifNotNil: [superComment, comment]].
+ 			superTMethod extraVariableNumber ifNotNil:
+ 				[:scvn|
+ 				extraVariableNumber := extraVariableNumber ifNil: [scvn] ifNotNil: [:cvn| cvn + scvn]].
+ 			superTMethod elideAnyFinalReturn.
+ 			^superTMethod parseTree]!

Item was removed:
- ----- Method: TMethod>>superExpansionNodeFor:args:isResult: (in category 'inlining') -----
- superExpansionNodeFor: aSelector args: argumentNodes isResult: superExpansionIsResult
- 	"Answer the expansion of a super send.  Merge the super expansion's
- 	 locals, properties and comment into this method's properties."
- 	(definingClass superclass lookupSelector: aSelector)
- 		ifNil: [self error: 'superclass does not define super method']
- 		ifNotNil:
- 			[:superMethod| | superTMethod commonVars varMap |
- 			superTMethod := superMethod methodNode asTranslationMethodOfClass: self class.
- 			((argumentNodes allSatisfy: [:parseNode| parseNode isVariableNode])
- 			and: [(argumentNodes asOrderedCollection collect: [:parseNode| parseNode key]) = superTMethod args]) ifFalse:
- 				[self error: definingClass name, '>>',selector, ' args ~= ',
- 							superTMethod definingClass name, '>>', aSelector,
- 							(String with: $. with: Character cr),
- 							'For super expansions to be translated correctly each argument must be a variable with the same name as the corresponding argument in the super method.'].
- 			(commonVars := superTMethod locals intersection: self locals) notEmpty ifTrue:
- 				[varMap := Dictionary new.
- 				 commonVars do:
- 					[:k| varMap at: k put: (superTMethod unusedNamePrefixedBy: k avoiding: self allLocals)].
- 				 superTMethod renameVariablesUsing: varMap].
- 			self mergePropertiesOfSuperMethod: superTMethod.
- 			self assert: (superTMethod locals allSatisfy: [:var| (self locals includes: var) not]).
- 			locals addAll: superTMethod locals.
- 			superTMethod declarations keysAndValuesDo:
- 				[:var :decl|
- 				self declarationAt: var put: decl].
- 			superTMethod comment ifNotNil:
- 				[:superComment|
- 				comment := comment
- 								ifNil: [superComment]
- 								ifNotNil: [superComment, comment]].
- 			superTMethod extraVariableNumber ifNotNil:
- 				[:scvn|
- 				extraVariableNumber := extraVariableNumber ifNil: [scvn] ifNotNil: [:cvn| cvn + scvn]].
- 			superTMethod elideAnyFinalReturn.
- 			superExpansionIsResult ifFalse:
- 				[superTMethod mapReturnsToGotos.
- 				 labels addAll: superTMethod labels].
- 			^superTMethod parseTree]!



More information about the Vm-dev mailing list