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

commits at source.squeak.org commits at source.squeak.org
Fri Sep 5 19:51:33 UTC 2014


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

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

Name: Cog-eem.202
Author: eem
Time: 5 September 2014, 12:51:18.647 pm
UUID: d0d65d71-4b3f-4969-964f-19e6b6c8bb83
Ancestors: Cog-eem.201

The 4.3 Spur bootstrap needs more stack space
because of the class reshapings.  Use ClassBuilder
class>>beSilent: to lose the progress notification.

Provide a category for computeMethodHeaderForNumArgs:numTemps:numLits:primitive:

=============== Diff against Cog-eem.201 ===============

Item was changed:
  ----- Method: SimulatorHarness>>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 savedStackPages result startByteCount |
  	self assert: ({receiver. selector}, arguments allSatisfy:
  					[:oop| oop isInteger and: [sim objectMemory addressCouldBeOop: oop]]).
  	savedpc := sim localIP.
  	savedsp := sim localSP.
  	savedStackPages := Set with: sim stackPage.
  	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 printFrame: sim localFP WithSP: sim localSP"
  	 "sim setBreakSelector: #elementsForwardIdentityTo:"
  	 "sim byteCount = 66849 ifTrue: [self halt]."
  	 "(sim byteCount > 7508930 and: [sim localFP = -16r27894]) ifTrue:
  		[self halt]."
  	 fp = sim localFP] whileFalse:
  		[sim singleStep.
  		 (savedStackPages includes: sim stackPage) ifFalse: "If the stack gets deep something has probably gone wrong..."
+ 			[savedStackPages size > 20 ifTrue: [self halt].
- 			[savedStackPages size > 3 ifTrue: [self halt].
  			 savedStackPages add: sim stackPage]].
  	result := sim internalPopStack.
  	self assert: savedsp = sim localSP.
  	self assert: sim localIP - 1 = savedpc.
  	sim localIP: savedpc.
  	^result!

Item was changed:
  ----- Method: SpurBootstrap class>>categoryForClass:meta:selector: (in category 'method prototype categorization') -----
  categoryForClass: className meta: isMeta selector: selector 
  	^(isMeta
  			ifTrue: [{ className. #class. selector }]
  			ifFalse: [{ className. selector }])
  		caseOf: {
  			[#(Behavior allInstancesOrNil)]					-> [#enumerating].
  			[#(Behavior byteSizeOfInstance)]				-> [#'accessing instances and variables'].
  			[#(Behavior byteSizeOfInstanceOfSize:)]		-> [#'accessing instances and variables'].
  			[#(Behavior elementSize)]						-> [#'accessing instances and variables'].
  			[#(Behavior handleFailingBasicNew)]			-> [#private].
  			[#(Behavior handleFailingBasicNew:)]			-> [#private].
  			[#(Behavior handleFailingFailingBasicNew)]		-> [#private].
  			[#(Behavior handleFailingFailingBasicNew:)]		-> [#private].
  			[#(Behavior identityHash)]						-> [#comparing].
  			[#(Behavior isEphemeronClass)]				-> [#testing].
  			[#(Behavior isImmediateClass)]					-> [#testing].
  			[#(Character identityHash)]						-> [#comparing].
  			[#(Class immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category:)]
  															-> [#'subclass creation'].
  			[#(ClassBuilder superclass:immediateSubclass:instanceVariableNames:classVariableNames:poolDictionaries:category:)]
  															-> [#public].
  			[#(CompiledMethod class handleFailingFailingNewMethod:header:)]
  															-> [#private].
  			[#(CompiledMethod class handleFailingNewMethod:header:)]
  															-> [#private].
  			[#(Context class allInstances)]					-> [#enumerating].
  			[#(Context class allInstancesDo:)]				-> [#enumerating].
  			[#(Context failPrimitiveWith:)]					-> [#'system simulation'].
  			[#(Context isPrimFailToken:)]					-> [#private].
  			[#(Context send:to:with:lookupIn:)]				-> [#controlling].
  			[#(ContextPart isPrimFailToken:)]				-> [#private].
  			[#(ContextPart send:to:with:lookupIn:)]			-> [#controlling].
  			[#(CompiledMethod class headerFlagForEncoder:)]
  															-> [#'method encoding'].
  			[#(CompiledMethod class installPrimaryBytecodeSet:)]
  															-> [#'class initialization'].
  			[#(CompiledMethod class installSecondaryBytecodeSet:)]
  															-> [#'class initialization'].
+ 			[#(EncoderForV3 computeMethodHeaderForNumArgs:numTemps:numLits:primitive:)]
+ 															-> [#'method encoding'].
  			[#(EncoderForV3PlusClosures genCallPrimitive:)]
  															-> [#'bytecode generation'].
  			[#(EncoderForV3PlusClosures class callPrimitiveCode)]
  															-> [#'bytecode decoding'].
  			[#(MethodContext failPrimitiveWith:)]			-> [#'system simulation'].
  			[#(MethodContext class allInstances)]			-> [#enumerating].
  			[#(MethodContext class allInstancesDo:)]		-> [#enumerating].
  			[#(SmallInteger asCharacter)]					-> [#converting].
  			[#(SmalltalkImage growMemoryByAtLeast:)]	-> [#'memory space'].
  			[#(SmalltalkImage maxIdentityHash)]			-> [#'system attributes'].
  			[#(SystemDictionary growMemoryByAtLeast:)]	-> [#'memory space'].
  			[#(SystemDictionary maxIdentityHash)]			-> [#'system attributes'].
  			[#(SystemDictionary setGCParameters)]		-> [#'snapshot and quit'].
  			[#(SystemNavigation allObjects)]				-> [#query].
  			[#(SystemNavigation allObjectsOrNil)]			-> [#query].
  			 }
  		otherwise:
  			[Transcript nextPutAll: className.
  			 isMeta ifTrue: [Transcript nextPutAll: ' class'].
  			 Transcript nextPutAll: '>>'; store: selector; nextPutAll: ' is unclassified'; cr; flush.
  			 ^Categorizer default]!

Item was changed:
  ----- Method: SpurBootstrap>>checkReshapeOf: (in category 'bootstrap image') -----
  checkReshapeOf: ourMethodClasses
  	"Check the shape of all our method classes match the shape of those in the image to be bootstrapped.
  	 Use the simulator to redefine any that need it.  Does /not/ reshape metaclasses; these we assume are ok."
  	| toReshape |
  	toReshape := Set new.
  	ourMethodClasses do:
  		[:mc|
  		(literalMap at: mc binding ifAbsent: []) ifNotNil:
  			[:binding|
  			(mc ~~ Character "Character will reshape anyway"
  			 and: [mc instSize ~= (oldHeap instanceSizeOf: (oldHeap fetchPointer: ValueIndex ofObject: binding))]) ifTrue:
  				[toReshape add: mc]]].
  	toReshape isEmpty ifTrue:
  		[^self].
+ 	self interpreter: oldInterpreter
+ 			object: (self oldClassOopFor: ClassBuilder)
+ 			perform: (self findSymbol: #beSilent:)
+ 			withArguments: {oldHeap trueObject}.
  	"Assume only one class in any subtree needs reshaping.  Fast and loose but gets us there for now."
  	toReshape copy do:
  		[:class|
  		toReshape removeAll: (toReshape select: [:ea| ea inheritsFrom: class])].
  	toReshape do:
  		[:class|
  		Transcript cr;  nextPutAll: 'RESHAPING '; print: class; flush.
  		self interpreter: oldInterpreter
  			object: (self oldClassOopFor: Compiler)
  			perform: (self findSymbol: #evaluate:)
  			withArguments: {oldHeap stringForCString: class definition}]!



More information about the Vm-dev mailing list