[Vm-dev] VM Maker: VMMaker.oscog-lw.185.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jul 17 20:40:27 UTC 2012


Lars Wassermann uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-lw.185.mcz

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

Name: VMMaker.oscog-lw.185
Author: lw
Time: 17 July 2012, 10:38:20.729 pm
UUID: 6f27e321-2227-2540-8b08-0e6a2cea3a99
Ancestors: VMMaker.oscog-eem.184

Added multiple functions which are called when starting the simulator. The simulator still does require more methods.

Pulled up genAlignCStackSavingRegisters:numArgs:wordAlignment:,
because the ARMCompiler implementation would have been the same except for the constant. Added that constant as NumberOfRegisters to AbstractInstruction.

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

Item was added:
+ CogAbstractInstruction subclass: #CogARMCompiler
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'LR PC R0 R1 R10 R11 R12 R2 R3 R4 R5 R6 R7 R8 R9 SP'
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogARMCompiler class>>initialize (in category 'class initialization') -----
+ initialize
+ 	super initialize.
+ 	
+ 	"Initialize various ARM instruction-related constants."
+ 	"CogARMCompiler initialize"
+ 	
+ 	R0 := 0. R1 := 1.
+ 	R2 := 2. R3 := 3.
+ 	R4 := 4. R5 := 5.
+ 	R6 := 6. R7 := 7.
+ 	R8 := 8. R9 := 9.
+ 	R10 := 10. R11 := 11.
+ 	R12 := 12.
+ 	SP := 13.
+ 	LR := 14.
+ 	PC := 15.
+ 	
+ 	MachineCodeSize := 16. "atm: MoveRAw"
+ 	NumberOfRegisters := 16.!

Item was added:
+ ----- Method: CogARMCompiler>>computeMaximumSize (in category 'generate machine code') -----
+ computeMaximumSize
+ 	"Because we don't use Thumb, each instruction has a multiple of 4 bytes. Most have exactly 4, but some abstract opcodes need more than one instruction."
+ 	opcode 
+ 		caseOf: {
+ 			[Label]				-> [^maxSize := 0].
+ 			[AlignmentNops]	-> [^maxSize := (operands at: 0) - 1].
+ 			[MoveRAw]			-> [^maxSize := 16 "3 for loadAllButLSB"].
+ 			[RetN]				-> [^(operands at: 0) = 0 
+ 										ifTrue: [maxSize := 4]
+ 										ifFalse: [maxSize := 8]]} 
+ 		otherwise: [^maxSize := 4].
+ 	^4 "to keep C compiler quiet"
+ !

Item was added:
+ ----- Method: CogARMCompiler>>concreteRegister: (in category 'encoding') -----
+ concreteRegister: registerIndex
+ 	 "Map a possibly abstract register into a concrete one.  Abstract registers
+ 	  (defined in CogAbstractOpcodes) are all negative.  If registerIndex is
+ 	 negative assume it is an abstract register."
+ 	
+ 	"N.B. According to BSABI, R0-R3 are caller-save, R4-R12 are callee save.
+ 	Note that R9 might be a special register for the implementation. In some slides it is refered to as sb. R10 contains the stack limit (sl), R11 the fp. R12 is an intra-procedure scratch instruction pointer for link purposes.
+ 	R3 is used as temporary inside a single abstract opcode implementation"
+ 
+ 	^registerIndex
+ 		caseOf: {
+ 			[TempReg]				-> [R0].
+ 			[ClassReg]				-> [R1].
+ 			[ReceiverResultReg]	-> [R2].
+ 			[SendNumArgsReg]		-> [R6].
+ 			[SPReg]					-> [SP].
+ 			[FPReg]					-> [R11].
+ 			[Arg0Reg]				-> [R4].
+ 			[Arg1Reg]				-> [R5] }
+ 		otherwise:
+ 			[self assert: (registerIndex between: R0 and: PC).
+ 			 registerIndex]!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeAt: (in category 'generate machine code') -----
+ concretizeAt: actualAddress
+ 	"Attempt to generate concrete machine code for the instruction at address.
+ 	 If possible, generate the relevant machine code, setting machineCodeSize,
+ 	 and answer the following address.  Otherwise answer -1."
+ 
+ 	self assert: actualAddress \\ 4 = 0.
+ 	address := actualAddress.
+ 	self dispatchConcretize.
+ 	self assert: (maxSize = nil or: [maxSize >= machineCodeSize]).
+ 	^actualAddress + machineCodeSize!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
+ concretizeMoveRAw
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg destAddr loadSize |
+ 	srcReg := self concreteRegister: (operands at: 0).
+ 	destAddr := operands at: 1.
+ 	"load the address into R3"
+ 	loadSize := self loadAllButLSBWord: destAddr.
+ 	machineCode 
+ 		at: loadSize + 3 put: 16rE5; "STR srcReg, [R3, +LSB(addr)]"
+ 		at: loadSize + 2 put: 16r83;
+ 		at: loadSize + 1 put: (srcReg << 4);
+ 		at: loadSize put: (destAddr bitAnd: 16rFF).
+ 	^machineCodeSize := loadSize + 4!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeMoveRR (in category 'generate machine code - concretize') -----
+ concretizeMoveRR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg destReg |
+ 	srcReg := self concreteRegister: (operands at: 0).
+ 	destReg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: 16rE1A0F00F.
+ 	machineCode
+ 		at: 1 put: (16rF0 bitAnd: destReg << 4);
+ 		at: 0 put: (16r0F bitAnd: srcReg).
+ 	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeRetN (in category 'generate machine code - concretize') -----
+ concretizeRetN
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| offset |
+ 	offset := operands at: 0.
+ 	offset = 0 ifTrue:
+ 		[self machineCodeAt: 0 put: 16rE8BD8000. "pop	{pc}"
+ 		^machineCodeSize := 4].
+ 	self assert: offset < 32. "We have an 8 bit immediate. If needed, we could rotate it less than 30 bit."
+ 	self machineCodeAt: 0 put: 16rE28DDFFF. "add sp, sp, #n, 14"
+ 	machineCode
+ 		at: 0 put: offset. "no bit-mask needed, because of the assert"
+ 	self machineCodeAt: 4 put: 16rE8BD8000.  "pop	{pc}"
+ 	^machineCodeSize := 8!

