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

commits at source.squeak.org commits at source.squeak.org
Wed Sep 11 00:51:03 UTC 2013


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

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

Name: VMMaker.oscog-eem.366
Author: eem
Time: 10 September 2013, 5:48:20.561 pm
UUID: 5e95754d-997a-428e-a9e0-d294a7a7a21b
Ancestors: VMMaker.oscog-eem.365

Add a plausible, but probably not final, version of tenuring and the
tenuringThreshold to teh scavenger.

Add float support to Spur32BitMMLESimulator.

Implement eeInstantiateMethodContextSlots:.

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

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>fetchFloatAt:into: (in category 'as yet unclassified') -----
+ fetchFloatAt: floatBitsAddress into: aFloat
+ 	aFloat at: 2 put: (self long32At: floatBitsAddress).
+ 	aFloat at: 1 put: (self long32At: floatBitsAddress+4)!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>storeFloatAt:from: (in category 'as yet unclassified') -----
+ storeFloatAt: floatBitsAddress from: aFloat
+ 	self long32At: floatBitsAddress put: (aFloat at: 2).
+ 	self long32At: floatBitsAddress+4 put: (aFloat at: 1)!

Item was changed:
  VMClass subclass: #SpurGenerationScavenger
+ 	instanceVariableNames: 'coInterpreter manager memory eden futureSpace pastSpace rememberedSet rememberedSetSize tenuringThreshold tenuringProportion'
- 	instanceVariableNames: 'coInterpreter manager memory eden futureSpace pastSpace rememberedSet rememberedSetSize'
  	classVariableNames: 'RememberedSetLimit RememberedSetRedZone'
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManager'!

Item was changed:
  ----- Method: SpurGenerationScavenger>>copyAndForward: (in category 'scavenger') -----
  copyAndForward: survivor
  	"copyAndForward: survivor copies a survivor object either to
  	 futureSurvivorSpace or, if it is to be promoted, to oldSpace.
  	 It leaves a forwarding pointer behind."
  	| newLocation |
  	newLocation := (self shouldBeTenured: survivor)
  						ifTrue: [self copyToOldSpace: survivor]
  						ifFalse: [self copyToFutureSpace: survivor].
+ 	manager forward: survivor to: newLocation!
- 	manager forward: survivor to: newLocation
- 			!

Item was changed:
  ----- Method: SpurGenerationScavenger>>initialize (in category 'initialization') -----
  initialize
  	rememberedSet := CArrayAccessor on: (Array new: RememberedSetLimit).
+ 	rememberedSetSize := 0.
+ 	tenuringThreshold := 0!
- 	rememberedSetSize := 0!

Item was changed:
  ----- Method: SpurGenerationScavenger>>scavenge (in category 'scavenger') -----
  scavenge
  	"The main routine, scavenge, scavenges young objects reachable from the roots (the stack zone
  	 and the rememberedTable).  It first scavenges the new objects immediately reachable from the
  	 stack zone, then those directly from old ones (all in the remembered table).  Then it scavenges
  	 those that are transitively reachable.  If this results in a promotion, the promotee gets remembered,
  	 and it first scavenges objects adjacent to the promotee, then scavenges the ones reachable from
  	 the promoted.  This loop continues until no more reachable objects are left.  At that point,
  	 pastSurvivorSpace is exchanged with futureSurvivorSpace.
  
  	 Notice that each pointer in a live object is inspected once and only once.  The previousRememberedSetSize
  	 and previousFutureSurvivorSpaceSize variables ensure that no object is scanned twice, as well as
  	 detecting closure.  If this were not true, some pointers might get forwarded twice."
  
  	coInterpreter scavengeStacks.
  	self scavengeLoop.
+ 	self exchange: pastSpace with: futureSpace.
+ 	self computeTenuringThreshold!
- 	self exchange: pastSpace with: futureSpace!

Item was added:
+ ----- Method: SpurGenerationScavenger>>scavengerTenuringThreshold (in category 'accessing') -----
+ scavengerTenuringThreshold "(Slang flattens so need unique selectors)"
+ 	<returnTypeC: #float>
+ 	^tenuringThreshold >= pastSpace start
+ 		ifTrue: [(tenuringThreshold - pastSpace start) asFloat / (pastSpace limit - pastSpace start)]
+ 		ifFalse: [0]!

Item was added:
+ ----- Method: SpurGenerationScavenger>>scavengerTenuringThreshold: (in category 'accessing') -----
+ scavengerTenuringThreshold: aProportion "(Slang flattens so need unique selectors)"
+ 	<var: 'aProportion' type: #float>
+ 	tenuringProportion := aProportion.
+ 	tenuringThreshold := aProportion = 0.0
+ 							ifTrue: [0]
+ 							ifFalse: [((pastSpace limit - pastSpace start) * aProportion) rounded + pastSpace start]!

