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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 5 01:18:14 UTC 2013


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

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

Name: VMMaker.oscog-eem.531
Author: eem
Time: 4 December 2013, 5:14:51.581 pm
UUID: 0593611a-d3b2-4c75-a08d-742f5d8f27cd
Ancestors: VMMaker.oscog-eem.530

Fix type of theIP in CoInterpreter>>makeBaseFrameFor: which was
causing mis-identification of machine-code pdcs in contexts.

Refactor validStackPageBaseFrames into validStackPageBaseFrame:
asnd use latter in makeBaseFrameFor:'s asserts to speed-up debug
VM.

Refactor followField:ofObject: into fixFollowedField:ofObject:withInitialValue:
and provide a non-immediate and an ecumenical version.

Add SpurMemMgr>>findStringBeginningWith: & printMethodReferencesTo:.

Add more debugging to inferTypesForImplicitlyTypedVariablesIn:.

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

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: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	self assert: HasBeenReturnedFromMCPC signedIntFromLong < 0.
  	theIP := (objectMemory isIntegerObject: theIP)
  				ifTrue: [objectMemory integerValueOf: theIP]
  				ifFalse: [HasBeenReturnedFromMCPC].
+ 	theMethod := objectMemory followNonImmediateField: MethodIndex ofObject: aContext.
- 	theMethod := objectMemory followField: MethodIndex ofObject: aContext.
  	page := self newStackPage.
  	"first word on stack is caller context of base frame"
  	stackPages
  		longAt: (pointer := page baseAddress)
  		put: (objectMemory fetchPointer: SenderIndex ofObject: aContext).
  	"second word is the context itself; needed for cannotReturn processing; see ceBaseReturn:."
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		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 receiver the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
  	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
  			[numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: maybeClosure]
  		ifFalse:
  			[| header |
  			 header := self headerOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
  			 self cppIf: MULTIPLEBYTECODESETS
  				ifTrue: "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
  					[(theIP signedIntFromLong > 0
  					  and: [(self methodHeaderHasPrimitive: header)
  					  and: [theIP = (1 + (objectMemory lastPointerOf: theMethod))]]) ifTrue:
  						[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)]].
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: rcvr].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is base return trampoline"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: cogit ceBaseFrameReturnPC.
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		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 signedIntFromLong < 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.
  			 theMethod := cogMethod asInteger.
  			 maybeClosure ~= objectMemory nilObject
  				ifTrue:
  					["If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  					  appropriately so that the frame stays in the cannotReturn: state."
  					 theIP = HasBeenReturnedFromMCPC signedIntFromLong
  						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].
  					 stackPages
  						longAt: (pointer := pointer - BytesPerWord)
  						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 signedIntFromLong
  								ifTrue: [cogit ceCannotResumePC]
  								ifFalse: [theMethod asInteger - theIP].
  					 stackPages
  						longAt: (pointer := pointer - BytesPerWord)
  						put: theMethod + MFMethodFlagHasContextFlag].
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: aContext]
  		ifFalse:
  			[stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: theMethod.
  			stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: aContext.
  			stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  			stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				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 - BytesPerWord)
  		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 - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	stackPages longAt: (pointer := pointer - BytesPerWord) 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).
- 	self assert: self validStackPageBaseFrames.
  	^page!

Item was added:
+ ----- Method: CoInterpreter>>validStackPageBaseFrame: (in category 'stack pages') -----
+ validStackPageBaseFrame: aPage
+ 	"Check that the base frame in the stack page has a valid sender and saved context."
+ 	<var: #aPage type: #'StackPage *'>
+ 	<inline: false>
+ 	| savedThisContext senderContextOrNil |
+ 	senderContextOrNil := stackPages longAt: aPage baseAddress.
+ 	savedThisContext := stackPages longAt: aPage baseAddress - BytesPerWord.
+ 	(self asserta: aPage baseFP + (self frameStackedReceiverOffset: aPage baseFP) + (2 * BytesPerWord) = aPage baseAddress) ifFalse:
+ 		[^false].
+ 	(self asserta: (objectMemory addressCouldBeObj: senderContextOrNil)) ifFalse:
+ 		[^false].
+ 	(self asserta: (objectMemory addressCouldBeObj: savedThisContext)) ifFalse:
+ 		[^false].
+ 	(self asserta: (senderContextOrNil = objectMemory nilObject or: [objectMemory isContext: senderContextOrNil])) ifFalse:
+ 		[^false].
+ 	(self asserta: (objectMemory isContext: savedThisContext)) ifFalse:
+ 		[^false].
+ 	(self asserta: (self frameCallerContext: aPage baseFP) = senderContextOrNil) ifFalse:
+ 		[^false].
+ 	(self asserta: (self frameContext: aPage baseFP) = savedThisContext) ifFalse:
+ 		[^false].
+ 	^true!

