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

commits at source.squeak.org commits at source.squeak.org
Tue May 5 17:11:10 UTC 2015


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

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

Name: VMMaker.oscog-eem.1287
Author: eem
Time: 5 May 2015, 10:08:54.172 am
UUID: 45fc3cf4-0050-4473-af9e-392747bdd689
Ancestors: VMMaker.oscog-cb.1286

Add a nice click step facility for single-steppng
through machine code that sets up a suitable
breakBlock and proceeds the debugger, prompting
for a click at each step.

Fix instruction decoration when printing instructions
with EagerInstructionDecoration false.

Add an assert to insist that the receiver not be
forwarded to mnuMethodOrNilFor:.

Safer comparison in simulator's createActualMessageTo:

=============== Diff against VMMaker.oscog-cb.1286 ===============

Item was changed:
  ----- Method: CoInterpreter>>mnuMethodOrNilFor: (in category 'message sending') -----
  mnuMethodOrNilFor: rcvr
  	"Lookup the doesNotUnderstand: selector in the class of the argument rcvr.
  	 Answer either the matching method (cogged if appropriate), or nil, if not found."
  	| currentClass mnuSelector dictionary mnuMethod methodHeader |
+ 	self deny: (objectMemory isOopForwarded: rcvr).
- 
  	currentClass := objectMemory fetchClassOf: rcvr.
  	mnuSelector := objectMemory splObj: SelectorDoesNotUnderstand.
  	[currentClass ~= objectMemory nilObject] whileTrue:
  		[dictionary := objectMemory fetchPointer: MethodDictionaryIndex ofObject: currentClass.
  		 dictionary = objectMemory nilObject ifTrue:
  			[^nil].
  		 mnuMethod := self lookupMethodFor: mnuSelector InDictionary: dictionary.
+ 		 mnuMethod ifNotNil:
- 		 mnuMethod notNil ifTrue:
  			[methodHeader := self rawHeaderOf: mnuMethod.
  			 ((self isCogMethodReference: methodHeader) not
  			  and: [self methodWithHeaderShouldBeCogged: methodHeader]) ifTrue:
  				[cogit cog: mnuMethod selector: mnuSelector].
  			^mnuMethod].
  		currentClass := self superclassOf: currentClass].
  	^nil!

Item was changed:
  ----- Method: CogVMSimulator>>createActualMessageTo: (in category 'debugging traps') -----
  createActualMessageTo: class
  
