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

commits at source.squeak.org commits at source.squeak.org
Sun Nov 15 23:55:10 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1520
Author: rmacnak
Time: 15 November 2015, 3:53:46.069 pm
UUID: 9198a43e-399e-42c8-9586-90f81ffa70cf
Ancestors: VMMaker.oscog-eem.1519

Get MIPSEL up to the first page fault accessing an interpreter variable.

Adjust CPIC verification to distinguish between conditional and uncondtional jumps.
Fix loading large literals.
Increase range of MwrR to support clever backwards use of base and offset in OPICs.

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

Item was added:
+ ----- Method: CogARMCompiler>>jumpLongConditionalTargetBeforeFollowingAddress: (in category 'inline cacheing') -----
+ jumpLongConditionalTargetBeforeFollowingAddress: mcpc
+ 	^self jumpLongTargetBeforeFollowingAddress: mcpc!

Item was added:
+ ----- Method: CogIA32Compiler>>jumpLongConditionalTargetBeforeFollowingAddress: (in category 'inline cacheing') -----
+ jumpLongConditionalTargetBeforeFollowingAddress: mcpc
+ 	^self jumpLongTargetBeforeFollowingAddress: mcpc !

Item was added:
+ ----- Method: CogMIPSELCompiler>>callTargetFromReturnAddress: (in category 'inline cacheing') -----
+ callTargetFromReturnAddress: callSiteReturnAddress
+ 	"csra - 16:	lui t9, high
+ 	 csra - 12:	ori t9, low
+ 	 csra - 8:	jalr t9
+ 	 csra - 4:	nop (delay slot)"
+ 	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. "Delay slot"
+ 	^self literalAtAddress: callSiteReturnAddress - 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAddCwR (in category 'generate machine code - concretize') -----
  concretizeAddCwR
  	| val reg |
  	val := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: val)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: val)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: val)).
  	self machineCodeAt: 8 put: (self adduR: reg R: reg R: AT).
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAndCqRR (in category 'generate machine code - concretize') -----
  concretizeAndCqRR
  	| value srcReg dstReg |
  	value := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	dstReg := self concreteRegister: (operands at: 2).
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: value)).
  	self machineCodeAt: 8 put: (self andR: dstReg R: srcReg R: AT).
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAndCwR (in category 'generate machine code - concretize') -----
  concretizeAndCwR
  	| value reg |
  	value := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: value)).
  	self machineCodeAt: 8 put: (self andR: reg R: reg R: AT).
  	self flag: #inefficient. "Cog RTL assumes we can do any kind of conditional branch after a Cmp."
  	self machineCodeAt: 12 put: (self andR: Cmp R: reg R: AT).
  	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeCallFull (in category 'generate machine code - concretize') -----
  concretizeCallFull
  	| jumpTarget |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := self longJumpTargetAddress.
  	self machineCodeAt: 0 put: (self luiR: TargetReg C: (self high16BitsOf: jumpTarget)).
+ 	self machineCodeAt: 4 put: (self oriR: TargetReg R: TargetReg C: (self low16BitsOf: jumpTarget)).	
- 	self machineCodeAt: 4 put: (self oriR: TargetReg R: ZR C: (self low16BitsOf: jumpTarget)).	
  	self machineCodeAt: 8 put: (self jalR: TargetReg).
  	self machineCodeAt: 12 put: self nop. "Delay slot"
  	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeCmpCwR (in category 'generate machine code - concretize') -----
  concretizeCmpCwR
  	| value reg |
  	value := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	self flag: #todo. "value - reg or reg - value?"
  	self flag: #inefficient. "Cog RTL assumes we can do any kind of conditional branch after a Cmp."
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: value)).
  	self machineCodeAt: 8 put: (self subuR: Cmp R: reg R: AT).
  	self machineCodeAt: 12 put: (self sltR: CmpSLT R: reg R: AT).
  	self machineCodeAt: 16 put: (self sltR: CmpSGT R: AT R: reg).
  	self machineCodeAt: 20 put: (self sltuR: CmpULT R: reg R: AT).
  	self machineCodeAt: 24 put: (self sltuR: CmpUGT R: AT R: reg).
  	^machineCodeSize := 28!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpFull (in category 'generate machine code - concretize') -----
  concretizeJumpFull
  	| jumpTarget |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := self longJumpTargetAddress.
  	self machineCodeAt: 0 put: (self luiR: TargetReg C: (self high16BitsOf: jumpTarget)).
