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

commits at source.squeak.org commits at source.squeak.org
Sat Sep 21 01:27:25 UTC 2013


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

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

Name: Cog-eem.96
Author: eem
Time: 20 September 2013, 6:27:12.089 pm
UUID: bd2cd65c-986e-413e-beb1-c0e9d480f5bb
Ancestors: Cog-eem.95

Make sure the format inst var of /all/ behaviors is converted to the
new representation.

Fix BehaviorPROTOTYPEbasicNew[:] to use handleFailingBasicNew[:]
instead of failingBasicNew[:].

=============== Diff against Cog-eem.95 ===============

Item was changed:
  Object subclass: #SpurBootstrap
+ 	instanceVariableNames: 'oldHeap newHeap map reverseMap classToIndex oldInterpreter lastClassTablePage literalMap methodClasses installedPrototypes sizeSym rehashSym classMetaclass'
- 	instanceVariableNames: 'oldHeap newHeap map reverseMap classToIndex oldInterpreter lastClassTablePage literalMap methodClasses installedPrototypes sizeSym rehashSym'
  	classVariableNames: 'ImageHeaderFlags ImageName TransformedImage'
  	poolDictionaries: 'VMObjectIndices'
  	category: 'Cog-Bootstrapping'!
  
  !SpurBootstrap commentStamp: 'eem 9/11/2013 05:45' 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 changed:
  ----- 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 handleFailingBasicNew!
- 	^self failingBasicNew!

Item was changed:
  ----- 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 handleFailingBasicNew: sizeRequested].
- 		^self failingBasicNew: sizeRequested].
  	self primitiveFailed!

Item was changed:
  ----- Method: SpurBootstrap>>fillInPointerObject:from: (in category 'bootstrap image') -----
  fillInPointerObject: newObj from: oldObj
  	"Fill-in a newObj with appropriately mapped contents from oldObj.
  	 Filter-out the character table and the compact classes array.
  	 Map character objects to immediate characters."
  	0 to: (oldHeap lastPointerOf: oldObj) / oldHeap wordSize - 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
  								
  								   or: [oldValue = (oldHeap splObj: CompactClasses)])
  									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].
+ 	(self isOldObjABehavior: oldObj) ifTrue:
- 	(classToIndex includesKey: oldObj) ifTrue:
  		[newHeap
  			storePointerUnchecked: InstanceSpecificationIndex
  			ofObject: newObj
  			withValue: (self newClassFormatFor: oldObj)]!

Item was changed:
+ ----- Method: SpurBootstrap>>findRequiredGlobals (in category 'bootstrap image') -----
- ----- Method: SpurBootstrap>>findRequiredGlobals (in category 'bootstrap methods') -----
  findRequiredGlobals
  	"Look for the necessary gobal bindings in the prototype methods in the old image.
+ 	 This has to be done early by sending bindingOf: to Smalltalk.  Also find out
+ 	 Metaclass, needed for identofying classes."
- 	 This has to be done early by sending bindingOf: to Smalltalk."
  	| globals bindingOf |
  	globals := Set new.
  	self prototypeClassNameMetaSelectorMethodDo:
  		[:c :m :s :method|
  		globals addAll: (method literals select: [:l|
  										l isVariableBinding
  										and: [l key isSymbol
  										and: [(Smalltalk bindingOf: l key) == l]]])].
  	bindingOf := self findSymbol: #bindingOf:.
  	self withExecutableInterpreter: oldInterpreter
  		do:	[globals do:
  				[:global|
  				literalMap
  					at: global
  					put: (self interpreter: oldInterpreter
  							object: (oldHeap splObj: 8) "Smalltalk"
  							perform: bindingOf
+ 							withArguments: {self findSymbol: global key})]].
+ 
+ 	classMetaclass := oldHeap fetchClassOfNonImm: (oldHeap fetchClassOfNonImm: oldHeap classArray)!
- 							withArguments: {self findSymbol: global key})]]!

Item was changed:
  ----- Method: SpurBootstrap>>freeForwarders (in category 'bootstrap image') -----
  freeForwarders
  	"Check that all forwarders have been followed.  Then free them."
  	| numForwarders numFreed |
  	numForwarders := numFreed := 0.
  	newHeap allObjectsDo:
  		[:o|
  		(newHeap isForwarded: o)
  			ifTrue: [numForwarders := numForwarders + 1]
  			ifFalse:
  				[0 to: (newHeap numPointerSlotsOf: o) - 1 do:
  					[:i|
  					self assert: (newHeap isOopForwarded: (newHeap fetchPointer: i ofObject: o)) not]]].
+ 	Transcript ensureCr;  nextPutAll: 'freeing '; print: numForwarders; nextPutAll: ' forwarders'; cr; flush.
- 	Transcript nextPutAll: 'freeing '; print: numForwarders; nextPutAll: ' forwarders'; cr; flush.
  	newHeap allObjectsDo:
  		[:o|
  		(newHeap isForwarded: o) ifTrue:
  			[numFreed := numFreed + 1.
  			 newHeap freeObject: o]].
  	self assert: numFreed = numForwarders!

Item was added:
+ ----- Method: SpurBootstrap>>isOldObjABehavior: (in category 'bootstrap image') -----
+ isOldObjABehavior: oldObj
+ 	| oldObjClass oldObjClassClass |
+ 	^(classToIndex includesKey: oldObj)
+ 	or: [oldObjClass := oldHeap fetchClassOfNonImm: oldObj.
+ 		oldObjClassClass := oldHeap fetchClassOfNonImm: oldObjClass.
+ 		oldObjClass = classMetaclass
+ 		or: [oldObjClassClass = classMetaclass]]!



More information about the Vm-dev mailing list