Item was added:
+ ----- 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."
+ 
+ 	opcode caseOf: {
+ 		"Noops & Pseudo Ops"
+ 		[Label]					-> [^self concretizeLabel].
+ 		[AlignmentNops]		-> [^self concretizeAlignmentNops].
+ 		[Fill16]					-> [^self concretizeFill16].
+ 		[Fill32]					-> [^self concretizeFill32].
+ 		[FillFromWord]			-> [^self concretizeFillFromWord].
+ 		[Nop]					-> [^self concretizeNop].
+ 		"Specific Control/Data Movement"
+ 		"[CDQ]					-> [^self concretizeCDQ].
+ 		[IDIVR]					-> [^self concretizeIDIVR].
+ 		[IMULRR]				-> [^self concretizeMulRR].
+ 		[CPUID]					-> [^self concretizeCPUID].
+ 		[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR].
+ 		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR].
+ 		[LFENCE]				-> [^self concretizeFENCE: 5].
+ 		[MFENCE]				-> [^self concretizeFENCE: 6].
+ 		[SFENCE]				-> [^self concretizeFENCE: 7].
+ 		[LOCK]					-> [^self concretizeLOCK].
+ 		[XCHGAwR]				-> [^self concretizeXCHGAwR].
+ 		[XCHGMwrR]			-> [^self concretizeXCHGMwrR].
+ 		[XCHGRR]				-> [^self concretizeXCHGRR]."
+ 		"Control"
+ 		[Call]					-> [^self concretizeCall].
+ 		[JumpR]					-> [^self concretizeJumpR].
+ 		[JumpLong]				-> [^self concretizeJumpLong].
+ 		[JumpLongZero]		-> [^self concretizeConditionalJumpLong: 16r4].
+ 		[JumpLongNonZero]	-> [^self concretizeConditionalJumpLong: 16r5].
+ 		[Jump]					-> [^self concretizeJump].
+ 		"Table B-1 Intel® 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
+ 		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
+ 		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
+ 		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
+ 		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
+ 		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
+ 		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
+ 		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
+ 		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
+ 		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
+ 		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
+ 		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
+ 		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
+ 		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
+ 		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
+ 		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
+ 		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
+ 		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
+ 		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
+ 		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
+ 		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
+ 		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
+ 		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
+ 		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
+ 		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
+ 		[RetN]						-> [^self concretizeRetN].
+ 		"Arithmetic"
+ 		[AddCqR]					-> [^self concretizeAddCqR].
+ 		[AddCwR]					-> [^self concretizeAddCwR].
+ 		[AddRR]						-> [^self concretizeAddRR].
+ 		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
+ 		[AndCqR]					-> [^self concretizeAndCqR].
+ 		[AndCwR]					-> [^self concretizeAndCwR].
+ 		[AndRR]						-> [^self concretizeAndRR].
+ 		[CmpCqR]					-> [^self concretizeCmpCqR].
+ 		[CmpCwR]					-> [^self concretizeCmpCwR].
+ 		[CmpRR]					-> [^self concretizeCmpRR].
+ 		[CmpRdRd]					-> [^self concretizeCmpRdRd].
+ 		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
+ 		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
+ 		[OrCqR]						-> [^self concretizeOrCqR].
+ 		[OrCwR]					-> [^self concretizeOrCwR].
+ 		[OrRR]						-> [^self concretizeOrRR].
+ 		[SubCqR]					-> [^self concretizeSubCqR].
+ 		[SubCwR]					-> [^self concretizeSubCwR].
+ 		[SubRR]						-> [^self concretizeSubRR].
+ 		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
+ 		[SqrtRd]						-> [^self concretizeSqrtRd].
+ 		[XorCwR]						-> [^self concretizeXorCwR].
+ 		[XorRR]							-> [^self concretizeXorRR].
+ 		[NegateR]						-> [^self concretizeNegateR].
+ 		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
+ 		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
+ 		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
+ 		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
+ 		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
+ 		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
+ 		"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].
+ 		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
+ 		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
+ 		[MoveRMwr]		-> [^self concretizeMoveRMwr].
+ 		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
+ 		[PopR]				-> [^self concretizePopR].
+ 		[PushR]				-> [^self concretizePushR].
+ 		[PushCw]			-> [^self concretizePushCw].
+ 		[PrefetchAw]		-> [^self concretizePrefetchAw].
+ 		"Conversion"
+ 		[ConvertRRd]		-> [^self concretizeConvertRRd] }!

