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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 25 22:00:17 UTC 2019


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

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

Name: VMMakerUI-eem.4
Author: eem
Time: 25 December 2019, 2:00:16.527374 pm
UUID: 06d2d94b-25bc-42ea-8b9c-7e4acad76748
Ancestors: VMMakerUI-eem.3

Implement the frame inspectors, one for the head frame, one for a specific frame.  Cope with invalid stack pointers and an uninitialized stack zone.  Make the processor alien inspector maintain its highlighting of the last changed general register, stack register or control register.
Move the stepping methods up to an abstract superclass.

=============== Diff against VMMakerUI-eem.3 ===============

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

Item was changed:
  CogVMObjectInspector subclass: #CogAbstractFrameInspector
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMakerUI-SqueakInspectors'!
+ 
+ !CogAbstractFrameInspector commentStamp: 'eem 12/24/2019 12:32' prior: 0!
+ A CogAbstractFrameInspector is an inspector for the state of a Smalltalk stack frame in Cog.!

Item was changed:
  ----- Method: CogAbstractFrameInspector>>textForFramePointer:stackPointer: (in category 'accessing - ui') -----
  textForFramePointer: framePointer stackPointer: stackPointer
  	"Print and emphasize the frame text as efficiently as possible, deferring as much interpretation until evaluation time."
  	| frameString frameText |
+ 	(coInterpreter stackPages apparentlyValidFramePointer: framePointer stackPointer: stackPointer) ifFalse:
+ 		[^('Invalid Frame fp: ', (framePointer isInteger ifTrue: [framePointer hex allButFirst: 3] ifFalse: [framePointer printString]),
+ 			' sp: ', (framePointer isInteger ifTrue: [framePointer hex allButFirst: 3] ifFalse: [framePointer printString])) asText allBold].
  	frameText := (String streamContents: [:fs| coInterpreter printFrame: framePointer WithSP: stackPointer on: fs]) allButFirst asText.
  	(frameString := frameText string)
  		findTokens: {Character cr}
  		indicesDo:
  			[:start :stop| | firstColonIndex fieldNameIndex fieldNameEndIndex valueIndex |
  			 start = 1
  				ifTrue:
  					[self windowTitle: (frameString copyFrom: 1 to: stop)]
  				ifFalse:
  					[fieldNameIndex := (firstColonIndex := frameString indexOf: $: startingAt: start + 1) + 1.
  					[(frameString at: fieldNameIndex) = Character space] whileTrue:
  						[fieldNameIndex := fieldNameIndex + 1].
  					fieldNameEndIndex := (frameString indexOf: $: startingAt: fieldNameIndex + 1) - 1.
  					valueIndex := fieldNameEndIndex + 2.
  					[(frameString at: valueIndex) = Character space] whileTrue:
  						[valueIndex := valueIndex + 1].
  					(self evalAttributeForFieldName: (frameString copyFrom:  fieldNameIndex to: fieldNameEndIndex)
  											framePointer: framePointer
  											value: (frameString copyFrom: valueIndex to: stop)
  											addressString: (frameString copyFrom: start to: firstColonIndex - 1))
  						ifNotNil:
  							[:attribute| frameText addAttribute: attribute from: fieldNameIndex to: fieldNameEndIndex]]].
  	^frameText!

Item was changed:
  CogAbstractFrameInspector subclass: #CogFrameInspector
  	instanceVariableNames: 'framePointer stackPointer'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMakerUI-SqueakInspectors'!
+ 
+ !CogFrameInspector commentStamp: 'eem 12/24/2019 12:32' prior: 0!
+ A CogFrameInspector is is an inspector for the state of a specific Smalltalk stack frame in Cog.
+ 
+ Instance Variables
+ 	framePointer:		<Integer>
+ 	stackPointer:		<Integer>!

Item was changed:
  CogAbstractFrameInspector subclass: #CogHeadFrameInspector
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMakerUI-SqueakInspectors'!
+ 
+ !CogHeadFrameInspector commentStamp: 'eem 12/24/2019 12:33' prior: 0!
+ A CogHeadFrameInspector is is an inspector for the state of the active Smalltalk stack frame in Cog. This frame is defined by Cogit>>headFramePointer and Cogit>>headStackPointer.!

Item was added:
+ ----- Method: CogHeadFrameInspector>>framePointer (in category 'accessing') -----
+ framePointer
+ 	^cogit headFramePointer!

Item was added:
+ ----- Method: CogHeadFrameInspector>>stackPointer (in category 'accessing') -----
+ stackPointer
+ 	^cogit headStackPointer!

Item was changed:
  CogVMObjectInspector subclass: #CogProcessorAlienInspector
+ 	instanceVariableNames: 'processor registerSelectors registerCache registerMap lastChangedControlGetter lastChangedRegisterGetter lastSP lastFP lastChangedStackGetter'
- 	instanceVariableNames: 'processor registerSelectors registerCache registerMap'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMakerUI-SqueakInspectors'!
  
  !CogProcessorAlienInspector commentStamp: 'eem 12/22/2019 08:27' prior: 0!
  A CogProcessorAlienInspector is an inspector for a CogProcessorAlien processor simulator that displays the processor simulator's register state.
  
  Instance Variables
  	processor:			<CogProcessorAlien>
  	registerCache:		<Array of Integer>
  	registerSelectors:	<Array of Symbol>
  	windowTitle:		<String>!

