[Vm-dev] VM Maker: VMMaker.oscog-tpr.1277.mcz

commits at source.squeak.org commits at source.squeak.org
Sun May 3 03:17:23 UTC 2015


tim Rowledge uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-tpr.1277.mcz

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

Name: VMMaker.oscog-tpr.1277
Author: tpr
Time: 2 May 2015, 8:16:00.792 pm
UUID: 433ce7ae-ccd7-4fa6-9c51-66b9feebe3ac
Ancestors: VMMaker.oscog-eem.1276

Some cleanups to make C happy(er). Some type stuff, some confusing names choices altered, some junk cleaned out.

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

Item was added:
+ ----- Method: CoInterpreter>>varBaseAddress (in category 'cog jit support') -----
+ varBaseAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^(self addressOf: stackPointer) asUnsignedInteger - 16r42!

Item was changed:
  ----- Method: CogARMCompiler>>at:moveCw:intoR: (in category 'generate machine code - support') -----
  at: offset moveCw: constant intoR: destReg
  	"This loads aWord into the inter-opcode temporary register. Because most ARM instruction enable using a (8-12bit) offset relative to a register, the LS Byte can be included in that instruction, saving one instruction. This is done in a decorator, e.g. CmpCqR"
  	"Generates:along the lines of
  	MOV destReg, #<constantByte3>, 12
  	ORR destReg, destReg, #<constantByte2>, 8
  	ORR destReg, destReg, #<constantByte1>, 4
  	ORR destReg, destReg, #<constantByte0>, 0
  	with minimal choice of the rotation (last digit)"
  	"The same area can be modified multiple times, because the opperation is (inclusive) or."
+ 	 <var: 'constant' type: #usqInt>
  	<inline: true>
  	"self assert: destReg < 12."
  
  	self machineCodeAt: offset put: (self mov: destReg imm: (constant >>24 bitAnd: 16rFF) ror: 8).
  	self machineCodeAt: offset +4 put: (self orr: destReg imm: (constant >> 16 bitAnd: 16rFF) ror: 16).
  	self machineCodeAt: offset +8 put: (self orr: destReg imm: (constant >> 8 bitAnd: 16rFF) ror: 24).
  	self machineCodeAt: offset +12 put: (self orr: destReg imm: (constant bitAnd: 16rFF) ror: 0).
  	^16!

Item was removed:
- ----- Method: CogARMCompiler>>condition (in category 'accessing') -----
- condition
- 	^conditionOrNil!

Item was removed:
- ----- Method: CogARMCompiler>>condition: (in category 'accessing') -----
- condition: condCode
- 	^conditionOrNil := condCode!

Item was added:
+ ----- Method: CogARMCompiler>>conditionOrNil (in category 'accessing') -----
+ conditionOrNil
+ "has to be named oddly like this to satisfay i-var code gen translating rules"
+ 	^conditionOrNil!

Item was added:
+ ----- Method: CogARMCompiler>>conditionOrNil: (in category 'accessing') -----
+ conditionOrNil: condCode
+ "has to be named oddly like this to satisfay i-var code gen translating rules"
+ 	^conditionOrNil := condCode!

Item was changed:
  ----- Method: CogARMCompiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	<returnTypeC: #void>
  	conditionOrNil ifNotNil:
  		[self concretizeConditionalInstruction.
  		 ^self].
  		 
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^self concretizeLabel].
  		[AlignmentNops]		-> [^self concretizeAlignmentNops].
  		[Fill16]					-> [^self concretizeFill16].
  		[Fill32]					-> [^self concretizeFill32].
  		[FillFromWord]			-> [^self concretizeFillFromWord].
  		[Nop]					-> [^self concretizeNop].
  		"ARM Specific Control/Data Movement" 
