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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 2 07:23:32 UTC 2015


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

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

Name: VMMaker.oscog-eem.1538
Author: eem
Time: 1 December 2015, 11:21:52.981 pm
UUID: 8eb28260-86bc-4f74-b62d-aab8212d9272
Ancestors: VMMaker.oscog-rmacnak.1537

Cogit:
Fix /horrible/ bug with primitive error codes and fixups.  The adjustment of the initialPC to skip the primitive and error code, if any, was done after generating fixups for backward branches, and hence these branches were bogus.  Object>>shallowCopy in Spur is subject to this, but amazingly enough it has not surfaced before now.  Fix this by adjusting the initialPC before scanMethod scans for fixups.

Add MoveRRd & MoveRdR for eventual use in 64-bit Spur immediate float primitives.

Implement ConvertRRd for x64, and make a stab at implementing MoveM64rRd, but this is falling foul of a disassembler bug with Bochs 2.3.7, the current Bochs code base :-(.

Add the additional 8 xmm registers to x64.

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

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

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 printFormatForOpcodeName: opcodeName]
+ 				on: Error
+ 				do: [:ex| ].
- 	(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: CogIA32CompilerForTests class>>registers (in category 'test support') -----
  registers
+ 	^(0 to: 7) "a.k.a. { EAX. ECX. EDX. EBX. ESP. EBP. ESI. EDI }"!
- 	^{ EAX. ECX. EDX. EBX. ESP. EBP. ESI. EDI } "a.k.a. (0 to: 7)"!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call CallFull ClassReg CmpC32R CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpFull JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg Literal LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRRd MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdR MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCq PushCw PushR RISCTempReg ReceiverResultReg RetN SPReg Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg Scratch6Reg Scratch7Reg SendNumArgsReg SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call CallFull ClassReg CmpC32R CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpFull JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg Literal LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCq PushCw PushR RISCTempReg ReceiverResultReg RetN SPReg Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg Scratch6Reg Scratch7Reg SendNumArgsReg SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg XorCqR XorCwR XorRR'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogRTLOpcodes commentStamp: '<historical>' prior: 0!
  I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes and abstract registers.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
  initialize
  	"Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers.
  	 e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to
  	 register instruction from operand 0 to operand 1.  The word and register size is assumed to be either 32-bits on
  	 a 32-bit architecture or 64-bits on a 64-bit architecture.  The abstract machine is mostly a 2 address machine
  	 with the odd three address instruction added to better exploit RISCs.
  			(self initialize)
  	The operand specifiers are
  		R		- general purpose register
  		Rd		- double-precision floating-point register
  		Cq		- a `quick' constant that can be encoded in the minimum space possible.
  		Cw		- a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits
  				  for a 32-bit VM, 64-bits for a 64-bit VM.  The generated constant must occupy the default number
  				  of bits.  This allows e.g. a garbage collector to update the value without invalidating the code.
  		C32	- a constant with 32 bit size.  The generated constant must occupy 32 bits.
  		C64	- a constant with 64 bit size.  The generated constant must occupy 64 bits.
  		Aw		- memory word at an absolute address
  		Ab		- memory byte at an absolute address
  		Mwr	- memory word whose address is at a constant offset from an address in a register
  		Mbr		- memory byte whose address is at a constant offset from an address in a register (zero-extended on read)
  		M16r	- memory 16-bit halfword whose address is at a constant offset from an address in a register
  		M32r	- memory 32-bit halfword whose address is at a constant offset from an address in a register
  		M64r	- memory 64-bit doubleword whose address is at a constant offset from an address in a register
  		XbrR	- memory word whose address is r * byte size away from an address in a register
  		X16rR	- memory word whose address is r * (2 bytes size) away from an address in a register
  		X32rR	- memory word whose address is r * (4 bytes size) away from an address in a register
  		XwrR	- memory word whose address is r * word size away from an address in a register
  		XowrR	- memory word whose address is (r * word size) + o away from an address in a register (scaled indexed)
  
  	An alternative would be to decouple opcodes from operands, e.g.
  		Move := 1. Add := 2. Sub := 3...
  		RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3...
  	But not all combinations make sense and even fewer are used so we stick with the simple compound approach.
  
  	The assumption is that comparison and arithmetic instructions set condition codes and that move instructions
  	leave the condition codes unaffected.  In particular LoadEffectiveAddressMwrR does not set condition codes
+ 	although it can be used to do arithmetic.  On processors such as MIPS this distinction is invalid; there are no
+ 	condition codes.  So the backend is allowed to collapse operation, branch pairs to internal instruciton definitions
+ 	(see sender and implementors of noteFollowingConditionalBranch:). 
- 	although it can be used to do arithmetic.
  
  	Not all of the definitions in opcodeDefinitions below are implemented.  In particular we do not implement the
  	XowrR scaled index addressing mode since it requires 4 operands.
  
+ 	Not all instructions make sense on all architectures.  MoveRRd and MoveRdR aqre meaningful only on 64-bit machines.
+ 
  	Note that there are no generic division instructions defined, but a processor may define some.
  
  	Branch/Call ranges.  Jump[Cond] can be generated as short as possible.  Call/Jump[Cond]Long must be generated
  	in the same number of bytes irrespective of displacement since their targets may be updated, but they need only
  	span 16Mb, the maximum size of the code zone.  This allows e.g. ARM to use single-word call and jump instructions
  	for most calls and jumps.  CallFull/JumpFull must also be generated in the same number of bytes irrespective of
  	displacement for the same reason, but they must be able to span the full (32-bit or 64-bit) address space because
  	they are used to call code in the C runtime, which may be distant from the code zone.  CallFull/JumpFull are allowed
  	to use the cResultRegister as a scratch if required (e.g. on x64 where there is no direct 64-bit call or jump).
  
  	Byte reads.  If the concrete compiler class answers true to byteReadsZeroExtend then byte reads must zero-extend
  	the byte read into the destination register.  If not, the other bits of the register should be left undisturbed and the
  	Cogit will add an instruction to zero the register as required.  Under no circumstances should byte reads sign-extend.
  
  	16-bit (and on 64-bits, 32-bit) reads.  These /are/ expected to always zero-extend."
  
  	| opcodeNames refs |
  	"A small fixed set of abstract registers are defined and used in code generation
  	 for Smalltalk code, and executes on stack pages in the stack zone.
  	 These are mapped to processor-specific registers by concreteRegister:"
  	FPReg := -1.	"A frame pointer is used for Smalltalk frames."
  	SPReg := -2.
  	ReceiverResultReg := -3.		"The receiver at point of send, and return value of a send"
  	TempReg := -4.
  	ClassReg := -5.					"The inline send cache class tag is in this register, loaded at the send site"
  	SendNumArgsReg := -6.		"Sends > 2 args set the arg count in this reg"
  	Arg0Reg := -7.					"In the StackToRegisterMappingCogit 1 & 2 arg sends marshall into these registers."
  	Arg1Reg := -8.
  
  	"A small fixed set of abstract scratch registers for register-rich machines (ARM can use 1, x64 can use 6)."
  	Scratch0Reg := -9.
  	Scratch1Reg := -10.
  	Scratch2Reg := -11.
  	Scratch3Reg := -12.
  	Scratch4Reg := -13.
  	Scratch5Reg := -14.
  	Scratch6Reg := -15.
  	Scratch7Reg := -16.
  
  	"RISC-specific registers"
  	LinkReg := -17.
  	RISCTempReg := -18.	"Used to synthesize CISC instructions from multiple RISC instructions."
  	PCReg := -19.
  	VarBaseReg := -20.		"If useful, points to base of interpreter variables."
  
  	"Floating-point registers"
  	DPFPReg0 := -21.
  	DPFPReg1 := -22.
  	DPFPReg2 := -23.
  	DPFPReg3 := -24.
  	DPFPReg4 := -25.
  	DPFPReg5 := -26.
  	DPFPReg6 := -27.
  	DPFPReg7 := -28.
  
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						Literal			"a word-sized literal"
  						AlignmentNops
  						FillBytesFrom	"output operand 0's worth of bytes from the address in operand 1"
  						Fill8				"output a byte's worth of bytes with operand 0"
  						Fill16			"output two byte's worth of bytes with operand 0"
  						Fill32			"output four byte's worth of bytes with operand 0"
  						FillFromWord	"output BytesPerWord's worth of bytes with operand 0 + operand 1"
  						Nop
  
  						"Control"
  						Call					"call within the code zone"
  						CallFull				"call anywhere within the full address space"
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  						Stop				"Halt the processor"
  
  						"N.B.  Jumps are contiguous.  Long and Full jumps are contigiuous within them.  See FirstJump et al below"
  						JumpFull			"Jump anywhere within the address space"
  						JumpLong			"Jump anywhere within the 16mb code zone."
  						JumpLongZero			"a.k.a. JumpLongEqual"
  						JumpLongNonZero		"a.k.a. JumpLongNotEqual"
  						Jump				"short jumps; can be encoded in as few bytes as possible; will not be disturbed by GC or relocation."
  						JumpZero				"a.k.a. JumpEqual"
  						JumpNonZero			"a.k.a. JumpNotEqual"
  						JumpNegative
  						JumpNonNegative
  						JumpOverflow
  						JumpNoOverflow
  						JumpCarry
  						JumpNoCarry
  						JumpLess			"signed"
  						JumpGreaterOrEqual
  						JumpGreater
  						JumpLessOrEqual
  						JumpBelow			"unsigned"
  						JumpAboveOrEqual
  						JumpAbove
  						JumpBelowOrEqual
  
  						JumpFPEqual
  						JumpFPNotEqual
  						JumpFPLess
  						JumpFPLessOrEqual
  						JumpFPGreater
  						JumpFPGreaterOrEqual
  						JumpFPOrdered
  						JumpFPUnordered
  
  						"Data Movement; destination is always last operand"
  						MoveRR
  						MoveAwR
  						MoveRAw
  						MoveAbR
  						MoveRAb
  						MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR MoveXowrR MoveRXowr
  						MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR
  						MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR
  						MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR
  						MoveCqR MoveCwR MoveC32R MoveC64R
+ 						MoveRRd MoveRdR MoveRdRd MoveM64rRd MoveRdM64r
- 						MoveRdRd MoveM64rRd MoveRdM64r
  						PopR PushR PushCq PushCw
  						PrefetchAw
  
  						"Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result"
  						LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR "Variants of add/multiply"
  						NegateR "2's complement negation"
  						ArithmeticShiftRightCqR ArithmeticShiftRightRR
  						LogicalShiftRightCqR LogicalShiftRightRR
  						LogicalShiftLeftCqR LogicalShiftLeftRR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR TstCqR XorCqR
  						CmpCwR CmpC32R AddCwR SubCwR AndCwR OrCwR XorCwR
  
  						AndCqRR
  
  						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd SqrtRd
  
  						"Conversion"
  						ConvertRRd
  
  						LastRTLCode).
  
  	"Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values"
  	"Find the variables directly referenced by this method"
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	"Move to Undeclared any opcodes in classPool not in opcodes or this method."
  	(classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	"Declare as class variables and number elements of opcodeArray above"
  	opcodeNames withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value].
  
  	"For CogAbstractInstruction>>isJump etc..."
  	FirstJump := JumpFull.
  	LastJump := JumpFPUnordered.
  	FirstShortJump := Jump.
  
  	"And now initialize the backends; they add their own opcodes and hence these must be reinitialized."
  	(Smalltalk classNamed: #CogAbstractInstruction) ifNotNil:
  		[:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]!

Item was changed:
  ----- Method: CogRTLOpcodes class>>nameForRegister: (in category 'debug printing') -----
  nameForRegister: reg "<Integer>"
  	^#(Arg0Reg Arg1Reg ClassReg FPReg ReceiverResultReg SPReg SendNumArgsReg TempReg
  		DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7
  		LinkReg RISCTempReg VarBaseReg PCReg)
+ 			detect: [:sym| (classPool at: sym) = reg]
+ 			ifNone: ['REG', reg printString, '?']!
- 			detect: [:sym| (classPool at: sym) = reg]!

Item was changed:
  CogAbstractInstruction subclass: #CogX64Compiler
  	instanceVariableNames: ''
+ 	classVariableNames: 'ABI CDQ CMPXCHGAwR CMPXCHGMwrR CPUID IDIVR IMULRR LFENCE LOCK MFENCE ModReg ModRegInd ModRegIndDisp32 ModRegIndSIB ModRegRegDisp32 ModRegRegDisp8 R10 R11 R12 R13 R14 R15 R8 R9 RAX RBP RBX RCX RDI RDX RSI RSP SFENCE SIB1 SIB2 SIB4 SIB8 XCHGAwR XCHGMwrR XCHGRR XMM0H XMM0L XMM10H XMM10L XMM11H XMM11L XMM12H XMM12L XMM13H XMM13L XMM14H XMM14L XMM15H XMM15L XMM1H XMM1L XMM2H XMM2L XMM3H XMM3L XMM4H XMM4L XMM5H XMM5L XMM6H XMM6L XMM7H XMM7L XMM8H XMM8L XMM9H XMM9L'
- 	classVariableNames: 'ABI CDQ CMPXCHGAwR CMPXCHGMwrR CPUID IDIVR IMULRR LFENCE LOCK MFENCE ModReg ModRegInd ModRegIndDisp32 ModRegIndSIB ModRegRegDisp32 ModRegRegDisp8 R10 R11 R12 R13 R14 R15 R8 R9 RAX RBP RBX RCX RDI RDX RSI RSP SFENCE SIB1 SIB2 SIB4 SIB8 XCHGAwR XCHGMwrR XCHGRR XMM0H XMM0L XMM1H XMM1L XMM2H XMM2L XMM3H XMM3L XMM4H XMM4L XMM5H XMM5L XMM6H XMM6L XMM7H XMM7L'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogX64Compiler commentStamp: 'eem 9/14/2015 17:12' prior: 0!
  I generate x64 (x86-64) instructions from CogAbstractInstructions.  For reference see
  1. IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M
  2. IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, N-Z
  	http://www.intel.com/products/processor/manuals/
  or
  AMD64 Architecture Programmer's Manual Volume 3: General-Purpose and System Instructions
  AMD64 Architecture Programmer's Manual Volume 4: 128-bit Media Instructions
  AMD64 Architecture Programmer's Manual Volume 5: 64-bit Media and x87 Floating Point Instructions
  	http://developer.amd.com/resources/documentation-articles/developer-guides-manuals/
  (® is supposed to be the Unicode "registered  sign").!

Item was changed:
  ----- Method: CogX64Compiler class>>initialize (in category 'class initialization') -----
  initialize
  	"Initialize various x64 instruction-related constants.
  	 [1] IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M"
  
  	"CogX64Compiler initialize"
  
  	self ~~ CogX64Compiler ifTrue: [^self].
  
  	ABI ifNil:
  		[ABI := #SysV]. "Default ABI; other choice is #MSVC"
  
  	RAX := 0.
  	RCX := 1.  "Were they completely mad or simply sadistic?"
  	RDX := 2.
  	RBX := 3.
  	RSP := 4.
  	RBP := 5.
  	RSI := 6.
  	RDI := 7.
  	R8 := 8.
  	R9 := 9.
  	R10 := 10.
  	R11 := 11.
  	R12 := 12.
  	R13 := 13.
  	R14 := 14.
  	R15 := 15.
  
  	XMM0L := 0.
  	XMM1L := 2.
  	XMM2L := 4.
  	XMM3L := 6.
  	XMM4L := 8.
  	XMM5L := 10.
  	XMM6L := 12.
  	XMM7L := 14.
+ 	XMM8L := 16.
+ 	XMM9L := 18.
+ 	XMM10L := 20.
+ 	XMM11L := 22.
+ 	XMM12L := 24.
+ 	XMM13L := 26.
+ 	XMM14L := 28.
+ 	XMM15L := 30.
  
  	XMM0H := 1.
  	XMM1H := 3.
  	XMM2H := 5.
  	XMM3H := 7.
  	XMM4H := 9.
  	XMM5H := 11.
  	XMM6H := 13.
  	XMM7H := 15.
+ 	XMM8H := 17.
+ 	XMM9H := 19.
+ 	XMM10H := 21.
+ 	XMM11H := 23.
+ 	XMM12H := 25.
+ 	XMM13H := 27.
+ 	XMM14H := 29.
+ 	XMM15H := 31.
  
  	"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"
  	self
  		initializeSpecificOpcodes: #(CDQ IDIVR IMULRR CPUID LFENCE MFENCE SFENCE LOCK CMPXCHGAwR CMPXCHGMwrR XCHGAwR XCHGMwrR XCHGRR)
  		in: thisContext method!

Item was changed:
  ----- Method: CogX64Compiler>>computeMaximumSize (in category 'generate machine code') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: CogX64Compiler>>concreteDPFPRegister: (in category 'encoding') -----
  concreteDPFPRegister: registerIndex
  	 "Map a possibly abstract double-precision floating-point register into a concrete one.
  	  Abstract registers (defined in CogAbstractOpcodes) are all negative.  If registerIndex
  	  is negative assume it is an abstract register.
  
  	[1] IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M"
  
  	^registerIndex
  		caseOf: {
  			[DPFPReg0]	-> [XMM0L / 2].
  			[DPFPReg1]	-> [XMM1L / 2].
  			[DPFPReg2]	-> [XMM2L / 2].
  			[DPFPReg3]	-> [XMM3L / 2].
  			[DPFPReg4]	-> [XMM4L / 2].
  			[DPFPReg5]	-> [XMM5L / 2].
  			[DPFPReg6]	-> [XMM6L / 2].
  			[DPFPReg7]	-> [XMM7L / 2] }
  		otherwise:
+ 			[self assert: (registerIndex between: XMM0L and: XMM15L).
- 			[self assert: (registerIndex between: XMM0L and: XMM7L).
  			 self assert: (registerIndex bitAnd: 1) = 0.
  			 registerIndex / 2]!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeConvertRRd (in category 'generate machine code') -----
+ concretizeConvertRRd
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg destReg |
+ 	srcReg := self concreteRegister: (operands at:0).
+ 	destReg := self concreteDPFPRegister: (operands at: 1).
+ 	machineCode
+ 		at: 0 put: 16rF2;
+ 		at: 1 put: (self rexR: destReg x: 0 b: srcReg);
+ 		at: 2 put: 16r0F;
+ 		at: 3 put: 16r2A;
+ 		at: 4 put: (self mod: ModReg RM: srcReg RO: destReg).
+ 	 ^machineCodeSize := 5!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveM64rRd (in category 'generate machine code') -----
+ concretizeMoveM64rRd
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| offset srcReg destReg skip |
+ 	offset := operands at: 0.
+ 	srcReg := self concreteRegister: (operands at: 1).
+ 	destReg := self concreteDPFPRegister: (operands at: 2).
+ 	machineCode at: 0 put: 16rF3.
+ 	(srcReg <= 7 and: [destReg <= 7])
+ 		ifTrue: [skip := 0]
+ 		ifFalse: [machineCode at: (skip := 1) put: (self rexw: false r: destReg x: 0 b: srcReg)].
+ 	machineCode
+ 		at: skip + 1 put: 16r0f;
+ 		at: skip + 2 put: 16r7e.
+ 	offset = 0 ifTrue:
+ 		[(srcReg bitAnd: 6) ~= RSP ifTrue:
+ 			[machineCode at: skip + 3 put: (self mod: ModRegInd RM: srcReg RO: destReg).
+ 			 ^machineCodeSize := skip + 4].
+ 		 (srcReg bitAnd: 7) = RSP ifTrue: "RBP & R13 fall through"
+ 			[machineCode
+ 				at: skip + 3 put: (self mod: ModRegInd RM: srcReg RO: destReg);
+ 				at: skip + 4 put: (self s: SIB1 i: 4 b: srcReg).
+ 			 ^machineCodeSize := skip + 5]].
+ 	(self isQuick: offset) ifTrue:
+ 		[(srcReg bitAnd: 7) ~= RSP ifTrue:
+ 			[machineCode
+ 				at: skip + 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
+ 				at: skip + 4 put: (offset bitAnd: 16rFF).
+ 			 ^machineCodeSize := skip + 5].
+ 		 machineCode
+ 			at: skip + 3 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
+ 			at: skip + 4 put: (self s: SIB1 i: 4 b: srcReg);
+ 			at: skip + 5 put: (offset bitAnd: 16rFF).
+ 		 ^machineCodeSize := skip + 6].
+ 	machineCode at: skip + 3 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg).
+ 	(srcReg bitAnd: 6) = RSP ifTrue:
+ 		[machineCode at: skip + 4 put: (self s: SIB1 i: 4 b: srcReg).
+ 		 skip := skip + 1].
+ 	machineCode
+ 		at: skip + 4 put: (offset bitAnd: 16rFF);
+ 		at: skip + 5 put: (offset >> 8 bitAnd: 16rFF);
+ 		at: skip + 6 put: (offset >> 16 bitAnd: 16rFF);
+ 		at: skip + 7 put: (offset >> 24 bitAnd: 16rFF).
+ 	^machineCodeSize := skip + 8!

Item was changed:
  ----- Method: CogX64CompilerForTests class>>xmmRegistersWithNamesDo: (in category 'test support') -----
  xmmRegistersWithNamesDo: aBinaryBlock
+ 	(XMM0L to: XMM15L by: XMM1L - XMM0L)
+ 		with: ((0 to: 15) collect: [:i| '%xmm', i printString])
- 	{XMM0L. XMM1L. XMM2L. XMM3L. XMM4L. XMM5L. XMM6L. XMM7L}
- 		with: #('%xmm0' '%xmm1' '%xmm2' '%xmm3' '%xmm4' '%xmm5' '%xmm6' '%xmm7')
  		do: aBinaryBlock!

Item was changed:
  ----- Method: CogX64CompilerTests>>testMoveM64rRd (in category 'tests') -----
  testMoveM64rRd
  	"self new testMoveM64rRd"
  	self concreteCompilerClass registersWithNamesDo:
  		[:sreg :srname|
  		self concreteCompilerClass xmmRegistersWithNamesDo:
  			[:dreg :drname|
+ 			#(0 8 32760) do:
- 			((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 := 'movq ',
+ 										(offset = 0
+ 											ifTrue: ['']
+ 											ifFalse: ['0x', ((offset printStringBase: 16 length: 16 padded: true) asLowercase)]),
+ 										'(', srname, '), ', drname.
+ 						self assert: herIntended equals: plainJane.
- 						herIntended := 'movsd 0x', (offset hex allButFirst: 3), '(', srname, '), ', drname.
- 						self assert: (plainJane match: herIntended).
  						self assert: len = sz]]]]!

Item was changed:
+ ----- Method: CogX64CompilerTests>>testMoveRIPRelativeCwR (in category 'tests') -----
- ----- Method: CogX64CompilerTests>>testMoveRIPRelativeCwR (in category 'as yet unclassified') -----
  testMoveRIPRelativeCwR
  	"test rip-relative constant generation"
  	"self new testMoveRIPRelativeCwR"
  	
  	| memory |
  	memory := ByteArray new: 16.
  	{self currentCompilationBase. self currentCompilationBase + 512} do:
  		[:n| | inst len |
  		self concreteCompilerClass dataRegistersWithAccessorsDo: 
  			[ :r :rgetter :rset |
  			inst := self gen: MoveCwR operand: n operand: r.
  			len := inst concretizeAt: 0.
  			memory replaceFrom: 1 to: len with: inst machineCode object startingAt: 1.
  			self processor
  				reset.
  			[[processor pc < len] whileTrue:
  				[self processor singleStepIn: memory]]
  				on: Error
  				do: [:ex| ].
  			self concreteCompilerClass dataRegistersWithAccessorsDo:
  				[:ireg :getter :setter| | expected |
  				expected := getter == rgetter ifTrue: [n] ifFalse: [0].
  				self assert: (self processor perform: getter) = expected].
  			self assert: self processor pc = inst machineCodeSize]]
  
  	"processor disassembleFrom: 0 to: inst machineCodeSize in: memory on: Transcript"!

Item was added:
+ ----- Method: Cogit>>MoveR:Rd: (in category 'abstract instructions') -----
+ MoveR: srcReg Rd: destDPReg
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	self assert: objectMemory wordSize = 8.
+ 	^self gen: MoveRRd operand: srcReg operand: destDPReg!

Item was added:
+ ----- Method: Cogit>>MoveRd:R: (in category 'abstract instructions') -----
+ MoveRd: srcDPReg R: destReg
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	self assert: objectMemory wordSize = 8.
+ 	^self gen: MoveRdR operand: srcDPReg operand: destReg!

Item was changed:
  ----- Method: Cogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  	"Scan the method (and all embedded blocks) to determine
  		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  		- if the method needs a frame or not
  		- what are the targets of any backward branches.
  		- how many blocks it creates
  		- if it contans an unknown bytecode
  	 Answer the block count or on error a negative error code"
  	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	inBlock := false.
  	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs := 0].
+ 	self checkForQuickPrimitiveAdjustingIntialPCIfErrorCodeUsed ifTrue:
- 	(primitiveIndex > 0
- 	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  		[^0].
  	pc := latestContinuation := initialPC.
  	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  	[pc <= endPC] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
  				[^EncounteredUnknownBytecode].
  			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 (descriptor isReturn
  		  and: [pc >= latestContinuation]) ifTrue:
  			[endPC := pc].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 descriptor isBranch ifTrue:
  			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  				ifTrue: [self initializeFixupAt: targetPC - initialPC]
  				ifFalse: [latestContinuation := latestContinuation max: targetPC]].
  		 descriptor isBlockCreation ifTrue:
  			[numBlocks := numBlocks + 1.
  			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 latestContinuation := latestContinuation max: targetPC].
  		 self cppIf: #NewspeakVM ifTrue:
  			[descriptor hasIRC ifTrue:
  				[numIRCs := numIRCs + 1]].
  		 pc := pc + descriptor numBytes.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0]].
  	^numBlocks!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>checkForQuickPrimitiveAdjustingIntialPCIfErrorCodeUsed (in category 'compile abstract instructions') -----
+ checkForQuickPrimitiveAdjustingIntialPCIfErrorCodeUsed
+ 	"Answer if methodObj contains a quick primitive.  In addition, if it has a primitive
+ 	 that uses an error code, update the initialPC to skip this code.  The code to
+ 	 process the error code is generated in compileFrameBuild.  For fixups to work
+ 	 correctly, the initialPC must be updated before scanning for backward branches."
+ 
+ 	| methodHeader |
+ 	primitiveIndex = 0 ifTrue:
+ 		[^false].
+ 	methodHeader := objectMemory methodHeaderOf: methodObj.
+ 	(self methodUsesPrimitiveErrorCode: methodHeader) ifTrue:
+ 		[initialPC := initialPC
+ 				+ (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
+ 				+ (coInterpreter sizeOfLongStoreTempBytecode: methodHeader)].
+ 	^coInterpreter isQuickPrimitiveIndex: primitiveIndex!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileFrameBuild (in category 'compile abstract instructions') -----
  compileFrameBuild
  	"Build a frame for a CogMethod activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		receiver (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	If there is a primitive and an error code the Nth temp is the error code.
  	Ensure SendNumArgsReg is set early on (incidentally to nilObj) because
  	it is the flag determining whether context switch is allowed on stack-overflow."
  	| methodHeader jumpSkip |
  	<inline: false>
  	<var: #jumpSkip type: #'AbstractInstruction *'>
  	needsFrame ifFalse: [^0].
  	methodHeader := objectMemory methodHeaderOf: methodObj.
  	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	methodLabel addDependent: (self annotateAbsolutePCRef:
  		(self PushCw: methodLabel asInteger)). "method"
  	self genMoveConstant: objectMemory nilObject R: SendNumArgsReg.
  	self PushR: SendNumArgsReg. "context"
  	self PushR: ReceiverResultReg.
  	methodOrBlockNumArgs + 1 to: (coInterpreter temporaryCountOfMethodHeader: methodHeader) do:
  		[:i|
  		self PushR: SendNumArgsReg].
+ 	(self methodUsesPrimitiveErrorCode: methodHeader) ifTrue:
+ 		[self compileGetErrorCode].
- 	(primitiveIndex > 0
- 	 and: [(coInterpreter longStoreBytecodeForHeader: methodHeader)
- 			= (objectMemory
- 				fetchByte: initialPC + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
- 				ofObject: methodObj)]) ifTrue:
- 		[self compileGetErrorCode.
- 		 initialPC := initialPC
- 				   + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
- 				   + (coInterpreter sizeOfLongStoreTempBytecode: methodHeader)].
  	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
  	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  	"If we can't context switch for this method, use a slightly
  	 slower overflow check that clears SendNumArgsReg."
  	(coInterpreter canContextSwitchIfActivating: methodObj header: methodHeader)
  		ifTrue:
  			[self JumpBelow: stackOverflowCall.
  			 stackCheckLabel := self Label]
  		ifFalse:
  			[jumpSkip := self JumpAboveOrEqual: 0.
  			 self MoveCq: 0 R: SendNumArgsReg.
  			 self Jump: stackOverflowCall.
  			 jumpSkip jmpTarget: (stackCheckLabel := self Label)].
  	self annotateBytecode: stackCheckLabel.
  	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs > 0 ifTrue:
  		 	[self PrefetchAw: theIRCs]]!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>methodUsesPrimitiveErrorCode: (in category 'compile abstract instructions') -----
+ methodUsesPrimitiveErrorCode: methodHeader
+ 	"Answer if methodObj contains a primitive and uses the primitive error code."
+ 	^(coInterpreter primitiveIndexOfMethod: methodObj header: methodHeader) > 0
+ 	  and: [(coInterpreter longStoreBytecodeForHeader: methodHeader)
+ 			= (objectMemory
+ 				fetchByte: initialPC + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
+ 				ofObject: methodObj)]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  	"Scan the method (and all embedded blocks) to determine
  		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  		- if the method needs a frame or not
  		- what are the targets of any backward branches.
  		- how many blocks it creates
  		- how many counters it needs/conditional branches it contains
  	 Answer the block count or on error a negative error code"
  	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	inBlock := false.
  	prevBCDescriptor := nil.
  	numCounters := 0.
  	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs := 0].
+ 	self checkForQuickPrimitiveAdjustingIntialPCIfErrorCodeUsed ifTrue:
- 	(primitiveIndex > 0
- 	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  		[^0].
  	pc := latestContinuation := initialPC.
  	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  	[pc <= endPC] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
  				[^EncounteredUnknownBytecode].
  			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 (descriptor isReturn
  		  and: [pc >= latestContinuation]) ifTrue:
  			[endPC := pc].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 descriptor isBranch ifTrue:
  			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  				ifTrue: [self initializeFixupAt: targetPC - initialPC]
  				ifFalse:
  					[latestContinuation := latestContinuation max: targetPC.
  					 (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
  						[numCounters := numCounters + 1]]].
  		 descriptor isBlockCreation ifTrue:
  			[numBlocks := numBlocks + 1.
  			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 latestContinuation := latestContinuation max: targetPC].
  		 self cppIf: #NewspeakVM ifTrue:
  			[descriptor hasIRC ifTrue:
  				[numIRCs := numIRCs + 1]].
  		 pc := pc + descriptor numBytes.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0].
  		 prevBCDescriptor := descriptor].
  	^numBlocks!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  	"Scan the method (and all embedded blocks) to determine
  		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  		- if the method needs a frame or not
  		- what are the targets of any backward branches.
  		- how many blocks it creates
  	 Answer the block count or on error a negative error code"
  	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	needsFrame := false.
  	inBlock := false.
  	prevBCDescriptor := nil.
  	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs := 0].
+ 	self checkForQuickPrimitiveAdjustingIntialPCIfErrorCodeUsed ifTrue:
- 	(primitiveIndex > 0
- 	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  		[^0].
  	pc := latestContinuation := initialPC.
  	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  	[pc <= endPC] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
  				[^EncounteredUnknownBytecode].
  			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 (descriptor isReturn
  		  and: [pc >= latestContinuation]) ifTrue:
  			[endPC := pc].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 descriptor isBranch ifTrue:
  			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  				ifTrue: [self initializeFixupAt: targetPC - initialPC]
  				ifFalse: [latestContinuation := latestContinuation max: targetPC]].
  		 descriptor isBlockCreation ifTrue:
  			[numBlocks := numBlocks + 1.
  			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 latestContinuation := latestContinuation max: targetPC].
  		 self cppIf: #NewspeakVM ifTrue:
  			[descriptor hasIRC ifTrue:
  				[numIRCs := numIRCs + 1]].
  		 pc := pc + descriptor numBytes.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0].
  		 prevBCDescriptor := descriptor].
  	^numBlocks!



More information about the Vm-dev mailing list