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

commits at source.squeak.org commits at source.squeak.org
Tue Feb 11 19:29:33 UTC 2020


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

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

Name: VMMaker.oscog-eem.2710
Author: eem
Time: 11 February 2020, 11:29:17.203522 am
UUID: 3a20ee43-fa7a-4b52-b097-c89ac862108f
Ancestors: VMMaker.oscog-nice.2709

Cogit: remove some references to BytesPerOop in Lowcode.  There are still lots of references to BytesPerWord we would like to rewrite to objectMemory bytesPerWord.  The issue is that using the messages allows us to have 32-bit and 64-bit images open side-by-side and at least have printing working.

SitackInterpreterSimulator:
Fix a bug in endPCOf: that hence fixes symbolicMethod:
Provide a breakBlock somewhat similar to the CogVMSimulator's
Have StackInterpreterSimulator>>close close attendant debuggers a la CogVMSimulator
Update the arg name in CogVMSimulator>>setBreakBlockFromString:

=============== Diff against VMMaker.oscog-nice.2709 ===============

Item was changed:
  ----- Method: CogObjectRepresentation>>genLcPointerToOop:class: (in category 'inline primitive support') -----
  genLcPointerToOop: pointer class: pointerClass
  	<option: #LowcodeVM>
  	cogit PushR: pointer.
  	cogit annotate: (cogit MoveCw: pointerClass R: Arg0Reg) objRef: pointerClass.
+ 	cogit MoveCq: objectMemory bytesPerOop R: Arg1Reg.
- 	cogit MoveCq: BytesPerOop R: Arg1Reg.
  	cogit CallRT: ceInstantiateClassIndexableSizeTrampoline.
  
  	cogit PopR: pointer.
  	cogit MoveR: pointer Mw: BaseHeaderSize r: TempReg.
  
  	cogit MoveR: TempReg R: pointer.
  	cogit ssPushRegister: pointer.!

Item was changed:
  ----- Method: CogObjectRepresentation>>generateLowcodeObjectTrampolines (in category 'initialization') -----
  generateLowcodeObjectTrampolines
  	<option: #LowcodeVM>
  	ceFloatObjectOfTrampoline := cogit genTrampolineFor: #floatObjectOf:
  												called: 'ceFloatObjectOfTrampoline'
  												floatArg: DPFPReg0
  												result: TempReg.
  	ceFloatValueOfTrampoline := cogit genTrampolineFor: #floatValueOf:
  												called: 'ceFloatValueOfTrampoline'
  												arg: ReceiverResultReg
  												floatResult: DPFPReg0.
  	ceInstantiateClassIndexableSizeTrampoline := cogit genTrampolineFor: #instantiateClass:indexableSize:
  												called: 'ceInstantiateClassIndexableSizeTrampoline'
  												arg: Arg0Reg
  												arg: Arg1Reg
  												result: TempReg.
  	ceInstantiateClassTrampoline := cogit genTrampolineFor: #instantiateClass:indexableSize:
  												called: 'ceInstantiateClassTrampoline'
  												arg: ReceiverResultReg
  												arg: 0
  												result: TempReg.
  	ceByteSizeOfTrampoline := cogit genTrampolineFor: #byteSizeOf:
  												called: 'ceByteSizeOfTrampoline'
  												arg: Arg0Reg
  												result: TempReg.
