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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 31 05:53:52 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1616
Author: rmacnak
Time: 30 December 2015, 9:52:25.92 pm
UUID: f9ab8d82-c5d7-4710-98be-572dd35495a9
Ancestors: VMMaker.oscog-cb.1615

MIPS: Implement I-cache flush with <asm/cachectl.h>.

Explicitly initialize scratch and floating point abstract registers to NoReg to make the translated VM compile again.

Use signed shift when generating I-type instructions.

=============== Diff against VMMaker.oscog-cb.1615 ===============

Item was removed:
- ----- Method: CogAbstractInstruction>>isLongJump (in category 'testing') -----
- isLongJump
- 	^opcode between: FirstJump and: FirstShortJump - 1!

Item was added:
+ ----- Method: CogMIPSELCompiler class>>declareCVarsIn: (in category 'translation') -----
+ declareCVarsIn: aCCodeGenerator
+ 	super declareCVarsIn: aCCodeGenerator.
+ 	aCCodeGenerator addHeaderFile: '<asm/cachectl.h>'. "For cacheflush"!

Item was changed:
  ----- Method: CogMIPSELCompiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
  	"See MIPSConstants>>initializeRegisters for a description of the C ABI."
  
  	"Note we can fit all of the abstract registers in C preserved registers, and
  	 not need to save or restore them at runtime calls."
- 	
  	super initializeAbstractRegisters.
  
  	ReceiverResultReg		:= S0.
  	Arg0Reg				:= S1.
  	Arg1Reg				:= S2.
  	ClassReg				:= S3.
  	SendNumArgsReg		:= S4.
  	TempReg				:= S5.
  	VarBaseReg			:= S6. "Must be callee saved"
  	SPReg					:= SP.
  	FPReg					:= FP.
  	RISCTempReg			:= AT.
+ 	LinkReg					:= RA.
+ 
+ 	self flag: #todo.
+ 	Scratch0Reg			:= NoReg.
+ 	Scratch1Reg			:= NoReg.
+ 	Scratch2Reg			:= NoReg.
+ 	Scratch3Reg			:= NoReg.
+ 	Scratch4Reg			:= NoReg.
+ 	Scratch5Reg			:= NoReg.
+ 	Scratch6Reg			:= NoReg.
+ 	Scratch7Reg			:= NoReg.
+ 
+ 	self flag: #todo.
+ 	DPFPReg0				:= NoReg.
+ 	DPFPReg1				:= NoReg.
+ 	DPFPReg2				:= NoReg.
+ 	DPFPReg3				:= NoReg.
+ 	DPFPReg4				:= NoReg.
+ 	DPFPReg5				:= NoReg.
+ 	DPFPReg6				:= NoReg.
+ 	DPFPReg7				:= NoReg.
+ 	DPFPReg8				:= NoReg.
+ 	DPFPReg9				:= NoReg.
+ 	DPFPReg10				:= NoReg.
+ 	DPFPReg11				:= NoReg.
+ 	DPFPReg12				:= NoReg.
+ 	DPFPReg13				:= NoReg.
+ 	DPFPReg14				:= NoReg.
+ 	DPFPReg15				:= NoReg.
+ 					
+ !
- 	LinkReg					:= RA!

Item was changed:
  ----- Method: CogMIPSELCompiler>>beqR:R:offset: (in category 'encoding - control') -----
  beqR: leftReg R: rightReg offset: offset
  	self assert: (offset bitAnd: 3) = 0.
  	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: BEQ rs: leftReg rt: rightReg signedImmediate: offset >>> 2!
- 	^self itype: BEQ rs: leftReg rt: rightReg signedImmediate: offset >> 2!

Item was changed:
  ----- Method: CogMIPSELCompiler>>bgezR:offset: (in category 'encoding - control') -----
  bgezR: cmpReg offset: offset
  	self assert: (offset bitAnd: 3) = 0.
  	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: REGIMM rs: cmpReg rt: BGEZ signedImmediate: offset >>> 2!
- 	^self itype: REGIMM rs: cmpReg rt: BGEZ signedImmediate: offset >> 2!

Item was changed:
  ----- Method: CogMIPSELCompiler>>bgtzR:offset: (in category 'encoding - control') -----
  bgtzR: cmpReg offset: offset
  	self assert: (offset bitAnd: 3) = 0.
  	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: BGTZ rs: cmpReg rt: 0 signedImmediate: offset >>> 2!
- 	^self itype: BGTZ rs: cmpReg rt: 0 signedImmediate: offset >> 2!

