[Vm-dev] VM Maker: Cog-eem.114.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Oct 11 22:07:38 UTC 2013


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

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

Name: Cog-eem.114
Author: eem
Time: 11 October 2013, 3:07:14.576 pm
UUID: f73eade5-3f36-4cd6-af32-ce83511bde41
Ancestors: Cog-eem.113

Spur bootstrap:
Add an efficient Character>>= method (#=='s primitive).

Turn off leak checking of the scavenger in the bootstrap.

Use the newly-minted bereaveAndNormalizeContextsAndFlushExternalPrimitives
to make sure the snapshot of the transformed image has no invalid
external function indices.

=============== Diff against Cog-eem.113 ===============

Item was added:
+ ----- Method: SpurBootstrap class>>CharacterPROTOTYPEDollarEquals: (in category 'method prototypes') -----
+ CharacterPROTOTYPEDollarEquals: aCharacter 
+ 	"Primitive. Answer if the receiver and the argument are the
+ 	 same object (have the same object pointer). Optional. See
+ 	 Object documentation whatIsAPrimitive."
+ 	<primitive: 110>
+ 	^self == aCharacter!

Item was changed:
  ----- Method: SpurBootstrap>>launch:simulatorClass:headerFlags: (in category 'testing') -----
  launch: heap simulatorClass: simulatorClass headerFlags: headerFlags
  	| sim methodCacheSize |
  	sim := simulatorClass onObjectMemory: heap.
  	heap coInterpreter: sim.
  	(sim class allInstVarNames includes: 'cogCodeSize')
  		ifTrue:
  			[sim initializeInterpreter: 0.
  			 methodCacheSize := sim methodCache size * heap wordSize.
  			 sim instVarNamed: 'heapBase' put: heap startOfMemory;
  				instVarNamed: 'numStackPages' put: 8;
  				instVarNamed: 'cogCodeSize' put: 1024*1024;
  				moveMethodCacheToMemoryAt: sim cogCodeSize + sim computeStackZoneSize;
  				movePrimTraceLogToMemoryAt: sim cogCodeSize + sim computeStackZoneSize + methodCacheSize;
  				"sendTrace: 1+ 2 + 8 + 16;"
  			 	initializeCodeGenerator]
  		ifFalse:
  			[sim initializeInterpreter: 0].
  	sim
  		setImageHeaderFlagsFrom: headerFlags;
  		imageName: ImageName;
  		flushExternalPrimitives;
  		openAsMorph;
  		transcript: Transcript. "deep copy copies this"
  	"sim
  		instVarNamed: 'printSends' put: true;
  		instVarNamed: 'printReturns' put: true;
  		instVarNamed: 'methodDictLinearSearchLimit' put: SmallInteger maxVal." "for now"
  	heap
+ 		setCheckForLeaks: 0;
- 		setCheckForLeaks: 15;
  		runLeakCheckerForFullGC: true.
  
  	sim halt; run!

Item was changed:
  ----- Method: SpurBootstrap>>on: (in category 'initialize-release') -----
  on: imageName
  	StackInterpreter initializeWithOptions: Dictionary new.
  	oldInterpreter := StackInterpreterSimulator new.
  	oldInterpreter openOn: imageName extraMemory: 0.
  	oldHeap := oldInterpreter objectMemory.
  	newHeap := Spur32BitMMLESimulator new.
  	newHeap
  		allocateMemoryOfSize: (oldHeap youngStart * 3 / 2 roundUpTo: 1024 * 1024)
  		newSpaceSize: 1024 * 1024
  		stackSize: 1024 * 1024
  		codeSize: 1024 * 1024.
+ 	newHeap setCheckForLeaks: 15 - 6. "don't check become; or newSpace; soooo many rehashes in bootstrap"
- 	newHeap setCheckForLeaks: 15 - 4. "don't check become; soooo many rehashes in bootstrap"
  	map := Dictionary new: oldHeap memory size // 4.
  	reverseMap := Dictionary new: oldHeap memory size // 4.
  	classToIndex := Dictionary new: 1024.
  	literalMap := IdentityDictionary new.
  	methodClasses := Set new.
  	installedPrototypes := Set new!

Item was changed:
  ----- Method: SpurBootstrap>>selectorForPrototypeMethod: (in category 'method prototypes') -----
  selectorForPrototypeMethod: protoMethod
  	| protoSelector |
  	protoSelector := protoMethod selector.
+ 	protoSelector := protoSelector last: protoSelector size
- 	^(protoSelector last: protoSelector size
  						- (protoSelector indexOfSubCollection: 'PROTOTYPE')
  						- 'PROTOTYPE' size
+ 						+ 1.
+ 	(protoSelector beginsWith: 'Dollar') ifTrue:
+ 		[protoSelector := (Dictionary newFromPairs: #('DollarEquals:' #=))
+ 							at: protoSelector].
+ 	^protoSelector asSymbol!
- 						+ 1) asSymbol!

Item was changed:
  ----- Method: SpurBootstrap>>writeSnapshotOfTransformedImage (in category 'testing') -----
  writeSnapshotOfTransformedImage
  	"The bootstrapped image typically contains a few big free chunks and one huge free chunk.
  	 Test snapshot writing and loading by turning the largest non-huge chunks into segment bridges
  	 and saving."
  	| last heap sizes counts barriers sim |
  	heap := TransformedImage veryDeepCopy.
  	sim := StackInterpreterSimulator onObjectMemory: heap.
  	heap coInterpreter: sim.
  	sim initializeInterpreter: 0;
  		setImageHeaderFlagsFrom: ImageHeaderFlags;
  		setDisplayForm: (Form extent: ImageScreenSize >> 16 @ (ImageScreenSize bitAnd: 16rFFFF)).
  	heap allOldSpaceEntitiesDo: [:e| last := e].
  	self assert: (heap isFreeObject: last).
  	sizes := Bag new.
  	heap allObjectsInFreeTree: (heap freeLists at: 0) do:
  		[:f|
  		sizes add: (heap bytesInObject: f)].
  	counts := sizes sortedCounts.
  	self assert: counts last key = 1. "1 huge chunk"
  	self assert: ((counts at: counts size - 1) key > 2
  				and: [(counts at: counts size - 1) value > 1024]).
  	barriers := (1 to: (counts at: counts size - 1) key) collect:
  					[:ign| heap allocateOldSpaceChunkOfExactlyBytes: (counts at: counts size - 1) value].
  	barriers := barriers, {heap allocateOldSpaceChunkOfExactlyBytes: (heap bytesInObject: last)}.
  	heap setEndOfMemory: barriers last.
  	heap allOldSpaceEntitiesDo: [:e| last := e].
  	self assert: (heap addressAfter: last) = barriers last.
  	heap checkFreeSpace.
  	heap runLeakCheckerForFullGC: true.
  	heap segmentManager initializeFromFreeChunks: (barriers sort collect: [:b| heap objectStartingAt: b]).
  	heap checkFreeSpace.
  	heap runLeakCheckerForFullGC: true.
+ 	sim bereaveAndNormalizeContextsAndFlushExternalPrimitives.
  	sim imageName: 'spur.image'.
  	sim writeImageFileIO!



More information about the Vm-dev mailing list