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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 1 00:02:34 UTC 2018


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

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

Name: VMMaker.oscog-eem.2488
Author: eem
Time: 30 November 2018, 4:02:16.051154 pm
UUID: 3d088675-fa5c-452e-8063-001ff1d4ab81
Ancestors: VMMaker.oscog-akg.2487

StackInterpreter:
Fix a bug where a reference in a married context in a base frame woudl prevent garbage collection.  The same issue is fixed for normal marriage/divorce of contexts, but was not handled in makeBaseFrameFor:.  Thanks to Ryan Macnak for identifying both bug and fix.

Fikx a typo.  Recategorise some tests and add a test for the iussue above.

=============== Diff against VMMaker.oscog-akg.2487 ===============

Item was changed:
  ----- Method: CoInterpreter>>makeBaseFrameFor: (in category 'frame access') -----
  makeBaseFrameFor: aContext "<Integer>"
  	"Marry aContext with the base frame of a new stack page.  Build the base
  	 frame to reflect the context's state.  Answer the new page.  Override to
  	 hold the caller context in a different place,  In the StackInterpreter we use
  	 the caller saved ip, but in the Cog VM caller saved ip is the ceBaseReturn:
  	 trampoline.  Simply hold the caller context in the first word of the stack."
  	<returnTypeC: #'StackPage *'>
  	| page pointer theMethod theIP numArgs stackPtrIndex maybeClosure rcvr |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  	"theIP must be typed as signed because it is assigned ceCannotResumePC and so maybe implicitly typed as unsigned."
  	<var: #theIP type: #sqInt>
  	self assert: (objectMemory isContext: aContext).
  	self assert: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	self assert: HasBeenReturnedFromMCPC < 0.
  	theIP := (objectMemory isIntegerObject: theIP)
  				ifTrue: [objectMemory integerValueOf: theIP]
  				ifFalse: [HasBeenReturnedFromMCPC].
  	theMethod := objectMemory followObjField: MethodIndex ofObject: aContext.
  	page := stackPages newStackPage.
  	"first word on stack is caller context of base frame"
  	stackPages
  		longAt: (pointer := page baseAddress)
  		put: (objectMemory followObjField: SenderIndex ofObject: aContext).
  	"second word is the context itself; needed for cannotReturn processing; see ceBaseReturn:."
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: aContext.
  	rcvr := objectMemory followField: ReceiverIndex ofObject: aContext.
  	"If the frame is a closure activation then the closure should be on the stack in
  	 the pushed receiver position (closures receive the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
  	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
  			[(objectMemory isForwarded: maybeClosure) ifTrue:
  				[maybeClosure := objectMemory fixFollowedField: ClosureIndex ofObject: aContext withInitialValue: maybeClosure].
  			 numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: maybeClosure]
  		ifFalse:
  			[| header |
  			 header := objectMemory methodHeaderOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
  			 "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
  			 ((self methodHeaderHasPrimitive: header)
  			  and: [theIP = (1 + (self startPCOfMethodHeader: header))]) ifTrue:
  				[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)].
  			 stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: rcvr].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is base return trampoline"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: cogit ceBaseFrameReturnPC.
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: 0.
  	"N.B.  Don't set the baseFP, which marks the page as in use, until after
  	 ensureMethodIsCogged: and/or instructionPointer:forContext:frame:. These
  	 can cause a compiled code compaction which, if marked as in use, will
  	 examine this partially initialized page and crash."
  	page headFP: pointer.
  	"Create either a machine code frame or an interpreter frame based on the pc.  If the pc is -ve
  	 it is a machine code pc and so we produce a machine code frame.  If +ve an interpreter frame.
  	 N.B. Do *not* change this to try and map from a bytecode pc to a machine code frame under
  	 any circumstances.  See ensureContextIsExecutionSafeAfterAssignToStackPointer:"
  	theIP < 0
  		ifTrue:
  			[| cogMethod |
  			 "Since we would have to generate a machine-code method to be able to map
  			  the native pc anyway we should create a native method and native frame."
  			 cogMethod := self ensureMethodIsCogged: theMethod maybeClosure: maybeClosure.
  			 theMethod := cogMethod asInteger.
  			 maybeClosure ~= objectMemory nilObject
  				ifTrue:
  					[(self isVanillaBlockClosure: maybeClosure)
  						ifTrue:
  							["If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  							  appropriately so that the frame stays in the cannotReturn: state."
  							 theIP = HasBeenReturnedFromMCPC
  								ifTrue:
  									[theMethod := (cogit findMethodForStartBcpc: (self startPCOfClosure: maybeClosure)
  														inHomeMethod: (self cCoerceSimple: theMethod
  																			to: #'CogMethod *')) asInteger.
  									 theMethod = 0 ifTrue:
  										[self error: 'cannot find machine code block matching closure''s startpc'].
  									 theIP := cogit ceCannotResumePC]
  								ifFalse:
  									[self assert: (theIP signedBitShift: -16) < -1. "See contextInstructionPointer:frame:"
  									 theMethod := theMethod - ((theIP signedBitShift: -16) * cogit blockAlignment).
  									 theIP := theMethod - theIP signedIntFromShort]]
  						ifFalse:
  							[self assert: (theIP signedBitShift: -16) >= -1.
  							 "If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  							  appropriately so that the frame stays in the cannotReturn: state."
  							 theIP := theIP = HasBeenReturnedFromMCPC
  										ifTrue: [cogit ceCannotResumePC]
  										ifFalse: [theMethod asInteger - theIP]].
  					 stackPages
  						longAt: (pointer := pointer - objectMemory wordSize)
  						put: theMethod + MFMethodFlagHasContextFlag + MFMethodFlagIsBlockFlag]
  				ifFalse:
  					[self assert: (theIP signedBitShift: -16) >= -1.
  					 "If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  					  appropriately so that the frame stays in the cannotReturn: state."
  					 theIP := theIP = HasBeenReturnedFromMCPC
  								ifTrue: [cogit ceCannotResumePC]
  								ifFalse: [theMethod asInteger - theIP].
  					 stackPages
  						longAt: (pointer := pointer - objectMemory wordSize)
  						put: theMethod + MFMethodFlagHasContextFlag].
  			 stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: aContext]
  		ifFalse:
  			[stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: theMethod.
  			stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: aContext.
  			stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  			stackPages
  				longAt: (pointer := pointer - objectMemory wordSize)
  				put: 0. "FoxIFSavedIP"
  			theIP := self iframeInstructionPointerForIndex: theIP method: theMethod].
  	page baseFP: page headFP.
  	self assert: (self frameHasContext: page baseFP).
  	self assert: (self frameNumArgs: page baseFP) == numArgs.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: rcvr.
  	stackPtrIndex := self quickFetchInteger: StackPointerIndex ofObject: aContext.
  	self assert: ReceiverIndex + stackPtrIndex < (objectMemory lengthOf: aContext).
  	numArgs + 1 to: stackPtrIndex do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
+ 			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext).
+ 		"nil the slot in the context so that it doesn't inadvertently hang onto some collectable object.
+ 		 Thanks to Ryan Macnak for identifying this bug"
+ 		objectMemory storePointerUnchecked: ReceiverIndex + i ofObject: aContext withValue: objectMemory nilObject].
- 			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	stackPages longAt: (pointer := pointer - objectMemory wordSize) put: theIP.
  	page headSP: pointer.
  	self assert: (self context: aContext hasValidInversePCMappingOf: theIP in: page baseFP).
  
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity) plus SmallInteger tags."
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: page baseFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: 0).
  	self assert: (objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)).
  	self assert: (self frameOfMarriedContext: aContext) = page baseFP.
  	self assert: (self validStackPageBaseFrame: page).
  	^page!