Item was added:
+ ----- Method: CogARMCompiler>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
+ genAlignCStackSavingRegisters: saveRegs numArgs: numArgs wordAlignment: alignment 
+ 	| wordsPushedModAlignment delta |
+ 	wordsPushedModAlignment := ((saveRegs ifTrue: [16] ifFalse: [0]) "number of registers saved by genSaveRegisters"
+ 								+ numArgs)
+ 								\\ alignment.
+ 	wordsPushedModAlignment ~= 0 ifTrue:
+ 		[delta := alignment - wordsPushedModAlignment.
+ 		 cogit SubCq: delta * 4 R: SPReg].
+ 	^0!

Item was added:
+ ----- Method: CogARMCompiler>>genGetLeafCallStackPointerFunction (in category 'assertions') -----
+ genGetLeafCallStackPointerFunction
+ 	cogit MoveR: SP R: R0.
+ 	cogit RetN: 0!

Item was added:
+ ----- Method: CogARMCompiler>>isPCDependent (in category 'testing') -----
+ isPCDependent
+ 	"Answer if the receiver is a pc-dependent instruction."
+ 	^self isJump or: [opcode = AlignmentNops]!

Item was added:
+ ----- Method: CogARMCompiler>>leafCallStackPointerDelta (in category 'abi') -----
+ leafCallStackPointerDelta
+ 	"Answer the delta from the stack pointer after a call to the stack pointer
+ 	 immediately prior to the call.  This is used to compute the stack pointer
+ 	 immediately prior to  call from within a leaf routine, which in turn is used
+ 	 to capture the c stack pointer to use in trampolines back into the C run-time."
+ 	"This might actually be false, since directly after a call, lr, fp and variable registers need be pushed onto the stack. It depends on the implementation of call."
+ 	^0!

Item was added:
+ ----- Method: CogARMCompiler>>loadAllButLSBWord: (in category 'generate machine code - concretize') -----
+ loadAllButLSBWord: aWord
+ 	"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."
+ 	"The temporary register within abstract opcodes is R3"
+ 	self 
+ 		machineCodeAt: 0   put: 16rE3A03C00; "mov R3, #<second lowest byte>, 12"
+ 		machineCodeAt: 4   put: 16rE3833800; "orr R3, R3, #<third lowest byte>, 8"
+ 		machineCodeAt: 8   put: 16rE3833400. "orr R3, R3, #<most significant byte>, 4"
+ 	"fill in the bytes"
+ 	machineCode 
+ 		at: 0 put: (aWord >> 8   bitAnd: 16rFF);
+ 		at: 4 put: (aWord >> 12 bitAnd: 16rFF);
+ 		at: 8 put: (aWord >> 24 bitAnd: 16rFF).
+ 	^12!