+ 	objectMemory bytesPerOop = 4
+ 		ifTrue:
+ 			[cePositive64BitIntegerTrampoline := cogit genTrampolineFor: #positive64BitIntegerFor:
+ 														called: 'cePositive64BitIntegerTrampoline'
+ 														arg: ReceiverResultReg
+ 														arg: Arg0Reg
+ 														result: TempReg.
+ 			cePositive64BitValueOfTrampoline := cogit genTrampolineFor: #positive64BitValueOf:
+ 														called: 'cePositive64BitValueOfTrampoline'
+ 														arg: ReceiverResultReg
+ 														result: TempReg
+ 														result: Arg0Reg.
+ 			ceSigned64BitIntegerTrampoline := cogit genTrampolineFor: #signed64BitIntegerFor:
+ 														called: 'ceSigned64BitIntegerTrampoline'
+ 														arg: ReceiverResultReg
+ 														arg: Arg0Reg
+ 														result: TempReg.
+ 			ceSigned64BitValueOfTrampoline := cogit genTrampolineFor: #signed64BitValueOf:
+ 														called: 'ceSigned64BitValueOfTrampoline'
+ 														arg: ReceiverResultReg
+ 														result: TempReg
+ 														result: Arg0Reg]
+ 		ifFalse:
+ 			[cePositive64BitIntegerTrampoline := cogit genTrampolineFor: #positive64BitIntegerFor:
+ 														called: 'cePositive64BitIntegerTrampoline'
+ 														arg: ReceiverResultReg
+ 														result: TempReg.
+ 			cePositive64BitValueOfTrampoline := cogit genTrampolineFor: #positive64BitValueOf:
+ 														called: 'cePositive64BitValueOfTrampoline'
+ 														arg: ReceiverResultReg
+ 														result: TempReg.
+ 			ceSigned64BitIntegerTrampoline := cogit genTrampolineFor: #signed64BitIntegerFor:
+ 														called: 'ceSigned64BitIntegerTrampoline'
+ 														arg: ReceiverResultReg
+ 														result: TempReg.
+ 			ceSigned64BitValueOfTrampoline := cogit genTrampolineFor: #signed64BitValueOf:
+ 														called: 'ceSigned64BitValueOfTrampoline'
+ 														arg: ReceiverResultReg
+ 														result: TempReg]!
- 	BytesPerOop = 4 ifTrue: [
- 		cePositive64BitIntegerTrampoline := cogit genTrampolineFor: #positive64BitIntegerFor:
- 													called: 'cePositive64BitIntegerTrampoline'
- 													arg: ReceiverResultReg
- 													arg: Arg0Reg
- 													result: TempReg.
- 		cePositive64BitValueOfTrampoline := cogit genTrampolineFor: #positive64BitValueOf:
- 													called: 'cePositive64BitValueOfTrampoline'
- 													arg: ReceiverResultReg
- 													result: TempReg
- 													result: Arg0Reg.
- 		ceSigned64BitIntegerTrampoline := cogit genTrampolineFor: #signed64BitIntegerFor:
- 													called: 'ceSigned64BitIntegerTrampoline'
- 													arg: ReceiverResultReg
- 													arg: Arg0Reg
- 													result: TempReg.
- 		ceSigned64BitValueOfTrampoline := cogit genTrampolineFor: #signed64BitValueOf:
- 													called: 'ceSigned64BitValueOfTrampoline'
- 													arg: ReceiverResultReg
- 													result: TempReg
- 													result: Arg0Reg.
- 	] ifFalse: [
- 		cePositive64BitIntegerTrampoline := cogit genTrampolineFor: #positive64BitIntegerFor:
- 													called: 'cePositive64BitIntegerTrampoline'
- 													arg: ReceiverResultReg
- 													result: TempReg.
- 		cePositive64BitValueOfTrampoline := cogit genTrampolineFor: #positive64BitValueOf:
- 													called: 'cePositive64BitValueOfTrampoline'
- 													arg: ReceiverResultReg
- 													result: TempReg.
- 		ceSigned64BitIntegerTrampoline := cogit genTrampolineFor: #signed64BitIntegerFor:
- 													called: 'ceSigned64BitIntegerTrampoline'
- 													arg: ReceiverResultReg
- 													result: TempReg.
- 		ceSigned64BitValueOfTrampoline := cogit genTrampolineFor: #signed64BitValueOf:
- 													called: 'ceSigned64BitValueOfTrampoline'
- 													arg: ReceiverResultReg
- 													result: TempReg.
- 	]!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genLcLoadObject:field: (in category 'inline primitive support') -----
  genLcLoadObject: object field: fieldIndex
  	<option: #LowcodeVM>
+ 	cogit MoveMw: objectMemory baseHeaderSize + (objectMemory bytesPerOop * fieldIndex) r: object R: object.
- 	cogit MoveMw: 8 + (BytesPerOop*fieldIndex) r: object R: object.
  	cogit ssPushRegister: object!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genLcStore:object:field: (in category 'inline primitive support') -----
  genLcStore: value object: object field: fieldIndex
  	<option: #LowcodeVM>
+ 	cogit MoveR: value Mw: objectMemory baseHeaderSize + (fieldIndex * objectMemory bytesPerOop) r: object.!
- 	cogit MoveR: value Mw: 8 + (fieldIndex * BytesPerOop) r: object.!