Item was added:
+ ----- Method: MemoryTests>>deepStack: (in category 'test support') -----
+ deepStack: n
+ 	"Not tail recursive."
+ 	^0 = n ifTrue: [0] ifFalse: [n + (self deepStack: n - 1) + n]!

Item was changed:
+ ----- Method: MemoryTests>>expectedFailures (in category 'tests') -----
- ----- Method: MemoryTests>>expectedFailures (in category 'testing') -----
  expectedFailures
  	"As yet we don't support Spur on any big endian platforms, let alone 64-bit ones."
  	^#(testBitmap64BitLongs)!

Item was changed:
+ ----- Method: MemoryTests>>testBitmap32BitLongs (in category 'tests') -----
- ----- Method: MemoryTests>>testBitmap32BitLongs (in category 'testing') -----
  testBitmap32BitLongs
  	"Test that Bitmap provides big-endian access for 32-bit accessors"
  	| memory |
  	memory := Bitmap new: 64.
  	0 to: 30 do:
  		[:shift|
  		#(-1 1) do:
  			[:initial| | value |
  			value := initial bitShift: shift.
  			memory longAt: 1 put: value.
  			self assert: value equals: (memory longAt: 1).
  			memory
  				longAt: 5 put: 16r00005555;
  				longAt: 9 put: 16r55550000.
  			self assert: 16r55555555 equals: (memory longAt: 7).
  			memory longAt: 7 put: value.
  			self assert: (memory longAt: 7) equals: value.
  			self assert: (memory at: (shift <= 15 = (initial >= 0) ifTrue: [5] ifFalse: [9])) equals: 0]].
  	31 to: 32 do:
  		[:shift|
  		self should: [memory longAt: 1 put: -1 << shift - 1] raise: Error.
  		self should: [memory longAt: 1 put: 1 << shift] raise: Error].
  	0 to: 31 do:
  		[:shift| | value |
  		value := 1 bitShift: shift.
  		memory unsignedLongAt: 1 put: value.
  		self assert: value equals: (memory unsignedLongAt: 1).
  			memory
  				longAt: 5 put: 16r00005555;
  				longAt: 9 put: 16r55550000.
  			self assert: 16r55555555 equals: (memory longAt: 7).
  		memory unsignedLongAt: 7 put: value.
  		self assert: value equals: (memory unsignedLongAt: 7).
  		self assert: 0 equals: (memory at: (shift <= 15 ifTrue: [5] ifFalse: [9]))].
  	self should: [memory unsignedLongAt: 1 put: -1] raise: Error.
  	32 to: 33 do:
  		[:shift|
  		self should: [memory unsignedLongAt: 1 put: 1 << shift] raise: Error]!

