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

commits at source.squeak.org commits at source.squeak.org
Tue Nov 24 02:12:31 UTC 2015


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

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

Name: VMMaker.oscog-eem.1531
Author: eem
Time: 23 November 2015, 6:10:46.101 pm
UUID: 6ce9cac7-d262-4fbc-b171-33134440cdaf
Ancestors: VMMaker.oscog-tpr.1530

Cogit:
Finish the CPIC rewrite cleanup.

Move the rewriteCPICFoo methods out of the AbstractInstruction classes and into Cogit.

Add asserts to check the three-operand rewrite routine rewriteCPICCaseAt:tag:objRef:target: works as intended.  Make expectedClosedPICPrototype: live up to its comment and answer a bitmask identifying errors.

Use inCurrentCompilation: in a few places that still used the bowels of inCurrentCompilation:.

=============== Diff against VMMaker.oscog-tpr.1530 ===============

Item was changed:
  ----- Method: CogARMCompiler>>concretizePushCw (in category 'generate machine code - concretize') -----
  concretizePushCw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| word instrOffset |
  	word := operands at: 0.	
+ 	(self inCurrentCompilation: word)
- 	((self isAnInstruction: (cogit cCoerceSimple: word to: #'AbstractInstruction *'))
- 	 or: [cogit addressIsInCurrentCompilation: word])
  		ifTrue:
  			[instrOffset := self loadCwInto: ConcreteIPReg]
  		ifFalse:
  			[self 
  				rotateable8bitBitwiseImmediate: word 
  				ifTrue:
  					[:rot :immediate :invert|
  					self machineCodeAt: 0
  						put: (invert
  								ifTrue: [self mvn: ConcreteIPReg imm: immediate ror: rot]
  								ifFalse: [self mov: ConcreteIPReg imm: immediate ror: rot]).
  					instrOffset := 4]
  				ifFalse:
  					[instrOffset := self loadCwInto: ConcreteIPReg]].
  	self machineCodeAt: instrOffset put: (self pushR: ConcreteIPReg).
  	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>rewriteCPICJumpAt:target: (in category 'inline cacheing') -----
+ rewriteCPICJumpAt: addressFollowingJump target: jumpTargetAddress
- rewriteCPICJumpAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a jump instruction to call a different target.  This variant is used to reset the 
  	jumps in the prototype CPIC to suit each use,.   
  	Answer the extent of the code change which is used to compute the range of the icache to flush."
+ 	<var: #addressFollowingJump type: #usqInt>
+ 	<var: #jumpTargetAddress type: #usqInt>
+ 	<inline: true>
+ 	^self rewriteTransferAt: addressFollowingJump target: jumpTargetAddress!
- 	<var: #callSiteReturnAddress type: #usqInt>
- 	<var: #callTargetAddress type: #usqInt>
- 	^self rewriteTransferAt: callSiteReturnAddress target: callTargetAddress!

Item was removed:
- ----- Method: CogAbstractInstruction>>rewriteCPICCaseAt:tag:objRef:target: (in category 'inline cacheing') -----
- rewriteCPICCaseAt: followingAddress tag: newTag objRef: newObjRef target: newTarget
- 	"Rewrite the three values involved in a CPIC case. Used by the initialize & extend CPICs."
- 	self subclassResponsibility
- 	!

Item was removed:
- ----- Method: CogIA32Compiler>>rewriteCPICCaseAt:tag:objRef:target: (in category 'inline cacheing') -----
- rewriteCPICCaseAt: followingAddress tag: newTag objRef: newObjRef target: newTarget
- 	"Rewrite the three values involved in a CPIC case. Used by the initialize & extend CPICs."
- 
- 	"IA32 CPIC cases are
- 	 cmpl $0x newTag, %eax
- 	 movl $0x newObjRef, %ebx
- 	 jz .+0x newTarget (0x00010924)"
- 
- 	"rewite the tag via the first ldr"	
- 	self storeLiteral: newTag beforeFollowingAddress: (followingAddress -11).
- 
- 	"write the obj ref/operand via the second ldr"
- 	self storeLiteral: newObjRef beforeFollowingAddress: (followingAddress - 6).
- 	
- 	"write the jump address for the new target address"
- 	self rewriteJumpLongAt: followingAddress target: newTarget!

Item was changed:
  ----- Method: CogIA32Compiler>>rewriteCPICJumpAt:target: (in category 'inline cacheing') -----
+ rewriteCPICJumpAt: addressFollowingJump target: jumpTargetAddress
- rewriteCPICJumpAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite the short jump instruction to jump to a new cpic case target. "
+ 	<var: #addressFollowingJump type: #usqInt>
+ 	<var: #jumpTargetAddress type: #usqInt>
- 	<var: #callSiteReturnAddress type: #usqInt>
- 	<var: #callTargetAddress type: #usqInt>
  	| callDistance |
+ 	callDistance := jumpTargetAddress - addressFollowingJump.
+ 	self assert: callDistance abs < 128.
- 	callDistance := (callTargetAddress - callSiteReturnAddress) signedIntToLong.
- 	self assert: (callDistance < 256).
  	objectMemory
+ 		byteAt: addressFollowingJump - 1
+ 		put:  (callDistance bitAnd: 16rFF).
- 		byteAt: callSiteReturnAddress - 1 put:  (callDistance  bitAnd: 16rFF).
  	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: addressFollowingJump - 10 to: addressFollowingJump - 1]."
- 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
  	^2!

Item was removed:
- ----- Method: CogMIPSELCompiler>>rewriteCPICCaseAt:tag:objRef:target: (in category 'inline cacheing') -----
- rewriteCPICCaseAt: followingAddress tag: newTag objRef: newObjRef target: newTarget
- 	"rewrite the three values involved in a CPIC case. Used by the create & extend cpcic methods"
- 
- 	"lui at, tagHigh
- 	 ori at, at, tagLow
- 	 subu t0, s5, at (Cmp)
- 	 slt ... (Cmp)
- 	 slt ... (Cmp)
- 	 sltu ... (Cmp)
- 	 sltu ... (Cmp)
- 	 lui s4, objRefHigh
- 	 ori s4, s4, objRefLow
- 	 bne t0, zr, +12
- 	 nop (delay slot)
- 	 j target
- 	 nop (delay slot)
- 	 .... <-- followingAddress"
- 
- 	cogit disassembleFrom: followingAddress - 52 to: followingAddress.
- 	self assert: (self opcodeAtAddress: followingAddress - 52) = LUI.
- 	self assert: (self opcodeAtAddress: followingAddress - 48) = ORI.
- 	self assert: (self functionAtAddress: followingAddress - 44) = SUBU.
- 	self assert: (self functionAtAddress: followingAddress - 40) = SLT.
- 	self assert: (self functionAtAddress: followingAddress - 36) = SLT.
- 	self assert: (self functionAtAddress: followingAddress - 32) = SLTU.
- 	self assert: (self functionAtAddress: followingAddress - 28) = SLTU.
- 	self assert: (self opcodeAtAddress: followingAddress - 24) = LUI.
- 	self assert: (self opcodeAtAddress: followingAddress - 20) = ORI.
- 	self assert: (self opcodeAtAddress: followingAddress - 16) = BNE.
- 	self assert: (objectMemory longAt: followingAddress - 12) = self nop.
- 	self assert: (self opcodeAtAddress: followingAddress - 8) = J.
- 	self assert: (objectMemory longAt: followingAddress - 4) = self nop.
- 	
- 	self literalAtAddress: followingAddress - 48 put: newTag.
- 	self literalAtAddress: followingAddress - 20 put: newObjRef.
- 	self rewriteJTypeAtAddress: followingAddress - 8 target: newTarget.
- 
- 	cogit disassembleFrom: followingAddress - 52 to: followingAddress.
- 	self assert: (self opcodeAtAddress: followingAddress - 52) = LUI.
- 	self assert: (self opcodeAtAddress: followingAddress - 48) = ORI.
- 	self assert: (self functionAtAddress: followingAddress - 44) = SUBU.
- 	self assert: (self functionAtAddress: followingAddress - 40) = SLT.
- 	self assert: (self functionAtAddress: followingAddress - 36) = SLT.
- 	self assert: (self functionAtAddress: followingAddress - 32) = SLTU.
- 	self assert: (self functionAtAddress: followingAddress - 28) = SLTU.
- 	self assert: (self opcodeAtAddress: followingAddress - 24) = LUI.
- 	self assert: (self opcodeAtAddress: followingAddress - 20) = ORI.
- 	self assert: (self opcodeAtAddress: followingAddress - 16) = BNE.
- 	self assert: (objectMemory longAt: followingAddress - 12) = self nop.
- 	self assert: (self opcodeAtAddress: followingAddress - 8) = J.
- 	self assert: (objectMemory longAt: followingAddress - 4) = self nop.
- 
- 	^56!

Item was changed:
  ----- Method: CogMIPSELCompiler>>rewriteCPICJumpAt:target: (in category 'inline cacheing') -----
+ rewriteCPICJumpAt: addressFollowingJump target: jumpTargetAddress
- rewriteCPICJumpAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a jump instruction to call a different target.  This variant is used to reset the 
  	jumps in the prototype CPIC to suit each use,.   
  	Answer the extent of the code change which is used to compute the range of the icache to flush."
+ 	<var: #addressFollowingJump type: #usqInt>
+ 	<var: #jumpTargetAddress type: #usqInt>
- 	<var: #callSiteReturnAddress type: #usqInt>
- 	<var: #callTargetAddress type: #usqInt>
  	
+ 	cogit disassembleFrom: addressFollowingJump - 16 to: addressFollowingJump + 16.
- 	cogit disassembleFrom: callSiteReturnAddress - 16 to: callSiteReturnAddress + 16.
  	self halt.!

Item was removed:
- ----- Method: CogOutOfLineLiteralsARMCompiler>>rewriteCPICCaseAt:tag:objRef:target: (in category 'inline cacheing') -----
- rewriteCPICCaseAt: followingAddress tag: newTag objRef: newObjRef target: newTarget
- 	"rewrite the three values involved in a CPIC case. Used by the create & extend cpcic methods"
- 
- 	"ARM CPIC cases are
- 	ldr TempReg, [pc relative -> tag]
- 	cmp TempReg0, TempReg 
- 	ldr SendNumArgs, [pc relative -> obj ref]
- 	beq target"
- 	"rewite the tag via the first ldr"	
- 	objectMemory longAt: (self pcRelativeAddressAt: followingAddress - 16) put: newTag.
- 
- 	"write the obj ref/operand via the second ldr"
- 	objectMemory longAt: (self pcRelativeAddressAt: followingAddress - 8) put: newObjRef.
- 	
- 	"write the jump address for the new target address"
- 	self rewriteJumpLongAt: followingAddress target: newTarget!

Item was changed:
  ----- Method: CogOutOfLineLiteralsARMCompiler>>usesOutOfLineLiteral (in category 'testing') -----
  usesOutOfLineLiteral
  	"Answer if the receiver uses an out-of-line literal.  Needs only
  	 to work for the opcodes created with gen:literal:operand: et al."
  
  	opcode
  		caseOf: {
  		[CallFull]		-> [^true].
  		[JumpFull]		-> [^true].
  		"Arithmetic"
  		[AddCqR]		-> [^self rotateable8bitSignedImmediate: (operands at: 0) ifTrue: [:r :i :n| false] ifFalse: [true]].
  		[AndCqR]		-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  								ifTrue: [:r :i :n| false]
  								ifFalse: [1 << (operands at: 0) highBit ~= ((operands at: 0) + 1)]].
  		[AndCqRR]		-> [^self rotateable8bitBitwiseImmediate: (operands at: 0)
  								ifTrue: [:r :i :n| false]
  								ifFalse: [1 << (operands at: 0) highBit ~= ((operands at: 0) + 1)]].
  		[CmpCqR]		-> [^self rotateable8bitSignedImmediate: (operands at: 0) ifTrue: [:r :i :n| false] ifFalse: [true]].
  		[OrCqR]			-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[SubCqR]		-> [^self rotateable8bitSignedImmediate: (operands at: 0) ifTrue: [:r :i :n| false] ifFalse: [true]].
  		[TstCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[XorCqR]		-> [^self rotateable8bitBitwiseImmediate: (operands at: 0) ifTrue: [:r :i :n| false] ifFalse: [true]].
  		[AddCwR]		-> [^true].
  		[AndCwR]		-> [^true].
  		[CmpCwR]		-> [^true].
  		[OrCwR]		-> [^true].
  		[SubCwR]		-> [^true].
  		[XorCwR]		-> [^true].
  		[LoadEffectiveAddressMwrR]
  						-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		"Data Movement"						
  		[MoveCqR]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
+ 		[MoveCwR]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
- 		[MoveCwR]		-> [^((self isAnInstruction: (cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *')) "i.e. a label, which by definition will be in the current compilation."
- 							  or: [cogit addressIsInCurrentCompilation: (operands at: 0)]) not].
  		[MoveAwR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) ifTrue: [false] ifFalse: [true]].
  		[MoveRAw]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) ifTrue: [false] ifFalse: [true]].
  		[MoveAbR]		-> [^(self isAddressRelativeToVarBase: (operands at: 0)) ifTrue: [false] ifFalse: [true]].
  		[MoveRAb]		-> [^(self isAddressRelativeToVarBase: (operands at: 1)) ifTrue: [false] ifFalse: [true]].
  		[MoveRMwr]	-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveRdM64r]	-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]]. 
  		[MoveMbrR]		-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveRMbr]		-> [^self is12BitValue: (operands at: 1) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveM16rR]	-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[MoveM64rRd]	-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]].
  		[MoveMwrR]	-> [^self is12BitValue: (operands at: 0) ifTrue: [:u :i| false] ifFalse: [true]].