+ 	self machineCodeAt: 4 put: (self oriR: TargetReg R: TargetReg C: (self low16BitsOf: jumpTarget)).	
- 	self machineCodeAt: 4 put: (self oriR: TargetReg R: ZR C: (self low16BitsOf: jumpTarget)).	
  	self machineCodeAt: 8 put: (self jR: TargetReg).
  	self machineCodeAt: 12 put: self nop. "Delay slot"
  	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveAwR (in category 'generate machine code - concretize') -----
  concretizeMoveAwR
  	| srcAddr destReg |
  	srcAddr := operands at: 0.
  	destReg := self concreteRegister: (operands at: 1).
  
  	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self lwR: destReg base: ConcreteVarBaseReg offset: srcAddr - cogit varBaseAddress).
  		 ^machineCodeSize := 4].
  
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: srcAddr)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: srcAddr)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: srcAddr)).
  	self machineCodeAt: 8 put: (self lwR: destReg base: AT offset: 0).
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveCwR (in category 'generate machine code - concretize') -----
  concretizeMoveCwR
  	<var: #word type: #sqInt>
  	| word reg |
  	word := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).	
  	self machineCodeAt: 0 put: (self luiR: reg C: (self high16BitsOf: word)).
+ 	self machineCodeAt: 4 put: (self oriR: reg R: reg C: (self low16BitsOf: word)).
- 	self machineCodeAt: 4 put: (self oriR: reg R: ZR C: (self low16BitsOf: word)).
  	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveMwrR (in category 'generate machine code - concretize') -----
  concretizeMoveMwrR
  	<var: #offset type: #sqInt>
  	| baseReg offset destReg |
  	offset := operands at: 0.
  	baseReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
+ 	(self isShortOffset: offset) ifTrue:
+ 		[self machineCodeAt: 0 put: (self lwR: destReg base: baseReg offset: offset).
+ 		^machineCodeSize := 4].
+ 	
+ 	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: offset)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: offset)).
+ 	self machineCodeAt: 8 put: (self adduR: AT R: baseReg R: ZR).
+ 	self machineCodeAt: 0 put: (self lwR: destReg base: AT offset: 0).
+ 	^machineCodeSize := 4.
+ !
- 	self machineCodeAt: 0 put: (self lwR: destReg base: baseReg offset: offset).
- 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
  concretizeMoveRAw
  	| srcReg destAddr |
  	srcReg := self concreteRegister: (operands at: 0).
  	destAddr := operands at: 1.
  
  	(self isAddressRelativeToVarBase: destAddr) ifTrue:
  		[self machineCodeAt: 0 put: (self swR: srcReg base: ConcreteVarBaseReg offset: destAddr - cogit varBaseAddress).
  		 ^machineCodeSize := 4].
  
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: destAddr)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: destAddr)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: destAddr)).
  	self machineCodeAt: 8 put: (self swR: srcReg base: AT offset: 0).
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeOrCwR (in category 'generate machine code - concretize') -----
  concretizeOrCwR
  	| value reg |
  	value := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: value)).
  	self machineCodeAt: 8 put: (self orR: reg R: reg R: AT).
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeSubCwR (in category 'generate machine code - concretize') -----
  concretizeSubCwR
  	| value reg |
  	value := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: value)).
  	self machineCodeAt: 8 put: (self subuR: reg R: reg R: AT).
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeTstCwR (in category 'generate machine code - concretize') -----
  concretizeTstCwR
  	| val reg |
  	val := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: val)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: val)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: val)).
  	self machineCodeAt: 8 put: (self andR: Cmp R: reg R: AT).
  	^machineCodeSize := 12!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeXorCwR (in category 'generate machine code - concretize') -----
+ concretizeXorCwR
+ 	| val reg |
+ 	val := operands at: 0.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: val)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: val)).
+ 	self machineCodeAt: 8 put: (self xorR: reg R: reg R: AT).
+ 	^machineCodeSize := 12!