Item was removed:
- ----- Method: CoInterpreter>>validStackPageBaseFrames (in category 'stack pages') -----
- validStackPageBaseFrames
- 	"Check that the base frames in all in-use stack pages have a sender and a saved context."
- 	<var: #aPage type: #'StackPage *'>
- 	0 to: numStackPages - 1 do:
- 		[:i| | aPage senderContextOrNil savedThisContext |
- 		aPage := stackPages stackPageAt: i.
- 		(stackPages isFree: aPage) ifFalse:
- 			[senderContextOrNil := stackPages longAt: aPage baseAddress.
- 			 savedThisContext := stackPages longAt: aPage baseAddress - BytesPerWord.
- 			 (self asserta: aPage baseFP + (self frameStackedReceiverOffset: aPage baseFP) + (2 * BytesPerWord) = aPage baseAddress) ifFalse:
- 				[^false].
- 			 (self asserta: (objectMemory addressCouldBeObj: senderContextOrNil)) ifFalse:
- 				[^false].
- 			 (self asserta: (objectMemory addressCouldBeObj: savedThisContext)) ifFalse:
- 				[^false].
- 			 (self asserta: (senderContextOrNil = objectMemory nilObject or: [objectMemory isContext: senderContextOrNil])) ifFalse:
- 				[^false].
- 			 (self asserta: (objectMemory isContext: savedThisContext)) ifFalse:
- 				[^false].
- 			 (self asserta: (self frameCallerContext: aPage baseFP) = senderContextOrNil) ifFalse:
- 				[^false].
- 			 (self asserta: (self frameContext: aPage baseFP) = savedThisContext) ifFalse:
- 				[^false]]].
- 	^true!

Item was added:
+ ----- Method: SpurMemoryManager>>findStringBeginningWith: (in category 'debug support') -----
+ findStringBeginningWith: aCString
+ 	"Print the oops of all string-like things that start with the same characters as aCString"
+ 	<api>
+ 	<var: #aCString type: #'char *'>
+ 	| cssz |
+ 	cssz := self strlen: aCString.
+ 	self allObjectsDo:
+ 		[:obj|
+ 		 ((self isBytesNonInt: obj)
+ 		  and: [(self lengthOf: obj) >= cssz
+ 		  and: [(self str: aCString n: (self pointerForOop: obj + BaseHeaderSize) cmp: cssz) = 0]]) ifTrue:
+ 				[coInterpreter printHex: obj; space; printNum: (self lengthOf: obj); space; printOopShort: obj; cr]]!

Item was added:
+ ----- Method: SpurMemoryManager>>fixFollowedField:ofObject:withInitialValue: (in category 'forwarding') -----
+ fixFollowedField: fieldIndex ofObject: anObject withInitialValue: initialValue
+ 	"Private helper for followField:ofObject: to avoid code duplication for rare case."
+ 	<inline: false>
+ 	| objOop |
+ 	self assert: (self isOopForwarded: initialValue).
+ 	objOop := self followForwarded: objOop.
+ 	self storePointer: fieldIndex ofObject: anObject withValue: objOop.
+ 	^objOop!

Item was changed:
  ----- Method: SpurMemoryManager>>followField:ofObject: (in category 'forwarding') -----
  followField: fieldIndex ofObject: anObject
  	"Make sure the oop at fieldIndex in anObject is not forwarded (follow the
+ 	 forwarder there-in if so).  Answer the (possibly followed) oop at fieldIndex."
- 	 forwarder there-in if so).  Answer the (possibly followed) oop at fieldIndex.
- 	 N.B. the oop is assumed to be non-immediate."
  	| objOop |
  	objOop := self fetchPointer: fieldIndex ofObject: anObject.
+ 	(self isOopForwarded: objOop) ifTrue:
+ 		[objOop := self fixFollowedField: fieldIndex ofObject: anObject withInitialValue: objOop].
- 	self assert: (self isNonImmediate: objOop).
- 	(self isForwarded: objOop) ifTrue:
- 		[objOop := self followForwarded: objOop.
- 		 self storePointer: fieldIndex ofObject: anObject withValue: objOop].
  	^objOop!

