[Vm-dev] VM Maker: VMMaker.oscog-rmacnak.1554.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Dec 5 22:20:56 UTC 2015


Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1554.mcz

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

Name: VMMaker.oscog-rmacnak.1554
Author: rmacnak
Time: 5 December 2015, 2:19:42.958 pm
UUID: 973f6adb-6fb4-4648-ab13-64872ee85702
Ancestors: VMMaker.oscog-eem.1553

MIPS: Get simulation just past the first code compaction. Fail shortly thereafter.

CPIC relocation: fix conflation of unconditional and conditional jumps.

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

Item was changed:
  ----- Method: CogAbstractInstruction>>instructionSizeAt: (in category 'disassembly') -----
  instructionSizeAt: pc
  	"Answer the instruction size at pc. This is used in method disassembly
  	 to decode the jumps in block dispatch to discover where block methods
  	 occur within a larger method."
+ 	^self subclassResponsibility!
- 	^4!

Item was added:
+ ----- Method: CogMIPSELCompiler>>instructionSizeAt: (in category 'disassembly') -----
+ instructionSizeAt: pc
+ 	"Answer the instruction size at pc."
+ 	^4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>isCallPrecedingReturnPC: (in category 'testing') -----
  isCallPrecedingReturnPC: mcpc
  	"Assuming mcpc is a send return pc answer if the instruction before it is a call (not a CallFull)."
  	"cogit disassembleFrom: mcpc - 8 to: mcpc."
  
  	(self opcodeAtAddress: mcpc - 8) = JAL ifTrue: [^true].
  	
  	((self opcodeAtAddress: mcpc - 8) = SPECIAL
+ 		and: [(self functionAtAddress: mcpc - 8) = JALR]) ifTrue: [^true].
- 		and: [(self opcodeAtAddress: mcpc - 8) = JALR]) ifTrue: [^true].
  	
  	^false!

Item was added:
+ ----- Method: CogMIPSELCompiler>>isJumpAt: (in category 'testing') -----
+ isJumpAt: pc
+ 	cogit disassembleFrom: pc to: pc + 4.
+ 
+ 	(self opcodeAtAddress: pc) = J ifTrue: [^true].
+ 	
+ 	(self opcodeAtAddress: pc) = SPECIAL ifTrue: [
+ 		(self functionAtAddress: pc) = JR ifTrue: [^true].
+ 	].
+ 
+ 	(self opcodeAtAddress: pc) = BEQ ifTrue: [^true].
+ 	(self opcodeAtAddress: pc) = BNE ifTrue: [^true].
+ 	(self opcodeAtAddress: pc) = BLEZ ifTrue: [^true].
+ 	(self opcodeAtAddress: pc) = BGTZ ifTrue: [^true].
+ 
+ 	(self opcodeAtAddress: pc) = REGIMM ifTrue: [
+ 		(self rtAtAddress: pc) = BLTZ ifTrue: [^true].
+ 		(self rtAtAddress: pc) = BGEZ ifTrue: [^true].
+ 	].	
+ 	
+ 	^false!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jumpTargetPCAt: (in category 'disassembly') -----
+ jumpTargetPCAt: pc
+ 	<returnTypeC: #usqInt>
+ 	"cogit disassembleFrom: pc to: pc + 4."
+ 	
+ 	(self opcodeAtAddress: pc) = J ifTrue: [^self targetFromJTypeAtAddress: pc].
+ 
+ 	(self opcodeAtAddress: pc) = BEQ ifTrue: [^self targetFromITypeAtAddress: pc].
+ 	(self opcodeAtAddress: pc) = BNE ifTrue: [^self targetFromITypeAtAddress: pc].
+ 	(self opcodeAtAddress: pc) = BLEZ ifTrue: [^self targetFromITypeAtAddress: pc].
+ 	(self opcodeAtAddress: pc) = BGTZ ifTrue: [^self targetFromITypeAtAddress: pc].
+ 	(self opcodeAtAddress: pc) = REGIMM ifTrue:
+ 		[(self rtAtAddress: pc) = BLTZ ifTrue: [^self targetFromITypeAtAddress: pc].
+ 		 (self rtAtAddress: pc) = BGEZ ifTrue: [^self targetFromITypeAtAddress: pc]].
+ 	
+ 	self unreachable.!

Item was added:
+ ----- Method: CogMIPSELCompiler>>relocateCallBeforeReturnPC:by: (in category 'inline cacheing') -----
+ relocateCallBeforeReturnPC: retpc by: delta
+ 	| target |
+ 	self assert: delta \\ 4 = 0.
+ 	delta = 0 ifTrue: [^self].
+ 	
+ 	self assert: (self opcodeAtAddress: retpc - 16) = LUI.
+ 	self assert: (self opcodeAtAddress: retpc - 12) = ORI.
+ 	self assert: (self opcodeAtAddress: retpc - 8) = SPECIAL.
+ 	self assert: (self functionAtAddress: retpc - 8) = JALR.
+ 	self assert: (objectMemory longAt: retpc - 4) = self nop.
+ 	"cogit disassembleFrom: retpc - 16 to: retpc."
+ 
+ 	target := self literalAtAddress: retpc - 12.
+ 	target := target + delta.
+ 	self literalAtAddress: retpc - 12 put: target.
+ 
+ 	self assert: (self opcodeAtAddress: retpc - 16) = LUI.
+ 	self assert: (self opcodeAtAddress: retpc - 12) = ORI.
+ 	self assert: (self opcodeAtAddress: retpc - 8) = SPECIAL.
+ 	self assert: (self functionAtAddress: retpc - 8) = JALR.
+ 	self assert: (objectMemory longAt: retpc - 4) = self nop.
+ 	"cogit disassembleFrom: retpc - 16 to: retpc."!

