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

commits at source.squeak.org commits at source.squeak.org
Sun Aug 22 03:09:46 UTC 2021


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

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

Name: VMMaker.oscog-eem.3047
Author: eem
Time: 21 August 2021, 8:09:37.258109 pm
UUID: 548d0a5b-eb23-4df6-bbb1-0b431cc840b3
Ancestors: VMMaker.oscog-eem.3046

...and fix the bug tail in Slang for introducing Cogit>>mapPerMethodProfile.  i.e. add TBraceNode for braces, and update printf nodes to use braces rather than raw sequences.

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

Item was changed:
  ----- Method: BraceNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
  	"Answer a TParseNode subclass equivalent of me."
  
  	"This is for case statements"
  	(elements allSatisfy: [:elem| elem isMessageNode and: [elem selector key = #->]]) ifTrue:
  		[self assert: (elements allSatisfy:
  			[:elem|
  			elem receiver isBlockNode
  			and: [elem arguments first isBlockNode
  			and: [elem receiver isPotentialCCaseLabelIn: aTMethod]]]).
  		^TBraceCaseNode new
  			caseLabels: (elements collect: [:elem| elem receiver asTranslatorNodeIn: aTMethod]);
  			cases: (elements collect: [:elem| elem arguments first asTranslatorNodeIn: aTMethod]);
  			comment: comment].
  
  	"This is for varargs selectors (variants of printf:)"
+ 	^TBraceNode new
+ 		elements: (elements collect: [:elem| elem asTranslatorNodeIn: aTMethod])!
- 	^elements collect: [:elem| elem asTranslatorNodeIn: aTMethod]!

Item was changed:
  ----- Method: CoInterpreter>>getCodeCompactionCount (in category 'internal interpreter access') -----
  getCodeCompactionCount
- 	<cmacro: '() integerObjectOf(GIV(statCodeCompactionCount))'>
  	^objectMemory integerObjectOf: statCodeCompactionCount!

Item was changed:
  ----- Method: CoInterpreter>>getCodeCompactionMSecs (in category 'internal interpreter access') -----
  getCodeCompactionMSecs
- 	<cmacro: '() integerObjectOf((GIV(statCodeCompactionUsecs) + 500) / 1000)'>
  	^objectMemory integerObjectOf: statCodeCompactionUsecs + 500 // 1000!

Item was changed:
  ----- Method: CoInterpreter>>getCogCodeSize (in category 'internal interpreter access') -----
  getCogCodeSize
- 	<cmacro: '() integerObjectOf(GIV(cogCodeSize))'>
  	^objectMemory integerObjectOf: cogCodeSize!

Item was changed:
  ----- Method: TBraceCaseNode>>nodesDo:parent: (in category 'enumerating') -----
  nodesDo: aBlock parent: parent
  	"Apply aBlock to all nodes in the receiver with each node's parent.
  	 N.B. This is assumed to be bottom-up, leaves first."
  	caseLabels do:
+ 		[:node| node nodesDo: aBlock parent: self].
- 		[:node| node nodesDo: aBlock parent: self.].
  	cases do:
  		[:node| node nodesDo: aBlock parent: self].
  	aBlock value: self value: parent!

Item was added:
+ TParseNode subclass: #TBraceNode
+ 	instanceVariableNames: 'elements'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Translation to C'!
+ 
+ !TBraceNode commentStamp: 'eem 8/21/2021 19:41' prior: 0!
+ A TBraceNode is a holder for a naked brace node ({ expr1. ... exprN}).  These are used in printf expressions, and also may pop up in macro methods (see Cogit>>#mapPerMethodProfile).
+ 
+ Instance Variables
+ 	elements:		<OrderedCollection>
+ 
+ elements
+ 	- the expressions of the brace!

Item was added:
+ ----- Method: TBraceNode>>bindVariableUsesIn: (in category 'transformations') -----
+ bindVariableUsesIn: aDictionary
+ 
+ 	elements := elements collect: [:node| node bindVariableUsesIn: aDictionary]!

Item was added:
+ ----- Method: TBraceNode>>bindVariableUsesIn:andConstantFoldIf:in: (in category 'transformations') -----
+ bindVariableUsesIn: aDictionary andConstantFoldIf: constantFold in: codeGen
+ 	"Answer either the receiver, if it contains no references to the given variables, or a new node with the given variables rebound."
+ 	| newElements |
+ 	newElements := elements collect: [:node| node bindVariableUsesIn: aDictionary andConstantFoldIf: constantFold in: codeGen].
+ 	^newElements = elements
+ 		ifTrue: [self]
+ 		ifFalse: [self shallowCopy
+ 					elements: newElements;
+ 					yourself]!

Item was added:
+ ----- Method: TBraceNode>>bindVariablesIn: (in category 'transformations') -----
+ bindVariablesIn: aDictionary
+ 
+ 	elements := elements collect: [:node| node bindVariablesIn: aDictionary]!

Item was added:
+ ----- Method: TBraceNode>>elements (in category 'accessing') -----
+ elements
+ 	^elements!

Item was added:
+ ----- Method: TBraceNode>>elements: (in category 'accessing') -----
+ elements: anObject
+ 	"Set the value of elements"
+ 
+ 	elements := anObject!

Item was added:
+ ----- Method: TBraceNode>>hasEffect (in category 'testing') -----
+ hasEffect
+ 	"Answer if this node has an effect on execution state (does something).
+ 	 Statements that don't have any effect can be elided if their value is unused."
+ 	^elements anySatisfy: [:node| node hasEffect]!

Item was added:
+ ----- Method: TBraceNode>>isBrace (in category 'testing') -----
+ isBrace
+ 	^true!

Item was added:
+ ----- Method: TBraceNode>>nodesDo: (in category 'enumerating') -----
+ nodesDo: aBlock
+ 	"Apply aBlock to all nodes in the receiver.
+ 	 N.B. This is assumed to be bottom-up, leaves first."
+ 	elements do:
+ 		[:node| node nodesDo: aBlock].
+ 	aBlock value: self!

Item was added:
+ ----- Method: TBraceNode>>nodesDo:parent: (in category 'enumerating') -----
+ nodesDo: aBlock parent: parent
+ 	"Apply aBlock to all nodes in the receiver with each node's parent.
+ 	 N.B. This is assumed to be bottom-up, leaves first."
+ 	elements do:
+ 		[:node| node nodesDo: aBlock parent: self].
+ 	aBlock value: self value: parent!

Item was added:
+ ----- Method: TBraceNode>>nodesDo:parent:unless: (in category 'enumerating') -----
+ nodesDo: aBlock parent: parent unless: cautionaryBlock
+ 
+ 	(cautionaryBlock value: self value: parent) ifTrue: [^self].
+ 	elements do:
+ 		[:node| node nodesDo: aBlock parent: self unless: cautionaryBlock].
+ 	aBlock value: self value: parent!

Item was added:
+ ----- Method: TBraceNode>>nodesDo:unless: (in category 'enumerating') -----
+ nodesDo: aBlock unless: cautionaryBlock
+ 
+ 	(cautionaryBlock value: self) ifTrue: [^self].
+ 	elements do:
+ 		[:node| node nodesDo: aBlock unless: cautionaryBlock].
+ 	aBlock value: self!

Item was added:
+ ----- Method: TBraceNode>>postCopy (in category 'copying') -----
+ postCopy
+ 	elements := elements collect: [:ea| ea copy]!

Item was added:
+ ----- Method: TBraceNode>>printOn:level: (in category 'printing') -----
+ printOn: aStream level: level
+ 	aStream crtab: level; nextPut: ${.
+ 	elements
+ 		do: [:element| element printOn: aStream]
+ 		separatedBy: [aStream nextPut: $.; space].
+ 	aStream space; nextPut: $}!

Item was added:
+ ----- Method: TBraceNode>>replaceNodesIn: (in category 'enumerating') -----
+ replaceNodesIn: aDictionary
+ 
+ 	^aDictionary
+ 		at: self
+ 		ifAbsent:
+ 			[elements := elements collect: [:node| node replaceNodesIn: aDictionary].
+ 			 self]!

Item was added:
+ ----- Method: TBraceNode>>typeOrNilFrom:in: (in category 'type inference') -----
+ typeOrNilFrom: aCodeGenerator in: aTMethod
+ 	^nil!

Item was changed:
  ----- Method: TMethod>>newCascadeTempFor: (in category 'initialization') -----
  newCascadeTempFor: aTParseNode
  	| varName varNode |
  	varName := self extraVariableName: 'cascade'.
  	varNode := TVariableNode new setName: varName.
  	aTParseNode isLeaf ifFalse:
  		[self
  			declarationAt: varName
  			put: [:tm :cg| | type |
  				type := tm determineTypeFor: aTParseNode in: cg.
  				(VMStructType structTargetKindForType: type) == #struct ifTrue:
  					["can't copy structs into cascade temps; the struct is not updated.
  					  must change to a pointer."
  					type := type, ' *'.
  					parseTree nodesDo:
  						[:node|
  						(node isAssignment
  						 and: [node variable name = varName]) ifTrue:
  							[node setExpression: (TSendNode new
  													setSelector: #addressOf:
  													receiver: (TVariableNode new setName: 'self')
  													arguments: {node expression})]]].
+ 				type ifNil: [#sqInt]]].
- 				type]].
  	^varNode!

Item was changed:
  ----- Method: TMethod>>transformPrintf: (in category 'transformations') -----
  transformPrintf: sendNode
  	"Handle forms of f:printf: & printf:. f:printf: is either
  		logFile f: formatLiteral printf: args
  	 or
  		formatLiteral f: streamName printf: args
  	 printf is
  		formatLiteral printf: args"
+ 	| map newArgs |
+ 	newArgs := OrderedCollection new.
+ 	sendNode args do:
+ 		[:arg|
+ 		arg isBrace
+ 			ifTrue: [newArgs addAllLast: arg elements]
+ 			ifFalse: [newArgs addLast: arg]].
- 	| map |
  	(sendNode receiver isConstant
  	 and: [sendNode receiver value isString]) ifTrue:
  		[| format |
   		 format := sendNode receiver asPrintfFormatStringNode.
  		 sendNode selector first == $f ifTrue: "fprintf et al..."
  			[sendNode receiver: (TVariableNode new setName: 'self').
+ 			 sendNode arguments: {sendNode args first. format}, newArgs allButFirst.
- 			 sendNode arguments: {sendNode args first. format}, sendNode args allButFirst.
  			 ^sendNode].
  		sendNode receiver: format.
+ 		sendNode arguments: newArgs.
  		^sendNode].
  	map := Dictionary new.
  	sendNode nodesDo:
  		[:subNode|
  		 (subNode isConstant and: [subNode value isString and: [subNode value includes: $%]]) ifTrue:
  			[map at: subNode put: subNode asPrintfFormatStringNode]].
+ 	sendNode arguments: newArgs.
  	sendNode replaceNodesIn: map.
  	^sendNode!

Item was added:
+ ----- Method: TParseNode>>isBrace (in category 'testing') -----
+ isBrace
+ 	^false!

Item was changed:
  ----- Method: TSwitchStmtNode>>nodesDo:parent: (in category 'enumerating') -----
  nodesDo: aBlock parent: parent
  	"Apply aBlock to all nodes in the receiver with each node's parent.
  	 N.B. This is assumed to be bottom-up, leaves first."
  	expression nodesDo: aBlock parent: self.
  	cases do:
  		[:pair|
+ 		pair first do: [:node| node nodesDo: aBlock parent: self].
+ 		pair last nodesDo: aBlock parent: self].
- 		pair first do: [:node| node nodesDo: aBlock parent: self.].
- 		pair last nodesDo: aBlock parent: self.].
  	otherwiseOrNil ifNotNil:
  		[otherwiseOrNil nodesDo: aBlock parent: self].
  	aBlock value: self value: parent!



More information about the Vm-dev mailing list