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

commits at source.squeak.org commits at source.squeak.org
Mon Oct 13 20:35:15 UTC 2014


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

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

Name: VMMaker.oscog-eem.897
Author: eem
Time: 13 October 2014, 1:25:02.635 pm
UUID: fcc5e4e2-808e-4ab1-97ae-079cc4b9d7b8
Ancestors: VMMaker.oscog-eem.896

Fix old V3 NewObjectMemory bug in fullGC.
sweepPhaseForFullGC failed to update freeStart
at the end of its sweep which could leave a partial object between the last object and freeStart,
causing subsequent crashes in enumeration.
This fixes an occasional crash in muO's release
process: MuODeployer makeImageRelease

Always initialize the DisownVM constants in
CoInterpreterMT to ensure that the defines in
src.vm/interp.h are non-nil.

Smulator:
get validate and validate: right.

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

Item was changed:
  ----- Method: CoInterpreterMT class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  
+ 	"N.B. some of these DisownFlags are replicated in platforms/Cross/vm/sqVirtualMachine.h.
+ 	 Hence they should always be initialized."
+ 	DisownVMLockOutFullGC := 1.
+ 	DisownVMForProcessorRelinquish := 2.
+ 
  	(initializationOptions notNil
  	 and: [(initializationOptions at: #COGMTVM ifAbsent: [false]) == false]) ifTrue:
  		[^self].
  
  	COGMTVM := true.
  
+ 	ReturnToThreadSchedulingLoop := 2. "setjmp/longjmp code."!
- 	ReturnToThreadSchedulingLoop := 2. "setjmp/longjmp code."
- 
- 	"N.B. some of these DisownFlags are replicated in platforms/Cross/vm/sqVirtualMachine.h"
- 	DisownVMLockOutFullGC := 1.
- 	DisownVMForProcessorRelinquish := 2!

Item was changed:
  ----- Method: NewCoObjectMemory>>validate: (in category 'simulation') -----
  validate: oop
  	<doNotGenerate>
  	| header type cc sz fmt nextChunk | 
  	header := self longAt: oop.
  	type := header bitAnd: 3.
  	type = 2 ifFalse: [type = (self rightType: header) ifFalse: [self halt]].
  	sz := (header bitAnd: SizeMask) >> 2.
  	nextChunk := oop + ((self isFreeObject: oop)
  							ifTrue: [self sizeOfFree: oop]
  							ifFalse: [self sizeBitsOf: oop]).
  	nextChunk >= freeStart
  		ifTrue:
+ 			[nextChunk ~= freeStart ifTrue: [self halt]]
- 			[nextChunk = freeStart ifFalse: [self halt]]
  		ifFalse:
  			[(self headerType: nextChunk) = 0 ifTrue:
  				[(self headerType: (nextChunk + (BytesPerWord*2))) = 0 ifFalse: [self halt]].
  			(self headerType: nextChunk) = 1 ifTrue:
+ 				[(self headerType: (nextChunk + BytesPerWord)) = 1 ifFalse: [self halt]]].
+ 	type = 2 ifTrue: "free block"
+ 		[^self].
- 				[(self headerType: (nextChunk + BytesPerWord)) = 1 ifFalse: [self halt]].
- 			type = 2 ifTrue:
- 				["free block" ^ self]].
  	fmt := self formatOfHeader: header.
  	cc := self compactClassIndexOfHeader: header.
  	cc > 16 ifTrue: [self halt].	"up to 32 are legal, but not used"
  	type = 0 ifTrue:
  		["three-word header"
  		((self longAt: oop-BytesPerWord) bitAnd: 3) = type ifFalse: [self halt].
  		((self longAt: oop-(BytesPerWord*2)) bitAnd: 3) = type ifFalse: [self halt].
  		((self longAt: oop-BytesPerWord) = type) ifTrue: [self halt].	"Class word is 0"
  		sz = 0 ifFalse: [self halt]].
  	type = 1 ifTrue:
  		["two-word header"
  		((self longAt: oop-BytesPerWord) bitAnd: 3) = type ifFalse: [self halt].
  		cc > 0 ifTrue: [sz = 1 ifFalse: [self halt]].
  		sz = 0 ifTrue: [self halt]].
  	type = 3 ifTrue:
  		["one-word header"
  		cc = 0 ifTrue: [self halt]].
  	fmt = 5 ifTrue: [self halt].
  	fmt = 7 ifTrue: [self halt].
  	fmt >= self firstCompiledMethodFormat ifTrue: "must have integer header or be cog method"
  		[header := self longAt: oop + BytesPerWord.
  		 ((self isIntegerObject: header)
  		  or: [(header bitAnd: 7) = 0
  			and: [header asUnsignedInteger < self startOfMemory
  			and: [header asUnsignedInteger >= cogit minCogMethodAddress]]]) ifFalse: [self halt]].!

Item was changed:
  ----- Method: NewObjectMemory>>sweepPhaseForFullGC (in category 'garbage collection') -----
  sweepPhaseForFullGC
  	"Sweep memory from youngStart through the end of memory. Free all
  	 inaccessible objects and coalesce adjacent free chunks. Clear the mark
  	 bits of accessible objects. Compute the starting point for the first pass
  	 of incremental compaction (compStart). Return the number of surviving
  	 objects.  Unlike sweepPhase this always leaves compStart pointing at the
  	 first free chunk."
  	| survivors freeChunk firstFree oop oopHeader oopHeaderType hdrBytes oopSize freeChunkSize endOfMemoryLocal |
  	<inline: false>
  	<var: #oop type: #usqInt>
  	<var: #endOfMemoryLocal type: #usqInt>
  	self fwdTableInit: BytesPerWord*2.
  	survivors := 0.
  	freeChunk := nil.
  	firstFree := nil.
  	"will be updated later"
  	endOfMemoryLocal := endOfMemory.
  	oop := self oopFromChunk: youngStart.
  	[oop < endOfMemoryLocal]
  		whileTrue: ["get oop's header, header type, size, and header size"
  			statSweepCount := statSweepCount + 1.
  			oopHeader := self baseHeader: oop.
  			oopHeaderType := oopHeader bitAnd: TypeMask.
  			hdrBytes := headerTypeBytes at: oopHeaderType.
  			(oopHeaderType bitAnd: 1) = 1
  				ifTrue: [oopSize := oopHeader bitAnd: SizeMask]
  				ifFalse: [oopHeaderType = HeaderTypeSizeAndClass
  						ifTrue: [oopSize := (self sizeHeader: oop) bitAnd: LongSizeMask]
  						ifFalse: [self assert: (oopHeader bitAnd: MarkBit) = 0.
  								oopSize := oopHeader bitAnd: LongSizeMask]].
  			(oopHeader bitAnd: MarkBit) = 0
  				ifTrue: ["object is not marked; free it"
  					"<-- Finalization support: We need to mark each oop chunk as free -->"
  					self longAt: oop - hdrBytes put: HeaderTypeFree.
  					freeChunk ~= nil
  						ifTrue: ["enlarge current free chunk to include this oop"
  							freeChunkSize := freeChunkSize + oopSize + hdrBytes]
  						ifFalse: ["start a new free chunk"
  							freeChunk := oop - hdrBytes.
  							"chunk may start 4 or 8 bytes before oop"
  							freeChunkSize := oopSize + (oop - freeChunk).
  							"adjust size for possible extra header bytes"
  							firstFree = nil ifTrue: [firstFree := freeChunk]]]
  				ifFalse: ["object is marked; clear its mark bit and possibly adjust 
  					the compaction start"
  					self longAt: oop put: (oopHeader bitAnd: AllButMarkBit).
  					"<-- Finalization support: Check if we're running about a weak class -->"
  					(self isWeakNonImm: oop) ifTrue: [self finalizeReference: oop].
  					freeChunk ~= nil
  						ifTrue: ["record the size of the last free chunk"
  							self longAt: freeChunk put: ((freeChunkSize bitAnd: LongSizeMask) bitOr: HeaderTypeFree).
  							freeChunk := nil].
  					survivors := survivors + 1].
  			oop := self oopFromChunk: oop + oopSize].
  	freeChunk ~= nil
  		ifTrue: ["record size of final free chunk"
  			self longAt: freeChunk put: ((freeChunkSize bitAnd: LongSizeMask) bitOr: HeaderTypeFree)].
  	oop = endOfMemory
+ 		ifTrue: [freeStart := endOfMemory]
  		ifFalse: [self error: 'sweep failed to find exact end of memory'].
  	firstFree = nil
  		ifTrue: [self error: 'expected to find at least one free object']
  		ifFalse: [compStart := firstFree].
  
  	^ survivors!

Item was changed:
  ----- Method: NewObjectMemory>>validate (in category 'simulation') -----
  validate
  	"Validate all the objects in the heap."
  	self cCode: [] inSmalltalk: [
  	| oop prev |
  	self interpreter transcript show: 'Validating...'.
  	oop := self firstObject.
  	[oop < freeStart] whileTrue:
  		[self validate: oop.
  		prev := oop.  "look here if debugging prev obj overlapping this one"
+ 		oop := self safeObjectAfter: oop].
- 		oop := self objectAfter: oop].
  	self touch: prev.  "Don't offer to delete this please"
  	self interpreter transcript show: 'done.'; cr]!

Item was changed:
  ----- Method: NewObjectMemory>>validate: (in category 'simulation') -----
  validate: oop
  	<doNotGenerate>
  	| header type cc sz fmt nextChunk | 
  	header := self longAt: oop.
  	type := header bitAnd: 3.
  	type = 2 ifFalse: [type = (self rightType: header) ifFalse: [self halt]].
  	sz := (header bitAnd: SizeMask) >> 2.
  	nextChunk := oop + ((self isFreeObject: oop)
  							ifTrue: [self sizeOfFree: oop]
  							ifFalse: [self sizeBitsOf: oop]).
  	nextChunk >= freeStart
  		ifTrue:
+ 			[nextChunk ~= freeStart ifTrue: [self halt]]
- 			[nextChunk = freeStart ifFalse: [self halt]]
  		ifFalse:
  			[(self headerType: nextChunk) = 0 ifTrue:
  				[(self headerType: (nextChunk + (BytesPerWord*2))) = 0 ifFalse: [self halt]].
  			(self headerType: nextChunk) = 1 ifTrue:
+ 				[(self headerType: (nextChunk + BytesPerWord)) = 1 ifFalse: [self halt]]].
+ 	type = 2 ifTrue: "free block"
+ 		[^self].
- 				[(self headerType: (nextChunk + BytesPerWord)) = 1 ifFalse: [self halt]].
- 			type = 2 ifTrue:
- 				["free block" ^ self]].
  	fmt := self formatOfHeader: header.
  	cc := self compactClassIndexOfHeader: header.
  	cc > 16 ifTrue: [self halt].	"up to 32 are legal, but not used"
  	type = 0 ifTrue:
  		["three-word header"
  		((self longAt: oop-BytesPerWord) bitAnd: 3) = type ifFalse: [self halt].
  		((self longAt: oop-(BytesPerWord*2)) bitAnd: 3) = type ifFalse: [self halt].
  		((self longAt: oop-BytesPerWord) = type) ifTrue: [self halt].	"Class word is 0"
  		sz = 0 ifFalse: [self halt]].
  	type = 1 ifTrue:
  		["two-word header"
  		((self longAt: oop-BytesPerWord) bitAnd: 3) = type ifFalse: [self halt].
  		cc > 0 ifTrue: [sz = 1 ifFalse: [self halt]].
  		sz = 0 ifTrue: [self halt]].
  	type = 3 ifTrue:
  		["one-word header"
  		cc = 0 ifTrue: [self halt]].
  	fmt = 5 ifTrue: [self halt].
  	fmt = 7 ifTrue: [self halt].
  	fmt >= self firstCompiledMethodFormat ifTrue: "must have integer header"
  		[(self isIntegerObject: (self longAt: oop + BytesPerWord)) ifFalse: [self halt]].!