Item was changed:
  ----- Method: CogSimStackNativeEntry>>stackSpillSize (in category 'accessing') -----
  stackSpillSize
  	<returnTypeC: #sqInt>
  	type caseOf: {
  		[SSConstantInt64]			-> [ ^ 8 ].
  		[SSConstantFloat64]		-> [ ^ 8 ].
  		[SSRegisterDoubleFloat]	-> [ ^ 8 ].
  		[SSRegisterPair]			-> [ ^ 8 ].
  		[SSSpillFloat64]				-> [ ^ 8 ].
  		[SSSpillInt64]				-> [ ^ 8 ].
+ 	} otherwise: [^ cogit objectMemory bytesPerOop ].
- 	} otherwise: [^ BytesPerOop ].
  	^ 0!

Item was changed:
  ----- Method: CogVMSimulator>>setBreakBlockFromString: (in category 'UI') -----
  setBreakBlockFromString: aString
  	| bString block |
  	bString := aString withBlanksTrimmed.
  	bString first = $- ifTrue:
  		[^cogit breakBlock: nil].
  	bString first ~= $[ ifTrue:
+ 		[bString := '[:_address|', bString, ']'].
- 		[bString := '[:ct|', bString, ']'].
  	block := [Compiler evaluate: bString for: self logged: false]
  				on: Error
  				do: [:ex|
  					UIManager default warn: ex messageText.
  					^self].
  	cogit breakBlock: block!

Item was added:
+ ----- Method: SimulatorHarness class>>defaultIntegerBaseInDebugger (in category 'debugger') -----
+ defaultIntegerBaseInDebugger
+ 	^VMClass defaultIntegerBaseInDebugger!

Item was changed:
  ----- Method: StackInterpreter>>internalPushShadowCallStackPointer: (in category 'internal interpreter access') -----
  internalPushShadowCallStackPointer: pointerValue
  	<option: #LowcodeVM>
  	<var: #pointerValue type: #'char*' >
  	"In the StackInterpreter stacks grow down."
+ 	shadowCallStackPointer := shadowCallStackPointer - objectMemory bytesPerOop.
- 	shadowCallStackPointer := shadowCallStackPointer - BytesPerOop.
  
  	"In the StackInterpreter stacks grow down."
  	stackPages pointerAtPointer: shadowCallStackPointer put: pointerValue!

Item was changed:
  StackInterpreterPrimitives subclass: #StackInterpreterSimulator
+ 	instanceVariableNames: 'parent bootstrapping byteCount breakCount sendCount lookupCount printSends printReturns traceOn myBitBlt displayForm fakeForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES primTraceLog breakBlock'
- 	instanceVariableNames: 'parent bootstrapping byteCount breakCount sendCount lookupCount printSends printReturns traceOn myBitBlt displayForm fakeForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES primTraceLog'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
  
  !StackInterpreterSimulator commentStamp: 'eem 9/3/2013 11:05' prior: 0!
  This class defines basic memory access and primitive simulation so that the StackInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(StackInterpreterSimulator new openOn: Smalltalk imageName) test
  
  	((StackInterpreterSimulator newWithOptions: #(NewspeakVM true MULTIPLEBYTECODESETS true))
  		openOn: 'ns101.image') test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example of what Eliot uses to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  | vm |
  vm := StackInterpreterSimulator newWithOptions: #().
  vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
  vm setBreakSelector: #&.
  vm openAsMorph; run!

Item was added:
+ ----- Method: StackInterpreterSimulator>>breakBlock (in category 'debug support') -----
+ breakBlock
+ 	^breakBlock!

Item was added:
+ ----- Method: StackInterpreterSimulator>>breakBlock: (in category 'debug support') -----
+ breakBlock: aBlockOrNil
+ 	breakBlock := aBlockOrNil!

Item was changed:
  ----- Method: StackInterpreterSimulator>>close (in category 'initialization') -----
  close  "close any files that ST may have opened, etc"
+ 	pluginList do: [:assoc| | plugin | plugin := assoc value. plugin ~~ self ifTrue: [plugin close]].
+ 	"Ugh; at least some of this code belongs in the UI..."
+ 	World submorphs do:
+ 		[:submorph|
+ 		(submorph model isVMObjectInspector
+ 		 and: [submorph model coInterpreter == self]) ifTrue:
+ 			[submorph delete].
+ 		(submorph model isDebugger
+ 		 and: [(submorph model interruptedProcess suspendedContext findContextSuchThat:
+ 					[:ctxt|
+ 					 ctxt receiver == self
+ 					 and: [ctxt selector == #run]]) notNil]) ifTrue:
+ 			[submorph model windowIsClosing.
+ 			 submorph delete]]!
- 	pluginList do: [:assoc| | plugin | plugin := assoc value. plugin ~~ self ifTrue: [plugin close]]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>endPCOf: (in category 'compiled methods') -----
  endPCOf: aMethod
  	"Determine the endPC of a method in the heap using interpretation that looks for returns and uses branches to skip intervening bytecodes."
  	| pc end farthestContinuation prim encoderClass inst is |
  	(prim := self primitiveIndexOf: aMethod) > 0 ifTrue:
  		[(self isQuickPrimitiveIndex: prim) ifTrue:
  			[^(self startPCOfMethod: aMethod) - 1]].
  	encoderClass := self encoderClassForHeader: (objectMemory methodHeaderOf: aMethod).
  	is := (InstructionStream
  			on: (VMCompiledMethodProxy new
  					for: aMethod
  					coInterpreter: self
  					objectMemory: objectMemory)).
  	pc := farthestContinuation := self startPCOfMethod: aMethod.
  	end := objectMemory numBytesOf: aMethod.
  	is pc: pc + 1.
  	[pc <= end] whileTrue:
  		[inst := encoderClass interpretNextInstructionFor: MessageCatcher new in: is.
+ 		 pc := is pc - 1.
  		 inst selector
  			caseOf: {
  				 [#pushClosureCopyNumCopiedValues:numArgs:blockSize:]	
  											->	[is pc: is pc + inst arguments last.
  												 farthestContinuation := farthestContinuation max: pc].
  				 [#jump:]					->	[farthestContinuation := farthestContinuation max: pc + inst arguments first].
  				 [#jump:if:]					->	[farthestContinuation := farthestContinuation max: pc + inst arguments first].
+ 				 [#methodReturnConstant:]	->	[pc > farthestContinuation ifTrue: [end := pc]].
+ 				 [#methodReturnReceiver]	->	[pc > farthestContinuation ifTrue: [end := pc]].
+ 				 [#methodReturnTop]		->	[pc > farthestContinuation ifTrue: [end := pc]].
- 				 [#methodReturnConstant:]	->	[pc >= farthestContinuation ifTrue: [end := pc]].
- 				 [#methodReturnReceiver]	->	[pc >= farthestContinuation ifTrue: [end := pc]].
- 				 [#methodReturnTop]		->	[pc >= farthestContinuation ifTrue: [end := pc]].
  				"This is for CompiledBlock/FullBlockClosure.  Since the response to pushClosure... above
  				 skips over all block bytecoes, we will only see a blockReturnTop if it is at the top level,
  				 and so it must be a blockReturnTop in a CompiledBlock for a FullBlockClosure."
+ 				 [#blockReturnTop]			->	[pc > farthestContinuation ifTrue: [end := pc]].
- 				 [#blockReturnTop]			->	[pc >= farthestContinuation ifTrue: [end := pc]].
  				 [#branchIfInstanceOf:distance:]
  											->	[farthestContinuation := farthestContinuation max: pc + inst arguments last].
  				 [#branchIfNotInstanceOf:distance:]
  											->	[farthestContinuation := farthestContinuation max: pc + inst arguments last] }
+ 			otherwise: []].
+ 	^end - 1!
- 			otherwise: [].
- 		 pc := is pc - 1].
- 	^end!

Item was changed:
  ----- Method: StackInterpreterSimulator>>ensureDebugAtEachStepBlock (in category 'testing') -----
  ensureDebugAtEachStepBlock
  	atEachStepBlock := [printFrameAtEachStep ifTrue:
  							[self printFrame: localFP WithSP: localSP].
  						 printBytecodeAtEachStep ifTrue:
  							[self printCurrentBytecodeOn: transcript.
  							 transcript cr; flush].
  						 byteCount = breakCount ifTrue:
+ 							["printFrameAtEachStep :=" printBytecodeAtEachStep := true].
+ 						 breakBlock ifNotNil:
+ 							[breakBlock value ifTrue: [self halt]]]!
- 							["printFrameAtEachStep :=" printBytecodeAtEachStep := true]]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>setBreakBlockFromString: (in category 'debug support') -----
+ setBreakBlockFromString: aString
+ 	| bString block |
+ 	bString := aString withBlanksTrimmed.
+ 	bString first = $- ifTrue:
+ 		[^self breakBlock: nil].
+ 	bString first ~= $[ ifTrue:
+ 		[bString := '[:_address|', bString, ']'].
+ 	block := [Compiler evaluate: bString for: self logged: false]
+ 				on: Error
+ 				do: [:ex|
+ 					UIManager default warn: ex messageText.
+ 					^self].
+ 	self breakBlock: block!



More information about the Vm-dev mailing list