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

commits at source.squeak.org commits at source.squeak.org
Wed Sep 11 14:48:23 UTC 2013


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

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

Name: Cog-eem.84
Author: eem
Time: 11 September 2013, 7:47:56.564 am
UUID: e3e8417e-67c7-40da-bec6-f6d9cf6e6bbb
Ancestors: Cog-eem.83

Spur: Rehash hash tables in the new image.  Breaks the bootstrap
because SpurMemoryManager doesn't yet implement become:.

Refactor interpreterObject:perform:withArguments: and
withExecutableInterpreterDo: to take the interpreter as an
argument so newHeap can be operated upon.

Assign newHeap's classTableIndex.

Assumes VMMaker.oscog-eem.370 or later.

=============== Diff against Cog-eem.83 ===============

Item was changed:
  Object subclass: #SpurBootstrap
+ 	instanceVariableNames: 'oldHeap newHeap map reverseMap classToIndex oldInterpreter lastClassTablePage symbolMap methodClasses installedPrototypes rehashSym'
- 	instanceVariableNames: 'oldHeap newHeap map reverseMap classToIndex oldInterpreter lastClassTablePage symbolMap methodClasses installedPrototypes'
  	classVariableNames: 'TransformedImage'
  	poolDictionaries: 'VMObjectIndices'
  	category: 'Cog-Bootstrapping'!
  
+ !SpurBootstrap commentStamp: 'eem 9/11/2013 05:45' prior: 0!
- !SpurBootstrap commentStamp: 'eem 9/7/2013 13:23' prior: 0!
  SpurBootstrap bootstraps an image in SpurMemoryManager format from a Squeak V3 + closures format.
  
  e.g.
  	(SpurBootstrap32 new on: '/Users/eliot/Cog/startreader.image')
  		transform;
  		launch
  
+ Bootstrap issues:
+ - should it implement a deterministic Symbol identityHash? This means set a Symbol's identityHash at instance creation time
+   based on its string hash so that e.g. MethodDIctionary instances have a deterministic order and don't need to be rehashed on load.
+ - should it collapse ContextPart and MethodContext down onto Context (and perhaps eliminate BlockContext)?
+ 
  Instance Variables
  	classToIndex:			<Dictionary>
  	lastClassTablePage:	<Integer>
  	map:					<Dictionary>
  	methodClasses:		<Set>
  	newHeap:				<SpurMemoryManager>
  	oldHeap:				<NewObjectMemory>
  	oldInterpreter:			<StackInterpreterSimulator>
  	reverseMap:			<Dictionary>
  	symbolMap:				<Dictionary>
  
  classToIndex
  	- oldClass to new classIndex map
  
  lastClassTablePage
  	- oop in newHeap of last classTable page.  U<sed in validation to filter-out class table.
  
  methodClasses
  	- cache of methodClassAssociations for classes in which modified methods are installed
  
  map
  	- oldObject to newObject map
  
  newHeap
  	- the output, bootstrapped image
  
  oldHeap
  	- the input, image
  
  oldInterpreter
  	- the interpreter associated with oldHeap, needed for a hack to grab WeakArray
  
  reverseMap
  	- newObject to oldObject map
  
  symbolMap
  	- symbol toi symbol oop in oldHeap, used to map prototype methdos to methods in oldHeap!

Item was added:
+ ----- Method: SpurBootstrap class>>CharacterPROTOTYPEidentityHash (in category 'method prototypes') -----
+ CharacterPROTOTYPEidentityHash
+ 	<primitive: 171>
+ 	^self primitiveFailed!

