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

commits at source.squeak.org commits at source.squeak.org
Wed Aug 14 23:32:38 UTC 2013


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

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

Name: VMMaker.oscog-eem.321
Author: eem
Time: 14 August 2013, 4:29:01.96 pm
UUID: 6134e40b-c38c-41ec-8f31-64a7f1c002b3
Ancestors: VMMaker.oscog-eem.320

Add Cogit support for clean blocks by scanning literals looking for
BlockClosures on the current method.

Refacor Cogit>>compileCogMethod: so that
SistaStackToRegisterMappingCogit's version is no longer needed.

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

Item was added:
+ ----- Method: CoInterpreter>>startPCOrNilOfLiteral:in: (in category 'cog jit support') -----
+ startPCOrNilOfLiteral: lit in: aMethodObj
+ 	"Answer the startPC of lit if it is a (clean) block in aMethodObj, oitherwise answer nil."
+ 	<api>
+ 	| outerContext |
+ 	(objectMemory isIntegerObject: lit) ifTrue:
+ 		[^nil].
+ 	(objectMemory lastPointerOf: lit) <= ClosureCopiedValuesIndex ifTrue:
+ 		[^nil].
+ 	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: lit.
+ 	(objectMemory isContext: outerContext) ifFalse:
+ 		[^nil].
+ 	aMethodObj ~~ (objectMemory fetchPointer: MethodIndex ofObject: outerContext) ifTrue:
+ 		[^nil].
+ 	^self quickFetchInteger: ClosureStartPCIndex ofObject: lit!

Item was added:
+ ----- Method: Cogit>>addCleanBlockStarts (in category 'compile abstract instructions') -----
+ addCleanBlockStarts
+ 	1 to: (coInterpreter literalCountOf: methodObj) do:
+ 		[:i| | lit |
+ 		lit := coInterpreter fetchPointer: i ofObject: methodObj.
+ 		(coInterpreter startPCOrNilOfLiteral: lit in: methodObj) ifNotNil:
+ 			[:startPCOrNil|
+ 			 maxLitIndex := maxLitIndex max: i.
+ 			 self addBlockStartAt: startPCOrNil - 1 "1-rel => 0-rel"
+ 				numArgs: (coInterpreter argumentCountOfClosure: lit)
+ 				numCopied: (coInterpreter copiedValueCountOfClosure: lit)
+ 				span: (self spanForCleanBlockStartingAt: startPCOrNil - 1)]]!

Item was changed:
  ----- Method: Cogit>>allocateBlockStarts: (in category 'initialization') -----
  allocateBlockStarts: numBlocks
  	"Allocate the structures used to manage block compilation.  This
  	 needs to be a macro since the structures are alloca'ed (stack
  	 allocated) to ensure their being freed when compilation is done."
  	<cmacro: '(numBlocks) do { \
+ 		blockStarts = (numBlocks) ? alloca(sizeof(BlockStart) * (numBlocks)) : 0; \
- 		blockStarts = numBlocks ? alloca(sizeof(BlockStart) * numBlocks) : 0; \
  } while (0)'>
  	blockStarts := numBlocks > 0 ifTrue:
  					[CArrayAccessor on:
  						((1 to: numBlocks) collect:
  							[:ign| CogBlockStart new])]!

Item was changed:
  ----- Method: Cogit>>compileCogMethod: (in category 'compile abstract instructions') -----
  compileCogMethod: selector
  	<returnTypeC: #'CogMethod *'>
