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

commits at source.squeak.org commits at source.squeak.org
Sun Oct 25 03:04:38 UTC 2020


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

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

Name: VMMaker.oscog-eem.2853
Author: eem
Time: 24 October 2020, 8:04:30.513205 pm
UUID: 73f500c3-adf8-47ea-97ca-362ccf156b11
Ancestors: VMMaker.oscog-eem.2852

Cogit: implement the VM lock/unlock funcitons on x86_64.  Recategorize x86 processor-specific instruction generators in the correct category.  Change the order of fields in 64-bit CogAbstractInstructions to get better packing (affects CogARMv8Instruction).  

Compute numTarmpolines correctly for COGMTVM.
Improve the map documentation in initializeAnnotationConstants.

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

Item was changed:
  ----- Method: CogAbstractInstruction class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"Enumerate aBinaryBlock with the names and C type strings for the inst vars to include in an AbstractInstruction struct."
+ 	"((CogAbstractInstruction withAllSubclasses reject:
+ 		[:c|
+ 		 (c class lookupSelector: #wordSize) isSubclassResponsibility
+ 		 or: [((c lookupSelector: #machineCodeBytes) ifNil: [false] ifNotNil: [:cm| cm isSubclassResponsibility])
+ 		 or: [c name includesSubstring: 'ForTests']]])
+ 			sort: [:a :b| a name <= b name]) do:
+ 			[:c| Transcript cr; cr; print: c; cr. c printTypedefOn: Transcript]"
+ 
+ 	"The first four fields of an insruction are byte variables. opcode, machineCodeSize, maxSize, annotation.
+ 	 On 64 bits we can get better packing if machine code follows these four..." 
+ 	(self wordSize = 8
+ 		ifTrue: [self filteredInstVarNames]
+ 		ifFalse: [(self filteredInstVarNames copyWithout: 'machineCode'), #('machineCode')]) do:
- 	"(CogAbstractInstruction withAllSubclasses reject: [:c| c name includesSubString: 'ForTests']) do:
- 		[:c| Transcript print: c; cr. c printTypedefOn: Transcript]"
- 	(self filteredInstVarNames copyWithout: 'machineCode'), #('machineCode') do:
  		[:ivn|
  		 aBinaryBlock
  			value: ivn
  			value: (ivn caseOf: {
  						['address']			-> [#usqInt]. "usqInt is always large enough to contain a pointer; we do not need to use usqIntptr_t"
  						['machineCode']	-> [self machineCodeDeclaration].
  						['operands']		-> [{#usqInt. '[', NumOperands printString, ']'}].
  						['dependent']		-> ['struct _AbstractInstruction *']}
  					otherwise:
  						[#'unsigned char'])]!

Item was changed:
  ----- Method: CogAbstractInstruction class>>wordSize (in category 'translation') -----
  wordSize
+ 	"Answer either 4 or 8 depending on the processor's basic architecture."
- 	"Answer either 4 or 8 depending on the processor's basic architacture."
  	self subclassResponsibility!

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

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeBSR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeBSR (in category 'generate machine code - concretize') -----
  concretizeBSR
  	"Bit Scan Reverse
  	First operand is input register (mask)
  	Second operand is output register (dest)"
  	"BSR"
  	<inline: true>
  	| dest maskReg |
  	maskReg := operands at: 0.
  	dest := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rBD;
  		at: 2 put: (self mod: ModReg RM: maskReg RO: dest).
  	 ^3!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeCDQ (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeCDQ (in category 'generate machine code - concretize') -----
  concretizeCDQ
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	machineCode at: 0 put: 16r99.
  	^1!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeCLD (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeCLD (in category 'generate machine code - concretize') -----
  concretizeCLD
  	<inline: true>
  	machineCode at: 0 put: 16rFC.
  	^1!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeCMPXCHGAwR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeCMPXCHGAwR (in category 'generate machine code - concretize') -----
  concretizeCMPXCHGAwR
  	<inline: true>
  	| addressOperand reg |
  	addressOperand := operands at: 0.
  	reg := operands at: 1.
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rB1;
  		at: 2 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 3 put: (addressOperand bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 6 put: (addressOperand >> 24 bitAnd: 16rFF).
  	^7!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeCMPXCHGMwrR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeCMPXCHGMwrR (in category 'generate machine code - concretize') -----
  concretizeCMPXCHGMwrR
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r0F;
  				at: 1 put: 16rB1;
  				at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 3 put: (offset bitAnd: 16rFF).
  			 ^4].
  		machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB1;
  			at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 3 put: (offset bitAnd: 16rFF);
  			at: 4 put: (offset >> 8 bitAnd: 16rFF);
  			at: 5 put: (offset >> 16 bitAnd: 16rFF);
  			at: 6 put: (offset >> 24 bitAnd: 16rFF).
  		^7].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r0F;
  			at: 1 put: 16rB1;
  			at: 2 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 4 put: (offset bitAnd: 16rFF).
  		 ^5].
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rB1;
  		at: 2 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 3 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 4 put: (offset bitAnd: 16rFF);
  		at: 5 put: (offset >> 8 bitAnd: 16rFF);
  		at: 6 put: (offset >> 16 bitAnd: 16rFF);
  		at: 7 put: (offset >> 24 bitAnd: 16rFF).
  	^8!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeCPUID (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeCPUID (in category 'generate machine code - concretize') -----
  concretizeCPUID
  	<inline: true>
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rA2.
  	^2!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeFENCE: (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeFENCE: (in category 'generate machine code - concretize') -----
  concretizeFENCE: regOpcode
  	<inline: true>
  	machineCode
  		at: 0 put: 16r0F;
  		at: 1 put: 16rAE;
  		at: 2 put: (self mod: ModReg RM: 0 RO: regOpcode).
  	^3!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeFSTPD (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeFSTPD (in category 'generate machine code - concretize') -----
  concretizeFSTPD
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	srcReg := 3.
  	offset := operands at: 0.
  	destReg := operands at: 1.
  	destReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			"FSTP dest"
  			[machineCode
  				at: 0 put: 16rDD;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 2 put: (offset bitAnd: 16rFF).
  			 ^3].
  		"FSTP dest"
  		machineCode
  			at: 0 put: 16rDD;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
  		^6].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16rDD;
  			at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: 2 put: (self s: SIB1 i: 4 b: destReg);
  			at: 3 put: (offset bitAnd: 16rFF).
  		 ^4].
  	machineCode
  		at: 0 put: 16rDD;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 2 put: (self s: SIB1 i: 4 b: destReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
  	^7!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeFSTPS (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeFSTPS (in category 'generate machine code - concretize') -----
  concretizeFSTPS
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	srcReg := 3.
  	offset := operands at: 0.
  	destReg := operands at: 1.
  	destReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			"FSTP dest"
  			[machineCode
  				at: 0 put: 16rD9;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  				at: 2 put: (offset bitAnd: 16rFF).
  			 ^3].
  		"FSTP dest"
  		machineCode
  			at: 0 put: 16rD9;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
  		^6].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16rD9;
  			at: 1 put: (self mod: ModRegRegDisp8 RM: destReg RO: srcReg);
  			at: 2 put: (self s: SIB1 i: 4 b: destReg);
  			at: 3 put: (offset bitAnd: 16rFF).
  		 ^4].
  	machineCode
  		at: 0 put: 16rD9;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: destReg RO: srcReg);
  		at: 2 put: (self s: SIB1 i: 4 b: destReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
  	^7!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeIDIVR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeIDIVR (in category 'generate machine code - concretize') -----
  concretizeIDIVR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| regDivisor |
  	regDivisor := operands at: 0.
  	machineCode
  		at: 0 put: 16rF7;
  		at: 1 put: (self mod: ModReg RM: regDivisor RO: 7).
  	^2!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeLOCK (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeLOCK (in category 'generate machine code - concretize') -----
  concretizeLOCK
  	<inline: true>
  	machineCode at: 0 put: 16rF0.
  	^1!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeMOVSB (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeMOVSB (in category 'generate machine code - concretize') -----
  concretizeMOVSB
  	<inline: true>
  	machineCode at: 0 put: 16rA4.
  	^1!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeMOVSD (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeMOVSD (in category 'generate machine code - concretize') -----
  concretizeMOVSD
  	<inline: true>
  	machineCode at: 0 put: 16rA5.
  	^1!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeREP (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeREP (in category 'generate machine code - concretize') -----
  concretizeREP
  	<inline: true>
  	machineCode at: 0 put: 16rF3.
  	^1!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeXCHGAwR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeXCHGAwR (in category 'generate machine code - concretize') -----
  concretizeXCHGAwR
  	<inline: true>
  	| addressOperand reg |
  	addressOperand := operands at: 0.
  	reg := operands at: 1.
  	machineCode
  		at: 0 put: 16r87;
  		at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 2 put: (addressOperand bitAnd: 16rFF);
  		at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
  	^6!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeXCHGMwrR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeXCHGMwrR (in category 'generate machine code - concretize') -----
  concretizeXCHGMwrR
  	<inline: true>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := operands at: 1.
  	destReg := operands at: 2.
  	srcReg ~= ESP ifTrue:
  		[(self isQuick: offset) ifTrue:
  			[machineCode
  				at: 0 put: 16r87;
  				at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  				at: 2 put: (offset bitAnd: 16rFF).
  			 ^3].
  		machineCode
  			at: 0 put: 16r87;
  			at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  			at: 2 put: (offset bitAnd: 16rFF);
  			at: 3 put: (offset >> 8 bitAnd: 16rFF);
  			at: 4 put: (offset >> 16 bitAnd: 16rFF);
  			at: 5 put: (offset >> 24 bitAnd: 16rFF).
  		^6].
  	"ESP:"
  	(self isQuick: offset) ifTrue:
  		[machineCode
  			at: 0 put: 16r87;
  			at: 1 put: (self mod: ModRegRegDisp8 RM: srcReg RO: destReg);
  			at: 2 put: (self s: SIB1 i: 4 b: srcReg);
  			at: 3 put: (offset bitAnd: 16rFF).
  		 ^4].
  	machineCode
  		at: 0 put: 16r87;
  		at: 1 put: (self mod: ModRegRegDisp32 RM: srcReg RO: destReg);
  		at: 2 put: (self s: SIB1 i: 4 b: srcReg);
  		at: 3 put: (offset bitAnd: 16rFF);
  		at: 4 put: (offset >> 8 bitAnd: 16rFF);
  		at: 5 put: (offset >> 16 bitAnd: 16rFF);
  		at: 6 put: (offset >> 24 bitAnd: 16rFF).
  	^7!

Item was changed:
+ ----- Method: CogIA32Compiler>>concretizeXCHGRR (in category 'generate machine code - concretize processor-specific') -----
- ----- Method: CogIA32Compiler>>concretizeXCHGRR (in category 'generate machine code - concretize') -----
  concretizeXCHGRR
  	<inline: true>
  	| reg1 reg2 |
  	reg1 := operands at: 0.
  	reg2 := operands at: 1.
  	reg2 = EAX ifTrue:
  		[reg2 := reg1.
  		 reg1 := EAX].
  	reg1 = EAX ifTrue:
  		[machineCode at: 0 put: 16r90 + reg2.
  		 ^1].
  	machineCode
  		at: 0 put: 16r87;
  		at: 1 put: (self mod: ModReg RM: reg1 RO: reg2).
  	^2!

Item was changed:
  ----- Method: CogIA32Compiler>>dispatchConcretizeProcessorSpecific (in category 'generate machine code') -----
  dispatchConcretizeProcessorSpecific
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is part of the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the number of literals limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	opcode caseOf: {
  		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
- 		[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR].
- 		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR].
- 		[LFENCE]				-> [^self concretizeFENCE: 5].
- 		[MFENCE]				-> [^self concretizeFENCE: 6].
- 		[SFENCE]				-> [^self concretizeFENCE: 7].
- 		[LOCK]					-> [^self concretizeLOCK].
- 		[XCHGAwR]				-> [^self concretizeXCHGAwR].
- 		[XCHGMwrR]			-> [^self concretizeXCHGMwrR].
- 		[XCHGRR]				-> [^self concretizeXCHGRR].
  		[FSTPS]					-> [^self concretizeFSTPS].
  		[FSTPD]				-> [^self concretizeFSTPD].
  		[REP]					-> [^self concretizeREP].
  		[CLD]					-> [^self concretizeCLD].
  		[MOVSB]				-> [^self concretizeMOVSB].
  		[MOVSD]				-> [^self concretizeMOVSD].
  		[BSR]					-> [^self concretizeBSR].
+ 		[XCHGRR]				-> [^self concretizeXCHGRR].
+ 		"Multi-processing"
+ 		"[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR].
+ 		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR]."
+ 		[LFENCE]				-> [^self concretizeFENCE: 5].
+ 		[MFENCE]				-> [^self concretizeFENCE: 6].
+ 		[SFENCE]				-> [^self concretizeFENCE: 7].
+ 		"[LOCK]					-> [^self concretizeLOCK]."
+ 		[XCHGAwR]				-> [^self concretizeXCHGAwR].
+ 		"[XCHGMwrR]			-> [^self concretizeXCHGMwrR]."
  	}.
  	^0!

Item was changed:
  ----- Method: CogThreadManager>>guiProcess (in category 'simulation') -----
  guiProcess
  	"Simulation only; answer the simulator's first process."
  	<doNotGenerate>
+ 	^threads ifNotNil: [threads first osThread]!
- 	^threads first osThread!

Item was changed:
  ----- Method: CogThreadManager>>vmOwnerLockAddress (in category 'public api') -----
  vmOwnerLockAddress
  	<api> "NB. For the JIT only, so it can generate the lock & unlock functions."
  	<returnTypeC: #usqInt>
  	^self
  		cCode: [(self addressOf: vmOwnerLock) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedVariableAddress: #vmOwnerLockFromMachineCode in: self]!
- 		inSmalltalk: [self inMemoryVMOwnerLockAddress]!

Item was added:
+ ----- Method: CogThreadManager>>vmOwnerLockFromMachineCode (in category 'simulation') -----
+ vmOwnerLockFromMachineCode
+ 	^vmOwnerLock!

Item was added:
+ ----- Method: CogThreadManager>>vmOwnerLockFromMachineCode: (in category 'simulation') -----
+ vmOwnerLockFromMachineCode: aValue
+ 	vmOwnerLock := aValue!

Item was removed:
- ----- Method: CogVMSimulator>>inMemoryVMOwnerLockAddress (in category 'rump c stack') -----
- inMemoryVMOwnerLockAddress
- 	^self rumpCStackAddress - 48!

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

Item was changed:
  ----- Method: CogVMSimulator>>windowIsClosing (in category 'primitive support') -----
  windowIsClosing
  	self threadManager ifNotNil:
  		[:threadManager|
+ 		threadManager guiProcess ifNotNil:
+ 			[:guiProcess|
+ 			guiProcess ~= Processor activeProcess ifTrue:
+ 				[guiProcess
+ 					signalException:
+ 						(Notification new tag: #evaluateQuit; yourself)].
- 		threadManager guiProcess ~= Processor activeProcess ifTrue:
- 			[threadManager guiProcess
- 				signalException:
- 					(Notification new tag: #evaluateQuit; yourself).
  			Processor terminateActive]].
  	quitBlock ifNotNil:
  		[:effectiveQuitBlock|
  		quitBlock := nil. "stop recursion on explicit window close."
  		[effectiveQuitBlock value]
  			on: BlockCannotReturn
  			do: [:ex|]]	"Cause return from #test, et al"!

Item was changed:
  CogAbstractInstruction subclass: #CogX64Compiler
  	instanceVariableNames: ''
+ 	classVariableNames: 'BSR CDQ CLD CMPXCHGAwR CMPXCHGMwrR CPUID IDIVR IMULRR LFENCE LOCK MFENCE MOVSB MOVSQ ModReg ModRegInd ModRegIndDisp32 ModRegIndSIB ModRegRegDisp32 ModRegRegDisp8 MoveRAwNoVBR R10 R11 R12 R13 R14 R15 R8 R9 RAX RBP RBX RCX RDI RDX REP RSI RSP SFENCE SIB1 SIB2 SIB4 SIB8 SysV XCHGAwR XCHGMwrR XCHGRR XMM0L XMM10L XMM11L XMM12L XMM13L XMM14L XMM15L XMM1L XMM2L XMM3L XMM4L XMM5L XMM6L XMM7L XMM8L XMM9L'
- 	classVariableNames: 'BSR CDQ CLD CMPXCHGAwR CMPXCHGMwrR CPUID IDIVR IMULRR LFENCE LOCK MFENCE MOVSB MOVSQ ModReg ModRegInd ModRegIndDisp32 ModRegIndSIB ModRegRegDisp32 ModRegRegDisp8 R10 R11 R12 R13 R14 R15 R8 R9 RAX RBP RBX RCX RDI RDX REP RSI RSP SFENCE SIB1 SIB2 SIB4 SIB8 SysV XCHGAwR XCHGMwrR XCHGRR XMM0L XMM10L XMM11L XMM12L XMM13L XMM14L XMM15L XMM1L XMM2L XMM3L XMM4L XMM5L XMM6L XMM7L XMM8L XMM9L'
  	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].
  
  	(InitializationOptions ifNil: [Dictionary new])
  		at: #ABI
  		ifPresent: [:abi| SysV := abi asUppercase ~= #WIN64 and: [abi asUppercase ~= #'_WIN64']]
  		ifAbsent: [SysV := true]. "Default ABI; set to true for SysV, false for WIN64/_WIN64"
  
  	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 := 1.
  	XMM2L := 2.
  	XMM3L := 3.
  	XMM4L := 4.
  	XMM5L := 5.
  	XMM6L := 6.
  	XMM7L := 7.
  	XMM8L := 8.
  	XMM9L := 9.
  	XMM10L := 10.
  	XMM11L := 11.
  	XMM12L := 12.
  	XMM13L := 13.
  	XMM14L := 14.
  	XMM15L := 15.
  
  	"Mod R/M Mod fields.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-2"
  	ModRegInd := 0.
  		ModRegIndSIB := 4.
  		ModRegIndDisp32 := 5.
  	ModRegRegDisp8 := 1.
  	ModRegRegDisp32 := 2.
  	ModReg := 3.
  
  	"SIB Scaled Index modes.  See [1] Sec 2.4, 2.5 & 2.6 & Table 2-3"
  	SIB1 := 0.
  	SIB2 := 1.
  	SIB4 := 2.
  	SIB8 := 3.
  
  	"Specific instructions"
  	self
+ 		initializeSpecificOpcodes: #(CDQ IDIVR IMULRR CPUID LFENCE MFENCE SFENCE LOCK CMPXCHGAwR CMPXCHGMwrR XCHGAwR MoveRAwNoVBR XCHGMwrR XCHGRR CLD REP MOVSB MOVSQ BSR)
- 		initializeSpecificOpcodes: #(CDQ IDIVR IMULRR CPUID LFENCE MFENCE SFENCE LOCK CMPXCHGAwR CMPXCHGMwrR XCHGAwR XCHGMwrR XCHGRR CLD REP MOVSB MOVSQ BSR)
  		in: thisContext method!

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

Item was added:
+ ----- Method: CogX64Compiler>>concretizeFENCE: (in category 'generate machine code - concretize processor-specific') -----
+ concretizeFENCE: regOpcode
+ 	<inline: true>
+ 	machineCode
+ 		at: 0 put: 16r0F;
+ 		at: 1 put: 16rAE;
+ 		at: 2 put: (self mod: ModReg RM: 0 RO: regOpcode).
+ 	^3!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeMoveRAwNoVBR (in category 'generate machine code - concretize') -----
+ concretizeMoveRAwNoVBR
+ 	"A version of concretizeMoveRAw tat does not use VarBaseReg."
+ 	<inline: true>
+ 	| addressOperand reg offset |
+ 	reg := operands at: 0.
+ 	addressOperand := operands at: 1.
+ 	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
+ 		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
+ 	"If storing RAX, store directly, otherwise, because of instruction encoding limitations, the register
+ 	 _must_ be stored through RAX.  If reg = RBP or RSP simply store directly, otherwise swap RAX with
+ 	 the register before and after the store through RAX.  We avoid sweapping before hand with RBP
+ 	 and RSP because setting RSP to whatever the contents of RAX is can cause disastrous results if
+ 	 an interrupt is delivered immediately after that point.  See mail threads beginning with
+ 		http://lists.squeakfoundation.org/pipermail/vm-dev/2019-September/031428.html
+ 		http://lists.squeakfoundation.org/pipermail/vm-dev/2019-October/031499.html"
+ 	(reg = RAX or: [reg = RBP or: [reg = RSP]])
+ 		ifTrue: [offset := 0]
+ 		ifFalse:
+ 			[(reg = RBP or: [reg = RSP])
+ 				ifTrue:
+ 					[machineCode
+ 						at: 0 put: (self rexR: reg x: 0 b: RAX);
+ 						at: 1 put: 16r89;
+ 						at: 2 put: (self mod: ModReg RM: RAX RO: reg).
+ 					 offset := 3]
+ 				ifFalse:
+ 					[machineCode
+ 						at: 0 put: (self rexR: RAX x: 0 b: reg);
+ 						at: 1 put: 16r90 + (reg \\ 8).
+ 					 offset := 2]].
+ 	machineCode
+ 		at: 0 + offset put: 16r48;
+ 		at: 1 + offset put: 16rA3;
+ 		at: 2 + offset put: (addressOperand bitAnd: 16rFF);
+ 		at: 3 + offset put: (addressOperand >> 8 bitAnd: 16rFF);
+ 		at: 4 + offset put: (addressOperand >> 16 bitAnd: 16rFF);
+ 		at: 5 + offset put: (addressOperand >> 24 bitAnd: 16rFF);
+ 		at: 6 + offset put: (addressOperand >> 32 bitAnd: 16rFF);
+ 		at: 7 + offset put: (addressOperand >> 40 bitAnd: 16rFF);
+ 		at: 8 + offset put: (addressOperand >> 48 bitAnd: 16rFF);
+ 		at: 9 + offset put: (addressOperand >> 56 bitAnd: 16rFF).
+ 	reg = RAX ifTrue:
+ 		[^10].
+ 	(reg = RBP or: [reg = RSP]) ifTrue:
+ 		[^13].
+ 	"Now effect the assignment via xchg, which restores RAX"
+ 	machineCode
+ 		at: 12 put: (machineCode at: 0);
+ 		at: 13 put: (machineCode at: 1).
+ 	^14!

Item was added:
+ ----- Method: CogX64Compiler>>concretizeXCHGAwR (in category 'generate machine code - concretize processor-specific') -----
+ concretizeXCHGAwR
+ 	"This is a very limited implementation that assumes RAX is available."
+ 	<inline: true>
+ 	| addressOperand reg scratch |
+ 	addressOperand := operands at: 0.
+ 	reg := operands at: 1.
+ 	scratch := operands at: 2.
+ 	self deny: reg = scratch.
+ 	machineCode
+ 		"movq addressOperand, %rscratch"
+ 		at:  0 put: (self rexR: 0 x: 0 b: scratch);
+ 		at:  1 put: 16rB8 + (scratch bitAnd: 7);
+ 		at:  2 put: (addressOperand bitAnd: 16rFF);
+ 		at:  3 put: (addressOperand >> 8 bitAnd: 16rFF);
+ 		at:  4 put: (addressOperand >> 16 bitAnd: 16rFF);
+ 		at:  5 put: (addressOperand >> 24 bitAnd: 16rFF);
+ 		at:  6 put: (addressOperand >> 32 bitAnd: 16rFF);
+ 		at:  7 put: (addressOperand >> 40 bitAnd: 16rFF);
+ 		at:  8 put: (addressOperand >> 48 bitAnd: 16rFF);
+ 		at:  9 put: (addressOperand >> 56 bitAnd: 16rFF);
+ 		"xchgq %reg, (%rscratch)" "0xf: 49 87 45 00              xchgq  %rax, (%r13)"
+ 		at: 10 put: (self rexR: reg x: 0 b: scratch);
+ 		at: 11 put: 16r87;
+ 		at: 12 put: (self s: SIB1 i: 0 b: scratch).
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object."
+ 	"cogit processor disassembleInstructionAt: 10 In: machineCode object"
+ 	^13!

Item was changed:
  ----- Method: CogX64Compiler>>dispatchConcretizeProcessorSpecific (in category 'generate machine code') -----
  dispatchConcretizeProcessorSpecific
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is part of the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the number of literals limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	opcode caseOf: {
+ 		"Specific Arithmetic"
- 		"Specific Control/Data Movement"
  		[CDQ]					-> [^self concretizeCDQ].
  		[IDIVR]					-> [^self concretizeIDIVR].
  		[IMULRR]				-> [^self concretizeMulRR].
  		[CPUID]					-> [^self concretizeCPUID].
- 		"[CMPXCHGAwR]			-> [^self concretizeCMPXCHGAwR]."
- 		"[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR]."
- 		"[LFENCE]				-> [^self concretizeFENCE: 5]."
- 		"[MFENCE]				-> [^self concretizeFENCE: 6].
- 		[SFENCE]				-> [^self concretizeFENCE: 7]."
- 		"[LOCK]					-> [^self concretizeLOCK]."
- 		"[XCHGAwR]				-> [^self concretizeXCHGAwR]."
- 		"[XCHGMwrR]			-> [^self concretizeXCHGMwrR]."
  		[XCHGRR]				-> [^self concretizeXCHGRR].
+ 		"Specific Data Movement"
  		[REP]					-> [^self concretizeREP].
  		[CLD]					-> [^self concretizeCLD].
  		[MOVSB]				-> [^self concretizeMOVSB].
  		[MOVSQ]				-> [^self concretizeMOVSQ].
  		[BSR]					-> [^self concretizeBSR].
+ 		"Multi-processing"
+ 		"[CMPXCHGAwR]		-> [^self concretizeCMPXCHGAwR].
+ 		[CMPXCHGMwrR]		-> [^self concretizeCMPXCHGMwrR].
+ 		[LFENCE]				-> [^self concretizeFENCE: 5]."
+ 		[MFENCE]				-> [^self concretizeFENCE: 6].
+ 		[SFENCE]				-> [^self concretizeFENCE: 7].
+ 		"[LOCK]				-> [^self concretizeLOCK]."
+ 		[MoveRAwNoVBR]		-> [^self concretizeMoveRAwNoVBR].
+ 		[XCHGAwR]				-> [^self concretizeXCHGAwR].
+ 		"[XCHGMwrR]			-> [^self concretizeXCHGMwrR]."
  	}.
  	^0!

Item was added:
+ ----- Method: CogX64Compiler>>generateLowLevelTryLock: (in category 'multi-threading') -----
+ generateLowLevelTryLock: vmOwnerLockAddress
+ 	"Generate a function that attempts to lock the vmOwnerLock and answers if it succeeded."
+ 	<inline: true>
+ 	| callerSavedReg |
+ 	vmOwnerLockAddress = 0 ifTrue:
+ 		[cogit
+ 			MoveCq: 1 R: RAX;
+ 			RetN: 0.
+ 		 ^self].
+ 	"There is no 64-bit absolute address form of XCHGQ.  Insteads, load the address into a scratch register."
+ 	callerSavedReg := cogit availableRegisterOrNoneIn: (ABICallerSavedRegisterMask bitClear: 1 << RAX).
+ 	cogit
+ 		MoveCq: 1 R: RAX;
+ 		gen: MFENCE; "make the XCHG globally consistent"
+ 		gen: XCHGAwR operand: vmOwnerLockAddress operand: RAX operand: callerSavedReg;
+ 		gen: SFENCE; "make the store globally visible"
+ 		SubCq: 1 R: RAX; "Since we only ever set the lock to 1 or 0, subtracting 1 sets
+ 						   RAX to 0 if the lock was already locked and non-zero if it wasn't."
+ 		RetN: 0!

Item was added:
+ ----- Method: CogX64Compiler>>generateLowLevelUnlock: (in category 'multi-threading') -----
+ generateLowLevelUnlock: vmOwnerLockAddress
+ 	vmOwnerLockAddress ~= 0 ifTrue:
+ 		[cogit
+ 			MoveCq: 0 R: RAX;
+ 			"VarBaseRegister is only live in Smalltalk machine code so cannot be used here."
+ 			gen: MoveRAwNoVBR operand: RAX operand: vmOwnerLockAddress;
+ 			gen: SFENCE].
+ 	cogit RetN: 0!

Item was added:
+ ----- Method: CogX64Compiler>>numLowLevelLockOpcodes (in category 'accessing') -----
+ numLowLevelLockOpcodes
+ 	"ceTryLockVMOwner:
+ 		movq $0x1, %rax
+ 		mfence  : 0F AE F0 
+ 		movq &vmOwnerLockFromMachineCode, %rcx  N.B. movq,xchgq are one XCHGAwR instruction
+ 		xchgq %rax, (%rcx)
+ 		sfence
+ 		subq $0x1, %rax
+ 		ret
+ 	 ceUnlockVMOwner:
+ 		xorq %rax, %rax
+ 		movq %rax, &vmOwnerLockFromMachineCode
+ 		sfence
+ 		ret"
+ 	^10!

Item was changed:
  ----- Method: Cogit class>>initializeAnnotationConstants (in category 'class initialization') -----
  initializeAnnotationConstants
  	"These form the method map for a cog method.  The map defines which addresses
  	 in a machine code method are ones with important functions, such as being a send
  	 site or being a reference to a heap object.  Each annotated instruction has a byte
+ 	 in the map, and each byte in the map has two parts.  In the least signficant bits is
+ 	 a distance.  In the most signficant bits is the type of annotation at the point reached.
+ 	 The first map entry's distance is that from the  the cmNoCheckEntryOffset, and
+ 	 subsequent distances are from the preceding map entry  A null byte ends the map.
- 	 in the map, and each byte in the map has two parts.  In the least signficant bits are
- 	 a distance in codeGranularity units from the start of the method or the previous
- 	 map entry, except for the IsAnnotationExtension type.  In the most signficant bits
- 	 are the type of annotation at the point reached.  A null byte ends the map.  The
- 	 first mapped location is a distance from the cmNoCheckEntryOffset.
  
+ 	 The map occurs at the end of a method (*), in reverse, so that its start is found by
+ 	 adding the method's block size.  If the distance between two mapped instructions
+ 	 will not fit in the displacement field then one or more displacement entries are placed
+ 	 in the map to bridge the gap.  The displacements are in codeGranularity units so that
+ 	 processors like e.g. ARM, with 4-byte instructions, do not have overly large maps.  In
+ 	 practice, maps are very compact, but they should be as quick to navigate as possible,
+ 	 hence they have a simple regular structure.  Each element of a map is a byte with the
+ 	 three bit type in the most significant bits, and the five bit displacement in the least
+ 	 significant. One annotation, IsAnnotationExtension, implicitly has a zero displacement
+ 	 and reinterprets the displacement field as an extended annotation type. One annotation,
+ 	 IsDisplacementX2N, interprets the displacement field as a power of two number of
+ 	 codeGranularity units, for spanning large displacements compactly.
- 	 The map occurs at the end of a method (*), in reverse, so that its start is found
- 	 by adding the method's block size.  If the distance between two mapped
- 	 instructions will not fit in the displacement field then one or more displacement
- 	 entries are placed in the map to bridge the gap.  There is a * 32 displacement
- 	 units type for spanning large gaps.  The displacements are in codeGranularity
- 	 units so that processors like e.g. ARM, with 4-byte instructions, do not have overly
- 	 large maps.  In [practice maps are very compact, but they should be as quick to
- 	 navigate as possible, and hence be as compact as possible.
  
+ 	 The map is the structure that allows methods to be dynamically linked, unlinked and
+ 	 relocated.  There are two categories of call that may need map entries, calls to (non-
+ 	 send) run-time and/or primitive routines, and send calls. Run-time calls may be
+ 	 changed during relocation. Send calls can be rewritten when linked or unlinked and
+ 	 during relocation. Absolute run- time calls do not need a map entry because they don't
+ 	 change on relocation. Hence the annotaion for non-send run-time/primitive calls is
+ 	 IsRelativeCall. There are several kinds of send call, sends, super sends, and exotic
+ 	 Newspeak sends (self sends, directed super sends, etc).  These send calls need different
+ 	 treatment at different times.  For example, when the send cache is flushed or the
+ 	 method zone is shrunk some sends must be unlinked and some sends must be relocated.
+ 	
+ 	 The map is also used to map machine code pcs to bytecode pcs and vice verse.  This is
+ 	 done by walking the machine code method using its map at the same time as walking
+ 	 the bytecoded method using its bytecodes, processing the pair of pcs at relevant points.
+ 	 In all cases, sends and run-time calls, the address in the map is the address following the
+ 	 call, which is also the return address for the call.
- 	 There is only one kind of call annotation that serves for all calls from machine
- 	 code. There are several kinds of call, sends, super sends, calls of the generated
- 	 run-time, and direct calls of primitive functions in the interpreter.  These need
- 	 different treatment at different times.  For example, when the send cache is
- 	 flushed or the method zone is shrunk some sends must be unlinked and some
- 	 sends must be relocated.  But to be able to parse bytecoded methods and match
- 	 their pcs with corresponding machine code pcs the map needs to differentiate
- 	 between sends and run-time calls. 
  
+ 	 Sends are in two states, linked, in which case they call other machine code methods, or
+ 	 unlinked, in which case they call a particular unlinked send run-time routine that will initiate
+ 	 linking. Linked can be distinguished from unlinked sends based on address; only linked
+ 	 sends have their target between methodZoneBase and methodZone freeStart.
+ 	 We used to distinguish normal sends from super sends based on alignment of entry-point,
+ 	 because normal sends link to the checked entry-point, whereas super sends link to the
+ 	 unchecked entry-point, and both entry points have different alignments. But with the
+ 	 arrival of exotic Newspeak sends came the need for supporting more varieties than merely
+ 	 send and super send. So now we use the IsAnnotationExtension to label sends other than
+ 	 normal sends. For these ``exotic'' sends there is both an IsAnnotationExtension annotation
+ 	 and an IsSendCall annotation.
- 	 Sends can be distinguished from run-time or direct primitive calls based on address;
- 	 only sends have their target between methodZoneBase and methodZone freeStart.
- 	 We used to distinguish normal sends from super sends based on alignment of
- 	 entry-point, because normal sends link to the checked entry-point, whereas super sends
- 	 link to the unchecked entry-point, and both entry points have different alignments.
- 	 But now we use the IsAnnotationExtension to label sends other than normal sends.
- 	 For these ``exotic'' sends there is both an IsAnnotationExtension annotation and an
- 	 IsSendCall annotation.
  
  	 While run-time calls can be distinguished from direct primitive calls on the basis
+ 	 of address there is no need to do so.  They are merely calls to locations that don't
+ 	 move during method zone compaction.
- 	 of address there is no need to do so.  They are merely calls to locations that
- 	 don't move during method zone compaction.
  
  	 Absolute PC references are used for method references and counter references.
  	 These are references from within a particular method to absolute pcs in that same
  	 method that must be relocated when the method moves."
  	"self initializeAnnotationConstants"
  
  	AnnotationShift := 5.
  	IsDisplacementX2N := 0.	"N.B. A 0 byte ends the map"
  	IsAnnotationExtension := 1.	"Used to extend IsSendCall with different codes for exotic send types."
  	IsObjectReference := 2.
  	IsAbsPCReference := 3.
  	IsRelativeCall := 4.
  	HasBytecodePC := 5.
  	IsNSSendCall := NewspeakVM ifTrue: [6].
  	IsSendCall := 7.
  	"These are formed by combining IsSendCall and IsAnnotationExtension annotations."
  	IsSuperSend := 8.
  	IsDirectedSuperSend := BytecodeSetHasDirectedSuperSend ifTrue: [9].
  	IsDirectedSuperBindingSend := BytecodeSetHasDirectedSuperSend ifTrue: [10].
  	IsNSSelfSend := NewspeakVM ifTrue: [11].
  	IsNSDynamicSuperSend := NewspeakVM ifTrue: [12].
  	IsNSImplicitReceiverSend := NewspeakVM ifTrue: [13].
  
  	DisplacementMask := (1 << AnnotationShift) - 1.
  	DisplacementX2N := IsDisplacementX2N << AnnotationShift.
  	FirstAnnotation := IsObjectReference << AnnotationShift.
  	MaxX2NDisplacement := DisplacementMask << AnnotationShift.
  
  	MapEnd := 0.
  
+ 	"These two tables are used for printing annotations during disassembly"
  	AnnotationConstantNames := #(	IsDisplacementX2N
  										IsAnnotationExtension
  										IsObjectReference
  										IsAbsPCReference
  										IsRelativeCall
  										HasBytecodePC
  										IsNSSendCall
  										IsSendCall
  										IsSuperSend
  										IsDirectedSuperSend
  										IsDirectedSuperBindingSend
  										IsNSSelfSend
  										IsNSDynamicSuperSend
  										IsNSImplicitReceiverSend).
  	AnnotationsWithBytecodePCs := #(HasBytecodePC
  										IsNSSendCall
  										IsSendCall
  										IsSuperSend
  										IsDirectedSuperSend
  										IsDirectedSuperBindingSend
  										IsNSSelfSend
  										IsNSDynamicSuperSend
  										IsNSImplicitReceiverSend),
  										{'IsRelativeCall:\HasBytecodePC' withCRs}!

Item was changed:
  ----- Method: Cogit class>>numTrampolines (in category 'trampoline support') -----
  numTrampolines
+ 	^37 "29 + 4 each for self and super sends"
+ 	+ (COGMTVM ifTrue: [2] ifFalse: [0]) "try lock/unlock routines"
+ 	+ (LowcodeVM ifTrue: [3] ifFalse: [0])
+ 	+ CogCompilerClass numTrampolines
- 	^37 "29 + 4 each for self and super sends" + (LowcodeVM ifTrue: [3] ifFalse: [0]) + CogCompilerClass numTrampolines
  
  	"self withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"!




More information about the Vm-dev mailing list