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

commits at source.squeak.org commits at source.squeak.org
Thu Mar 12 03:19:20 UTC 2015


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

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

Name: VMMaker.oscog-eem.1088
Author: eem
Time: 11 March 2015, 8:17:26.624 pm
UUID: 8298a649-68d4-4bac-ace3-46649a076245
Ancestors: VMMaker.oscog-eem.1087

Cogit:
Fix asserts around missOffset for ARM (a LinkReg
issue).  Implement callInstructionByteSize for ARM.

Fix LinkReg pushing in method abort calls; since abort
sequences always push it, tramspolines don't need to.
(hence may be able to remove pushLinkReg: arg from
trampoline generation routines soon).

Fix LinkReg management in genUpArrowReturn; LinkReg is
/not/ pushed in leaf routines (hence will have to save and
restore it around calls such as store checks in frameless
methods).

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

Item was added:
+ ----- Method: CogARMCompiler>>callInstructionByteSize (in category 'accessing') -----
+ callInstructionByteSize
+ 	^4!

Item was changed:
+ ----- Method: CogIA32Compiler>>callInstructionByteSize (in category 'accessing') -----
- ----- Method: CogIA32Compiler>>callInstructionByteSize (in category 'assertions') -----
  callInstructionByteSize
  	^5!

Item was changed:
  ----- Method: Cogit>>cogMNUPICSelector:receiver:methodOperand:numArgs: (in category 'in-line cacheing') -----
  cogMNUPICSelector: selector receiver: rcvr methodOperand: methodOperand numArgs: numArgs
  	<api>
  	"Attempt to create a one-case PIC for an MNU.
  	 The tag for the case is at the send site and so doesn't need to be generated."
  	<returnTypeC: #'CogMethod *'>
  	| startAddress headerSize size end |
  	((objectMemory isYoung: selector)
  	 or: [(objectRepresentation inlineCacheTagForInstance: rcvr) = self picAbortDiscriminatorValue]) ifTrue:
  		[^0].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: true.
  	self assert: endCPICCase0 notNil.
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[coInterpreter callForCogCompiledCodeCompaction.
  		 ^0].
  	methodLabel
  		address: startAddress;
  		dependent: nil.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
  	self compileMNUCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		methodOperand: methodOperand
  		numArgs: numArgs.
  	self computeMaximumSizes.
  	headerSize := self sizeof: CogMethod.
  	size := self generateInstructionsAt: startAddress + headerSize.
  	end := self outputInstructionsAt: startAddress + headerSize.