Item was changed:
  ----- Method: SpurBootstrap>>addNewMethods (in category 'bootstrap methods') -----
  addNewMethods
  	"Get the simulator to add any and all missing methods immediately."
  	| cmaiaSym basSym |
  	cmaiaSym := self findSymbol: #compiledMethodAt:ifAbsent:.
  	basSym := self findSymbol: #basicAddSelector:withMethod:.
  	basSym ifNil:
  		[basSym := self findSymbol: #addSelectorSilently:withMethod:].
  	self allPrototypeClassNamesDo:
  		[:sym :symIsMeta| | class |
  		class := self findClassNamed: (symbolMap at: sym).
  		symIsMeta ifTrue: [class := oldHeap fetchClassOfNonImm: class].
  		self prototypeClassNameMetaSelectorMethodDo:
  			[:className :isMeta :selector :method| | methodOrNil |
  			(className = sym
  			 and: [symIsMeta = isMeta]) ifTrue:
  				["probe method dictionary of the class for each method, installing a dummy if not found."
  				 "Transcript cr; nextPutAll: 'checking for '; nextPutAll: selector; flush."
+ 				 methodOrNil := self interpreter: oldInterpreter
+ 									object: class
- 				 methodOrNil := self interpreterObject: class
  									perform: cmaiaSym
  									withArguments: {symbolMap at: selector. oldHeap nilObject}.
  				 methodOrNil = oldHeap nilObject
  					ifTrue: "no method.  install the real thing now"
  						[Transcript
  							cr;
  							nextPutAll: 'installing ';
  							nextPutAll: className;
  							nextPutAll: (isMeta ifTrue: [' class>>'] ifFalse: ['>>']);
  							store: selector;
  							flush.
+ 						 self interpreter: oldInterpreter
+ 							object: class
- 						 self interpreterObject: class
  							perform: basSym
  							withArguments: { symbolMap at: selector.
  											   self installableMethodFor: method
  												selector: selector
  												className: className
  												isMeta: isMeta}.
  						installedPrototypes add: method selector]
  					ifFalse: "existing method; collect the methodClassAssociation; its needed later"
  						[methodClasses add: (oldInterpreter methodClassAssociationOf: methodOrNil)]]]]!

Item was changed:
  ----- Method: SpurBootstrap>>bootstrapImage (in category 'bootstrap image') -----
  bootstrapImage
  	Transcript cr; nextPutAll: 'transforming image...'; flush.
  	self cloneNilTrueAndFalse.
  	self buildClassMap.
  	self allocateClassTable.
  	self cloneObjects.
  	self fillInObjects.
  	self fillInClassTable.
+ 	newHeap initializePostBootstrap!
- 	Transcript nextPutAll: 'done.'; flush.!

Item was changed:
  ----- Method: SpurBootstrap>>cloneObjects (in category 'bootstrap image') -----
  cloneObjects
  	| characterClass characterTable compactClasses oldObj oldClass |
  	characterClass := oldHeap classCharacter.
  	characterTable := oldHeap characterTable.
  	compactClasses := oldHeap splObj: CompactClasses.
  	oldObj := oldHeap objectAfter: oldHeap trueObject.
  	[oldObj < oldHeap freeStart] whileTrue:
  		[oldClass := oldHeap fetchClassOfNonImm: oldObj.
  		 (oldObj ~= characterTable
  		 and: [oldObj ~= compactClasses
  		 and: [oldClass ~= characterClass]]) ifTrue:
  			[self clone: oldObj classIndex: (classToIndex at: oldClass)].
  		 oldObj := oldHeap objectAfter: oldObj].
+ 	newHeap
+ 		specialObjectsOop: (map at: oldHeap specialObjectsOop);
+ 		lastHash: oldHeap lastHash!
- 	newHeap specialObjectsOop: (map at: oldHeap specialObjectsOop)!

Item was changed:
  ----- Method: SpurBootstrap>>fillInClassTable (in category 'bootstrap image') -----
  fillInClassTable
+ 	| firstPage classWeakArray maxIndex |
+ 	maxIndex := 0.
- 	| firstPage classWeakArray |
  	classToIndex keysAndValuesDo:
  		[:oldClass :index| | newClass page |
+ 		maxIndex := maxIndex max: index.
  		newClass := map at: oldClass.
  		self assert: (newHeap isPointersNonImm: newClass).
  		newHeap setHashBitsOf: newClass to: index.
  		page := newHeap
  					fetchPointer: index >> newHeap classTableMajorIndexShift
  					ofObject: newHeap classTableRootObj.
  		newHeap
  			storePointer: (index bitAnd: newHeap classTableMinorIndexMask)
  			ofObject: page
  			withValue: newClass.
  		self assert: (newHeap classAtIndex: index) = newClass].
  	firstPage := newHeap
  					fetchPointer: 0
  					ofObject: newHeap classTableRootObj.
  	classWeakArray := classToIndex keys detect:
  							[:oldClass|
  							(oldHeap instSpecOfClass: oldClass) = 4
  							and: [oldInterpreter classNameOf: oldClass Is: 'WeakArray']].
  	newHeap
  		storePointer: 1
  			ofObject: firstPage
  				withValue: (map at: oldHeap classSmallInteger);
  		storePointer: 2
  			ofObject: firstPage
  				withValue: (map at: oldHeap classCharacter);
  		storePointer: 3
  			ofObject: firstPage
  				withValue: (map at: oldHeap classSmallInteger);
  		storePointer: newHeap arrayClassIndexPun
  			ofObject: firstPage
  				withValue: (map at: oldHeap classArray);
  		storePointer: newHeap weakArrayClassIndexPun
  			ofObject: firstPage
+ 				withValue: (map at: classWeakArray).
+ 
+ 	newHeap classTableIndex: maxIndex!
- 				withValue: (map at: classWeakArray)!

Item was changed:
  ----- Method: SpurBootstrap>>installModifiedMethods (in category 'bootstrap methods') -----
  installModifiedMethods
  	"Install all the methods in the class-side method prototypes protocol in the relevant classes
  	 in the new image.  First use the simulator to get the image to intern all symbols and add
  	 dummy methods under new selectors.  With that done we can manually replace the relevant
  	 methods with the prototypes, mapping selectors and global variables as required."
  	symbolMap := Dictionary new.
  	methodClasses := Set new.
  	installedPrototypes := Set new.
+ 	self withExecutableInterpreter: oldInterpreter
+ 		do: [self internAllSymbols.
+ 			 self addNewMethods.
+ 			 self replaceMethods].
- 	self withExecutableInterpreterDo:
- 		[self internAllSymbols.
- 		 self addNewMethods.
- 		 self replaceMethods].
  	self modifyCharacterMethods!

Item was changed:
  ----- Method: SpurBootstrap>>installableMethodFor:selector:className:isMeta: (in category 'bootstrap methods') -----
  installableMethodFor: aCompiledMethod selector: selector className: className isMeta: isMeta
  	| compiledMethodClass sourcelessMethod bytes newMethod methodClass |
  	compiledMethodClass := self findClassNamed: (self findSymbol: #CompiledMethod).
  	"the prototypes hve source pointers.  the Character methods to be replaced don't."
  	sourcelessMethod := aCompiledMethod trailer hasSourcePointer
  							ifTrue: [aCompiledMethod copyWithTempsFromMethodNode: aCompiledMethod methodNode]
  							ifFalse: [aCompiledMethod].
  	bytes := sourcelessMethod size - sourcelessMethod initialPC + 1.
  	newMethod := self
+ 					interpreter: oldInterpreter
+ 					object: compiledMethodClass
- 					interpreterObject: compiledMethodClass
  					perform: (self findSymbol: #newMethod:header:)
  					withArguments: { oldHeap integerObjectOf: bytes.
  									   oldHeap integerObjectOf: sourcelessMethod header }.
  	1 to: sourcelessMethod numLiterals - 1 do:
  		[:i| | literal oop |
  		literal := sourcelessMethod literalAt: i.
  		literal isMethodProperties ifTrue:
  			[literal := selector].
  		oop := (literal isLiteral or: [literal isVariableBinding])
  					ifTrue:
  						[literal isInteger
  							ifTrue: [oldHeap integerObjectOf: literal]
  							ifFalse: [symbolMap at: literal ifAbsent: [self findLiteral: literal]]]
  					ifFalse: "should be a VMObjectProxy"
  						[literal oop].
  		oldHeap storePointer: i ofObject: newMethod withValue: oop].
  	methodClass := self methodClassForClassName: className isMeta: isMeta.
  	oldHeap storePointer: sourcelessMethod numLiterals ofObject: newMethod withValue: methodClass.
  	sourcelessMethod initialPC to: sourcelessMethod size do:
  		[:i|
  		oldHeap storeByte: i - 1 ofObject: newMethod withValue: (sourcelessMethod byteAt: i)].
  	^newMethod!

Item was changed:
  ----- Method: SpurBootstrap>>internAllSymbols (in category 'bootstrap methods') -----
  internAllSymbols
  	"Ensure that all symbols in the method prototypes are interned so that later we can install them.
  	 Enter them into the map, this system's symbol -> oldHeap's version.
  	 Do this by interpreting Symbol intern: 'aSymbol' for each symbol."
  	| internSym |
  	internSym := self findSymbol: #intern:.
  	self allPrototypeMethodSymbols do:
  		[:sym|
  		(self findSymbol: sym)
  			ifNotNil: [:imageSym| symbolMap at: sym put: imageSym]
  			ifNil:[Transcript cr; nextPutAll: 'interning '; nextPutAll: sym; flush.
  				"Interpret Symbol intern: sym to ... intern it :-)"
  				symbolMap
  					at: sym
+ 					put: (self interpreter: oldInterpreter
+ 							object: self symbolClass
- 					put: (self interpreterObject: self symbolClass
  							perform: internSym
  							withArguments: {self stringFor: sym})]].
  	symbolMap keysAndValuesDo:
  		[:sym :imageSym|
  		self assert: sym = (oldHeap stringOf: imageSym)]!

Item was added:
+ ----- 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 singleStep].
+ 	result := sim internalPopStack.
+ 	self assert: sim localIP - 1 = savedpc.
+ 	sim localIP: savedpc.
+ 	^result!

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

Item was added:
+ ----- 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.
+ 	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: [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 added:
+ ----- Method: SpurBootstrap>>rememberRehashSymbol (in category 'bootstrap image') -----
+ rememberRehashSymbol
+ 	rehashSym := self findSymbol: #rehash!

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

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: ((0 to: maxClassIndex) select:
  					[:idx| | classObj |
  					(classObj := newHeap classAtIndex: idx) ~= newHeap nilObject
+ 					and: [(newHeap classIndexOf: classObj) = (newHeap rawHashBitsOf: classObj)]]) isEmpty.
- 					and: [(newHeap classIndexOf: classObj) = (newHeap hashBitsOf: classObj)]]) isEmpty.
  	0 to: maxClassIndex do:
  		[:index| | classObj |
  		(classObj := newHeap classAtIndex: index) = newHeap nilObject
  			ifTrue:
  				[self assert: (classToIndex keyAtValue: index ifAbsent: []) isNil]
  			ifFalse:
+ 				[self assert: (newHeap classIndexOf: classObj) ~= (newHeap rawHashBitsOf: classObj).
- 				[self assert: (newHeap classIndexOf: classObj) ~= (newHeap hashBitsOf: classObj).
  				(duplicates includes: index) ifFalse:
+ 					[self assert: (newHeap rawHashBitsOf: classObj) = index]]].
- 					[self assert: (newHeap hashBitsOf: classObj) = index]]].
  	classToIndex keysAndValuesDo:
  		[:oldClass :idx|
+ 		self assert: (newHeap rawHashBitsOf: (map at: oldClass)) = idx. 
- 		self assert: (newHeap hashBitsOf: (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"!

Item was added:
+ ----- Method: SpurBootstrap>>withExecutableInterpreter:do: (in category 'bootstrap methods') -----
+ withExecutableInterpreter: sim do: aBlock
+ 	"With the oldInterpreter ready to execute code, evaluate aBlock,
+ 	 then return the interpreter (and the heap) to the ``just snapshotted'' state."
+ 	| savedpc initialContext finalContext |
+ 	sim
+ 		initStackPages;
+ 		loadInitialContext;
+ 		internalizeIPandSP.
+ 	initialContext := sim frameContext: sim localFP.
+ 	savedpc := sim localIP.
+ 	"sim printHeadFrame."
+ 	aBlock value.
+ 	"sim printHeadFrame."
+ 	sim
+ 		internalPush: sim localIP;
+ 		externalizeIPandSP.
+ 	"now undo the execution state"
+ 	finalContext := sim voidVMStateForSnapshot.
+ 	self assert: initialContext = finalContext.
+ 	self assert: sim localIP = savedpc!

Item was removed:
- ----- Method: SpurBootstrap>>withExecutableInterpreterDo: (in category 'bootstrap methods') -----
- withExecutableInterpreterDo: aBlock
- 	"With the oldInterpreter ready to execute code, evaluate aBlock,
- 	 then return the interpreter (and the heap) to the ``just snapshotted'' state."
- 	| savedpc initialContext finalContext |
- 	oldInterpreter
- 		initStackPages;
- 		loadInitialContext;
- 		internalizeIPandSP.
- 	initialContext := oldInterpreter frameContext: oldInterpreter localFP.
- 	savedpc := oldInterpreter localIP.
- 	"oldInterpreter printHeadFrame."
- 	aBlock value.
- 	"oldInterpreter printHeadFrame."
- 	oldInterpreter
- 		internalPush: oldInterpreter localIP;
- 		externalizeIPandSP.
- 	"now undo the execution state"
- 	finalContext := oldInterpreter voidVMStateForSnapshot.
- 	self assert: initialContext = finalContext.
- 	self assert: oldInterpreter localIP = savedpc!



More information about the Vm-dev mailing list