Item was added:
+ ----- Method: SpurMemoryManager>>followNonImmediateField:ofObject: (in category 'forwarding') -----
+ followNonImmediateField: fieldIndex ofObject: anObject
+ 	"Make sure the oop at fieldIndex in anObject is not forwarded (follow the
+ 	 forwarder there-in if so).  Answer the (possibly followed) oop at fieldIndex.
+ 	 N.B. the oop is assumed to be non-immediate."
+ 	| objOop |
+ 	objOop := self fetchPointer: fieldIndex ofObject: anObject.
+ 	self assert: (self isNonImmediate: objOop).
+ 	(self isForwarded: objOop) ifTrue:
+ 		[objOop := self fixFollowedField: fieldIndex ofObject: anObject withInitialValue: objOop].
+ 	^objOop!

Item was added:
+ ----- Method: SpurMemoryManager>>printMethodReferencesTo: (in category 'debug printing') -----
+ printMethodReferencesTo: anOop
+ 	"Scan the heap printing the oops of any and all methods that refer to anOop"
+ 	<api>
+ 	self allObjectsDo:
+ 		[:obj| | i |
+ 		 (self isCompiledMethod: obj) ifTrue:
+ 			[i := (self literalCountOf: obj) + LiteralStart - 1.
+ 			[(i := i - 1) >= 0] whileTrue:
+ 				[anOop = (self fetchPointer: i ofObject: obj) ifTrue:
+ 					[coInterpreter printHex: obj; print: ' @ '; printNum: i; space; printOopShort: obj; cr.
+ 					 i := 0]]]]!

Item was changed:
  ----- Method: StackInterpreter>>followForwardingPointersInScheduler (in category 'object memory support') -----
  followForwardingPointersInScheduler
  	| schedAssoc sched procLists |
  	schedAssoc := objectMemory splObj: SchedulerAssociation.
  	"the GC follows pointers in the special objects array for us."
  	self assert: (objectMemory isForwarded: schedAssoc) not.
  
+ 	sched := objectMemory followNonImmediateField: ValueIndex ofObject: schedAssoc.
- 	sched := objectMemory followField: ValueIndex ofObject: schedAssoc.
  
