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

commits at source.squeak.org commits at source.squeak.org
Sun Nov 15 06:01:06 UTC 2020


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

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

Name: VMMaker.oscog-eem.2884
Author: eem
Time: 14 November 2020, 10:00:58.142178 pm
UUID: a121227d-80b9-46e4-aa93-f9ac9d7b2ca6
Ancestors: VMMaker.oscog-eem.2883

Slang: Fix a regression with inlining isClassOfNonImm:equalTo:compactClassIndex:.  Not quite sure why but an argument assignment for the unused classOop argument was being generated when it shouldn't be.

Cogit: save several lines by inlining wrappers around genTrampolineFor:called:numArgs:arg:arg:arg:arg:regsToSave:pushLinkReg:resultReg:appendOpcodes:

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

Item was changed:
  ----- Method: CoInterpreter>>convertToInterpreterFrame: (in category 'frame access') -----
  convertToInterpreterFrame: pcDelta
+ 	"Convert the top machine code frame to an interpreter frame.  Support for
- 	"Convert the top machine code frame to an interpeeter frame.  Support for
  	 mustBeBoolean in the RegisterAllocatingCogit and for cloneContext: in shallowCopy
  	 when a code compaction is caused by machine code to bytecode pc mapping."
  
  	|  cogMethod methodHeader methodObj startBcpc |
  	<var: 'cogMethod' type: #'CogBlockMethod *'>
  	<var: 'p' type: #'char *'>
  
  	self assert: (self isMachineCodeFrame: framePointer).
  
  	cogMethod := self mframeCogMethod: framePointer.
  	((self mframeIsBlockActivation: framePointer)
  	 and: [cogMethod cmIsFullBlock not])
  		ifTrue:
  			[methodHeader := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodHeader.
  			 methodObj := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodObject.
  			 startBcpc := cogMethod startpc]
  		ifFalse:
  			[methodHeader := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodHeader.
  			 methodObj := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodObject.
  			 startBcpc := self startPCOfMethod: methodObj].
  
  	"Map the machine code instructionPointer to the interpreter instructionPointer of the branch."
  	instructionPointer := cogit bytecodePCFor: instructionPointer startBcpc: startBcpc in: cogMethod.
  	instructionPointer := methodObj + objectMemory baseHeaderSize + instructionPointer - pcDelta - 1. "pre-decrement"
  	 self validInstructionPointer: instructionPointer inMethod: methodObj framePointer: framePointer.
  
  	"Make space for the two extra fields in an interpreter frame"
  	stackPointer to: framePointer + FoxMFReceiver by: objectMemory wordSize do:
  		[:p| | oop |
  		 oop := objectMemory longAt: p.
  		 objectMemory
  			longAt: p - objectMemory wordSize - objectMemory wordSize
  			put: (objectMemory longAt: p)].
  	stackPointer := stackPointer - objectMemory wordSize - objectMemory wordSize.
  	"Fill in the fields"
  	objectMemory
  		longAt: framePointer + FoxIFrameFlags
  			put: (self
  					encodeFrameFieldHasContext: (self mframeHasContext: framePointer)
  					isBlock: (self mframeIsBlockActivation: framePointer)
  					numArgs: cogMethod cmNumArgs);
  		longAt: framePointer + FoxIFSavedIP
  			put: instructionPointer;
  		longAt: framePointer + FoxMethod
  			put: methodObj.
  
  	self setMethod: methodObj methodHeader: methodHeader!

Item was changed:
  ----- Method: CoInterpreter>>iframeSavedIP: (in category 'frame access') -----
  iframeSavedIP: theFP
  	<var: #theFP type: #'char *'>
+ 	^(stackPages longAt: theFP + FoxIFSavedIP) asUnsignedInteger!
- 	^stackPages longAt: theFP + FoxIFSavedIP!

