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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 12 22:02:46 UTC 2014


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

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

Name: VMMaker.oscog-eem.614
Author: eem
Time: 12 February 2014, 1:59:26.509 pm
UUID: fd533002-1a4b-4bbe-a8bc-d1d8c82080ae
Ancestors: VMMaker.oscog-eem.613

Improve Spur's identity hash LCG, eliminating the mod calc.

Comment out the format collection code in the stakc simulator's
primitiveNewWithArg.

Fix 32-bit Spur's genInnerPrimitiveIdentityHash:

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

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genInnerPrimitiveIdentityHash: (in category 'primitive generators') -----
+ genInnerPrimitiveIdentityHash: retNoffset
+ 	| jumpImm jumpSI jumpNotSet ret |
+ 	<var: #jumpSI type: #'AbstractInstruction *'>
+ 	<var: #jumpImm type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSet type: #'AbstractInstruction *'>
+ 	cogit MoveR: ReceiverResultReg R: ClassReg.
+ 	jumpImm := self genJumpImmediateInScratchReg: ClassReg.
+ 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
+ 	cogit CmpCq: ConstZero R: TempReg.
+ 	jumpNotSet := cogit JumpZero: 0.
+ 	cogit MoveR: TempReg R: ReceiverResultReg.
+ 	ret := cogit RetN: 0.
+ 	jumpImm jmpTarget: (cogit MoveR: ReceiverResultReg R: ClassReg).
+ 	jumpSI := self genJumpSmallIntegerInScratchReg: ClassReg.
+ 	jumpSI jmpTarget: ret.
+ 	self genConvertCharacterToSmallIntegerInReg: ReceiverResultReg.
+ 	cogit Jump: ret.
+ 	jumpNotSet jmpTarget: cogit Label.
+ 	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genInnerPrimitiveIdentityHash: (in category 'primitive generators') -----
  genInnerPrimitiveIdentityHash: retNoffset
+ 	self subclassResponsibility!
- 	| jumpImm jumpSI jumpNotSet ret |
- 	<var: #jumpSI type: #'AbstractInstruction *'>
- 	<var: #jumpImm type: #'AbstractInstruction *'>
- 	<var: #jumpNotSet type: #'AbstractInstruction *'>
- 	cogit MoveR: ReceiverResultReg R: ClassReg.
- 	jumpImm := self genJumpImmediateInScratchReg: ClassReg.
- 	self genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
- 	cogit CmpCq: ConstZero R: TempReg.
- 	jumpNotSet := cogit JumpZero: 0.
- 	cogit MoveR: TempReg R: ReceiverResultReg.
- 	ret := cogit RetN: 0.
- 	cogit MoveR: ReceiverResultReg R: ClassReg.
- 	jumpSI := self genJumpSmallIntegerInScratchReg: ClassReg.
- 	jumpSI jmpTarget: ret.
- 	jumpImm jmpTarget: cogit Label.
- 	self genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
- 	self genSetCharacterTagsIn: ReceiverResultReg.
- 	cogit Jump: ret.
- 	jumpNotSet jmpTarget: cogit Label.
- 	^0!

Item was changed:
  ----- Method: SpurMemoryManager>>newObjectHash (in category 'accessing') -----
  newObjectHash
+ 	"Use a slight variation on D.H. Lehmer's linear congruential generator from 1951.
+ 	 See e.g. http://en.wikipedia.org/wiki/Linear_congruential_generator."
+ 	lastHash := self cCode: [lastHash * 16807] "7 raisedTo: 5"
+ 					inSmalltalk: [lastHash := lastHash * 16807 bitAnd: 16rFFFFFFFF].
- 	"Use simple algorithm by D.H. Lehmer from 1951, for now."
- 	lastHash := lastHash * 16807 "7 raisedTo: 5" \\ 16r7ffffffd "(2 raisedTo: 31) - 1".
  	self assert: lastHash ~= 0.
