[Vm-dev] VM Maker: VMMaker.oscog-cb.1782.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Apr 8 02:43:17 UTC 2016


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.1782.mcz

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

Name: VMMaker.oscog-cb.1782
Author: cb
Time: 7 April 2016, 7:40:42.399 pm
UUID: 71fce71a-5a23-4640-9d08-212b83d860e4
Ancestors: VMMaker.oscog-eem.1781

Next iteration on full block closure in the JIT.

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

Item was changed:
  ----- Method: Cogit>>cogFullBlockMethod:numCopied: (in category 'jit - api') -----
  cogFullBlockMethod: aMethodObj numCopied: numCopied
  	"Attempt to produce a machine code method for the bytecode method
  	 object aMethodObj.  N.B. If there is no code memory available do *NOT*
  	 attempt to reclaim the method zone.  Certain clients (e.g. ceSICMiss:)
  	 depend on the zone remaining constant across method generation."
  	<api>
  	<returnTypeC: #'CogMethod *'>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	self cCode: [] inSmalltalk: "for debugging, allow excluding methods based on selector or methodClass"
  		[self halt class initializationOptions
  			at: #DoNotJIT
  			ifPresent:
  				[:excluded| 
  				(excluded anySatisfy: [:exclude| aMethodObj = exclude]) ifTrue:
  					[coInterpreter transcript nextPutAll: 'EXCLUDING '; nextPutAll: aMethodObj; nextPutAll: ' (compiled block)'; cr; flush.
  					 ^nil]]].
  	self deny: (coInterpreter methodHasCogMethod: aMethodObj).
  	aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of breakMethod'].
  	"If the generators for the alternate bytecode set are missing then interpret."
  	(coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
  		ifTrue:
  			[(self numElementsIn: generatorTable) <= 256 ifTrue:
  				[^nil].
  			 bytecodeSetOffset := 256]
  		ifFalse:
  			[bytecodeSetOffset := 0].
  	objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
  	methodObj := aMethodObj.
  	methodHeader := objectMemory methodHeaderOf: aMethodObj.
+ 	cogMethod := self compileCogFullBlockMethod: numCopied.
- 	cogMethod := self compileCogFullBlockMethod.
  	(cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  		[cogMethod asInteger = InsufficientCodeSpace ifTrue:
  			[coInterpreter callForCogCompiledCodeCompaction].
  		 self maybeFreeCounters.
  		 "Right now no errors should be reported, so nothing more to do."
  		 "self reportError: (self cCoerceSimple: cogMethod to: #sqInt)."
  		 ^nil].
  	"self cCode: ''
  		inSmalltalk:
  			[coInterpreter printCogMethod: cogMethod.
  			 ""coInterpreter symbolicMethod: aMethodObj.""
  			 self assertValidMethodMap: cogMethod."
  			 "self disassembleMethod: cogMethod."
  			 "printInstructions := clickConfirm := true""]."
  	^cogMethod!

Item was removed:
- ----- Method: Cogit>>compileCogFullBlockMethod (in category 'compile abstract instructions') -----
- compileCogFullBlockMethod
- 	<returnTypeC: #'CogMethod *'>
- 	| numBytecodes numBlocks numCleanBlocks result |
- 	hasYoungReferent := (objectMemory isYoungObject: methodObj).
- 	methodOrBlockNumArgs := coInterpreter argumentCountOf: methodObj.
- 	inBlock := true.
- 	postCompileHook := nil.
- 	maxLitIndex := -1.
- 	self assert: (coInterpreter primitiveIndexOf: methodObj) = 0.
- 	initialPC := coInterpreter startPCOfMethod: methodObj.
- 	"initial estimate.  Actual endPC is determined in scanMethod."
- 	endPC := objectMemory numBytesOf: methodObj.
- 	numBytecodes := endPC - initialPC + 1.
- 	self allocateOpcodes: (numBytecodes + 10) * self estimateOfAbstractOpcodesPerBytecodes
- 		bytecodes: numBytecodes
- 		ifFail: [^coInterpreter cCoerceSimple: MethodTooBig to: #'CogMethod *'].
- 	(numBlocks := self scanMethod) < 0 ifTrue:
- 		[^coInterpreter cCoerceSimple: numBlocks to: #'CogMethod *'].
- 	self assert: numBlocks = 0. "blocks in full blocks are full blocks, they are not inlined."
- 	numCleanBlocks := self scanForCleanBlocks.
- 	self assert: numCleanBlocks = 0. "blocks in full blocks are full blocks, they are not inlined."
- 	self allocateBlockStarts: numBlocks + numCleanBlocks.
- 	blockCount := 0.
- 	numCleanBlocks > 0 ifTrue:
- 		[self addCleanBlockStarts].
- 	(self maybeAllocAndInitCounters
- 	 and: [self maybeAllocAndInitIRCs]) ifFalse: "Inaccurate error code, but it'll do.  This will likely never fail."
- 		[^coInterpreter cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
- 
- 	blockEntryLabel := nil.
- 	methodLabel dependent: nil.
- 	(result := self compileEntireFullBlockMethod) < 0 ifTrue:
- 		[^coInterpreter cCoerceSimple: result to: #'CogMethod *'].
- 	^self generateCogFullBlock!

Item was added:
+ ----- Method: Cogit>>compileCogFullBlockMethod: (in category 'compile abstract instructions') -----
+ compileCogFullBlockMethod: numCopied
+ 	<returnTypeC: #'CogMethod *'>
+ 	| numBytecodes numBlocks numCleanBlocks result |
+ 	hasYoungReferent := (objectMemory isYoungObject: methodObj).
+ 	methodOrBlockNumArgs := coInterpreter argumentCountOf: methodObj.
+ 	inBlock := true.
+ 	postCompileHook := nil.
+ 	maxLitIndex := -1.
+ 	self assert: (coInterpreter primitiveIndexOf: methodObj) = 0.
+ 	initialPC := coInterpreter startPCOfMethod: methodObj.
+ 	"initial estimate.  Actual endPC is determined in scanMethod."
+ 	endPC := objectMemory numBytesOf: methodObj.
+ 	numBytecodes := endPC - initialPC + 1.
+ 	self allocateOpcodes: (numBytecodes + 10) * self estimateOfAbstractOpcodesPerBytecodes
+ 		bytecodes: numBytecodes
+ 		ifFail: [^coInterpreter cCoerceSimple: MethodTooBig to: #'CogMethod *'].
+ 	(numBlocks := self scanMethod) < 0 ifTrue:
+ 		[^coInterpreter cCoerceSimple: numBlocks to: #'CogMethod *'].
+ 	self assert: numBlocks = 0. "blocks in full blocks are full blocks, they are not inlined."
+ 	numCleanBlocks := self scanForCleanBlocks.
+ 	self assert: numCleanBlocks = 0. "blocks in full blocks are full blocks, they are not inlined."
+ 	self allocateBlockStarts: numBlocks + numCleanBlocks.
+ 	blockCount := 0.
+ 	numCleanBlocks > 0 ifTrue:
+ 		[self addCleanBlockStarts].
+ 	(self maybeAllocAndInitCounters
+ 	 and: [self maybeAllocAndInitIRCs]) ifFalse: "Inaccurate error code, but it'll do.  This will likely never fail."
+ 		[^coInterpreter cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
+ 
+ 	blockEntryLabel := nil.
+ 	methodLabel dependent: nil.
+ 	(result := self compileEntireFullBlockMethod: numCopied) < 0 ifTrue:
+ 		[^coInterpreter cCoerceSimple: result to: #'CogMethod *'].
+ 	^self generateCogFullBlock!

Item was removed:
- ----- Method: Cogit>>compileEntireFullBlockMethod (in category 'compile abstract instructions') -----
- compileEntireFullBlockMethod
- 	"Compile the abstract instructions for the entire method, including blocks."
- 	| result |	
- 	self compileFullBlockEntry.
- 
- 	"Frame build"
- 	self compileFullBlockMethodFrameBuild.
- 	"Method body"
- 	(result := self compileMethodBody) < 0 ifTrue:
- 		[^result].
- 	self assert: blockCount = 0.
- 	^0!

Item was added:
+ ----- Method: Cogit>>compileEntireFullBlockMethod: (in category 'compile abstract instructions') -----
+ compileEntireFullBlockMethod: numCopied
+ 	"Compile the abstract instructions for the entire method, including blocks."
+ 	| result |	
+ 	self compileFullBlockEntry.
+ 
+ 	"Frame build"
+ 	self compileFullBlockMethodFrameBuild: numCopied.
+ 	"Method body"
+ 	(result := self compileMethodBody) < 0 ifTrue:
+ 		[^result].
+ 	self assert: blockCount = 0.
+ 	^0!

Item was added:
+ ----- Method: Cogit>>generateCogFullBlock (in category 'compile abstract instructions') -----
+ generateCogFullBlock
+ 	"We handle jump sizing simply.  First we make a pass that asks each
+ 	 instruction to compute its maximum size.  Then we make a pass that
+ 	 sizes jumps based on the maxmimum sizes.  Then we make a pass
+ 	 that fixes up jumps.  When fixing up a jump the jump is not allowed to
+ 	 choose a smaller offset but must stick to the size set in the second pass."
+ 	<returnTypeC: #'CogMethod *'>
+ 	| codeSize headerSize mapSize totalSize startAddress result method |
+ 	<var: #method type: #'CogMethod *'>
+ 	headerSize := self sizeof: CogMethod.
+ 	methodLabel address: methodZone freeStart.
+ 	self computeMaximumSizes.
+ 	methodLabel concretizeAt: methodZone freeStart.
+ 	codeSize := self generateInstructionsAt: methodLabel address + headerSize.
+ 	mapSize := self generateMapAt: nil start: methodLabel address + cbNoSwitchEntryOffset.
+ .
+ 	totalSize := methodZone roundUpLength: headerSize + codeSize + mapSize.
+ 	totalSize > MaxMethodSize ifTrue:
+ 		[^self cCoerceSimple: MethodTooBig to: #'CogMethod *'].
+ 	startAddress := methodZone allocate: totalSize.
+ 	startAddress = 0 ifTrue:
+ 		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
+ 	self assert: startAddress + cbEntryOffset = fullBlockEntry address.
+ 	self assert: startAddress + cbNoSwitchEntryOffset = fullBlockNoContextSwitchEntry address.
+ 	result := self outputInstructionsAt: startAddress + headerSize.
+ 	self assert: startAddress + headerSize + codeSize = result.
+ 	backEnd padIfPossibleWithStopsFrom: result to: startAddress + totalSize - mapSize.
+ 	self generateMapAt: startAddress + totalSize - 1 start: startAddress + cbNoSwitchEntryOffset.
+ 	self flag: #TOCHECK. "It's not clear we want the same header than regular methods. 
+ 	It could be of the same size, but maybe the cmType could be different and the selector could be ignored." 
+ 	method := self fillInMethodHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
+ 					size: totalSize
+ 					selector: objectMemory nilObject.
+ 	postCompileHook ifNotNil:
+ 		[self perform: postCompileHook with: method.
+ 		 postCompileHook := nil].
+ 	^method!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>compileFullBlockMethodFrameBuild (in category 'compile abstract instructions') -----
- compileFullBlockMethodFrameBuild
- 	"Build a frame for a block activation.  See CoInterpreter class>>initializeFrameIndices.
- 	 		closure (in ReceiverResultReg)
- 			arg0
- 			...
- 			argN
- 			caller's saved ip/this stackPage (for a base frame)
- 	fp->	saved fp
- 			method
- 			context (uninitialized?)
- 			receiver
- 			first temp
- 			...
- 	sp->	Nth temp
- 	Avoid use of SendNumArgsReg which is the flag determining whether
- 	context switch is allowed on stack-overflow."
- 	<inline: false>
- 	needsFrame ifFalse: [^self].
- 	backEnd hasLinkRegister ifTrue:
- 		[self PushR: LinkReg].
- 	self PushR: FPReg.
- 	self MoveR: SPReg R: FPReg.
- 	"Think of ClassReg as ClosureReg"
- 	self MoveR: ReceiverResultReg R: ClassReg.
- 	"The block method field must have its MFMethodFlagIsBlockFlag bit set.
- 	 We arrange this using a labelOffset.  A hack, but it works."
- 	methodLabel addDependent: (self annotateAbsolutePCRef:
- 			(self PushCw: methodLabel asInteger)). "method"
- 	self annotate: (self PushCw: objectMemory nilObject) "context"
- 		objRef: objectMemory nilObject.
- 	"Fetch home receiver from outer context. closure is on stack and initially in ReceiverResultReg.
- 	 It is safe to use Arg0Reg because reg args are pushed by the value primitives if there are any.".
- 	
- 	self flag: 'we could do the following only if the block has inst var ref'.
- 	"Use ReceiverResultReg for Context to agree with store check trampoline"
- 	objectRepresentation
- 		genLoadSlot: FullClosureReceiverIndex
- 			sourceReg: ClassReg
- 				destReg: Arg0Reg.
- 	objectRepresentation
- 		genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg updatingSlot: FullClosureReceiverIndex in: ReceiverResultReg.
- 	self MoveR: Arg0Reg R: ReceiverResultReg.
- 	self PushR: ReceiverResultReg. "closure receiver"
- 	"Push copied values; bytecode initializes temporaries"
- 	self flag: 'numCopied needs to be passed as parameter'.
- 	0 to: self numCopied - 1 do:
- 		[:i|
- 		objectRepresentation
- 			genLoadSlot: i + FullClosureFirstCopiedValueIndex
- 			sourceReg: ClassReg
- 			destReg: TempReg.
- 		self PushR: TempReg].
- 	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
- 	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
- 	self JumpBelow: stackOverflowCall.
- 	stackCheckLabel := (self annotateBytecode: self Label)!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
+ compileFullBlockMethodFrameBuild: numCopied
+ 	"Build a frame for a block activation.  See CoInterpreter class>>initializeFrameIndices.
+ 	 		closure (in ReceiverResultReg)
+ 			arg0
+ 			...
+ 			argN
+ 			caller's saved ip/this stackPage (for a base frame)
+ 	fp->	saved fp
+ 			method
+ 			context (uninitialized?)
+ 			receiver
+ 			first temp
+ 			...
+ 	sp->	Nth temp
+ 	Avoid use of SendNumArgsReg which is the flag determining whether
+ 	context switch is allowed on stack-overflow."
+ 	<inline: false>
+ 	needsFrame ifFalse: [^self].
+ 	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
+ 	self PushR: FPReg.
+ 	self MoveR: SPReg R: FPReg.
+ 	"Think of ClassReg as ClosureReg"
+ 	self MoveR: ReceiverResultReg R: ClassReg.
+ 	"The block method field must have its MFMethodFlagIsBlockFlag bit set.
+ 	 We arrange this using a labelOffset.  A hack, but it works."
+ 	methodLabel addDependent: (self annotateAbsolutePCRef:
+ 			(self PushCw: methodLabel asInteger));
+ 			setLabelOffset: MFMethodFlagIsBlockFlag.. "method"
+ 	self genMoveConstant: objectMemory nilObject R: SendNumArgsReg.
+ 	self PushR: SendNumArgsReg. "context"
+ 	"Closure is on stack and initially in ReceiverResultReg.
+ 	 It is safe to use Arg0Reg because reg args are pushed by the value primitives if there are any.".
+ 
+ 	self flag: #TODO. "we could follow the receiver only if the block has inst var ref. Currently we use scanMethod for fullBlock 
+ 	and that scanner does not provide this information. We could extend it based on the scanBlock: method"
+ 	"Use ReceiverResultReg for the closure to agree with store check trampoline"
+ 	objectRepresentation
+ 		genLoadSlot: FullClosureReceiverIndex
+ 			sourceReg: ClassReg
+ 				destReg: Arg0Reg.
+ 	objectRepresentation
+ 		genEnsureOopInRegNotForwarded: Arg0Reg scratchReg: TempReg updatingSlot: FullClosureReceiverIndex in: ReceiverResultReg.
+ 	self MoveR: Arg0Reg R: ReceiverResultReg.
+ 
+ 	self PushR: ReceiverResultReg. "closure receiver"
+ 	"Push copied values"
+ 	0 to: numCopied - 1 do:
+ 		[:i|
+ 		objectRepresentation
+ 			genLoadSlot: i + FullClosureFirstCopiedValueIndex
+ 			sourceReg: ClassReg
+ 			destReg: TempReg.
+ 		self PushR: TempReg].
+ 	"Push slots for temps"
+ 	methodOrBlockNumArgs + numCopied + 1 to: (coInterpreter temporaryCountOfMethodHeader: methodHeader) do:
+ 		[:i|
+ 		self PushR: SendNumArgsReg].
+ 	
+ 	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
+ 	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
+ 	self JumpBelow: stackOverflowCall.
+ 	stackCheckLabel := (self annotateBytecode: self Label)!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>compileCogFullBlockMethod: (in category 'compile abstract instructions') -----
+ compileCogFullBlockMethod: numCopied
+ 	counters := 0.
+ 	^super compileCogFullBlockMethod: numCopied!

Item was added:
+ ----- Method: SistaStackToRegisterMappingCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
+ compileFullBlockMethodFrameBuild: numCopied
+ 	"Override to prefetch counters if any"
+ 	super compileFullBlockMethodFrameBuild: numCopied.
+ 	counters ~= 0 ifTrue:
+ 		[self PrefetchAw: counters]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>compileCogFullBlockMethod: (in category 'compile abstract instructions') -----
+ compileCogFullBlockMethod: numCopied
+ 	methodOrBlockNumTemps := coInterpreter tempCountOf: methodObj.
+ 	self cCode: '' inSmalltalk:
+ 		[debugStackPointers := coInterpreter debugStackPointersFor: methodObj].
+ 	^super compileCogFullBlockMethod: numCopied!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>compileEntireFullBlockMethod: (in category 'compile abstract instructions') -----
+ compileEntireFullBlockMethod: numCopied
+ 	regArgsHaveBeenPushed := false.
+ 	^super compileEntireFullBlockMethod: numCopied!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
+ compileFullBlockMethodFrameBuild: numCopied
+ 	needsFrame ifFalse:
+ 		[self initSimStackForFramelessMethod: initialPC.
+ 		 ^self].
+ 	self genPushRegisterArgs.
+ 	super compileFullBlockMethodFrameBuild: numCopied.
+ 	self initSimStackForFramefulMethod: initialPC!



More information about the Vm-dev mailing list