[Vm-dev] VM Maker: VMMaker.oscog-eem.1306.mcz

commits at source.squeak.org commits at source.squeak.org
Fri May 15 20:09:24 UTC 2015


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

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

Name: VMMaker.oscog-eem.1306
Author: eem
Time: 15 May 2015, 1:07:11.757 pm
UUID: 88864d96-33bb-4285-9fb5-02d57043a1e2
Ancestors: VMMaker.oscog-eem.1305

Fix old bug in ceMNUFromPICMNUMethod:receiver:
that has been masked by cacheing of MNU method
in MNU PIC entries.  ceMNUFromPICMNUMethod:receiver:
must set up lkupClass before calling handleMNU:...

Simulation:
Fix MNU send breakpoint in simulator's
ceMNUFromPICMNUMethod:receiver:; don't pop the
PIC abort ret pc twice.

Fix the click-step breakBlock when there's a breakPC in effect.

Speed up simulated GC by short-cutting unnecessary
copying when cloning the VM.

=============== Diff against VMMaker.oscog-eem.1305 ===============

Item was changed:
  ----- Method: CoInterpreter>>ceMNUFromPICMNUMethod:receiver: (in category 'trampolines') -----
  ceMNUFromPICMNUMethod: aMethodObj receiver: rcvr
  	<api>
  	| cPIC primitiveIndex |
  	<var: #cPIC type: #'CogMethod *'>
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self assert: (aMethodObj = 0
  				or: [(objectMemory addressCouldBeObj: aMethodObj)
  					and: [objectMemory isOopCompiledMethod: aMethodObj]]).
  	cPIC := self cCoerceSimple: self popStack - cogit mnuOffset to: #'CogMethod *'.
  	self assert: (cPIC cmType = CMClosedPIC or: [cPIC cmType = CMOpenPIC]).
  	argumentCount := cPIC cmNumArgs.
  	messageSelector := cPIC selector.
  	aMethodObj ~= 0 ifTrue:
  		[instructionPointer := self popStack.
  		self createActualMessageTo: (objectMemory fetchClassOf: rcvr).
  		(self maybeMethodHasCogMethod: aMethodObj) ifTrue:
  			[self push: instructionPointer.
  			 self executeCogMethod: (self cogMethodOf: aMethodObj)
  				 fromUnlinkedSendWithReceiver: rcvr.
  			 "NOTREACHED"
  			 self assert: false].
  		newMethod := aMethodObj.
  		primitiveIndex := self primitiveIndexOf: aMethodObj.
  		primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: objectMemory nilObject.
  		^self interpretMethodFromMachineCode].
+ 	"handleMNU:InMachineCodeTo:classForMessage: assumes lkupClass is set, since every other use is
+ 	 after a lookupMethodNoMNUEtcInClass: call, which sets lkupClass.  Here we must set it manually.
+ 	 Global variables.  Bah!!"
  	self handleMNU: SelectorDoesNotUnderstand
  		InMachineCodeTo: rcvr
+ 		classForMessage: (lkupClass := objectMemory fetchClassOf: rcvr).
- 		classForMessage: (objectMemory fetchClassOf: rcvr).
  	"NOTREACHED"
  	self assert: false!

Item was changed:
  ----- Method: CogVMSimulator>>ceMNUFromPICMNUMethod:receiver: (in category 'trampolines') -----
  ceMNUFromPICMNUMethod: aMethodObj receiver: rcvr
  	| cPIC |
+ 	cPIC := self cCoerceSimple: self stackTop - cogit mnuOffset to: #'CogMethod *'.
- 	cPIC := self cCoerceSimple: self popStack - cogit mnuOffset to: #'CogMethod *'.
  	self assert: (cPIC cmType = CMClosedPIC or: [cPIC cmType = CMOpenPIC]).
  	self mnuBreakpoint: cPIC selector receiver: nil.
  	^super ceMNUFromPICMNUMethod: aMethodObj receiver: rcvr!

Item was added:
+ ----- Method: CogVMSimulator>>veryDeepCopyWith: (in category 'debug support') -----
+ veryDeepCopyWith: deepCopier
+ 	"Override to short-circuit the copying of any VMPluginCodeGenerators referenced from mappedPluginEntries and
+ 	 uniqueIndices. These can in turn hold onto Monticello state, resulting in a huge ammount of unnecessary copying."
+ 	deepCopier references
+ 		at: mappedPluginEntries ifAbsentPut: [mappedPluginEntries];
+ 		at: uniqueIndices ifAbsentPut: [uniqueIndices].
+ 	mappedPluginEntries do:
+ 		[:tuple|
+ 		[:sim :sel :block :argCount|
+ 		deepCopier references at: block ifAbsentPut: [block]] valueWithArguments: tuple].
+ 	uniqueIndices keysDo:
+ 		[:block|
+ 		deepCopier references at: block ifAbsentPut: [block]].
+ 	^super veryDeepCopyWith: deepCopier!