Item was changed:
+ ----- Method: MemoryTests>>testBitmap64BitLongs (in category 'tests') -----
- ----- Method: MemoryTests>>testBitmap64BitLongs (in category 'testing') -----
  testBitmap64BitLongs
  	"Test that Bitmap provides big-endian access for 64-bit accessors"
  	| memory |
  	memory := Bitmap new: 64.
  	0 to: 62 do:
  		[:shift|
  		#(-1 1) do:
  			[:initial| | value |
  			memory atAllPut: 0.
  			value := initial bitShift: shift.
  			memory long64At: 1 put: value.
  			self assert: value equals: (memory long64At: 1).
  			memory
  				long64At: 10 put: 16r0000000000555555;
  				long64At: 18 put: 16r5555555555000000.
  			self assert: 16r5555555555555555 equals: (memory long64At: 15).
  			"(1 to: 7) collect: [:i| (memory at: i) hex]"
  			memory long64At: 13 put: value.
  			self assert: value equals: (memory long64At: 13).
  			self assert: 0 equals: (memory at: (shift <= 15 = (initial >= 0) ifTrue: [9] ifFalse: [17])).
  			self assert: 0 equals: (memory at: (shift <= 15 = (initial >= 0) ifTrue: [13] ifFalse: [21]))]].
  	63 to: 64 do:
  		[:shift|
  		self should: [memory long64At: 1 put: -1 << shift - 1] raise: Error.
  		self should: [memory long64At: 1 put: 1 << shift] raise: Error].
  	0 to: 63 do:
  		[:shift| | value |
  		value := 1 bitShift: shift.
  		memory unsignedLong64At: 1 put: value.
  		self assert: value equals: (memory unsignedLong64At: 1).
  			memory
  				unsignedLong64At: 10 put: 16r0000000000555555;
  				unsignedLong64At: 18 put: 16r5555555555000000.
  			self assert: 16r5555555555555555 equals: (memory unsignedLong64At: 15).
  		memory unsignedLong64At: 7 put: value.
  		self assert: value equals: (memory unsignedLong64At: 7).
  		self assert: 0 equals: (memory at: (shift <= 31 ifTrue: [9] ifFalse: [17])).
  		self assert: 0 equals: (memory at: (shift <= 31  ifTrue: [13] ifFalse: [21]))].
  	self should: [memory unsignedLong64At: 1 put: -1] raise: Error.
  	64 to: 65 do:
  		[:shift|
  		self should: [memory unsignedLong64At: 1 put: 1 << shift] raise: Error]!