Item was added:
+ ----- Method: CogMIPSELCompiler>>relocateJumpLongBeforeFollowingAddress:by: (in category 'inline cacheing') -----
+ relocateJumpLongBeforeFollowingAddress: pc by: delta	
+ 	"lui t9, stub/targetHigh
+ 	 ori t9, t9, stub/targetLow
+ 	 jr t9
+ 	 nop (delay slot)
+ 	 ...  <-- pc"
+ 
+ 	| target |
+ 	self assert: delta \\ 4 = 0.
+ 	delta = 0 ifTrue: [^self].
+ 	
+ 	self assert: (self opcodeAtAddress: pc - 16) = LUI.
+ 	self assert: (self opcodeAtAddress: pc - 12) = ORI.
+ 	self assert: (self opcodeAtAddress: pc - 8) = SPECIAL.
+ 	self assert: (self functionAtAddress: pc - 8) = JR.
+ 	self assert: (objectMemory longAt: pc - 4) = self nop.
+ 	"cogit disassembleFrom: pc - 16 to: pc."
+ 
+ 	target := self literalAtAddress: pc - 12.
+ 	target := target + delta.
+ 	self literalAtAddress: pc - 12 put: pc.
+ 
+ 	self assert: (self opcodeAtAddress: pc - 16) = LUI.
+ 	self assert: (self opcodeAtAddress: pc - 12) = ORI.
+ 	self assert: (self opcodeAtAddress: pc - 8) = SPECIAL.
+ 	self assert: (self functionAtAddress: pc - 8) = JR.
+ 	self assert: (objectMemory longAt: pc - 4) = self nop.
+ 	"cogit disassembleFrom: pc - 16 to: pc."!

Item was added:
+ ----- Method: CogMIPSELCompiler>>relocateJumpLongConditionalBeforeFollowingAddress:by: (in category 'inline cacheing') -----
+ relocateJumpLongConditionalBeforeFollowingAddress: pc by: delta	
+ 	"lui t9, stub/targetHigh
+ 	 ori t9, t9, stub/targetLow
+ 	 jalr t9
+ 	 nop (delay slot)
+ 	 ...  <-- callSiteReturnAddress"
+ 
+ 	self assert: (self opcodeAtAddress: pc - 16) = BNE.
+ 	self assert: (objectMemory longAt: pc - 12) = self nop.
+ 	self assert: (self opcodeAtAddress: pc - 8) = J.
+ 	self assert: (objectMemory longAt: pc - 4) = self nop.
+ 	"cogit disassembleFrom: pc - 16 to: pc."
+ 	
+ 	self rewriteJTypeAtAddress: pc - 8 delta: delta.
+ 
+ 	self assert: (self opcodeAtAddress: pc - 16) = BNE.
+ 	self assert: (objectMemory longAt: pc - 12) = self nop.
+ 	self assert: (self opcodeAtAddress: pc - 8) = J.
+ 	self assert: (objectMemory longAt: pc - 4) = self nop.
+ 	"cogit disassembleFrom: pc - 16 to: pc."!

Item was changed:
  ----- Method: CogMIPSELCompiler>>relocateMethodReferenceBeforeAddress:by: (in category 'inline cacheing') -----
  relocateMethodReferenceBeforeAddress: pc by: delta
  	| oldValue newValue |
+ 	"cogit disassembleFrom: pc - 16 to: pc + 16 a StackToRegisterMappingCogit."
+ 	
+ 	((self opcodeAtAddress: pc - 8) = ADDIU and: [(self opcodeAtAddress: pc - 4) = SW]) ifTrue:
+ 		["PushCwR"
+ 		oldValue := self literalAtAddress: pc - 12.
+ 		newValue := oldValue + delta.
+ 		self literalAtAddress: pc - 12 put: newValue.	
+ 		self assert: (self literalAtAddress: pc - 12) = newValue.
+ 		^self].
- 	"cogit disassembleFrom: pc - 8 to: pc."
  
+ 	"MoveCwR"
  	oldValue := self literalAtAddress: pc - 4.
  	newValue := oldValue + delta.
  	self literalAtAddress: pc - 4 put: newValue.
  	
  	"cogit disassembleFrom: pc - 8 to: pc."
  	self assert: (self literalAtAddress: pc - 4) = newValue.
  	!