+ 	procLists := objectMemory followNonImmediateField: ProcessListsIndex ofObject: sched.
- 	procLists := objectMemory followField: ProcessListsIndex ofObject: sched.
  
  	0 to: (objectMemory numSlotsOf: procLists) - 1 do:
  		[:i| | list first last next |
+ 		list := objectMemory followNonImmediateField: i ofObject: procLists.
+ 		first := objectMemory followNonImmediateField: FirstLinkIndex ofObject: list.
+ 		last := objectMemory followNonImmediateField: LastLinkIndex ofObject: list.
- 		list := objectMemory followField: i ofObject: procLists.
- 		first := objectMemory followField: FirstLinkIndex ofObject: list.
- 		last := objectMemory followField: LastLinkIndex ofObject: list.
  		[first ~= last] whileTrue:
+ 			[next := objectMemory followNonImmediateField: NextLinkIndex ofObject: first.
- 			[next := objectMemory followField: NextLinkIndex ofObject: first.
  			 first := next]]
  !

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: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	page := self newStackPage.
  	pointer := page baseAddress.
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
+ 	theMethod := objectMemory followNonImmediateField: MethodIndex ofObject: aContext.
- 	theMethod := objectMemory followField: 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 receiver the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
  	maybeClosure := objectMemory followField: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
  			[numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages longAt: pointer put: maybeClosure]
  		ifFalse:
+ 			[| header |
- 			[| header field |
  			 header := self headerOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
  			 self cppIf: MULTIPLEBYTECODESETS
  				ifTrue: "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
  					[(theIP signedIntFromLong > 0
  					  and: [(self methodHeaderHasPrimitive: header)
  					  and: [theIP = (1 + (objectMemory lastPointerOf: theMethod))]]) 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 - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is sender context in base frame"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: (objectMemory fetchPointer: SenderIndex ofObject: aContext).
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: 0.
  	page baseFP: pointer; headFP: pointer.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: theMethod.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		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 - BytesPerWord)
  		put: aContext.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		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 - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	theIP := self iframeInstructionPointerForIndex: theIP method: theMethod.
  	stackPages longAt: (pointer := pointer - BytesPerWord) 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).
- 	self assert: self validStackPageBaseFrames.
  	^page!

Item was added:
+ ----- Method: StackInterpreter>>validStackPageBaseFrame: (in category 'stack pages') -----
+ validStackPageBaseFrame: aPage
+ 	"Check that the base frame in the stack page has a valid sender context."
+ 	<var: #aPage type: #'StackPage *'>
+ 	<inline: false>
+ 	| senderContextOrNil |
+ 	(self asserta: (self isBaseFrame: aPage baseFP)) ifFalse:
+ 		[^false].
+ 	senderContextOrNil := self frameCallerContext: aPage baseFP.
+ 	(self asserta: (objectMemory addressCouldBeObj: senderContextOrNil)) ifFalse:
+ 		[^false].
+ 	(self asserta: (senderContextOrNil = objectMemory nilObject or: [objectMemory isContext: senderContextOrNil])) ifFalse:
+ 		[^false].
+ 	^true!

Item was changed:
  ----- Method: StackInterpreter>>validStackPageBaseFrames (in category 'stack pages') -----
  validStackPageBaseFrames
+ 	"Check that the base frames in all in-use stack pages have a sender and a saved context."
- 	"Check that the base frames in all in-use stack pages have a valid sender context."
  	<var: #aPage type: #'StackPage *'>
  	0 to: numStackPages - 1 do:
+ 		[:i| | aPage senderContextOrNil savedThisContext |
- 		[:i| | aPage senderContextOrNil |
  		aPage := stackPages stackPageAt: i.
  		(stackPages isFree: aPage) ifFalse:
+ 			[(self validStackPageBaseFrame: aPage) ifFalse:
- 			[(self asserta: (self isBaseFrame: aPage baseFP)) ifFalse:
- 				[^false].
- 			 senderContextOrNil := self frameCallerContext: aPage baseFP.
- 			 (self asserta: (objectMemory addressCouldBeObj: senderContextOrNil)) ifFalse:
- 				[^false].
- 			 (self asserta: (senderContextOrNil = objectMemory nilObject or: [objectMemory isContext: senderContextOrNil])) ifFalse:
  				[^false]]].
  	^true!

Item was changed:
  ----- Method: TMethod>>inferTypesForImplicitlyTypedVariablesIn: (in category 'type inference') -----
  inferTypesForImplicitlyTypedVariablesIn: aCodeGen
+ 	"infer types for untyped variables form assignments and arithmetic uses.
+ 	 This for debugging:
+ 		(self copy inferTypesForImplicitlyTypedVariablesIn: aCodeGen)"
+ 	| explicitlyTyped effectiveNodes |
- 	| explicitlyTyped |
  	explicitlyTyped := declarations keys asSet.
+ 	effectiveNodes := Dictionary new. "this for debugging"
  	parseTree nodesDo:
  		[:node| | type var m |
  		"If there is something of the form i >= 0, then i should be signed, not unsigned."
  		(node isSend
  		 and: [(locals includes: (var := node receiver variableNameOrNil))
  		 and: [(explicitlyTyped includes: var) not
  		 and: [(#(<= < >= >) includes: node selector)
  		 and: [node args first isConstant
  		 and: [node args first value = 0
  		 and: [(type := self typeFor: var in: aCodeGen) notNil
  		 and: [type first == $u]]]]]]]) ifTrue:
+ 			[declarations at: var put: (declarations at: var) allButFirst.
+ 			 effectiveNodes at: var put: { declarations at: var. node }].
- 			[declarations at: var put: (declarations at: var) allButFirst].
  		"if an assignment of a known send, set the variable's type to the return type of the send."
  		(node isAssignment
  		 and: [(locals includes: (var := node variable name))
  		 and: [(declarations includesKey: var) not
  		 and: [node expression isSend
  		 and: [(m := aCodeGen anyMethodNamed: node expression selector) notNil]]]]) ifTrue:
  			[(#(sqInt void nil) includes: m returnType) ifFalse:
  				["the $: is to map things like unsigned field : 3 to usqInt"
  				 declarations
  					at: var
+ 					put: ((m returnType includes: $:) ifTrue: [#usqInt] ifFalse: [m returnType]), ' ', var.
+ 				 effectiveNodes at: var put: { declarations at: var. node }]]].
+ 	^effectiveNodes!
- 					put: ((m returnType includes: $:) ifTrue: [#usqInt] ifFalse: [m returnType]), ' ', var]]]!



More information about the Vm-dev mailing list