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

commits at source.squeak.org commits at source.squeak.org
Tue Jan 14 01:39:52 UTC 2014


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

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

Name: VMMaker.oscog-eem.584
Author: eem
Time: 13 January 2014, 5:36:41.137 pm
UUID: f8e3994b-6462-4df0-bc8e-c71034adf6aa
Ancestors: VMMaker.oscog-eem.583

Spur:
Fix swizzling on startup.  Enumerate up to freeOldSpaceStart, not
endOfMemory.  Fixes startup of e.g. bootstrapped Squeak4.3 image.

Beef up asserts in initializeFromFreeChunks: (for bootstrap).

Fix isValidSegmentBridge: to not subtract header size from bridge.

Fix assert in checkForAndFollowForwardedPrimitiveState.

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

Item was changed:
  ----- Method: SpurMemoryManager>>adjustAllOopsBy: (in category 'snapshot') -----
  adjustAllOopsBy: bytesToShift
  	"Adjust all oop references by the given number of bytes. This is
  	 done just after reading in an image when the new base address
  	 of the object heap is different from the base address in the image,
  	 or when loading multiple segments that have been coalesced.  Also
  	 set bits in the classTableBitmap corresponding to used classes."
  
  	| obj |
  	self countNumClassPagesPreSwizzle: bytesToShift;
  		ensureAdequateClassTableBitmap.
  	(bytesToShift ~= 0
  	 or: [segmentManager numSegments > 1])
  		ifTrue:
  			[self assert: self newSpaceIsEmpty.
  			 obj := self objectStartingAt: oldSpaceStart.
+ 			 [self oop: obj isLessThan: freeOldSpaceStart] whileTrue:
- 			 [self oop: obj isLessThan: endOfMemory] whileTrue:
  				[(self isFreeObject: obj)
  					ifTrue: [self swizzleFieldsOfFreeChunk: obj]
  					ifFalse:
  						[self inClassTableBitmapSet: (self classIndexOf: obj).
  						 self swizzleFieldsOfObject: obj].
  				 obj := self objectAfter: obj]]
  		ifFalse:
  			[self assert: self newSpaceIsEmpty.
  			 obj := self objectStartingAt: oldSpaceStart.
  			 [self oop: obj isLessThan: endOfMemory] whileTrue:
  				[(self isFreeObject: obj) ifFalse:
  					[self inClassTableBitmapSet: (self classIndexOf: obj)].
  				 obj := self objectAfter: obj]]!

Item was changed:
  ----- Method: SpurSegmentManager>>initializeFromFreeChunks: (in category 'simulation only') -----
  initializeFromFreeChunks: freeChunks
  	"For testing, create a set of segments using the freeChunks as bridges."
+ 	self assert: (freeChunks allSatisfy: [:f| manager hasOverflowHeader: f]).
  	numSegments := freeChunks size.
  	freeChunks do:
  		[:f|
  		manager initSegmentBridgeWithBytes: (manager bytesInObject: f) at: (manager startOfObject: f).
  		self assert: (manager isSegmentBridge: f)].
  	segments := (1 to: numSegments) collect:
  					[:i| | bridge start size |
  					bridge := freeChunks at: i.
  					start := i = 1
  								ifTrue: [manager newSpaceLimit]
  								ifFalse: [manager addressAfter: (freeChunks at: i - 1)].
  					size := bridge + manager baseHeaderSize - start.
  					SpurSegmentInfo new
  						segStart: start;
  						segSize: size;
  						yourself].
  	manager setEndOfMemory: segments last segLimit.
  	segments := CArrayAccessor on: segments.
+ 	freeChunks with: segments object do:
+ 		[:bridge :segment|
+ 		self assert: (self isValidSegmentBridge: bridge).
+ 		self assert: bridge = (self bridgeFor: segment)]!
- 	freeChunks do:
- 		[:bridge| self assert: (self isValidSegmentBridge: bridge)]!

Item was changed:
  ----- Method: SpurSegmentManager>>isValidSegmentBridge: (in category 'testing') -----
  isValidSegmentBridge: objOop
  	"bridges bridge the gaps between segments. They are the last object in each segment."
+ 	^(manager addressCouldBeObj: objOop)
+ 	  and: [(manager isSegmentBridge: objOop)
+ 	  and: [(manager hasOverflowHeader: objOop)
- 	^(manager addressCouldBeObj: objOop - manager baseHeaderSize)
- 	 and: [(manager isSegmentBridge: objOop)
- 	 and: [(manager hasOverflowHeader: objOop)
  		or: [(manager numSlotsOfAny: objOop) = 0]]]!

Item was changed:
  ----- Method: StackInterpreter>>checkForAndFollowForwardedPrimitiveState (in category 'primitive support') -----
  checkForAndFollowForwardedPrimitiveState
  	"In Spur a primitive may fail due to encountering a forwarder.
  	 On failure check the accessorDepth for the primitive and
  	 if non-negative scan the args to the depth, following any
  	 forwarders.  Answer if any are found so the prim can be retried."
  	<option: #SpurObjectMemory>
  	| primIndex accessorDepth found |
  	self assert: self successful not.
  	found := false.
  	primIndex := self primitiveIndexOf: newMethod.
+ 	self assert: (primIndex = 117
+ 				 or: [primitiveFunctionPointer = (self functionPointerFor: primIndex inClass: objectMemory nilObject)]).
- 	self assert: (self
- 					cCode:
- 						[primitiveFunctionPointer = (self functionPointerFor: primIndex inClass: objectMemory nilObject)]
- 					inSmalltalk:
- 						[((primitiveFunctionPointer isInteger and: [primitiveFunctionPointer >= 1000])
- 							ifTrue: [#primitiveExternalCall]
- 							ifFalse: [primitiveFunctionPointer]) = (self functionPointerFor: primIndex inClass: objectMemory nilObject)]).
  	self assert: argumentCount = (self argumentCountOf: newMethod).
  	accessorDepth := (primIndex = 117 and: [primitiveFunctionPointer ~~ #primitiveExternalCall])
  							ifTrue: [self primitiveAccessorDepthForExternalPrimitiveMethod: newMethod]
  							ifFalse: [primitiveAccessorDepthTable at: primIndex].
  	accessorDepth < 0 ifTrue:
  		[^false].
  	0 to: argumentCount do:
  		[:index| | oop |
  		oop := self stackValue: index.
  		(objectMemory isNonImmediate: oop) ifTrue:
  			[(objectMemory isForwarded: oop) ifTrue:
  				[self assert: index < argumentCount. "receiver should have been caught at send time."
  				 found := true.
  				 oop := objectMemory followForwarded: oop.
  				 self stackValue: index put: oop].
  			((objectMemory hasPointerFields: oop)
  			 and: [objectMemory followForwardedObjectFields: oop toDepth: accessorDepth]) ifTrue:
  				[found := true]]].
  	^found!



More information about the Vm-dev mailing list