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

commits at source.squeak.org commits at source.squeak.org
Sat Sep 7 21:04:48 UTC 2013


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

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

Name: Cog-eem.77
Author: eem
Time: 7 September 2013, 2:04:35.375 pm
UUID: bec1ed80-2794-4350-b2d6-91d25c87c0c4
Ancestors: Cog-eem.76

Finish installation of prototype methods; modifying Character
methods yet to be done.

=============== Diff against Cog-eem.76 ===============

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 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 interpreterObject: class
  							perform: basSym
  							withArguments: { symbolMap at: selector.
  											   self installableMethodFor: method
  												selector: selector
  												className: className
  												isMeta: isMeta}]
  					ifFalse: "existing method; collect the methodClassAssociation; its needed later"
  						[methodClasses add: (oldInterpreter methodClassAssociationOf: methodOrNil)]]]]!

Item was added:
+ ----- Method: SpurBootstrap>>findLiteral: (in category 'bootstrap methods') -----
+ findLiteral: aLiteral
+ 	| symbolOop smalltalk array |
+ 	aLiteral isString ifTrue:
+ 		[^self stringFor: aLiteral].
+ 	self assert: aLiteral isVariableBinding.
+ 	symbolOop := self findSymbol: aLiteral key.
+ 	smalltalk := oldHeap splObj: 8.
+ 	array := oldHeap fetchPointer: 1 ofObject: smalltalk.
+ 	self assert: (oldHeap isArray: array).
+ 	0 to: (oldHeap fetchWordLengthOf: array) - 1 do:
+ 		[:i| | bindingOrNil |
+ 		bindingOrNil := oldHeap fetchPointer: i ofObject: array.
+ 		(bindingOrNil ~= oldHeap nilObject
+ 		 and: [symbolOop = (oldHeap fetchPointer: KeyIndex ofObject: bindingOrNil)
+ 		 and: [aLiteral key == #Smalltalk
+ 				ifTrue:
+ 					[(oldHeap fetchPointer: ValueIndex ofObject: bindingOrNil) = smalltalk]
+ 				ifFalse:
+ 					[oldInterpreter
+ 						classNameOf: (oldHeap fetchPointer: ValueIndex ofObject: bindingOrNil)
+ 						Is: aLiteral key]]]) ifTrue:
+ 			[^bindingOrNil]].
+ 	self error: 'couldn''t find literal ', aLiteral printString!

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).
  	sourcelessMethod := aCompiledMethod copyWithTempsFromMethodNode: aCompiledMethod methodNode.
  	sourcelessMethod selector: selector.
  	bytes := sourcelessMethod size - sourcelessMethod initialPC + 1.
  	newMethod := self
  					interpreterObject: compiledMethodClass
  					perform: (self findSymbol: #newMethod:header:)
  					withArguments: { oldHeap integerObjectOf: bytes.
  									   oldHeap integerObjectOf: sourcelessMethod header }.
  	1 to: sourcelessMethod numLiterals - 1 do:
  		[:i| | literal |
  		literal := sourcelessMethod literalAt: i.
+ 		literal isMethodProperties ifTrue:
+ 			[literal := selector].
  		literal := literal isInteger
  					ifTrue: [oldHeap integerObjectOf: literal]
+ 					ifFalse: [symbolMap at: literal ifAbsent: [self findLiteral: literal]].
- 					ifFalse: [symbolMap at: literal].
  		oldHeap storePointer: i ofObject: newMethod withValue: literal].
  	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|
- 		[:sym| | string |
  		(self findSymbol: sym)
  			ifNotNil: [:imageSym| symbolMap at: sym put: imageSym]
+ 			ifNil:[Transcript cr; nextPutAll: 'interning '; nextPutAll: sym; flush.
- 			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 :-)"
  				symbolMap
  					at: sym
  					put: (self interpreterObject: self symbolClass
  							perform: internSym
+ 							withArguments: {self stringFor: sym})]].
- 							withArguments: {string})]].
  	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: (symbolMap at: classNameSymbol).
- 	class := self findClassNamed: 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 added:
+ ----- Method: SpurBootstrap>>stringFor: (in category 'bootstrap methods') -----
+ stringFor: aString
+ 	| string |
+ 	string := oldHeap instantiateClass: (oldHeap splObj: ClassByteString) indexableSize: aString size.
+ 	1 to: aString size do:
+ 		[:i| oldHeap storeByte: i - 1 ofObject: string withValue: (aString at: i) asInteger].
+ 	^string
+ !



More information about the Vm-dev mailing list