Item was added:
+ ----- Method: CogARMCompiler>>machineCodeAt:put: (in category 'accessing') -----
+ machineCodeAt: anOffset put: aWord
+ 	"add aWord to machineCode, with little endian"
+ 	machineCode
+ 		at: anOffset + 3 put: (16rFF bitAnd: aWord >> 24);
+ 		at: anOffset + 2 put: (16rFF bitAnd: aWord >> 16);
+ 		at: anOffset + 1 put: (16rFF bitAnd: aWord >> 8);
+ 		at: anOffset"+ 0"put: (16rFF bitAnd: aWord">> 0")!

Item was added:
+ ----- Method: CogARMCompiler>>nopsFrom:to: (in category 'generate machine code - concretize') -----
+ nopsFrom: startAddr to: endAddr
+ 	self assert: endAddr - startAddr + 1 \\ 4 = 0.
+ 	startAddr to: endAddr by: 4 do:
+ 		[:p| objectMemory 
+ 			byteAt: p put: 16r01;
+ 			byteAt: p+1 put: 16r10;
+ 			byteAt: p+2 put: 16rA0;
+ 			byteAt: p+3 put: 16rE1]!

Item was added:
+ ----- Method: CogARMCompiler>>stackPageInterruptHeadroomBytes (in category 'accessing') -----
+ stackPageInterruptHeadroomBytes
+ 	"Return a minimum amount of headroom for each stack page (in bytes).  In a
+ 	 JIT the stack has to have room for interrupt handlers which will run on the stack.
+ 	According to ARM architecture v5 reference manual chapter A2.6, the basic interrupt procedure does not push anything onto the stack. It uses SPSR_err and R14_err to preserve state. Afterwards, it calls an interrupt procedure. So leave some room."
+ 	^128 "32 words"!

Item was added:
+ CogARMCompiler subclass: #CogARMCompilerForTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Tests'!

Item was added:
+ ----- Method: CogARMCompilerForTests class>>registers (in category 'test support') -----
+ registers
+ 	^{ R0. R1. R2. R3. R4. R5. R6. R7. R8. R9. R10. R11. R12. SP. LR. PC } "a.k.a. (0 to: 15)"!

Item was added:
+ ----- Method: CogARMCompilerForTests class>>registersWithNamesDo: (in category 'test support') -----
+ registersWithNamesDo: aBinaryBlock
+ 	self registers
+ 		with: #('r0' 'r1' 'r2' 'r3' 'r4' 'r5' 'r6' 'r7' 'r8' 'r9' 'r10' 'fp' 'r12' 'sp' 'lr' 'pc')
+ 		do: aBinaryBlock!

Item was added:
+ AbstractInstructionTests subclass: #CogARMCompilerTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Tests'!

Item was added:
+ ----- Method: CogARMCompilerTests>>concreteCompilerClass (in category 'accessing') -----
+ concreteCompilerClass
+ 	^CogARMCompilerForTests!

Item was added:
+ ----- Method: CogARMCompilerTests>>processor (in category 'accessing') -----
+ processor
+ 	processor ifNil:
+ 		[processor := GdbARMAlien new].
+ 	^processor!

Item was added:
+ ----- Method: CogARMCompilerTests>>strip: (in category 'accessing') -----
+ strip: aFancyDisassembledInstruction
+ 	"When havin an immediate > 15, the disassembler appends '	; 0x\d\d'. That is stripped."
+ 	^(aFancyDisassembledInstruction copyUpTo: $;) withBlanksTrimmed!

Item was added:
+ ----- Method: CogARMCompilerTests>>testRetN (in category 'tests') -----
+ testRetN
+ 	"self new testRetN"
+ 	
+ 	#(0) do:
+ 		[:n| | inst len |
+ 		inst := self gen: RetN operand: n.
+ 		len := inst concretizeAt: 0.
+ 		self processor
+ 			disassembleInstructionAt: 0
+ 			In: inst machineCode object
+ 			into: [:str :sz| | plainJane herIntended |
+ 				"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 				plainJane := self strip: str.
+ 				herIntended := 'pop	{pc}'.
+ 				self assert: (plainJane match: herIntended).
+ 				self assert: len = sz]].
+ 	
+ 	#(1 2 4 8 16 31) do:
+ 		[:n| | inst len |
+ 		inst := self gen: RetN operand: n.
+ 		len := inst concretizeAt: 0.
+ 		self processor
+ 			disassembleInstructionAt: 0
+ 			In: inst machineCode object
+ 			into: [:str :sz| | plainJane herIntended |
+ 				"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 				plainJane := self strip: str.
+ 				herIntended := 'add	sp, sp, #', n asString,', 30'.
+ 				self assert: (plainJane match: herIntended).
+ 				self assert: len = 8]]!