Item was added:
+ ----- Method: CogMIPSELCompiler>>isShortOffset: (in category 'accessing') -----
+ isShortOffset: offset
+ 	^offset between: -16r8000 and: 16r7FFF!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jumpLongConditionalTargetBeforeFollowingAddress: (in category 'inline cacheing') -----
+ jumpLongConditionalTargetBeforeFollowingAddress: mcpc
+ 	Transcript nextPutAll: mcpc hex; cr.
+ 	"mcpc - 16:	beq/ne Cmp, ZR, +12
+ 	 mcpc - 12:	nop (delay slot)
+ 	 mcpc - 8:	j psuedo-address
+ 	 mcpc - 4:	nop (delay slot)"		
+ 	self assert: (((self opcodeAtAddress: mcpc - 16) == BEQ) 
+ 				or: [(self opcodeAtAddress: mcpc - 16) == BNE]).
+ 	self assert: (objectMemory longAt: mcpc - 12) == self nop. "Delay slot"
+ 	self assert: (self opcodeAtAddress: mcpc - 8) == J.
+ 	self assert: (objectMemory longAt: mcpc - 4) == self nop. "Delay slot"
+ 	^self targetFromJTypeAtAddress: mcpc - 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>jumpLongTargetBeforeFollowingAddress: (in category 'inline cacheing') -----
  jumpLongTargetBeforeFollowingAddress: mcpc 
  	"Answer the target address for the long jump immediately preceding mcpc"
  	self assert: (objectMemory longAt: mcpc - 4) == self nop. "Delay slot"
  	self assert: (self opcodeAtAddress: mcpc - 8) == SPECIAL.
  	self assert: (self functionAtAddress: mcpc - 8) == JR.
  	^self literalAtAddress: mcpc - 12
  	!

Item was added:
+ ----- Method: CogMIPSELCompiler>>literalAtAddress:put: (in category 'inline cacheing') -----
+ literalAtAddress: mcpc put: newLiteral
+ 	| instruction |
+ 	self assert: (self opcodeAtAddress: mcpc) = ORI.
+ 	self assert: (self opcodeAtAddress: mcpc - 4) = LUI.
+ 	
+ 	instruction := (objectMemory longAt: mcpc) bitAnd: 16rFFFF000.
+ 	instruction := instruction bitOr: (self low16BitsOf: newLiteral).
+ 	objectMemory longAt: mcpc put: instruction.
+ 
+ 	instruction := (objectMemory longAt: mcpc - 4) bitAnd: 16rFFFF000.
+ 	instruction := instruction bitOr: (self high16BitsOf: newLiteral).
+ 	objectMemory longAt: mcpc put: instruction.
+ 	
+ 	^newLiteral!

Item was changed:
  ----- Method: CogMIPSELCompiler>>literalBeforeFollowingAddress: (in category 'inline cacheing') -----
  literalBeforeFollowingAddress: followingAddress
  	"Answer the literal embedded in the instruction immediately preceding followingAddress.
  	 This is used in the MoveCwR, PushCwR and CmpCwR cases."
  	
  	"lui/ori, lui/ori/sw/addi, lui/ori/subu/slt/slt/sltu/sltu"
  	
+ 	| lastOpcode lastFunction oriAddress |
+ 	lastOpcode := self opcodeAtAddress: followingAddress - 4.
+ 	lastFunction := self functionAtAddress: followingAddress - 4.
- 	| lastInstruction lastOpcode lastFunction oriAddress |
- 	lastInstruction := objectMemory longAt: followingAddress - 4.
- 	lastOpcode := lastInstruction >> 26.
- 	lastFunction := lastInstruction bitAnd: 63.
  	oriAddress := 0.
  	lastOpcode = ORI ifTrue: [oriAddress := followingAddress - 4].
  	lastOpcode = ADDIU ifTrue: [oriAddress := followingAddress - 16].
  	(lastOpcode = SPECIAL and: [lastFunction = SLTU]) ifTrue: [oriAddress := followingAddress - 24].
  	self assert: oriAddress ~= 0.
  	^self literalAtAddress: oriAddress
  !

Item was added:
+ ----- Method: CogMIPSELCompiler>>machineCodeBytes (in category 'generate machine code') -----
+ machineCodeBytes
+ 	^self machineCodeWords * 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>machineCodeWords (in category 'generate machine code') -----
  machineCodeWords
  	"Answer the maximum number of words of machine code generated for any abstract instruction.
  	 e.g. CmpCwR =>
+ 			lui at, <high>
+ 			ori at, <low>
+ 			subu Cmp, reg, at
+ 			slt CmpSLT, reg, at
+ 			slt CmpSGT, reg, at
+ 			slt CmpULT, reg, at
+ 			slt CmpUGT, reg, at"
+ 	self flag: #inefficient.
- 			mov R3, #<addressByte1>, 12
- 			orr R3, R3, #<addressByte2>, 8
- 			orr R3, R3, #<addressByte3>, 4
- 			orr R3, R3, #<addressByte4>, 0
- 			cmp R?, R3"
  	^7!

