[Vm-dev] VM Maker: VMMaker.oscog-eem.2611.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Dec 9 07:37:00 UTC 2019


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2611.mcz

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

Name: VMMaker.oscog-eem.2611
Author: eem
Time: 8 December 2019, 11:36:41.233693 pm
UUID: a1c152a6-e044-4b14-9eac-4aedeeb61684
Ancestors: VMMaker.oscog-eem.2610

A64 Call, CallFull, MoveCqR, PopR, PushR. More ABI implementation, nameForRegister:.

Eliminate duplication in genLoadStackPointers; implement in CogAbstractInstruction.
Add a few subclass responsibilities.
Correct 64-bit instruction printing (signedIntFromLong64 instead of signedIntFromLong).
Add Extra6Reg & Extra7Reg to nameForRegister:.

Now all send trampolines compile and generated code "looks ok" (which is potyentially very different from correwct).

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

Item was removed:
- ----- Method: CogARMCompiler>>genLoadStackPointers (in category 'smalltalk calling convention') -----
- genLoadStackPointers
- 	"Switch back to the Smalltalk stack. Assign SPReg first
- 	 because typically it is used immediately afterwards."
- 	cogit MoveAw: cogit stackPointerAddress R: SPReg.
- 	cogit MoveAw: cogit framePointerAddress R: FPReg.
- 	^0!

Item was changed:
  ----- Method: CogARMCompiler>>nameForRegister: (in category 'printing') -----
  nameForRegister: reg "<Integer>"
  	<doNotGenerate>
  	| default |
  	default := super nameForRegister: reg.
  	^default last = $?
  		ifTrue:
+ 			[#(LR SP PC CArg0Reg CArg1Reg CArg2Reg CArg3Reg)
- 			[#(LR SP PC CArg0Reg CArg0Reg CArg1Reg CArg2Reg CArg3Reg)
  				detect: [:sym| (thisContext method methodClass classPool at: sym) = reg] 
  				ifNone: [default]]
  		ifFalse:
  			[default]!

Item was changed:
  ----- Method: CogARMv8Compiler>>computeJumpTargetOffset (in category 'generate machine code') -----
  computeJumpTargetOffset
  	<inline: true>
  	| jumpTarget |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := self jumpTargetAddress.
+ 	^jumpTarget signedIntFromLong64 - address signedIntFromLong64!
- 	^jumpTarget signedIntFromLong - address signedIntFromLong.!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCall (in category 'generate machine code - concretize') -----
+ concretizeCall
+ 	| offset |
+ 	offset := ((operands at: 0) - address) signedIntFromLong64.
+ 	self assert: (offset noMask: 3).
+ 	self assert: (self isInImmediateBranchAndLinkRange: offset).
+ 	machineCode
+ 		at: 0
+ 		put: 2r100101 << 26
+ 			+ (offset >> 2 bitAnd: 1 << 26 - 1).
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeCallFull (in category 'generate machine code - concretize') -----
+ concretizeCallFull
+ 	"Will get inlined into concretizeAt: switch."
+ 	"Sizing/generating calls.
+ 		Jump targets can be to absolute addresses or other abstract instructions.
+ 		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
+ 		Otherwise instructions must have a machineCodeSize which must be kept to."
+ 	<inline: true>
+ 	| jumpTarget instrOffset|
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self longJumpTargetAddress.
+ 	instrOffset := self moveCw: jumpTarget intoR: RISCTempReg.
+ 	machineCode
+ 		at: instrOffset // 4
+ 		put: (self cond: AL br: 1 reg: RISCTempReg).
+ 	self assert: instrOffset = self literalLoadInstructionBytes.
+ 	^instrOffset + 4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeConditionalJump: (in category 'generate machine code - concretize') -----
  concretizeConditionalJump: conditionCode
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| offset |
  	offset := self computeJumpTargetOffset.
   	self assert: (self isInImmediateBranchRange: offset).
+ 	machineCode at: 0 put: (self cond: conditionCode br: 0 offset: offset). "B offset"
- 	self machineCodeAt: 0 put: (self cond: conditionCode br: 0 offset: offset). "B offset"
  	^4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeLogicalShiftLeftCqR (in category 'generate machine code - concretize') -----
  concretizeLogicalShiftLeftCqR
+ 	<inline: true>
  	"C6.2.17 	ASR (immediate)	C6-785		100100110 (1)
  	 C6.2.177	LSL (immediate)	C6-1075	110100110 (1)
  	 C6.2.180	LSR (immediate)	C6-1081	110100110 (1)"
  	| reg constant |
  	constant := operands at: 0.
  	reg := operands at: 1.
  	self assert: (constant between: 1 and: 63).
  	machineCode
  		at: 0
  		put: 2r1101001101 << 22
  			+ (64 - constant << 16)
  			+ (63 - constant << 10)
  			+ (reg << 5)
  			+ reg.
  	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMoveCqR (in category 'generate machine code') -----
+ concretizeMoveCqR
+ 	"C3.3.4		Move (immediate)	C3-215
+ 
+ 	 The Move (immediate) instructions are aliases for a single MOVZ, MOVN, or ORR (immediate with zero register),
+ 	 instruction to load an immediate value into the destination register. An assembler must permit a signed or
+ 	 unsigned immediate, as long as its binary representation can be generated using one of these instructions,
+ 	 and an assembler error results if the immediate cannot be generated in this way. On disassembly, it is
+ 	 unspecified whether the immediate is output as a signed or an unsigned value.
+ 
+ 	 C6.2.191	MOVZ	C6-1102	Move wide with zero moves an optionally-shifted 16-bit immediate value to a register.
+ 	 C6.2.190	MOVN	C6-1100	Move wide with NOT moves the inverse of an optionally-shifted 16-bit immediate value to a register.
+ 	 C6.2.204	ORR (immediate)	C6-1125
+ 										Bitwise OR (immediate) performs a bitwise (inclusive) OR of a register value and an immediate
+ 										register value, and writes the result to the destination register."
+ 
+ 	| constant destReg |
+ 	constant := operands at: 0.
+ 	destReg := operands at: 1.
+ 	destReg ~= SP ifTrue:
+ 		[| lowBit lowBitMod16 mask |
+ 		lowBit := constant > 0
+ 					ifTrue: [self cCode: [self lowBit: constant] inSmalltalk: [constant lowBit - 1]]
+ 					ifFalse: [0].
+ 		lowBitMod16 := lowBit // 16 * 16.
+ 		mask := 1 << 16 - 1 << lowBitMod16.
+ 		(constant bitAnd: mask) = constant ifTrue:
+ 			["Use MOVZ"
+ 			 machineCode
+ 				at: 0
+ 				put: 2r110100101 << 23
+ 					+ (lowBitMod16 // 16 << 21)
+ 					+ (constant >> lowBitMod16 << 5)
+ 					+ destReg.
+ 			 ^4].
+ 		lowBit := constant signedIntFromLong64 < -1
+ 					ifTrue: [self cCode: [self lowBit: constant bitInvert64] inSmalltalk: [constant bitInvert64 lowBit - 1]]
+ 					ifFalse: [0].
+ 		(constant bitOr: mask) signedIntFromLong64 = -1 ifTrue:
+ 			["Use MOVN"
+ 			 self assert: (constant bitInvert64 >> lowBitMod16) = ((constant bitInvert64 >> lowBitMod16) bitAnd: mask).
+ 			 machineCode
+ 				at: 0
+ 				put: 2r100100101 << 23
+ 					+ (lowBitMod16 // 16 << 21)
+ 					+ (constant bitInvert64 >> lowBitMod16 << 5)
+ 					+ destReg.
+ 			 ^4]].
+ 	self isImmNImmSImmREncodableBitmask: constant
+ 		ifTrue:
+ 			[:n :imms :immr| "Use ORR"
+ 			machineCode
+ 				at: 0
+ 				put: 2r1011001001 << 22
+ 					+ (immr << 16)
+ 					+ (imms << 10)
+ 					+ (XZR << 5)
+ 					+ destReg.
+ 			^4]
+ 		ifFalse: [].
+ 	^self moveCw: constant intoR: destReg!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveM16rR (in category 'generate machine code - concretize') -----
  concretizeMoveM16rR
+ 	<inline: true>
  	"C6.2.136	LDRH (immediate)	C6-990"
  	| offset destReg srcReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	(offset between: -2048 and: 2047)
  		ifTrue:
  			[machineCode
  				at: 0
  				put: 2r0111100101 << 22
  					+ ((offset bitAnd: 1 << 12 - 1) << 10)
  					+ (srcReg << 5)
  					+ destReg.
  			^4]
  		ifFalse:
  			[self shouldBeImplemented]!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveMbrR (in category 'generate machine code - concretize') -----
  concretizeMoveMbrR
+ 	<inline: true>
  	"C6.2.134	LDRB (immediate)	C6-985"
  	| offset destReg srcReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	(offset between: -2048 and: 2047)
  		ifTrue:
  			[machineCode
  				at: 0
  				put: 2r0011100101 << 22
  					+ ((offset bitAnd: 1 << 12 - 1) << 10)
  					+ (srcReg << 5)
  					+ destReg.
  			^4]
  		ifFalse:
  			[self shouldBeImplemented]!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeMoveXwrRR (in category 'generate machine code - concretize') -----
  concretizeMoveXwrRR
+ 	<inline: true>
  	"Xwr - memory word whose address is r * word size away from an address in a register"
  	"C6.2.132	LDR (register)	C6-981"
  	| index base dest |
  	index := operands at: 0.
  	base := operands at: 1.
  	dest := operands at: 2.
  	self deny: SP = dest.
  	machineCode
  		at: 0
  		put: 2r11111000011 << 21
  			+ (index << 16)
  			+ (UXTX << 13)
  			+ (3 << 11)
  			+ (base << 5)
  			+ dest.
  	^4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeNegateR (in category 'generate machine code - concretize') -----
  concretizeNegateR
+ 	<inline: true>
  	"C6.2.313	SUBS (extended register)	C6-1318"
  	| reg |
  	reg := operands at: 0.
  	self deny: SP = reg.
  	machineCode
  		at: 0
  		put: 2r11101011001 << 21
  			+ (31 << 16)
  			+ (UXTX << 13)
  			+ (reg << 5)
  			+ reg.
  	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizePopR (in category 'generate machine code - concretize') -----
+ concretizePopR
+ 	<inline: true>
+ 	"C6.2.273	LDR (immediate)	C6-1239
+ 	 Post-index"
+ 	| reg |
+ 	reg := operands at: 0.
+ 	self deny: SP = reg.
+ 	machineCode
+ 		at: 0
+ 		put: 2r1111100001 << 22
+ 			+ ((-8 bitAnd: 1 << 9 - 1) << 12)
+ 			+ (2r01 << 10)
+ 			+ (SP << 5)
+ 			+ reg.
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizePushR (in category 'generate machine code - concretize') -----
+ concretizePushR
+ 	<inline: true>
+ 	"C6.2.273	STR (immediate)	C6-1239
+ 	 Pre-index"
+ 	| reg |
+ 	reg := operands at: 0.
+ 	self deny: SP = reg.
+ 	machineCode
+ 		at: 0
+ 		put: 2r11111 << 27
+ 			+ ((-8 bitAnd: 1 << 9 - 1) << 12)
+ 			+ (2r11 << 10)
+ 			+ (SP << 5)
+ 			+ reg.
+ 	^4!

Item was changed:
  ----- Method: CogARMv8Compiler>>concretizeSubRR (in category 'generate machine code - concretize') -----
  concretizeSubRR
+ 	<inline: true>
  	"C6.2.313	SUBS (extended register)	C6-1318"
  	| destReg srcReg |
  	srcReg := operands at: 0.
  	destReg := operands at: 1.
  	self deny: SP = destReg.
  	machineCode
  		at: 0
  		put: 2r11101011001 << 21
  			+ (destReg << 16)
  			+ (UXTX << 13)
  			+ (srcReg << 5)
  			+ destReg.
  	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>cond:br:reg: (in category 'generate machine code - support') -----
+ cond: cond br: link reg: reg
+ 	self assert: link = 1.
+ 	self assert: cond = AL.
+ 	^2r1101011000111111 << 16 + (reg << 5)!

Item was added:
+ ----- Method: CogARMv8Compiler>>fullCallsAreRelative (in category 'abi') -----
+ fullCallsAreRelative
+ 	"Answer if CallFull and/or JumpFull are relative and hence need relocating on method
+ 	 compation. If so, they are annotated with IsRelativeCall in methods and relocated in
+ 	 relocateIfCallOrMethodReference:mcpc:delta:"
+ 	^false!

Item was added:
+ ----- Method: CogARMv8Compiler>>genPushRegisterArgsForAbortMissNumArgs: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForAbortMissNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the outer and
+ 	 inner retpcs at an entry miss for arity <= self numRegArgs.  The
+ 	 outer retpc is that of a call at a send site.  The inner is the call
+ 	 from a method or PIC abort/miss to the trampoline."
+ 
+ 	"Putting the receiver and args above the return address means the
+ 	 CoInterpreter has a single machine-code frame format which saves
+ 	 us a lot of work."
+ 
+ 	"Iff there are register args convert
+ 		sp		->	outerRetpc			(send site retpc)
+ 		linkReg = innerRetpc			(PIC abort/miss retpc)
+ 	 to
+ 		base	->	receiver
+ 					(arg0)
+ 					(arg1)
+ 		sp		->	outerRetpc			(send site retpc)
+ 		sp		->	linkReg/innerRetpc	(PIC abort/miss retpc)"
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 cogit MoveMw: 0 r: SPReg R: TempReg. "Save return address"
+ 		 cogit MoveR: ReceiverResultReg Mw: 0 r: SPReg.
+ 		 numArgs > 0 ifTrue:
+ 			[cogit PushR: Arg0Reg.
+ 			 numArgs > 1 ifTrue:
+ 				[cogit PushR: Arg1Reg]].
+ 		cogit PushR: TempReg]. "push back return address"
+ 	cogit PushR: LinkReg!

Item was added:
+ ----- Method: CogARMv8Compiler>>genRemoveNArgsFromStack: (in category 'abi') -----
+ genRemoveNArgsFromStack: n
+ 	"This is a no-op on ARM64 since the ABI passes up to 6 args in registers and trampolines currently observe that limit, using only 4."
+ 	<inline: true>
+ 	self assert: n <= 6.
+ 	^0!

Item was added:
+ ----- Method: CogARMv8Compiler>>genRestoreRegs: (in category 'abi') -----
+ genRestoreRegs: regMask
+ 	"Restore the registers in regMask as saved by genSaveRegs:."
+ 	R0 to: R17 do:
+ 		[:reg|
+ 		 (regMask anyMask: (cogit registerMaskFor: reg)) ifTrue:
+ 			[cogit PopR: reg]].
+ 	^0!

Item was added:
+ ----- Method: CogARMv8Compiler>>isInImmediateBranchAndLinkRange: (in category 'testing') -----
+ isInImmediateBranchAndLinkRange: offset
+ 	"ARM64 calls span +/- 128 mb.
+ 	 C6.2.33 BL		C6-812"
+ 	<var: #offset type: #'usqIntptr_t'>
+ 	self assert: (offset noMask: 3).
+ 	^offset signedIntFromLong64 >> 27 between: -16r1 and: 0!

Item was changed:
  ----- Method: CogARMv8Compiler>>isInImmediateBranchRange: (in category 'testing') -----
  isInImmediateBranchRange: offset
  	"ARM64 calls and jumps span +/- 1 mb."
  	<var: #offset type: #'usqIntptr_t'>
+ 	self assert: (offset noMask: 3).
+ 	^offset signedIntFromLong64 >> 18 between: -16r1 and: 0!
- 	^offset signedIntFromLong between: -16r100000 and: 16rFFFFC!

Item was added:
+ ----- Method: CogARMv8Compiler>>literalLoadInstructionBytes (in category 'accessing') -----
+ literalLoadInstructionBytes
+ 	"Answer the size of a literal load instruction (which does not include the size of the literal).
+ 	 With out-of-line literals this is always a single LDR instruction that refers to the literal."
+ 	<inline: true>
+ 	^4!

Item was added:
+ ----- Method: CogARMv8Compiler>>nameForRegister: (in category 'printing') -----
+ nameForRegister: reg "<Integer>"
+ 	<doNotGenerate>
+ 	| default |
+ 	default := super nameForRegister: reg.
+ 	^default last = $?
+ 		ifTrue:
+ 			[reg = 31
+ 				ifTrue:
+ 					['SP/XZR']
+ 				ifFalse:
+ 					[#(LR CArg0Reg CArg1Reg CArg2Reg CArg3Reg)
+ 						detect: [:sym| (thisContext method methodClass classPool at: sym) = reg] 
+ 						ifNone: [default]]]
+ 		ifFalse:
+ 			[default]!

Item was changed:
  ----- Method: CogAbstractInstruction>>computeJumpTargetOffsetPlus: (in category 'generate machine code') -----
  computeJumpTargetOffsetPlus: anPCOffset
  	<inline: true> "Since it's an extraction from other methods."
  	| jumpTarget |
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := self jumpTargetAddress.
+ 	^objectMemory wordSize = 8
+ 		ifTrue: [jumpTarget signedIntFromLong64 - (address + anPCOffset) signedIntFromLong64]
+ 		ifFalse: [jumpTarget signedIntFromLong - (address + anPCOffset) signedIntFromLong]!
- 	^jumpTarget signedIntFromLong - (address + anPCOffset) signedIntFromLong.!

Item was changed:
  ----- Method: CogAbstractInstruction>>genLoadStackPointers (in category 'smalltalk calling convention') -----
  genLoadStackPointers
  	"Switch back to the Smalltalk stack. Assign SPReg first
  	 because typically it is used immediately afterwards."
+ 	cogit MoveAw: cogit stackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit framePointerAddress R: FPReg.
+ 	^0!
- 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>genRemoveNArgsFromStack: (in category 'abi') -----
+ genRemoveNArgsFromStack: n
+ 	"Remove n arguments from teh stack (iff any of the N arguments was passed on the stack)."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>genRestoreRegs: (in category 'abi') -----
+ genRestoreRegs: regMask
+ 	"Restore the registers in regMask as saved by genSaveRegs:."
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: CogAbstractInstruction>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	| opcodeName orneryOperands format |
  	<doNotGenerate> "Smalltalk-side only"
  	opcode ifNil:
  		[^self].
  	aStream space; nextPut: $(; nextPutAll: (opcodeName := self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	format := ((CogRTLOpcodes classPool includesKey: opcodeName)
  				ifTrue: [CogRTLOpcodes]
  				ifFalse: [self class]) printFormatForOpcodeName: opcodeName.
  	orneryOperands withIndexDo:
  		[:operand :index|
  		operand ifNotNil:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 (format notNil and: ['rf' includes: (format at: index ifAbsent: $-)])
  				ifTrue: [aStream nextPutAll: ((format at: index) = $r
  												ifTrue: [self nameForRegister: operand]
  												ifFalse: [self nameForFPRegister: operand])]
  				ifFalse:
  					[aStream print: operand.
  					 (operand isInteger and: [operand > 16 and: [opcode ~= Label]]) ifTrue:
+ 						[objectMemory wordSize = 8
+ 							ifTrue:
+ 								[(operand allMask: 1 << 63) ifTrue:
+ 									[aStream nextPut: $/; print: operand signedIntFromLong64]]
+ 							ifFalse:
+ 								[(operand allMask: 1 << 31) ifTrue:
+ 									[aStream nextPut: $/; print: operand signedIntFromLong]].
- 						[(operand allMask: 16r80000000) ifTrue:
- 							[aStream nextPut: $/; print: operand signedIntFromLong].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16]]]].
  	machineCodeSize ifNotNil:
  		[(machineCodeSize between: 1 and: machineCode size) ifTrue:
  			[0 to: machineCodeSize - 1 by: self codeGranularity do:
  				[:i|
  				 aStream space.
  				 (self machineCodeAt: i)
  					ifNil: [aStream nextPut: $.]
  					ifNotNil:
  						[:mc|
  						mc isInteger
  							ifTrue: [mc printOn: aStream base: 16]
  							ifFalse: [mc printOn: aStream]]]]].
  	address ifNotNil:
  		[aStream nextPut: $@.
  		 address printOn: aStream base: 16].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: CogAbstractInstruction>>symbolicOn: (in category 'printing') -----
  symbolicOn: aStream
  	| orneryOperands |
  	<doNotGenerate> "Smalltalk-side only"
  	(machineCodeSize isNil
  	 or: [opcode = 16rAAA]) ifTrue:
  		[^aStream nextPut: 'uninitialized opcode'].
  	aStream space; nextPut: $(; nextPutAll: (self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	orneryOperands withIndexDo:
  		[:operand :index|
  		operand ifNotNil:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 operand class == self class
  				ifTrue:
  					[operand symbolicOn: aStream]
  				ifFalse:
  					[aStream print: operand.
  					 (operand isInteger and: [operand > 16]) ifTrue:
+ 						[objectMemory wordSize = 8
+ 							ifTrue:
+ 								[(operand allMask: 1 << 63) ifTrue:
+ 									[aStream nextPut: $/; print: operand signedIntFromLong64]]
+ 							ifFalse:
+ 								[(operand allMask: 1 << 31) ifTrue:
+ 									[aStream nextPut: $/; print: operand signedIntFromLong]].
- 						[(operand allMask: 16r80000000) ifTrue:
- 							[aStream nextPut: $/; print: operand signedIntFromLong].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16]]]].
  	machineCodeSize > 0 ifTrue:
  		[machineCodeSize > machineCode size
  			ifTrue: [aStream nextPutAll: ' no mcode']
  			ifFalse:
  				[0 to: machineCodeSize - 1 by: self codeGranularity do:
  					[:i|
  					 aStream space.
  					 (self machineCodeAt: i) printOn: aStream base: 16]]].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: CogAbstractRegisters class>>nameForRegister: (in category 'debug printing') -----
  nameForRegister: reg "<Integer>"
  	^#(Arg0Reg Arg1Reg ClassReg FPReg ReceiverResultReg SPReg SendNumArgsReg TempReg
  		LinkReg RISCTempReg VarBaseReg PCReg
+ 		Extra0Reg Extra1Reg Extra2Reg Extra3Reg Extra4Reg Extra5Reg Extra6Reg Extra7Reg)
- 		Extra0Reg Extra1Reg Extra2Reg Extra3Reg Extra4Reg Extra5Reg)
  			detect: [:sym| (classPool at: sym) = reg]
  			ifNone: ['REG', reg printString, '?']!

Item was removed:
- ----- Method: CogIA32Compiler>>genLoadStackPointers (in category 'smalltalk calling convention') -----
- genLoadStackPointers
- 	"Switch back to the Smalltalk stack. Assign SPReg first
- 	 because typically it is used immediately afterwards."
- 	cogit MoveAw: cogit stackPointerAddress R: SPReg.
- 	cogit MoveAw: cogit framePointerAddress R: FPReg.
- 	^0!

Item was removed:
- ----- Method: CogMIPSELCompiler>>genLoadStackPointers (in category 'smalltalk calling convention') -----
- genLoadStackPointers
- 	"Switch back to the Smalltalk stack. Assign SPReg first
- 	 because typically it is used immediately afterwards."
- 	cogit MoveAw: cogit stackPointerAddress R: SPReg.
- 	cogit MoveAw: cogit framePointerAddress R: FPReg.
- 	^0!

Item was removed:
- ----- Method: CogX64Compiler>>genLoadStackPointers (in category 'smalltalk calling convention') -----
- genLoadStackPointers
- 	"Switch back to the Smalltalk stack. Assign SPReg first
- 	 because typically it is used immediately afterwards."
- 	cogit MoveAw: cogit stackPointerAddress R: SPReg.
- 	cogit MoveAw: cogit framePointerAddress R: FPReg.
- 	^0!

Item was changed:
  ----- Method: Cogit>>compileCallFor:numArgs:arg:arg:arg:arg:floatResultReg:regsToSave: (in category 'initialization') -----
  compileCallFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 floatResultReg: resultRegOrNone regsToSave: regMask
  	"Generate a call to aRoutine with up to 4 arguments.  If resultRegOrNone is not
  	 NoReg assign the C result to resultRegOrNone.  If saveRegs, save all registers.
  	 Hack: a negative arg value indicates an abstract register, a non-negative value
  	 indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<inline: false>
  	| regsToSave |
  	regsToSave := resultRegOrNone = NoReg
  						ifTrue: [regMask]
  						ifFalse: [regMask bitClear: (self registerMaskFor: resultRegOrNone)].
  	cStackAlignment > objectMemory wordSize ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: regsToSave
  			numArgs: numArgs
  			wordAlignment: cStackAlignment / objectMemory wordSize].
  	backEnd
  		genSaveRegs: regsToSave;
  		genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3.
  	self CallFullRT: (self cCode: [aRoutine asUnsignedInteger]
  						inSmalltalk: [self simulatedTrampolineFor: aRoutine]).
  	resultRegOrNone ~= NoReg ifTrue:
  		[backEnd cFloatResultToRd: resultRegOrNone].
+ 	backEnd
+ 		genRemoveNArgsFromStack: numArgs;
+ 		genRestoreRegs: regsToSave!
- 	 backEnd genRemoveNArgsFromStack: numArgs.
- 	backEnd genRestoreRegs: regsToSave!



More information about the Vm-dev mailing list