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

commits at source.squeak.org commits at source.squeak.org
Tue Apr 1 22:54:22 UTC 2014


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

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

Name: VMMaker.oscog-eem.661
Author: eem
Time: 1 April 2014, 3:51:53.558 pm
UUID: e09e68b7-6224-4c07-acd0-ea1f7cf57370
Ancestors: VMMaker.oscog-eem.660

Sista:
Reload TempReg from ReceiverResultReg on return from
counter trip, so that branch retry tests the right value.
Add a primitive to reset branch counters in a method.

Spur: abstract out the average object size calculation into its own
method (it'll be needed for pig compact).

Simulator:
Fix sqFile:Read:Into:At: for stdout when stdoiut is the Transcript
(Pharo startup indirectly tries to set line-end convention of stdout).

Implement remapping in remapOop:in: (simulating a Sista image
resulted in a GC in one of the LargeInteger routines).

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

Item was added:
+ ----- Method: CoInterpreterPrimitives>>primitiveResetCountersInMethod (in category 'method introspection primitives') -----
+ primitiveResetCountersInMethod
+ 	<export: true>
+ 	<option: #SistaStackToRegisterMappingCogit>
+ 	| methodReceiver |
+ 	argumentCount ~= 0 ifTrue:
+ 		[self primitiveFailFor: PrimErrBadNumArgs].
+ 	methodReceiver := self stackTop.
+ 	(self methodHasCogMethod: methodReceiver) ifTrue:
+ 		[cogit resetCountersIn: (self cogMethodOf: methodReceiver)]!

Item was added:
+ ----- Method: CogVMSimulator>>ceCounterTripped: (in category 'cog jit support') -----
+ ceCounterTripped: condition
+ 	self transcript cr; nextPutAll: 'counter trpped in '.
+ 	self shortPrintFrame: framePointer.
+ 	^super ceCounterTripped: condition!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFile:Read:Into:At: (in category 'simulation') -----
  sqFile: file Read: count Into: byteArrayIndex At: startIndex
  	| interpreter |
  	interpreter := interpreterProxy interpreter.
+ 	[[startIndex to: startIndex + count - 1 do:
- 	startIndex to: startIndex + count - 1 do:
  		[ :i |
  		file atEnd ifTrue: [^i - startIndex].
+ 		interpreter
+ 			byteAt: byteArrayIndex + i
+ 			put: file next asInteger]]
+ 			on: Error
+ 			do: [:ex|
+ 				(file isKindOf: TranscriptStream) ifFalse: [ex pass].
+ 				^0]]
+ 		ensure: [self recordStateOf: file].
- 		interpreter byteAt: byteArrayIndex + i put: file next asInteger].
- 	self recordStateOf: file.
  	^count!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generators') -----
  genJumpIf: boolean to: targetBytecodePC
  	"The heart of performance counting in Sista.  Conditional branches are 6 times less
  	 frequent than sends and can provide basic block frequencies (send counters can't).
  	 Each conditional has a 32-bit counter split into an upper 16 bits counting executions
  	 and a lower half counting untaken executions of the branch.  Executing the branch
  	 decrements the upper half, tripping if the count goes negative.  Not taking the branch
  	 decrements the lower half."
  	<inline: false>
  	| desc fixup ok counter countTripped retry |
  	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #counter type: #'AbstractInstruction *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 1.
  	desc := self ssTop.
  	self ssPop: 1.
  	(desc type == SSConstant
  	 and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:
  		["Must arrange there's a fixup at the target whether it is jumped to or
  		  not so that the simStackPtr can be kept correct."
  		 fixup := self ensureFixupAt: targetBytecodePC - initialPC.
  		 "Must enter any annotatedConstants into the map"
  		 self annotateBytecodeIfAnnotated: desc.
  		 "Must annotate the bytecode for correct pc mapping."
  		 self annotateBytecode: (desc constant = boolean
  									ifTrue: [self Jump: fixup]
  									ifFalse: [self prevInstIsPCAnnotated
  												ifTrue: [self Nop]
  												ifFalse: [self Label]]).
  		 ^0].
  	desc popToReg: TempReg.
  
  	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
  	counter := self addressOf: (counters at: counterIndex).
  	counterIndex := counterIndex + 1.
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: BytesPerWord = CounterBytes.
  	retry := counter addDependent: (self annotateAbsolutePCRef:
  				(self MoveAw: counter asUnsignedInteger R: SendNumArgsReg)).
  	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"Don't write back if we trip; avoids wrapping count back to initial value, and if we trip we don't execute."
  	countTripped := self JumpCarry: 0.
  	counter addDependent: (self annotateAbsolutePCRef:
  		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  
  	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
  	counter addDependent: (self annotateAbsolutePCRef:
  		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
  	self MoveCq: 0 R: SendNumArgsReg. "if SendNumArgsReg is 0 this is a mustBeBoolean, not a counter trip."
  	countTripped jmpTarget:
  		(self CallRT: (boolean == objectMemory falseObject
  						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])).
+ 	"Return to machine code (e.g. via ceEnterCogCodePopReceiverReg in returnToMachineCodeFrame
+ 	 loads return value into ReceiverResultReg but branch code tests TempReg.  So reload Tempreg."
+ 	self MoveR: ReceiverResultReg R: TempReg.
+ 	self CmpCq: 0 R: ReceiverResultReg.
- 	self CmpCq: 0 R: TempReg.
  	self JumpNonZero: retry.
  	ok jmpTarget: (self annotateBytecode: self Label).
  	^0!

Item was changed:
  ----- Method: SmartSyntaxInterpreterPlugin>>remapOop:in: (in category 'simulation') -----
  remapOop: oopOrList in: aBlock
  	<doNotGenerate>
+ 	| ctxt tempNames tempIndices |
+ 	ctxt := thisContext sender.
+ 	tempNames := ctxt tempNames.
+ 	oopOrList isArray
+ 		ifTrue:
+ 			[tempIndices := oopOrList collect: [:tempName| tempNames indexOf: tempName].
+ 			 tempIndices do:
+ 				[:index| interpreterProxy pushRemappableOop: (ctxt namedTempAt: index)]]
+ 		ifFalse: [interpreterProxy pushRemappableOop: oopOrList].
+ 	^aBlock ensure:
+ 		[oopOrList isArray
+ 			ifTrue:
+ 				[tempIndices reverseDo:
+ 					[:index| ctxt namedTempAt: index put: interpreterProxy popRemappableOop]]
+ 			ifFalse:
+ 				[1 to: ctxt numTemps do:
+ 					[:index|
+ 					(ctxt tempAt: index) = oopOrList ifTrue:
+ 						[ctxt tempAt: index put: interpreterProxy topRemappableOop]].
+ 				 interpreterProxy popRemappableOop]]!
- 	| numGCs result |
- 	numGCs := interpreterProxy statNumGCs.
- 	result := aBlock value.
- 	"If you really did want to implement remapping you would try and locate the
- 	 arguments in the caller context and update them via tempAt:put:.  But beware
- 	 ambiguities.  You'd have to parse the bytecode to be sure to get the right temps."
- 	numGCs ~= interpreterProxy statNumGCs ifTrue:
- 		[self error: 'GC occurred in middle of remapOop:in: and remapping in this context is not implemented'].
- 	^result!

Item was added:
+ ----- Method: SpurMemoryManager>>averageObjectSize (in category 'accessing') -----
+ averageObjectSize
+ 	"Answer an approximation of the average object size.  This is a bit of an underestimate.
+ 	 In the 32-bit system average object size is about 11 words per object, including header."
+ 	^8 * self bytesPerSlot!

Item was changed:
  ----- 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."
+ 	^(scavenger scavengerTenuringThreshold * scavenger pastSpaceBytes // self averageObjectSize) asInteger!
- 	| averageObjectSize |
- 	averageObjectSize := 8 * self wordSize.
- 	^(scavenger scavengerTenuringThreshold * scavenger pastSpaceBytes // averageObjectSize) asInteger!

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



More information about the Vm-dev mailing list