[Vm-dev] VM Maker: VMMakerUI-eem.19.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Feb 10 16:55:53 UTC 2020


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

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

Name: VMMakerUI-eem.19
Author: eem
Time: 10 February 2020, 8:55:51.970773 am
UUID: a7749363-2561-45fd-b771-33811e174cbc
Ancestors: VMMakerUI-eem.18

Get (some of?) the CogXXXInspectors to work in the StackInterpreterSimulator.

=============== Diff against VMMakerUI-eem.18 ===============

Item was changed:
  ----- Method: CogAbstractFrameInspector>>interpretOop:value:at: (in category 'evaluating') -----
  interpretOop: fieldName value: valueString at: address
  	(CogOopInspector on: coInterpreter)
+ 		oop: (address < 0
+ 				ifTrue: [coInterpreter stackPages longAt: address]
+ 				ifFalse: [objectMemory longAt: address]);
- 		oop: (coInterpreter longAt: address);
  		displayPinnable: fieldName, ' ', valueString!

Item was added:
+ ----- Method: InterpreterStackPages>>apparentlyValidFramePointer:stackPointer: (in category '*VMMakerUI-testing') -----
+ apparentlyValidFramePointer: framePointer stackPointer: stackPointer
+ 	<doNotGenerate>
+ 	^framePointer isInteger
+ 	 and: [stackPointer isInteger
+ 	 and: [stackPointer < framePointer
+ 	 and: [(self pageIndexFor: framePointer) = (self pageIndexFor: stackPointer)]]]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>printHex:on: (in category '*VMMakerUI-debug printing') -----
+ printHex: anInteger on: aStream
+ 	<doNotGenerate>
+ 	aStream next: 8 - (anInteger digitLength * 2) put: Character space.
+ 	anInteger storeOn: aStream base: 16!

Item was added:
+ ----- Method: StackInterpreterSimulator>>printStringOf:on: (in category '*VMMakerUI-debug printing') -----
+ printStringOf: oop on: aStream
+ 	<doNotGenerate>
+ 	| fmt len cnt max i |
+ 	(objectMemory isImmediate: oop) ifTrue:
+ 		[^self].
+ 	(objectMemory addressCouldBeObj: oop) ifFalse:
+ 		[^self].
+ 	fmt := objectMemory formatOf: oop.
+ 	fmt < objectMemory firstByteFormat ifTrue: [^self].
+ 
+ 	cnt := (max := 128) min: (len := objectMemory lengthOf: oop).
+ 	i := 0.
+ 
+ 	((objectMemory is: oop
+ 		  instanceOf: (objectMemory splObj: ClassByteArray)
+ 		  compactClassIndex: classByteArrayCompactIndex)
+ 	or: [(objectMemory isLargeIntegerInstance: oop)])
+ 		ifTrue:
+ 			[[i < cnt] whileTrue:
+ 				[self printHex: (objectMemory fetchByte: i ofObject: oop) on: aStream.
+ 				 (i := i + 1) \\ 16 = 0 ifTrue: [aStream cr]]]
+ 		ifFalse:
+ 			[[i < cnt] whileTrue:
+ 				[aStream nextPut: (objectMemory fetchByte: i ofObject: oop) asCharacter.
+ 				 i := i + 1]].
+ 	len > max ifTrue:
+ 		[aStream nextPutAll: '...']!

Item was changed:
  ----- Method: StackInterpreterSimulator>>utilitiesMenu: (in category '*VMMakerUI-user interface') -----
  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: 'short print ext frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		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: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
+ 		add: 'inspect frame...' action: [(self promptHex: 'inspect frame') ifNotNil: [:fp| (CogFrameInspector on: self) framePointer: fp; open]];
+ 		add: 'inspect head frame' action: [CogHeadFrameInspector openFor: self];
  		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: 'print prim trace log' action: #dumpPrimTraceLog;
  		addLine;
  		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: 'run leak checker' action: [Cursor execute showWhile: [self runLeakChecker]];
  		add: 'inspect interpreter' action: #inspect;
  		addLine;
  		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 (MNU:foo for MNU)'.
  											s notEmpty ifTrue:
  												[(s size > 4 and: [s beginsWith: 'MNU:'])
  													ifTrue: [self setBreakMNUSelector: (s allButFirst: 4)]
  													ifFalse: [self setBreakSelector: s]]];
  		add: 'turn valid exec ptrs assert o', (assertVEPAES ifTrue: ['ff'] ifFalse: ['n']) action: [assertVEPAES := assertVEPAES not];
  		add: 'click step' action: [self setClickStepBreakBlock];
  		add: (printSends
  				ifTrue: ['no print sends']
  				ifFalse: ['print sends'])
  			action: [self ensureDebugAtEachStepBlock.
  					printSends := printSends not];
  		"currently printReturns does nothing"
  		"add: (printReturns
  				ifTrue: ['no print returns']
  				ifFalse: ['print returns'])
  			action: [self ensureDebugAtEachStepBlock.
  					printReturns := printReturns not];"
  		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!



More information about the Vm-dev mailing list