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

commits at source.squeak.org commits at source.squeak.org
Wed Aug 9 20:38:26 UTC 2017


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

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

Name: VMMaker.oscog-eem.2260
Author: eem
Time: 9 August 2017, 1:37:32.145179 pm
UUID: 1c83a01b-3423-408d-8adb-db126b0bddac
Ancestors: VMMaker.oscog-eem.2259

Fix Spur instantiateClass:indexableSize: for non-indexaqble objects.  Old code would allocate if num indexable slots was 0, but would zero-fill.  New code has the fixed old code ifdef'ed out and always fails.  We can make the old code work for Squeak if required, but since no one's noticed DirectoryEntry crashing the system this shouldn't be an issue.  If peopel feel strongly about the ugly old code simply delete it.

Fix Slang so that e.g. cppIf: (PharoVM or: [true]) ifTrue: aBlock => aBlock

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

Item was changed:
  ----- Method: CCodeGenerator>>generateInlineCppIfElse:asArgument:on:indent: (in category 'C translation') -----
  generateInlineCppIfElse: msgNode asArgument: asArgument on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  	| expr putStatement |
  	"Compile-time expansion for constants set in the options dictionary,
  	 e.g. to cut down on noise for MULTIPLEBYTECODESETS."
  	putStatement := asArgument
  		ifTrue: "emitCCodeAsArgumentOn: doesn't indent, the code needs indenting if it takes multiple lines, so post-process."
  			[[:node| | expansion |
  			  expansion := String streamContents: [:s| node emitCCodeAsArgumentOn: s level: level generator: self].
  			  aStream nextPutAll:
  			  ((expansion includes: Character cr)
  				ifTrue:
  					[(String streamContents:
  							[:s|
  							s position > 0 ifTrue: [s tab: level + 1].
  							node emitCCodeAsArgumentOn: s level: level generator: self])
  						copyReplaceAll: (String with: Character cr)
  						with: (String with: Character cr), (String new: level + 1 withAll: Character tab)]
  				ifFalse: [expansion])]]
  		ifFalse:
  			[[:node| | expansion |
  			  expansion := String streamContents: [:s| node emitCCodeOn: s level: level generator: self].
  			 "Remove tabs from first line to avoid indenting a second time"
  			 expansion ifNotEmpty:
  				[expansion := expansion allButFirst: (expansion findFirst: [:c| c ~~ Character tab]) - 1].
  			 aStream nextPutAll: expansion]].
  
+ 	(self nilOrBooleanConditionFor: msgNode args first) ifNotNil:
- 	(self nilOrBooleanConditionFor: msgNode) ifNotNil:
  		[:condition|
  		 condition
  			ifTrue:
  				[putStatement value: msgNode args second]
  			ifFalse:
  				[msgNode args size >= 3 ifTrue:
  					[putStatement value: msgNode args third]].
  		 ^self].
  
  	"Full #if ... #else..."
  	putStatement := asArgument
  		ifTrue: "emitCCodeAsArgumentOn: doesn't indent, the code needs indenting in this case, so post-process."
  			[[:node|
  			  aStream nextPutAll:
  				((String streamContents:
  						[:s|
  						s next: level + 1 put: Character tab.
  						node emitCCodeAsArgumentOn: s level: level generator: self])
  					copyReplaceAll: (String with: Character cr)
  					with: (String with: Character cr), (String new: level + 1 withAll: Character tab))]]
  		ifFalse:
  			[[:node| node emitCCodeOn: aStream level: level generator: self]].
  
  	expr := String streamContents:
  				[:es|
  				msgNode args first
  					emitCCodeAsArgumentOn: es
  					level: 0
  					generator: self].
  	[expr last isSeparator] whileTrue:
  		[expr := expr allButLast].
  	aStream
  		ensureCr;
  		nextPut: $#; next: level * 2 put: Character space; nextPutAll: 'if '; nextPutAll: expr; cr.
  
  	self with: msgNode args first
  		ifAppropriateSetTo: true
  		do: [putStatement value: msgNode args second].
  	expr := ' /* ', expr, ' */'.
  	msgNode args size >= 3 ifTrue:
  		[aStream
  			ensureCr;
  			nextPut: $#; next: level * 2 put: Character space; nextPutAll: 'else'; nextPutAll: expr;
  			cr.
  		self with: msgNode args first
  			ifAppropriateSetTo: false
  			do: [putStatement value: msgNode args third]].
  	aStream
  		ensureCr;
  		nextPut: $#; next: level * 2 put: Character space; nextPutAll: 'endif'; nextPutAll: expr;
  		cr.
  	asArgument ifTrue:
  		[aStream next: level + 1 put: Character tab]!