+ 		[PushCw]		-> [^(self inCurrentCompilation: (operands at: 0)) not].
- 		[PushCw]		-> [^((self isAnInstruction: (cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *')) "i.e. a label, which by definiion will be in the current compilation."
- 							  or: [cogit addressIsInCurrentCompilation: (operands at: 0)]) not].
  		[PushCq]		-> [^self rotateable8bitImmediate: (operands at: 0) ifTrue: [:r :i| false] ifFalse: [true]].
  		[PrefetchAw] 	-> [^(self isAddressRelativeToVarBase: (operands at: 0)) ifTrue: [false] ifFalse: [true]].
  		}
  		otherwise: [self assert: false].
  	^false "to keep C compiler quiet"
  !

Item was added:
+ ----- Method: CogX64Compiler>>rewriteCallAt:target: (in category 'inline cacheing') -----
+ rewriteCallAt: callSiteReturnAddress target: callTargetAddress
+ 	"Rewrite a call instruction to call a different target.  This variant is used to link PICs
+ 	 in ceSendMiss et al, and to rewrite cached primitive calls.   Answer the extent of
+ 	 the code change which is used to compute the range of the icache to flush."
+ 	<var: #callSiteReturnAddress type: #usqInt>
+ 	<var: #callTargetAddress type: #usqInt>
+ 	| callDistance |
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	false
+ 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
+ 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
+ 					[self error: 'linking callsite to invalid address']].
+ 	callDistance := (callTargetAddress - callSiteReturnAddress) signedIntToLong.
+ 	objectMemory
+ 		byteAt: callSiteReturnAddress - 1 put: (callDistance >> 24 bitAnd: 16rFF);
+ 		byteAt: callSiteReturnAddress - 2 put: (callDistance >> 16 bitAnd: 16rFF);
+ 		byteAt: callSiteReturnAddress - 3 put: (callDistance >>   8 bitAnd: 16rFF);
+ 		byteAt: callSiteReturnAddress - 4 put: (callDistance            bitAnd: 16rFF).
+ 	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) signedIntToLong = callTargetAddress.
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	^5!

