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

commits at source.squeak.org commits at source.squeak.org
Tue Jan 27 00:32:08 UTC 2015


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

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

Name: VMMaker.oscog-eem.1027
Author: eem
Time: 26 January 2015, 4:30:51.306 pm
UUID: ab1faad9-ecf8-43d7-843d-b718feb0917c
Ancestors: VMMaker.oscog-eem.1026

Spur:
Make postBecomeAction's stack sweep only occur
in Spur (fix regression).  Refactor so that the scan is
not inlined. Don't assume newMethod is
non-immediate in post-become actions.

Fix stack adjust slip in primitiveSmallFloatTimesTwoPower

Make ensureBehaviorHash: fail for uninitialized
behaviours and hence fix the Behavior basicNew basicNew hang.

Fix word size assumption in assert in
withoutSmallIntegerTags:

LargeIntegersPlugin:
Remove/fix assumption of 32-bit digit length in
normalization routines.

Simulator:
Fix element sizes in Integer>>coerceTo:sim:

Add another objmem=>coInterpreter redirect

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

Item was changed:
  ----- Method: CoInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  	 To avoid a read barrier on inst var fetch we scan the receivers in the stack zone and follow
  	 any forwarded ones.  This is way cheaper than scanning all of memory as in the old become."
  	| theIPPtr |
  	<inline: false>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
+ 		(objectMemory isOopForwarded: newMethod) ifTrue:
- 		(objectMemory isForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP oop offset |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[theSP := thePage headSP.
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage
  				ifTrue: [theIPPtr := 0]
  				ifFalse:
  					[theIPPtr := theSP asUnsignedInteger.
  					 theSP := theSP + objectMemory wordSize].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  offset := self frameStackedReceiverOffset: theFP.
  			  oop := stackPages longAt: theFP + offset.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + offset
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			 (self isMachineCodeFrame: theFP)
  				ifTrue:
  					[oop := stackPages longAt: theFP + FoxMFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxMFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 oop := (self mframeHomeMethod: theFP) methodObject.
  					 self assert: (objectMemory isForwarded: oop) not]
  				ifFalse:
  					[oop := stackPages longAt: theFP + FoxIFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 oop := self iframeMethod: theFP.
  					 (objectMemory isForwarded: oop) ifTrue:
  						[| newOop delta |
  						 newOop := objectMemory followForwarded: oop.
  						 delta := newOop - oop.
  						 (theIPPtr ~= 0
  						  and: [(stackPages longAt: theIPPtr) > oop]) ifTrue:
  							[stackPages
  								longAt: theIPPtr
  								put: (stackPages longAt: theIPPtr) + delta].
  						stackPages
  							longAt: theFP + FoxIFSavedIP
  							put: (stackPages longAt: theFP + FoxIFSavedIP) + delta.
  						stackPages
  							longAt: theFP + FoxMethod
  							put: (oop := newOop)]].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theFP := callerFP].
  			 "And finally follow the saved context and the caller context."
  			 theSP := thePage baseAddress - objectMemory wordSize.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory isForwarded: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory followForwarded: oop)].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was changed:
  ----- Method: CoInterpreterTests>>testMinimumUnusedHeadroom (in category 'tests') -----
  testMinimumUnusedHeadroom
  	"self new testMinimumUnusedHeadroom"
  	| ci bpw |
  	CoInterpreter initializeWithOptions: Dictionary new.
  	ci := CogVMSimulator new.
+ 	bpw := ci objectMemory wordSize.
- 	bpw := ci objectMemory bytesPerWord.
  	ci initStackPagesForTests.
  	self assert: ci minimumUnusedHeadroom = ci stackPageByteSize.
  	0 to: ci stackPageByteSize - 1 by: bpw do:
  		[:p|
  		0 to: ci numStackPages - 1 do:
  			[:i| | page |
  			page := ci stackPages stackPageAt: i.
  			ci longAt: page baseAddress - p put: 1].
  		self assert: ci minimumUnusedHeadroom = (ci stackPageByteSize - (p + bpw))]!

Item was changed:
  ----- Method: Integer>>coerceTo:sim: (in category '*VMMaker-interpreter simulator') -----
  coerceTo: cTypeString sim: interpreter
  
  	| unitSize |
