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

commits at source.squeak.org commits at source.squeak.org
Tue Sep 22 18:58:37 UTC 2015


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

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

Name: VMMaker.oscog-eem.1461
Author: eem
Time: 22 September 2015, 11:56:19.984 am
UUID: 5745bccf-6b46-4e68-bcd6-e33a3124ff25
Ancestors: VMMaker.oscog-rmacnak.1460

Refactor concreatizeAt: to eliminate duplicatuion and to check for exact size matching in the tests.

Add the missing X64 tests from IA32.

Improve CogIA32Compiler>>computeMaximumSize's accuracy.

=============== Diff against VMMaker.oscog-rmacnak.1460 ===============

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

Item was added:
+ ----- Method: CogARMCompilerForTests>>concretizeAt: (in category 'generate machine code') -----
+ concretizeAt: actualAddress
+ 	"Override to check maxSize and machineCodeSize"
+ 
+ 	| result |
+ 	maxSize ifNil: [maxSize := self computeMaximumSize].
+ 	result := super concretizeAt: actualAddress.
+ 	self assert: (maxSize notNil
+ 				and: [self isPCDependent
+ 						ifTrue: [maxSize >= machineCodeSize]
+ 						ifFalse: [maxSize = machineCodeSize]]).
+ 	^result!

Item was added:
+ ----- Method: CogAbstractInstruction class>>localNameForOpcode: (in category 'printing') -----
+ localNameForOpcode: opcode
+ 	^(self classPool keyAtValue: opcode ifAbsent: nil)
+ 		ifNotNil: [:opcodeName| opcodeName]
+ 		ifNil: [self == CogAbstractInstruction
+ 				ifTrue: [opcode printString]
+ 				ifFalse: [superclass localNameForOpcode: opcode]]!

Item was changed:
  ----- Method: CogAbstractInstruction class>>nameForOpcode: (in category 'debug printing') -----
  nameForOpcode: opcode "<Integer>"
  	^(CogRTLOpcodes nameForOpcode: opcode)
  		ifNotNil:
  			[:opcodeName| opcodeName]
  		ifNil:
+ 			[self localNameForOpcode: opcode]!
- 			[(self classPool keyAtValue: opcode ifAbsent: [])
- 				ifNotNil: [:opcodeName| opcodeName]
- 				ifNil: [opcode printString]]!

Item was changed:
  ----- Method: CogAbstractInstruction>>concretizeAt: (in category 'generate machine code') -----
  concretizeAt: actualAddress
  	"Generate concrete machine code for the instruction at actualAddress,
  	 setting machineCodeSize, and answer the following address."
+ 
+ 	address := actualAddress.
+ 	self dispatchConcretize.
+ 	self assert: (maxSize = nil or: [maxSize >= machineCodeSize]).
+ 	^actualAddress + machineCodeSize!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: CogAbstractInstruction>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	| opcodeName orneryOperands format |
  	<doNotGenerate> "Smalltalk-side only"
