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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 19 20:22:35 UTC 2013


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

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

Name: Cog-eem.92
Author: eem
Time: 19 September 2013, 1:22:23.662 pm
UUID: 03144fa4-dcb6-46ce-9d5b-05ed9cdbd3b8
Ancestors: Cog-eem.91

SpurBootstrap:
Rename symbolMap to literalMap and abstract away from direct
access to Smalltalk object's internals, instead simulating bindingOf:,
hence allowing bootstrap of Squeak trunk image that uses Environments.

=============== Diff against Cog-eem.91 ===============

Item was changed:
  Object subclass: #SpurBootstrap
+ 	instanceVariableNames: 'oldHeap newHeap map reverseMap classToIndex oldInterpreter lastClassTablePage literalMap methodClasses installedPrototypes sizeSym rehashSym'
- 	instanceVariableNames: 'oldHeap newHeap map reverseMap classToIndex oldInterpreter lastClassTablePage symbolMap methodClasses installedPrototypes sizeSym rehashSym'
  	classVariableNames: 'NewInterpreter 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>>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: (literalMap at: sym).
- 		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
  									perform: cmaiaSym
+ 									withArguments: {literalMap at: selector. oldHeap nilObject}.
- 									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
  							perform: basSym
+ 							withArguments: { literalMap at: selector.
- 							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>>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".
  	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; see below"
- 		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 classPoint put: 54;
  
+ 	{{oldHeap classMutex. 49}.
+ 	 {oldHeap classExternalAddress. 128}.
+ 	 {oldHeap classExternalData. 129}.
+ 	 {oldHeap classExternalFunction. 130}.
+ 	 {oldHeap classExternalLibrary. 131}.
+ 	 {oldHeap classExternalStructure. 132}.
+ 	 {oldHeap classAlien. 133}.
+ 	 {oldHeap classUnsafeAlien. 134}}
+ 		do: [:pair|
+ 			[:oop :index|
+ 			oop ~= oldHeap nilObject ifTrue:
+ 				[classToIndex at: oop put: index]] valueWithArguments: pair].
+ 
- 		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 added:
+ ----- 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."
+ 	| 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})]]!

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 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
  					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: [literalMap at: literal ifAbsent: [self findLiteral: 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| literalMap at: sym put: imageSym]
- 			ifNotNil: [:imageSym| symbolMap at: sym put: imageSym]
  			ifNil:[Transcript cr; nextPutAll: 'interning '; nextPutAll: sym; flush.
  				"Interpret Symbol intern: sym to ... intern it :-)"
+ 				literalMap
- 				symbolMap
  					at: sym
  					put: (self interpreter: oldInterpreter
  							object: self symbolClass
  							perform: internSym
  							withArguments: {self stringFor: sym})]].
+ 	literalMap keysAndValuesDo:
+ 		[:symOrGlobal :imageSymOrGlobal|
+ 		symOrGlobal isSymbol ifTrue:
+ 			[self assert: symOrGlobal = (oldHeap stringOf: imageSymOrGlobal)]]!
- 	symbolMap keysAndValuesDo:
- 		[:sym :imageSym|
- 		self assert: sym = (oldHeap stringOf: imageSym)]!

Item was changed:
  ----- Method: SpurBootstrap>>methodClassForClassName:isMeta: (in category 'bootstrap methods') -----
  methodClassForClassName: classNameSymbol isMeta: isMeta 
  	| class |
+ 	class := self findClassNamed: (literalMap at: classNameSymbol).
- 	class := self findClassNamed: (symbolMap at: classNameSymbol).
  	isMeta ifTrue: [class := oldHeap fetchClassOfNonImm: class].
  	methodClasses do:
  		[:mca|
  		class = (oldHeap fetchPointer: ValueIndex ofObject: mca) ifTrue:
  			[^mca]].
  	oldHeap allObjectsDo:
  		[:o| | methodClassAssociation |
  		(oldHeap isCompiledMethod: o) ifTrue:
  			[methodClassAssociation := oldInterpreter methodClassAssociationOf: o.
  			 class == (oldHeap fetchPointer: ValueIndex ofObject: methodClassAssociation) ifTrue:
  				[methodClasses add: methodClassAssociation.
  				 ^methodClassAssociation]]].
  	self error: 'could not find methodClassAssociation for ', classNameSymbol, (isMeta ifTrue: [' class'] ifFalse:[''])!