- 		[LDMFD]				-> [^self concretizeLDMFD].
- 		[STMFD]				-> [^self concretizeSTMFD].
  		[SMULL]				-> [^self concretizeSMULL]	.
  		[CMPSMULL]				-> [^self concretizeCMPSMULL].
  		[MSR]						-> [^self concretizeMSR].
  		[BICCqR]					-> [^self concretizeDataOperationCqR: BicOpcode].
  		"Control"
  		[Call]						-> [^self concretizeCall]. "call code within code space"
  		[CallFull]					-> [^self concretizeCallFull]. "call code anywhere in address space"
  		[JumpR]						-> [^self concretizeJumpR].
  		[JumpFull]					-> [^self concretizeJumpFull]."jump within address space"
  		[JumpLong]					-> [^self concretizeConditionalJump: AL]."jumps witihn code space"
  		[JumpLongZero]			-> [^self concretizeConditionalJump: EQ].
  		[JumpLongNonZero]		-> [^self concretizeConditionalJump: NE].
  		[Jump]						-> [^self concretizeConditionalJump: AL].
  		[JumpZero]					-> [^self concretizeConditionalJump: EQ].
  		[JumpNonZero]				-> [^self concretizeConditionalJump: NE].
  		[JumpNegative]				-> [^self concretizeConditionalJump: MI].
  		[JumpNonNegative]			-> [^self concretizeConditionalJump: PL].
  		[JumpOverflow]				-> [^self concretizeConditionalJump: VS].
  		[JumpNoOverflow]			-> [^self concretizeConditionalJump: VC].
  		[JumpCarry]				-> [^self concretizeConditionalJump: CS].
  		[JumpNoCarry]				-> [^self concretizeConditionalJump: CC].
  		[JumpLess]					-> [^self concretizeConditionalJump: LT].
  		[JumpGreaterOrEqual]		-> [^self concretizeConditionalJump: GE].
  		[JumpGreater]				-> [^self concretizeConditionalJump: GT].
  		[JumpLessOrEqual]			-> [^self concretizeConditionalJump: LE].
  		[JumpBelow]				-> [^self concretizeConditionalJump: CC]. "unsigned lower"
  		[JumpAboveOrEqual]		-> [^self concretizeConditionalJump: CS]. "unsigned greater or equal"
  		[JumpAbove]				-> [^self concretizeConditionalJump: HI].
  		[JumpBelowOrEqual]		-> [^self concretizeConditionalJump: LS].
  		[JumpFPEqual]				-> [^self concretizeFPConditionalJump: EQ].
  		[JumpFPNotEqual]			-> [^self concretizeFPConditionalJump: NE].
  		[JumpFPLess]				-> [^self concretizeFPConditionalJump: LT].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeFPConditionalJump: GE].
  		[JumpFPGreater]			-> [^self concretizeFPConditionalJump: GT].
  		[JumpFPLessOrEqual]		-> [^self concretizeFPConditionalJump: LE].
  		[JumpFPOrdered]			-> [^self concretizeFPConditionalJump: VC].
  		[JumpFPUnordered]			-> [^self concretizeFPConditionalJump: VS].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AddCwR]					-> [^self concretizeDataOperationCwR: AddOpcode].
  		[AddRR]						-> [^self concretizeDataOperationRR: AddOpcode].
  		[AddRdRd]					-> [^self concretizeAddRdRd].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCqRR]					-> [^self concretizeAndCqRR].
  		[AndCwR]					-> [^self concretizeDataOperationCwR: AndOpcode].
  		[AndRR]						-> [^self concretizeDataOperationRR: AndOpcode].
  		[CmpCqR]					-> [^self concretizeDataOperationCqR: CmpOpcode].
  		[CmpCwR]					-> [^self concretizeDataOperationCwR: CmpOpcode].
  		[CmpRR]					-> [^self concretizeDataOperationRR: CmpOpcode].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[DivRdRd]					-> [^self concretizeDivRdRd].
  		[MulRdRd]					-> [^self concretizeMulRdRd].
  		[OrCqR]						-> [^self concretizeDataOperationCqR: OrOpcode].
  		[OrCwR]					-> [^self concretizeDataOperationCwR: OrOpcode].
  		[OrRR]						-> [^self concretizeDataOperationRR: OrOpcode].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeDataOperationCwR: SubOpcode].
  		[SubRR]						-> [^self concretizeDataOperationRR: SubOpcode].
  		[SubRdRd]					-> [^self concretizeSubRdRd].
  		[SqrtRd]					-> [^self concretizeSqrtRd].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[XorCqR]						-> [^self concretizeDataOperationCqR: XorOpcode].
  		[XorCwR]						-> [^self concretizeDataOperationCwR: XorOpcode].
  		[XorRR]							-> [^self concretizeDataOperationRR: XorOpcode].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[LogicalShiftRightRR]			-> [^self concretizeLogicalShiftRightRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd]}!