Item was changed:
  ----- Method: CogMIPSELCompiler>>rewriteInlineCacheAt:tag:target: (in category 'inline cacheing') -----
  rewriteInlineCacheAt: callSiteReturnAddress tag: cacheTag target: callTargetAddress
  	"Rewrite an inline cache to call a different target for a new tag.  This variant is used
  	 to link unlinked sends in ceSend:to:numArgs: et al.  Answer the extent of the code
  	 change which is used to compute the range of the icache to flush."
  	
  	"MoveCwR ClassReg selectorIndex/expectedClass
  	 Call: unlinked send stub/expectedTarget
  	 Push ReceiverResult <-- callSiteReturnAddress"
  	
  	"lui s3, selector/tagHigh
  	 ori s3, s3, selector/tagLow
  	 lui t9, stub/targetHigh
  	 ori t9, t9, stub/targetLow
  	 jalr t9
  	 nop (delay slot)
  	 ...  <-- callSiteReturnAddress"
  	
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 24) = LUI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 20) = ORI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
  	self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JALR.
  	self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
  	"cogit disassembleFrom: callSiteReturnAddress - 24 to: callSiteReturnAddress."
  
  	self literalAtAddress: callSiteReturnAddress - 20 put: cacheTag.
  	self literalAtAddress: callSiteReturnAddress - 12 put: callTargetAddress.
  
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 24) = LUI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 20) = ORI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
  	self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JALR.
  	self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
  	"cogit disassembleFrom: callSiteReturnAddress - 24 to: callSiteReturnAddress."
  
+ 	^24!
- 	^28!

Item was added:
+ ----- Method: CogMIPSELCompiler>>rewriteJTypeAtAddress:delta: (in category 'inline cacheing') -----
+ rewriteJTypeAtAddress: mcpc delta: delta
+ 	| target |
+ 	target := self targetFromJTypeAtAddress: mcpc.
+ 	target := target + delta.
+ 	self rewriteJTypeAtAddress: mcpc target: target.!

Item was changed:
  ----- Method: CogMIPSELCompiler>>rewriteJTypeAtAddress:target: (in category 'inline cacheing') -----
  rewriteJTypeAtAddress: mcpc target: newTarget
  	| regionMask |
+ 	self assert: (self opcodeAtAddress: mcpc) = J.
  	regionMask := 16rF0000000.
  	"mcpc + 4: relative to delay slot not j"
  	self assert: (mcpc + 4 bitAnd: regionMask) = (newTarget bitAnd: regionMask).
  	objectMemory longAt: mcpc put: (self jA: newTarget).!

Item was added:
+ ----- Method: CogMIPSELCompiler>>targetFromITypeAtAddress: (in category 'inline cacheing') -----
+ targetFromITypeAtAddress: mcpc
+ 	| offset |
+ 	offset := (objectMemory longAt: mcpc) bitAnd: 16rFFFF.
+ 	offset >= 16r8000 ifTrue: [offset := offset - 16r10000].
+ 	offset := offset << 2.
+ 	^mcpc + offset + OneInstruction. "Offset is relative to the delay slot"!

Item was changed:
  ----- Method: Cogit>>relocateCallsInClosedPIC: (in category 'compaction') -----
  relocateCallsInClosedPIC: cPIC
  	<var: #cPIC type: #'CogMethod *'>
  	| delta pc entryPoint targetMethod |
  	<var: #targetMethod type: #'CogMethod *'>
  	delta := cPIC objectHeader.
  	self assert: (backEnd callTargetFromReturnAddress: cPIC asInteger + missOffset)
  					= (self picAbortTrampolineFor: cPIC cmNumArgs).
  	backEnd relocateCallBeforeReturnPC: cPIC asInteger + missOffset by: delta negated.
  
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	1 to: cPIC cPICNumCases do:
  		[:i|
  		pc := self addressOfEndOfCase: i inCPIC: cPIC.
  		entryPoint := i = 1
  						ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
  						ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
  		"Find target from jump.  Ignore jumps to the interpret and MNU calls within this PIC"
  		(cPIC containsAddress: entryPoint) ifFalse:
  			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  			 self assert: targetMethod cmType = CMMethod.
+ 			 i = 1 ifTrue:
+ 				[backEnd
+ 					relocateJumpLongBeforeFollowingAddress: pc
+ 					by: (delta - targetMethod objectHeader) negated]
+ 				ifFalse:
+ 				[backEnd
+ 					relocateJumpLongConditionalBeforeFollowingAddress: pc
+ 					by: (delta - targetMethod objectHeader) negated]]].
- 			 backEnd
- 				relocateJumpLongBeforeFollowingAddress: pc
- 				by: (delta - targetMethod objectHeader) negated]].
  	self assert: cPIC cPICNumCases > 0.
  
  	"Finally relocate the load of the PIC and the jump to the overflow routine ceCPICMiss:receiver:"
  	backEnd relocateMethodReferenceBeforeAddress: (self addressOfEndOfCase: 2 inCPIC: cPIC)+ backEnd loadPICLiteralByteSize by: delta.
  	backEnd relocateJumpLongBeforeFollowingAddress: cPIC asInteger + cPICEndOfCodeOffset by: delta negated!



More information about the Vm-dev mailing list