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

commits at source.squeak.org commits at source.squeak.org
Tue Sep 17 23:57:50 UTC 2013


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

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

Name: VMMaker.oscog-eem.388
Author: eem
Time: 17 September 2013, 4:54:38.785 pm
UUID: 92fbeee7-a269-41b1-bb01-9a970c4a50fa
Ancestors: VMMaker.oscog-eem.387

Move the zeroing of stackPage to zeroStackPage to provide a
debugging hook.

Fix Spur??BitMemoryManager>>instantiateClass:indexableSize: for
missing weakArrayFormat.

Fix shortPrint: for immediate characters.

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

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveVoidVMStateForMethod (in category 'system control primitives') -----
  primitiveVoidVMStateForMethod
  	"The receiver is a compiledMethod.  Clear all VM state associated with the method,
  	 including any machine code, or machine code pcs in context objects."
  	<var: #theFrame type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	super primitiveFlushCacheByMethod.
  	(self methodHasCogMethod: self stackTop) ifTrue:
  		[| activeContext methodObj theFrame thePage |
  		methodObj := self stackTop.
  		self push: instructionPointer.
  		self externalWriteBackHeadFramePointers.
  		activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  		self divorceMachineCodeFramesWithMethod: methodObj.
  		self ensureAllContextsWithMethodHaveBytecodePCs: methodObj.
  		cogit unlinkSendsTo: methodObj andFreeIf: true.
  		(self isStillMarriedContext: activeContext)
  			ifTrue:
  				[theFrame := self frameOfMarriedContext: activeContext.
  				 thePage := stackPages stackPageFor: theFrame.
  				 self assert: thePage headFP = theFrame.
  				 self setStackPageAndLimit: thePage.
  				 stackPointer := thePage headSP.
  				 framePointer := thePage headFP.
  				 instructionPointer := self popStack.
  				 self assert: methodObj = self stackTop]
  			ifFalse:
+ 				[self zeroStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
- 				[stackPage := 0. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
  				 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  				 self popStack. "pop bogus machine-code instructionPointer"
  				 self assert: methodObj = self stackTop.
  				 self siglong: reenterInterpreter jmp: ReturnToInterpreter]]
  !

Item was changed:
  ----- Method: Spur32BitMemoryManager>>instantiateClass:indexableSize: (in category 'allocation') -----
  instantiateClass: classObj indexableSize: nElements
  	| instSpec classFormat numSlots classIndex newObj fillValue |
  	classFormat := self formatOfClass: classObj.
  	instSpec := self instSpecOfClassFormat: classFormat.
  	fillValue := 0.
  	instSpec caseOf: {
  		[self arrayFormat]	->
  			[numSlots := nElements.
  			 fillValue := nilObj].
  		[self indexablePointersFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
+ 		[self weakArrayFormat]	->
+ 			[numSlots := nElements.
+ 			 fillValue := nilObj].
  		[self sixtyFourBitIndexableFormat]	->
  			[numSlots := nElements * 2].
  		[self firstLongFormat]	->
  			[numSlots := nElements].
  		[self firstShortFormat]	->
  			[numSlots := nElements + 1 // 2.
  			 instSpec := instSpec + (nElements bitAnd: 1)].
  		[self firstByteFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (nElements bitAnd: 3)].
  		[self firstCompiledMethodFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (nElements bitAnd: 3)] }
  		otherwise: [^nil]. "non-indexable"
  	classIndex := self ensureBehaviorHash: classObj.
  	classIndex < 0 ifTrue:
  		[coInterpreter primitiveFailFor: classIndex negated.
  		 ^nil].
  	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 'allocation') -----
  instantiateClass: classObj indexableSize: nElements
  	| instSpec classFormat numSlots classIndex newObj fillValue |
  	classFormat := self formatOfClass: classObj.
  	instSpec := self instSpecOfClassFormat: classFormat.
  	fillValue := 0.
  	instSpec caseOf: {
  		[self arrayFormat]	->
  			[numSlots := nElements.
  			 fillValue := nilObj].
  		[self indexablePointersFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
+ 		[self weakArrayFormat]	->
+ 			[numSlots := nElements.
+ 			 fillValue := nilObj].
  		[self sixtyFourBitIndexableFormat]	->
  			[numSlots := nElements].
  		[self firstLongFormat]	->
  			[numSlots := nElements + 1 // 2.
  			 instSpec := instSpec + (nElements bitAnd: 1)].
  		[self firstShortFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (nElements bitAnd: 3)].
  		[self firstByteFormat]	->
  			[numSlots := nElements + 7 // 8.
  			 instSpec := instSpec + (nElements bitAnd: 7)].
  		[self firstCompiledMethodFormat]	->
  			[numSlots := nElements + 7 // 8.
  			 instSpec := instSpec + (nElements bitAnd: 7)] }
  		otherwise: [^nil]. "non-indexable"
  	classIndex := self ensureBehaviorHash: classObj.
  	classIndex < 0 ifTrue:
  		[coInterpreter primitiveFailFor: classIndex negated.
  		 ^nil].
  	newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex.
  	newObj ifNotNil:
  		[self fillObj: newObj numSlots: numSlots with: fillValue].
  	^newObj!

Item was changed:
  ----- Method: StackInterpreter>>divorceAllFrames (in category 'frame access') -----
  divorceAllFrames
  	| activeContext |
  	<inline: false>
  	<var: #aPage type: #'StackPage *'>
  	self externalWriteBackHeadFramePointers.
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	0 to: numStackPages - 1 do:
  		[:i| | aPage |
  		aPage := stackPages stackPageAt: i.
  		(stackPages isFree: aPage) ifFalse:
  			[self divorceFramesIn: aPage]].
+ 	self zeroStackPage.
- 	stackPage := 0.
  	^activeContext!

Item was changed:
  ----- Method: StackInterpreter>>printActivationNameFor:receiver:isBlock:firstTemporary: (in category 'debug printing') -----
  printActivationNameFor: aMethod receiver: anObject isBlock: isBlock firstTemporary: maybeMessage
  	| methClass methodSel classObj |
  	<inline: false>
  	isBlock ifTrue:
  		[self print: '[] in '].
  	methClass := self findClassOfMethod: aMethod forReceiver: anObject.
  	methodSel := self findSelectorOfMethod: aMethod.
  	((objectMemory addressCouldBeOop: anObject)
+ 	 and: [(objectMemory isOopForwarded: anObject) not
- 	 and: [(objectMemory isForwarded: anObject) not
  	 and: [self addressCouldBeClassObj: (classObj := objectMemory fetchClassOf: anObject)]])
  		ifTrue:
  			[classObj = methClass
  				ifTrue: [self printNameOfClass: methClass count: 5]
  				ifFalse:
  					[self printNameOfClass: classObj count: 5.
  					 self print: '('.
  					 self printNameOfClass: methClass count: 5.
  					 self print: ')']]
  		ifFalse:
  			[self cCode: '' inSmalltalk: [self halt].
  			 self print: 'INVALID RECEIVER'].
  	self print: '>'.
  	(objectMemory addressCouldBeOop: methodSel)
  		ifTrue:
  			[methodSel = objectMemory nilObject
  				ifTrue: [self print: '?']
  				ifFalse: [self printStringOf: methodSel]]
  		ifFalse: [self print: 'INVALID SELECTOR'].
  	(methodSel = (objectMemory splObj: SelectorDoesNotUnderstand)
  	and: [(objectMemory addressCouldBeObj: maybeMessage)
  	and: [(objectMemory fetchClassOf: maybeMessage) = (objectMemory splObj: ClassMessage)]]) ifTrue:
  		["print arg message selector"
  		methodSel := objectMemory fetchPointer: MessageSelectorIndex ofObject: maybeMessage.
  		self print: ' '.
  		self printStringOf: methodSel]!

Item was changed:
  ----- Method: StackInterpreter>>setStackPageAndLimit: (in category 'stack pages') -----
  setStackPageAndLimit: thePage
  	"Set stackPage to a different page.  Set stackLimit unless it has
  	 been smashed.  Make the stackPage the most recently used"
  	<inline: true>
  	<asmLabel: false>
  	<var: #thePage type: #'StackPage *'>
+ 	self assert: thePage ~= 0.
  	stackPage := thePage.
  	stackLimit ~= (self cCoerceSimple: -1 signedIntToLong to: #'char *') ifTrue:
  		[stackLimit := stackPage stackLimit].
  	stackPages markStackPageMostRecentlyUsed: thePage!

Item was added:
+ ----- Method: StackInterpreter>>zeroStackPage (in category 'stack pages') -----
+ zeroStackPage
+ 	"In its own method as a debugging hook."
+ 	<inline: true>
+ 	stackPage := 0!

Item was changed:
  ----- Method: StackInterpreterSimulator>>shortPrint: (in category 'debug support') -----
  shortPrint: oop
  	| name classOop |
  	(objectMemory isImmediate: oop) ifTrue:
+ 		[(objectMemory isImmediateCharacter: oop) ifTrue:
+ 			[^ '=$' , (objectMemory characterValueOf: oop) printString , 
+ 			' (' , (String with: (Character value: (objectMemory characterValueOf: oop))) , ')'].
+ 		(objectMemory isIntegerObject: oop) ifTrue:
+ 			[^ '=' , (objectMemory integerValueOf: oop) printString , 
- 		[(objectMemory isImmediateCharacter: oop) ifTrue: [^ '=$' , (objectMemory integerValueOf: oop) printString , 
- 			' (' , (String with: (Character value: (objectMemory integerValueOf: oop))) , ')'].
- 		(objectMemory isIntegerObject: oop) ifTrue: [^ '=' , (objectMemory integerValueOf: oop) printString , 
  			' (' , (objectMemory integerValueOf: oop) hex , ')'].
  		^'= UNKNOWN IMMEDIATE', ' (' , (objectMemory integerValueOf: oop) hex , ')'].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[^(oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  			ifTrue: [' is misaligned']
  			ifFalse: [' is not on the heap']].
  	(objectMemory isFreeObject: oop) ifTrue:
  		[^' is a free chunk of size ', (objectMemory sizeOfFree: oop) printString].
  	(objectMemory isForwarded: oop) ifTrue:
  		[^' is a forwarded object to ', (objectMemory followForwarded: oop) hex,
  			' of slot size ', (objectMemory numSlotsOfAny: oop) printString].
  	classOop := objectMemory fetchClassOfNonImm: oop.
  	(objectMemory sizeBitsOf: classOop) = metaclassSizeBits ifTrue:
  		[^'class ' , (self nameOfClass: oop)].
  	name := self nameOfClass: classOop.
  	name size = 0 ifTrue: [name := '??'].
  	name = 'String' ifTrue: [^ (self stringOf: oop) printString].
  	name = 'ByteString' ifTrue: [^ (self stringOf: oop) printString].
  	name = 'Symbol' ifTrue: [^ '#' , (self stringOf: oop)].
  	name = 'ByteSymbol' ifTrue: [^ '#' , (self stringOf: oop)].
  	name = 'Character' ifTrue: "SpurMemoryManager has immediate Characters; ObjectMemory does not"
  		[^ '=' , (Character value: (objectMemory integerValueOf: 
  				(objectMemory fetchPointer: 0 ofObject: oop))) printString].
  	name = 'UndefinedObject' ifTrue: [^ 'nil'].
  	name = 'False' ifTrue: [^ 'false'].
  	name = 'True' ifTrue: [^ 'true'].
  	name = 'Float' ifTrue: [^ '=' , (self dbgFloatValueOf: oop) printString].
  	name = 'Association' ifTrue: [^ '(' ,
  				(self shortPrint: (self longAt: oop + BaseHeaderSize)) ,
  				' -> ' ,
  				(self longAt: oop + BaseHeaderSize + BytesPerWord) hex8 , ')'].
  	('AEIOU' includes: name first)
  		ifTrue: [^ 'an ' , name]
  		ifFalse: [^ 'a ' , name]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>stackPage (in category 'spur bootstrap') -----
+ stackPage
+ 	^stackPage!



More information about the Vm-dev mailing list