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

commits at source.squeak.org commits at source.squeak.org
Sun Apr 26 01:53:22 UTC 2020


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

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

Name: VMMaker.oscog-eem.2745
Author: eem
Time: 25 April 2020, 6:53:02.146876 pm
UUID: 8a9b863d-7a2a-49f7-8856-61b563e34732
Ancestors: VMMaker.oscog-eem.2744

Simulation: Simplify handleCallOrJumpSimulationTrap:; it has no business knowing whether a control transfer was initiated by a jump or a call.  What matters is what the target choses to do (this after pairing with Boris; thanks).  Consequently simplify simulateEnilopmart:numArgs:.  Move the primitives not to be checked for a consistent stack on success to their own collection, as a micro-optimisation yes, but more importantly to name them.

Fix a few sends of splObj: and one of integerObjectOf: which should be to objectMemory.

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

Item was changed:
  ----- Method: CoInterpreter>>sendInvokeCallback:Stack:Registers:Jmpbuf: (in category 'callback support') -----
  sendInvokeCallback: thunkPtr Stack: stackPtr Registers: regsPtr Jmpbuf: jmpBufPtr
  	"Override to log and check stack alignment.  Since this is an implicit send we need to
  	 log it explicitly. The return side is done via a primitive so that gets logged normally."
  	cogit assertCStackWellAligned.
  	cogit recordPrimTrace ifTrue:
+ 		[self fastLogPrim: (objectMemory splObj: SelectorInvokeCallback)].
- 		[self fastLogPrim: (self splObj: SelectorInvokeCallback)].
  	^super sendInvokeCallback: thunkPtr Stack: stackPtr Registers: regsPtr Jmpbuf: jmpBufPtr!

Item was changed:
  ----- Method: CoInterpreter>>sendInvokeCallbackContext: (in category 'callback support') -----
  sendInvokeCallbackContext: vmCallbackContext
  	"Override to log and check stack alignment.  Since this is an implicit send we need to
  	 log it explicitly. The return side is done via a primitive so that gets logged normally."
  	cogit assertCStackWellAligned.
  	cogit recordPrimTrace ifTrue:
+ 		[self fastLogPrim: (objectMemory splObj: SelectorInvokeCallback)].
- 		[self fastLogPrim: (self splObj: SelectorInvokeCallback)].
  	^super sendInvokeCallbackContext: vmCallbackContext!

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
  	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue effectiveCogCodeSize expectedSends expecting'
+ 	classVariableNames: 'ByteCountsPerMicrosecond ExpectedSends NLRFailures NLRSuccesses StackAlteringPrimitives'
- 	classVariableNames: 'ByteCountsPerMicrosecond ExpectedSends NLRFailures NLRSuccesses'
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' prior: 0!
  This class defines basic memory access and primitive simulation so that the CoInterpreter 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.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(CogVMSimulator new openOn: Smalltalk imageName) 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 to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  	desiredNumStackPages: 8;
  	openOn: '/Users/eliot/Cog/startreader.image';
  	openAsMorph;
  	run
  
  Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
  
  | cos proc opts |
  CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
  CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
  cos := CogVMSimulator new.
  "cos initializeThreadSupport." "to test the multi-threaded VM"
  cos desiredNumStackPages: 8. "to set the size of the stack zone"
  "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
  cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
  "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
  proc := cos cogit processor.
  "cos cogit sendTrace: 7." "turn on tracing"
  "set a complex breakpoint at a specific point in machine code"
  "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
  "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
  "cos cogit setBreakMethod: 16rB38880."
  cos
  	openAsMorph;
  	"toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
  	halt;
  	run!

Item was added:
+ ----- Method: CogVMSimulator class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"These are primtiives that alter the state of the stack.  They are here simply for assert checking.
+ 	 After invocation the Cogit should not check for the expected stack delta when these primitives
+ 	 succeed, because the stack will usually have been modified."
+ 	StackAlteringPrimitives := #(	primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
+ 									primitiveEnterCriticalSection primitiveExitCriticalSection
+ 									primitiveFullClosureValue primitiveFullClosureValueWithArgs primitiveFullClosureValueNoContextSwitch
+ 									primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
+ 									primitiveExecuteMethodArgsArray primitiveExecuteMethod
+ 									primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
+ 									primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs) asIdentitySet!