Item was changed:
+ ----- Method: StackInterpreter>>maybeFailForLastObjectOverwrite (in category 'primitive support') -----
- ----- Method: StackInterpreter>>maybeFailForLastObjectOverwrite (in category 'simulation') -----
  maybeFailForLastObjectOverwrite
  	<inline: true>
  	checkAllocFiller ifTrue: 
  		[(objectMemory freeStart < objectMemory scavengeThreshold
  		  and: [(objectMemory longAt: objectMemory freeStart) ~= objectMemory freeStart]) ifTrue:
  			[self primitiveFailFor: PrimErrWritePastObject]]!

Item was changed:
  ----- Method: StackInterpreter>>slowPrimitiveResponse (in category 'primitive support') -----
  slowPrimitiveResponse
  	"Invoke a normal (non-quick) primitive.
  	 Called under the assumption that primFunctionPointer has been preloaded."
  	| nArgs savedFramePointer savedStackPointer |
  	<inline: true>
  	<asmLabel: false>
  	<var: #savedFramePointer type: #'char *'>
  	<var: #savedStackPointer type: #'char *'>
  	self assert: (objectMemory isOopForwarded: (self stackValue: argumentCount)) not.
  	FailImbalancedPrimitives ifTrue:
  		[nArgs := argumentCount.
  		 savedStackPointer := stackPointer.
  		 savedFramePointer := framePointer].
  	self initPrimCall.
  	self dispatchFunctionPointer: primitiveFunctionPointer.
  	"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.  Retry the primitive if any are found."
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[(self successful not
+ 			  and: [(objectMemory isOopCompiledMethod: newMethod)
+ 			  and: [self checkForAndFollowForwardedPrimitiveState]]) ifTrue:
+ 				[self initPrimCall.
+ 				 self dispatchFunctionPointer: primitiveFunctionPointer]]
+ 		ifFalse:
+ 			[self assert: objectMemory remapBufferCount = 0].
- 	(objectMemory hasSpurMemoryManagerAPI
- 	 and: [self successful not
- 	 and: [(objectMemory isOopCompiledMethod: newMethod)
- 	 and: [self checkForAndFollowForwardedPrimitiveState]]]) ifTrue:
- 		[self initPrimCall.
- 		 self dispatchFunctionPointer: primitiveFunctionPointer].
  	self maybeFailForLastObjectOverwrite.
  	(FailImbalancedPrimitives
  	and: [self successful
  	and: [framePointer = savedFramePointer
  	and: [(self isMachineCodeFrame: framePointer) not]]]) ifTrue:"Don't fail if primitive has done something radical, e.g. perform:"
  		[stackPointer ~= (savedStackPointer + (nArgs * BytesPerWord)) ifTrue:
  			[self flag: 'Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context'.
  			 "This is necessary but insufficient; the result may still have been written to the stack.
  			   At least we'll know something is wrong."
  			 stackPointer := savedStackPointer.
  			 self failUnbalancedPrimitive]].
  	"If we are profiling, take accurate primitive measures"
  	nextProfileTick > 0 ifTrue:
  		[self checkProfileTick: newMethod].
  	^self successful!



More information about the Vm-dev mailing list