Item was changed:
+ ----- Method: MemoryTests>>testByteArray16BitShorts (in category 'tests') -----
- ----- Method: MemoryTests>>testByteArray16BitShorts (in category 'testing') -----
  testByteArray16BitShorts
  	"Test that ByteArray provides little-endian access for 16-bit accessors"
  	self testLittleEndianShortAccessFor: ByteArray!

Item was changed:
+ ----- Method: MemoryTests>>testByteArray32BitLongs (in category 'tests') -----
- ----- Method: MemoryTests>>testByteArray32BitLongs (in category 'testing') -----
  testByteArray32BitLongs
  	"Test that ByteArray provides big-endian access for 32-bit accessors"
  	self testLittleEndian32BitLongAccessFor: ByteArray!

Item was changed:
+ ----- Method: MemoryTests>>testByteArray64BitLongs (in category 'tests') -----
- ----- Method: MemoryTests>>testByteArray64BitLongs (in category 'testing') -----
  testByteArray64BitLongs
  	"Test that ByteArray provides big-endian access for 64-bit accessors"
  	self testLittleEndian64BitLongAccessFor: ByteArray!

Item was changed:
+ ----- Method: MemoryTests>>testDoubleWordArray16BitShorts (in category 'tests') -----
- ----- Method: MemoryTests>>testDoubleWordArray16BitShorts (in category 'testing') -----
  testDoubleWordArray16BitShorts
  	"Test that DoubleWordArray provides little-endian access for 16-bit accessors"
  	self testLittleEndianShortAccessFor: DoubleWordArray!

Item was changed:
+ ----- Method: MemoryTests>>testDoubleWordArray32BitLongs (in category 'tests') -----
- ----- Method: MemoryTests>>testDoubleWordArray32BitLongs (in category 'testing') -----
  testDoubleWordArray32BitLongs
  	"Test that DoubleWordArray provides little-endian access for 32-bit accessors"
  	self testLittleEndian32BitLongAccessFor: DoubleWordArray!

Item was changed:
+ ----- Method: MemoryTests>>testDoubleWordArray64BitLongs (in category 'tests') -----
- ----- Method: MemoryTests>>testDoubleWordArray64BitLongs (in category 'testing') -----
  testDoubleWordArray64BitLongs
  	"Test that DoubleWordArray provides little-endian access for 64-bit accessors"
  	self testLittleEndian64BitLongAccessFor: DoubleWordArray!

Item was added:
+ ----- Method: MemoryTests>>testFrameActivationLeak (in category 'tests') -----
+ testFrameActivationLeak
+ 	"This test tests if a remarried context hides a reference to an object... Thanks to Ryan Macnak for the test."
+ 	| array object |
+ 	array := WeakArray new: 1.
+ 	object := Object new.
+ 
+ 	array at: 1 put: object.
+ 	self assert: (array at: 1) == object.
+ 
+ 	Smalltalk garbageCollect.
+ 
+ 	self assert: (array at: 1) == object.
+ 	
+ 	"Trigger stack overflow, causing this frame to be flushed to an activation. When control returns here, a new frame will be created for the activation."
+ 	self assert: (self deepStack: 4096) = 16781312.
+ 
+ 	"Clears the temporary in the frame."
+ 	object := nil.
+ 	Smalltalk garbageCollect.
+ 
+ 	"Check the activation is not retaining a copy of our cleared temporary."
+ 	self assert: (array at: 1) == nil.!

Item was changed:
+ ----- Method: MemoryTests>>testLittleEndianBitmap16BitShorts (in category 'tests') -----
- ----- Method: MemoryTests>>testLittleEndianBitmap16BitShorts (in category 'testing') -----
  testLittleEndianBitmap16BitShorts
  	"Test that LittleEndianBitmap provides little-endian access for 16-bit accessors"
  	self testLittleEndianShortAccessFor: LittleEndianBitmap!