Item was changed:
  ----- Method: SpurBootstrap>>on: (in category 'initialize-release') -----
  on: imageName
  	StackInterpreter initializeWithOptions: Dictionary new.
  	oldInterpreter := StackInterpreterSimulator new.
  	oldInterpreter openOn: imageName extraMemory: 0.
  	oldHeap := oldInterpreter objectMemory.
  	newHeap := Spur32BitMMLESimulator new.
  	newHeap
  		allocateMemoryOfSize: (oldHeap youngStart * 5 / 4 roundUpTo: 8)
  		newSpaceSize: 1024 * 1024
  		codeSize: 1024 * 1024.
  		newHeap setCheckForLeaks: 15 - 4. "don't check become"
  	map := Dictionary new: oldHeap memory size // 4.
  	reverseMap := Dictionary new: oldHeap memory size // 4.
+ 	classToIndex := Dictionary new: 1024.
+ 	literalMap := IdentityDictionary new.
+ 	methodClasses := Set new.
+ 	installedPrototypes := Set new!
- 	classToIndex := Dictionary new: 1024!

Item was changed:
  ----- Method: SpurBootstrap>>replaceMethods (in category 'bootstrap methods') -----
  replaceMethods
  	"Replace all the modified method prototypes."
  	self allPrototypeClassNamesDo:
  		[:sym :symIsMeta| | class |
+ 		class := self findClassNamed: (literalMap at: sym).
- 		class := self findClassNamed: (symbolMap at: sym).
  		symIsMeta ifTrue: [class := oldHeap fetchClassOfNonImm: class].
  		self prototypeClassNameMetaSelectorMethodDo:
  			[:className :isMeta :selector :method| | replacement methodDict index |
  			(className = sym
  			 and: [symIsMeta = isMeta]) ifTrue:
  				[(installedPrototypes includes: method selector) ifFalse:
  					["probe method dictionary of the class for each method, installing a dummy if not found."
  					Transcript
  						cr;
  						nextPutAll: 'replacing ';
  						nextPutAll: className;
  						nextPutAll: (isMeta ifTrue: [' class>>'] ifFalse: ['>>']);
  						store: selector;
  						flush.
  					replacement := self installableMethodFor: method
  										selector: selector
  										className: className
  										isMeta: isMeta.
  					methodDict := oldHeap fetchPointer: MethodDictionaryIndex ofObject: class.
+ 					index := self indexOfSelector: (literalMap at: selector) in: methodDict.
- 					index := self indexOfSelector: (symbolMap at: selector) in: methodDict.
  					oldHeap
  						storePointer: index - SelectorStart
  						ofObject: (oldHeap fetchPointer: MethodArrayIndex ofObject: methodDict)
  						withValue: replacement.
  					installedPrototypes add: method selector]]]]!

Item was changed:
  ----- Method: SpurBootstrap>>replacementForCharacterMethod: (in category 'bootstrap methods') -----
  replacementForCharacterMethod: characterMethodOop
  	"Answer a replacement method for the argument if it refers
  	 to Character's old inst var value.  Otherwise answer nil."
  	| proxy asIntegerProxy clone assembly newInsts newMethod |
  	"(oldHeap stringOf: (oldHeap longAt: characterMethodOop + (oldHeap lastPointerOf: characterMethodOop) - 4)) = 'isOctetCharacter' ifTrue:
  		[self halt]."
  	proxy := VMCompiledMethodProxy new
  				for: characterMethodOop
  				coInterpreter: oldInterpreter
  				objectMemory: oldHeap.
  	clone := self cloneMethodProxy: proxy.
  	"Quick methods accessing value should have been replaced."
  	clone isReturnField ifTrue: [self halt].
  	clone hasInstVarRef ifFalse:
  		[^nil].
  	clone setSourcePointer: 0.
  	asIntegerProxy := VMObjectProxy new
+ 							for: (literalMap at: #asInteger)
- 							for: (symbolMap at: #asInteger)
  							coInterpreter: oldInterpreter
  							objectMemory: oldHeap.
  	assembly := BytecodeDisassembler new disassemble: clone.
  	assembly literals: (assembly literals allButLast: 2), {asIntegerProxy}, (assembly literals last: 2).
  		"Do this by looking for index of pushReceiverVariable: and replacing it by pushSelf, send asInteger"
  	newInsts := (assembly instructions piecesCutWhere:
  					[:msgOrLabelAssoc :nextInst|
  					 msgOrLabelAssoc isVariableBinding not
  					 and: [msgOrLabelAssoc selector == #pushReceiverVariable:]]) fold:
  				[:a :b|
  				 a allButLast,
  				 {	Message selector: #pushReceiver.
  					Message
  						selector: #send:super:numArgs:
  						arguments: {asIntegerProxy. false. 0}},
  				 b].
  	assembly instructions: newInsts.
  	newMethod := assembly assemble.
  	^self
  		installableMethodFor: newMethod
  		selector: clone selector
  		className: #Character
  		isMeta: false!

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



More information about the Vm-dev mailing list