- 
  	cTypeString last = $* ifTrue: [  "C pointer"
  		unitSize := cTypeString caseOf: {
  		['char *'] -> [1].
+ 		['short *'] -> [2].
- 		['short *'] -> [4].
  		['int *'] -> [4].
+ 		['long *'] -> [interpreter wordSize].
  		['float *'] -> [4].
  		['double *'] -> [8].
  		['unsigned *'] -> [4].
  		['oop *'] -> [interpreter bytesPerOop].
  		}
+ 		otherwise: [ (cTypeString beginsWith: 'char') ifTrue: [1] ifFalse: [interpreter wordSize] ].
- 		otherwise: [ (cTypeString beginsWith: 'char') ifTrue: [1] ifFalse: [4] ].
  		^(CArray basicNew)
  			interpreter: interpreter address: self unitSize: unitSize;
  			yourself.
  	].
  	^ self  "C number (int, char, float, etc)"!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSmallFloatTimesTwoPower (in category 'arithmetic float primitives') -----
  primitiveSmallFloatTimesTwoPower
  	<option: #Spur64BitMemoryManager>
  	| rcvr arg |
  	<var: #rcvr type: #double>
  	arg := self stackTop.
  	(objectMemory isIntegerObject: arg)
  		ifTrue:
  			[rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
  			 arg := objectMemory integerValueOf: arg.
+ 			 self pop: 2
- 			 self pop: 1
  				thenPushFloat: (self cCode: [self ld: rcvr exp: arg]
  									inSmalltalk: [rcvr timesTwoPower: arg])]
  		ifFalse:
  			[self primitiveFail]!

Item was changed:
  ----- Method: LargeIntegersPlugin>>normalizeNegative: (in category 'oop functions') -----
  normalizeNegative: aLargeNegativeInteger 
  	"Check for leading zeroes and return shortened copy if so."
  	"First establish len = significant length."
  	| sLen val len oldLen minVal |
  	len := oldLen := self digitLength: aLargeNegativeInteger.
+ 	[len ~= 0 and: [(self unsafeByteOf: aLargeNegativeInteger at: len) = 0]]
- 	[len ~= 0 and: [(self unsafeByteOf: aLargeNegativeInteger at: len)
- 			= 0]]
  		whileTrue: [len := len - 1].
  	len = 0 ifTrue: [^ 0 asOop: SmallInteger].
  	"Now check if in SmallInteger range"