Item was changed:
+ ----- Method: MemoryTests>>testLittleEndianBitmap32BitLongs (in category 'tests') -----
- ----- Method: MemoryTests>>testLittleEndianBitmap32BitLongs (in category 'testing') -----
  testLittleEndianBitmap32BitLongs
  	"Test that LittleEndianBitmap provides little-endian access for 32-bit accessors"
  	self testLittleEndian32BitLongAccessFor: LittleEndianBitmap!

Item was changed:
+ ----- Method: MemoryTests>>testLittleEndianBitmap64BitLongs (in category 'tests') -----
- ----- Method: MemoryTests>>testLittleEndianBitmap64BitLongs (in category 'testing') -----
  testLittleEndianBitmap64BitLongs
  	"Test that LittleEndianBitmap provides little-endian access for 64-bit accessors"
  	self testLittleEndian64BitLongAccessFor: LittleEndianBitmap!

Item was changed:
+ ----- Method: MemoryTests>>testSignedOutOfRangeAccess (in category 'tests') -----
- ----- Method: MemoryTests>>testSignedOutOfRangeAccess (in category 'testing') -----
  testSignedOutOfRangeAccess
  	{ByteArray. Bitmap. LittleEndianBitmap. DoubleWordArray} do:
  		[:class| | bytesPerElement memory |
  		bytesPerElement := (class new: 0) bytesPerElement.
  		memory := class new: 64 / bytesPerElement.
  		1 to: 16 do:
  			[:i|
  			self should: [memory byteAt: i put: 1 << 8] raise: Error.
  			self should: [memory byteAt: i put: -1 << 7 - 1] raise: Error.
  			self should: [memory shortAt: i put: 1 << 16] raise: Error.
  			self should: [memory shortAt: i put: -1 << 15 - 1] raise: Error.
  			self should: [memory longAt: i put: 1 << 32] raise: Error.
  			self should: [memory longAt: i put: -1 << 31 - 1] raise: Error.
  			self should: [memory long64At: i put: 1 << 64] raise: Error.
  			self should: [memory long64At: i put: -1 << 63 - 1] raise: Error].
  		1 to: memory size do:
  			[:i|
  			self assert: 0 equals: (memory at: i)]]!

Item was changed:
+ ----- Method: MemoryTests>>testUnsignedOutOfRangeAccess (in category 'tests') -----
- ----- Method: MemoryTests>>testUnsignedOutOfRangeAccess (in category 'testing') -----
  testUnsignedOutOfRangeAccess
  	{ByteArray. Bitmap. LittleEndianBitmap. DoubleWordArray} do:
  		[:class| | bytesPerElement memory |
  		bytesPerElement := (class new: 0) bytesPerElement.
  		memory := class new: 64 / bytesPerElement.
  		1 to: 16 do:
  			[:i|
  			self should: [memory unsignedByteAt: i put: 1 << 8] raise: Error.
  			self should: [memory unsignedByteAt: i put: -1] raise: Error.
  			self should: [memory unsignedShortAt: i put: 1 << 16] raise: Error.
  			self should: [memory unsignedShortAt: i put: -1] raise: Error.
  			self should: [memory unsignedLongAt: i put: 1 << 32] raise: Error.
  			self should: [memory unsignedLongAt: i put: -1] raise: Error.
  			self should: [memory unsignedLong64At: i put: 1 << 64] raise: Error.
  			self should: [memory unsignedLong64At: i put: -1] raise: Error].
  		1 to: memory size do:
  			[:i|
  			self assert: 0 equals: (memory at: i)]]!