Item was changed:
  ----- Method: CogMIPSELCompiler>>blezR:offset: (in category 'encoding - control') -----
  blezR: cmpReg offset: offset
  	self assert: (offset bitAnd: 3) = 0.
  	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: BLEZ rs: cmpReg rt: 0 signedImmediate: offset >>> 2!
- 	^self itype: BLEZ rs: cmpReg rt: 0 signedImmediate: offset >> 2!

Item was changed:
  ----- Method: CogMIPSELCompiler>>bltzR:offset: (in category 'encoding - control') -----
  bltzR: cmpReg offset: offset
  	self assert: (offset bitAnd: 3) = 0.
  	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: REGIMM rs: cmpReg rt: BLTZ signedImmediate: offset >>> 2!
- 	^self itype: REGIMM rs: cmpReg rt: BLTZ signedImmediate: offset >> 2!

Item was changed:
  ----- Method: CogMIPSELCompiler>>bneR:R:offset: (in category 'encoding - control') -----
  bneR: leftReg R: rightReg offset: offset
  	self assert: (offset bitAnd: 3) = 0.
  	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: BNE rs: leftReg rt: rightReg signedImmediate: offset >>> 2!
- 	^self itype: BNE rs: leftReg rt: rightReg signedImmediate: offset >> 2!

Item was changed:
  ----- Method: CogMIPSELCompiler>>callerSavedRegisterMask (in category 'accessing') -----
  callerSavedRegisterMask
+ 	"Volatile"
  	"See MIPSConstants initializeRegisters."
  	self flag: #OABI.
  	^cogit
+ 		registerMaskFor: T0
+ 		and: T1
+ 		and: T2
+ 		and: T3
+ 		and: T4
+ 		and: T5
+ 		and: T6
+ 		and: T7
+ 		and: T8
+ 		and: T9!
- 		registerMaskFor: S0
- 		and: S1
- 		and: S2
- 		and: S3
- 		and: S4
- 		and: S5
- 		and: S6
- 		and: S7!

Item was changed:
  ----- Method: CogMIPSELCompiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
  flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
+ 	<cmacro: '(me,startAddress,endAddress) cacheflush((char*) startAddress, endAddress - startAddress, ICACHE)'>
+ 	"See http://www.linux-mips.org/wiki/Cacheflush_Syscall"
- 	<cmacro: '(me,startAddress,endAddress) __clear_cache((char*) startAddress, (char*) (endAddress ))'>
- 	"On ARM we almost certainly need to flush and wash hands. On linux we use __clear_cache (see http://community.arm.com/groups/processors/blog/2010/02/17/caches-and-self-modifying-code for a decent example) and remember that the end address is *exclusive* so we can just use the end address passed in since it is always the byte after the actual last one needing flushing"
  	self halt: #ceFlushICache!

Item was changed:
  ----- Method: CogMIPSELCompiler>>high16BitsOf: (in category 'encoding') -----
  high16BitsOf: word
+ 	<var: #word type: #usqInt>
  	^word >> 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>itype:rs:rt:eitherImmediate: (in category 'encoding') -----
+ itype: op rs: rs rt: rt eitherImmediate: immediate	
- itype: op rs: rs rt: rt eitherImmediate: signedImmediate	
- 	| unsignedImmediate |
  	self assert: (op between: 0 and: 63).
  	self assert: (rs between: 0 and: 31).
  	self assert: (rt between: 0 and: 31).
+ 	"signedImmediate < 0
- 	signedImmediate < 0
  		ifTrue: [unsignedImmediate := signedImmediate + 16r10000]
  		ifFalse: [unsignedImmediate := signedImmediate].
+ 	self assert: (unsignedImmediate between: 0 and: 16rFFFF)."
+ 	^(((op << 26) bitOr: (rs << 21)) bitOr: (rt << 16)) bitOr: (immediate bitAnd: 16rFFFF)!
- 	self assert: (unsignedImmediate between: 0 and: 16rFFFF).
- 	^(((op << 26) bitOr: (rs << 21)) bitOr: (rt << 16)) bitOr: unsignedImmediate!

Item was changed:
  ----- Method: CogMIPSELCompiler>>itype:rs:rt:signedImmediate: (in category 'encoding') -----
+ itype: op rs: rs rt: rt signedImmediate: immediate	
- itype: op rs: rs rt: rt signedImmediate: signedImmediate	
- 	| unsignedImmediate |
  	self assert: (op between: 0 and: 63).
  	self assert: (rs between: 0 and: 31).
  	self assert: (rt between: 0 and: 31).