Item was changed:
  ----- Method: Cogit>>setClickStepBreakBlock (in category 'simulation only') -----
  setClickStepBreakBlock
  	"Set the break block to present a confirmer, breaking if true, and restoring the previous break block.
  	 If an open debugger on the receiver can be found, proceed it."
  	<doNotGenerate>
+ 	| previousBreakBlock previousBreakPC |
- 	| previousBreakBlock |
  	previousBreakBlock := breakBlock.
+ 	previousBreakPC := breakPC.
  	breakBlock := [:ign|
+ 					(processor pc ~= previousBreakPC
+ 					 and: [UIManager confirm: 'step?'])
- 					(UIManager confirm: 'step?')
  						ifTrue: [false]
  						ifFalse: [breakBlock := previousBreakBlock.
+ 								breakPC := previousBreakPC.
  								true]].
+ 	singleStep := true.
+ 	breakPC := nil.
  	(World submorphs
  		detect:
  			[:m|
  			 m model class == Debugger
  			 and: [(m model interruptedProcess suspendedContext findContextSuchThat:
  					[:ctxt|
  					ctxt receiver == self
  					and: [ctxt selector == #simulateCogCodeAt:]]) notNil]]
  		ifNone: []) ifNotNil:
  			[:debuggerWindow|
  			 WorldState addDeferredUIMessage:
  				[debuggerWindow model proceed]]!

Item was changed:
+ ----- Method: StackInterpreter>>lookupMethodNoMNUEtcInClass: (in category 'message sending') -----
- ----- Method: StackInterpreter>>lookupMethodNoMNUEtcInClass: (in category 'callback support') -----
  lookupMethodNoMNUEtcInClass: class
  	"Lookup messageSelector in class.  Answer 0 on success. Answer the splObj: index
  	 for the error selector to use on failure rather than performing MNU processing etc."
  	| currentClass dictionary |
  	<inline: false>
  
  	currentClass := class.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		 dictionary = objectMemory nilObject ifTrue:
  			[lkupClass := self superclassOf: currentClass.
  			 ^SelectorCannotInterpret].
  		 (self lookupMethodInDictionary: dictionary) ifTrue:
  			[self addNewMethodToCache: class.
  			 ^0].
  		currentClass := self superclassOf: currentClass].
  	lkupClass := class.
  	^SelectorDoesNotUnderstand!

Item was added:
+ ----- Method: StackInterpreterSimulator>>veryDeepCopyWith: (in category 'debug support') -----
+ veryDeepCopyWith: deepCopier
+ 	"Override to short-circuit the copying of any VMPluginCodeGenerators referenced from mappedPluginEntries.
+ 	 These can in turn hold onto Monticello state, resulting in a huge ammount of unnecessary copying."
+ 	deepCopier references
+ 		at: mappedPluginEntries ifAbsentPut: [mappedPluginEntries].
+ 	mappedPluginEntries do:
+ 		[:tuple|
+ 		[:sim :sel :block :argCount|
+ 		deepCopier references at: block ifAbsentPut: [block]] valueWithArguments: tuple].
+ 	^super veryDeepCopyWith: deepCopier!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>allocateEqualsEqualsRegistersArgNeedsReg:rcvrNeedsReg:into: (in category 'bytecode generator support') -----
  allocateEqualsEqualsRegistersArgNeedsReg: argNeedsReg rcvrNeedsReg: rcvrNeedsReg into: binaryBlock
  	<inline: true>
  	| argReg rcvrReg |
  	self assert: (argNeedsReg or: [rcvrNeedsReg]).
  	argNeedsReg
  		ifTrue: 
  			[rcvrNeedsReg
  				ifTrue:
  					[self allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
  					 self ssTop popToReg: argReg.
  					 (self ssValue: 1) popToReg: rcvrReg]
  				ifFalse:
  					[argReg := self allocateRegForStackEntryAt: 0.
  					 self ssTop popToReg: argReg.
  					 "If the receiver is a spilled constant we need to pop it from the stack."
  					 (self ssValue: 1) spilled ifTrue:
  						[self AddCq: objectMemory wordSize R: SPReg]]]
  		ifFalse:
  			[self assert: rcvrNeedsReg.
+ 			 self deny: self ssTop spilled.
+ 			 rcvrReg := self allocateRegForStackEntryAt: 1.
+ 			 (self ssValue: 1) popToReg: rcvrReg].
- 			rcvrReg := self allocateRegForStackEntryAt: 1.
- 			(self ssValue: 1) popToReg: rcvrReg].
  		
  	self assert: (argNeedsReg not or: [argReg notNil]).
  	self assert: (rcvrNeedsReg not or: [rcvrReg notNil]).
+ 
- 	
  	binaryBlock value: rcvrReg value: argReg!



More information about the Vm-dev mailing list