Item was changed:
  ----- Method: CogARMCompiler>>extractOffsetFromBL: (in category 'testing') -----
  extractOffsetFromBL: instr
  	"we are told this is a BL <offset> instruction, so work out the offset it encodes"
  	<inline: true>
  	| relativeJump |
  	relativeJump := instr bitAnd: 16r00FFFFFF.
+ 	relativeJump := ((relativeJump bitAnd: 1<<24) >> 24) = 1
- 	relativeJump := (relativeJump bitAt: 24) = 1 
  						ifTrue: [((relativeJump bitOr: 16r3F000000) << 2) signedIntFromLong]
  						ifFalse: [relativeJump << 2].
  	^relativeJump!

Item was added:
+ ----- Method: CogARMCompiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
+ flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
+ 	<cmacro: '(me,startAddress,endAddress) __clear_cache((char*) startAddress, (char*) (endAddress + 4))'>
+ 	"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 add 4 for now"
+ 	self halt: #ceFlushICache!

Item was added:
+ ----- Method: CogARMCompiler>>genDivR:R:Quo:Rem: (in category 'abstract instructions') -----
+ genDivR: abstractRegDivisor R: abstractRegDividend Quo: abstractRegQuotient Rem: abstractRegRemainder
+ "Currently no instruction level support for divide on ARM. See also #canDivQuoRem"!

Item was added:
+ ----- Method: CogARMCompiler>>genRestoreRegsExcept: (in category 'abi') -----
+ genRestoreRegsExcept: abstractReg
+ 	"Restore the general purpose registers except for abstractReg for a trampoline call."
+ 	"Restore none, because the ARM ABI only defines callee saved registers, no caller-saved regs."
+ !

Item was removed:
- ----- Method: CogARMCompiler>>isBranch: (in category 'testing') -----
- isBranch: anInstruction
- 
- 	^ (anInstruction >> 24 bitAnd: 16r0E) = 16rA!

Item was added:
+ ----- Method: CogARMCompiler>>numICacheFlushOpcodes (in category 'inline cacheing') -----
+ numICacheFlushOpcodes
+ 	"ARM needs to do icache flushing when code is written"
+ 	"for now return 0 to skip it and probably blow up"
+ 	^0
+ 	!

Item was added:
+ ----- Method: CogARMCompiler>>storeLiteral:beforeFollowingAddress: (in category 'inline cacheing') -----
+ storeLiteral: literal beforeFollowingAddress: followingAddress
+ 	"Rewrite the long constant loaded by a MOV/ORR/ORR/ORR
+ 	 or MOV/ORR/ORR/ORR/PUSH  sequence, just before this address:"
+ 	^(self instructionIsOR: (self instructionBeforeAddress: followingAddress))
+ 		ifTrue: [self insert32BitOperand: literal into4InstructionsPreceeding: followingAddress]
+ 		ifFalse: [self insert32BitOperand: literal into4InstructionsPreceeding: followingAddress - 4]!

Item was changed:
  ----- Method: CogARMCompiler>>wantsNearAddressFor: (in category 'simulation') -----
  wantsNearAddressFor: anObject
  	"A hack hook to allow ARM to override the simulated address for the short-cut trampolines"
+ 	<doNotGenerate>
  	^anObject isSymbol and: [anObject beginsWith: 'ceShortCut']!



More information about the Vm-dev mailing list