Item was added:
+ ----- Method: CogMIPSELCompiler>>padIfPossibleWithNopsFrom:to: (in category 'generate machine code') -----
+ padIfPossibleWithNopsFrom: startAddr to: endAddr
+ 	self flag: #bogus. "Methods should be initialized with the stop instruction, not nop."
+ 
+ 	startAddr to: endAddr - 1 by: 4 do: 
+ 		[:addr | objectMemory longAt: addr put: self stop].!

Item was added:
+ ----- Method: CogMIPSELCompiler>>storeLiteral:beforeFollowingAddress: (in category 'inline cacheing') -----
+ storeLiteral: literal beforeFollowingAddress: followingAddress
+ 	"Rewrite the long constant loaded by a MoveCwR or PushCwR before the given address"
+ 	| lastOpcode oriAddress |
+ 	
+ 	self flag: #bogus. "The caller ought to know what it is patching, and this should be split into separate methods with stricter checking."
+ 	
+ 	lastOpcode := self opcodeAtAddress: followingAddress - 4.
+ 	oriAddress := 0.
+ 	lastOpcode = ORI ifTrue: [oriAddress := followingAddress - 4].
+ 	lastOpcode = ADDIU ifTrue: [oriAddress := followingAddress - 16].
+ 	self assert: oriAddress ~= 0.
+ 	^self literalAtAddress: oriAddress put: literal!

Item was added:
+ ----- Method: CogMIPSELCompiler>>targetFromJTypeAtAddress: (in category 'inline cacheing') -----
+ targetFromJTypeAtAddress: mcpc
+ 	| targetLow |
+ 	targetLow := (objectMemory longAt: mcpc) bitAnd: 16r3FFFFFF.
+ 	"mcpc + 4: relative to delay slot not j"
+ 	^((mcpc + 4) bitAnd: 16rF0000000) + (targetLow << 2) !

Item was changed:
  ----- Method: Cogit>>expectedClosedPICPrototype: (in category 'garbage collection') -----
  expectedClosedPICPrototype: cPIC
  	"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 offsetToLiteral object entryPoint |
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	"First jump is unconditional; subsequent ones are conditional"
  	offsetToLiteral := backEnd jumpLongByteSize.
+ 	
+ 	object := literalsManager objRefInClosedPICAt: pc - offsetToLiteral.
+ 	self assert: (object = 16r5EAF00D).
+ 
+ 	entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc.
+ 	self assert: (entryPoint = (self cPICPrototypeCaseOffset + 16rCA5E10)).
+ 
+ 	1 to: maxCPICCases - 1 do:
+ 		[:i |
+ 		pc := pc + cPICCaseSize.
- 	1 to: maxCPICCases do:
- 		[:i|
- 		i > 1 ifTrue:
- 			[object := literalsManager classRefInClosedPICAt: pc - offsetToLiteral.
- 			 object = (16rBABE1F15 + i - 1) ifFalse:
- 				[^1]].
- 		object := literalsManager objRefInClosedPICAt: pc - offsetToLiteral.
- 		object = (i = 1
- 					ifTrue: [16r5EAF00D]
- 					ifFalse: [16rBADA550 + i - 1]) ifFalse:
- 			[^2].
  		offsetToLiteral := backEnd jumpLongConditionalByteSize.
+ 				
+ 		object := literalsManager classRefInClosedPICAt: pc - offsetToLiteral.
+ 		self assert: (object = (16rBABE1F15 + i)).
+ 
+ 		object := literalsManager objRefInClosedPICAt: pc - offsetToLiteral.
+ 		self assert: (object = (16rBADA550 + i)).
+ 
+ 		entryPoint := backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc.
+ 		self assert: (entryPoint = (self cPICPrototypeCaseOffset + 16rCA5E10 + (i * 16)))].
+ 
- 		entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc.
- 		entryPoint = (self cPICPrototypeCaseOffset + 16rCA5E10 + (i - 1 * 16)) ifFalse:
- 				[^3].
- 		pc := pc + cPICCaseSize].
- 	pc := pc - cPICCaseSize.
  	entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc + cPICEndSize - literalsManager endSizeOffset.
+ 	self assert: (entryPoint = (self cPICMissTrampolineFor: 0)).
+ 	
- 	entryPoint = (self cPICMissTrampolineFor: 0) ifFalse:
- 		[^4].
  	^0!



More information about the Vm-dev mailing list