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

commits at source.squeak.org commits at source.squeak.org
Thu Jan 1 21:20:07 UTC 2015


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

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

Name: VMMaker.oscog-eem.1005
Author: eem
Time: 1 January 2015, 1:17:34.558 pm
UUID: 60586ca3-d2d0-4b96-b7e0-7956eb990e3c
Ancestors: VMMaker.oscog-eem.1004

Fix stupid regression in findUnwindThroughContext:.

Minor streamline to commonReturn in CoInterpreter.

Add range check for 64-bit SmallInteger to Float
conversion since in 64-bits this can overflow the
exact float range.

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

Item was changed:
  ----- Method: Spur64BitMemoryManager>>loadFloatOrIntFrom: (in category 'interpreter access') -----
  loadFloatOrIntFrom: floatOrIntOop
  	"If floatOrInt is an integer, then convert it to a C double float and return it.
  	 If it is a Float, then load its value and return it.
  	 Otherwise fail -- ie return with primErrorCode non-zero."
  
  	<inline: true>
  	<returnTypeC: #double>
+ 	| result tagBits shift |
- 	| result tagBits |
  	<var: #result type: #double>
  
  	(tagBits := floatOrIntOop bitAnd: self tagMask) ~= 0
  		ifTrue:
  			[tagBits = self smallFloatTag ifTrue:
  				[^self smallFloatValueOf: floatOrIntOop].
+ 			 (tagBits = self smallIntegerTag
+ 			  and: [shift := 64 - self numTagBits - self smallFloatMantissaBits.
+ 				(self cCode: [floatOrIntOop << shift]
+ 						inSmalltalk: [floatOrIntOop << shift bitAnd: 1 << 64 - 1]) >> shift = floatOrIntOop]) ifTrue:
- 			 tagBits = self smallIntegerTag ifTrue:
  				[^(self integerValueOf: floatOrIntOop) asFloat]]
  		ifFalse:
  			[(self classIndexOf: floatOrIntOop) = ClassFloatCompactIndex ifTrue:
  				[self cCode: '' inSmalltalk: [result := Float new: 2].
  				 self fetchFloatAt: floatOrIntOop + self baseHeaderSize into: result.
  				 ^result]].
  	coInterpreter primitiveFail.
  	^0.0!

Item was changed:
  ----- Method: StackInterpreter>>commonReturn (in category 'return bytecodes') -----
  commonReturn
  	"Do an ^-return (return from method), checking for unwinds if this is a block activation.
  	 Note: Assumed to be inlined into the dispatch loop."
  
  	<sharedCodeInCase: #returnReceiver>
  	| closure home unwindContextOrNilOrZero frameToReturnTo contextToReturnTo theFP callerFP newPage |
  	<var: #frameToReturnTo type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #newPage type: #'StackPage *'>
  	<var: #thePage type: #'StackPage *'>
  
  	"If this is a method simply return to the  sender/caller."
+ 	(self iframeIsBlockActivation: localFP) ifFalse:
- 	(self frameIsBlockActivation: localFP) ifFalse:
  		[^self commonCallerReturn].
  
  	"Since this is a block activation the closure is on the stack above any args and the frame."
  	closure := self pushedReceiverOrClosureOfFrame: localFP.
  
  	home := nil.
  	"Walk the closure's lexical chain to find the context or frame to return from (home)."
  	[closure ~= objectMemory nilObject] whileTrue:
  		[home := objectMemory followField: ClosureOuterContextIndex ofObject: closure.
  		 closure := objectMemory followField: ClosureIndex ofObject: home].
  	"home is to be returned from provided there is no unwind-protect activation between
  	 this frame and home's sender.  Search for an unwind.  findUnwindThroughContext:
  	 will answer either the context for an unwind-protect activation or nilObj if the sender
  	 cannot be found or 0 if no unwind is found but the sender is.  We must update the
  	 current page's headFrame pointers to enable the search to identify widowed contexts
  	 correctly."
  	self writeBackHeadFramePointers.
  	self externalizeIPandSP.
  	unwindContextOrNilOrZero := self findUnwindThroughContext: home.
  	unwindContextOrNilOrZero = objectMemory nilObject ifTrue:
  		["error: can't find home on chain; cannot return"
  		 ^self internalCannotReturn: localReturnValue].
  	unwindContextOrNilOrZero ~= 0 ifTrue:
  		[^self internalAboutToReturn: localReturnValue through: unwindContextOrNilOrZero].
  
  	"Now we know home is on the sender chain.
  	 We could be returning to either a context or a frame.  Find out which."
  	contextToReturnTo := nil.
  	(self isMarriedOrWidowedContext: home)
  		ifTrue:
  			[self assert: (self checkIsStillMarriedContext: home currentFP: localFP).
  			 theFP := self frameOfMarriedContext: home.
  			 (self isBaseFrame: theFP)
  				ifTrue:
  					[contextToReturnTo := self frameCallerContext: theFP]
  				ifFalse:
  					[frameToReturnTo := self frameCallerFP: theFP]]
  		ifFalse:
  			[contextToReturnTo := objectMemory fetchPointer: SenderIndex ofObject: home.
  			 ((objectMemory isContext: contextToReturnTo)
  			  and: [self isMarriedOrWidowedContext: contextToReturnTo]) ifTrue:
  				[self assert: (self checkIsStillMarriedContext: contextToReturnTo currentFP: localFP).
  			 	 frameToReturnTo := self frameOfMarriedContext: contextToReturnTo.
  				 contextToReturnTo := nil]].
  
  	"If returning to a context we must make a frame for it unless it is dead."
  	contextToReturnTo ~= nil ifTrue:
  		[frameToReturnTo := self establishFrameForContextToReturnTo: contextToReturnTo.
  		 frameToReturnTo == 0 ifTrue:
  			["error: home's sender is dead; cannot return"
  			 ^self internalCannotReturn: localReturnValue]].
  
  	"Now we have a frame to return to.  If it is on a different page we must free intervening pages and
  	 nil out intervening contexts.  We must free intervening stack pages because if we leave the pages
  	 to be divorced then their contexts will be divorced with intact senders and instruction pointers.  This