Item was changed:
  ----- Method: CoInterpreter>>returnToExecutive:postContextSwitch: (in category 'enilopmarts') -----
  returnToExecutive: inInterpreter postContextSwitch: switchedContext
  	"Return to the current frame, either by entering machine code, or longjmp-ing back to the
  	 interpreter or simply returning, depending on where we are. To know whether to return or
  	 enter machine code we have to know from whence we came.  We could have come from
  	 the interpreter, either directly or via a machine code primitive.  We could have come from
  	 machine code.  The instructionPointer tells us where from.  If it is above startOfMemory we're
  	 in the interpreter.  If it is below, then we are in machine-code unless it is ceReturnToInterpreterPC,
  	 in which case we're in a machine-code primitive called from the interpreter."
  	<inline: false>
  	| cogMethod retValue fullyInInterpreter |
  	<var: #cogMethod type: #'CogBlockMethod *'>
  
  	cogit assertCStackWellAligned.
  	(self isMachineCodeFrame: framePointer) ifTrue:
  		[self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: false line: #'__LINE__'.
  		 "If returning after a context switch then a result may have to be popped from the stack.
  		  If the process is suspended at a send then the result of the primitive in which the
  		  process was suspended is still on the stack and must be popped into ReceiverResultReg.
  		  If not, nothing should be popped and ReceiverResultReg gets the receiver."
  		 switchedContext
  			ifTrue:
  				[cogMethod := self mframeCogMethod: framePointer.
  				self assert: (instructionPointer > cogit minCogMethodAddress 
  							and: [instructionPointer < cogit maxCogMethodAddress]).
  				 (instructionPointer ~= (cogMethod asInteger + cogMethod stackCheckOffset)
  				  and: [cogit isSendReturnPC: instructionPointer])
  					ifTrue:
  						[self assert: (objectMemory addressCouldBeOop: self stackTop).
  						 retValue := self popStack]
  					ifFalse:
  						[retValue := self mframeReceiver: framePointer]]
  			ifFalse: [retValue := self mframeReceiver: framePointer].
  		 self push: instructionPointer.
  		 self push: retValue.
  		 cogit ceEnterCogCodePopReceiverReg
  		 "NOTREACHED"].
  	self setMethod: (self iframeMethod: framePointer).
  	fullyInInterpreter := inInterpreter.
  	instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