Item was added:
+ ----- Method: CogX64Compiler>>rewriteJumpLongAt:target: (in category 'inline cacheing') -----
+ rewriteJumpLongAt: addressFollowingJump target: jumpTargetAddress
+ 	"Rewrite a long jump instruction to jump to a different target.  This variant
+ 	 is used to rewrite cached primitive calls.   Answer the extent of the
+ 	 code change which is used to compute the range of the icache to flush."
+ 	<inline: true>
+ 	^self rewriteCallAt: addressFollowingJump target: jumpTargetAddress!

Item was changed:
  ----- Method: Cogit>>cogExtendPIC:CaseNMethod:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogExtendPIC: cPIC CaseNMethod: caseNMethod tag: caseNTag isMNUCase: isMNUCase
  	"Extend the cPIC with the supplied case.  If caseNMethod is cogged dispatch direct to
  	 its unchecked entry-point.  If caseNMethod is not cogged, jump to the fast interpreter
  	 dispatch, and if isMNUCase then dispatch to fast MNU invocation and mark the cPIC as
  	 having the MNU case for cache flushing."
   	<var: #cPIC type: #'CogMethod *'>
  	| operand target address |
  
  	coInterpreter
  		compilationBreak: cPIC selector
  		point: (objectMemory numBytesOf: cPIC selector)
  		isMNUCase: isMNUCase.
  
  	self assert: (objectRepresentation inlineCacheTagIsYoung: caseNTag) not.
  	"Caller patches to open pic if caseNMethod is young."
  	self assert: (caseNMethod notNil and: [(objectMemory isYoung: caseNMethod) not]).
  	(isMNUCase not and: [coInterpreter methodHasCogMethod: caseNMethod])