Item was changed:
  ----- Method: SpurMemoryManager>>markWeaklingsAndMarkAndFireEphemerons (in category 'gc - global') -----
  markWeaklingsAndMarkAndFireEphemerons
  	"After the initial scan-mark is complete ephemerons can be processed.
  	 Weaklings have accumulated on the weaklingStack, but more may be
  	 uncovered during ephemeron processing.  So trace the strong slots
  	 of the weaklings, and as ephemerons are processed ensure any newly
  	 reached weaklings are also traced."
  	| numTracedWeaklings |
  	<inline: false>
  	numTracedWeaklings := 0.
  	[coInterpreter markAndTraceUntracedReachableStackPages.
  	 coInterpreter markAndTraceMachineCodeOfMarkedMethods.
+ 	 "Make sure all reached weaklings have their strong slots traced before firing ephemerons..."
- 	 "Make sure all reached weaklings have their string slots traced before firing ephemerons..."
  	 [numTracedWeaklings := self markAndTraceWeaklingsFrom: numTracedWeaklings.
  	  (self sizeOfObjStack: weaklingStack) > numTracedWeaklings] whileTrue.
  	 self noUnscannedEphemerons ifTrue:
  		[coInterpreter
  			markAndTraceUntracedReachableStackPages;
  	 		markAndTraceMachineCodeOfMarkedMethods;
  			freeUntracedStackPages;
  			freeUnmarkedMachineCode.
  		 ^self].
  	 self markInactiveEphemerons ifFalse:
  		[self fireAllUnscannedEphemerons].
  	 self markAllUnscannedEphemerons]
  		repeat!

Item was changed:
  ----- Method: StackInterpreter>>makeBaseFrameFor: (in category 'frame access') -----
  makeBaseFrameFor: aContext "<Integer>"
  	"Marry aContext with the base frame of a new stack page.  Build the base
  	 frame to reflect the context's state.  Answer the new page."
  	<returnTypeC: #'StackPage *'>
  	| page pointer theMethod theIP numArgs stackPtrIndex maybeClosure rcvr |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
  	self assert: (objectMemory isContext: aContext).
  	self assert: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	page := stackPages newStackPage.
  	pointer := page baseAddress.
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	theMethod := objectMemory followObjField: MethodIndex ofObject: aContext.
  	(objectMemory isIntegerObject: theIP) ifFalse:
  		[self error: 'context is not resumable'].
  	theIP := objectMemory integerValueOf: theIP.
  	rcvr := objectMemory followField: ReceiverIndex ofObject: aContext.
  	"If the frame is a closure activation then the closure should be on the stack in
  	 the pushed receiver position (closures receive the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
  	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
  			[(objectMemory isForwarded: maybeClosure) ifTrue:
  				[maybeClosure := objectMemory fixFollowedField: ClosureIndex ofObject: aContext withInitialValue: maybeClosure].
  			 numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages longAt: pointer put: maybeClosure]
  		ifFalse:
  			[| header |
  			 header := objectMemory methodHeaderOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
  			 "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
  			 ((self methodHeaderHasPrimitive: header)
  			  and: [theIP = (1 + (self startPCOfMethodHeader: header))]) ifTrue:
  				[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)].
  			 stackPages longAt: pointer put: rcvr].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
+ 			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext).
+ 		"nil the slot in the context so that it doesn't inadvertently hang onto some collectable object.
+ 		 Thanks to Ryan Macnak for identifying this bug"
+ 		objectMemory storePointerUnchecked: ReceiverIndex + i ofObject: aContext withValue: objectMemory nilObject].
- 			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is sender context in base frame"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: (objectMemory followObjField: SenderIndex ofObject: aContext).
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: 0.
  	page baseFP: pointer; headFP: pointer.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: theMethod.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  	self assert: (self frameHasContext: page baseFP).
  	self assert: (self frameNumArgs: page baseFP) == numArgs.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: aContext.
  	stackPages
  		longAt: (pointer := pointer - objectMemory wordSize)
  		put: rcvr.
  	stackPtrIndex := self quickFetchInteger: StackPointerIndex ofObject: aContext.
  	self assert: ReceiverIndex + stackPtrIndex < (objectMemory lengthOf: aContext).
  	numArgs + 1 to: stackPtrIndex do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - objectMemory wordSize)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	theIP := self iframeInstructionPointerForIndex: theIP method: theMethod.
  	stackPages longAt: (pointer := pointer - objectMemory wordSize) put: theIP.
  	page headSP: pointer.
  	self assert: (self context: aContext hasValidInversePCMappingOf: theIP in: page baseFP).
  
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity) plus SmallInteger tags."
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: page baseFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: 0).
  	self assert: (objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)).
  	self assert: (self frameOfMarriedContext: aContext) = page baseFP.
  	self assert: (self validStackPageBaseFrame: page).
  	^page!



More information about the Vm-dev mailing list