+ 	class = objectMemory nilObject ifTrue: [self halt].
- 	class == objectMemory nilObject ifTrue: [self halt].
  
  	^super createActualMessageTo: class!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulationWindow;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
  		add: 'print mc/cog frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
  		add: 'short print ext frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		add: 'short print mc/cog frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
  		add: 'long print ext frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  		add: 'long print int frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  		add: 'long print mc/cog frame & callers' action: [self printFrameAndCallers: cogit processor fp SP: cogit processor sp];
  		add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  		add: 'print call stack' action: #printCallStack;
  		add: 'print stack call stack' action: #printStackCallStack;
  		add: 'print stack call stack of...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printStackCallStackOf: fp]];
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print call stack of frame...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printCallStackFP: fp]];
  		add: 'print all stacks' action: #printAllStacks;
  		add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  											self writeBackHeadFramePointers];
  		add: 'write back mc ptrs' action: [stackPointer := cogit processor sp. framePointer := cogit processor fp. instructionPointer := cogit processor eip.
  											self writeBackHeadFramePointers];
  		addLine;
  		add: 'print rump C stack' action: [objectMemory printMemoryFrom: cogit processor sp to: self CStackPointer];
  		add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  		add: 'print register map' action: [cogit printRegisterMapOn: transcript];
  		add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  		add: 'disassemble method/trampoline at pc' action: [cogit disassembleCodeAt: cogit processor pc];
  		add: 'disassemble ext head frame method' action: [cogit disassembleMethod: (self frameMethod: framePointer)];
  		add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  		add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
  		add: 'print context...' action: [(self promptHex: 'print context') ifNotNil: [:oop| self printContext: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'inspect cointerpreter' action: #inspect;
  		add: 'inspect cogit' target: cogit action: #inspect;
  		add: 'inspect method zone' target: cogit methodZone action: #inspect.
  	self isThreadedVM ifTrue:
  		[aMenuMorph add: 'inspect thread manager' target: self threadManager action: #inspect].
  	aMenuMorph
  		addLine;
  		add: 'print cog methods' target: cogMethodZone action: #printCogMethods;
  		add: 'print cog methods with prim...' action: [(self promptNum: 'prim index') ifNotNil: [:pix| cogMethodZone printCogMethodsWithPrimitive: pix]];
  		add: 'print cog methods with selector...' action:
  			[|s| s := UIManager default request: 'selector'.
  			s notEmpty ifTrue:
  				[s = 'nil' ifTrue: [s := nil].
  				 cogMethodZone methodsDo:
  					[:m|
  					(s ifNil: [m selector = objectMemory nilObject]
  					 ifNotNil: [(objectMemory numBytesOf: m selector) = s size
  							and: [(self str: s
  									n: (m selector + objectMemory baseHeaderSize)
  									cmp: (objectMemory numBytesOf: m selector)) = 0]]) ifTrue:
  						[cogit printCogMethod: m]]]];
  		add: 'print cog method for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodFor: pc]];
  		add: 'print cog method header for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodHeaderFor: pc]];
  		add: 'print trampoline table' target: cogit action: #printTrampolineTable;
  		add: 'print prim trace log' action: #dumpPrimTraceLog;
  		add: 'report recent instructions' target: cogit action: #reportLastNInstructions;
  		add: 'set break pc (', (cogit breakPC isInteger ifTrue: [cogit breakPC hex] ifFalse: [cogit breakPC printString]), ')...' action: [(self promptHex: 'break pc') ifNotNil: [:bpc| cogit breakPC: bpc]];
  		add: (cogit singleStep
  				ifTrue: ['no single step']
  				ifFalse: ['single step'])
  			action: [cogit singleStep: cogit singleStep not];
  		add: (cogit printRegisters
  				ifTrue: ['no print registers each instruction']
  				ifFalse: ['print registers each instruction'])
  			action: [cogit printRegisters: cogit printRegisters not];
  		add: (cogit printInstructions
  				ifTrue: ['no print instructions each instruction']
  				ifFalse: ['print instructions each instruction'])
  			action: [cogit printInstructions: cogit printInstructions not];
  		addLine;
+ 		add: 'click step' action: [cogit setClickStepBreakBlock];
  		add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  											s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
  		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector'.
  											s notEmpty ifTrue: [self setBreakSelector: s]];
  		add: 'set break block...' action: [|s| s := UIManager default request: 'break block' initialAnswer: '[:theCogit| false]'.
  											s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  		add: 'set cogit break method...' action: [(self promptHex: 'cogit breakMethod') ifNotNil: [:bm| cogit setBreakMethod: bm]];
  		add: (printBytecodeAtEachStep
  				ifTrue: ['no print bytecode each bytecode']
  				ifFalse: ['print bytecode each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printBytecodeAtEachStep := printBytecodeAtEachStep not];
  		add: (printFrameAtEachStep
  				ifTrue: ['no print frame each bytecode']
  				ifFalse: ['print frame each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printFrameAtEachStep := printFrameAtEachStep not].
  	^aMenuMorph!

Item was changed:
  ----- Method: Cogit>>recordLastInstruction (in category 'simulation only') -----
  recordLastInstruction
  	<doNotGenerate>
  	^self recordInstruction: (processor
  								disassembleNextInstructionIn: coInterpreter memory
+ 								for: ((EagerInstructionDecoration or: [printInstructions]) ifTrue: [self]))!
- 								for: (EagerInstructionDecoration ifTrue: [self]))!

Item was added:
+ ----- 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 |
+ 	previousBreakBlock := breakBlock.
+ 	breakBlock := [:ign|
+ 					(UIManager confirm: 'step?')
+ 						ifTrue: [false]
+ 						ifFalse: [breakBlock := previousBreakBlock.
+ 								true]].
+ 	(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]]!



More information about the Vm-dev mailing list