+ 	| numBytecodes numBlocks numCleanBlocks result extra |
- 	| numBytecodes numBlocks result extra |
  	hasYoungReferent := (objectMemory isYoung: methodObj)
  						  or: [objectMemory isYoung: selector].
  	methodOrBlockNumArgs := coInterpreter argumentCountOf: methodObj.
  	inBlock := false.
  	primInvokeLabel := nil.
  	postCompileHook := nil.
  	maxLitIndex := -1.
  	extra := ((primitiveIndex := coInterpreter primitiveIndexOf: methodObj) > 0
  			and: [(coInterpreter isQuickPrimitiveIndex: primitiveIndex) not])
  				ifTrue: [30]
  				ifFalse: [10].
  	initialPC := coInterpreter startPCOfMethod: methodObj.
  	"initial estimate.  Actual endPC is determined in scanMethod."
  	endPC := (coInterpreter isQuickPrimitiveIndex: primitiveIndex)
  					ifTrue: [initialPC - 1]
  					ifFalse: [objectMemory byteLengthOf: methodObj].
  	numBytecodes := endPC - initialPC + 1.
  	self allocateOpcodes: (numBytecodes + extra) * 10
  		bytecodes: numBytecodes
  		ifFail: [^coInterpreter cCoerceSimple: MethodTooBig to: #'CogMethod *'].
  	(numBlocks := self scanMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: numBlocks to: #'CogMethod *'].
+ 	numCleanBlocks := self scanForCleanBlocks.
+ 	self allocateBlockStarts: numBlocks + numCleanBlocks.
+ 	blockCount := 0.
+ 	numCleanBlocks > 0 ifTrue:
+ 		[self addCleanBlockStarts].
+ 	self maybeAllocAndInitCounters.
- 	self allocateBlockStarts: numBlocks.
  	blockEntryLabel := nil.
  	methodLabel dependent: nil.
  	(result := self compileEntireMethod) < 0 ifTrue:
  		[^coInterpreter cCoerceSimple: result to: #'CogMethod *'].
  	^self generateCogMethod: selector!

Item was changed:
  ----- Method: Cogit>>compileEntireMethod (in category 'compile abstract instructions') -----
  compileEntireMethod
  	"Compile the abstract instructions for the entire method, including blocks."
  	| result |
  	self compileAbort.
  	self compileEntry.
  	(result := self compilePrimitive) < 0 ifTrue:
  		[^result].
  	self compileFrameBuild.
- 	blockCount := 0.
  	(result := self compileMethodBody) < 0 ifTrue:
  		[^result].
  	blockCount = 0 ifTrue:
  		[^0].
  	(result := self compileBlockBodies) < 0 ifTrue:
  		[^result].
  	^self compileBlockDispatch!

Item was added:
+ ----- Method: Cogit>>maybeAllocAndInitCounters (in category 'compile abstract instructions') -----
+ maybeAllocAndInitCounters
+ 	"No-op in the non-Sista Cogits..."
+ 	<inline: true>!

Item was added:
+ ----- Method: Cogit>>scanForCleanBlocks (in category 'compile abstract instructions') -----
+ scanForCleanBlocks
+ 	"Answer the number of clean blocks found in the literal frame"
+ 	| numCleanBlocks |
+ 	numCleanBlocks := 0.
+ 	1 to: (coInterpreter literalCountOf: methodObj) do:
+ 		[:i| | lit |
+ 		lit := coInterpreter fetchPointer: i ofObject: methodObj.
+ 		(coInterpreter startPCOrNilOfLiteral: lit in: methodObj) ifNotNil:
+ 			[:startPCOrNil| numCleanBlocks := numCleanBlocks + 1]].
+ 	^numCleanBlocks!

Item was added:
+ ----- Method: Cogit>>spanForCleanBlockStartingAt: (in category 'compile abstract instructions') -----
+ spanForCleanBlockStartingAt: startPC
+ 	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	| pc end descriptor |
+ 	pc := startPC.
+ 	end := objectMemory byteLengthOf: methodObj.
+ 	[pc <= end] whileTrue:
+ 		[descriptor := self generatorAt: (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
+ 		 pc := pc + descriptor numBytes.
+ 		 descriptor isReturn ifTrue:
+ 			[^pc - startPC]].
+ 	self error: 'couldn''t locate end of clean block'.
+ 	^0!

Item was removed:
- ----- Method: SistaStackToRegisterMappingCogit>>compileCogMethod: (in category 'compile abstract instructions') -----
- compileCogMethod: selector
- 	<returnTypeC: #'CogMethod *'>
- 	| numBytecodes numBlocks result extra |
- 	self cCode: '' inSmalltalk:
- 		[debugStackPointers := coInterpreter debugStackPointersFor: methodObj].
- 	hasYoungReferent := (objectMemory isYoung: methodObj)
- 						  or: [objectMemory isYoung: selector].
- 	methodOrBlockNumArgs := coInterpreter argumentCountOf: methodObj.
- 	methodOrBlockNumTemps := coInterpreter tempCountOf: methodObj.
- 	inBlock := false.
- 	primInvokeLabel := nil.
- 	postCompileHook := nil.
- 	extra := ((primitiveIndex := coInterpreter primitiveIndexOf: methodObj) > 0
- 			and: [(coInterpreter isQuickPrimitiveIndex: primitiveIndex) not])
- 				ifTrue: [30]
- 				ifFalse: [10].
- 	initialPC := coInterpreter startPCOfMethod: methodObj.
- 	"initial estimate.  Actual endPC is determined in scanMethod."
- 	endPC := (coInterpreter isQuickPrimitiveIndex: primitiveIndex)
- 					ifTrue: [initialPC - 1]
- 					ifFalse: [objectMemory byteLengthOf: methodObj].
- 	numBytecodes := endPC - initialPC + 1.
- 	self allocateOpcodes: (numBytecodes + extra) * 10 bytecodes: numBytecodes.
- 	(numBlocks := self scanMethod) < 0 ifTrue:
- 		[^coInterpreter cCoerceSimple: numBlocks to: #'CogMethod *'].
- 	self allocateBlockStarts: numBlocks.
- 	self allocateCounters; initializeCounters.
- 	blockEntryLabel := nil.
- 	methodLabel dependent: nil.
- 	(result := self compileEntireMethod) < 0 ifTrue:
- 		[^coInterpreter cCoerceSimple: result to: #'CogMethod *'].
- 	^self generateCogMethod: selector!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>maybeAllocAndInitCounters (in category 'compile abstract instructions') -----
+ maybeAllocAndInitCounters
+ 	<inline: true>
+ 	self allocateCounters; initializeCounters!

Item was changed:
  ----- Method: StackInterpreter>>argumentCountOfClosure: (in category 'internal interpreter access') -----
  argumentCountOfClosure: closurePointer
+ 	<api> "for Cogit"
- 
  	^self quickFetchInteger: ClosureNumArgsIndex ofObject: closurePointer!

Item was changed:
  ----- Method: StackInterpreter>>copiedValueCountOfClosure: (in category 'internal interpreter access') -----
  copiedValueCountOfClosure: closurePointer
+ 	<api> "for Cogit"
- 
  	^(objectMemory fetchWordLengthOf: closurePointer) - ClosureFirstCopiedValueIndex!



More information about the Vm-dev mailing list