Item was added:
+ ----- Method: SpurGenerationScavenger>>shouldBeTenured: (in category 'scavenger') -----
+ shouldBeTenured: survivor
+ 	"Answer if an object should be tenured.  Use the tenuringThreshold to decide.
+ 	 If the survivors (measured in bytes) are above some fraction of the survivor
+ 	 space then objects below the threshold (older objects, since allocation grows
+ 	 upwards and hence new objects are later than old) are scavenged.  Otherwise,
+ 	 the threshold is set to 0 and no objects are tenured.  See e.g.
+ 	 An adaptive tenuring policy for generation scavengers, David Ungar & Frank Jackson.
+ 	 ACM TOPLAS, Volume 14 Issue 1, Jan. 1992, pp 1 - 27."
+ 
+ 	^survivor < tenuringThreshold!

Item was added:
+ ----- Method: SpurMemoryManager>>edenBytes (in category 'accessing') -----
+ edenBytes
+ 	^scavenger eden limit - scavenger eden start!

Item was added:
+ ----- Method: SpurMemoryManager>>eeInstantiateMethodContextSlots: (in category 'allocation') -----
+ eeInstantiateMethodContextSlots: numSlots
+ 	<inline: true>
+ 	^self
+ 		allocateSlots: numSlots
+ 		format: self indexablePointersFormat
+ 		classIndex: ClassMethodContextCompactIndex!

Item was added:
+ ----- Method: SpurMemoryManager>>scavenger (in category 'debug support') -----
+ scavenger
+ 	<doNotGenerate>
+ 	^scavenger!

Item was added:
+ ----- Method: SpurMemoryManager>>tenuringThreshold (in category 'accessing') -----
+ tenuringThreshold
+ 	"In the scavenger the tenuring threshold is effectively a number of bytes of objects,
+ 	 accessed as a proportion of pastSpace from 0 to 1.   In the Squeak image the tenuring
+ 	 threshold is an object count. Marry the two notions  by multiplying the proportion by
+ 	 the size of pastSpace and dividing by the average object size, as derived from observation."
+ 	| averageObjectSize |
+ 	averageObjectSize := 8 * self wordSize.
+ 	^scavenger scavengerTenuringThreshold * (scavenger pastSpace limit - scavenger pastSpace start) // averageObjectSize!

Item was added:
+ ----- Method: SpurMemoryManager>>tenuringThreshold: (in category 'accessing') -----
+ tenuringThreshold: threshold
+ 	"c.f. tenuringThreshold"
+ 	scavenger scavengerTenuringThreshold:
+ 		(threshold * 8 * self wordSize) asFloat
+ 		/ (scavenger pastSpace limit - scavenger pastSpace start) asFloat!

Item was changed:
  ----- Method: StackInterpreter>>dbgFloatValueOf: (in category 'utilities') -----
  dbgFloatValueOf: oop
  	"This version answers the value of a float or nil if not a flat *WITHOUT* setting successFlag or any other such nonsense.  It is hence safe for use in debug printing.  Sheesh."
  
  	| result |
  	<returnTypeC: #double>
  	<var: #result type: #double>
  	self flag: #Dan.  "None of the float stuff has been converted for 64 bits"
+ 	((objectMemory isNonImmediate: oop)
- 	((objectMemory isNonIntegerObject: oop)
  	and: [(objectMemory fetchClassOfNonImm: oop) = (objectMemory splObj: ClassFloat)]) ifTrue:
  		[self cCode: '' inSmalltalk: [result := Float new: 2].
  		 objectMemory fetchFloatAt: oop + BaseHeaderSize into: result.
  		 ^result].
  	^nil!

Item was changed:
  ----- Method: StackInterpreter>>floatValueOf: (in category 'utilities') -----
  floatValueOf: oop
  	"Answer the C double precision floating point value of the argument,
  	 or fail if it is not a Float, and answer 0.
  	 Note: May be called by translated primitive code."
  
  	| isFloat result |
  	<asmLabel: false>
  	<returnTypeC: #double>
  	<var: #result type: #double>
  	isFloat := self isInstanceOfClassFloat: oop.
  	isFloat ifTrue:
  		[self cCode: '' inSmalltalk: [result := Float new: 2].
+ 		 objectMemory fetchFloatAt: oop + objectMemory baseHeaderSize into: result.
- 		 objectMemory fetchFloatAt: oop + BaseHeaderSize into: result.
  		 ^result].
  	self primitiveFail.
  	^0.0!

Item was removed:
- ----- Method: StackInterpreterSimulator>>primitiveBeCursor (in category 'debugging traps') -----
- primitiveBeCursor
- 	self halt.
- 	^super primitiveBeCursor!



More information about the Vm-dev mailing list