+ 	^lastHash + (lastHash >> 8) "adding the top bits gives much better spread.  See below:"
+ 
+ 	"| r s n |
+ 	r := 1.
+ 	n := 256 * 256 * 256.
+ 	s := Set new: n * 2.
+ 	n timesRepeat:
+ 		[s add: (r + (r bitShift: -8) bitAnd: n - 1).
+ 		r := r * 16807 bitAnd: 16rFFFFFFFF].
+ 	{ s size. s size / n asFloat. s includes: 0. r hex }
+ =>	#(10702109 0.637895405292511 false '16r38000001')"
+ 
+ 	"| r s n |
+ 	r := 1.
+ 	n := 256 * 256 * 256.
+ 	s := Set new: n * 2.
+ 	n timesRepeat:
+ 		[s add: (r bitAnd: n - 1).
+ 		r := r * 16807 bitAnd: 16rFFFFFFFF].
+ 	{ s size. s size / n asFloat. s includes: 0. r hex }
+ =>	 #(2097152 0.125 false '16r38000001')"!
- 	^lastHash!

Item was changed:
  ----- Method: StackInterpreterSimulator>>primitiveNewWithArg (in category 'debugging traps') -----
  primitiveNewWithArg
  	"(objectMemory hasSpurMemoryManagerAPI
  	 and: [self classNameOf: (self stackValue: 1) Is: 'MethodDictionary']) ifTrue:
  		[self halt]."
  	"| hash |
  	hash := objectMemory rawHashBitsOf: (self stackValue: 1)."
+ 	"| format |
+ 	format := objectMemory instSpecOfClass: (self stackValue: 1)."
+ 	"(objectMemory numSlotsOf: (self stackValue: 1)) = 3 ifTrue:
+ 		[self halt]."
- 	| format |
- 	format := objectMemory instSpecOfClass: (self stackValue: 1).
  	super primitiveNewWithArg.
+ 	"self successful ifTrue:
+ 		[(Smalltalk at: #Counts ifAbsentPut: [Bag new]) add: format]."
- 	self successful ifTrue:
- 		[(Smalltalk at: #Counts ifAbsentPut: [Bag new]) add: format].
  	"(self successful and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
  		[(Smalltalk at: #Counts ifAbsentPut: [Bag new]) add: hash]"
  	"Smalltalk removeKey: #Counts"
  	"Counts sortedCounts collect: [:assoc|
  		assoc key -> ((SpurMemoryManager organization listAtCategoryNamed: #'header formats') detect:
  										[:f| (SpurMemoryManager basicNew perform: f) = assoc value])]
  		{3251->#arrayFormat.
  		 1685->#firstByteFormat.
  		 1533->#firstLongFormat.
  		 110->#weakArrayFormat.
  		 35->#indexablePointersFormat.
  		 5->#nonIndexablePointerFormat}"
  	"Counts sortedCounts collect: [:assoc|
  		assoc value = 0
  			ifTrue: [assoc]
  			ifFalse: [assoc key -> {(self nameOfClass: (objectMemory classAtIndex: assoc value)).
  									(SpurMemoryManager organization listAtCategoryNamed: #'header formats') detect:
  										[:f| (objectMemory perform: f)
  											= (objectMemory instSpecOfClass: (objectMemory classAtIndex: assoc value))]}]]
  	{1062->#('Array' #arrayFormat).
  	 777->#('Bitmap' #firstLongFormat).
  	 395->#('Float' #firstLongFormat).
  	 345->#('ByteString' #firstByteFormat).
  	 237->#('MatrixTransform2x3' #firstLongFormat).
  	 233->#('LargePositiveInteger' #firstByteFormat).
  	 103->#('WordArray' #firstLongFormat).
  	 58->#('WeakArray' #weakArrayFormat).
  	 52->#('WeakMessageSend' #weakArrayFormat).
  	 9->#('MethodContext' #indexablePointersFormat).
  	 4->#('DirectoryEntry' #nonIndexablePointerFormat).
  	 3->#('BalloonBuffer' #firstLongFormat).
  	 1->#('ByteArray' #firstByteFormat).
  	 1->0}"!



More information about the Vm-dev mailing list