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

commits at source.squeak.org commits at source.squeak.org
Fri Sep 6 21:14:17 UTC 2013


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

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

Name: Cog-eem.73
Author: eem
Time: 6 September 2013, 2:14:04.626 pm
UUID: f0f69347-38f2-489a-b027-ade5091ddc1d
Ancestors: Cog-eem.72

Reorganize, splitting bootstrap into bootstrap image & bootstrap
methods.

Add prototypes for instance creation that allow the scavenger to run.

Write first-phase of installing modified methods; intern any and all
symbols in the prototype methods.

=============== Diff against Cog-eem.72 ===============

Item was changed:
  Object subclass: #SpurBootstrap
+ 	instanceVariableNames: 'oldHeap newHeap map reverseMap classToIndex oldInterpreter lastClassTablePage symbolMap'
- 	instanceVariableNames: 'oldHeap newHeap map reverseMap classToIndex oldInterpreter lastClassTablePage'
  	classVariableNames: ''
  	poolDictionaries: 'VMObjectIndices'
  	category: 'Cog-Bootstrapping'!
  
  !SpurBootstrap commentStamp: 'eem 9/2/2013 13:26' prior: 0!
  SpurBootstrap bootstraps an image in CogMemoryManager format from a Squeak V3 + closures format.
  
  e.g.
  	(SpurBootstrap32 new on: '/Users/eliot/Cog/startreader.image')
  		transform;
  		launch
  
  Instance Variables
  	classToIndex:		<Dictionary>
  	map:		<Dictionary>
  	newHeap:		<CogMemoryManager>
  	oldHeap:		<NewObjectMemory>
  	oldInterpreter:		<StackInterpreterSimulator>
  
  classToIndex
  	- oldClass to new classIndex map
  
  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
  !

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEbasicNew (in category 'method prototypes') -----
+ BehaviorPROTOTYPEbasicNew
+ 	"Primitive. Answer an instance of the receiver (which is a class) with no 
+ 	 indexable variables. Fail if the class is indexable. Essential. See Object 
+ 	 documentation whatIsAPrimitive.
+ 	
+ 	 If the primitive fails because space is low then the scavenger
+ 	 will run before the method is activated.  Check arguments and
+ 	 retry via failingBasicNew: if they're OK."
+ 
+ 	<primitive: 70>
+ 	self isVariable ifTrue: [^self basicNew: 0].
+ 	"space must have been low, and the scavenger must have run.
+ 	 retry after the scavenge."
+ 	^self failingBasicNew!

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEbasicNew: (in category 'method prototypes') -----
+ BehaviorPROTOTYPEbasicNew: sizeRequested 
+ 	"Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive.
+ 	
+ 	 If the primitive fails because space is low then the scavenger will run before the
+ 	 method is activated.  Check arguments and retry via failingBasicNew: if they're OK."
+ 
+ 	<primitive: 71>
+ 	self isVariable ifFalse:
+ 		[self error: self printString, ' cannot have variable sized instances'].
+ 	(sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue:
+ 		["arg okay; space must have been low, and the scavenger must have run.
+ 		  retry after the scavenge"
+ 		^self failingBasicNew: sizeRequested].
+ 	self primitiveFailed!

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEhandleFailingBasicNew (in category 'method prototypes') -----
+ BehaviorPROTOTYPEhandleFailingBasicNew
+ 	"This basicNew gets sent after basicNew has failed and allowed a
+ 	 scavenging garbage collection to occur.  The scavenging collection
+ 	 will have happened as the VM is activating the (failing) basicNew.
+ 	 If failingBasicNew fails then the scavenge failed to reclaim sufficient
+ 	 space and a global garbage collection is required.
+ 
+ 	 Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 70>
+ 	self isVariable ifTrue: [^self basicNew: 0].
+ 	Smalltalk garbageCollect.
+ 	^self failingFailingBasicNew "retry after global garbage collect"!

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEhandleFailingBasicNew: (in category 'method prototypes') -----
+ BehaviorPROTOTYPEhandleFailingBasicNew: sizeRequested
+ 	"This basicNew: gets sent after basicNew: has failed and allowed a
+ 	 scavenging garbage collection to occur.  The scavenging collection
+ 	 will have happened as the VM is activating the (failing) basicNew:.
+ 	 If failingBasicNew: fails then the scavenge failed to reclaim sufficient
+ 	 space and a global garbage collection is required.
+ 
+ 	 Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 71>
+ 	self isVariable ifFalse:
+ 		[self error: self printString, ' cannot have variable sized instances'].
+ 	(sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue:
+ 		[Smalltalk garbageCollect.
+ 		^self failingFailingBasicNew: sizeRequested  "retry after global garbage collect"].
+ 	self primitiveFailed!

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEhandleFailingFailingBasicNew (in category 'method prototypes') -----
+ BehaviorPROTOTYPEhandleFailingFailingBasicNew
+ 	"This basicNew gets sent after failingBasicNew: has sent Smalltalk garbageCollect.
+ 	 If this fails then the system really is low on space.
+ 
+ 	 Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 70>
+ 	self isVariable ifTrue: [^self basicNew: 0].
+ 	"space must be low"
+ 	OutOfMemory signal.
+ 	^self basicNew  "retry if user proceeds"!

Item was added:
+ ----- Method: SpurBootstrap class>>BehaviorPROTOTYPEhandleFailingFailingBasicNew: (in category 'method prototypes') -----
+ BehaviorPROTOTYPEhandleFailingFailingBasicNew: sizeRequested
+ 	"This basicNew: gets sent after failingBasicNew: has sent Smalltalk garbageCollect.
+ 	 If that fails the system really is low on space.
+ 
+ 	 Primitive. Answer an instance of this class with the number of indexable
+ 	 variables specified by the argument, sizeRequested.  Fail if this class is not
+ 	 indexable or if the argument is not a positive Integer, or if there is not
+ 	 enough memory available. Essential. See Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 71>
+ 	self isVariable ifFalse:
+ 		[self error: self printString, ' cannot have variable sized instances'].
+ 	(sizeRequested isInteger and: [sizeRequested >= 0]) ifTrue:
+ 		["arg okay; space must be low."
+ 		OutOfMemory signal.
+ 		^self basicNew: sizeRequested  "retry if user proceeds"].
+ 	self primitiveFailed!

Item was changed:
  ----- Method: SpurBootstrap class>>ClassBuilderPROTOTYPEformat:variable:words:pointers:weak: (in category 'method prototypes') -----
  ClassBuilderPROTOTYPEformat: nInstVars variable: isVar words: isWords pointers: isPointers weak: isWeak
  	"Compute the format for the given instance specfication.
  	 Above Cog Spur the class format is
  		<5 bits inst spec><16 bits inst size>
  	 where the 5-bit inst spec is
  		 0 = 0 sized objects (UndefinedObject True False et al)
  		 1 = non-indexable objects with inst vars (Point et al)
  		 2 = indexable objects with no inst vars (Array et al)
  		 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  		 4 = weak indexable objects with inst vars (WeakArray et al)
  		 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  		 6,7,8 unused
  		 9 (?) 64-bit indexable
  		 10 - 11 32-bit indexable
  		 12 - 15 16-bit indexable
  		 16 - 23 byte indexable
  		 24 - 31 compiled method"
  	| instSpec |
  	instSpec := isWeak
  					ifTrue: [4]
  					ifFalse:
  						[isPointers
  							ifTrue:
  								[isVar
  									ifTrue: [nInstVars > 0 ifTrue: [3] ifFalse: [2]]
  									ifFalse: [nInstVars > 0 ifTrue: [1] ifFalse: [0]]]
  							ifFalse: [isWords ifTrue: [12] ifFalse: [16]]].
+ 	^(instSpec bitShift: 16) + nInstVars!
- 	^instSpec << 16 + nInstVars!

Item was added:
+ ----- Method: SpurBootstrap>>allPrototypeMethodSymbols (in category 'method prototypes') -----
+ allPrototypeMethodSymbols
+ 	"self basicNew allPrototypeMethodSymbols"
+ 	| symbols |
+ 	symbols := Set new.
+ 	(SpurBootstrap class organization listAtCategoryNamed: #'method prototypes') do:
+ 		[:protoSelector| | method |
+ 		method := SpurBootstrap class >> protoSelector.
+ 		symbols add: (self selectorForPrototypeMethod: method).
+ 		symbols addAll: (method literals select: [:l| l isSymbol and: [l ~~ protoSelector]])].
+ 	^symbols!

Item was changed:
+ ----- Method: SpurBootstrap>>allocateClassTable (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>allocateClassTable (in category 'bootstrap') -----
  allocateClassTable
  	"Allocate the root of the classTable plus enough pages to accomodate all classes in
  	 the classToIndex map.  Don't fill in the entries yet; the classes have yet to be cloned."
  	| tableRootSize tableRoot page maxSize numPages |
  	tableRootSize := self classTableSize / newHeap classTablePageSize.
  	tableRoot := newHeap
  					allocateSlots: tableRootSize
  					format: newHeap arrayFormat
  					classIndex: newHeap arrayClassIndexPun.
  	self assert: (newHeap numSlotsOf: tableRoot) = tableRootSize.
  	self assert: (newHeap formatOf: tableRoot) = newHeap arrayFormat.
  	self assert: (newHeap classIndexOf: tableRoot) = newHeap arrayClassIndexPun.
  	newHeap nilFieldsOf: tableRoot.
  	"first page is strong"
  	page := newHeap
  					allocateSlots: newHeap classTablePageSize
  					format: newHeap arrayFormat
  					classIndex: newHeap arrayClassIndexPun.
  	self assert: (newHeap numSlotsOf: page) = newHeap classTablePageSize.
  	self assert: (newHeap formatOf: tableRoot) = newHeap arrayFormat.
  	self assert: (newHeap classIndexOf: tableRoot) = newHeap arrayClassIndexPun.
  	self assert: (newHeap objectAfter: tableRoot limit: newHeap freeStart) = page.
  	lastClassTablePage := page.
  	newHeap nilFieldsOf: page.
  	newHeap storePointer: 0 ofObject: tableRoot withValue: page.
  	newHeap classTableRootObj: tableRoot.
  	maxSize := classToIndex inject: 0 into: [:a :b| a max: b].
  	numPages := (maxSize + newHeap classTableMinorIndexMask / newHeap classTablePageSize) truncated.
  	2 to: numPages do:
  		[:i|
  		page := newHeap
  					allocateSlots: newHeap classTablePageSize
  					format: newHeap weakArrayFormat
  					classIndex: newHeap weakArrayClassIndexPun.
  		self assert: (newHeap numSlotsOf: page) = newHeap classTablePageSize.
  		self assert: (newHeap formatOf: page) = newHeap weakArrayFormat.
  		self assert: (newHeap classIndexOf: page) = newHeap weakArrayClassIndexPun.
  		newHeap nilFieldsOf: page.
  		newHeap storePointer: i - 1 ofObject: tableRoot withValue: page.
  		self assert: (newHeap objectAfter: (newHeap fetchPointer: i - 2 ofObject: tableRoot)  limit: newHeap freeStart) = page.
  		lastClassTablePage := page]!

Item was changed:
+ ----- Method: SpurBootstrap>>bootstrapImage (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>bootstrapImage (in category 'bootstrap') -----
  bootstrapImage
  	self cloneNilTrueAndFalse.
  	self buildClassMap.
  	self allocateClassTable.
  	self cloneObjects.
  	self fillInObjects.
  	self fillInClassTable!

Item was changed:
+ ----- Method: SpurBootstrap>>buildClassMap (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>buildClassMap (in category 'bootstrap') -----
  buildClassMap
  	"enumerate all objects asking isBehavior:?  (class == Metaclass or class class == Metaclass) doesn't work for Newspeak"
  	"Build a map from all classes in oldHeap to a class index.
  	 ONLY DEALS WITH CLASSES THAT HAVE INSTANCES!!!! (can walk superclass chain?  Can walk subclasses set? Can ask class == Metaclass or class class == Metaclass class?)"
  	| classes classTableIndex |
  	self defineKnownClassIndices.
  	classes := classToIndex keys asSet.
  	classTableIndex := classToIndex inject: 0 into: [:a :b| a max: b].
  	oldHeap allObjectsDo:
  		[:oldObj| | oldClass |
  		 oldClass := oldHeap fetchClassOfNonImm: oldObj.
  		 self assert: (oldHeap isPointersNonImm: oldClass).
  		 (classes includes: oldClass) ifFalse:
  			[classes add: oldClass.
  			 classToIndex at: oldClass put: (classTableIndex := classTableIndex + 1)]]!

Item was added:
+ ----- Method: SpurBootstrap>>classNameForPrototypeMethod: (in category 'method prototypes') -----
+ classNameForPrototypeMethod: protoMethod
+ 	| protoSelector |
+ 	protoSelector := protoMethod selector.
+ 	^(protoSelector first: (protoSelector indexOfSubCollection: 'PROTOTYPE') - 1) asSymbol!

Item was changed:
+ ----- Method: SpurBootstrap>>clone:classIndex: (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>clone:classIndex: (in category 'bootstrap') -----
  clone: oldObj classIndex: classIndex
  	| newObj |
  	newObj := newHeap
  				allocateSlots: (oldHeap fetchWordLengthOf: oldObj)
  				format: (self newFormatFor: oldObj)
  				classIndex: classIndex.
  	reverseMap at: newObj put: oldObj.
  	^map at: oldObj put: newObj!

Item was changed:
+ ----- Method: SpurBootstrap>>cloneNilTrueAndFalse (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>cloneNilTrueAndFalse (in category 'bootstrap') -----
  cloneNilTrueAndFalse
  	{	oldHeap nilObject.
  		oldHeap falseObject.
  		oldHeap trueObject. }
  		with: (self firstOrdinaryClassIndex to: self firstOrdinaryClassIndex + 2)
  		do: [:obj :classIndex|
  			classToIndex at: (oldHeap fetchClassOfNonImm: obj) put: classIndex.
  			self clone: obj classIndex: classIndex].
  	newHeap
  		nilObject: (map at: oldHeap nilObject); "needed for nilling objects etc"
  		falseObject: (map at: oldHeap falseObject);
  		trueObject: (map at: oldHeap trueObject)!

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

Item was changed:
+ ----- Method: SpurBootstrap>>fillInClassTable (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>fillInClassTable (in category 'bootstrap') -----
  fillInClassTable
  	| firstPage classWeakArray |
  	classToIndex keysAndValuesDo:
  		[:oldClass :index| | newClass page |
  		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)!

Item was changed:
+ ----- Method: SpurBootstrap>>fillInCompiledMethod:from: (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>fillInCompiledMethod:from: (in category 'bootstrap') -----
  fillInCompiledMethod: newObj from: oldObj
  	self fillInBitsObject: newObj from: oldObj.
  	self fillInPointerObject: newObj from: oldObj!

Item was changed:
+ ----- Method: SpurBootstrap>>fillInObjects (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>fillInObjects (in category 'bootstrap') -----
  fillInObjects
  	oldHeap allObjectsDo:
  		[:oldObj|
  		(map at: oldObj ifAbsent: nil) ifNotNil:
  			[:newObj|
  			(newHeap isCompiledMethod: newObj)
  				ifTrue: [self fillInCompiledMethod: newObj from: oldObj]
  				ifFalse:
  					[(newHeap isPointersNonImm: newObj)
  						ifTrue: [self fillInPointerObject: newObj from: oldObj]
  						ifFalse: [self fillInBitsObject: newObj from: oldObj]]]]!

Item was changed:
+ ----- Method: SpurBootstrap>>fillInPointerObject:from: (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>fillInPointerObject:from: (in category 'bootstrap') -----
  fillInPointerObject: newObj from: oldObj
  	0 to: (oldHeap lastPointerOf: oldObj) / oldHeap bytesPerWord - 1 do:
  		[:i| | oldValue newValue |
  		oldValue := oldHeap fetchPointer: i ofObject: oldObj.
  		newValue := (oldHeap isIntegerObject: oldValue)
  						ifTrue: [oldValue]
  						ifFalse:
  							[map at: oldValue ifAbsent:
  								[oldValue = oldHeap characterTable
  									ifTrue: [newHeap nilObject]
  									ifFalse:
  										[self assert: (oldHeap fetchClassOfNonImm: oldValue) = oldHeap classCharacter.
  										 newHeap characterObjectOf:
  											(oldHeap integerValueOf:
  												(oldHeap fetchPointer: CharacterValueIndex ofObject: oldValue))]]].
  		newHeap
  			storePointerUnchecked: i
  			ofObject: newObj
  			withValue: newValue].
  	(classToIndex includesKey: oldObj) ifTrue:
  		[newHeap
  			storePointerUnchecked: InstanceSpecificationIndex
  			ofObject: newObj
  			withValue: (self newClassFormatFor: oldObj)]!

Item was added:
+ ----- Method: SpurBootstrap>>findSymbol: (in category 'bootstrap methods') -----
+ findSymbol: aString
+ 	"Find the Symbol equal to aString in oldHeap."
+ 	| symbolClass |
+ 	symbolClass := self symbolClass.
+ 	oldHeap allObjectsDo:
+ 		[:o|
+ 		(symbolClass = (oldHeap fetchClassOfNonImm: o)
+ 		 and: [(oldHeap byteLengthOf: o) = aString size
+ 		 and: [aString = (oldHeap stringOf: o)]]) ifTrue:
+ 			[^o]].
+ 	^nil!

Item was added:
+ ----- 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."
+ 	self internAllSymbols.
+ 	self addDummyMethods.
+ 	self addInstallMethods.
+ 	self modifyCharacterMethods!

Item was added:
+ ----- 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.
+ 	 Do this by interpreting Symbol intern: 'aSymbol' for each symbol.  Make sure the execution state
+ 	 has not advanced when doing so, and restore the image to the state it has on snapshot."
+ 	| internSym savedpc initialContext finalContext |
+ 	symbolMap := Dictionary new.
+ 	internSym := self findSymbol: #intern:.
+ 	oldInterpreter
+ 		initStackPages;
+ 		loadInitialContext;
+ 		internalizeIPandSP.
+ 	initialContext := oldInterpreter frameContext: oldInterpreter localFP.
+ 	savedpc := oldInterpreter localIP.
+ 	"oldInterpreter printHeadFrame."
+ 	self allPrototypeMethodSymbols do:
+ 		[:sym| | string fp |
+ 		(self findSymbol: sym)
+ 			ifNotNil: [:imageSym| symbolMap at: sym put: imageSym]
+ 			ifNil:
+ 				[Transcript cr; nextPutAll: 'interning '; nextPutAll: sym; flush.
+ 				string := oldHeap instantiateClass: (oldHeap splObj: ClassByteString) indexableSize: sym size.
+ 				1 to: sym size do:
+ 					[:i| oldHeap storeByte: i - 1 ofObject: string withValue: (sym at: i) asInteger].
+ 				"Interpret Symbol intern: sym to ... intern it :-)"
+ 				oldInterpreter
+ 					internalPush: self symbolClass;
+ 					internalPush: string;
+ 					argumentCount: 1;
+ 					messageSelector: internSym.
+ 				fp := oldInterpreter localFP.
+ 				oldInterpreter normalSend.
+ 				[fp = oldInterpreter localFP] whileFalse:
+ 					[oldInterpreter singleStep].
+ 				symbolMap at: sym put: oldInterpreter internalPopStack.
+ 				self assert: oldInterpreter localIP - 1 = savedpc.
+ 				oldInterpreter localIP: savedpc]].
+ 	symbolMap keysAndValuesDo:
+ 		[:sym :imageSym|
+ 		self assert: sym = (oldHeap stringOf: imageSym)].
+ 	"oldInterpreter printHeadFrame."
+ 	oldInterpreter
+ 		internalPush: oldInterpreter localIP;
+ 		externalizeIPandSP.
+ 	"now undo the execution state"
+ 	finalContext := oldInterpreter voidVMStateForSnapshot.
+ 	self assert: initialContext = finalContext.
+ 	self assert: oldInterpreter localIP = savedpc!

Item was changed:
+ ----- Method: SpurBootstrap>>newClassFormatFor: (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>newClassFormatFor: (in category 'bootstrap') -----
  newClassFormatFor: oldClassObj
  	"OLD: 		<2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0>
  	 NEW: 		<5 bits inst spec><16 bits inst size>"
  	| oldFormat instSize newInstSpec |
  	oldFormat := oldHeap formatOfClass: oldClassObj. "N.B. SmallInteger with tag bit cleared"
  	oldFormat := oldFormat >> 1.
  	instSize := ((oldFormat bitShift: -10) bitAnd: 16rC0) + ((oldFormat bitShift: -1) bitAnd: 16r3F) - 1.
  	newInstSpec := #(0 1 2 3 4 5 6 7 16 16 16 16 24 24 24 24) at: ((oldFormat bitShift: -7) bitAnd: 16rF) + 1.
  	^newHeap integerObjectOf: newInstSpec << 16 + instSize!

Item was changed:
+ ----- Method: SpurBootstrap>>newFormatFor: (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>newFormatFor: (in category 'bootstrap') -----
  newFormatFor: oldObj
  	"OLD:
  	 0	no fields
  	 1	fixed fields only (all containing pointers)
  	 2	indexable fields only (all containing pointers)
  	 3	both fixed and indexable fields (all containing pointers)
  	 4	both fixed and indexable weak fields (all containing pointers).
  
  	 5	unused
  	 6	indexable word fields only (no pointers)
  	 7	indexable long (64-bit) fields (only in 64-bit images)
   
  	 8-11	indexable byte fields only (no pointers) (low 2 bits are low 2 bits of size)
  	 12-15	compiled methods:
  	 	    # of literal oops specified in method header,
  	 	    followed by indexable bytes (same interpretation of low 2 bits as above)"
  
  	"NEW:
  	 0 = 0 sized objects (UndefinedObject True False et al)
  	 1 = non-indexable objects with inst vars (Point et al)
  	 2 = indexable objects with no inst vars (Array et al)
  	 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  	 4 = weak indexable objects with inst vars (WeakArray et al)
  	 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
  
  	 and here it gets messy, we need 8 CompiledMethod values, 8 byte values, 4 16-bit values, 2 32-bit values and a 64-bit value, = 23 values, 23 + 5 = 30, so there may be room.
  
  	 9 (?) 64-bit indexable
  	 10 - 11 32-bit indexable
  	 12 - 15 16-bit indexable
  	 16 - 23 byte indexable
  	 24 - 31 compiled method"
  	| oldFormat |
  	oldFormat := oldHeap formatOf: oldObj.
  	oldFormat <= 4 ifTrue:
  		[^oldFormat].
  	oldFormat >= 12 ifTrue: "CompiledMethod"
  		[^24 + (self wordSize - (oldHeap byteLengthOf: oldObj) bitAnd: self wordSizeMask)].
  	oldFormat >= 8 ifTrue: "ByteArray et al"
  		[^16 + (self wordSize - (oldHeap byteLengthOf: oldObj) bitAnd: self wordSizeMask)].
  	oldFormat = 6 ifTrue: "32-bit indexable"
  		[^10 + ((oldHeap byteLengthOf: oldObj) bitAnd: self wordSizeMask) sign].
  	oldFormat = 7 ifTrue: "64-bit indexable"
  		[^9].
  	self error: 'illegal old format'!

Item was added:
+ ----- Method: SpurBootstrap>>selectorForPrototypeMethod: (in category 'method prototypes') -----
+ selectorForPrototypeMethod: protoMethod
+ 	| protoSelector |
+ 	protoSelector := protoMethod selector.
+ 	^(protoSelector last: protoSelector size
+ 						- (protoSelector indexOfSubCollection: 'PROTOTYPE')
+ 						- 'PROTOTYPE' size
+ 						+ 1) asSymbol!

Item was added:
+ ----- Method: SpurBootstrap>>symbolClass (in category 'bootstrap methods') -----
+ symbolClass
+ 	^oldHeap fetchClassOfNonImm: (oldHeap splObj: SelectorDoesNotUnderstand)!

Item was changed:
+ ----- Method: SpurBootstrap>>transform (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>transform (in category 'bootstrap') -----
  transform
+ 	self installModifiedMethods.
  	self bootstrapImage.
  	newHeap initializePostBootstrap.
  	self validate!

Item was changed:
+ ----- Method: SpurBootstrap>>validate (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>validate (in category 'bootstrap') -----
  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 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 hashBitsOf: classObj).
  				(duplicates includes: index) ifFalse:
  					[self assert: (newHeap hashBitsOf: classObj) = index]]].
  	classToIndex keysAndValuesDo:
  		[: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"!



More information about the Vm-dev mailing list