+ 		ifTrue: "this isn't an MNU and we have an already cogged method to jump to"
- 		ifTrue: "this isn't an mNU and we have an already cogged method to jump to"
  			[operand := 0.
  			 target := (coInterpreter cogMethodOf: caseNMethod) asInteger + cmNoCheckEntryOffset]
  		ifFalse: 
  			[operand := caseNMethod.
  			 isMNUCase
+ 				ifTrue: "this is an MNU so tag the CPIC header and setup a jump to the MNUAbort"
- 				ifTrue: "this is an mNU so tag the CPIC header and setup a jump to the mNUAbort"
  					[cPIC cpicHasMNUCase: true.
  					 target := cPIC asInteger + (self sizeof: CogMethod)]
  				ifFalse: "setup a jump to the interpretAborth so we can cog the target method"
  					[target := cPIC asInteger + self picInterpretAbortOffset]].
  
  	"find the end address of the new case"
  	address := self addressOfEndOfCase: cPIC cPICNumCases +1 inCPIC: cPIC.
  	
+ 	self rewriteCPICCaseAt: address tag: caseNTag objRef: operand target: target.
- 	backEnd rewriteCPICCaseAt: address tag: caseNTag objRef: operand target: target.
  
  	"finally, rewrite the jump 3 instr  before firstCPICCaseOffset to jump to the beginning of this new case"
  	self rewriteCPIC: cPIC caseJumpTo: address - cPICCaseSize. 
  
  	processor flushICacheFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize.
  	"update the header flag for the number of cases"
  	cPIC cPICNumCases: cPIC cPICNumCases + 1.
  	^0!