Item was changed:
  ----- Method: CogProcessorAlienInspector>>registerTextAt: (in category 'accessing - ui') -----
+ registerTextAt: aRegisterGetter
- registerTextAt: aRegisterSelector
  	| current last text |
+ 	current := processor perform: aRegisterGetter.
+ 	last := registerCache at: aRegisterGetter ifAbsent: [].
+ 	registerCache at: aRegisterGetter put: current.	
- 	current := processor perform: aRegisterSelector.
- 	last := registerCache at: aRegisterSelector ifAbsent: [].
- 	registerCache at: aRegisterSelector put: current.	
  
  	text := (self printStringForRegisterContents: current) asText.
  
  	last ~= current ifTrue:
+ 		[(#fp == aRegisterGetter or: [#sp == aRegisterGetter or: [#lr == aRegisterGetter]])
+ 			ifTrue: [lastChangedStackGetter := aRegisterGetter]
+ 			ifFalse:
+ 				[(processor controlRegisterGetters includes: aRegisterGetter)
+ 					ifTrue: [lastChangedControlGetter := aRegisterGetter]
+ 					ifFalse: [lastChangedRegisterGetter := aRegisterGetter]]].
+ 	(aRegisterGetter == lastChangedRegisterGetter
+ 		ifTrue: [Color blue darker]
+ 		ifFalse:
+ 			[aRegisterGetter == lastChangedStackGetter
+ 				ifTrue: [Color red darker]	
+ 				ifFalse:
+ 					[aRegisterGetter == lastChangedControlGetter ifTrue:
+ 						[Color green darker darker]]]) ifNotNil:
+ 		[:color|
+ 		text addAllAttributes: {TextEmphasis bold. TextColor color: color}].
- 		[text addAllAttributes: {TextEmphasis bold. TextColor color: Color salmon}].
  	^text!

Item was removed:
- ----- Method: CogProcessorAlienInspector>>stepIn: (in category 'stepping') -----
- stepIn: window
- 	self changed: #text.!

Item was removed:
- ----- Method: CogProcessorAlienInspector>>stepTimeIn: (in category 'stepping') -----
- stepTimeIn: window
- 	"The minimum update time in milliseconds."
- 	^500!

Item was changed:
  ----- Method: CogProcessorAlienInspector>>text (in category 'accessing - ui') -----
  text
  
  	^Text streamContents:
  		[:s | | max exclude fpstate |
+ 		(cogit notNil
+ 		 and: [cogit addressIsInCodeZone: processor pc])
+ 			ifTrue:
+ 				[s tab; nextPutAll: (processor decorateDisassembly: (processor disassembleInstructionAt: processor pc In: memory)
+ 								for: cogit
+ 								fromAddress: processor pc); cr]
+ 			ifFalse: [s cr].
  		max := (registerSelectors ifEmpty: [1] ifNotEmpty: [:selector | (selector collect: #size) max]).
  		exclude := Set new.
  		1 to: (fpstate := processor floatingPointRegisterStateGetters) size by: 4 do:
  			[:index|
  			((index to: index + 3) allSatisfy: [:fpri| (processor perform: (fpstate at: fpri)) isZero]) ifTrue:
  				[exclude addAll: (fpstate copyFrom: index to: index + 3)]].
  		registerSelectors do:
  			[:selector | | attribute |
  			(exclude includes: selector) ifFalse:
  				[s
  					nextPutAll: ((selector asUppercase padded: #right to: max with: Character space)
  						asText addAttribute: (attribute := PluggableTextAttribute evalBlock: [self interpret: selector]));
  					space;
  					nextPutAll: (self registerTextAt: selector).
  				 (registerMap at: selector ifAbsent: []) ifNotNil:
  					[:abstractReg|
  					 s space; nextPutAll: (abstractReg asText addAttribute: attribute)].
  				 s cr]]]!

Item was removed:
- ----- Method: CogProcessorAlienInspector>>wantsStepsIn: (in category 'stepping') -----
- wantsStepsIn: window
- 	^ true!

Item was added:
+ ----- Method: CogVMObjectInspector>>stepIn: (in category 'stepping') -----
+ stepIn: window
+ 	self changed: #text!

Item was added:
+ ----- Method: CogVMObjectInspector>>stepTimeIn: (in category 'stepping') -----
+ stepTimeIn: window
+ 	"The minimum update time in milliseconds."
+ 	^500!

Item was added:
+ ----- Method: CogVMObjectInspector>>wantsStepsIn: (in category 'stepping') -----
+ wantsStepsIn: window
+ 	^true!

Item was added:
+ ----- Method: CogVMSimulator>>headFramePointer (in category '*VMMakerUI-user interface') -----
+ headFramePointer
+ 	^localFP ifNil: [framePointer]!

Item was added:
+ ----- Method: CogVMSimulator>>headStackPointer (in category '*VMMakerUI-user interface') -----
+ headStackPointer
+ 	^localFP ifNotNil: [localSP] ifNil: [stackPointer]!

Item was changed:
  ----- Method: CogVMSimulator>>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: 'print mc/cog head frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
  		add: 'short print ext head frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int head frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		add: 'short print mc/cog head frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
  		add: 'long print ext head frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  		add: 'long print int head frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  		add: 'long print mc/cog head 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 pc.
  											self externalWriteBackHeadFramePointers];
  		addLine;
  		add: 'print rump C stack' action: [objectMemory printMemoryFrom: cogit processor sp to: CFramePointer];
  		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 codeEntryFor: cogit processor pc) isNil
  										  and: [(cogit methodZone methodFor: cogit processor pc) = 0])
  											ifTrue: [instructionPointer]
  											ifFalse: [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]];
  		add: 'symbolic method...' action: [(self promptHex: 'method bytecodes') ifNotNil: [:oop| self symbolicMethod: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'run leak checker' action: [Cursor execute showWhile: [self runLeakChecker]];
  		add: 'inspect cointerpreter' action: #inspect;
  		add: 'inspect cogit' target: cogit action: #inspect;
  		add: 'inspect method zone' target: cogit methodZone action: #inspect;
+ 		add: 'inspect head frame' action: [CogHeadFrameInspector openFor: self];
  		add: 'inspect processor' action: [CogProcessorAlienInspector openFor: self].
  	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 strncmp: s
  											_: (m selector + objectMemory baseHeaderSize)
  											_: (objectMemory numBytesOf: m selector)) = 0]]) ifTrue:
  						[cogit printCogMethod: m]]]];
  		add: 'print cog methods with method...' action:
  			[(self promptHex: 'method') ifNotNil: [:methodOop| cogMethodZone printCogMethodsWithMethod: methodOop]];
  		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: (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: (cogit singleStep
  				ifTrue: ['no single step']
  				ifFalse: ['single step'])
  			action: [cogit singleStep: cogit singleStep not];
  		add: 'click step' action: [cogit setClickStepBreakBlock];
  		add: 'set break pc', cogit breakPC menuPrompt, '...-ve to disable or remove' action: [cogit promptForBreakPC];
  		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: 'set break block...' action: [|s| s := UIManager default request: 'break block' initialAnswer: '[:address| 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 added:
+ ----- Method: Cogit>>headFramePointer (in category '*VMMakerUI-accessing') -----
+ headFramePointer
+ 	<doNotGenerate>
+ 	^processorFrameValid
+ 		ifTrue: [processor fp]
+ 		ifFalse: [coInterpreter headFramePointer]!

Item was added:
+ ----- Method: Cogit>>headStackPointer (in category '*VMMakerUI-accessing') -----
+ headStackPointer
+ 	<doNotGenerate>
+ 	^processorFrameValid
+ 		ifTrue: [processor sp]
+ 		ifFalse: [coInterpreter headStackPointer]!

Item was added:
+ ----- Method: Cogit>>processorFrameValid (in category '*VMMakerUI-accessing') -----
+ processorFrameValid
+ 	"Answer if the processor's sp & fp are the current valid system frame pointers."
+ 	^processorFrameValid!

Item was added:
+ ----- Method: Object>>isVMObjectInspector (in category '*VMMakerUI-testing') -----
+ isVMObjectInspector
+ 	^false!

Item was added:
+ ----- Method: StackInterpreter>>headFramePointer (in category '*VMMakerUI-user interface') -----
+ headFramePointer
+ 	"Answer the framePointer for the active frame.  In the production VM all we can
+ 	 get our hands on is framePointer.  localFP is a register variable inside interpret.
+ 	 But in the simulator we have access to localFP and so this mehtod is reimplemented there-in"
+ 	<inline: #always>
+ 	^framePointer!

Item was added:
+ ----- Method: StackInterpreter>>headStackPointer (in category '*VMMakerUI-user interface') -----
+ headStackPointer
+ 	"Answer the stackPointer for the active frame.  In the production VM all we can
+ 	 get our hands on is stackPointer.  localFP is a register variable inside interpret.
+ 	 But in the simulator we have access to localFP and so this mehtod is reimplemented there-in"
+ 	<inline: #always>
+ 	^stackPointer!

Item was added:
+ ----- Method: StackInterpreterSimulator>>headFramePointer (in category '*VMMakerUI-user interface') -----
+ headFramePointer
+ 	^localFP ifNil: [framePointer]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>headStackPointer (in category '*VMMakerUI-user interface') -----
+ headStackPointer
+ 	^localFP ifNotNil: [localSP] ifNil: [stackPointer]!

Item was added:
+ ----- Method: VMObjectInspector>>coInterpreter (in category 'accessing') -----
+ coInterpreter
+ 	^coInterpreter!

Item was added:
+ ----- Method: VMObjectInspector>>isVMObjectInspector (in category 'testing') -----
+ isVMObjectInspector
+ 	^true!

Item was added:
+ ----- Method: VMObjectInspector>>objectMemory (in category 'accessing') -----
+ objectMemory
+ 	^objectMemory!



More information about the Vm-dev mailing list