+ 	sLen := interpreterProxy minSmallInteger < -16r40000000
+ 				ifTrue: [8]
+ 				ifFalse: [4]. "SmallInteger minVal digitLength"
- 	sLen := 4.
- 	"SmallInteger minVal digitLength"
  	len <= sLen
  		ifTrue: 
  			["SmallInteger minVal"
  			minVal := interpreterProxy minSmallInteger.
+ 			(len < sLen
+ 			 or: [(self digitOfBytes: aLargeNegativeInteger at: sLen) < (self cDigitOfCSI: minVal at: sLen)
- 			(len < sLen or: [(self digitOfBytes: aLargeNegativeInteger at: sLen)
- 					< (self cDigitOfCSI: minVal at: sLen)
  				"minVal lastDigit"])
  				ifTrue: 
  					["If high digit less, then can be small"
  					val := 0.
+ 					len to: 1 by: -1 do:
+ 						[:i | val := val * 256 - (self unsafeByteOf: aLargeNegativeInteger at: i)].
- 					len
- 						to: 1
- 						by: -1
- 						do: [:i | val := val * 256 - (self unsafeByteOf: aLargeNegativeInteger at: i)].
  					^ val asOop: SmallInteger].
+ 			1 to: sLen do: [:i | "If all digits same, then = minVal (sr: minVal digits 1 to 3 are 0)"
+ 				(self digitOfBytes: aLargeNegativeInteger at: i) = (self cDigitOfCSI: minVal at: i)
+ 					ifFalse: "Not so; return self shortened"
+ 						[len < oldLen
+ 							ifTrue: "^ self growto: len"
+ 								[^ self bytes: aLargeNegativeInteger growTo: len]
- 			1 to: sLen do: [:i | "If all digits same, then = minVal (sr: minVal digits 1 to 3 are 
- 				          0)"
- 				(self digitOfBytes: aLargeNegativeInteger at: i)
- 					= (self cDigitOfCSI: minVal at: i)
- 					ifFalse: ["Not so; return self shortened"
- 						len < oldLen
- 							ifTrue: ["^ self growto: len"
- 								^ self bytes: aLargeNegativeInteger growTo: len]
  							ifFalse: [^ aLargeNegativeInteger]]].
  			^ minVal asOop: SmallInteger].
  	"Return self, or a shortened copy"
  	len < oldLen
+ 		ifTrue: "^ self growto: len"
+ 			[^ self bytes: aLargeNegativeInteger growTo: len]
- 		ifTrue: ["^ self growto: len"
- 			^ self bytes: aLargeNegativeInteger growTo: len]
  		ifFalse: [^ aLargeNegativeInteger]!

Item was changed:
  ----- Method: LargeIntegersPlugin>>normalizePositive: (in category 'oop functions') -----
  normalizePositive: aLargePositiveInteger 
  	"Check for leading zeroes and return shortened copy if so."
  	"First establish len = significant length."
  	| sLen val len oldLen |
  	len := oldLen := self digitLength: aLargePositiveInteger.
  	[len ~= 0 and: [(self unsafeByteOf: aLargePositiveInteger at: len)
  			= 0]]
  		whileTrue: [len := len - 1].
  	len = 0 ifTrue: [^ 0 asOop: SmallInteger].
  	"Now check if in SmallInteger range"
+ 	sLen := interpreterProxy minSmallInteger > 16r3FFFFFFF "SmallInteger maxVal digitLength."
+ 				ifTrue: [8]
+ 				ifFalse: [4].
- 	sLen := interpreterProxy bytesPerOop.
- 	"SmallInteger maxVal digitLength."
  	(len <= sLen
  	 and: [(self digitOfBytes: aLargePositiveInteger at: sLen)
  			<= (self cDigitOfCSI: interpreterProxy maxSmallInteger at: sLen)
  		"SmallInteger maxVal"])
  		ifTrue: 
  			["If so, return its SmallInt value"
  			val := 0.
  			len
  				to: 1
  				by: -1
  				do: [:i | val := val * 256 + (self unsafeByteOf: aLargePositiveInteger at: i)].
  			^ val asOop: SmallInteger].
  	"Return self, or a shortened copy"
  	len < oldLen
  		ifTrue: ["^ self growto: len"
  			^ self bytes: aLargePositiveInteger growTo: len]
  		ifFalse: [^ aLargePositiveInteger]!

Item was added:
+ ----- Method: NewCoObjectMemorySimulator>>signedMachineIntegerValueOf: (in category 'simulation only') -----
+ signedMachineIntegerValueOf: oop
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter signedMachineIntegerValueOf: oop!

Item was added:
+ ----- Method: NewObjectMemorySimulator>>signedMachineIntegerValueOf: (in category 'simulation only') -----
+ signedMachineIntegerValueOf: oop
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter signedMachineIntegerValueOf: oop!

Item was changed:
  ----- Method: SpurMemoryManager>>ensureBehaviorHash: (in category 'class table') -----
  ensureBehaviorHash: aBehavior
  	| newHash err |
  	<inline: true>
  	self assert: (coInterpreter addressCouldBeClassObj: aBehavior).
  	(newHash := self rawHashBitsOf: aBehavior) = 0 ifTrue:
+ 		[(coInterpreter objCouldBeClassObj: aBehavior) ifFalse:
+ 			[^PrimErrBadReceiver negated].
+ 		 (err := self enterIntoClassTable: aBehavior) ~= 0 ifTrue:
- 		[(err := self enterIntoClassTable: aBehavior) ~= 0 ifTrue:
  			[^err negated].
  		 newHash := self rawHashBitsOf: aBehavior.
  		 self assert: (self classAtIndex: newHash) = aBehavior].
  	^newHash!

Item was added:
+ ----- Method: SpurMemoryManager>>signedMachineIntegerValueOf: (in category 'simulation only') -----
+ signedMachineIntegerValueOf: oop
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	<doNotGenerate>
+ 	^coInterpreter signedMachineIntegerValueOf: oop!

Item was changed:
  ----- Method: StackInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  	 To avoid a read barrier on bytecode, literal and inst var fetch we scan the receivers and
  	 methods in the stack zone and follow any forwarded ones.  This is of course way cheaper
  	 than scanning all of memory as in the old become."
  	| theIPPtr |
  	<inline: false>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
+ 		(objectMemory isOopForwarded: newMethod) ifTrue:
- 		(objectMemory isForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP theIP oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[theSP := thePage headSP.
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage
  				ifTrue: [theIPPtr := 0]
  				ifFalse:
  					[theIPPtr := theSP asInteger.
  					 theSP := theSP + objectMemory wordSize].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  oop := stackPages longAt: theFP + FoxReceiver.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + FoxReceiver
  					put: (objectMemory followForwarded: oop)].
  			  theIP := (theFP + (self frameStackedReceiverOffset: theFP)) asInteger. "reuse theIP; its just an offset here"
  			  oop := stackPages longAt: theIP.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theIP
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  oop := self frameMethod: theFP.
  			  (objectMemory isForwarded: oop) ifTrue:
  				[| newOop delta |
  				 newOop := objectMemory followForwarded: oop.
  				 theIPPtr ~= 0 ifTrue:
  					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
  					 delta := newOop - oop.
  					 stackPages
  						longAt: theIPPtr
  						put: (stackPages longAt: theIPPtr) + delta].
  				stackPages
  					longAt: theFP + FoxMethod
  					put: (oop := newOop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asInteger.
  				 theFP := callerFP].
  			 "And finally follow the caller context."
  			 self assert: theFP = thePage baseFP.
  			 oop := self frameCallerContext: theFP.
  			 (objectMemory isForwarded: oop) ifTrue:
  				[self frameCallerContext: theFP put: (objectMemory followForwarded: oop)]]]!

Item was changed:
  ----- Method: StackInterpreter>>postBecomeAction: (in category 'object memory support') -----
  postBecomeAction: theBecomeEffectsFlags
+ 	objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 		[self spurPostBecomeAction: theBecomeEffectsFlags]!
- 	"Insulate the stack zone from the effects of a become.
- 	 All receivers must be unfollowed for two reasons:
- 		1. inst var access is direct with no read barrier
- 		2. super sends (always to the receiver) have no class check and so don't trap
- 		   for forwarded receivers.
- 	 Methods must be unfollowed since bytecode access is direct with no read barrier.
- 	 But this only needs to be done if the becomeEffectsFlags indicate that a
- 	 CompiledMethod was becommed.
- 	 The scheduler state must be followed, but only if the becomeEffectsFlags indicate
- 	 that a pointer object was becommed."
- 	self followForwardingPointersInStackZone: theBecomeEffectsFlags.
- 	theBecomeEffectsFlags ~= 0 ifTrue:
- 		[(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
- 			[self followForwardedMethodsInMethodCache.
- 			 self followForwardedMethodsInMethodZone]. "for CoInterpreter"
- 		 (theBecomeEffectsFlags anyMask: BecameActiveClassFlag) ifTrue:
- 			[self flushBecommedClassesInMethodCache.
- 			 self flushBecommedClassesInMethodZone]. "for CoInterpreter"
- 		 self followForwardingPointersInScheduler.
- 		 self followForwardingPointersInSpecialObjectsArray.
- 		 self followForwardingPointersInProfileState]!

Item was added:
+ ----- Method: StackInterpreter>>spurPostBecomeAction: (in category 'object memory support') -----
+ spurPostBecomeAction: theBecomeEffectsFlags
+ 	"Insulate the stack zone from the effects of a become.
+ 	 All receivers must be unfollowed for two reasons:
+ 		1. inst var access is direct with no read barrier
+ 		2. super sends (always to the receiver) have no class check and so don't trap
+ 		   for forwarded receivers.
+ 	 Methods must be unfollowed since bytecode access is direct with no read barrier.
+ 	 But this only needs to be done if the becomeEffectsFlags indicate that a
+ 	 CompiledMethod was becommed.
+ 	 The scheduler state must be followed, but only if the becomeEffectsFlags indicate
+ 	 that a pointer object was becommed."
+ 	<inline: false> "For VM profiling"
+ 	theBecomeEffectsFlags ~= 0 ifTrue:
+ 		["(theBecomeEffectsFlags anyMask: BecamePointerObjectFlag+BecameCompiledMethodFlag) ifTrue:
+ 			["self followForwardingPointersInStackZone: theBecomeEffectsFlags"]".
+ 		 (theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
+ 			[self followForwardedMethodsInMethodCache.
+ 			 self followForwardedMethodsInMethodZone]. "for CoInterpreter"
+ 		 (theBecomeEffectsFlags anyMask: BecameActiveClassFlag) ifTrue:
+ 			[self flushBecommedClassesInMethodCache.
+ 			 self flushBecommedClassesInMethodZone]. "for CoInterpreter"
+ 		 self followForwardingPointersInScheduler.
+ 		 self followForwardingPointersInSpecialObjectsArray.
+ 		 self followForwardingPointersInProfileState]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>withoutSmallIntegerTags: (in category 'frame access') -----
  withoutSmallIntegerTags: anInteger
+ 	self assert: (anInteger >= 0 and: [anInteger highBit <= (objectMemory wordSize * 8)]).
- 	self assert: (anInteger >= 0 and: [anInteger highBit <= 32]).
  	^(anInteger bitAnd: 16r80000000) ~= 0
  		ifTrue: ["negative"
  				(anInteger bitAnd: 16r7FFFFFFE) - 16r80000000]
  		ifFalse: ["positive"
  				anInteger - 1]!



More information about the Vm-dev mailing list