+ 	opcode ifNil:
- 	opcode isNil ifTrue:
  		[^self].
  	aStream space; nextPut: $(; nextPutAll: (opcodeName := self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	(cogit isKindOf: Cogit) ifTrue:
  		[format := CogRTLOpcodes printFormatForOpcodeName: opcodeName].
  	orneryOperands withIndexDo:
  		[:operand :index|
  		operand notNil ifTrue:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 (format notNil and: [(format at: index ifAbsent: nil) = $r])
  				ifTrue: [aStream nextPutAll: (self nameForRegister: operand)]
  				ifFalse:
  					[aStream print: operand.
  					 (operand isInteger and: [operand > 16 and: [opcode ~= Label]]) ifTrue:
  						[(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: CogIA32Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Compute the maximum size for each opcode.  This allows jump offsets to
  	 be determined, provided that all backward branches are long branches."
  	"N.B.  The ^N forms are to get around the bytecode compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^0].
  		[AlignmentNops]		-> [^(operands at: 0) - 1].
  		[Fill16]					-> [^2].
  		[Fill32]					-> [^4].
  		[FillFromWord]			-> [^4].
  		[Nop]					-> [^1].
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^1].
  		[IDIVR]					-> [^2].
  		[IMULRR]				-> [^3].
  		[CPUID]					-> [^2].
  		[CMPXCHGAwR]			-> [^7].
+ 		[CMPXCHGMwrR]		-> [^(self concreteRegister: (operands at: 1)) = ESP
+ 										ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
+ 										ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
- 		[CMPXCHGMwrR]		-> [^8].
  		[LFENCE]				-> [^3].
  		[MFENCE]				-> [^3].
  		[SFENCE]				-> [^3].
  		[LOCK]					-> [^1].
  		[XCHGAwR]				-> [^6].
+ 		[XCHGMwrR]			-> [^(self concreteRegister: (operands at: 1)) = ESP
+ 										ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]
+ 										ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [3] ifFalse: [6]]].
+ 		[XCHGRR]				-> [^((self concreteRegister: (operands at: 0)) = EAX
+ 									   or: [(self concreteRegister: (operands at: 1)) = EAX])
+ 										ifTrue: [1]
+ 										ifFalse: [2]].
- 		[XCHGMwrR]			-> [^7].
- 		[XCHGRR]				-> [^2].
  		"Control"
  		[CallFull]					-> [^5].
  		[Call]						-> [^5].
  		[JumpR]						-> [^2].
  		[JumpFull]					-> [self resolveJumpTarget. ^5].
  		[JumpLong]					-> [self resolveJumpTarget. ^5].
  		[Jump]						-> [self resolveJumpTarget. ^5].
  		[JumpZero]					-> [self resolveJumpTarget. ^6].
  		[JumpNonZero]				-> [self resolveJumpTarget. ^6].
  		[JumpNegative]				-> [self resolveJumpTarget. ^6].
  		[JumpNonNegative]			-> [self resolveJumpTarget. ^6].
  		[JumpOverflow]				-> [self resolveJumpTarget. ^6].
  		[JumpNoOverflow]			-> [self resolveJumpTarget. ^6].
  		[JumpCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpNoCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpLess]					-> [self resolveJumpTarget. ^6].
  		[JumpGreaterOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpGreater]				-> [self resolveJumpTarget. ^6].
  		[JumpLessOrEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpBelow]				-> [self resolveJumpTarget. ^6].
  		[JumpAboveOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpAbove]				-> [self resolveJumpTarget. ^6].
  		[JumpBelowOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpLongZero]			-> [self resolveJumpTarget. ^6].
  		[JumpLongNonZero]		-> [self resolveJumpTarget. ^6].
  		[JumpFPEqual]				-> [self resolveJumpTarget. ^6].
  		[JumpFPNotEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLess]				-> [self resolveJumpTarget. ^6].
  		[JumpFPGreaterOrEqual]	-> [self resolveJumpTarget. ^6].
  		[JumpFPGreater]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLessOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpFPOrdered]			-> [self resolveJumpTarget. ^6].
  		[JumpFPUnordered]			-> [self resolveJumpTarget. ^6].
  		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [1] ifFalse: [3]].
  		[Stop]						-> [^1].
  
  		"Arithmetic"
  		[AddCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AndCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[CmpCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[OrCqR]			-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[SubCqR]		-> [^(self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[TstCqR]		-> [^((self isQuick: (operands at: 0)) and: [(self concreteRegister: (operands at: 1)) < 4])
  											ifTrue: [3]
  											ifFalse: [(self concreteRegister: (operands at: 1)) = EAX
  														ifTrue: [5]
  														ifFalse: [6]]].
  		[AddCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[AndCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[CmpCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[OrCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[SubCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[XorCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[AddRR]			-> [^2].
  		[AndRR]			-> [^2].
  		[CmpRR]		-> [^2].
  		[OrRR]			-> [^2].
  		[XorRR]			-> [^2].
  		[SubRR]			-> [^2].
  		[NegateR]		-> [^2].
  		[LoadEffectiveAddressMwrR]
  						-> [^((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[LogicalShiftLeftCqR]		-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
  		[LogicalShiftRightCqR]		-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
  		[ArithmeticShiftRightCqR]	-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
  		[LogicalShiftLeftRR]			-> [^self computeShiftRRSize].
  		[LogicalShiftRightRR]		-> [^self computeShiftRRSize].
  		[ArithmeticShiftRightRR]		-> [^self computeShiftRRSize].
  		[AddRdRd]					-> [^4].
  		[CmpRdRd]					-> [^4].
  		[SubRdRd]					-> [^4].
  		[MulRdRd]					-> [^4].
  		[DivRdRd]					-> [^4].
  		[SqrtRd]					-> [^4].
  		"Data Movement"
  		[MoveCqR]		-> [^(operands at: 0) = 0 ifTrue: [2] ifFalse: [5]].
  		[MoveCwR]		-> [^5].
  		[MoveRR]		-> [^2].
  		[MoveRdRd]		-> [^4].
  		[MoveAwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[MoveRAw]		-> [^(self concreteRegister: (operands at: 0)) = EAX ifTrue: [5] ifFalse: [6]].
  		[MoveRMwr]	-> [^((self isQuick: (operands at: 1))
+ 									ifTrue: [((operands at: 1) = 0
+ 											and: [(self concreteRegister: (operands at: 2)) ~= EBP])
+ 												ifTrue: [2]
+ 												ifFalse: [3]]
+ 									ifFalse: [6])
+ 								+ ((self concreteRegister: (operands at: 2)) = ESP
+ 									ifTrue: [1]
+ 									ifFalse: [0])].
- 											ifTrue: [3]
- 											ifFalse: [6])
- 										+ ((self concreteRegister: (operands at: 2)) = ESP
- 											ifTrue: [1]
- 											ifFalse: [0])].
  		[MoveRdM64r]	-> [^((self isQuick: (operands at: 1))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
+ 		[MoveMbrR]		-> [^(self concreteRegister: (operands at: 1)) = ESP
+ 								ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
+ 								ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
+ 		[MoveRMbr]		-> [^(self concreteRegister: (operands at: 2)) = ESP
+ 								ifTrue: [7]
+ 								ifFalse: [(self isQuick: (operands at: 1)) ifTrue: [3] ifFalse: [6]]].
+ 		[MoveM16rR]	-> [^(self concreteRegister: (operands at: 1)) = ESP
+ 								ifTrue: [(self isQuick: (operands at: 0)) ifTrue: [5] ifFalse: [8]]
+ 								ifFalse: [(self isQuick: (operands at: 0)) ifTrue: [4] ifFalse: [7]]].
- 		[MoveMbrR]		-> [^((self isQuick: (operands at: 0))
- 											ifTrue: [4]
- 											ifFalse: [7])
- 										+ ((self concreteRegister: (operands at: 1)) = ESP
- 											ifTrue: [1]
- 											ifFalse: [0])].
- 		[MoveRMbr]		-> [^((self isQuick: (operands at: 1))
- 											ifTrue: [3]
- 											ifFalse: [6])
- 										+ ((self concreteRegister: (operands at: 2)) = ESP
- 											ifTrue: [1]
- 											ifFalse: [0])].
- 		[MoveM16rR]	-> [^((self isQuick: (operands at: 0))
- 											ifTrue: [4]
- 											ifFalse: [7])
- 										+ ((self concreteRegister: (operands at: 1)) = ESP
- 											ifTrue: [1]
- 											ifFalse: [0])].
  		[MoveM64rRd]	-> [^((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMwrR]		-> [^((self isQuick: (operands at: 0))
+ 									ifTrue: [((operands at: 0) = 0
+ 											and: [(self concreteRegister: (operands at: 1)) ~= EBP])
+ 												ifTrue: [2]
+ 												ifFalse: [3]]
+ 									ifFalse: [6])
+ 								+ ((self concreteRegister: (operands at: 1)) = ESP
+ 									ifTrue: [1]
+ 									ifFalse: [0])].
- 											ifTrue: [3]
- 											ifFalse: [6])
- 										+ ((self concreteRegister: (operands at: 1)) = ESP
- 											ifTrue: [1]
- 											ifFalse: [0])].
  		[MoveXbrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^(self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^((self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3])
  										+ ((self concreteRegister: (operands at: 0)) >= 4
  											ifTrue: [2]
  											ifFalse: [0])].
  		[MoveXwrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^(self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveRXwrR]	-> [self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^(self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[PopR]			-> [^1].
  		[PushR]			-> [^1].
  		[PushCq]		-> [^(self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
  		[PushCw]		-> [^5].
  		[PrefetchAw]	-> [^self hasSSEInstructions ifTrue: [7] ifFalse: [0]].
  		"Conversion"
  		[ConvertRRd]	-> [^4] }.
  	^0 "to keep C compiler quiet"!

Item was removed:
- ----- Method: CogIA32Compiler>>concretizeAt: (in category 'generate machine code') -----
- concretizeAt: actualAddress
- 	"Generate concrete machine code for the instruction at actualAddress,
- 	 setting machineCodeSize, and answer the following address."
- 
- 	address := actualAddress.
- 	self dispatchConcretize.
- 	self assert: (maxSize = nil or: [maxSize >= machineCodeSize]).
- 	^actualAddress + machineCodeSize!

Item was added:
+ ----- Method: CogIA32CompilerForTests>>concretizeAt: (in category 'generate machine code') -----
+ concretizeAt: actualAddress
+ 	"Override to check maxSize and machineCodeSize"
+ 
+ 	| result |
+ 	maxSize ifNil: [maxSize := self computeMaximumSize].
+ 	result := super concretizeAt: actualAddress.
+ 	self assert: (maxSize notNil
+ 				and: [self isPCDependent
+ 						ifTrue: [maxSize >= machineCodeSize]
+ 						ifFalse: [maxSize = machineCodeSize]]).
+ 	^result!

Item was added:
+ ----- Method: CogIA32CompilerForTests>>machineCodeAt: (in category 'accessing') -----
+ machineCodeAt: anOffset
+ 	^machineCode at: anOffset!

Item was removed:
- ----- Method: CogIA32CompilerTests>>testMoveM0wrR (in category 'tests') -----
- testMoveM0wrR
- 	"self new testMoveM0wrR"
- 	CogIA32CompilerForTests registersWithNamesDo:
- 		[:sreg :srname|
- 		CogIA32CompilerForTests registersWithNamesDo:
- 			[:dreg :drname| | inst len |
- 			inst := self gen: MoveMwrR operand: 0 operand: sreg operand: dreg.
- 			len := inst concretizeAt: 0.
- 			self processor
- 				disassembleInstructionAt: 0
- 				In: inst machineCode object
- 				into: [:str :sz| | plainJane herIntended |
- 					plainJane := self strip: str.
- 					herIntended := 'movl (', srname, '), ', drname.
- 					self assert: (plainJane match: herIntended).
- 					self assert: len = sz]]]!

Item was changed:
  ----- Method: CogIA32CompilerTests>>testMoveMwrR (in category 'tests') -----
  testMoveMwrR
  	"self new testMoveMwrR"
+ 	self concreteCompilerClass registersWithNamesDo:
- 	CogIA32CompilerForTests registersWithNamesDo:
  		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname| | inst len |
+ 			inst := self gen: MoveMwrR operand: 0 operand: sreg operand: dreg.
+ 			len := inst concretizeAt: 0.
+ 			self processor
+ 				disassembleInstructionAt: 0
+ 				In: inst machineCode object
+ 				into: [:str :sz| | plainJane herIntended |
+ 					plainJane := self strip: str.
+ 					herIntended := 'movl (', srname, '), ', drname.
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!
- 		CogIA32CompilerForTests registersWithNamesDo:
- 			[:dreg :drname|
- 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 				[:offset| | inst len |
- 				inst := self gen: MoveMwrR operand: offset operand: sreg operand: dreg.
- 				len := inst concretizeAt: 0.
- 				self processor
- 					disassembleInstructionAt: 0
- 					In: inst machineCode object
- 					into: [:str :sz| | plainJane herIntended |
- 						plainJane := self strip: str.
- 						herIntended := 'movl 0x', (offset hex allButFirst: 3), '(', srname, '), ', drname.
- 						self assert: (plainJane match: herIntended).
- 						self assert: len = sz]]]]!

Item was removed:
- ----- Method: CogIA32CompilerTests>>testMoveRM0wr (in category 'tests') -----
- testMoveRM0wr
- 	"self new testMoveRM0wr"
- 	CogIA32CompilerForTests registersWithNamesDo:
- 		[:sreg :srname|
- 		CogIA32CompilerForTests registersWithNamesDo:
- 			[:dreg :drname| | inst len |
- 			inst := self gen: MoveRMwr operand: sreg operand: 0 operand: dreg.
- 			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 := 'movl ', srname, ', (',drname,')'.
- 					self assert: (plainJane match: herIntended).
- 					self assert: len = sz]]]!

Item was changed:
  ----- Method: CogIA32CompilerTests>>testMoveRMwr (in category 'tests') -----
  testMoveRMwr
  	"self new testMoveRMwr"
+ 	self concreteCompilerClass registersWithNamesDo:
- 	CogIA32CompilerForTests registersWithNamesDo:
  		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname| | inst len |
+ 			inst := self gen: MoveRMwr operand: sreg operand: 0 operand: dreg.
+ 			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 := 'movl ', srname, ', (',drname,')'.
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!
- 		CogIA32CompilerForTests registersWithNamesDo:
- 			[:dreg :drname|
- 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
- 				[:offset| | inst len |
- 				inst := self gen: MoveRMwr operand: sreg operand: offset operand: dreg.
- 				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 := 'movl ', srname, ', 0x', (offset hex allButFirst: 3), '(',drname,')'.
- 						self assert: (plainJane match: herIntended).
- 						self assert: len = sz]]]]!

Item was added:
+ ----- Method: CogInLineLiteralsX64Compiler>>computeSizeOfArithCwR (in category 'generate machine code') -----
+ computeSizeOfArithCwR
+ 	<inline: true>
+ 	^10 "MoveCwR" +  3 "ArithRR"!

Item was added:
+ ----- Method: CogVMSimulator>>getCogVMFlags (in category 'multi-threading simulation switch') -----
+ getCogVMFlags
+ 	"This method includes or excludes CoInterpreterMT methods as required.
+ 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
+ 
+ 	^self perform: #getCogVMFlags
+ 		withArguments: {}
+ 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was added:
+ ----- Method: CogVMSimulator>>getImageHeaderFlags (in category 'multi-threading simulation switch') -----
+ getImageHeaderFlags
+ 	"This method includes or excludes CoInterpreterMT methods as required.
+ 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
+ 
+ 	^self perform: #getImageHeaderFlags
+ 		withArguments: {}
+ 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was added:
+ ----- Method: CogVMSimulator>>setCogVMFlags: (in category 'multi-threading simulation switch') -----
+ setCogVMFlags: flags
+ 	"This method includes or excludes CoInterpreterMT methods as required.
+ 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
+ 
+ 	^self perform: #setCogVMFlags:
+ 		withArguments: {flags}
+ 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was changed:
  ----- Method: CogX64Compiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Compute the maximum size for each opcode.  This allows jump offsets to
  	 be determined, provided that all backward branches are long branches."
  	"N.B.  The ^N forms are to get around the bytecode compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^0].
  		[AlignmentNops]		-> [^(operands at: 0) - 1].
  		[Fill16]					-> [^2].
  		[Fill32]					-> [^4].
  		[FillFromWord]			-> [^4].
  		[Nop]					-> [^1].
  		"Specific Control/Data Movement"
  		"[CDQ]					-> [^1].
  		[IDIVR]					-> [^2].
  		[IMULRR]				-> [^3].
  		[CPUID]					-> [^2].
  		[CMPXCHGAwR]			-> [^7].
  		[CMPXCHGMwrR]		-> [^8].
  		[LFENCE]				-> [^3].
  		[MFENCE]				-> [^3].
  		[SFENCE]				-> [^3].
  		[LOCK]					-> [^1].
  		[XCHGAwR]				-> [^6].
  		[XCHGMwrR]			-> [^7].
  		[XCHGRR]				-> [^2]."
  		"Control"
  		[CallFull]					-> [^12].
  		[Call]						-> [^5].
  		[JumpR]						-> [^2].
  		[JumpFull]					-> [self resolveJumpTarget. ^12].
  		[JumpLong]					-> [self resolveJumpTarget. ^5].
  		[Jump]						-> [self resolveJumpTarget. ^5].
  		[JumpZero]					-> [self resolveJumpTarget. ^6].
  		[JumpNonZero]				-> [self resolveJumpTarget. ^6].
  		[JumpNegative]				-> [self resolveJumpTarget. ^6].
  		[JumpNonNegative]			-> [self resolveJumpTarget. ^6].
  		[JumpOverflow]				-> [self resolveJumpTarget. ^6].
  		[JumpNoOverflow]			-> [self resolveJumpTarget. ^6].
  		[JumpCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpNoCarry]				-> [self resolveJumpTarget. ^6].
  		[JumpLess]					-> [self resolveJumpTarget. ^6].
  		[JumpGreaterOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpGreater]				-> [self resolveJumpTarget. ^6].
  		[JumpLessOrEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpBelow]				-> [self resolveJumpTarget. ^6].
  		[JumpAboveOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpAbove]				-> [self resolveJumpTarget. ^6].
  		[JumpBelowOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpLongZero]			-> [self resolveJumpTarget. ^6].
  		[JumpLongNonZero]		-> [self resolveJumpTarget. ^6].
  		[JumpFPEqual]				-> [self resolveJumpTarget. ^6].
  		[JumpFPNotEqual]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLess]				-> [self resolveJumpTarget. ^6].
  		[JumpFPGreaterOrEqual]	-> [self resolveJumpTarget. ^6].
  		[JumpFPGreater]			-> [self resolveJumpTarget. ^6].
  		[JumpFPLessOrEqual]		-> [self resolveJumpTarget. ^6].
  		[JumpFPOrdered]			-> [self resolveJumpTarget. ^6].
  		[JumpFPUnordered]			-> [self resolveJumpTarget. ^6].
  		[RetN]						-> [^(operands at: 0) = 0 ifTrue: [1] ifFalse: [3]].
  		[Stop]						-> [^1].
  
  		"Arithmetic"
+ 		[AddCqR]		-> [^self computeSizeOfArithCqR].
+ 		[AndCqR]		-> [^self computeSizeOfArithCqR].
+ 		[CmpCqR]		-> [^self computeSizeOfArithCqR].
+ 		[OrCqR]			-> [^self computeSizeOfArithCqR].
+ 		[SubCqR]		-> [^self computeSizeOfArithCqR].
+ 		[TstCqR]		-> [^self computeSizeOfArithCqR].
+ 		[AddCwR]		-> [^self computeSizeOfArithCwR].
+ 		[AndCwR]		-> [^self computeSizeOfCwR].
+ 		[CmpCwR]		-> [^self computeSizeOfCwR].
+ 		[OrCwR]		-> [^self computeSizeOfCwR].
+ 		[SubCwR]		-> [^self computeSizeOfCwR].
+ 		[XorCwR]		-> [^self computeSizeOfCwR].
- 		[AddCqR]		-> [^(self isQuick: (operands at: 0))
- 											ifTrue: [4]
- 											ifFalse: [(self concreteRegister: (operands at: 1)) = RAX
- 														ifTrue: [6]
- 														ifFalse: [7]]].
- 		[AndCqR]		-> [^(self isQuick: (operands at: 0))
- 											ifTrue: [4]
- 											ifFalse: [(self concreteRegister: (operands at: 1)) = RAX
- 														ifTrue: [6]
- 														ifFalse: [7]]].
- 		[CmpCqR]		-> [^(self isQuick: (operands at: 0))
- 											ifTrue: [4]
- 											ifFalse: [(self concreteRegister: (operands at: 1)) = RAX
- 														ifTrue: [6]
- 														ifFalse: [7]]].
- 		[OrCqR]			-> [^(self isQuick: (operands at: 0))
- 											ifTrue: [4]
- 											ifFalse: [(self concreteRegister: (operands at: 1)) = RAX
- 														ifTrue: [6]
- 														ifFalse: [7]]].
- 		[SubCqR]		-> [^(self isQuick: (operands at: 0))
- 											ifTrue: [4]
- 											ifFalse: [(self concreteRegister: (operands at: 1)) = RAX
- 														ifTrue: [6]
- 														ifFalse: [7]]].
- 		[TstCqR]		-> [^(self isQuick: (operands at: 0))
- 											ifTrue: [4]
- 											ifFalse: [(self concreteRegister: (operands at: 1)) = RAX
- 														ifTrue: [6]
- 														ifFalse: [7]]].
- 		"[AddCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
- 		[AndCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
- 		[CmpCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
- 		[OrCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
- 		[SubCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
- 		[XorCwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]]."
  		[AddRR]			-> [^3].
  		[AndRR]			-> [^3].
  		[CmpRR]		-> [^3].
  		[OrRR]			-> [^3].
  		[XorRR]			-> [^3].
  		[SubRR]			-> [^3].
  		[NegateR]		-> [^3].
  		"[LoadEffectiveAddressMwrR]
  						-> [^((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[LogicalShiftLeftCqR]		-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
  		[LogicalShiftRightCqR]		-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]].
  		[ArithmeticShiftRightCqR]	-> [^(operands at: 0) = 1 ifTrue: [2] ifFalse: [3]]."
  		[LogicalShiftLeftRR]			-> [^self computeShiftRRSize].
  		[LogicalShiftRightRR]		-> [^self computeShiftRRSize].
  		[ArithmeticShiftRightRR]		-> [^self computeShiftRRSize].
  		[AddRdRd]					-> [^4].
  		[CmpRdRd]					-> [^4].
  		[SubRdRd]					-> [^4].
  		[MulRdRd]					-> [^4].
  		[DivRdRd]					-> [^4].
  		[SqrtRd]					-> [^4].
  		"Data Movement"
  		[MoveCqR]		-> [^(operands at: 0) = 0 ifTrue: [3] ifFalse: [(self is32BitSignedImmediate: (operands at: 0)) ifTrue: [7] ifFalse: [10]]].
  		[MoveCwR]		-> [^10].
  		[MoveRR]		-> [^3].
  		[MoveRdRd]		-> [^4].
  		"[MoveAwR]		-> [^(self concreteRegister: (operands at: 1)) = EAX ifTrue: [5] ifFalse: [6]].
  		[MoveRAw]		-> [^(self concreteRegister: (operands at: 0)) = EAX ifTrue: [5] ifFalse: [6]].
  		[MoveRMwr]	-> [^((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveRdM64r]	-> [^((self isQuick: (operands at: 1))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMbrR]		-> [^((self isQuick: (operands at: 0))
  											ifTrue: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveRMbr]		-> [^((self isQuick: (operands at: 1))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 2)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveM16rR]	-> [^((self isQuick: (operands at: 0))
  											ifTrue: [4]
  											ifFalse: [7])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveM64rRd]	-> [^((self isQuick: (operands at: 0))
  											ifTrue: [5]
  											ifFalse: [8])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveMwrR]		-> [^((self isQuick: (operands at: 0))
  											ifTrue: [3]
  											ifFalse: [6])
  										+ ((self concreteRegister: (operands at: 1)) = ESP
  											ifTrue: [1]
  											ifFalse: [0])].
  		[MoveXbrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^(self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [5]
  											ifFalse: [4]].
  		[MoveRXbrR]	->	[self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^((self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3])
  										+ ((self concreteRegister: (operands at: 0)) >= 4
  											ifTrue: [2]
  											ifFalse: [0])].
  		[MoveXwrRR]	-> [self assert: (self concreteRegister: (operands at: 0)) ~= ESP.
  							^(self concreteRegister: (operands at: 1)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[MoveRXwrR]	-> [self assert: (self concreteRegister: (operands at: 1)) ~= ESP.
  							^(self concreteRegister: (operands at: 2)) = EBP
  											ifTrue: [4]
  											ifFalse: [3]].
  		[PopR]			-> [^1].
  		[PushR]			-> [^1].
  		[PushCq]		-> [^(self isQuick: (operands at: 0)) ifTrue: [2] ifFalse: [5]].
  		[PushCw]		-> [^5].
  		[PrefetchAw]	-> [^self hasSSEInstructions ifTrue: [7] ifFalse: [0]]."
  		"Conversion"
  		"[ConvertRRd]	-> [^4]" }.
  	^0 "to keep C compiler quiet"!

Item was added:
+ ----- Method: CogX64Compiler>>computeSizeOfArithCqR (in category 'generate machine code') -----
+ computeSizeOfArithCqR
+ 	"With CqR we assume constants are 32-bits or less."
+ 	<inline: true>
+ 	^(self isQuick: (operands at: 0))
+ 		ifTrue: [4]
+ 		ifFalse: [(self concreteRegister: (operands at: 1)) = RAX
+ 					ifTrue: [6]
+ 					ifFalse: [7]]!

Item was added:
+ ----- Method: CogX64Compiler>>computeSizeOfArithCwR (in category 'generate machine code') -----
+ computeSizeOfArithCwR
+ 	"The implementation depends on in-line or out-of-line literals."
+ 	^self subclassResponsibility!

Item was removed:
- ----- Method: CogX64Compiler>>concretizeAt: (in category 'generate machine code') -----
- concretizeAt: actualAddress
- 	"Generate concrete machine code for the instruction at actualAddress,
- 	 setting machineCodeSize, and answer the following address."
- 
- 	address := actualAddress.
- 	self dispatchConcretize.
- 	self assert: (maxSize = nil or: [maxSize >= machineCodeSize]).
- 	^actualAddress + machineCodeSize!

Item was added:
+ ----- Method: CogX64Compiler>>genDivR:R:Quo:Rem: (in category 'abstract instructions') -----
+ genDivR: abstractRegDivisor R: abstractRegDividend Quo: abstractRegQuotient Rem: abstractRegRemainder
+ 	| rDividend rDivisor rQuotient rRemainder saveRestoreEAX saveRestoreEDX saveRestoreExchanged |
+ 	self assert: abstractRegDividend ~= abstractRegDivisor.
+ 	self assert: abstractRegQuotient ~= abstractRegRemainder.
+ 	rDividend := self concreteRegister: abstractRegDividend.
+ 	rDivisor := self concreteRegister: abstractRegDivisor.
+ 	rQuotient := self concreteRegister: abstractRegQuotient.
+ 	rRemainder := self concreteRegister: abstractRegRemainder.
+ 	"IDIV r does a signed divide of EDX:EAX by r, EAX := Quotient, EDX := Remainder.
+ 	 Since we must sign extend the dividend into EDX we must substitute another register if EDX is an input"
+ 	(rDividend = EDX or: [rDivisor = EDX]) ifTrue:
+ 		[| rUnused |
+ 		"Slang, sigh..."
+ 		rUnused := EAX.
+ 		[rUnused <= EDI] whileTrue:
+ 			[(rUnused ~= ESP and: [rUnused ~= EBP and: [rUnused ~= EDX
+ 			  and: [rUnused ~= rDividend and: [rUnused ~= rDivisor
+ 			  and: [rUnused ~= rQuotient and: [rUnused ~= rRemainder]]]]]]) ifTrue:
+ 				[cogit PushR: rUnused.
+ 				cogit MoveR: EDX R: rUnused.
+ 				rDividend = EDX
+ 					ifTrue: [self genDivR: rDivisor R: rUnused Quo: rQuotient Rem: rRemainder]
+ 					ifFalse: [self genDivR: rUnused R: rDividend Quo: rQuotient Rem: rRemainder].
+ 				cogit PopR: rUnused.
+ 				^self].
+ 			  rUnused := rUnused + 1].
+ 		self error: 'couldn''t find unused register in genDivR:R:Quo:Rem:'].
+ 	"If either output does not include EAX or EDX we must save and restore EAX and/or EDX."
+ 	(saveRestoreEAX := rQuotient ~= EAX and: [rRemainder ~= EAX]) ifTrue:
+ 		[cogit PushR: EAX].
+ 	(saveRestoreEDX := rQuotient ~= EDX and: [rRemainder ~= EDX]) ifTrue:
+ 		[cogit PushR: EDX].
+ 	saveRestoreExchanged := -1.
+ 	rDividend ~= EAX ifTrue:
+ 		[rDivisor = EAX
+ 			ifTrue: [((rDividend ~= rQuotient and: [rDividend ~= rRemainder])
+ 					and: [rDividend ~= EDX or: [saveRestoreEDX not]]) ifTrue:
+ 						[cogit PushR: (saveRestoreExchanged := rDividend)].
+ 					cogit gen: XCHGRR operand: rDivisor operand: rDividend]
+ 			ifFalse: [cogit MoveR: rDividend R: EAX]].
+ 	"CDQ sign-extends EAX into EDX as required for IDIV"
+ 	cogit gen: CDQ.
+ 	cogit gen: IDIVR operand: (rDivisor = EAX ifTrue: [rDividend] ifFalse: [rDivisor]).
+ 	"Must not overwrite result while juggling"
+ 	(rQuotient = EDX and: [rRemainder = EAX])
+ 		ifTrue: [cogit gen: XCHGRR operand: rQuotient operand: rRemainder]
+ 		ifFalse:
+ 			[rQuotient = EDX
+ 				ifTrue:
+ 					[rRemainder ~= EDX ifTrue:
+ 						[cogit MoveR: EDX R: rRemainder].
+ 					rQuotient ~= EAX ifTrue:
+ 						[cogit MoveR: EAX R: rQuotient]]
+ 				ifFalse:
+ 					[rQuotient ~= EAX ifTrue:
+ 						[cogit MoveR: EAX R: rQuotient].
+ 					rRemainder ~= EDX ifTrue:
+ 						[cogit MoveR: EDX R: rRemainder]]].
+ 	saveRestoreExchanged >= 0 ifTrue:
+ 		[cogit PopR: saveRestoreExchanged].
+ 	saveRestoreEDX ifTrue:
+ 		[cogit PopR: EDX].
+ 	saveRestoreEAX ifTrue:
+ 		[cogit PopR: EAX]!

Item was added:
+ ----- Method: CogX64Compiler>>genJumpFPEqual: (in category 'abstract instructions') -----
+ genJumpFPEqual: jumpTarget
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	<var: #jumpTarget type: #'void *'>
+ 	| jumpUnordered jumpToTarget |
+ 	<var: #jumpUnordered type: #'AbstractInstruction *'>
+ 	<var: #jumpToTarget type: #'AbstractInstruction *'>
+ 	jumpUnordered := cogit gen: JumpFPUnordered.
+ 	jumpToTarget := cogit gen: JumpFPEqual operand: jumpTarget asInteger.
+ 	jumpUnordered jmpTarget: cogit Label.
+ 	^jumpToTarget!

Item was added:
+ ----- Method: CogX64Compiler>>genJumpFPNotEqual: (in category 'abstract instructions') -----
+ genJumpFPNotEqual: jumpTarget
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	<var: #jumpTarget type: #'void *'>
+ 	| jumpUnordered jumpToTarget |
+ 	<var: #jumpUnordered type: #'AbstractInstruction *'>
+ 	<var: #jumpToTarget type: #'AbstractInstruction *'>
+ 	jumpToTarget := cogit gen: JumpFPNotEqual operand: jumpTarget asInteger.
+ 	jumpUnordered := cogit gen: JumpFPUnordered operand: jumpTarget asInteger.
+ 	jumpToTarget addDependent: jumpUnordered.
+ 	^jumpToTarget!

Item was added:
+ ----- Method: CogX64Compiler>>genMulR:R: (in category 'abstract instructions') -----
+ genMulR: regSource R: regDest
+ 	cogit gen: IMULRR operand: regSource operand: regDest!

Item was added:
+ ----- Method: CogX64Compiler>>genSubstituteReturnAddress: (in category 'abstract instructions') -----
+ genSubstituteReturnAddress: retpc
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^cogit PushCw: retpc!

Item was added:
+ ----- Method: CogX64Compiler>>maybeEstablishVarBase (in category 'abstract instructions') -----
+ maybeEstablishVarBase
+ 	"The receiver does not have a VarBaseReg; do nothing."!

Item was added:
+ ----- Method: CogX64CompilerForTests>>concretizeAt: (in category 'generate machine code') -----
+ concretizeAt: actualAddress
+ 	"Override to check maxSize and machineCodeSize"
+ 
+ 	| result |
+ 	maxSize ifNil: [maxSize := self computeMaximumSize].
+ 	result := super concretizeAt: actualAddress.
+ 	self assert: (maxSize notNil
+ 				and: [self isPCDependent
+ 						ifTrue: [maxSize >= machineCodeSize]
+ 						ifFalse: [maxSize = machineCodeSize]]).
+ 	^result!

Item was changed:
  ----- Method: CogX64CompilerTests>>testAndCqR (in category 'tests') -----
  testAndCqR
  	"self new testAndCqR"
  	self concreteCompilerClass registersWithNamesDo:
  		[:reg :regname|
+ 		#(16r1 16r3 16r7 16r555555 16rAAAAAA) do:
- 		#(16r1 16r3 16r7 16r555555 16rAAAAAA "16r55AA55AA55AA 16rAA55AA55AA55 no 64-bit constant support with AndC") do:
  			[:const| | inst len|
  			inst := self gen: AndCqR operand: const operand: reg.
  			len := inst concretizeAt: 0.
  			self processor
  				disassembleInstructionAt: 0
  				In: inst machineCode object
  				into: [:str :sz| | plainJane herIntended |
+ 					"Convert e.g. '00000000: movl %rax, 0x2(%rax) : 48 89 40 02' to  'movl %rax, 0x2(%rax)'"
- 					"Convert e.g. '00000000: movq %rax, 0x2(%rax) : 89 40 02' to  'movl %rax, 0x2(%rax)'"
  					plainJane := self strip: str.
+ 					herIntended := 'andl $0x', (const printStringBase: 16 length: 16 padded: true), ', ', regname.
- 					herIntended := 'andq $0x', (const printStringBase: 16 length: 16 padded: true), ', ', regname.
  					self assert: (plainJane match: herIntended).
  					self assert: len = sz]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testArithmeticShiftRightRR (in category 'tests') -----
+ testArithmeticShiftRightRR
+ 	"CogX64CompilerTests new testArithmeticShiftRightRR"
+ 	self concreteCompilerClass dataRegistersWithAccessorsDo:
+ 		[:sreg :srgetter :srsetter|
+ 		self concreteCompilerClass dataRegistersWithAccessorsDo:
+ 			[:dreg :drgetter :drsetter| | inst len |
+ 			inst := self gen: ArithmeticShiftRightRR operand: sreg operand: dreg.
+ 			len := inst concretizeAt: 0.
+ 			self assert: len = (srgetter = #rcx
+ 								ifTrue: [3]
+ 								ifFalse:
+ 									[srgetter = #rax
+ 										ifTrue: [5]
+ 										ifFalse: [7]])
+ 			"self processor disassembleFrom: 0 to: inst machineCodeSize in: inst machineCode object on: Transcript"]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testCMPXCHGAwR (in category 'tests') -----
+ testCMPXCHGAwR
+ 	"self new testCMPXCHGAwR"
+ 	| cmpxchgAwR |
+ 	cmpxchgAwR := CogX64Compiler classPool at: #CMPXCHGAwR.
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:reg :regname|
+ 		#(16r555555 16rAAAAAA) do:
+ 			[:addr| | inst len |
+ 			inst := self gen: cmpxchgAwR operand: addr operand: reg.
+ 			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 := 'cmpxchgl ', regname, ', 0x', (addr hex allButFirst: 3).
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testCMPXCHGMwrR (in category 'tests') -----
+ testCMPXCHGMwrR
+ 	"self new testCMPXCHGMwrR"
+ 	| cmpxchgMwrR lock |
+ 	cmpxchgMwrR := CogX64Compiler classPool at: #CMPXCHGMwrR.
+ 	lock := CogX64Compiler classPool at: #LOCK.
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset|
+ 				#(false true) do:
+ 					[:prefixLock| | memory |
+ 					self resetGen.
+ 					prefixLock ifTrue: [self gen: lock].
+ 					self gen: cmpxchgMwrR operand: offset operand: sreg operand: dreg.
+ 					memory := self generateInstructions.
+ 					self processor
+ 						disassembleInstructionAt: 0
+ 						In: memory
+ 						into: [:str :sz| | plainJane herIntended |
+ 							plainJane := self strip: str.
+ 							herIntended := (prefixLock ifTrue: ['lock '] ifFalse: ['']),
+ 											'cmpxchgl ', drname, ', 0x', (offset hex allButFirst: 3), '(', srname, ')'.
+ 							self assert: (plainJane match: herIntended).
+ 							self assert: memory size = sz]]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testDivQuoRem (in category 'tests') -----
+ testDivQuoRem
+ 	"| failures ops |
+ 	 failures := Set new.
+ 	 [ops := (CogX64CompilerTests new testDivQuoRem)]
+ 		on: TestResult failure
+ 		do: [:ex| | c |
+ 			c := ex signalerContext.
+ 			[c tempNames includes: 'op'] whileFalse:
+ 				[c := c sender].
+ 			failures add: (c namedTempAt: (c tempNames indexOf: 'op')).
+ 			ex resume].
+ 	 { ops size. failures size. ops asSortedCollection asArray. failures asSortedCollection asArray}"
+ 	| map compiler memory ops |
+ 	map := Dictionary new.
+ 	compiler := self gen: nil.
+ 	memory := ByteArray new: 4096 * 2.
+ 	ops := Set new.
+ 	self concreteCompilerClass dataRegistersWithAccessorsExcept: #(rbp rsp) do:
+ 		[:sreg :srget :srset|
+ 		self concreteCompilerClass dataRegistersWithAccessorsExcept: { #rbp. #rsp. srget } do:
+ 			[:dreg :drget :drset|
+ 			 | instructions op |
+ 			self concreteCompilerClass dataRegistersWithAccessorsExcept: #(rbp rsp) do:
+ 				[:qreg :qrget :qrset| 
+ 				self concreteCompilerClass dataRegistersWithAccessorsExcept: { #rbp. #rsp. qrget } do:
+ 					[:rreg :rrget :rrset|
+ 					self resetGen.
+ 					op := qrget, ' := ', drget, ' quo: ', srget, '. ', rrget, ' := ', drget, ' rem: ', srget.
+ 					ops add: op.
+ 					compiler genDivR: sreg R: dreg Quo: qreg Rem: rreg.
+ 					instructions := self generateInstructions.
+ 					memory atAllPut: 0; replaceFrom: 1 to: instructions size with: instructions startingAt: 1; at: instructions size + 1 put: self processor nopOpcode.
+ 					#(-768 -456 -123 123 456 789)
+ 						with: #(987 654 321 -321 -654 -987)
+ 						do: [:dd :dv| "| calc |
+ 							calc := ((dd quo: dv) bitAnd: 16rFFFFFFFF) hex, ' := ', (dd bitAnd: 16rFFFFFFFF) hex, ' quo: ', (dv bitAnd: 16rFFFFFFFF) hex, '. ', ((dd rem: dv) bitAnd: 16rFFFFFFFF) hex, ' := ', (dd bitAnd: 16rFFFFFFFF) hex, ' rem: ', (dv bitAnd: 16rFFFFFFFF) hex.
+ 							calc := calc."
+ 							"Transcript cr; cr; nextPutAll: op; cr; nextPutAll: calc; cr.
+ 							 self processor
+ 								disassembleFrom: 0 to: instructions size in: memory on: Transcript;
+ 								printIntegerRegistersOn: Transcript."
+ 							map
+ 								at: #rax put: (self processor rax: 16rA5A5A5A5);
+ 								at: #rbx put: (self processor rbx: 16rB5B5B5B5);
+ 								at: #rcx put: (self processor rcx: 16rC5C5C5C5);
+ 								at: #rdx put: (self processor rdx: 16rD5D5D5D5);
+ 								at: #rsi put: (self processor rsi: 16r51515151);
+ 								at: #rdi put: (self processor rdi: 16rD1D1D1D1);
+ 								at: srget put: (self processor perform: srset with: (self processor convertIntegerToInternal: dv));
+ 								at: drget put: (self processor perform: drset with: (self processor convertIntegerToInternal: dd)).
+ 							self processor rsp: memory size; rip: 0.
+ 							self shouldnt:
+ 								[[self processor pc < instructions size] whileTrue:
+ 									[self processor singleStepIn: memory readExecuteOnlyBelow: memory size / 2]]
+ 								raise: Error.
+ 							map
+ 								at: qrget put: (self processor convertIntegerToInternal: (dd quo: dv));
+ 								at: rrget put: (self processor convertIntegerToInternal: (dd rem: dv)).
+ 							map keysAndValuesDo:
+ 								[:accessor :value|
+ 								self assert: value = (self processor perform: accessor)]]]]]].
+ 	^ops!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveAwR (in category 'tests') -----
+ testMoveAwR
+ 	"self new testMoveAwR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:reg :regname|
+ 		#(16r555555 16rAAAAAA) do:
+ 			[:addr| | inst len |
+ 			inst := self gen: MoveAwR operand: addr operand: reg.
+ 			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 := 'movl 0x', (addr hex allButFirst: 3), ', ', regname.
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveM64rRd (in category 'tests') -----
+ testMoveM64rRd
+ 	"self new testMoveM64rRd"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass xmmRegistersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveM64rRd operand: offset operand: sreg operand: dreg.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'movsd 0x', (offset hex allButFirst: 3), '(', srname, '), ', drname.
+ 						self assert: (plainJane match: herIntended).
+ 						self assert: len = sz]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveMbrR (in category 'tests') -----
+ testMoveMbrR
+ 	"self new testMoveMbrR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveMbrR operand: offset operand: sreg operand: dreg.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'movzbl 0x', (offset hex allButFirst: 3), '(', srname, '), ', drname.
+ 						self assert: (plainJane match: herIntended).
+ 						self assert: len = sz]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveMwrR (in category 'tests') -----
+ testMoveMwrR
+ 	"self new testMoveMwrR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname| | inst len |
+ 			inst := self gen: MoveMwrR operand: 0 operand: sreg operand: dreg.
+ 			len := inst concretizeAt: 0.
+ 			self processor
+ 				disassembleInstructionAt: 0
+ 				In: inst machineCode object
+ 				into: [:str :sz| | plainJane herIntended |
+ 					plainJane := self strip: str.
+ 					herIntended := 'movl (', srname, '), ', drname.
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveRAw (in category 'tests') -----
+ testMoveRAw
+ 	"self new testMoveRAw"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:reg :regname|
+ 		#(16r555555 16rAAAAAA) do:
+ 			[:addr| | inst len |
+ 			inst := self gen: MoveRAw operand: reg operand: addr.
+ 			len := inst concretizeAt: 0.
+ 			self processor
+ 				disassembleInstructionAt: 0
+ 				In: inst machineCode object
+ 				into: [:str :sz| | plainJane herIntended |
+ 					plainJane := self strip: str.
+ 					herIntended := 'movl ', regname, ', 0x', (addr hex allButFirst: 3).
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveRMbr (in category 'tests') -----
+ testMoveRMbr
+ 	"self new testMoveRMbr"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :srname| | brname |
+ 		sreg < 4 ifTrue:
+ 			[brname := #('%al' '%cl' '%dl' '%bl') at: sreg + 1.
+ 			self concreteCompilerClass registersWithNamesDo:
+ 				[:dreg :drname|
+ 				((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 					[:offset| | inst len |
+ 					inst := self gen: MoveRMbr operand: sreg operand: offset operand: dreg.
+ 					len := inst concretizeAt: 0.
+ 					self processor
+ 						disassembleInstructionAt: 0
+ 						In: inst machineCode object
+ 						into: [:str :sz| | plainJane herIntended |
+ 							plainJane := self strip: str.
+ 							herIntended := 'movb ', brname, ', 0x', (offset hex allButFirst: 3), '(', drname, ')'.
+ 							self assert: (plainJane match: herIntended).
+ 							self assert: len = sz]]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveRMwr (in category 'tests') -----
+ testMoveRMwr
+ 	"self new testMoveRM0wr"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname| | inst len |
+ 			inst := self gen: MoveRMwr operand: sreg operand: 0 operand: dreg.
+ 			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 := 'movl ', srname, ', (',drname,')'.
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveRdM64r (in category 'tests') -----
+ testMoveRdM64r
+ 	"self new testMoveRdM64r"
+ 	self concreteCompilerClass xmmRegistersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | inst len |
+ 				inst := self gen: MoveRdM64r operand: sreg operand: offset operand: dreg.
+ 				len := inst concretizeAt: 0.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: inst machineCode object
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'movsd ', srname, ', 0x', (offset hex allButFirst: 3), '(', drname, ')'.
+ 						self assert: (plainJane match: herIntended).
+ 						self assert: len = sz]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveXbrRR (in category 'tests') -----
+ testMoveXbrRR
+ 	"self new testMoveXbrRR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:idxreg :irname|
+ 			irname ~= '%esp' ifTrue:
+ 				[self concreteCompilerClass registersWithNamesDo:
+ 					[:basereg :brname|
+ 					self concreteCompilerClass registersWithNamesDo:
+ 						[:dreg :drname|
+ 						((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 							[:offset| | inst len |
+ 							inst := self gen: MoveXbrRR operand: idxreg operand: basereg operand: dreg.
+ 							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 := 'movzbl (', brname, ',', irname, ',1), ',drname.
+ 									self assert: (plainJane match: herIntended).
+ 									self assert: len = sz]]]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMoveXwrRR (in category 'tests') -----
+ testMoveXwrRR
+ 	"self new testMoveXwrRR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:idxreg :irname|
+ 			irname ~= '%esp' ifTrue:
+ 				[self concreteCompilerClass registersWithNamesDo:
+ 					[:basereg :brname|
+ 					self concreteCompilerClass registersWithNamesDo:
+ 						[:dreg :drname|
+ 						((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 							[:offset| | inst len |
+ 							inst := self gen: MoveXwrRR operand: idxreg operand: basereg operand: dreg.
+ 							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 := 'movl (', brname, ',', irname, ',4), ',drname.
+ 									self assert: (plainJane match: herIntended).
+ 									self assert: len = sz]]]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testMul (in category 'tests') -----
+ testMul
+ 	"CogX64CompilerTests new setUp testMul"
+ 	| map compiler memory |
+ 	map := Dictionary new.
+ 	compiler := self gen: nil.
+ 	memory := ByteArray new: 1024.
+ 	self concreteCompilerClass dataRegistersWithAccessorsExcept: #(rbp rsp) do:
+ 		[:sreg :srget :srset|
+ 		self concreteCompilerClass dataRegistersWithAccessorsExcept: { #rbp. #rsp. srget } do:
+ 			[:dreg :drget :drset| | instructions |
+ 			self resetGen.
+ 			compiler genMulR: sreg R: dreg.
+ 			instructions := self generateInstructions.
+ 			memory atAllPut: 0; replaceFrom: 1 to: instructions size with: instructions startingAt: 1.
+ 			#(-768 -456 -123 123 456 789)
+ 				with: #(987 654 321 -321 -654 -987)
+ 				do: [:a :b|
+ 					"self processor
+ 						disassembleFrom: 0 to: instructions size in: memory on: Transcript;
+ 						printIntegerRegistersOn: Transcript."
+ 					map
+ 						at: #eax put: (self processor eax: 16rA5A5A5A5);
+ 						at: #ebx put: (self processor ebx: 16rB5B5B5B5);
+ 						at: #ecx put: (self processor ecx: 16rC5C5C5C5);
+ 						at: #edx put: (self processor edx: 16rD5D5D5D5);
+ 						at: #esi put: (self processor esi: 16r51515151);
+ 						at: #edi put: (self processor edi: 16rD1D1D1D1);
+ 								at: srget put: (self processor perform: srset with: (self processor convertIntegerToInternal: b));
+ 								at: drget put: (self processor perform: drset with: (self processor convertIntegerToInternal: a)).
+ 					self processor esp: memory size; eip: 0.
+ 					self shouldnt:
+ 						[[self processor pc < instructions size] whileTrue:
+ 							[self processor singleStepIn: memory]]
+ 						raise: Error.
+ 					map at: drget put: (self processor convertIntegerToInternal: (a * b)).
+ 					map keysAndValuesDo:
+ 						[:accessor :value|
+ 						self assert: value = (self processor perform: accessor)]]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testTstCqR (in category 'tests') -----
+ testTstCqR
+ 	"self new testTstCqR"
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:reg :theRegname|
+ 		#(16r1 16r3 16r7 16r555555 16rAAAAAA) do:
+ 			[:const| | op regname inst len constString|
+ 			inst := self gen: TstCqR operand: const operand: reg.
+ 			len := inst concretizeAt: 0.
+ 			((inst isQuick: const) and: [reg < 4])
+ 				ifTrue:
+ 					[op := 'testb'.
+ 					 regname := #('%al' '%cl' '%dl' '%bl') at: reg + 1.
+ 					 constString := const printStringBase: 16 length: 2 padded: true]
+ 				ifFalse:
+ 					[op := 'testl'.
+ 					 regname := theRegname.
+ 					 constString := const printStringBase: 16 length: 8 padded: true].
+ 			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 := op, ' $0x', constString, ', ', regname.
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testXCHGAwR (in category 'tests') -----
+ testXCHGAwR
+ 	"self new testXCHGAwR"
+ 	| xchgAwR |
+ 	xchgAwR := CogX64Compiler classPool at: #XCHGAwR.
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:reg :regname|
+ 		#(16r555555 16rAAAAAA) do:
+ 			[:addr| | inst len |
+ 			inst := self gen: xchgAwR operand: addr operand: reg.
+ 			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 := 'xchgl ', regname, ', 0x', (addr hex allButFirst: 3).
+ 					self assert: (plainJane match: herIntended).
+ 					self assert: len = sz]]]!

Item was added:
+ ----- Method: CogX64CompilerTests>>testXCHGMwrR (in category 'tests') -----
+ testXCHGMwrR
+ 	"self new testXCHGMwrR"
+ 	| xchgMwrR |
+ 	xchgMwrR := CogX64Compiler classPool at: #XCHGMwrR.
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:sreg :srname|
+ 		self concreteCompilerClass registersWithNamesDo:
+ 			[:dreg :drname|
+ 			((1 to: 19 by: 3) collect: [:po2| 2 raisedToInteger: po2]) do:
+ 				[:offset| | memory |
+ 				self resetGen.
+ 				self gen: xchgMwrR operand: offset operand: sreg operand: dreg.
+ 				memory := self generateInstructions.
+ 				self processor
+ 					disassembleInstructionAt: 0
+ 					In: memory
+ 					into: [:str :sz| | plainJane herIntended |
+ 						plainJane := self strip: str.
+ 						herIntended := 'xchgl ', drname, ', 0x', (offset hex allButFirst: 3), '(', srname, ')'.
+ 						self assert: (plainJane match: herIntended).
+ 						self assert: memory size = sz]]]]!



More information about the Vm-dev mailing list