Item was changed:
  VMStructType subclass: #CogAbstractInstruction
  	instanceVariableNames: 'opcode machineCodeSize maxSize machineCode operands address dependent cogit objectMemory bcpc'
+ 	classVariableNames: 'MachineCodeSize NumberOfRegisters'
- 	classVariableNames: 'MachineCodeSize'
  	poolDictionaries: 'CogRTLOpcodes'
  	category: 'VMMaker-JIT'!
  
  !CogAbstractInstruction commentStamp: '<historical>' prior: 0!
  I am an abstract instruction generated by the Cogit.  I am subsequently concretized to machine code for the current processor.  A sequence of concretized CogAbstractInstructions are concatenated to form the code for a CogMethod.!

Item was added:
+ ----- Method: CogAbstractInstruction>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
+ genAlignCStackSavingRegisters: saveRegs numArgs: numArgs wordAlignment: alignment 
+ 	| wordsPushedModAlignment delta |
+ 	wordsPushedModAlignment := ((saveRegs ifTrue: [NumberOfRegisters] ifFalse: [0]) "number of registers saved by genSaveRegisters"
+ 								+ numArgs)
+ 								\\ alignment.
+ 	wordsPushedModAlignment ~= 0 ifTrue:
+ 		[delta := alignment - wordsPushedModAlignment.
+ 		 cogit SubCq: delta * 4 R: SPReg].
+ 	^0!

Item was changed:
  ----- Method: CogIA32Compiler class>>initialize (in category 'class initialization') -----
  initialize
  	"Initialize various IA32/x86 instruction-related constants.
  	 [1] IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M"
  
  	"CogIA32Compiler initialize"
  
  	| specificOpcodes refs |
  	self ~~ CogIA32Compiler ifTrue: [^self].
  
  	"N.B. EAX ECX and EDX are caller-save (scratch) registers.
  		EBX ESI and EDI are callee-save; see concreteRegisterFor:"
  	EAX := 0.
  	ECX := 1.  "Were they completely mad or simply sadistic?"
  	EDX := 2.
  	EBX := 3.
  	ESP := 4.
  	EBP := 5.
  	ESI := 6.
  	EDI := 7.
  
  	XMM0L := 0.
  	XMM1L := 2.
  	XMM2L := 4.
  	XMM3L := 6.
  	XMM4L := 8.
  	XMM5L := 10.
  	XMM6L := 12.
  	XMM7L := 14.
  
  	XMM0H := 1.
  	XMM1H := 3.
  	XMM2H := 5.
  	XMM3H := 7.
  	XMM4H := 9.
  	XMM5H := 11.
  	XMM6H := 13.
  	XMM7H := 15.
  
  	"Mod R/M Mod fields.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-2"
  	ModRegInd := 0.
  		ModRegIndSIB := 4.
  		ModRegIndDisp32 := 5.
  	ModRegRegDisp8 := 1.
  	ModRegRegDisp32 := 2.
  	ModReg := 3.
  
  	"SIB Scaled Index modes.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-3"
  	SIB1 := 0.
  	SIB2 := 1.
  	SIB4 := 2.
  	SIB8 := 3.
  
  	"Specific instructions"
  	LastRTLCode isNil ifTrue:
  		[CogRTLOpcodes initialize].
  	specificOpcodes := #(CDQ IDIVR IMULRR CPUID LFENCE MFENCE SFENCE LOCK CMPXCHGAwR CMPXCHGMwrR XCHGAwR XCHGMwrR XCHGRR).
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	(classPool keys reject: [:k| (specificOpcodes includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	specificOpcodes withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value + LastRTLCode - 1].
  
+ 	MachineCodeSize := 10. "e.g. lock movsd  0x400(%esp),%xmm4 => f0 f2 0f 10 a4 24 00 04 00 00"
+ 	NumberOfRegisters := 6!
- 	MachineCodeSize := 10 "e.g. lock movsd  0x400(%esp),%xmm4 => f0 f2 0f 10 a4 24 00 04 00 00"!

Item was removed:
- ----- Method: CogIA32Compiler>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
- genAlignCStackSavingRegisters: saveRegs numArgs: numArgs wordAlignment: alignment 
- 	| wordsPushedModAlignment delta |
- 	wordsPushedModAlignment := ((saveRegs ifTrue: [6] ifFalse: [0]) "number of registers saved by genSaveRegisters"
- 								+ numArgs)
- 								\\ alignment.
- 	wordsPushedModAlignment ~= 0 ifTrue:
- 		[delta := alignment - wordsPushedModAlignment.
- 		 cogit SubCq: delta * 4 R: SPReg].
- 	^0!



More information about the Vm-dev mailing list