Item was changed:
  ----- Method: Cogit>>configureCPIC:Case0:Case1Method:tag:isMNUCase:numArgs:delta: (in category 'in-line cacheing') -----
  configureCPIC: cPIC Case0: case0CogMethod Case1Method: case1Method tag: case1Tag isMNUCase: isMNUCase numArgs: numArgs delta: addrDelta
  	"Configure a copy of the prototype CPIC for 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; jump to its unchecked entry-point
  		- a CompiledMethod; jump to the ceInterpretFromPIC trampoline
  		- nil; call ceMNUFromPIC
+ 	addDelta is the address change from the prototype to the new CPIC location, needed
+ 	because the loading of the CPIC label at the end may use a literal instead of a pc relative load."
+ 	"self disassembleFrom: cPIC asInteger + (self sizeof: CogMethod) to: cPIC asInteger + closedPICSize"
- 	addDelta is the address change from the prototype to the new CPCI location, needed
- 	because the loading of the CPIC lable at the end may use a literal instead of a pc relative"
  	<var: #cPIC type: #'CogMethod *'>
  	<var: #case0CogMethod type: #'CogMethod *'>
  	| operand targetEntry caseEndAddress|
  	<var: #targetEntry type: #'void *'>
  	self assert: case1Method notNil.
  
  	"adjust the call at missOffset, the ceAbortXArgs"
  	backEnd rewriteCallAt: cPIC asInteger + missOffset target: (self picAbortTrampolineFor: numArgs).
  	
  	self assert: (objectRepresentation inlineCacheTagIsYoung: case1Tag) not.
  	(isMNUCase not
  	 and: [coInterpreter methodHasCogMethod: case1Method])
  		ifTrue:
  			[operand := 0.
  			 targetEntry := ((coInterpreter cogMethodOf: case1Method) asInteger + cmNoCheckEntryOffset) asVoidPointer]
  		ifFalse: "We do not scavenge PICs, hence we cannot cache the MNU method if it is in new space."
  			[operand := (case1Method isNil or: [objectMemory isYoungObject: case1Method])
  							ifTrue: [0]
  							ifFalse: [case1Method].
  			 targetEntry := case1Method isNil ifTrue: [cPIC asInteger + (self sizeof: CogMethod)] ifFalse: [cPIC asInteger + self picInterpretAbortOffset]].
  
  	"set the jump to the case0 method"
  	backEnd rewriteJumpLongAt: cPIC asInteger + firstCPICCaseOffset target: case0CogMethod asInteger + cmNoCheckEntryOffset.
  
  	caseEndAddress := self addressOfEndOfCase: 2 inCPIC: cPIC.
  