Item was changed:
  ----- Method: CCodeGenerator>>nilOrBooleanConstantReceiverOf: (in category 'utilities') -----
  nilOrBooleanConstantReceiverOf: aNode
  	"Answer nil or the boolean constant that is the receiver of the given message send.
  	 Used to suppress conditional code when the condition is a translation-time constant."
  
  	| val receiver argument arms |
  	generateDeadCode ifTrue:[^nil].
  	((self isConstantNode: aNode valueInto: [:v| val := v])
  	 and: [#(true false) includes: val]) ifTrue:
  		[^val].
  	aNode isSend ifTrue:
  		[aNode selector == #not ifTrue:
  			[(self nilOrBooleanConstantReceiverOf: aNode receiver) ifNotNil:
  				[:bool| ^bool not]].
  		 ((#(isNil notNil) includes: aNode selector)
  		  and: [self isNilConstantReceiverOf: aNode]) ifTrue:
  			[^aNode selector == #isNil].
  		 ((#(or: and:) includes: aNode selector)
  		 and: [aNode args last isStmtList
  		 and: [aNode args last statements size = 1]]) ifTrue:
  			[(self nilOrBooleanConstantReceiverOf: aNode receiver) ifNotNil:
  				[:rcvr|
  				((rcvr == false and: [aNode selector == #and:])
  				 or: [rcvr == true and: [aNode selector == #or:]]) ifTrue:
  					[^rcvr].
  				(self nilOrBooleanConstantReceiverOf: aNode args last statements first) ifNotNil:
  					[:arg|
  					^rcvr perform: aNode selector with: [arg]]].
+ 			 "We can also eliminate expr and: [false], expr or: [true], but only if expr is side-effect free.
- 			 "We can also eliminate expr and: [false], but only if expr is side-effect free.
  			  This is a weak test; we don't traverse calls.  Caveat emptor!!"
+ 			 ((aNode receiver noneSatisfy: [:node| node isAssignment]) "No side-effects in the elided expression"
+ 			  and: [aNode args last statements size = 1]) ifTrue:
- 			 (aNode selector == #and:
- 			  and: [(aNode receiver noneSatisfy: [:node| node isAssignment]) "No side-effects in the elided expression"
- 			  and: [aNode args last statements size = 1]]) ifTrue:
  				[(self nilOrBooleanConstantReceiverOf: aNode args last statements first) ifNotNil:
  					[:arg|
+ 					((arg == false and: [aNode selector == #and:])
+ 					 or: [arg == true and: [aNode selector == #or:]]) ifTrue:
- 					arg ifFalse:
  						[^arg]]]].
  		"Look for Const ifTrue: [self foo] ifFalse: [false] => false"
  		 ((#(ifTrue:ifFalse: ifFalse:ifTrue:) includes: aNode selector)
  		  and: [(self isConstantNode: aNode receiver valueInto: [:v| val := v])
  		  and: [(#(true false) includes: val)
  		  and: [arms := aNode args collect:
  							[:altBlock| | bval |
  							 (altBlock statements size = 1
  							 and: [(self isConstantNode: altBlock statements last valueInto: [:v| bval := v])
  							 and: [#(true false) includes: bval]]) ifTrue:
  								[bval]].
  				arms asArray ~= #(nil nil)]]]) ifTrue:
  			[| arm |
  			 arm := aNode selector == #ifTrue:ifFalse: == val
  						ifTrue: [arms first]
  						ifFalse: [arms last].
  			 (#(true false) includes: arm) ifTrue:
  				[^arm]].
  		 ((#(= ~= < > <= >=) includes: aNode selector)
  		  and: [(self isConstantNode: aNode receiver valueInto: [:v| receiver := v])
  		  and: [receiver isInteger
  		  and: [(self isConstantNode: aNode args first valueInto: [:v| argument := v])
  		  and: [argument isInteger]]]]) ifTrue:
  			[^receiver perform: aNode selector with: argument].
  		 "Inlining for e.g. CharacterTable ifNil: [...] ifNotNil: [...]], which compiles to CharacterTable == nil ifTrue: [...] ifFalse: [...]"
  		(aNode selector == #==
  		 and: [aNode args first isVariable
  		 and: [aNode args first name = 'nil'
  		 and: [aNode receiver isConstant
  		 and: [aNode receiver value == nil]]]]) ifTrue:
  			[^true]].
  	^nil!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>instantiateClass:indexableSize: (in category 'instantiation') -----
  instantiateClass: classObj indexableSize: nElements
  	<api>
  	<var: #nElements type: #usqInt>
  	"Allocate an instance of a variable class, excepting CompiledMethod."
  	| instSpec classFormat numSlots classIndex newObj fillValue |
  	classFormat := self formatOfClass: classObj.
  	instSpec := self instSpecOfClassFormat: classFormat.
  	classIndex := self rawHashBitsOf: classObj.
  	fillValue := 0.
  	instSpec caseOf: {
  		[self arrayFormat]	->
  			[numSlots := nElements.
  			 fillValue := nilObj].
  		[self indexablePointersFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self weakArrayFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self sixtyFourBitIndexableFormat]	->
  			[nElements > (self maxSlotsForAlloc / 2) ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrUnsupported.
  				 ^nil].
  			 numSlots := nElements * 2].
  		[self firstLongFormat]	->
  			[(classIndex = ClassFloatCompactIndex and: [nElements ~= 2]) ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrBadReceiver.
  				 ^nil].
  			 numSlots := nElements].
  		[self firstShortFormat]	->
  			[numSlots := nElements + 1 // 2.
  			 instSpec := instSpec + (nElements bitAnd: 1)].
  		[self firstByteFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (4 - nElements bitAnd: 3)] }
+ 		otherwise: "non-indexable"
+ 			[self cppIf: (PharoVM or: [true]) "Leave the old code but ignore it completely unless someone complains."
+ 				ifTrue:
+ 					[^nil]
+ 				ifFalse:
+ 					["some Squeak images include funky fixed subclasses of abstract variable
+ 					  superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
+ 					  Allow fixed classes to be instantiated here iff nElements = 0."
- 		otherwise: ["some Squeak images include funky fixed subclasses of abstract variable
- 					 superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
- 					 Allow fixed classes to be instantiated here iff nElements = 0."
  					 (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:
  						[^nil].
+ 					 numSlots := self fixedFieldsOfClassFormat: classFormat.
+ 					 fillValue := nilObj]].
- 					 numSlots := self fixedFieldsOfClassFormat: classFormat]. "non-indexable"
  	classIndex = 0 ifTrue:
  		[classIndex := self ensureBehaviorHash: classObj.
  		 classIndex < 0 ifTrue:
  			[coInterpreter primitiveFailFor: classIndex negated.
  			 ^nil]].
  	numSlots > self maxSlotsForNewSpaceAlloc
  		ifTrue:
  			[numSlots > self maxSlotsForAlloc ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrUnsupported.
  				 ^nil].
  			 newObj := self allocateSlotsInOldSpace: numSlots format: instSpec classIndex: classIndex]
  		ifFalse:
  			[newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex].
  	newObj ifNotNil:
  		[self fillObj: newObj numSlots: numSlots with: fillValue].
  	^newObj!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>instantiateClass:indexableSize: (in category 'instantiation') -----
  instantiateClass: classObj indexableSize: nElements
  	<api>
  	<var: #nElements type: #usqInt>
  	"Allocate an instance of a variable class, excepting CompiledMethod."
  	| instSpec classFormat numSlots classIndex newObj fillValue |
  	classFormat := self formatOfClass: classObj.
  	instSpec := self instSpecOfClassFormat: classFormat.
  	classIndex := self rawHashBitsOf: classObj.
  	fillValue := 0.
  	instSpec caseOf: {
  		[self arrayFormat]	->
  			[numSlots := nElements.
  			 fillValue := nilObj].
  		[self indexablePointersFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self weakArrayFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self sixtyFourBitIndexableFormat]	->
  			[numSlots := nElements].
  		[self firstLongFormat]	->
  			[(classIndex = ClassFloatCompactIndex and: [nElements ~= 2]) ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrBadReceiver.
  				 ^nil].
  			 numSlots := nElements + 1 // 2.
  			 instSpec := instSpec + (nElements bitAnd: 1)].
  		[self firstShortFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (4 - nElements bitAnd: 3)].
  		[self firstByteFormat]	->
  			[numSlots := nElements + 7 // 8.
  			 instSpec := instSpec + (8 - nElements bitAnd: 7)] }
+ 		otherwise: "non-indexable"
+ 			[self cppIf: (PharoVM or: [true]) "Leave the old code but ignore it completely unless someone complains."
+ 				ifTrue:
+ 					[^nil]
+ 				ifFalse:
+ 					["some Squeak images include funky fixed subclasses of abstract variable
+ 					  superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
+ 					  Allow fixed classes to be instantiated here iff nElements = 0."
- 		otherwise: ["some Squeak images include funky fixed subclasses of abstract variable
- 					 superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
- 					 Allow fixed classes to be instantiated here iff nElements = 0."
  					 (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:
  						[^nil].
+ 					 numSlots := self fixedFieldsOfClassFormat: classFormat.
+ 					 fillValue := nilObj]].
- 					 numSlots := self fixedFieldsOfClassFormat: classFormat]. "non-indexable"
  	classIndex = 0 ifTrue:
  		[classIndex := self ensureBehaviorHash: classObj.
  		 classIndex < 0 ifTrue:
  			[coInterpreter primitiveFailFor: classIndex negated.
  			 ^nil]].
  	numSlots > self maxSlotsForNewSpaceAlloc
  		ifTrue:
  			[numSlots > self maxSlotsForAlloc ifTrue:
  				[coInterpreter primitiveFailFor: PrimErrUnsupported.
  				 ^nil].
  			 newObj := self allocateSlotsInOldSpace: numSlots format: instSpec classIndex: classIndex]
  		ifFalse:
  			[newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex].
  	newObj ifNotNil:
  		[self fillObj: newObj numSlots: numSlots with: fillValue].
  	^newObj!



More information about the Vm-dev mailing list