+ 	 code is similar to primitiveTerminateTo.  We must move any frames on intervening pages above the
- 	 code is similar to primitiveTerminateTo.  We must move any frames on itervening pages above the
  	 frame linked to because these may be in use, e.g. via co-routining (see baseFrameReturn)."
  	self assert: stackPages pageListIsWellFormed.
  	newPage := stackPages stackPageFor: frameToReturnTo.
  	newPage ~~ stackPage ifTrue:
  		[| currentCtx thePage nextCntx |
  		 currentCtx := self frameCallerContext: stackPage baseFP.
  		 stackPages freeStackPage: stackPage.
  		 [self assert: (objectMemory isContext: currentCtx).
  		  (self isMarriedOrWidowedContext: currentCtx)
  		   and: [(stackPages stackPageFor: (theFP := self frameOfMarriedContext: currentCtx)) = newPage]] whileFalse:
  			[(self isMarriedOrWidowedContext: currentCtx)
  				ifTrue:
  					[thePage := stackPages stackPageFor: theFP.
  					 theFP ~= thePage headFP ifTrue:
  						["Since we've just deallocated a page we know that newStackPage won't deallocate an existing one."
  						 self moveFramesIn: thePage through: (self findFrameAbove: theFP inPage: thePage) toPage: self newStackPage].
  					 currentCtx := self frameCallerContext: thePage baseFP.
  					 stackPages freeStackPage: thePage]
  				ifFalse:
  					[nextCntx := objectMemory fetchPointer: SenderIndex ofObject: currentCtx.
  					 self markContextAsDead: currentCtx.
  					 currentCtx := nextCntx]].
  		 self setStackPageAndLimit: newPage.
  		 localSP := stackPage headSP.
  		 localFP := stackPage headFP].
  
  	"Two cases.  Returning to the top frame on a new page or an interior frame on the current page.
  	 The top frame has its instruction pointer on top of stack. An interior frame has its instruction pointer
  	 in the caller frame. We need to peel back any frames on the page until we get to the correct frame."
  
  	localFP = frameToReturnTo
  		ifTrue: "pop the saved IP, push the return value and continue."
  			[localIP := self pointerForOop: self internalStackTop]
  		ifFalse:
  			[[callerFP := localFP.
  			  localFP := self frameCallerFP: localFP.
  			  localFP ~~ frameToReturnTo] whileTrue.
  			localIP := self frameCallerSavedIP: callerFP.
  			localSP := (self frameCallerSP: callerFP) - objectMemory wordSize].
  	self maybeReturnToMachineCodeFrame.
  	self setMethod: (self frameMethod: localFP).
  	self fetchNextBytecode.
  	self internalStackTopPut: localReturnValue!

Item was changed:
  ----- Method: StackInterpreter>>findUnwindThroughContext: (in category 'return bytecodes') -----
  findUnwindThroughContext: homeContext
  	"Search for either an unwind-protect (activation of method with primitive 198)
  	 or homeContext along the sender chain, which ever is found first.  Return values:
  		0			home context was found on sender chain with no intervening unwind-protects
  		nilObj		home context could not be found => cannotReturn
  		context		the context of an intervening unwind-protect implies home context was found"
  	| onSamePage ctxtOrNilOrZero theMethod |
  	"Almost always (98%) the home is on the same page."
  	onSamePage := (self isStillMarriedContext: homeContext)
  					and: [(stackPages pageIndexFor: framePointer) = (stackPages pageIndexFor: (self frameOfMarriedContext: homeContext))].
  	"Since nothing changes we don't need to internalize."
  	ctxtOrNilOrZero := self findMethodWithPrimitive: 198 FromFP: framePointer UpToContext: homeContext.
  	(onSamePage or: [ctxtOrNilOrZero = 0]) ifTrue:
  		[theMethod := objectMemory fetchPointer: MethodIndex ofObject: homeContext.
  		 (self primitiveIndexOf: theMethod) = 198 ifTrue:
  			[^homeContext].
+ 		 self assert: ctxtOrNilOrZero ~= objectMemory nilObject.
+ 		 ^ctxtOrNilOrZero].
+ 	"If an unwnd was found, can the home context be found also?"
+ 	ctxtOrNilOrZero ~= objectMemory nilObject ifTrue:
- 		 ^0].
- 	"Found an unwind.  Can the home context be found also?"
- 	ctxtOrNilOrZero = objectMemory nilObject ifFalse:
  		[(self findMethodWithPrimitive: 0 FromContext: ctxtOrNilOrZero UpToContext: homeContext)
  		  = objectMemory nilObject ifTrue:
  			[^objectMemory nilObject]].
  	^ctxtOrNilOrZero!

Item was added:
+ ----- Method: StackInterpreter>>iframeIsBlockActivation: (in category 'frame access') -----
+ iframeIsBlockActivation: theFP "<Integer>"
+ 	^self frameIsBlockActivation: theFP!



More information about the Vm-dev mailing list