+ 	"update the cpic case"
+ 	self
+ 		rewriteCPICCaseAt: caseEndAddress
+ 		tag: case1Tag
+ 		objRef: operand
+ 		target: (isMNUCase ifTrue: [cPIC asInteger + (self sizeof: CogMethod)] ifFalse: [targetEntry]) asInteger.
- 	"update the cpic case - deferred to backend because messy"
- 	backEnd rewriteCPICCaseAt: caseEndAddress tag: case1Tag objRef: operand target: (isMNUCase ifTrue: [cPIC asInteger + (self sizeof: CogMethod)] ifFalse: [targetEntry]) asInteger.
  
+ 	"update the loading of the CPIC address"
- 	"update the loading of the PCIC label address"
  	backEnd relocateMethodReferenceBeforeAddress: cPIC asInteger + cPICEndOfCodeOffset - backEnd jumpLongByteSize by: addrDelta.
  
  	"write the final desperate jump to cePICMissXArgs"
  	backEnd rewriteJumpLongAt: cPIC asInteger + cPICEndOfCodeOffset target: (self cPICMissTrampolineFor: numArgs).
  	^0
  	"self disassembleFrom: cPIC + (self sizeof: CogMethod) to: cPIC + closedPICSize - 1."!

Item was changed:
  ----- Method: Cogit>>configureMNUCPIC:methodOperand:numArgs:delta: (in category 'in-line cacheing') -----
  configureMNUCPIC: cPIC methodOperand: methodOperand numArgs: numArgs delta: addrDelta
+ 	"Configure a copy of the prototype CPIC for a one-case MNU CPIC that calls ceMNUFromPIC for
+ 	 case0Tag The tag for case0 is at the send site and so doesn't need to be generated.
+ 	 addDelta is the address change from the prototype to the new CPIC location, needed
+ 	 because the loading of the CPIC label at the end may be a literal instead of a pc-relative load."
- 	"Configure a copy of the prototype CPIC for a one-case MNU PIC that calls ceMNUFromPIC for case0Tag
- 	 The tag for case0 is at the send site and so doesn't need to be generated.
- 	addDelta is the address change from the prototype to the new CPCI location, needed
- 	because the loading of the CPIC label at the end may use a literal instead of a pc relative"
  	<var: #cPIC type: #'CogMethod *'>
  	| operand |
  
  	"adjust the jump at missOffset, the ceAbortXArgs"
  	backEnd rewriteJumpLongAt: cPIC asInteger + missOffset target: (self picAbortTrampolineFor: numArgs).
  	
  	"We do not scavenge PICs, hence we cannot cache the MNU method if it is in new space."
  	operand := (methodOperand isNil or: [objectMemory isYoungObject: methodOperand])
  					ifTrue: [0]
  					ifFalse: [methodOperand].
  	"set the jump to the case0 method"
  	backEnd rewriteJumpLongAt: cPIC asInteger + firstCPICCaseOffset target: cPIC asInteger + (self sizeof: CogMethod) .
  
  	backEnd storeLiteral: operand beforeFollowingAddress: cPIC asInteger + firstCPICCaseOffset - backEnd jumpLongByteSize.
  
  	"rewrite the final desperate jump to cePICMissXArgs"
  	backEnd rewriteJumpLongAt: cPIC asInteger + cPICEndOfCodeOffset target: (self cPICMissTrampolineFor: numArgs).	
  
