[Vm-dev] VM Maker: Cog-eem.85.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Sep 14 01:02:14 UTC 2013


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

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

Name: Cog-eem.85
Author: eem
Time: 13 September 2013, 6:01:48.2 pm
UUID: 0eff864f-7f98-4184-8cdb-75b5a35a46cb
Ancestors: Cog-eem.84

Fix validation for the new value of tyhe forwarded object class index.

Make sure nil is hashed (for the class table scan).

Comment typo.

Bootstrap now proceeds through many rehashes, crashing at bytecode 3976273.

Needs VMMaker.oscog-eem.378.

=============== Diff against Cog-eem.84 ===============

Item was changed:
  ----- Method: SpurBootstrap>>defineKnownClassIndices (in category 'class indices') -----
  defineKnownClassIndices
  	"The classTable is laid out
  		- to make it easy to map immediates to classes; the tag pattern of an immediate is its class index.
  		  hence there are two entries for SmallInteger
  		- to assign small indices to well-known classes such as Array, Message et al
  		- to leave plenty of room for new known classes; hence the first page contains only well-known classes
  		- to enable overlaps and avoid conflicts with indices in the specialObjectsArray (?really? eem)
  		- to provide a WeakArray pun for the pages of the table itself so that these do not show up as instances of WeakArray"
  	| classMethodContext classBlockClosure classMessage "no api method for these" |
  	classMessage := oldHeap splObj: (VMObjectIndices bindingOf: #ClassMessage) value.
  	classMethodContext := oldHeap splObj: (VMObjectIndices bindingOf: #ClassMethodContext) value.
  	classBlockClosure := oldHeap splObj: (VMObjectIndices bindingOf: #ClassBlockClosure) value.
+ 	"c.f. SpurMemoryManager class>>intializeCompactClassIndices".
- 	"c.f. CogMemoryManager class>>intializeCompactClassIndices".
  	classToIndex keysDo:
  		[:oldClass|
  		self assert: (oldInterpreter addressCouldBeClassObj: oldClass)].
  	classToIndex
  		at: oldHeap classSmallInteger put: 1; "N.B. must fill-in index 3 manually"
  		at: oldHeap classCharacter put: 2;
  		"at: oldHeap classSmallInteger put: 3" "N.B. must fill-in index 3 manually"
  		"leave room for up to 15 tagged classes"
  		"leave room for up to 16 puns"
  		at: oldHeap classLargeNegativeInteger put: 32;
  		at: oldHeap classLargePositiveInteger put: 33;
  		at: oldHeap classFloat put: 34;
  
  		at: "oldHeap" classMessage put: 35;
  		at: "oldHeap" classMethodContext put: 36;
  		at: "oldHeap" classBlockClosure put: 37;
  
  		at: oldHeap classSemaphore put: 48;
  		at: oldHeap classMutex put: 49;
  
  		at: oldHeap classByteArray put: 50;
  		at: oldHeap classArray put: 51;
  		at: oldHeap classString put: 52;
  		at: oldHeap classBitmap put: 53;
  		at: oldHeap classPoint put: 54;
  
  		at: oldHeap classExternalAddress put: 128;
  		at: oldHeap classExternalData put: 129;
  		at: oldHeap classExternalFunction put: 130;
  		at: oldHeap classExternalLibrary put: 131;
  		at: oldHeap classExternalStructure put: 132;
  		at: oldHeap classAlien put: 133;
  		at: oldHeap classUnsafeAlien put: 134.
  	classToIndex keysDo:
  		[:oldClass|
  		self assert: (oldInterpreter addressCouldBeClassObj: oldClass)]!

Item was changed:
  ----- Method: SpurBootstrap>>interpreter:object:perform:withArguments: (in category 'bootstrap methods') -----
  interpreter: sim object: receiver perform: selector withArguments: arguments
  	"Interpret an expression in oldHeap using oldInterpreter.
  	 Answer the result."
  	| fp savedpc result |
  	savedpc := sim localIP.
  	sim internalPush: receiver.
  	arguments do: [:arg| sim internalPush: arg].
  	sim
  		argumentCount: arguments size;
  		messageSelector: selector.
  	fp := sim localFP.
  	sim normalSend.
  	[fp = sim localFP] whileFalse:
+ 		[sim byteCount = 3976273 ifTrue: [self halt].
+ 		 sim singleStep].
- 		[sim singleStep].
  	result := sim internalPopStack.
  	self assert: sim localIP - 1 = savedpc.
  	sim localIP: savedpc.
  	^result!

Item was changed:
  ----- Method: SpurBootstrap>>rehashImage (in category 'bootstrap image') -----
  rehashImage
  	"Rehash all collections in newHeap.
  	 Find out which classes implement rehash, entering a 1 against their classIndex in rehashFlags.
  	 Enumerate all objects, rehashing those whose class has a bit set in rehashFlags."
  	| n sim rehashFlags |
  	sim := StackInterpreterSimulator onObjectMemory: newHeap.
  	newHeap coInterpreter: sim.
  	sim initializeInterpreter: 0.
  	sim instVarNamed: 'methodDictLinearSearchLimit' put: SmallInteger maxVal.
+ 
+ 	newHeap
+ 		setHashBitsOf: newHeap nilObject to: 1;
+ 		setHashBitsOf: newHeap falseObject to: 2;
+ 		setHashBitsOf: newHeap trueObject to: 3.
+ 
  	rehashFlags := ByteArray new: newHeap classTableIndex + 7 // 8.
  	n := 0.
  	newHeap classTableObjectsDo:
  		[:class| | classIndex |
  		sim messageSelector: (map at: rehashSym).
  		"Lookup rehash but don't be fooled by ProtoObject>>rehash, which is just ^self."
  		((sim lookupMethodNoMNUEtcInClass: class) = 0
  		 and: [(sim isQuickPrimitiveIndex: (sim primitiveIndexOf: (sim instVarNamed: 'newMethod'))) not]) ifTrue:
  			[n := n + 1.
  			 classIndex := newHeap rawHashBitsOf: class.
  			 rehashFlags
  				at: classIndex >> 3 + 1
  				put: ((rehashFlags at: classIndex >> 3 + 1)
  						bitOr: (1 << (classIndex bitAnd: 7)))]].
  	Transcript cr; print: n; nextPutAll: ' classes understand rehash. rehashing instances...'; flush.
  	self withExecutableInterpreter: sim
+ 		do: "don't rehash twice (actually without limit), so don't rehash any new objects created."
+ 			[newHeap allExistingObjectsDo:
- 		do: [newHeap allObjectsDo:
  				[:o| | classIndex |
  				classIndex := newHeap classIndexOf: o.
  				((rehashFlags at: classIndex >> 3 + 1) anyMask: 1 << (classIndex bitAnd: 7)) ifTrue:
  					[Transcript nextPut: $.; flush.
  					 self interpreter: sim
  						object: o
  						perform: (map at: rehashSym)
  						withArguments: #()]]]!

Item was changed:
  ----- Method: SpurBootstrap>>transform (in category 'bootstrap image') -----
  transform
  	self rememberRehashSymbol.
  	self installModifiedMethods.
  	self bootstrapImage.
  	self validate.
  	self rehashImage.
+ 	self followForwardingPointers.
  	Transcript nextPutAll: 'done.'; flush.!

Item was changed:
  ----- Method: SpurBootstrap>>validate (in category 'bootstrap image') -----
  validate
  	| p n duplicates maxClassIndex |
  	self assert: (reverseMap at: newHeap specialObjectsOop) = oldHeap specialObjectsOop.
  	self assert: (map at: oldHeap specialObjectsOop) = newHeap specialObjectsOop.
  	self assert: (reverseMap at: newHeap classTableRootObj ifAbsent: []) isNil.
  
  	duplicates := { 3. newHeap arrayClassIndexPun. newHeap weakArrayClassIndexPun }.
  	maxClassIndex := classToIndex inject: 0 into: [:a :b| a max: b].
+ 	self assert: ((newHeap arrayClassIndexPun to: maxClassIndex) select:
- 	self assert: ((0 to: maxClassIndex) select:
  					[:idx| | classObj |
  					(classObj := newHeap classAtIndex: idx) ~= newHeap nilObject
  					and: [(newHeap classIndexOf: classObj) = (newHeap rawHashBitsOf: classObj)]]) isEmpty.
  	0 to: maxClassIndex do:
  		[:index| | classObj |
+ 		(index <= newHeap tagMask
+ 		 and: [index > newHeap isForwardedObjectClassIndexPun]) ifTrue:
+ 			[(classObj := newHeap classAtIndex: index) = newHeap nilObject
+ 				ifTrue:
+ 					[self assert: (classToIndex keyAtValue: index ifAbsent: []) isNil]
+ 				ifFalse:
+ 					[self assert: (newHeap classIndexOf: classObj) ~= (newHeap rawHashBitsOf: classObj).
+ 					(duplicates includes: index) ifFalse:
+ 						[self assert: (newHeap rawHashBitsOf: classObj) = index]]]].
- 		(classObj := newHeap classAtIndex: index) = newHeap nilObject
- 			ifTrue:
- 				[self assert: (classToIndex keyAtValue: index ifAbsent: []) isNil]
- 			ifFalse:
- 				[self assert: (newHeap classIndexOf: classObj) ~= (newHeap rawHashBitsOf: classObj).
- 				(duplicates includes: index) ifFalse:
- 					[self assert: (newHeap rawHashBitsOf: classObj) = index]]].
  	classToIndex keysAndValuesDo:
  		[:oldClass :idx|
  		self assert: (newHeap rawHashBitsOf: (map at: oldClass)) = idx. 
  		self assert: oldClass = (reverseMap at: (newHeap classAtIndex: idx))].
  	n := 0.
  	newHeap allObjectsDo:
  		[:o|
  		(o <= newHeap trueObject
  		 or: [o > lastClassTablePage]) ifTrue:
  			[self assert: (reverseMap includesKey: o).
  			 self assert: (newHeap fetchClassOfNonImm: o) = (map at: (oldHeap fetchClassOfNonImm: (reverseMap at: o)))].
  		n := n + 1.
  		p := o].
  	p class.
  	self assert: (n between: map size and: map size + 5) "+ 5 is room for classTable"!



More information about the Vm-dev mailing list