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

commits at source.squeak.org commits at source.squeak.org
Wed Sep 18 01:11:26 UTC 2013


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

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

Name: Cog-eem.89
Author: eem
Time: 17 September 2013, 6:11:13.622 pm
UUID: d56a6961-bf18-450f-9aaa-427cfb9e753d
Ancestors: Cog-eem.88

Bring modifyCharacterMethods into withExecutableInterpreter:
scope.

Fix replacementForCharacterMethod: (was installing oop of
asInteger selector as a SmallInteger, not the oop itself).

Make sure interpreter:object:perform:withArguments: increments
byteCount even if performed send is primitive.

Needs VMMaker.oscog-eem.388.

=============== Diff against Cog-eem.88 ===============

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]!
- 			 self replaceMethods].
- 	self modifyCharacterMethods!

Item was changed:
  ----- 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 savedsp result startByteCount |
- 	| fp savedpc savedsp result |
  	savedpc := sim localIP.
  	savedsp := sim localSP.
  	sim internalPush: receiver.
  	arguments do: [:arg| sim internalPush: arg].
  	sim
  		argumentCount: arguments size;
  		messageSelector: selector.
  	fp := sim localFP.
+ 	startByteCount := sim byteCount.
+ 	"sim byteCount = 66849 ifTrue: [self halt]."
  	sim normalSend.
+ 	sim incrementByteCount. "otherwise, send is not counted"
+ 	["sim byteCount = 66849 ifTrue: [self halt]."
+ 	 "(sim byteCount > 7508930 and: [sim localFP = -16r27894]) ifTrue:
+ 		[self halt]."
+ 	 fp = sim localFP] whileFalse:
- 	[fp = sim localFP] whileFalse:
  		[sim singleStep].
  	result := sim internalPopStack.
  	self assert: savedsp = sim localSP.
  	self assert: sim localIP - 1 = savedpc.
  	sim localIP: savedpc.
  	^result!

Item was changed:
  ----- 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.
  
  	newHeap
  		setHashBitsOf: newHeap nilObject to: 1;
  		setHashBitsOf: newHeap falseObject to: 2;
  		setHashBitsOf: newHeap trueObject to: 3.
  
  	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.
  	n := 0.
  	self withExecutableInterpreter: sim
  		do: "don't rehash twice (actually without limit), so don't rehash any new objects created."
  			[newHeap allExistingObjectsDo:
  				[:o| | classIndex |
  				classIndex := newHeap classIndexOf: o.
  				((rehashFlags at: classIndex >> 3 + 1) anyMask: 1 << (classIndex bitAnd: 7)) ifTrue:
  					[(n := n + 1) \\ 8 = 0 ifTrue:
  					 	[Transcript nextPut: $.; flush].
+ 					 "2845 = n ifTrue: [self halt]."
  					 (self interpreter: sim
  							object: o
  							perform: (map at: sizeSym)
  							withArguments: #()) ~= (newHeap integerObjectOf: 0) ifTrue:
  						[self interpreter: sim
  							object: o
  							perform: (map at: rehashSym)
  							withArguments: #()]]]]!

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 clone assembly newInsts |
  	proxy := VMCompiledMethodProxy new
  				for: characterMethodOop
  				coInterpreter: oldInterpreter
  				objectMemory: oldHeap.
  	clone := self cloneMethodProxy: proxy.
- 	clone dropSourcePointer.
  	clone hasInstVarRef ifFalse:
  		[^nil].
+ 	clone setSourcePointer: 0.
+ 	asIntegerProxy := VMObjectProxy new
+ 							for: (symbolMap at: #asInteger)
+ 							coInterpreter: oldInterpreter
+ 							objectMemory: oldHeap.
  	assembly := BytecodeDisassembler new disassemble: clone.
+ 	assembly literals: (assembly literals allButLast: 2), {asIntegerProxy}, (assembly literals last: 2).
- 	assembly literals: (assembly literals allButLast: 2), {symbolMap at: #asInteger}, (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}},
- 						arguments: {symbolMap at: #asInteger. false. 0}},
  				 b].
  	assembly instructions: newInsts.
+ 	newMethod := assembly assemble.
  	^self
+ 		installableMethodFor: newMethod
- 		installableMethodFor: assembly assemble
  		selector: clone selector
  		className: #Character
  		isMeta: false!



More information about the Vm-dev mailing list