+ 	"update the loading of the CPIC label address"
- 	"update the loading of the PCIC label address"
  	backEnd relocateMethodReferenceBeforeAddress: cPIC asInteger + cPICEndOfCodeOffset - backEnd jumpLongByteSize by: addrDelta.
  
+ 	"finally, rewrite the jump 3 instr before firstCPICCaseOffset to jump to the end of case 2, missing the actual case"
- 	"finally, rewrite the jump 3 instr  before firstCPICCaseOffset to jump to the end of case 2, missing the actual case"
  	self rewriteCPIC: cPIC caseJumpTo: (self addressOfEndOfCase: 2 inCPIC: cPIC). 
  
+ 	^0!
- 
- 	^0
- !

Item was changed:
  ----- Method: Cogit>>expectedClosedPICPrototype: (in category 'in-line cacheing') -----
  expectedClosedPICPrototype: cPIC
+ 	"Use asserts to check if the ClosedPICPrototype is as expected from compileClosedPICPrototype,
+ 	 and can be updated as required via rewriteCPICCaseAt:tag:objRef:target:.  If all asserts pass, answer
+ 	 0, otherwise answer a bit mask identifying all the errors."
- 	"Answer 0 if the ClosedPIC is as expected from compileClosedPICPrototype,
- 	 otherwise answer an error code identifying the first discrepancy found."
  	"self disassembleFrom: methodZoneBase + (self sizeof: CogMethod) to: methodZoneBase + closedPICSize"
  	<var: #cPIC type: #'CogMethod *'>
+ 	| pc errors object classTag entryPoint |
+ 	errors := 0.
- 	| pc object entryPoint |
  	pc := cPIC asUnsignedInteger + firstCPICCaseOffset.
  	"First jump is unconditional; subsequent ones are conditional"
  	object := backEnd literalBeforeFollowingAddress: pc - backEnd jumpLongByteSize.
+ 	(self asserta: object = 16r5EAF00D) ifFalse:
+ 		[errors := 1].
- 	self assert: object = 16r5EAF00D.
  
  	entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc.
+ 	(self asserta: entryPoint = (self cPICPrototypeCaseOffset + 16rCA5E10)) ifFalse:
+ 		[errors := errors + 2].
- 	self assert: entryPoint = (self cPICPrototypeCaseOffset + 16rCA5E10).
  
  	1 to: maxCPICCases - 1 do:
  		[:i | | methodObjPC classTagPC |
  		pc := pc + cPICCaseSize.
  
+ 		"verify information in case is as expected."
  		methodObjPC := pc - backEnd jumpLongConditionalByteSize - backEnd cmpC32RTempByteSize.
  		object := backEnd literalBeforeFollowingAddress: methodObjPC.
+ 		(self asserta: object = (16rBADA550 + i)) ifFalse:
+ 			[errors := errors bitOr: 4].
- 		self assert: object = (16rBADA550 + i).
- 		backEnd storeLiteral: (object bitXor: 16rA5A5A5A5) beforeFollowingAddress: methodObjPC.
- 		object := backEnd literalBeforeFollowingAddress: methodObjPC.
- 		self assert: object = (16rBADA550 + i bitXor: 16rA5A5A5A5).
- 		backEnd storeLiteral: (object bitXor: 16rA5A5A5A5) beforeFollowingAddress: methodObjPC.
  
  		classTagPC := pc - backEnd jumpLongConditionalByteSize.
+ 		classTag := backEnd literal32BeforeFollowingAddress: classTagPC.
+ 		(self asserta: classTag = (16rBABE1F15 + i)) ifFalse:
+ 			[errors := errors bitOr: 8].
- 		object := backEnd literal32BeforeFollowingAddress: classTagPC.
- 		self assert: object = (16rBABE1F15 + i).
- 		backEnd storeLiteral32: (object bitXor: 16r5A5A5A5A) beforeFollowingAddress: classTagPC.
- 		object := backEnd literal32BeforeFollowingAddress: classTagPC.
- 		self assert: object = (16rBABE1F15 + i bitXor: 16r5A5A5A5A).
- 		backEnd storeLiteral32: (object bitXor: 16r5A5A5A5A) beforeFollowingAddress: classTagPC.
  
  		entryPoint := backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc.
+ 		(self asserta: entryPoint = (self cPICPrototypeCaseOffset + 16rCA5E10 + (i * 16))) ifFalse:
+ 			[errors := errors bitOr: 16].
- 		self assert: entryPoint = (self cPICPrototypeCaseOffset + 16rCA5E10 + (i * 16))].
  
