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

commits at source.squeak.org commits at source.squeak.org
Sat Jan 14 02:44:53 UTC 2023


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

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

Name: VMMaker.oscog.seperateMarking-eem.3308
Author: eem
Time: 13 January 2023, 6:44:34.267653 pm
UUID: 8ceb1c5c-2147-4d19-b6b0-860d4a68b7d0
Ancestors: VMMaker.oscog.seperateMarking-WoC.3307

Merge VMMaker.oscog-eem.3283/3301 (machine code primitive for perform:withArguments:)

=============== Diff against VMMaker.oscog.seperateMarking-WoC.3307 ===============

Item was changed:
  ----- Method: CogARMv8Compiler>>decodeN:imms:immr: (in category 'generate machine code - support') -----
  decodeN: n imms: imms immr: immr
  	"See aarch64/instrs/integer/bitmasks/DecodeBitMasks J1-7389."
  	<returnTypeC: #usqInt>
  	| bits immediate mask rotation width |
  	<var: 'mask' type: #usqInt>
  	self assert: ((n between: 0 and: 1) and: [(imms between: 0 and: 63) and: [immr between: 0 and: 63]]).
  	"For logical immediates an all-ones value of S is reserved since it would generate a useless all-ones result (many times)"
  	imms = 63 ifTrue:
  		[^self cCode: [0] inSmalltalk: [#undefined]].
  
  	n = 1
  		ifTrue:
  			[width := 64.
  			 mask := 16rffffffffffffffff.
  			 bits := imms.
  			 rotation := immr]
  		ifFalse:
  			[imms < 16r20
  				ifTrue: [width := 32. bits := imms] ifFalse: [
  			 imms < 16r30
  				ifTrue: [width := 16. bits := imms bitAnd: 16rF] ifFalse: [
  			 imms < 16r38
  				ifTrue: [width := 8. bits := imms bitAnd: 16r7] ifFalse: [
  			 imms < 16r3C
  				ifTrue: [width := 4. bits := imms bitAnd: 16r3] ifFalse: [
  			 imms < 16r3E
  				ifTrue: [width := 2. bits := imms bitAnd: 16r1]
  				ifFalse: [self error: 'invalid logical immediate']]]]].
  			mask := 1 << width - 1.
  			rotation := immr bitAnd: width - 1].
  
  	width - 1 = bits ifTrue:
  		[^0].
  
  	immediate := (1 << (bits + 1)) - 1.
  
  	rotation > 0 ifTrue:
+ 		[immediate := immediate << (width - rotation)].
- 		[immediate := immediate << (width - rotation) - 1].
  
  	(width between: 2 and: 32) ifTrue:
  		[immediate := (immediate bitShift: width) bitOr: immediate].
  
  	^immediate!

Item was added:
+ ----- Method: CogARMv8Compiler>>deconstructBitwiseImmediateInsruction: (in category 'debugging') -----
+ deconstructBitwiseImmediateInsruction: v
+ 	<doNotGenerate>
+ 	^{#n. v >> 22 bitAnd: 1. #imms. v >> 10 bitAnd: 16r3F. (v >> 10 bitAnd: 16r3F) hex. #immr. v >> 16 bitAnd: 16r3F. (v >> 16 bitAnd: 16r3F) hex }
+ 
+ 	"self basicNew deconstructBitwiseImmediateInsruction: 16r321a3be0"!

Item was changed:
  ----- Method: CogARMv8Compiler>>isImmNImmSImmREncodableBitmask:ifTrue:ifFalse: (in category 'generate machine code - support') -----
  isImmNImmSImmREncodableBitmask: constant ifTrue: trinaryBlock "[:n :imms :immr|...]" ifFalse: nullaryBlock
  	"See DecodeBitMasks J1-7389.
  	 See https://dinfuehr.github.io/blog/encoding-of-immediate-values-on-aarch64/
  	 This method is adapted from The LLVM Compiler Infrastructure, AArch64AddressingModes.h processLogicalImmediate"
  	<inline: #always>
  	| imm size mask numLeadingOnes numTrailingOnes immr n nImms rotateCount |
  	<var: 'mask' type: #usqInt>
  	<var: 'nImms' type: #usqInt>
  	(constant between: -1 and: 0) ifTrue:
  		[^nullaryBlock value].
  	imm := self cCode: [constant] inSmalltalk: [constant signedIntToLong64].
   
  	"First, determine the element size."
  	size := 32.
  	[mask := 1 << size - 1.
+ 	 (imm bitAnd: mask) ~= ((imm >> size) bitAnd: mask)
- 	 (imm bitAnd: mask) ~= (imm >> size)
  			ifTrue: [size := size * 2. false]
  			ifFalse: [size > 2]]
  		whileTrue: [size := size / 2].
  
  	"Second, determine the rotation to make the element be: 0^m 1^n."
  	mask := 1 << 64 - 1 >> (64 - size).
  	imm := imm bitAnd: mask.
  
  	(self isShiftedMask: imm)
  		ifTrue:
  			[rotateCount := self countTrailingZeros: imm.
  			 numTrailingOnes := self countTrailingOnes: imm >> rotateCount]
  		ifFalse:
  			[imm := imm bitOr: mask bitInvert64.
  			 (self isShiftedMask: imm) ifFalse:
  				[^nullaryBlock value].
  			 numLeadingOnes := self countLeadingOnes: imm.
  			 rotateCount := 64 - numLeadingOnes.
  			 numTrailingOnes := numLeadingOnes + (self countTrailingOnes: imm) - (64 - size)].
  
  	"Encode in Immr the number of RORs it would take to get *from* 0^m 1^n
  	 to our target value, where I is the number of RORs to go the opposite direction."
   
  	self assert: size > rotateCount. "rotateCount should be smaller than element size"
  	immr := size - rotateCount bitAnd: size - 1.
  
  	"If size has a 1 in the n'th bit, create a value that has zeroes in bits [0, n] and ones above that."
  	nImms := self cCode: [(size - 1) bitInvert64 << 1] inSmalltalk: [(size - 1) bitInvert64 << 1 bitAnd: 16rFFFFFFFFFFFFFFFF].
  
  	"Or the CTO value into the low bits, which must be below the Nth bit mentioned above."
  	nImms := nImms bitOr: numTrailingOnes - 1.
  
  	"Extract the seventh bit and toggle it to create the N field."
  	n := ((nImms >> 6) bitAnd: 1) bitXor: 1.
  
  	nImms := nImms bitAnd: 16r3F.
  
  	self assert: (self decodeN: n imms: nImms immr: immr) = constant signedIntToLong64.
  
  	^trinaryBlock
  		value: n
  		value: nImms
  		value: immr
  !

Item was changed:
  ----- Method: CogBytecodeFixup>>printStateOn: (in category 'debug printing') -----
  printStateOn: aStream
  	<doNotGenerate>
+ 	targetInstruction ifNil:
+ 		[^self].
+ 	aStream space; nextPut: $(.
  	targetInstruction ifNotNil:
+ 		[aStream space; print: targetInstruction].
+ 	instructionIndex ifNotNil:
+ 		[aStream nextPutAll: ' ix '; print: instructionIndex].
+ 	bcpc ifNotNil:
+ 		[aStream nextPutAll: ' bc '; print: bcpc].
+ 	aStream nextPut: $)!
- 		[aStream space; nextPut: $(; print: targetInstruction; nextPutAll: ' bc '; print: bcpc; nextPut: $)]!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genFetchRegArgsForPerformWithArguments: (in category 'primitive generators') -----
+ genFetchRegArgsForPerformWithArguments: sizeReg
+ 	"The arguments are in an array in Arg1Reg. Its size is in sizeReg.
+ 	 Load Arg0Reg and Arg1Reg with the first two slots.
+ 	 Since objects always have at least one slot and are aligned to 64-bits
+ 	 it is safe to load both args without checking."
+ 
+ 	cogit
+ 		MoveMw: objectMemory baseHeaderSize r: Arg1Reg R: Arg0Reg;
+ 		MoveMw: objectMemory baseHeaderSize + self wordSize r: Arg1Reg R: Arg1Reg.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genFetchRegArgsForPerformWithArguments: (in category 'primitive generators') -----
+ genFetchRegArgsForPerformWithArguments: sizeReg
+ 	"The arguments are in an array in Arg1Reg. Its size is in sizeReg.
+ 	 Load Arg0Reg and Arg1Reg with the first two slots, as appropriate.
+ 	 Since objects always have at least one slot it is safe to load arg0 without checking.
+ 	 But the array could be at the end of memory so we must check that it has two
+ 	 slots before it is safe to access the second slot."
+ 
+ 	| skip |
+ 	cogit MoveMw: objectMemory baseHeaderSize r: Arg1Reg R: Arg0Reg.
+ 	cogit CmpCq: 2 R: sizeReg.
+ 	skip := cogit JumpLess: 0.
+ 	cogit MoveMw: objectMemory baseHeaderSize + self wordSize r: Arg1Reg R: Arg1Reg.
+ 	skip jmpTarget: cogit Label.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genFetchRegArgsForPerformWithArguments: (in category 'primitive generators') -----
+ genFetchRegArgsForPerformWithArguments: sizeReg
+ 	"The arguments are in an array in Arg1Reg. Its size is in sizeReg.
+ 	 Load Arg0Reg and Arg1Reg with the first two slots."
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genPrimitivePerformWithArguments (in category 'primitive generators') -----
+ genPrimitivePerformWithArguments
+ 	<doNotGenerate>
+ 	^cogit genPrimitivePerformWithArguments!

Item was changed:
  ----- Method: CogSSBytecodeFixup>>printStateOn: (in category 'debug printing') -----
  printStateOn: aStream
  	<doNotGenerate>
  	(targetInstruction isNil and: [simStackPtr isNil]) ifTrue:
  		[^self].
  	aStream space; nextPut: $(.
  	targetInstruction ifNotNil:
  		[aStream space; print: targetInstruction].
+ 	instructionIndex ifNotNil:
+ 		[aStream nextPutAll: ' ix '; print: instructionIndex].
  	simStackPtr ifNotNil:
  		[aStream nextPutAll: ' sp '; print: simStackPtr].
  	bcpc ifNotNil:
  		[aStream nextPutAll: ' bc '; print: bcpc].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: Cogit class>>initializeErrorCodes (in category 'class initialization') -----
  initializeErrorCodes
  	"External errors, returned to or from cog:selector:"
  	NotFullyInitialized := -1.
  	InsufficientCodeSpace := -2.
  	MethodTooBig := -4.
  	YoungSelectorInPIC := -5.
  	EncounteredUnknownBytecode := -6.
+ 	UnimplementedPrimitive := -7. "Answered by a primitive generator that always falls back on the interpreter primitive."
- 	UnimplementedPrimitive := -7.
  	ShouldNotJIT := -8.
  	MaxNegativeErrorCode := ShouldNotJIT.
  	"Internal errors returned by generator routines to other generator routines"
  	BadRegisterSet := 1.
  	UnimplementedOperation := 2.
  	"Internal successes answered by CogObjectRepresentation to JIT, etc"
+ 	UnfailingPrimitive := 3. "Answered by a primitive generator for a primitive that will never fail, and hence does not need to fall back on the interpreter primitive."
+ 	CompletePrimitive := 4 "Answered by a primitive generator that does not need to fall back on the interpreter primitive except for an error code.
+ 							 The fall back code will only be generated if the method being jitted uses the error code."!
- 	UnfailingPrimitive := 3. "Answered by a primitive generator for a primitive that will never fail"
- 	CompletePrimitive := 4 "Answered by a primitive generator that does not bneed to fall back on the interpreter primitive except for an error code."!

Item was changed:
  ----- Method: Cogit>>MoveMb:r:R: (in category 'abstract instructions') -----
  MoveMb: offset r: baseReg R: destReg
+ 	"N.B.  This instruction is guaranteed to zero-extend the byte into destReg
+ 	 iff backEnd byteReadsZeroExtend."
- 	"N.B.  This instruction is guaranteed to zero-extend the byte into destReg."
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	^self gen: MoveMbrR quickConstant: offset operand: baseReg operand: destReg!

Item was added:
+ ----- Method: Cogit>>genPrimitivePerformWithArguments (in category 'primitive generators') -----
+ genPrimitivePerformWithArguments
+ 	"Generate an in-line perform:withArguments: primitive.  The lookup code requires the selector to be in Arg0Reg
+ 	 and the array to be in Arg1Reg.  The primitive will only handle cases 0 to numRegArgs.  Is it worth it you ask?
+ 	 Here are arguemnt count requencies for a short run of Croquet/Virtend which show that even for V3, with only
+ 	 one rtegister arg, it very much is (but we wimp out on V3 cuz of the complexity of checking the Array):
+ 		[0] = 253743		52.5%
+ 		[1] = 116117		24%/76.5%
+ 		[2] = 99876		20.7%/97.2%
+ 		[3] = 12837		2.7%/99.9%
+ 		[4] = 209
+ 		[5] = 84
+ 		[6] = 2
+ 		[7] = 313
+ 		[8] = 0
+ 		[9] = 0
+ 		[10] = 0
+ 		[11] = 1
+ 		[12] = 0
+ 		[13] = 0
+ 		[14] = 0
+ 		[15] = 0"
+ 	^UnimplementedPrimitive!

Item was changed:
  ----- Method: Cogit>>maybeBreakGeneratingInstructionWithIndex: (in category 'simulation only') -----
  maybeBreakGeneratingInstructionWithIndex: index
  	"Variation on maybeBreakAt: that only works for integer abstract instruction indexes,
  	 so we can have break blocks that stop at any pc, except when generating."
  	<cmacro: '(i) 0'> "Simulation only; void in C"
+ 	(InitializationOptions at: #instructionIndex ifAbsent: nil) ifNotNil:
+ 		[:breakIndexOrIndices|
+ 		(breakIndexOrIndices isCollection
+ 				ifTrue: [breakIndexOrIndices includes: index]
+ 				ifFalse: [breakIndexOrIndices = index]) ifTrue:
+ 			[self halt]]!
- 	(InitializationOptions at: #instructionIndex ifAbsent: nil) ifNotNil: [:breakIndex| index = breakIndex ifTrue: [self halt]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForNewsqueak (in category 'class initialization') -----
  initializePrimitiveTableForNewsqueak
  	"Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter.
  	 N.B. primitives that don't have an explicit arg count (the integer following the generator) may be variadic."
  	"SimpleStackBasedCogit initializePrimitiveTableForNewsqueak"
  	MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8
  										ifTrue: [575]
  										ifFalse: [575].
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
  		(1 genPrimitiveAdd				1)
  		(2 genPrimitiveSubtract			1)
  		(3 genPrimitiveLessThan		1)
  		(4 genPrimitiveGreaterThan		1)
  		(5 genPrimitiveLessOrEqual		1)
  		(6 genPrimitiveGreaterOrEqual	1)
  		(7 genPrimitiveEqual			1)
  		(8 genPrimitiveNotEqual		1)
  		(9 genPrimitiveMultiply			1)
  		(10 genPrimitiveDivide			1)
  		(11 genPrimitiveMod			1)
  		(12 genPrimitiveDiv				1)
  		(13 genPrimitiveQuo			1)
  		(14 genPrimitiveBitAnd			1)
  		(15 genPrimitiveBitOr			1)
  		(16 genPrimitiveBitXor			1)
  		(17 genPrimitiveBitShift			1)
  		"(18 primitiveMakePoint)"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
  		"(38 genPrimitiveFloatAt)"
  		"(39 genPrimitiveFloatAtPut)"
  		(40 genPrimitiveAsFloat					0)
  		(41 genPrimitiveFloatAdd				1)
  		(42 genPrimitiveFloatSubtract			1)
  		(43 genPrimitiveFloatLessThan			1)
  		(44 genPrimitiveFloatGreaterThan		1)
  		(45 genPrimitiveFloatLessOrEqual		1)
  		(46 genPrimitiveFloatGreaterOrEqual	1)
  		(47 genPrimitiveFloatEqual				1)
  		(48 genPrimitiveFloatNotEqual			1)
  		(49 genPrimitiveFloatMultiply			1)
  		(50 genPrimitiveFloatDivide				1)
  		"(51 genPrimitiveTruncated)"
  		"(52 genPrimitiveFractionalPart)"
  		"(53 genPrimitiveExponent)"
  		"(54 genPrimitiveTimesTwoPower)"
  		(55 genPrimitiveFloatSquareRoot		0)
  		"(56 genPrimitiveSine)"
  		"(57 genPrimitiveArctan)"
  		"(58 genPrimitiveLogN)"
  		"(59 genPrimitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt				1)
  		(61 genPrimitiveAtPut			2)
  		(62 genPrimitiveSize			0)
  		(63 genPrimitiveStringAt		1)
  		(64 genPrimitiveStringAtPut		2)
  		"The stream primitives no longer pay their way; normal Smalltalk code is faster."
  		(65 genFastPrimFail)"was primitiveNext"
  		(66 genFastPrimFail) "was primitiveNextPut"
  		(67 genFastPrimFail) "was primitiveAtEnd"
  
  		"StorageManagement Primitives (68-79)"
  		(68 genPrimitiveObjectAt			1)	"Good for debugger/InstructionStream performance"
  		"(69 primitiveObjectAtPut)"
  		(70 genPrimitiveNew)				"For VMMirror support 1 argument instantiateFixedClass: as well as baiscNew"
  		(71 genPrimitiveNewWithArg)		"For VMMirror support 2 argument instantiateVariableClass:withSize: as well as baiscNew:"
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
  		(79 genPrimitiveNewMethod	2)
  
  		"Control Primitives (80-89)"
  		"(80 primitiveFail)"							"Blue Book: primitiveBlockCopy"
  		"(81 primitiveFail)"							"Blue Book: primitiveValue"
  		"(82 primitiveFail)"							"Blue Book: primitiveValueWithArgs"
  		(83 genPrimitivePerform)
+ 		(84 genPrimitivePerformWithArguments	2)
- 		"(84 primitivePerformWithArgs)"
  		"(85 primitiveSignal)"
  		"(86 primitiveWait)"
  		"(87 primitiveResume)"
  		"(88 primitiveSuspend)"
  		"(89 primitiveFlushCache)"
  
  		"System Primitives (110-119)"
  		(110 genPrimitiveIdentical 1)
  		(111 genPrimitiveClass)			"For objectClass: and VMMirror support 1 argument classOf: as well as class"
  		"(112 primitiveBytesLeft)"
  		"(113 primitiveQuit)"
  		"(114 primitiveExitToDebugger)"
  		"(115 primitiveChangeClass)"					"Blue Book: primitiveOopsLeft"
  		"(116 primitiveFlushCacheByMethod)"
  		"(117 primitiveExternalCall)"
  		"(118 primitiveDoPrimitiveWithArgs)"
  		"(119 primitiveFlushCacheSelective)"
  
  		(148 genPrimitiveShallowCopy 0)			"a.k.a. clone"
  
  		(165 genPrimitiveIntegerAt			1)	"Signed version of genPrimitiveAt"
  		(166 genPrimitiveIntegerAtPut		2)	"Signed version of genPrimitiveAtPut"
  
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)				"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveImmediateAsInteger 0)	"Character>>asInteger/hash/identityHash, SmallFloat64>>identityHash"
  			
  		"(173 primitiveSlotAt 1)"
  		"(174 primitiveSlotAtPut 2)"
  		(175 genPrimitiveIdentityHash	0)		"Behavior>>identityHash"
  
  		"Old closure primitives"
  		"(186 primitiveFail)" "was primitiveClosureValue"
  		"(187 primitiveFail)" "was primitiveClosureValueWithArgs"
  
  		"Perform method directly"
  		"(188 primitiveExecuteMethodArgsArray)"
  		"(189 primitiveExecuteMethod)"
  
  		"Unwind primitives"
  		"(195 primitiveFindNextUnwindContext)"
  		"(196 primitiveTerminateTo)"
  		"(197 primitiveFindHandlerContext)"
  		(198 genFastPrimFail "primitiveMarkUnwindMethod")
  		(199 genFastPrimFail "primitiveMarkHandlerMethod")
  
  		"new closure primitives"
  		"(200 primitiveClosureCopyWithCopiedValues)"
  		(201 genPrimitiveClosureValue	0) "value"
  		(202 genPrimitiveClosureValue	1) "value:"
  		(203 genPrimitiveClosureValue	2) "value:value:"
  		(204 genPrimitiveClosureValue	3) "value:value:value:"
  		(205 genPrimitiveClosureValue	4) "value:value:value:value:"
  		"(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"
  
  		"(210 primitiveContextAt)"
  		"(211 primitiveContextAtPut)"
  		"(212 primitiveContextSize)"
  
  		"(218 primitiveDoNamedPrimitiveWithArgs)"
  		"(219 primitiveFail)"	"reserved for Cog primitives"
  
  		"(220 primitiveFail)"		"reserved for Cog primitives"
  
  		(221 genPrimitiveClosureValue	0) "valueNoContextSwitch"
  		(222 genPrimitiveClosureValue	1) "valueNoContextSwitch:"
  
  		"SmallFloat primitives (540-559)"
  		(541 genPrimitiveSmallFloatAdd				1)
  		(542 genPrimitiveSmallFloatSubtract			1)
  		(543 genPrimitiveSmallFloatLessThan			1)
  		(544 genPrimitiveSmallFloatGreaterThan		1)
  		(545 genPrimitiveSmallFloatLessOrEqual		1)
  		(546 genPrimitiveSmallFloatGreaterOrEqual		1)
  		(547 genPrimitiveSmallFloatEqual				1)
  		(548 genPrimitiveSmallFloatNotEqual			1)
  		(549 genPrimitiveSmallFloatMultiply				1)
  		(550 genPrimitiveSmallFloatDivide				1)
  		"(551 genPrimitiveSmallFloatTruncated			0)"
  		"(552 genPrimitiveSmallFloatFractionalPart		0)"
  		"(553 genPrimitiveSmallFloatExponent			0)"
  		"(554 genPrimitiveSmallFloatTimesTwoPower	1)"
  		(555 genPrimitiveSmallFloatSquareRoot			0)
  		"(556 genPrimitiveSmallFloatSine				0)"
  		"(557 genPrimitiveSmallFloatArctan				0)"
  		"(558 genPrimitiveSmallFloatLogN				0)"
  		"(559 genPrimitiveSmallFloatExp				0)"
  		(575 genPrimitiveHighBit			0)
  	)!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForSqueak (in category 'class initialization') -----
  initializePrimitiveTableForSqueak
  	"Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter.
  	 N.B. primitives that don't have an explicit arg count (the integer following the generator) may be variadic."
  	"SimpleStackBasedCogit initializePrimitiveTableForSqueak"
  	MaxCompiledPrimitiveIndex := 582.
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
  		(1 genPrimitiveAdd				1)
  		(2 genPrimitiveSubtract		1)
  		(3 genPrimitiveLessThan		1)
  		(4 genPrimitiveGreaterThan		1)
  		(5 genPrimitiveLessOrEqual		1)
  		(6 genPrimitiveGreaterOrEqual	1)
  		(7 genPrimitiveEqual			1)
  		(8 genPrimitiveNotEqual		1)
  		(9 genPrimitiveMultiply			1)
  		(10 genPrimitiveDivide			1)
  		(11 genPrimitiveMod			1)
  		(12 genPrimitiveDiv				1)
  		(13 genPrimitiveQuo			1)
  		(14 genPrimitiveBitAnd			1)
  		(15 genPrimitiveBitOr			1)
  		(16 genPrimitiveBitXor			1)
  		(17 genPrimitiveBitShift		1)
  		(18 genPrimitiveMakePoint		1)	"this is here mainly to remove noise from printPrimTraceLog()"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
  		"(38 genPrimitiveFloatAt)"
  		"(39 genPrimitiveFloatAtPut)"
  		(40 genPrimitiveAsFloat					0)
  		(41 genPrimitiveFloatAdd				1)
  		(42 genPrimitiveFloatSubtract			1)
  		(43 genPrimitiveFloatLessThan			1)
  		(44 genPrimitiveFloatGreaterThan		1)
  		(45 genPrimitiveFloatLessOrEqual		1)
  		(46 genPrimitiveFloatGreaterOrEqual	1)
  		(47 genPrimitiveFloatEqual				1)
  		(48 genPrimitiveFloatNotEqual			1)
  		(49 genPrimitiveFloatMultiply			1)
  		(50 genPrimitiveFloatDivide				1)
  		"(51 genPrimitiveTruncated)"
  		"(52 genPrimitiveFractionalPart)"
  		"(53 genPrimitiveExponent)"
  		"(54 genPrimitiveTimesTwoPower)"
  		(55 genPrimitiveFloatSquareRoot		0)
  		"(56 genPrimitiveSine)"
  		"(57 genPrimitiveArctan)"
  		"(58 genPrimitiveLogN)"
  		"(59 genPrimitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt				1)
  		(61 genPrimitiveAtPut			2)
  		(62 genPrimitiveSize			0)
  		(63 genPrimitiveStringAt		1)
  		(64 genPrimitiveStringAtPut	2)
  		"The stream primitives no longer pay their way; normal Smalltalk code is faster."
  		(65 genFastPrimFail)"was primitiveNext"
  		(66 genFastPrimFail) "was primitiveNextPut"
  		(67 genFastPrimFail) "was primitiveAtEnd"
  
  		"StorageManagement Primitives (68-79)"
  		(68 genPrimitiveObjectAt		1)	"Good for debugger/InstructionStream performance"
  		"(69 primitiveObjectAtPut)"
  		(70 genPrimitiveNew			0)
  		(71 genPrimitiveNewWithArg	1)
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
  		(79 genPrimitiveNewMethod	2)
  
  		"Control Primitives (80-89)"
  		"(80 primitiveFail)"							"Blue Book: primitiveBlockCopy"
  		"(81 primitiveFail)"							"Blue Book: primitiveValue"
  		"(82 primitiveFail)"							"Blue Book: primitiveValueWithArgs"
  		(83 genPrimitivePerform)
+ 		(84 genPrimitivePerformWithArguments	2)
- 		"(84 primitivePerformWithArgs)"
  		"(85 primitiveSignal)"
  		"(86 primitiveWait)"
  		"(87 primitiveResume)"
  		"(88 primitiveSuspend)"
  		"(89 primitiveFlushCache)"
  
  		"(90 primitiveMousePoint)"
  		"(91 primitiveTestDisplayDepth)"			"Blue Book: primitiveCursorLocPut"
  		"(92 primitiveSetDisplayMode)"				"Blue Book: primitiveCursorLink"
  		"(93 primitiveInputSemaphore)"
  		"(94 primitiveGetNextEvent)"				"Blue Book: primitiveSampleInterval"
  		"(95 primitiveInputWord)"
  		"(96 primitiveFail)"	"primitiveCopyBits"
  		"(97 primitiveSnapshot)"
  		"(98 primitiveStoreImageSegment)"
  		"(99 primitiveLoadImageSegment)"
  		"(100 primitivePerformInSuperclass)"		"Blue Book: primitiveSignalAtTick"
  		"(101 primitiveBeCursor)"
  		"(102 primitiveBeDisplay)"
  		"(103 primitiveScanCharacters)"
  		"(104 primitiveFail)"	"primitiveDrawLoop"
  		(105 genPrimitiveStringReplace)
  		"(106 primitiveScreenSize)"
  		"(107 primitiveMouseButtons)"
  		"(108 primitiveKbdNext)"
  		"(109 primitiveKbdPeek)"
  
  
  		"System Primitives (110-119)"
  		(110 genPrimitiveIdentical 1)
  		(111 genPrimitiveClass)				"Support both class and Context>>objectClass:"
  		"(112 primitiveBytesLeft)"
  		"(113 primitiveQuit)"
  		"(114 primitiveExitToDebugger)"
  		"(115 primitiveChangeClass)"					"Blue Book: primitiveOopsLeft"
  		"(116 primitiveFlushCacheByMethod)"
  		"(117 primitiveExternalCall)"
  		"(118 primitiveDoPrimitiveWithArgs)"
  		"(119 primitiveFlushCacheSelective)"
  
  		(148 genPrimitiveShallowCopy 0)			"a.k.a. clone"
  
  		(158 genPrimitiveStringCompareWith 1)
  		(159 genPrimitiveHashMultiply 0)
  
  		(165 genPrimitiveIntegerAt			1)	"Signed version of genPrimitiveAt"
  		(166 genPrimitiveIntegerAtPut		2)	"Signed version of genPrimitiveAtPut"
  
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)				"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveImmediateAsInteger 0)	"Character>>asInteger/hash/identityHash, SmallFloat64>>identityHash"
  			
  		(173 genPrimitiveSlotAt 1)				"Good for micro-benchmark performance, and for reducing noise in Croquet primitive trace logs"
  		(174 genPrimitiveSlotAtPut 2)			"ditto"
  		(175 genPrimitiveIdentityHash	0)		"Behavior>>identityHash"
  
  		"Old closure primitives"
  		"(186 primitiveFail)" "was primitiveClosureValue"
  		"(187 primitiveFail)" "was primitiveClosureValueWithArgs"
  
  		"Perform method directly"
  		"(188 primitiveExecuteMethodArgsArray)"
  		"(189 primitiveExecuteMethod)"
  
  		"Unwind primitives"
  		"(195 primitiveFindNextUnwindContext)"
  		"(196 primitiveTerminateTo)"
  		"(197 primitiveFindHandlerContext)"
  		(198 genFastPrimFail "primitiveMarkUnwindMethod")
  		(199 genFastPrimFail "primitiveMarkHandlerMethod")
  
  		"new closure primitives"
  		"(200 primitiveClosureCopyWithCopiedValues)"
  		(201 genPrimitiveClosureValue	0) "value"
  		(202 genPrimitiveClosureValue	1) "value:"
  		(203 genPrimitiveClosureValue	2) "value:value:"
  		(204 genPrimitiveClosureValue	3) "value:value:value:"
  		(205 genPrimitiveClosureValue	4) "value:value:value:value:"
  		"(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"
  
  		(207 genPrimitiveFullClosureValue) "value[:value:value:value:] et al"
  		"(208 genPrimitiveFullClosureValueWithArgs)" "valueWithArguments:"
  		(209 genPrimitiveFullClosureValue) "valueNoContextSwitch[:value:] et al"
  
  		"(210 primitiveContextAt)"
  		"(211 primitiveContextAtPut)"
  		"(212 primitiveContextSize)"
  
  		"(218 primitiveDoNamedPrimitiveWithArgs)"
  		"(219 primitiveFail)"	"reserved for Cog primitives"
  
  		"(220 primitiveFail)"		"reserved for Cog primitives"
  
  		(221 genPrimitiveClosureValue	0) "valueNoContextSwitch"
  		(222 genPrimitiveClosureValue	1) "valueNoContextSwitch:"
  
  		"SmallFloat primitives (540-559)"
  		(541 genPrimitiveSmallFloatAdd				1)
  		(542 genPrimitiveSmallFloatSubtract			1)
  		(543 genPrimitiveSmallFloatLessThan			1)
  		(544 genPrimitiveSmallFloatGreaterThan		1)
  		(545 genPrimitiveSmallFloatLessOrEqual		1)
  		(546 genPrimitiveSmallFloatGreaterOrEqual		1)
  		(547 genPrimitiveSmallFloatEqual				1)
  		(548 genPrimitiveSmallFloatNotEqual			1)
  		(549 genPrimitiveSmallFloatMultiply				1)
  		(550 genPrimitiveSmallFloatDivide				1)
  		"(551 genPrimitiveSmallFloatTruncated			0)"
  		"(552 genPrimitiveSmallFloatFractionalPart		0)"
  		"(553 genPrimitiveSmallFloatExponent			0)"
  		"(554 genPrimitiveSmallFloatTimesTwoPower	1)"
  		(555 genPrimitiveSmallFloatSquareRoot			0)
  		"(556 genPrimitiveSmallFloatSine				0)"
  		"(557 genPrimitiveSmallFloatArctan				0)"
  		"(558 genPrimitiveSmallFloatLogN				0)"
  		"(559 genPrimitiveSmallFloatExp				0)"
  
  		"(568 primitiveSuspendBackingUpV1)				0)"
  
  		(575 genPrimitiveHighBit							0)
  
  		"(578 primitiveSuspendBackingUpV2				0)"
  
  		"(580 primitivePinnedNewInOldSpace				0)"
  		"(581 primitivePinnedNewWithArgInOldSpace	1)"
  		(582 genPrimitiveUninitializedNewWithArg		1)
  		"reserved for (583 primitivePinnedUninitializedNewWithArgInOldSpace	1)"
  	)!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genLoadcmNumArgsOf:into: (in category 'primitive generators') -----
+ genLoadcmNumArgsOf: cogMethodReg into: targetReg
+ 	"Currently cmNumArgs is the first byte following the objectHeader."
+ 	<inline: true>
+ 	backEnd byteReadsZeroExtend ifFalse:
+ 		[self MoveCq: 0 R: targetReg].
+ 	self MoveMb: objectRepresentation wordSize r: cogMethodReg R: targetReg!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genLookupForPerformWithArguments (in category 'primitive generators') -----
+ genLookupForPerformWithArguments
+ 	"Compile the code for a probe of the first-level method cache for the perform:withArguments: primitive.
+ 	 The selector is assumed to be in Arg0Reg an d the array in Arg1Reg.  Fall back to the interpreter if
+ 	 the size of the array is greater than numRegArgs."
+ 	<inline: true>
+ 	| jumpImmArray jumpSelectorMiss jumpClassMiss jumpInterpret jumpBadNumArgs1 jumpBadNumArgs2 itsAHit cacheBaseReg |
+ 
+ 	"N.B.  Can't assume TempReg already contains the tag because a method can
+ 	 of course be invoked via the unchecked entry-point, e.g. as does perform:."
+ 	jumpImmArray := objectRepresentation genJumpImmediate: Arg1Reg.
+ 	objectRepresentation genGetInlineCacheClassTagFrom: ReceiverResultReg into: SendNumArgsReg forEntry: false.
+ 	
+ 
+ 	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:class:"
+ 
+ 	cacheBaseReg := NoReg.
+ 	(backEnd isWithinMwOffsetRange: coInterpreter methodCacheAddress) ifFalse:
+ 		[self MoveCq: coInterpreter methodCacheAddress R: (cacheBaseReg := Extra0Reg)].
+ 
+ 	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:classTag:"
+ 	jumpSelectorMiss := self compilePerformMethodCacheProbeFor: Arg0Reg withShift: 0 baseRegOrNone: cacheBaseReg.
+ 	jumpClassMiss := self JumpNonZero: 0.
+ 
+ 	"Fetch the method, and check if it is cogged."
+ 	itsAHit := self MoveMw: (cacheBaseReg = NoReg
+ 								ifTrue: [coInterpreter methodCacheAddress + (MethodCacheMethod << objectMemory shiftForWord)]
+ 								ifFalse: [MethodCacheMethod << objectMemory shiftForWord])
+ 					r: ClassReg
+ 					R: SendNumArgsReg.
+ 	"If the method is not compiled fall back on the interpreter primitive."
+ 	objectRepresentation genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: ClassReg.
+ 	jumpInterpret := objectRepresentation genJumpImmediate: ClassReg.
+ 	"check the argument count; if it's wrong fall back on the interpreter primitive."
+ 	self genLoadcmNumArgsOf: ClassReg into: SendNumArgsReg.
+ 	objectRepresentation genGetRawSlotSizeOfNonImm: Arg1Reg into: TempReg.
+ 	self CmpR: TempReg R: SendNumArgsReg.
+ 	jumpBadNumArgs1 := self JumpNonZero: 0.
+ 	self CmpCq: self numRegArgs R: SendNumArgsReg.
+ 	jumpBadNumArgs2 := self JumpGreater: 0.
+ 	
+ 	"Fetch arguments and jump to the method's unchecked entry-point."
+ 	objectRepresentation genFetchRegArgsForPerformWithArguments: TempReg.
+ 	self AddCq: cmNoCheckEntryOffset R: ClassReg.
+ 	self JumpR: ClassReg.
+ 
+ 	"First probe missed.  Do second of three probes.  Shift hash right one and retry."
+ 	jumpSelectorMiss jmpTarget: (jumpClassMiss jmpTarget: self Label).
+ 	jumpSelectorMiss := self compilePerformMethodCacheProbeFor: Arg0Reg withShift: 1 baseRegOrNone: cacheBaseReg.
+ 	self JumpZero: itsAHit.
+ 
+ 	"Second probe missed.  Do last probe.  Shift hash right two and retry."
+ 	jumpSelectorMiss jmpTarget: self Label.
+ 	jumpSelectorMiss := self compilePerformMethodCacheProbeFor: Arg0Reg withShift: 2 baseRegOrNone: cacheBaseReg.
+ 	self JumpZero: itsAHit.
+ 
+ 	"Last probe missed/not jitted/bad num args.  Caller will generate the call to fall back on the interpreter primitive."
+ 	jumpImmArray jmpTarget:
+ 	(jumpSelectorMiss jmpTarget:
+ 	(jumpInterpret jmpTarget:
+ 	(jumpBadNumArgs1 jmpTarget:
+ 	(jumpBadNumArgs2 jmpTarget: self Label)))).
+ 	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitivePerformWithArguments (in category 'primitive generators') -----
+ genPrimitivePerformWithArguments
+ 	"Generate an in-line perform:withArguments: primitive.  The lookup code requires the selector to be in Arg0Reg
+ 	 and the array to be in Arg1Reg.  The primitive will only handle cases 0 to numRegArgs.  Is it worth it you ask?
+ 	 Here are arguemnt count requencies for a short run of Croquet/Virtend which show that even for V3, with only
+ 	 one rtegister arg, it very much is (but we wimp out on V3 cuz of the complexity of checking the Array):
+ 		[0] = 253743		52.5%
+ 		[1] = 116117		24%/76.5%
+ 		[2] = 99876		20.7%/97.2%
+ 		[3] = 12837		2.7%/99.9%
+ 		[4] = 209
+ 		[5] = 84
+ 		[6] = 2
+ 		[7] = 313
+ 		[8] = 0
+ 		[9] = 0
+ 		[10] = 0
+ 		[11] = 1
+ 		[12] = 0
+ 		[13] = 0
+ 		[14] = 0
+ 		[15] = 0"
+ 	<option: #SpurObjectMemory>
+ 	self MoveMw: (backEnd hasLinkRegister
+ 					ifTrue: [1]
+ 					ifFalse: [2]) * objectMemory wordSize
+ 		r: SPReg
+ 		R: Arg0Reg;
+ 		MoveMw: (backEnd hasLinkRegister
+ 					ifTrue: [2]
+ 					ifFalse: [3]) * objectMemory wordSize
+ 		r: SPReg
+ 		R: Arg1Reg.
+ 	^self genLookupForPerformWithArguments!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genPrimitivePerformWithArguments (in category 'primitive generators') -----
+ genPrimitivePerformWithArguments
+ 	"Generate an in-line perform:withArguments: primitive.  The lookup code requires the selector to be in Arg0Reg
+ 	 and the array to be in Arg1Reg.  The primitive will only handle cases 0 to numRegArgs.  Is it worth it you ask?
+ 	 Here are arguemnt count requencies for a short run of Croquet/Virtend which show that even for V3, with only
+ 	 one rtegister arg, it very much is (but we wimp out on V3 cuz of the complexity of checking the Array):
+ 		[0] = 253743		52.5%
+ 		[1] = 116117		24%/76.5%
+ 		[2] = 99876		20.7%/97.2%
+ 		[3] = 12837		2.7%/99.9%
+ 		[4] = 209
+ 		[5] = 84
+ 		[6] = 2
+ 		[7] = 313
+ 		[8] = 0
+ 		[9] = 0
+ 		[10] = 0
+ 		[11] = 1
+ 		[12] = 0
+ 		[13] = 0
+ 		[14] = 0
+ 		[15] = 0"
+ 	<option: #SpurObjectMemory>
+ 	^self genLookupForPerformWithArguments!



More information about the Vm-dev mailing list