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

commits at source.squeak.org commits at source.squeak.org
Mon Dec 9 22:37:29 UTC 2013


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

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

Name: VMMaker.oscog-eem.551
Author: eem
Time: 9 December 2013, 2:34:05.721 pm
UUID: f898f520-c8dd-4413-8282-f13bbf1e0438
Ancestors: VMMaker.oscog-eem.550

Fix bug in StackToRegisterMappingCogit>>generateEnilopmarts
that set up the pic entry enilopmarts incorrectly with 2 reg args.

Refactor numRegArgs to defer to the obj rep.

Rename executeCogMethodFromLinkedSend:withReceiver: et al to
executeCogMethod:fromLinkedSendWithReceiver: et al.

Fix the bogus memory layout assumptions in senders of
lookup:for:methodAndErrorSelectorInto:.

Don't use cogit numRegArgs > 0 and: [...] to allow Slang to do its
dead code removal thang.

Do a better job of decorating the recent instructions report.

Make CogObjectRepresentationForSpur use 2 reg args.

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

Item was changed:
  ----- Method: CoInterpreter>>activateCoggedNewMethod: (in category 'message sending') -----
  activateCoggedNewMethod: inInterpreter
  	"Activate newMethod when newMethod has been cogged, i.e. create a machine-code frame and (re)enter machine-code."
  	| methodHeader cogMethod rcvr numTemps errorCode switched |
  	<var: #cogMethod type: #'CogMethod *'>
  
  	methodHeader := self rawHeaderOf: newMethod.
  	self assert: (self isCogMethodReference: methodHeader).
  
  	cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  	methodHeader := cogMethod methodHeader.
  	rcvr := self stackValue: cogMethod cmNumArgs. "could new rcvr be set at point of send?"
  	self push: instructionPointer.
  	cogMethod stackCheckOffset = 0 ifTrue:
  		["frameless method; nothing to activate..."
+ 		 cogit numRegArgs > 0 ifTrue: "dont use and: so as to get Slang to inline cogit numRegArgs > 0"
+ 			[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
+ 				[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
- 		(cogit numRegArgs > 0
- 		 and: [cogMethod cmNumArgs <= cogit numRegArgs]) ifTrue:
- 			[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr].
  		 self push: cogMethod asInteger + cogit noCheckEntryOffset.
  		 self push: rcvr.
  		 cogit ceEnterCogCodePopReceiverReg.
  		 self error: 'should not be reached'].
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: cogMethod asInteger.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	cogMethod cmNumArgs + 1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		[| initialPC |
  		 "Store the error code if the method starts with a long store temp.  No instructionPointer skip because we're heading for machine code."
  		 initialPC := (self initialPCForHeader: methodHeader method: newMethod) + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[(objectMemory byteAt: initialPC) = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	stackPointer >= stackLimit ifTrue:
  		[self assert: cogMethod stackCheckOffset > cogit noCheckEntryOffset.
  		 self push: cogMethod asInteger + cogMethod stackCheckOffset.
  		 self push: rcvr.
  		 cogit ceEnterCogCodePopReceiverReg.
  		 self error: 'should not be reached'].
  	instructionPointer := cogMethod asInteger + cogMethod stackCheckOffset.
  	switched := self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was changed:
  ----- Method: CoInterpreter>>ceInterpretMethodFromPIC:receiver: (in category 'trampolines') -----
  ceInterpretMethodFromPIC: aMethodObj receiver: rcvr
  	<api>
  	| pic primitiveIndex |
  	<var: #pic type: #'CogMethod *'>
  	self assert: (self methodHasCogMethod: aMethodObj) not.
  	"pop off inner return and locate open PIC"
  	pic := self cCoerceSimple: self popStack - cogit interpretOffset to: #'CogMethod *'.
  	self assert: (pic cmType = CMOpenPIC or: [pic cmType = CMClosedPIC]).
  	"If found from an open PIC then it must be an uncogged method and, since it's been found
  	 in the method cache, should be cogged if possible.  If found from a closed PIC it should
  	 be interpreted (since being reached by that route implies it is uncoggable)."
  	pic cmType = CMOpenPIC
  		ifTrue:
  			[(self methodShouldBeCogged: aMethodObj) ifTrue:
  				[cogit cog: aMethodObj selector: pic selector.
  				 (self methodHasCogMethod: aMethodObj) ifTrue:
+ 					[self executeCogMethod: (self cogMethodOf: aMethodObj)
+ 						fromUnlinkedSendWithReceiver: rcvr]]]
- 					[self executeCogMethodFromUnlinkedSend: (self cogMethodOf: aMethodObj)
- 						withReceiver: rcvr]]]
  		ifFalse:
  			[self assert: (cogCompiledCodeCompactionCalledFor
  						or: [(cogit methodShouldBeCogged: aMethodObj) not])].
  	messageSelector := pic selector.
  	newMethod := aMethodObj.
  	primitiveIndex := self primitiveIndexOf: aMethodObj.
  	primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: objectMemory nilObject.
  	argumentCount := pic cmNumArgs.
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceMNUFromPICMNUMethod:receiver: (in category 'trampolines') -----
  ceMNUFromPICMNUMethod: aMethodObj receiver: rcvr
  	<api>
  	| cPIC primitiveIndex |
  	<var: #cPIC type: #'CogMethod *'>
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self assert: (aMethodObj = 0
  				or: [(objectMemory addressCouldBeObj: aMethodObj)
  					and: [objectMemory isOopCompiledMethod: aMethodObj]]).
  	cPIC := self cCoerceSimple: self popStack - cogit mnuOffset to: #'CogMethod *'.
  	self assert: cPIC cmType = CMClosedPIC.
  	argumentCount := cPIC cmNumArgs.
  	messageSelector := cPIC selector.
  	aMethodObj ~= 0 ifTrue:
  		[instructionPointer := self popStack.
  		self createActualMessageTo: (objectMemory fetchClassOf: rcvr).
  		(self maybeMethodHasCogMethod: aMethodObj) ifTrue:
  			[self push: instructionPointer.
+ 			 self executeCogMethod: (self cogMethodOf: aMethodObj)
+ 				 fromUnlinkedSendWithReceiver: rcvr.
- 			 self executeCogMethodFromUnlinkedSend: (self cogMethodOf: aMethodObj)
- 				 withReceiver: rcvr.
  			 "NOTREACHED"
  			 self assert: false].
  		newMethod := aMethodObj.
  		primitiveIndex := self primitiveIndexOf: aMethodObj.
  		primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: objectMemory nilObject.
  		^self interpretMethodFromMachineCode].
  	self handleMNU: SelectorDoesNotUnderstand
  		InMachineCodeTo: rcvr
  		classForMessage: (objectMemory fetchClassOf: rcvr).
  	"NOTREACHED"
  	self assert: false!

Item was added:
+ ----- Method: CoInterpreter>>executeCogMethod:fromLinkedSendWithReceiver: (in category 'enilopmarts') -----
+ executeCogMethod: cogMethod fromLinkedSendWithReceiver: rcvr
+ 	<api>
+ 	"Execute a CogMethod from a linked send.  The receiver,
+ 	 arguments and return address are on the Smalltalk stack.  First
+ 	 push the entry-point and finally the register argument(s).  Then write
+ 	 back the frame pointers and call the routine that will pop off the register
+ 	 argument(s) and jump to the entry by executing a return instruction.
+ 
+ 	 In the simple jit only the receiver gets passed in registers, so only the
+ 	 receiver gets pushed."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	cogit assertCStackWellAligned.
+ 	self assert: (self isMachineCodeFrame: framePointer).
+ 	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
+ 	cogit numRegArgs > 0 ifTrue: "dont use and: so as to get Slang to inline cogit numRegArgs > 0"
+ 		[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
+ 			[self enterRegisterArgCogMethod: cogMethod at: cogit entryOffset receiver: rcvr]].
+ 	self
+ 		push: cogMethod asInteger + cogit entryOffset;
+ 		push: rcvr.
+ 	cogit ceEnterCogCodePopReceiverReg
+ 	"NOTREACHED"!

Item was added:
+ ----- Method: CoInterpreter>>executeCogMethod:fromLinkedSendWithReceiver:andCacheTag: (in category 'enilopmarts') -----
+ executeCogMethod: cogMethod fromLinkedSendWithReceiver: rcvr andCacheTag: cacheTag
+ 	<api>
+ 	"Execute a CogMethod from a linked send.  The receiver,
+ 	 arguments and return address are on the Smalltalk stack.  First
+ 	 push the entry-point and finally the register argument(s).  Then write
+ 	 back the frame pointers and call the routine that will pop off the register
+ 	 argument(s) and jump to the entry by executing a return instruction.
+ 
+ 	 In the simple jit only the receiver gets passed in registers, so only the
+ 	 receiver gets pushed."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	cogit assertCStackWellAligned.
+ 	self assert: (self isMachineCodeFrame: framePointer).
+ 	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
+ 	self push: cogMethod asInteger + cogit entryOffset.
+ 	cogit numRegArgs > 0 ifTrue:"dont use and: so as to get Slang to inline cogit numRegArgs > 0"
+ 		[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
+ 			[self push: cacheTag.
+ 			 cogMethod cmNumArgs caseOf: {
+ 				[0]	->	[cogit ceEnter0ArgsPIC].
+ 				[1]	->	[cogit ceEnter1ArgsPIC].
+ 				[2]	->	[cogit ceEnter2ArgsPIC]
+ 			 	}
+ 				otherwise: [].
+ 			 self error: 'not reached']].
+ 	self
+ 		push: rcvr;
+ 		push: cacheTag.
+ 	cogit ceEnterCogCodePopReceiverAndClassRegs
+ 	"NOTREACHED"!

Item was added:
+ ----- Method: CoInterpreter>>executeCogMethod:fromUnlinkedSendWithReceiver: (in category 'enilopmarts') -----
+ executeCogMethod: cogMethod fromUnlinkedSendWithReceiver: rcvr
+ 	"Execute a CogMethod from an unlinked send.  The receiver,
+ 	 arguments and return address are on the Smalltalk stack.  First
+ 	 push the entry-point and finally the register argument(s).  Then write
+ 	 back the frame pointers and call the routine that will pop off the register
+ 	 argument(s) and jump to the entry by executing a return instruction.
+ 
+ 	 In the simple jit only the receiver gets passed in registers, so only the
+ 	 receiver gets pushed."
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	cogit assertCStackWellAligned.
+ 	self assert: (self isMachineCodeFrame: framePointer).
+ 	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
+ 	cogit numRegArgs > 0 ifTrue: "dont use and: so as to get Slang to inline cogit numRegArgs > 0"
+ 		[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
+ 			[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
+ 	self
+ 		push: cogMethod asInteger + cogit noCheckEntryOffset;
+ 		push: rcvr.
+ 	cogit ceEnterCogCodePopReceiverReg
+ 	"NOTREACHED"!

Item was removed:
- ----- Method: CoInterpreter>>executeCogMethodFromLinkedSend:withReceiver: (in category 'enilopmarts') -----
- executeCogMethodFromLinkedSend: cogMethod withReceiver: rcvr
- 	<api>
- 	"Execute a CogMethod from a linked send.  The receiver,
- 	 arguments and return address are on the Smalltalk stack.  First
- 	 push the entry-point and finally the register argument(s).  Then write
- 	 back the frame pointers and call the routine that will pop off the register
- 	 argument(s) and jump to the entry by executing a return instruction.
- 
- 	 In the simple jit only the receiver gets passed in registers, so only the
- 	 receiver gets pushed."
- 	<var: #cogMethod type: #'CogMethod *'>
- 	cogit assertCStackWellAligned.
- 	self assert: (self isMachineCodeFrame: framePointer).
- 	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
- 	(cogit numRegArgs > 0
- 	 and: [cogMethod cmNumArgs <= cogit numRegArgs]) ifTrue:
- 		[self enterRegisterArgCogMethod: cogMethod at: cogit entryOffset receiver: rcvr].
- 	self
- 		push: cogMethod asInteger + cogit entryOffset;
- 		push: rcvr.
- 	cogit ceEnterCogCodePopReceiverReg
- 	"NOTREACHED"!

Item was removed:
- ----- Method: CoInterpreter>>executeCogMethodFromLinkedSend:withReceiver:andCacheTag: (in category 'enilopmarts') -----
- executeCogMethodFromLinkedSend: cogMethod withReceiver: rcvr andCacheTag: cacheTag
- 	<api>
- 	"Execute a CogMethod from a linked send.  The receiver,
- 	 arguments and return address are on the Smalltalk stack.  First
- 	 push the entry-point and finally the register argument(s).  Then write
- 	 back the frame pointers and call the routine that will pop off the register
- 	 argument(s) and jump to the entry by executing a return instruction.
- 
- 	 In the simple jit only the receiver gets passed in registers, so only the
- 	 receiver gets pushed."
- 	<var: #cogMethod type: #'CogMethod *'>
- 	cogit assertCStackWellAligned.
- 	self assert: (self isMachineCodeFrame: framePointer).
- 	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
- 	self push: cogMethod asInteger + cogit entryOffset.
- 	cogit numRegArgs > 0 ifTrue:
- 		[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
- 			[self assert: cogit numRegArgs <= 2.
- 			 self push: cacheTag.
- 			 cogMethod cmNumArgs = 0 ifTrue:
- 				[cogit ceEnter0ArgsPIC].
- 			 cogMethod cmNumArgs = 1 ifTrue:
- 				[cogit ceEnter1ArgsPIC].
- 			 cogMethod cmNumArgs = 2 ifTrue:
- 				[cogit ceEnter2ArgsPIC].
- 			 self error: 'not reached']].
- 	self
- 		push: rcvr;
- 		push: cacheTag.
- 	cogit ceEnterCogCodePopReceiverAndClassRegs
- 	"NOTREACHED"!

Item was removed:
- ----- Method: CoInterpreter>>executeCogMethodFromUnlinkedSend:withReceiver: (in category 'enilopmarts') -----
- executeCogMethodFromUnlinkedSend: cogMethod withReceiver: rcvr
- 	"Execute a CogMethod from an unlinked send.  The receiver,
- 	 arguments and return address are on the Smalltalk stack.  First
- 	 push the entry-point and finally the register argument(s).  Then write
- 	 back the frame pointers and call the routine that will pop off the register
- 	 argument(s) and jump to the entry by executing a return instruction.
- 
- 	 In the simple jit only the receiver gets passed in registers, so only the
- 	 receiver gets pushed."
- 	<var: #cogMethod type: #'CogMethod *'>
- 	cogit assertCStackWellAligned.
- 	self assert: (self isMachineCodeFrame: framePointer).
- 	self assertValidExecutionPointe: self stackTop r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
- 	(cogit numRegArgs > 0
- 	 and: [cogMethod cmNumArgs <= cogit numRegArgs]) ifTrue:
- 		[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr].
- 	self
- 		push: cogMethod asInteger + cogit noCheckEntryOffset;
- 		push: rcvr.
- 	cogit ceEnterCogCodePopReceiverReg
- 	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>handleMNU:InMachineCodeTo:classForMessage: (in category 'message sending') -----
  handleMNU: selectorIndex InMachineCodeTo: rcvr classForMessage: classForMessage
  	"A message send from either an open PIC or an unlinked send has not  been
  	 understood.  Create a message and execute the relevant resulting MNU method.
  	 messageSelector is an implicit argument (yuck)."
  	| errSelIdx classForThisMessage |
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	instructionPointer := self popStack.
  	self createActualMessageTo: classForMessage.
  	messageSelector := objectMemory splObj: selectorIndex.
  	(self lookupInMethodCacheSel: messageSelector classTag: (objectMemory classTagForClass: lkupClass))
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: messageSelector]
  		ifFalse:
  			[errSelIdx := self lookupMethodNoMNUEtcInClass: (classForThisMessage := lkupClass).
  			 errSelIdx ~= 0 ifTrue:
  				[selectorIndex = SelectorDoesNotUnderstand ifTrue:
  					[self error: 'Recursive not understood error encountered'].
  				 self push: instructionPointer.
  				 ^self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: classForThisMessage]].
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[self push: instructionPointer.
+ 		 self executeCogMethod: (self cogMethodOf: newMethod)
+ 			 fromUnlinkedSendWithReceiver: rcvr.
- 		 self executeCogMethodFromUnlinkedSend: (self cogMethodOf: newMethod)
- 			 withReceiver: rcvr.
  		 "NOTREACHED"
  		 self assert: false].
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>lookup:receiver: (in category 'cog jit support') -----
  lookup: selector receiver: rcvr
  	<api>
  	"Lookup selector in rcvr, without doing MNU processing, and answer either a
+ 	 method or an error code if the message was not understood.  Used to populate closed PICs."
- 	 method or nil if the message was not understood.  Used to populate closed PICs."
  	| classTag erridx |
  	"self printFrame: stackPage headFP WithSP: stackPage headSP"
  	"self printStringOf: selector"
  	classTag := objectMemory fetchClassTagOf: rcvr.
  	(self lookupInMethodCacheSel: selector classTag: classTag) ifFalse:
  		[messageSelector := selector.
  		 (erridx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
+ 			[self assert: erridx <= self maxLookupNoMNUErrorCode.
+ 			 ^erridx]].
- 			[^erridx]].
  	^newMethod!

Item was added:
+ ----- Method: CoInterpreter>>maxLookupNoMNUErrorCode (in category 'cog jit support') -----
+ maxLookupNoMNUErrorCode
+ 	<api>
+ 	^SelectorCannotInterpret max: SelectorDoesNotUnderstand!

Item was added:
+ ----- Method: CogObjectRepresentation>>numRegArgs (in category 'calling convention') -----
+ numRegArgs
+ 	"Define how many register arguments a StackToRegisterMapngCogit can and should use
+ 	 with the receiver.  The value must be 0, 1 or 2.  Note that a SimpleStackBasedCogit always
+ 	 has 0 register args (although the receiver is passed in a register)."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>numRegArgs (in category 'calling convention') -----
+ numRegArgs
+ 	"The Spur object representation is simple enough that implementing
+ 	 at:put: is straight-forward and hence 2 register args are worth while."
+ 	<api>
+ 	^2!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>numRegArgs (in category 'calling convention') -----
+ numRegArgs
+ 	"CogObjectRepresentationForSqueakV3 only implements at most 1-arg primitives, because
+ 	 the complexity of the object representation makes it difficult to implement at:put:, the most
+ 	 performance-critical 2-argument primitive."
+ 	<api>
+ 	^1!

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 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: 'set break pc...' 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: (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:
  ----- Method: Cogit>>ceCPICMiss:receiver: (in category 'in-line cacheing') -----
  ceCPICMiss: cPIC receiver: receiver
  	"Code entry closed PIC miss.  A send has fallen
  	 through a closed (finite) polymorphic inline cache.
  	 Either extend it or patch the send site to an open PIC.
  	 The stack looks like:
  			receiver
  			args
  	  sp=>	sender return address"
  	<var: #cPIC type: #'CogMethod *'>
  	<api>
  	| outerReturn newTargetMethodOrNil errorSelectorOrNil cacheTag result |
  	self cCode: ''
  		inSmalltalk:
  			[cPIC isInteger ifTrue:
  				[^self ceCPICMiss: (self cogMethodSurrogateAt: cPIC) receiver: receiver]].
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: cPIC].
  	outerReturn := coInterpreter stackTop.
  	cPIC cPICNumCases < numPICCases
  		ifTrue:
  			[self lookup: cPIC selector
  				for: receiver
  				methodAndErrorSelectorInto:
  					[:method :errsel|
  					newTargetMethodOrNil := method.
  					errorSelectorOrNil := errsel]]
  		ifFalse: [newTargetMethodOrNil := errorSelectorOrNil := nil].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	(cPIC cPICNumCases >= numPICCases
  	 or: [(errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: cPIC selector
  					numArgs: cPIC cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: cPIC].
  	"Now extend the PIC with the new case."
  	self cogExtendPIC: cPIC
  		CaseNMethod: newTargetMethodOrNil
  		tag: cacheTag
  		isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  	"Jump back into the pic at its entry in case this is an MNU."
  	coInterpreter
+ 		executeCogMethod: cPIC
+ 		fromLinkedSendWithReceiver: receiver
- 		executeCogMethodFromLinkedSend: cPIC
- 		withReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: Cogit>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	outerReturn := coInterpreter stackTop.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self cppIf: NewspeakVM ifTrue:
  		[self assert: (targetMethod asInteger + cmEntryOffset = entryPoint
  					or: [targetMethod asInteger + cmDynSuperEntryOffset = entryPoint]).
  		 "Avoid the effort of implementing PICs for the relatively low dynamic frequency
  		  dynamic super send and simply rebind the send site."
  		 targetMethod asInteger + cmDynSuperEntryOffset = entryPoint ifTrue:
  			[^coInterpreter
  				ceDynamicSuperSend: targetMethod selector
  				to: receiver
  				numArgs: targetMethod cmNumArgs]].
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
  	pic isNil ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  		 processor flushICacheFrom: pic asInteger to: pic asInteger + closedPICSize].
  	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
  	 for the benefit of the cacheTag assert check in checkIfValidObjectRef:pc:cogMethod:."
  	extent := pic cmType = CMOpenPIC
  				ifTrue:
  					[backEnd
  						rewriteInlineCacheAt: outerReturn
  						tag: targetMethod selector
  						target: pic asInteger + cmEntryOffset]
  				ifFalse:
  					[backEnd
  						rewriteCallAt: outerReturn
  						target: pic asInteger + cmEntryOffset].
  	processor flushICacheFrom: outerReturn - 1 - extent to: outerReturn - 1.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
+ 		executeCogMethod: pic
+ 		fromLinkedSendWithReceiver: receiver
- 		executeCogMethodFromLinkedSend: pic
- 		withReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: Cogit>>lookup:for:methodAndErrorSelectorInto: (in category 'in-line cacheing') -----
  lookup: selector for: receiver methodAndErrorSelectorInto: binaryBlock
  	"Lookup selector in the class of receiver.  If found, evaluate binaryBlock with the
  	 method, cogged if appropriate..  If not found, due to MNU, lookup the DNU selector
  	 and evaluate binaryBlock with the MNU method, cogged if appropriate..  If not found
  	 due to cannot interpret, evaluate binaryBlock with a nil method and the error selector."
  	| methodOrSelectorIndex |
  	<inline: true>
  	methodOrSelectorIndex := coInterpreter
  									lookup: selector
  									receiver: receiver.
+ 	methodOrSelectorIndex asUnsignedInteger > coInterpreter maxLookupNoMNUErrorCode ifTrue:
- 	methodOrSelectorIndex asUnsignedInteger >= objectMemory nilObject ifTrue:
  		[(objectMemory isOopCompiledMethod: methodOrSelectorIndex) ifFalse:
  			[^binaryBlock value: methodOrSelectorIndex value: SelectorCannotInterpret].
  		 ((coInterpreter methodHasCogMethod: methodOrSelectorIndex) not
  		  and: [coInterpreter methodShouldBeCogged: methodOrSelectorIndex]) ifTrue:
  			["We assume cog:selector: will *not* reclaim the method zone"
  			 self cog: methodOrSelectorIndex selector: selector].
  		^binaryBlock value: methodOrSelectorIndex value: nil].
  	methodOrSelectorIndex = SelectorDoesNotUnderstand ifTrue:
  		[methodOrSelectorIndex := coInterpreter
  										lookup: (objectMemory splObj: SelectorDoesNotUnderstand)
  										receiver: receiver.
+ 		 methodOrSelectorIndex asUnsignedInteger > coInterpreter maxLookupNoMNUErrorCode ifTrue:
- 		 methodOrSelectorIndex asUnsignedInteger >= objectMemory nilObject ifTrue:
  			[self assert: (objectMemory isOopCompiledMethod: methodOrSelectorIndex).
  			 ((coInterpreter methodHasCogMethod: methodOrSelectorIndex) not
  			  and: [coInterpreter methodShouldBeCogged: methodOrSelectorIndex]) ifTrue:
  				["We assume cog:selector: will *not* reclaim the method zone"
  				 self cog: methodOrSelectorIndex selector: selector].
  			^binaryBlock value: methodOrSelectorIndex value: SelectorDoesNotUnderstand].
  		^binaryBlock value: nil value: SelectorDoesNotUnderstand].
  	^binaryBlock value: nil value: methodOrSelectorIndex!

Item was changed:
  ----- Method: Cogit>>patchToOpenPICFor:numArgs:receiver: (in category 'in-line cacheing') -----
  patchToOpenPICFor: selector numArgs: numArgs receiver: receiver
  	"Code entry closed PIC full or miss to an instance of a young class or to a young target method.
  	 Attempt to patch the send site to an open PIC.  Answer if the attempt succeeded; in fact it will
  	 only return if the attempt failed.
  	 The stack looks like:
  			receiver
  			args
  	 sp=>	sender return address"
  	<api>
  	| oPIC outerReturn extent |
  	<var: #oPIC type: #'CogMethod *'>
  	outerReturn := coInterpreter stackTop.
  	"See if an Open PIC is already available."
  	oPIC := methodZone openPICWithSelector: selector.
  	oPIC isNil ifTrue:
  		["otherwise attempt to create an Open PIC."
  		oPIC := self cogOpenPICSelector: selector numArgs: numArgs.
  		(oPIC asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory."
  			oPIC asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^false]].
  	extent := backEnd
  				rewriteInlineCacheAt: outerReturn
  				tag: selector
  				target: oPIC asInteger + cmEntryOffset.
  	processor
  		flushICacheFrom: outerReturn - 1 - extent to: outerReturn - 1;
  		flushICacheFrom: oPIC asInteger to: oPIC asInteger + openPICSize.
  	"Jump into the oPIC at its entry"
+ 	coInterpreter executeCogMethod: oPIC fromLinkedSendWithReceiver: receiver.
- 	coInterpreter executeCogMethodFromLinkedSend: oPIC withReceiver: receiver.
  	"NOTREACHED"
  	^true!

Item was changed:
  ----- Method: Cogit>>reportLastNInstructions (in category 'debugging') -----
  reportLastNInstructions
  	<doNotGenerate>
+ 	| skipNext printInst |
+ 	skipNext := false.
+ 	printInst := [:inst|
+ 				coInterpreter transcript nextPutAll:
+ 					(EagerInstructionDecoration
+ 						ifTrue: [inst]
+ 						ifFalse: [processor
+ 									decorateDisassembly: inst
+ 									for: self]); cr].
+ 	lastNInstructions withIndexDo:
+ 		[:thing :idx| | next pc label |
+ 		skipNext
+ 			ifTrue: [skipNext := false]
+ 			ifFalse:
+ 				[thing isArray
- 	lastNInstructions do:
- 		[:thing|
- 		thing isArray
- 			ifTrue:
- 				[thing first isString "i.e. { '(simulated return to '. processor retpcIn: coInterpreter memory. ')'}"
  					ifTrue:
+ 						[thing first isString "i.e. { '(simulated return to '. processor retpcIn: coInterpreter memory. ')'}"
+ 							ifTrue:
+ 								[thing do:
+ 									[:stringOrNumber|
+ 									coInterpreter transcript nextPutAll: (stringOrNumber isString
+ 															ifTrue: [stringOrNumber]
+ 															ifFalse: [stringOrNumber hex])].
+ 									coInterpreter transcript cr]
+ 							ifFalse: "if possible, add the label to the instruction line to condense the output"
+ 								[coInterpreter transcript cr.
+ 								 pc := thing at: processor registerStatePCIndex.
+ 								 label := self relativeLabelForPC: pc.
+ 								 ((next := lastNInstructions at: idx + 1 ifAbsent: []) notNil
+ 								  and: [next isString
+ 								  and: [(Integer readFrom: next readStream radix: 16) = pc]])
+ 									ifTrue: "Decorate instruction and eliminate pc line"
+ 										[skipNext := true.
+ 										 processor printRegisterStateExceptPC: thing on: coInterpreter transcript.
+ 										 label ifNotNil: [coInterpreter transcript nextPutAll: label; space].
+ 										 printInst value: next]
+ 									ifFalse:
+ 										[label ifNotNil: [coInterpreter transcript nextPutAll: label; nextPut: $:; cr].
+ 										 processor printRegisterState: thing on: coInterpreter transcript]]]
- 						[thing do:
- 							[:stringOrNumber|
- 							coInterpreter transcript nextPutAll: (stringOrNumber isString
- 													ifTrue: [stringOrNumber]
- 													ifFalse: [stringOrNumber hex])].
- 							coInterpreter transcript cr]
  					ifFalse:
+ 						[printInst value: thing]]].
- 						[coInterpreter transcript cr.
- 						 (self relativeLabelForPC: (thing at: processor registerStatePCIndex)) ifNotNil:
- 							[:label| coInterpreter transcript nextPutAll: label; nextPut: $:; cr].
- 						 processor printRegisterState: thing on: coInterpreter transcript]]
- 			ifFalse:
- 				[coInterpreter transcript
- 					nextPutAll: (EagerInstructionDecoration
- 									ifTrue: [thing]
- 									ifFalse: [processor
- 												decorateDisassembly: thing
- 												for: self]); cr]].
  	coInterpreter transcript flush!

Item was removed:
- StackToRegisterMappingCogit subclass: #StackToRegisterMapping2RegArgsCogit
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-JIT'!

Item was removed:
- ----- Method: StackToRegisterMapping2RegArgsCogit>>numRegArgs (in category 'calling convention') -----
- numRegArgs
- 	<api>
- 	^2!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ceEnter2ArgsPIC (in category 'simulation only') -----
  ceEnter2ArgsPIC
  	<api: 'extern void (*ceEnter2ArgsPIC)()'>
  	<doNotGenerate>
+ 	self simulateEnilopmart: ceEnter2ArgsPIC numArgs: 1!
- 	self simulateEnilopmart: ceEnter2ArgsPIC numArgs: 2!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateEnilopmarts (in category 'initialization') -----
  generateEnilopmarts
  	"Enilopmarts transfer control from C into machine code (backwards trampolines).
  	 Override to add version for generic and PIC-specific entry with reg args."
  	super generateEnilopmarts.
  
  	self cppIf: Debug
  		ifTrue:
  			[realCEEnterCogCodePopReceiverArg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg
  					called: 'realCEEnterCogCodePopReceiverArg0Regs'.
  			 ceEnterCogCodePopReceiverArg0Regs := #enterCogCodePopReceiverArg0Regs.
  			 realCEEnterCogCodePopReceiverArg1Arg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg							
  					and: Arg1Reg
  					called: 'realCEEnterCogCodePopReceiverArg1Arg0Regs'.
  			 ceEnterCogCodePopReceiverArg1Arg0Regs := #enterCogCodePopReceiverArg1Arg0Regs]
  		ifFalse:
  			[ceEnterCogCodePopReceiverArg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg
  					called: 'ceEnterCogCodePopReceiverArg0Regs'.
  			 ceEnterCogCodePopReceiverArg1Arg0Regs :=
  				self genEnilopmartFor: ReceiverResultReg
  					and: Arg0Reg							
  					and: Arg1Reg
  					called: 'ceEnterCogCodePopReceiverArg1Arg0Regs'].
  
  	"These are special versions of the ceEnterCogCodePopReceiverAndClassRegs enilopmart that also
  	 pop register argsfrom the stack to undo the pushing of register args in the abort/miss trampolines."
  	ceEnter0ArgsPIC := self genEnterPICEnilopmartNumArgs: 0.
  	self numRegArgs >= 1 ifTrue:
  		[ceEnter1ArgsPIC := self genEnterPICEnilopmartNumArgs: 1.
  		 self numRegArgs >= 2 ifTrue:
+ 			[ceEnter2ArgsPIC := self genEnterPICEnilopmartNumArgs: 2.
- 			[ceEnter1ArgsPIC := self genEnterPICEnilopmartNumArgs: 2.
  			 self assert: self numRegArgs = 2]]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>numRegArgs (in category 'compile abstract instructions') -----
  numRegArgs
+ 	<doNotGenerate>
+ 	^objectRepresentation numRegArgs!
- 	<api>
- 	^1!

Item was changed:
  ----- Method: VMClass>>promptHex: (in category 'simulation support') -----
  promptHex: string
  	<doNotGenerate>
  	| s |
  	s := UIManager default request: string, ' (hex)'.
  	s := s withBlanksTrimmed.
+ 	^(s notEmpty and: ['-+0123456789abcdefABCDEF' includes: s first]) ifTrue:
- 	^s notEmpty ifTrue:
  		[(s includes: $r)
  			ifTrue:
  				[Number readFrom: s readStream]
  			ifFalse:
  				[(#('0x' '-0x') detect: [:prefix| s beginsWith: prefix] ifNone: []) ifNotNil:
  					[:prefix|
  					s := s allButFirst: prefix size.
  					prefix first = $- ifTrue: [s := '-', s]].
  				Integer readFrom: s readStream base: 16]]!



More information about the Vm-dev mailing list