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

commits at source.squeak.org commits at source.squeak.org
Tue Mar 18 21:18:43 UTC 2014


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

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

Name: VMMaker.oscog-eem.645
Author: eem
Time: 18 March 2014, 2:16:19.323 pm
UUID: ae96679e-8754-455f-9cf3-4cb0f631d85a
Ancestors: VMMaker.oscog-eem.644

In the interests of pushing the lemming over the cliff, mak the
FilePluginSimulator correctly reopen its files after a snapshot,
restoring them to their previous position, etc.

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

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulation;
  		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 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]];
  		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 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: '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'.
  											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:
  FilePlugin subclass: #FilePluginSimulator
+ 	instanceVariableNames: 'openFiles states'
- 	instanceVariableNames: 'openFiles'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
  
  !FilePluginSimulator commentStamp: 'tpr 5/5/2003 12:02' prior: 0!
  File plugin simulation for the VM simulator!

Item was changed:
  ----- Method: FilePluginSimulator>>fileValueOf: (in category 'simulation') -----
  fileValueOf: objectPointer
+ 	| index file |
- 	| index |
  	index := (interpreterProxy isIntegerObject: objectPointer)
  				ifTrue: [interpreterProxy integerValueOf: objectPointer]
  				ifFalse:
  					[((interpreterProxy isBytes: objectPointer)
  					  and: [(interpreterProxy byteSizeOf: objectPointer) = BytesPerWord]) ifFalse:
  						[interpreterProxy primitiveFail.
  						 ^nil].
  					interpreterProxy longAt: objectPointer + BaseHeaderSize].
+ 	file := openFiles at: index.
+ 	"this attempts to preserve file positions across snapshots when debugging the VM
+ 	 requires saving an image in full flight and pushing it over the cliff time after time..."
+ 	(file closed and: [states includesKey: file]) ifTrue:
+ 		[[:pos :isBinary|
+ 		  file reopen; position: pos.
+ 		  isBinary ifTrue:
+ 			[file binary]] valueWithArguments: (states at: file)].
+ 	^file!
- 	^openFiles at: index!

Item was changed:
  ----- Method: FilePluginSimulator>>initialiseModule (in category 'initialize-release') -----
  initialiseModule
  	"See FilePluginSimulator>>sqFileStdioHandlesInto:"
  	(openFiles := Dictionary new)
  		at: 0 put: (FakeStdinStream for: interpreterProxy interpreter); "stdin"
  		at: 1 put: Transcript; "stdout"
  		at: 2 put: Transcript. "stderr"
+ 	states := IdentityDictionary new.
  	^super initialiseModule!

Item was added:
+ ----- Method: FilePluginSimulator>>recordStateOf: (in category 'simulation') -----
+ recordStateOf: file
+ 	([file position]
+ 			on: Error
+ 			do: [:ex| nil]) ifNotNil:
+ 		[:position|
+ 		states at: file put: {position. file isBinary}]!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFile:Read:Into:At: (in category 'simulation') -----
  sqFile: file Read: count Into: byteArrayIndex At: startIndex
  	| interpreter |
  	interpreter := interpreterProxy interpreter.
  	startIndex to: startIndex + count - 1 do:
  		[ :i |
  		file atEnd ifTrue: [^i - startIndex].
  		interpreter byteAt: byteArrayIndex + i put: file next asInteger].
+ 	self recordStateOf: file.
  	^count!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFile:SetPosition: (in category 'simulation') -----
  sqFile: file SetPosition: newPosition
+ 	file position: newPosition.
+ 	self recordStateOf: file!
- 	file position: newPosition!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFile:Truncate: (in category 'simulation') -----
  sqFile: file Truncate: truncatePosition
+ 	file truncate: truncatePosition.
+ 	self recordStateOf: file!
- 	file truncate: truncatePosition!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFile:Write:From:At: (in category 'simulation') -----
  sqFile: file Write: count From: byteArrayIndex At: startIndex
  	| interpreter |
  	interpreter := interpreterProxy interpreter.
  	file isBinary
  		ifTrue:
  			[startIndex to: startIndex + count - 1 do:
  				[ :i | file nextPut: (interpreter byteAt: byteArrayIndex + i)]]
  		ifFalse:
  			[startIndex to: startIndex + count - 1 do:
  				[ :i | | byte |
  				byte := interpreter byteAt: byteArrayIndex + i.
  				file nextPut: (Character value: (byte == 12 "lf" ifTrue: [15"cr"] ifFalse: [byte]))]].
+ 	self recordStateOf: file.
  	^count!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFileClose: (in category 'simulation') -----
  sqFileClose: file
+ 	file close.
+ 	self recordStateOf: file!
- 	file close!



More information about the Vm-dev mailing list