+ 		[instructionPointer := self iframeSavedIP: framePointer.
- 		[instructionPointer := (self iframeSavedIP: framePointer) asUnsignedInteger.
  		 fullyInInterpreter := false].
  	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
  	fullyInInterpreter ifFalse:
  		[cogit ceInvokeInterpret
  		 "NOTREACHED"].
  	^nil!

Item was changed:
  ----- Method: CoInterpreterMT>>primitiveRelinquishProcessor (in category 'I/O primitives') -----
  primitiveRelinquishProcessor
  	"Relinquish the processor for up to the given number of microseconds.
  	 The exact behavior of this primitive is platform dependent.
  	 Override to check for waiting threads."
  
  	| microSecs threadIndexAndFlags currentCStackPointer currentCFramePointer |
  	<var: #currentCStackPointer type: #'void *'>
  	<var: #currentCFramePointer type: #'void *'>
- 	<var: #savedReenterInterpreter type: #'jmp_buf'>
  	microSecs := self stackTop.
  	(objectMemory isIntegerObject: microSecs) ifFalse:
  		[^self primitiveFail].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  	self assert: relinquishing not.
  	"DO NOT allow relinquishing the processor while we are profiling since this
  	 may skew the time base for our measures (it may reduce processor speed etc).
  	 Instead we go full speed, therefore measuring the precise time we spend in the
  	 inner idle loop as a busy loop."
  	nextProfileTick = 0 ifTrue:
  		"Presumably we have nothing to do; this primitive is typically called from the
  		 background process. So we should /not/ try and activate any threads in the
  		 pool; they will waste cycles finding there is no runnable process, and will
  		 cause a VM abort if no runnable process is found.  But we /do/ want to allow
  		 FFI calls that have completed, or callbacks a chance to get into the VM; they
  		 do have something to do.  DisownVMForProcessorRelinquish indicates this."
  		[currentCStackPointer := CStackPointer.
  		 currentCFramePointer := CFramePointer.
  		 threadIndexAndFlags := self disownVM: DisownVMForProcessorRelinquish.
  		 self assert: relinquishing.
  		 self ioRelinquishProcessorForMicroseconds: (objectMemory integerValueOf: microSecs).
  		 self assert: relinquishing.
  		 self ownVM: threadIndexAndFlags.
  		 self assert: relinquishing not.
  		 self assert: cogThreadManager currentVMThread state = CTMAssignableOrInVM.
  		 self assert: currentCStackPointer = CStackPointer.
  		 self assert: currentCFramePointer = CFramePointer.
  		 "In simulation we allow ioRelinquishProcessorForMicroseconds: to fail so that
  		  we can arrange that the simulator responds to input events promply.  This
  		  *DOES NOT HAPPEN* in the real vm."
  		 self cCode: [] inSmalltalk: [primFailCode ~= 0 ifTrue: [^self]]].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  	self pop: 1  "microSecs; leave rcvr on stack"!

Item was changed:
  ----- Method: Cogit>>genCheckForInterruptsTrampoline (in category 'initialization') -----
  genCheckForInterruptsTrampoline
+ 	<inline: true>
  	self zeroOpcodeIndex.
  	"if we have a link register we will assume that it does not get automatically pushed onto the stack
  	and thus there is no need to pop it before saving to instructionPointerAddress"
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
  	^self genTrampolineFor: #ceCheckForInterrupts
  		called: 'ceCheckForInterruptsTrampoline'
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: false
  		resultReg: NoReg
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genNonLocalReturnTrampoline (in category 'initialization') -----
  genNonLocalReturnTrampoline
+ 	<inline: true>
  	self zeroOpcodeIndex.
  	"write the return address to the coInterpreter instructionPointerAddress;
  	 following the CallRT to this CISCs will have pushed it on the stack, so pop it first; RISCs will have it in
  	 their link register so just write it directly."
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
  	^self genTrampolineFor: #ceNonLocalReturn:
  		called: 'ceNonLocalReturnTrampoline'
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: false
  		resultReg: NoReg
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genPICAbortTrampoline (in category 'initialization') -----
  genPICAbortTrampoline
  	"Generate the abort for a PIC.  This abort performs either a call of
  	 ceInterpretMethodFromPIC:receiver: to handle invoking an uncogged
  	 target or a call of ceMNUFromPICMNUMethod:receiver: to handle an
  	 MNU dispatch in a closed PIC.  It distinguishes the two by testing
  	 ClassReg.  If the register is zero then this is an MNU."
+ 	<inline: true>
  	self zeroOpcodeIndex.
  	backEnd hasLinkRegister ifTrue:
  		[self PushR: LinkReg].
  	^self genInnerPICAbortTrampoline: 'cePICAbort'!

Item was changed:
  ----- Method: Cogit>>genReturnTrampolineFor:called:arg: (in category 'initialization') -----
  genReturnTrampolineFor: aRoutine  called: aString arg: regOrConst0
  	"Generate a trampoline for a routine used as a return address, that has one argument.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: false "Since the routine is reached by a return instruction it should /not/ push the link register."
  		resultReg: NoReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString
  	"Generate a trampoline with no arguments"
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: true
  		resultReg: NoReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg: (in category 'initialization') -----
  genTrampolineFor: aRoutine  called: aString arg: regOrConst0
  	"Generate a trampoline with one argument.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: true
  		resultReg: NoReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1
  	"Generate a trampoline with two arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 2
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: nil
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: true
  		resultReg: NoReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg:arg: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2
  	"Generate a trampoline with three arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 3
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: true
  		resultReg: NoReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg:arg:arg: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate a trampoline with four arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 4
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: regOrConst3
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: true
  		resultReg: NoReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg:arg:result: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 result: resultReg
  	"Generate a trampoline with two arguments that answers a result.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 3
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: true
  		resultReg: resultReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg:regsToSave: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 regsToSave: regMask
  	"Generate a trampoline with two arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 2
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: nil
  		arg: nil
  		regsToSave: regMask
  		pushLinkReg: true
  		resultReg: NoReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg:result: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 result: resultReg
  	"Generate a trampoline with two arguments that answers a result.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 2
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: nil
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: true
  		resultReg: resultReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:regsToSave: (in category 'initialization') -----
  genTrampolineFor: aRoutine  called: aString arg: regOrConst0 regsToSave: regMask
  	"Generate a trampoline with one argument.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: regMask
  		pushLinkReg: true
  		resultReg: NoReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:regsToSave:result: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 regsToSave: regMask result: resultReg
  	"Generate a trampoline with one argument that answers a result.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: regMask
  		pushLinkReg: true
  		resultReg: resultReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:result: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 result: resultReg
  	"Generate a trampoline with one argument that answers a result.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: self emptyRegisterMask
  		pushLinkReg: true
  		resultReg: resultReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:regsToSave: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString regsToSave: regMask
  	"Generate a trampoline with no arguments"
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
+ 	<inline: #always>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: regMask
  		pushLinkReg: true
  		resultReg: NoReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: StackInterpreter>>frameCallerFP: (in category 'frame access') -----
  frameCallerFP: theFP
  	<inline: true>
  	<var: #theFP type: #'char *'>
+ 	<returnTypeC: #'char *'>
- 	<returnTypeC: 'char *'>
  	^self pointerForOop: (stackPages longAt: theFP + FoxSavedFP)!

Item was changed:
  ----- Method: StackInterpreter>>postGCUpdateDisplayBits (in category 'object memory support') -----
  postGCUpdateDisplayBits
  	"Update the displayBits after a GC may have moved it.
  	 Answer if the displayBits appear valid.  The wrinkle here is that the displayBits could be a surface handle."
  	<inline: false>
  	| displayObj bitsOop bitsNow |
  	displayObj := objectMemory splObj: TheDisplay.
  	((objectMemory isPointers: displayObj)
  	 and: [(objectMemory lengthOf: displayObj) >= 4]) ifFalse:
  		[^false].
  	
  	bitsOop := objectMemory fetchPointer: 0 ofObject: displayObj.
  	(objectMemory isIntegerObject: bitsOop) ifTrue: "It's a surface; our work here is done..."
  		[^true].
  
+ 	self assert: ((objectMemory addressCouldBeObj: bitsOop)
+ 				 and: [objectMemory isWordsOrBytes: bitsOop]).
- 	((objectMemory addressCouldBeObj: bitsOop)
- 	 and: [objectMemory isWordsOrBytes: bitsOop]) ifFalse:
- 		[^false].
  
  	(objectMemory hasSpurMemoryManagerAPI
  	 and: [objectMemory isPinned: bitsOop]) ifFalse:
  		[bitsNow := self cCode: [objectMemory firstIndexableField: bitsOop]
  					inSmalltalk: [(objectMemory firstIndexableField: bitsOop) asInteger].
  		 displayBits ~= bitsNow ifTrue:
  			[displayBits := bitsNow.
  			 self ioNoteDisplayChanged: displayBits width: displayWidth height: displayHeight depth: displayDepth].
  		 objectMemory hasSpurMemoryManagerAPI ifTrue:
  			[objectMemory pinObject: bitsOop]].
  	^true!

Item was changed:
  ----- Method: StackInterpreter>>printStackCallStackOf: (in category 'debug printing') -----
  printStackCallStackOf: aContextOrProcessOrFrame
  	<api>
  	| theFP context |
  	<var: #theFP type: #'char *'>
  	(self cCode: [false] "In the stack simulator, frame pointers are negative which upsets addressCouldBeObj:"
  		inSmalltalk: [stackPages couldBeFramePointer: aContextOrProcessOrFrame]) ifFalse:
  		[(objectMemory addressCouldBeObj: aContextOrProcessOrFrame) ifTrue:
  			[((objectMemory isContext: aContextOrProcessOrFrame)
  			  and: [self checkIsStillMarriedContext: aContextOrProcessOrFrame currentFP: nil]) ifTrue:
  				[^self printStackCallStackOf: (self frameOfMarriedContext: aContextOrProcessOrFrame) asInteger].
  			 aContextOrProcessOrFrame = self activeProcess ifTrue:
+ 				[^self printStackCallStackOf: (self cCode: [framePointer asInteger] inSmalltalk: [self headFramePointer])].
- 				[^self printStackCallStackOf: (self cCode: [framePointer] inSmalltalk: [self headFramePointer])].
  			 (self couldBeProcess: aContextOrProcessOrFrame) ifTrue:
  				[^self printCallStackOf: (objectMemory
  											fetchPointer: SuspendedContextIndex
  											ofObject: aContextOrProcessOrFrame)].
  			 ^nil]].
  
  	theFP := aContextOrProcessOrFrame asVoidPointer.
  	[context := self shortReversePrintFrameAndCallers: theFP.
  	 ((self isMarriedOrWidowedContext: context)
  	  and:
  		[theFP := self frameOfMarriedContext: context.
  		 self checkIsStillMarriedContext: context currentFP: theFP]) ifFalse:
  			[^nil]] repeat!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPICAbortTrampolineFor: (in category 'initialization') -----
  genPICAbortTrampolineFor: numArgs
  	"Generate the abort for a PIC.  This abort performs either a call of
  	 ceInterpretMethodFromPIC:receiver: to handle invoking an uncogged
  	 target or a call of ceMNUFromPICMNUMethod:receiver: to handle an
  	 MNU dispatch in a closed PIC.  It distinguishes the two by testing
  	 ClassReg.  If the register is zero then this is an MNU."
+ 	<inline: true>
  	self zeroOpcodeIndex. 
  	backEnd genPushRegisterArgsForAbortMissNumArgs: numArgs.
  	^self genInnerPICAbortTrampoline: (self trampolineName: 'cePICAbort' numRegArgs: numArgs)!

Item was changed:
  ----- Method: TMethod>>addTypesFor:to:in: (in category 'type inference') -----
  addTypesFor: node to: typeSet in: aCodeGen
  	"Add the value types for the node to typeSet.
  	 Answer if any type was derived from an as-yet-untyped method or variable, which allows us to abort
  	 inferReturnTypeFromReturnsIn: if the return type depends on a yet-to-be-typed method or variable."
  	| expr |
  	expr := node.
  	[expr isAssignment or: [expr isStmtList]] whileTrue:
  		[expr isAssignment ifTrue:
  			[expr := expr variable].
  		 expr isStmtList ifTrue:
  			[expr := expr statements last]].
  	expr isSend ifTrue:
  		[(#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:) includes: expr selector) ifTrue:
  			[^expr args
  				inject: false
  				into: [:asYetUntyped :block|
  					asYetUntyped | (self addTypesFor: block to: typeSet in: aCodeGen)]].
  		(aCodeGen returnTypeForSend: expr in: self ifNil: nil)
  			ifNil: [^(aCodeGen methodNamed: expr selector) notNil and: [expr selector ~~ selector]]
  			ifNotNil:
  				[:type |
  				typeSet add: type.
  				^false]].
  	expr isVariable ifTrue:
  		[(aCodeGen typeOfVariable: expr name)
  			ifNotNil: [:type| typeSet add: type]
+ 			ifNil: [expr name ~= 'nil' ifTrue: "nil could be a pointer or integer value, so it is effectively untyped."
+ 					[(typeSet add: (expr name = 'self' "self definitely means no type, at least in non-struct classes..."
- 			ifNil: [(typeSet add: (expr name = 'self'
  										ifTrue: [#void]
  										ifFalse: [#sqInt])) == #sqInt ifTrue:
+ 						[^true]]]].
- 					[^true]]].
  	expr isConstant ifTrue:
  		[(expr value isInteger and: [expr value >= 0]) "cannot determine if signed or unsigned yet..."
  			ifTrue: [typeSet add: expr value]
  			ifFalse:
  				[(expr typeOrNilFrom: aCodeGen in: self) ifNotNil:
  					[:type | typeSet add: type]]].
  	^false!

Item was added:
+ ----- Method: TMethod>>allReferencedArgumentsUsing: (in category 'accessing') -----
+ allReferencedArgumentsUsing: aCodeGen
+ 	"Answer the set of all variables referenced in the receiver."
+ 	| refs |
+ 	refs := Set new.
+ 	"Find all the variable names referenced in this method.
+ 	 Don't descend into conditionals that won't be generated."
+ 	parseTree
+ 		nodesWithParentsDo:
+ 			[:node :parent|
+ 			node isVariable ifTrue: [refs add: node name asString].
+ 			(node isSend
+ 			 and: [node selector beginsWith: #cCode:]) ifTrue:
+ 				[aCodeGen addVariablesInVerbatimCIn: node to: refs]]
+ 		unless:
+ 			[:node :parent|
+ 			parent notNil
+ 			and: [parent isSend
+ 			and: [aCodeGen nodeIsDeadCode: node withParent: parent]]].
+ 	^refs intersection: args!

Item was changed:
  ----- Method: TMethod>>argAssignmentsFor:send:except:in: (in category 'inlining') -----
  argAssignmentsFor: meth send: aSendNode except: elidedArgs in: aCodeGen
+ 	"Answer a collection of assignment nodes that assign the given argument expressions to the formal parameter variables of the given method."
+ 	"Optimization: If the actual parameters are either constants or local variables in the target method (the receiver), substitute them directly into the body of meth. Note that global variables cannot be substituted because the inlined method might depend on the exact ordering of side effects to the globals.
+ 	 Optimization: Don't answer statements for formal parameters which are unused in the method body."
- 	"Return a collection of assignment nodes that assign the given argument expressions to the formal parameter variables of the given method."
- 	"Optimization: If the actual parameters are either constants or local variables in the target method (the receiver), substitute them directly into the body of meth. Note that global variables cannot be subsituted because the inlined method might depend on the exact ordering of side effects to the globals."
  
+ 	| stmtList substitutionDict argList referencedArguments |
- 	| stmtList substitutionDict argList |
  	meth args size > (argList := aSendNode args) size ifTrue:
  		[self assert: (meth args first beginsWith: 'self_in_').
  		 argList := {aSendNode receiver}, aSendNode args].
- 	
  	stmtList := OrderedCollection new: argList size.
  	substitutionDict := Dictionary new: argList size.
  	meth args with: argList do:
  		[:argName :exprNode |
  		(self isNode: exprNode substitutableFor: argName inMethod: meth in: aCodeGen)
  			ifTrue:
  				[substitutionDict
  					at: argName
  					put: (aCodeGen
  							node: exprNode
  							typeCompatibleWith: argName
  							inliningInto: meth
  							in: self).
  				 locals remove: argName ifAbsent: [self assert: (argName beginsWith: 'self_in_')].
  				 declarations removeKey: argName ifAbsent: nil]
  			ifFalse: "Add an assignment for anything except an unused self_in_foo argument"
  				[(elidedArgs includes: argName) ifFalse:
  					[self deny: exprNode isLiteralBlock.
  					 stmtList addLast:
  						(TAssignmentNode new
  							setVariable: (TVariableNode new setName: argName)
  							expression: (aCodeGen
  											node: exprNode copy
  											typeCompatibleWith: argName
  											inliningInto: meth
  											in: self))]]].
  	meth parseTree: (meth parseTree bindVariablesIn: substitutionDict).
+ 	referencedArguments := meth allReferencedArgumentsUsing: aCodeGen.
+ 	^stmtList select: [:assignment| referencedArguments includes: assignment variable name]!
- 	^stmtList!



More information about the Vm-dev mailing list