Item was added:
+ ----- Method: CogVMSimulator class>>stackAlteringPrimitives (in category 'accessing') -----
+ stackAlteringPrimitives
+ 	^StackAlteringPrimitives!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
+ 	| evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount retpc |
- 	| evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount leaf retpc |
  	evaluable := simulatedTrampolines
  					at: aProcessorSimulationTrap address
  					ifAbsent: [self errorProcessingSimulationTrap: aProcessorSimulationTrap
  								in: simulatedTrampolines].
  	function := evaluable isBlock
  					ifTrue: ['aBlock; probably some plugin primitive']
  					ifFalse:
  						[evaluable receiver == backEnd ifTrue:
  							[^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
  						 evaluable selector].
  	function ~~ #ceBaseFrameReturn: ifTrue:
  		[coInterpreter assertValidExternalStackPointers].
  	(backEnd wantsNearAddressFor: function) ifTrue:
  		[^self perform: function with: aProcessorSimulationTrap].
  	memory := coInterpreter memory.
+ 	processor
+ 		simulateCallOf: aProcessorSimulationTrap address
+ 		nextpc: aProcessorSimulationTrap nextpc
+ 		memory: memory.
+ 	retpc := processor retpcIn: memory.
+ 	self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}.
- 	aProcessorSimulationTrap type == #call
- 		ifTrue:
- 			[(leaf := coInterpreter mcprims includes: function)
- 				ifTrue:
- 					[processor
- 						simulateLeafCallOf: aProcessorSimulationTrap address
- 						nextpc: aProcessorSimulationTrap nextpc
- 						memory: memory.
- 					 retpc := processor leafRetpcIn: memory]
- 				ifFalse:
- 					[processor
- 						simulateCallOf: aProcessorSimulationTrap address
- 						nextpc: aProcessorSimulationTrap nextpc
- 						memory: memory.
- 					 retpc := processor retpcIn: memory].
- 			 self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
- 		ifFalse:
- 			[leaf := false.
- 			 processor
- 				simulateJumpCallOf: aProcessorSimulationTrap address
- 				memory: memory.
- 			 retpc := processor retpcIn: memory. "sideways call; the primitive has pushed a return address."
- 			 self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
  	function == #interpret ifTrue: "i.e. we're here via ceInvokeInterpret and should discard all state back to enterSmalltalkExecutiveImplementation"
  		[coInterpreter reenterInterpreter].
  	savedFramePointer := coInterpreter framePointer.
  	savedStackPointer := coInterpreter stackPointer.
  	savedArgumentCount := coInterpreter argumentCount.
  	result := ["self halt: evaluable selector."
  		   	   clickConfirm ifTrue:
  			 	[(self confirm: 'skip run-time call?') ifFalse:
  					[clickConfirm := false. self halt]].
  			   evaluable valueWithArguments: (processor
  												postCallArgumentsNumArgs: evaluable numArgs
  												in: memory)]
  				on: ReenterMachineCode
+ 				do: [:ex| ex return: #continueNoReturn].
- 				do: [:ex| ex return: ex returnValue].
  			
  	coInterpreter assertValidExternalStackPointers.
  	"Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  	 not called something that has built a frame, such as closure value or evaluate method, or
  	 switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  	(function beginsWith: 'primitive') ifTrue:
  		[coInterpreter primFailCode = 0
+ 			ifTrue: [(CogVMSimulator stackAlteringPrimitives includes: function) ifFalse:
- 			ifTrue: [(#(	primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
- 						primitiveFullClosureValue primitiveFullClosureValueWithArgs primitiveFullClosureValueNoContextSwitch
- 						primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
- 						primitiveExecuteMethodArgsArray primitiveExecuteMethod
- 						primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
- 						primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs)
- 							includes: function) ifFalse:
  						["This is a rare case (e.g. in Scorch where a married context's sender is set to nil on trapTrpped and hence the stack layout is altered."
  						 (function == #primitiveSlotAtPut and: [objectMemory isContext: (coInterpreter frameReceiver: coInterpreter framePointer)]) ifFalse:
  							[self assert: savedFramePointer = coInterpreter framePointer.
  							 self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize)
  									= coInterpreter stackPointer]]]
  			ifFalse:
  				[self assert: savedFramePointer = coInterpreter framePointer.
  				 self assert: savedStackPointer = coInterpreter stackPointer]].
  	result ~~ #continueNoReturn ifTrue:
  		[self recordInstruction: {'(simulated return to '. processor retpcIn: memory. ')'}.
+ 		 processor simulateReturnIn: memory.
- 		 leaf
- 			ifTrue: [processor simulateLeafReturnIn: memory]
- 			ifFalse: [processor simulateReturnIn: memory].
  		 self assert: processor pc = retpc.
  		 processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory].
  	self assert: (result isInteger "an oop result"
  			or: [result == coInterpreter
  			or: [result == objectMemory
+ 			or: [result == nil
+ 			or: [result == #continueNoReturn]]]]).
- 			or: [#(nil continue continueNoReturn) includes: result]]]).
  	processor cResultRegister: (result
+ 								ifNil: [0]
+ 								ifNotNil: [result isInteger
+ 											ifTrue: [result]
+ 											ifFalse: [16rF00BA222]])!
- 							ifNil: [0]
- 							ifNotNil: [result isInteger
- 										ifTrue: [result]
- 										ifFalse: [16rF00BA222]])
- 
- 	"coInterpreter cr.
- 	 processor sp + 32 to: processor sp - 32 by: -4 do:
- 		[:sp|
- 		 sp = processor sp
- 			ifTrue: [coInterpreter print: 'sp->'; tab]
- 			ifFalse: [coInterpreter printHex: sp].
- 		 coInterpreter tab; printHex: (coInterpreter longAt: sp); cr]"!

Item was changed:
  ----- Method: Cogit>>simulateEnilopmart:numArgs: (in category 'simulation only') -----
  simulateEnilopmart: enilopmartAddress numArgs: n
  	<doNotGenerate>
  	"Enter Cog code, popping the class reg and receiver from the stack
  	 and then returning to the address beneath them.
  	 In the actual VM the enilopmart is a function pointer and so senders
  	 of this method end up calling the enilopmart to enter machine code.
  	 In simulation we either need to start simulating execution (if we're in
  	 the interpreter) or return to the simulation (if we're in the run-time
  	 called from machine code. We should also smash the register state
  	 since, being an abnormal entry, no saved registers will be restored."
  	self assert: (coInterpreter isOnRumpCStack: processor sp).
  	self assert: (n = 0 or: [(coInterpreter stackValue: n) between: guardPageSize and: methodZone freeStart - 1]).
  	(printInstructions or: [printRegisters]) ifTrue:
  		[coInterpreter printExternalHeadFrame].
  	processor
  		smashRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
  		simulateLeafCallOf: enilopmartAddress
  		nextpc: 16rBADF00D
  		memory: coInterpreter memory.
  	"If we're already simulating in the context of machine code then
  	 this will take us back to handleCallSimulationTrap:.  Otherwise
  	 start executing machine code in the simulator."
+ 	ReenterMachineCode new signal.
- 	(ReenterMachineCode new returnValue: #continueNoReturn) signal.
  	self simulateCogCodeAt: enilopmartAddress.
  	"We should either longjmp back to the interpreter or
  	 stay in machine code so control should not reach here."
  	self assert: false!

Item was changed:
  ----- Method: StackInterpreter>>cannotAssign:to:withIndex: (in category 'stack bytecodes') -----
  cannotAssign: resultObj to: targetObj withIndex: index
  	<option: #IMMUTABILITY>
  	<inline: true> "because of use of normalSend..."
  	self internalPush: targetObj.
  	self internalPush: resultObj.
+ 	self internalPush: (objectMemory integerObjectOf: index + 1).
+ 	messageSelector := objectMemory splObj: SelectorAttemptToAssign.
- 	self internalPush: (self integerObjectOf: index + 1).
- 	messageSelector := self splObj: SelectorAttemptToAssign.
  	argumentCount := 2.
  	^ self normalSend!

Item was changed:
  ----- Method: StackInterpreter>>sendInvokeCallback:Stack:Registers:Jmpbuf: (in category 'callback support') -----
  sendInvokeCallback: thunkPtr Stack: stackPtr Registers: regsPtr Jmpbuf: jmpBufPtr
  	"Send the 4 argument callback message invokeCallback:stack:registers:jmpbuf:
  	 to Alien class with the supplied args.  The arguments are raw C addresses
  	 and are converted to integer objects on the way."
  	<export: true>
  	| classTag |
+ 	classTag := self fetchClassTagOfNonImm: (objectMemory splObj: ClassAlien).
- 	classTag := self fetchClassTagOfNonImm: (self splObj: ClassAlien).
  	messageSelector := self splObj: SelectorInvokeCallback.
  	argumentCount := 4.
  	(self lookupInMethodCacheSel: messageSelector classTag: classTag) ifFalse:
  	 	[(self lookupOrdinaryNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  			[^false]].
  	((self argumentCountOf: newMethod) = 4
  	and: [primitiveFunctionPointer = 0]) ifFalse:
  		[^false].
  	self push: (self splObj: ClassAlien). "receiver"
  	self push: (self positiveMachineIntegerFor: thunkPtr).
  	self push: (self positiveMachineIntegerFor: stackPtr).
  	self push: (self positiveMachineIntegerFor: regsPtr).
  	self push: (self positiveMachineIntegerFor: jmpBufPtr).
  	self ifAppropriateCompileToNativeCode: newMethod selector: messageSelector.
  	self justActivateNewMethod: false. "either interpreted or machine code"
  	(self isMachineCodeFrame: framePointer) ifFalse:
  		[self maybeFlagMethodAsInterpreted: newMethod].
  	self checkForStackOverflow.
  	self enterSmalltalkExecutiveFromCallback.
  	"not reached"
  	^true!



More information about the Vm-dev mailing list