+ 		"change case via rewriteCPICCaseAt:tag:objRef:target:"
+ 		self rewriteCPICCaseAt: pc
+ 			tag: (classTag bitXor: 16r5A5A5A5A)
+ 			objRef: (object bitXor: 16rA5A5A5A5)
+ 			target: (entryPoint bitXor: 16r55AA50). "don't xor least 4 bits to leave instruction alignment undisturbed"
+ 
+ 		"verify information in case is as expected post update."
+ 		object := backEnd literalBeforeFollowingAddress: methodObjPC.
+ 		(self asserta: object = (16rBADA550 + i bitXor: 16rA5A5A5A5)) ifFalse:
+ 			[errors := errors bitOr: 32].
+ 		classTag := backEnd literal32BeforeFollowingAddress: classTagPC.
+ 		(self asserta: classTag = (16rBABE1F15 + i bitXor: 16r5A5A5A5A)) ifFalse:
+ 			[errors := errors bitOr: 64].
+ 		entryPoint := backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc.
+ 		(self asserta: entryPoint = ((self cPICPrototypeCaseOffset + 16rCA5E10 + (i * 16)) bitXor: 16r55AA50)) ifFalse:
+ 			[errors := errors bitOr: 128].
+ 
+ 		"finally restore case to the original state"
+ 		self rewriteCPICCaseAt: pc
+ 			tag: (classTag bitXor: 16r5A5A5A5A)
+ 			objRef: (object bitXor: 16rA5A5A5A5)
+ 			target: (entryPoint bitXor: 16r55AA50)].
+ 
  	entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc + cPICEndSize - literalsManager endSizeOffset.
+ 	(self asserta: entryPoint = (self cPICMissTrampolineFor: 0)) ifFalse:
+ 		[errors := errors + 256].
- 	self assert: entryPoint = (self cPICMissTrampolineFor: 0).
  	
+ 	^errors!
- 	^0!

Item was added:
+ ----- Method: Cogit>>rewriteCPICCaseAt:tag:objRef:target: (in category 'in-line cacheing') -----
+ rewriteCPICCaseAt: followingAddress tag: newTag objRef: newObjRef target: newTarget
+ 	"Rewrite the three values involved in a CPIC case.  Used by the initialize & extend CPICs.
+ 	 c.f. expectedClosedPICPrototype:"
+ 
+ 	"write the obj ref/operand via the second ldr"
+ 	| classTagPC methodObjPC |
+ 	methodObjPC := followingAddress - backEnd jumpLongConditionalByteSize - backEnd cmpC32RTempByteSize.
+ 	backEnd storeLiteral: newObjRef beforeFollowingAddress: methodObjPC.
+ 
+ 	classTagPC := followingAddress - backEnd jumpLongConditionalByteSize.
+ 	"rewite the tag via the first ldr"	
+ 	backEnd storeLiteral32: newTag beforeFollowingAddress: classTagPC.
+ 
+ 	"write the jump address for the new target address"
+ 	backEnd rewriteJumpLongAt: followingAddress target: newTarget!



More information about the Vm-dev mailing list