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

commits at source.squeak.org commits at source.squeak.org
Tue Oct 15 03:26:01 UTC 2013


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

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

Name: VMMaker.oscog-eem.457
Author: eem
Time: 14 October 2013, 8:22:22.312 pm
UUID: c4aa88bc-7af4-4cfe-94e4-c79f485a488d
Ancestors: VMMaker.oscog-eem.456

More protocol added to SpurMemoryManager.

More primitives marked with <option: #SqueakV3ObjectMemory>.

Time to desist...

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

Item was added:
+ ----- Method: CCodeGenerator>>generateNoMask:on:indent: (in category 'C translation') -----
+ generateNoMask: msgNode on: aStream indent: level
+ 	"Generate the C code for this message onto the given stream."
+ 
+ 	aStream nextPut: $(.
+ 	self generateBitAnd: msgNode on: aStream indent: level.
+ 	aStream nextPutAll: ') == 0'!

Item was added:
+ ----- Method: CCodeGenerator>>generateRounded:on:indent: (in category 'C translation') -----
+ generateRounded: msgNode on: aStream indent: level
+ 	"Generate the C code for rounded onto the given stream."
+ 
+ 	aStream nextPutAll: 'round('.
+ 	self emitCExpression: msgNode receiver on: aStream.
+ 	aStream nextPut: $)!

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation') -----
  initializeCTranslationDictionary 
  	"Initialize the dictionary mapping message names to actions for C code generation."
  
  	| pairs |
  	
  	translationDict := Dictionary new: 200.
  	pairs := #(
  	#&				#generateAnd:on:indent:
  	#|				#generateOr:on:indent:
  	#and:			#generateSequentialAnd:on:indent:
  	#or:			#generateSequentialOr:on:indent:
  	#not			#generateNot:on:indent:
  
  	#+				#generatePlus:on:indent:
  	#-				#generateMinus:on:indent:
  	#negated		#generateNegated:on:indent:
  	#*				#generateTimes:on:indent:
  	#/				#generateDivide:on:indent:
  	#//				#generateDivide:on:indent:
  	#\\				#generateModulo:on:indent:
  	#<<			#generateShiftLeft:on:indent:
  	#>>			#generateShiftRight:on:indent:
  	#min:			#generateMin:on:indent:
  	#max:			#generateMax:on:indent:
  	#between:and:	#generateBetweenAnd:on:indent:
  
  	#bitAnd:			#generateBitAnd:on:indent:
  	#bitOr:				#generateBitOr:on:indent:
  	#bitXor:			#generateBitXor:on:indent:
  	#bitShift:			#generateBitShift:on:indent:
  	#signedBitShift:	#generateSignedBitShift:on:indent:
  	#bitInvert32		#generateBitInvert32:on:indent:
  	#bitClear:			#generateBitClear:on:indent:
  	#truncateTo:		#generateTruncateTo:on:indent:
+ 	#rounded			#generateRounded:on:indent:
  
  	#<				#generateLessThan:on:indent:
  	#<=			#generateLessThanOrEqual:on:indent:
  	#=				#generateEqual:on:indent:
  	#>				#generateGreaterThan:on:indent:
  	#>=			#generateGreaterThanOrEqual:on:indent:
  	#~=			#generateNotEqual:on:indent:
  	#==			#generateEqual:on:indent:
  	#~~			#generateNotEqual:on:indent:
  	#isNil			#generateIsNil:on:indent:
  	#notNil			#generateNotNil:on:indent:
  
  	#whileTrue: 	#generateWhileTrue:on:indent:
  	#whileFalse:	#generateWhileFalse:on:indent:
  	#whileTrue 	#generateDoWhileTrue:on:indent:
  	#whileFalse		#generateDoWhileFalse:on:indent:
  	#to:do:			#generateToDo:on:indent:
  	#to:by:do:		#generateToByDo:on:indent:
  	#repeat 		#generateRepeat:on:indent:
  
  	#ifTrue:			#generateIfTrue:on:indent:
  	#ifFalse:		#generateIfFalse:on:indent:
  	#ifTrue:ifFalse:	#generateIfTrueIfFalse:on:indent:
  	#ifFalse:ifTrue:	#generateIfFalseIfTrue:on:indent:
  
  	#ifNotNil:		#generateIfNotNil:on:indent:
  	#ifNil:			#generateIfNil:on:indent:
  	#ifNotNil:ifNil:	#generateIfNotNilIfNil:on:indent:
  	#ifNil:ifNotNil:	#generateIfNilIfNotNil:on:indent:
  
  	#at:				#generateAt:on:indent:
  	#at:put:			#generateAtPut:on:indent:
  	#basicAt:		#generateAt:on:indent:
  	#basicAt:put:	#generateAtPut:on:indent:
  
  	#integerValueOf:			#generateIntegerValueOf:on:indent:
  	#integerObjectOf:			#generateIntegerObjectOf:on:indent:
  	#isIntegerObject: 			#generateIsIntegerObject:on:indent:
  	#cCode:					#generateInlineCCode:on:indent:
  	#cCode:inSmalltalk:			#generateInlineCCode:on:indent:
  	#cPreprocessorDirective:	#generateInlineCPreprocessorDirective:on:indent:
  	#cppIf:ifTrue:ifFalse:		#generateInlineCppIfElse:on:indent:
  	#cppIf:ifTrue:				#generateInlineCppIfElse:on:indent:
  	#cCoerce:to:				#generateCCoercion:on:indent:
  	#cCoerceSimple:to:			#generateCCoercion:on:indent:
  	#addressOf:				#generateAddressOf:on:indent:
  	#signedIntFromLong		#generateSignedIntFromLong:on:indent:
  	#signedIntToLong			#generateSignedIntToLong:on:indent:
  	#signedIntFromShort		#generateSignedIntFromShort:on:indent:
  	#signedIntToShort			#generateSignedIntToShort:on:indent:
  	#preIncrement				#generatePreIncrement:on:indent:
  	#preDecrement			#generatePreDecrement:on:indent:
  	#inline:						#generateInlineDirective:on:indent:
  	#asFloat					#generateAsFloat:on:indent:
  	#asInteger					#generateAsInteger:on:indent:
  	#asUnsignedInteger		#generateAsUnsignedInteger:on:indent:
  	#asLong					#generateAsLong:on:indent:
  	#asUnsignedLong			#generateAsUnsignedLong:on:indent:
  	#asSymbol					#generateAsSymbol:on:indent:
  	#flag:						#generateFlag:on:indent:
  	#anyMask:					#generateBitAnd:on:indent:
+ 	#noMask:					#generateNoMask:on:indent:
  	#raisedTo:					#generateRaisedTo:on:indent:
  	#touch:						#generateTouch:on:indent:
  
  	#bytesPerWord 			#generateBytesPerWord:on:indent:
  	#wordSize		 			#generateBytesPerWord:on:indent:
  	#baseHeaderSize			#generateBaseHeaderSize:on:indent:
  	
  	#sharedCodeNamed:inCase:		#generateSharedCodeDirective:on:indent:
  
  	#perform:							#generatePerform:on:indent:
  	#perform:with:						#generatePerform:on:indent:
  	#perform:with:with:					#generatePerform:on:indent:
  	#perform:with:with:with:				#generatePerform:on:indent:
  	#perform:with:with:with:with:		#generatePerform:on:indent:
  	#perform:with:with:with:with:with:	#generatePerform:on:indent:
  
  	#value								#generateValue:on:indent:
  	#value:								#generateValue:on:indent:
  	#value:value:						#generateValue:on:indent:
  
  	#shouldNotImplement				#generateSmalltalkMetaError:on:indent:
  	#shouldBeImplemented			#generateSmalltalkMetaError:on:indent:
  	#subclassResponsibility			#generateSmalltalkMetaError:on:indent:
  	).
  
  	1 to: pairs size by: 2 do: [:i |
  		translationDict at: (pairs at: i) put: (pairs at: i + 1)].
  
  	pairs := #(
  	#ifTrue:					#generateIfTrueAsArgument:on:indent:	
  	#ifFalse:				#generateIfFalseAsArgument:on:indent:
  	#ifTrue:ifFalse:			#generateIfTrueIfFalseAsArgument:on:indent:
  	#ifFalse:ifTrue:			#generateIfFalseIfTrueAsArgument:on:indent:
  	#ifNotNil:				#generateIfNotNilAsArgument:on:indent:	
  	#ifNil:					#generateIfNilAsArgument:on:indent:
  	#ifNotNil:ifNil:			#generateIfNotNilIfNilAsArgument:on:indent:
  	#ifNil:ifNotNil:			#generateIfNilIfNotNilAsArgument:on:indent:
  	#cCode:				#generateInlineCCodeAsArgument:on:indent:
  	#cCode:inSmalltalk:		#generateInlineCCodeAsArgument:on:indent:
  	#cppIf:ifTrue:ifFalse:	#generateInlineCppIfElseAsArgument:on:indent:
  	#cppIf:ifTrue:			#generateInlineCppIfElseAsArgument:on:indent:
  	).
  
  	asArgumentTranslationDict := Dictionary new: 8.
  	1 to: pairs size by: 2 do: [:i |
  		asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveIsYoung (in category 'memory space primitives') -----
  primitiveIsYoung
  	"Primitive. Answer whether the argument to the primitive resides in young space."
  	| oop |
  	<export: true>
+ 	<option: #SqueakV3ObjectMemory> "for now..."
  	oop := self stackObjectValue: 0.
  	self successful ifTrue:
  		[self pop: argumentCount + 1 thenPushBool: (self oop: oop isGreaterThanOrEqualTo: objectMemory youngStart)]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitivePathToUsing (in category 'other primitives') -----
  primitivePathToUsing
  	"primitivePathTo: anObject using: stack <Array> followWeak: boolean
  	 Answer a path to anObject from the root that does not pass through
  	 the current context"
  	| err path |
  	<export: true>
+ 	<option: #SqueakV3ObjectMemory> "for now..."
  	self externalWriteBackHeadFramePointers.
  	err := self pathTo: (self stackValue: 2) using: (self stackValue: 1) followWeak: self stackTop = objectMemory trueObject.
  	err ~= 0 ifTrue:
  		[^self primitiveFailFor: err].
  	path := self self stackValue: 1.
  	self pop: argumentCount + 1 thenPush: path!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSetGCBiasToGrow (in category 'memory space primitives') -----
  primitiveSetGCBiasToGrow
  	"Primitive. Indicate if the GC logic should have bias to grow"
  	| flag |
  	<export: true>
+ 	<option: #SqueakV3ObjectMemory> "for now..."
  	flag := self stackIntegerValue: 0.
  	self successful ifTrue:[
  		objectMemory gcBiasToGrow: flag.
  		self pop: argumentCount.
  	]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSetGCBiasToGrowGCLimit (in category 'memory space primitives') -----
  primitiveSetGCBiasToGrowGCLimit
  	"Primitive. If the GC logic has  bias to grow, set growth limit"
  	| value |
  	<export: true>
+ 	<option: #SqueakV3ObjectMemory> "for now..."
  	value := self stackIntegerValue: 0.
  	self successful ifTrue:
  		[objectMemory gcBiasToGrowGCLimit: value.
  		 objectMemory gcBiasToGrowThreshold: objectMemory youngStart - objectMemory startOfMemory asInteger.
  		 self pop: argumentCount]!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>byteSwapped: (in category 'snapshot') -----
+ byteSwapped: w
+ 	"Answer the given integer with its bytes in the reverse order."
+ 	<api>
+ 	<returnTypeC: #sqInt>
+ 	^  ((w bitShift: Byte3ShiftNegated) bitAnd: Byte0Mask)
+ 	 + ((w bitShift: Byte1ShiftNegated) bitAnd: Byte1Mask)
+ 	 + ((w bitShift: Byte1Shift             ) bitAnd: Byte2Mask)
+ 	 + ((w bitShift: Byte3Shift             ) bitAnd: Byte3Mask)!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>byteSwapped: (in category 'snapshot') -----
+ byteSwapped: w
+ 	"Answer the given integer with its bytes in the reverse order."
+ 	<api>
+ 	<returnTypeC: #sqInt>
+ 	^  ((w bitShift: Byte7ShiftNegated) bitAnd: Byte0Mask)
+ 	 + ((w bitShift: Byte5ShiftNegated) bitAnd: Byte1Mask)
+ 	 + ((w bitShift: Byte3ShiftNegated) bitAnd: Byte2Mask)
+ 	 + ((w bitShift: Byte1ShiftNegated) bitAnd: Byte3Mask)
+ 	 + ((w bitShift: Byte1Shift             ) bitAnd: Byte4Mask)
+ 	 + ((w bitShift: Byte3Shift             ) bitAnd: Byte5Mask)
+ 	 + ((w bitShift: Byte5Shift             ) bitAnd: Byte6Mask)
+ 	 + ((w bitShift: Byte7Shift             ) bitAnd: Byte7Mask)!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was added:
+ ----- Method: SpurMemoryManager>>accessibleObjectAfter: (in category 'object enumeration') -----
+ accessibleObjectAfter: objOop
+ 	"Answer the accessible object following the given object or 
+ 	free chunk in the heap. Return nil when heap is exhausted.
+ 	 This is for primitiveNextObject subsequent to primtiiveSomeObject."
+ 	<inline: false>
+ 	| objAfter |
+ 	objAfter := objOop.
+ 	[objAfter := self objectAfter: objAfter limit: freeOldSpaceStart.
+ 	 objAfter = freeOldSpaceStart ifTrue:
+ 		[^nil].
+ 	 (self isNormalObject: objAfter) ifTrue:
+ 		[^objAfter]] repeat!

Item was added:
+ ----- Method: SpurMemoryManager>>byteSwapped: (in category 'snapshot') -----
+ byteSwapped: w
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>characterValueOf: (in category 'immediates') -----
  characterValueOf: oop
  	"Immediate characters are unsigned"
+ 	<api>
  	^oop asUnsignedInteger >> self numTagBits!

Item was added:
+ ----- Method: SpurMemoryManager>>classCharacter (in category 'plugin support') -----
+ classCharacter
+ 	^self splObj: ClassCharacter!

Item was added:
+ ----- Method: SpurMemoryManager>>classExternalStructure (in category 'accessing') -----
+ classExternalStructure
+ 	^self splObj: ClassExternalStructure!

Item was added:
+ ----- Method: SpurMemoryManager>>classFloat (in category 'plugin support') -----
+ classFloat
+ 	^self splObj: ClassFloat!

Item was added:
+ ----- Method: SpurMemoryManager>>classSmallInteger (in category 'accessing') -----
+ classSmallInteger
+ 	^self splObj: ClassInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>displayObject (in category 'accessing') -----
+ displayObject
+ 	^self splObj: TheDisplay!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
  	"We can put all initializations that set something to 0 or to false here.
  	 In C all global variables are initialized to 0, and 0 is false."
  	remapBuffer := Array new: RemapBufferSize.
  	remapBufferCount := 0.
  	freeListsMask := totalFreeOldSpace := lowSpaceThreshold := 0.
  	checkForLeaks := 0.
  	needGCFlag := signalLowSpace := scavengeInProgress := false.
  	becomeEffectsFlags := 0.
  	statScavenges := statIncrGCs := statFullGCs := 0.
+ 	statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := statGCEndUsecs := 0.
- 	statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := 0.
  	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
+ 	statGrowMemory := statShrinkMemory := statRootTableCount := statTenures := statSurvivorCount := 0.
+ 	statRootTableOverflows := statSweepCount := statMarkCount := statSpecialMarkCount := statMkFwdCount := 0.
  	self flag: #temporary.
  	shrinkThreshold := 16r10000000. "something huge for now"
  
  	"we can initialize things that are virtual in C."
  	scavenger := SpurGenerationScavengerSimulator new manager: self; yourself.
  	segmentManager := SpurSegmentManager new manager: self; yourself.
  
  	"We can also initialize here anything that is only for simulation."
  	heapMap := self wordSize = 4 ifTrue: [CogCheck32BitHeapMap new]!

Item was changed:
+ ----- Method: SpurMemoryManager>>isCharacterObject: (in category 'immediates') -----
- ----- Method: SpurMemoryManager>>isCharacterObject: (in category 'object testing') -----
  isCharacterObject: oop
+ 	<api>
+ 	^self isImmediateCharacter: oop!
- 	^(oop bitAnd: self tagMask) = self characterTag!

Item was added:
+ ----- Method: SpurMemoryManager>>isCharacterValue: (in category 'immediates') -----
+ isCharacterValue: anInteger
+ 	<api>
+ 	^self isInRangeCharacterCode: anInteger!

Item was changed:
+ ----- Method: SpurMemoryManager>>isForwardedObjectClassIndexPun (in category 'class table puns') -----
- ----- Method: SpurMemoryManager>>isForwardedObjectClassIndexPun (in category 'class table') -----
  isForwardedObjectClassIndexPun
  	^8 "Not to be confused with that of any immediate class"!

Item was added:
+ ----- Method: SpurMemoryManager>>isNormalObject: (in category 'object enumeration') -----
+ isNormalObject: objOop
+ 	^(self classIndexOf: objOop) > self lastClassIndexPun!

Item was added:
+ ----- Method: SpurMemoryManager>>isWeak: (in category 'object testing') -----
+ isWeak: oop
+ 	"Answer if the argument has only weak fields that can hold oops. See comment in formatOf:"
+ 	^(self isNonImmediate: oop) and: [self isWeakNonImm: oop]!

Item was added:
+ ----- Method: SpurMemoryManager>>lastClassIndexPun (in category 'class table puns') -----
+ lastClassIndexPun
+ 	"Class puns are class indices not used by any class.  There is an entry
+ 	 for the pun that refers to the notional class of objects with this class
+ 	 index.  But because the index doesn't match the class it won't show up
+ 	 in allInstances, hence hiding the object with a pun as its class index.
+ 	 The puns occupy indices 16 through 31."
+ 	^31!

Item was added:
+ ----- Method: SpurMemoryManager>>obsoleteDontUseThisFetchWord:ofObject: (in category 'plugin support') -----
+ obsoleteDontUseThisFetchWord: fieldIndex ofObject: oop
+ 	"This message is deprecated but supported for a while via a tweak to sqVirtualMachine.[ch] Use fetchLong32, fetchLong64 or fetchPointer instead for new code"
+ 	<api>
+ 	^self fetchLong32: fieldIndex ofObject: oop!

Item was added:
+ ----- Method: SpurMemoryManager>>reverseBytesFrom:to: (in category 'snapshot') -----
+ reverseBytesFrom: startAddr to: stopAddr
+ 	"Byte-swap the given range of memory (not inclusive of stopAddr!!)."
+ 	| addr |
+ 	addr := startAddr.
+ 	[self oop: addr isLessThan: stopAddr] whileTrue:
+ 		[self longAt: addr put: (self byteSwapped: (self longAt: addr)).
+ 		addr := addr + BytesPerWord]!

Item was added:
+ ----- Method: SpurMemoryManager>>reverseBytesInMemory (in category 'snapshot') -----
+ reverseBytesInMemory
+ 	self reverseBytesFrom: newSpaceLimit to: freeOldSpaceStart!

Item was added:
+ ----- Method: SpurMemoryManager>>rootTableCount (in category 'accessing') -----
+ rootTableCount
+ 	^scavenger rememberedSetSize!

Item was changed:
  ----- Method: SpurMemoryManager>>scavengingGCTenuringIf: (in category 'generation scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
  	"Run the scavenger."
  
  	self assert: remapBufferCount = 0.
  	self assert: (segmentManager numSegments = 0 "true in the spur image bootstrap"
  				or: [scavenger eden limit - freeStart > coInterpreter interpreterAllocationReserveBytes]).
  	self checkFreeSpace.
  	"coInterpreter printCallStackFP: coInterpreter framePointer"
  
  	self runLeakCheckerForFullGC: false.
  	coInterpreter
  		preGCAction: GCModeIncr;
  		"would prefer this to be in mapInterpreterOops, but
  		 compatibility with ObjectMemory dictates it goes here."
  		flushMethodCacheFrom: startOfMemory to: newSpaceLimit.
  	needGCFlag := false.
  
  	gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
  
  	scavengeInProgress := true.
  	pastSpaceStart := scavenger scavenge: tenuringCriterion.
  	self assert: (self
  					oop: pastSpaceStart
  					isGreaterThanOrEqualTo: scavenger pastSpace start
  					andLessThanOrEqualTo: scavenger pastSpace limit).
  	freeStart := scavenger eden start.
  	self initSpaceForAllocationCheck: (self addressOf: scavenger eden).
  	scavengeInProgress := false.
  
  	statScavenges := statScavenges + 1.
  	statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
  	statSGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
  	statScavengeGCUsecs := statScavengeGCUsecs + statSGCDeltaUsecs.
+ 	statRootTableCount := scavenger rememberedSetSize.
  
  	coInterpreter postGCAction.
  	self runLeakCheckerForFullGC: false.
  
  	self checkFreeSpace!

Item was added:
+ ----- Method: SpurMemoryManager>>statFGCDeltaUsecs (in category 'accessing') -----
+ statFGCDeltaUsecs
+ 	^statFGCDeltaUsecs!

Item was added:
+ ----- Method: SpurMemoryManager>>statGCEndUsecs (in category 'accessing') -----
+ statGCEndUsecs
+ 	^statGCEndUsecs!

Item was added:
+ ----- Method: SpurMemoryManager>>statGrowMemory (in category 'accessing') -----
+ statGrowMemory
+ 	^statGrowMemory!

Item was added:
+ ----- Method: SpurMemoryManager>>statMarkCount (in category 'accessing') -----
+ statMarkCount
+ 	^statMarkCount!

Item was added:
+ ----- Method: SpurMemoryManager>>statMkFwdCount (in category 'accessing') -----
+ statMkFwdCount
+ 	^statMkFwdCount!

Item was changed:
  ----- Method: SpurMemoryManager>>statRootTableCount (in category 'accessing') -----
  statRootTableCount
+ 	^statRootTableCount!
- 	^scavenger rememberedSetSize!

Item was added:
+ ----- Method: SpurMemoryManager>>statRootTableOverflows (in category 'accessing') -----
+ statRootTableOverflows
+ 	^statRootTableOverflows!

Item was added:
+ ----- Method: SpurMemoryManager>>statSGCDeltaUsecs (in category 'accessing') -----
+ statSGCDeltaUsecs
+ 	^statSGCDeltaUsecs!

Item was added:
+ ----- Method: SpurMemoryManager>>statScavengeGCUsecs (in category 'accessing') -----
+ statScavengeGCUsecs
+ 	^statScavengeGCUsecs!

Item was added:
+ ----- Method: SpurMemoryManager>>statShrinkMemory (in category 'accessing') -----
+ statShrinkMemory
+ 	^statShrinkMemory!

Item was added:
+ ----- Method: SpurMemoryManager>>statSpecialMarkCount (in category 'accessing') -----
+ statSpecialMarkCount
+ 	^statSpecialMarkCount!

Item was added:
+ ----- Method: SpurMemoryManager>>statSurvivorCount (in category 'accessing') -----
+ statSurvivorCount
+ 	^statSurvivorCount!

Item was added:
+ ----- Method: SpurMemoryManager>>statSweepCount (in category 'accessing') -----
+ statSweepCount
+ 	^statSweepCount!

Item was added:
+ ----- Method: SpurMemoryManager>>statTenures (in category 'accessing') -----
+ statTenures
+ 	^statTenures!

Item was changed:
  ----- Method: SpurMemoryManager>>totalMemorySize (in category 'accessing') -----
  totalMemorySize
+ 	^scavenger newSpaceCapacity + segmentManager totalBytesInSegments!
- 	^scavenger newSpaceCapacity + segmentManager totalSegmentSize!

Item was changed:
  ----- Method: SpurSegmentManager>>totalBytesInSegments (in category 'snapshot') -----
  totalBytesInSegments
  	| total |
  	total := 0.
  	0 to: numSegments - 1 do:
  		[:i|
+ 		total := total + (segments at: i) segSize - manager bridgeSize].
- 		total := total + (segments at: i) segSize].
  	^total!

Item was changed:
  ----- Method: TMethod>>newCascadeTempFor: (in category 'initialization') -----
  newCascadeTempFor: aTParseNode
  	| varNode |
  	varNode := TVariableNode new setName: (self extraVariableName: 'cascade').
  	aTParseNode isLeaf ifFalse:
  		[declarations
  			at: varNode name
+ 			put: [:tm :cg| tm determineTypeFor: aTParseNode in: cg]].
- 			put: [:tm :cg| tm halt; determineTypeFor: aTParseNode in: cg]].
  	^varNode!



More information about the Vm-dev mailing list