+ 	"The missOffset is the same as the interpretOffset. On RISCs it includes an additional instruction."
+ 	self assert: missOffset = ((backEnd hasLinkRegister ifTrue: [backEnd callInstructionByteSize] ifFalse: [0])
+ 								+ picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
- 	"The missOffset is the same as the interpretOffset."
- 	self assert: missOffset = (picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
  	self assert: startAddress + cmEntryOffset = entry address.
  	^self
  		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		size: closedPICSize
  		numArgs: numArgs
  		numCases: 1
  		hasMNUCase: true
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>cogPICSelector:numArgs:Case0Method:Case1Method:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogPICSelector: selector numArgs: numArgs Case0Method: case0CogMethod Case1Method: case1MethodOrNil tag: case1Tag isMNUCase: isMNUCase
  	"Attempt to create a two-case PIC for case0CogMethod and  case1Method,case1Tag.
  	 The tag for case0CogMethod is at the send site and so doesn't need to be generated.
  	 case1Method may be any of
  		- a Cog method; link to its unchecked entry-point
  		- a CompiledMethod; link to ceInterpretMethodFromPIC:
  		- a CompiledMethod; link to ceMNUFromPICMNUMethod:receiver:"
  	<var: #case0CogMethod type: #'CogMethod *'>
  	<returnTypeC: #'CogMethod *'>
  	| startAddress headerSize size end |
  	(objectMemory isYoung: selector) ifTrue:
  		[^self cCoerceSimple: YoungSelectorInPIC to: #'CogMethod *'].
  	coInterpreter
  		compilationBreak: selector
  		point: (objectMemory numBytesOf: selector)
  		isMNUCase: isMNUCase.
  	startAddress := methodZone allocate: closedPICSize.
  	startAddress = 0 ifTrue:
  		[^self cCoerceSimple: InsufficientCodeSpace to: #'CogMethod *'].
  	methodLabel
  		address: startAddress;
  		dependent: nil.
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: numPICCases * 7 bytecodes: 0.
  	self compileCPIC: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		Case0: case0CogMethod
  		Case1Method: case1MethodOrNil
  		tag: case1Tag
  		isMNUCase: isMNUCase
  		numArgs: numArgs.
  	self computeMaximumSizes.
  	headerSize := self sizeof: CogMethod.
  	size := self generateInstructionsAt: startAddress + headerSize.
  	end := self outputInstructionsAt: startAddress + headerSize.
+ 	"The missOffset is the same as the interpretOffset. On RISCs it includes an additional instruction."
+ 	self assert: missOffset = ((backEnd hasLinkRegister ifTrue: [backEnd callInstructionByteSize] ifFalse: [0])
+ 								+ picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
- 	"The missOffset is th same as the interpretOffset."
- 	self assert: missOffset = (picInterpretAbort address + picInterpretAbort machineCodeSize - startAddress).
  	self assert: startAddress + cmEntryOffset = entry address.
  	self assert: endCPICCase0 address = (startAddress + firstCPICCaseOffset).
  	self assert: endCPICCase1 address = (startAddress + firstCPICCaseOffset + cPICCaseSize).
  	^self
  		fillInCPICHeader: (self cCoerceSimple: startAddress to: #'CogMethod *')
  		size: closedPICSize
  		numArgs: numArgs
  		numCases: 2
  		hasMNUCase: isMNUCase
  		selector: selector !

Item was changed:
  ----- Method: Cogit>>genMethodAbortTrampoline (in category 'initialization') -----
  genMethodAbortTrampoline
  	"Generate the abort for a method.  This abort performs either a call of ceSICMiss:
  	 to handle a single-in-line cache miss or a call of ceStackOverflow: to handle a
  	 stack overflow.  It distinguishes the two by testing ResultReceiverReg.  If the
  	 register is zero then this is a stack-overflow because a) the receiver has already
  	 been pushed and so can be set to zero before calling the abort, and b) the
  	 receiver must always contain an object (and hence be non-zero) on SIC miss."
  	| jumpSICMiss |
  	<var: #jumpSICMiss type: #'AbstractInstruction *'>
  	opcodeIndex := 0.
  	self CmpCq: 0 R: ReceiverResultReg.
  	jumpSICMiss := self JumpNonZero: 0.
  
  	self compileTrampolineFor: #ceStackOverflow:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: false "The LinkReg has already been pushed in the abort sequence."
- 		pushLinkReg: true
  		resultReg: nil.
  	jumpSICMiss jmpTarget: self Label.
  	^self genTrampolineFor: #ceSICMiss:
  		called: 'ceMethodAbort'
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: false "The LinkReg has already been pushed in the abort sequence."
- 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genUpArrowReturn (in category 'bytecode generators') -----
  genUpArrowReturn
  	"Generate a method return from within a method or a block.
  	 Frameless method activation looks like
  				receiver
  				args
  		sp->	ret pc.
  	 Return pops receiver and arguments off the stack.  Callee pushes the result."
  	self flag: 'currently caller pushes result'.
  	inBlock ifTrue:
  		[self assert: needsFrame.
  		 self annotateBytecode: (self CallRT: ceNonLocalReturnTrampoline).
  		 ^0].
  	needsFrame ifTrue:
  		[self MoveR: FPReg R: SPReg.
+ 		 self PopR: FPReg.
+ 		 backEnd hasLinkRegister ifTrue:
+ 			[self PopR: LinkReg]].
- 		 self PopR: FPReg].
- 	backEnd hasLinkRegister ifTrue:
- 		[self PopR: LinkReg].
  	self RetN: methodOrBlockNumArgs + 1 * objectMemory wordSize.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMethodAbortTrampolineFor: (in category 'initialization') -----
  genMethodAbortTrampolineFor: numArgs
  	
  	"Generate the abort for a method.  This abort performs either a call of ceSICMiss:
  	 to handle a single-in-line cache miss or a call of ceStackOverflow: to handle a
  	 stack overflow.  It distinguishes the two by testing ResultReceiverReg.  If the
  	 register is zero then this is a stack-overflow because a) the receiver has already
  	 been pushed and so can be set to zero before calling the abort, and b) the
  	 receiver must always contain an object (and hence be non-zero) on SIC miss."
  	| jumpSICMiss |
  	<var: #jumpSICMiss type: #'AbstractInstruction *'>
  	opcodeIndex := 0.
  	self CmpCq: 0 R: ReceiverResultReg.
  	jumpSICMiss := self JumpNonZero: 0.
  
  	self compileTrampolineFor: #ceStackOverflow:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: false "The LinkReg has already been pushed in the abort sequence."
- 		pushLinkReg: true
  		resultReg: nil.
  	jumpSICMiss jmpTarget: self Label.
  	backEnd genPushRegisterArgsForAbortMissNumArgs: numArgs.
  	^self genTrampolineFor: #ceSICMiss:
  		called: (self trampolineName: 'ceMethodAbort' numArgs: (numArgs <= self numRegArgs ifTrue: [numArgs] ifFalse: [-1]))
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: false "The LinkReg has already been pushed in the abort sequence."
- 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genUpArrowReturn (in category 'bytecode generators') -----
  genUpArrowReturn
  	"Generate a method return from within a method or a block.
  	 Frameless method activation looks like
  				receiver
  				args
  		sp->	ret pc.
  	 Return pops receiver and arguments off the stack.  Callee pushes the result."
  	inBlock ifTrue:
  		[self assert: needsFrame.
  		 self annotateBytecode: (self CallRT: ceNonLocalReturnTrampoline).
  		 ^0].
  	needsFrame
  		ifTrue:
  			[self MoveR: FPReg R: SPReg.
  			 self PopR: FPReg.
  			 backEnd hasLinkRegister ifTrue:
  				[self PopR: LinkReg].
  			 self RetN: methodOrBlockNumArgs + 1 * objectMemory wordSize]
  		ifFalse:
+ 			[self RetN: ((methodOrBlockNumArgs > self numRegArgs
- 			[backEnd hasLinkRegister ifTrue:
- 				[self PopR: LinkReg].
- 			 self RetN: ((methodOrBlockNumArgs > self numRegArgs
  						"A method with an interpreter prim will push its register args for the prim.  If the failure
  						 body is frameless the args must still be popped, see e.g. Behavior>>nextInstance."
  						or: [regArgsHaveBeenPushed])
  							ifTrue: [methodOrBlockNumArgs + 1 * objectMemory wordSize]
  							ifFalse: [0])].
  	^0!



More information about the Vm-dev mailing list