+ 	self assert: (immediate between: -16r8000 and: 16r7FFF).
+ 	"signedImmediate < 0
- 	self assert: (signedImmediate between: -16r8000 and: 16r7FFF).
- 	signedImmediate < 0
  		ifTrue: [unsignedImmediate := signedImmediate + 16r10000]
  		ifFalse: [unsignedImmediate := signedImmediate].
+ 	self assert: (unsignedImmediate between: 0 and: 16rFFFF)."
+ 	^(((op << 26) bitOr: (rs << 21)) bitOr: (rt << 16)) bitOr: (immediate bitAnd: 16rFFFF)!
- 	self assert: (unsignedImmediate between: 0 and: 16rFFFF).
- 	^(((op << 26) bitOr: (rs << 21)) bitOr: (rt << 16)) bitOr: unsignedImmediate!

Item was changed:
  ----- Method: CogMIPSELCompiler>>literalAtAddress: (in category 'inline cacheing') -----
  literalAtAddress: mcpc
+ 	<var: #high type: #usqInt>
+ 	<var: #low type: #usqInt>
  	| high low |
  	self assert: (self opcodeAtAddress: mcpc) = ORI.
  	self assert: (self opcodeAtAddress: mcpc - 4) = LUI.
  	low := (objectMemory longAt: mcpc) bitAnd: 16rFFFF.
  	high := (objectMemory longAt: mcpc - 4) bitAnd: 16rFFFF.
  	^high << 16 bitOr: low
  !

Item was changed:
  ----- Method: CogMIPSELCompiler>>literalAtAddress:put: (in category 'inline cacheing') -----
  literalAtAddress: mcpc put: newLiteral
+ 	<var: #oldUpper type: #usqInt>
+ 	<var: #newUpper type: #usqInt>
+ 	<var: #oldLower type: #usqInt>
+ 	<var: #newLower type: #usqInt>
  	| oldUpper newUpper oldLower newLower |
  	self assert: (self opcodeAtAddress: mcpc - 4) = LUI.
  	self assert: (self opcodeAtAddress: mcpc) = ORI.
  	
  	oldUpper := objectMemory longAt: mcpc - 4.
  	newUpper := (oldUpper bitAnd: 16rFFFF0000) bitOr: (self high16BitsOf: newLiteral).
  	objectMemory longAt: mcpc - 4 put: newUpper.
  	
  	oldLower := objectMemory longAt: mcpc.
  	newLower := (oldLower bitAnd: 16rFFFF0000) bitOr: (self low16BitsOf: newLiteral).
  	objectMemory longAt: mcpc put: newLower.
  	
  	self assert: (self opcodeAtAddress: mcpc - 4) = LUI.
  	self assert: (self opcodeAtAddress: mcpc) = ORI.
  	
  	self assert: (self literalAtAddress: mcpc) = newLiteral.
  	
  	^newLiteral!

Item was changed:
  ----- Method: CogMIPSELCompiler>>low16BitsOf: (in category 'encoding') -----
  low16BitsOf: word
+ 	<var: #word type: #usqInt>
  	^word bitAnd: 16rFFFF!

Item was changed:
  ----- Method: CogMIPSELCompiler>>rewriteITypeBranchAtAddress:target: (in category 'inline cacheing') -----
  rewriteITypeBranchAtAddress: mcpc target: newTarget
  	| newDisplacement oldInstruction newInstruction |
  	newDisplacement := newTarget - (mcpc + 4). "Displacement is relative to delay slot."
+ 	newDisplacement := newDisplacement >>> 2. "Displacement is in words."
+ 	newDisplacement := (newDisplacement bitAnd: 16rFFFF).
- 	newDisplacement := newDisplacement >> 2. "Displacement is in words."
- 	
- 	self assert: (newDisplacement between: -16r8000 and: 16r7FFF).
- 	newDisplacement < 0
- 		ifTrue: [newDisplacement := newDisplacement + 16r10000]
- 		ifFalse: [newDisplacement := newDisplacement].
- 	self assert: (newDisplacement between: 0 and: 16rFFFF).
  
  	oldInstruction := objectMemory longAt: mcpc.
  	newInstruction := (oldInstruction bitAnd: 16rFFFF0000) bitOr: newDisplacement.
  	
  	objectMemory longAt: mcpc put: newInstruction.!

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

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

Item was added:
+ ----- Method: Cogit>>registerMaskFor:and:and:and:and:and:and:and:and:and: (in category 'register management') -----
+ registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9 and: reg10
+ 	^((((((((1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3) bitOr: 1 << reg4) bitOr: 1 << reg5) bitOr: 1 << reg6) bitOr: 1 << reg7) bitOr: 1 << reg8) bitOr: 1 << reg9) bitOr: 1 << reg10!



More information about the Vm-dev mailing list