[Vm-dev] VM Maker: VMMaker.oscog-cb.2273.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Oct 23 09:42:43 UTC 2017


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2273.mcz

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

Name: VMMaker.oscog-cb.2273
Author: cb
Time: 23 October 2017, 11:37:06.338298 am
UUID: c60f4b8e-d260-455d-abe8-d1e99e972953
Ancestors: VMMaker.oscog-cb.2272

Added primitiveStringReplace in the JIT with Spur (was showing to Sophie how to write code in the JIT, so we did that together). We implemented only the quick paths for byte objects and array-like objects.

Can't wait to see people like Levente benching these things again. Aside from the copying loops, I am pretty sure the machine code generated can be improved - but we see the 2x perf boost on copies of less than 10 elements, which is the main case I wanted to speed up.

=============== Diff against VMMaker.oscog-cb.2272 ===============

Item was added:
+ ----- Method: CogObjectRepresentation>>genPrimitiveStringReplace (in category 'primitive generators') -----
+ genPrimitiveStringReplace
+ 	"subclasses override if they can"
+ 	^UnimplementedPrimitive!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genPrimitiveStringReplace (in category 'primitive generators') -----
+ genPrimitiveStringReplace
+ 	"replaceFrom: start to: stop with: replacement startingAt: repStart. 
+ 	
+ 	The primitive in the JIT tries to deal with two pathological cases, copy of arrays and byteStrings,
+ 	which often copies only a dozen of fields and where switching to the C runtime cost a lot.
+ 	
+ 	Based on heuristics on the method class, I generate a quick array path (typically for Array),
+ 	a quick byteString path (typically for ByteString, ByteArray and LargeInteger) or no quick 
+ 	path at all (Typically for Bitmap).
+ 	
+ 	The many tests to ensure that the primitive won't fail are not super optimised (multiple reloading
+ 	or stack arguments in registers) but this is still good enough and worth it since we're avoiding 
+ 	the Smalltalk to C stack switch. The tight copying loops are optimised. 
+ 	
+ 	It is possible to build a bigger version with the 2 different paths but I (Clement) believe this 
+ 	is too big machine code wise to be worth it."
+ 	
+ 	|arrayReg startReg stopReg replReg repStartReg jumpNotSmi1 jumpNotSmi2 jumpNotSmi3 jumpImm jumpEmpty jumpImmutable jumpOutOfBounds1 jumpOutOfBounds2 jumpOutOfBounds3 jumpOutOfBounds4 jumpIncorrectFormat1 jumpIncorrectFormat2 jumpIncorrectFormat3 jumpIncorrectFormat4 result jmpDestYoung jmpAlreadyRemembered instr jumpFinished adjust|
+ 	
+ 	<var: #jumpImm type: #'AbstractInstruction *'>
+ 	<var: #jumpEmpty type: #'AbstractInstruction *'>
+ 	<var: #jumpFinished type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSmi1 type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSmi2 type: #'AbstractInstruction *'>
+ 	<var: #jumpNotSmi3 type: #'AbstractInstruction *'>
+ 	<var: #jmpDestYoung type: #'AbstractInstruction *'>
+ 	<var: #jumpImmutable type: #'AbstractInstruction *'>
+ 	<var: #jumpOutOfBounds1 type: #'AbstractInstruction *'>
+ 	<var: #jumpOutOfBounds2 type: #'AbstractInstruction *'>
+ 	<var: #jumpOutOfBounds3 type: #'AbstractInstruction *'>
+ 	<var: #jumpOutOfBounds4 type: #'AbstractInstruction *'>
+ 	<var: #jumpIncorrectFormat1 type: #'AbstractInstruction *'>
+ 	<var: #jumpIncorrectFormat2 type: #'AbstractInstruction *'>
+ 	<var: #jumpIncorrectFormat3 type: #'AbstractInstruction *'>
+ 	<var: #jumpIncorrectFormat4 type: #'AbstractInstruction *'>
+ 	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
+ 	
+ 	"Can I generate a quick path for this method ?"
+ 	((cogit seemsToBeInstantiating: objectMemory arrayFormat)
+ 		or: [cogit seemsToBeInstantiating: objectMemory firstByteFormat]) ifFalse: [^UnimplementedPrimitive].
+ 	
+ 	"I redefine those name to ease program comprehension"
+ 	arrayReg := ReceiverResultReg.
+ 	startReg := Arg0Reg.
+ 	stopReg := Arg1Reg.
+ 	replReg := ClassReg.
+ 	repStartReg := SendNumArgsReg.
+ 	
+ 	"Load arguments in reg"
+ 	cogit genStackArgAt: 0 into: repStartReg.
+ 	cogit genStackArgAt: 1 into: replReg.
+ 	cogit genStackArgAt: 2 into: stopReg.
+ 	cogit genStackArgAt: 3 into: startReg.
+ 
+ 	"start,stop,repStart Smis or fail the primitive"
+ 	jumpNotSmi1 := self genJumpNotSmallInteger: repStartReg scratchReg: TempReg.
+ 	jumpNotSmi2 := self genJumpNotSmallInteger: stopReg scratchReg: TempReg.
+ 	jumpNotSmi3 := self genJumpNotSmallInteger: startReg scratchReg: TempReg.
+ 	"repl non immediate or fail the primitive"
+ 	jumpImm := self genJumpImmediate: replReg.
+ 	
+ 	"if start>stop primitive success"
+ 	cogit CmpR: startReg R: stopReg.
+ 	jumpEmpty := cogit JumpLess: 0.
+ 	
+ 	"If receiver immutable fail the primitive "
+ 	self
+ 		cppIf: IMMUTABILITY
+ 		ifTrue: [jumpImmutable := self genJumpImmutable: ReceiverResultReg scratchReg: TempReg].
+ 		
+ 	"0 >= start, fail"
+ 	cogit CmpCq: (objectMemory integerObjectOf: 0) R: startReg.
+ 	jumpOutOfBounds1 := cogit JumpLess: 0.
+ 	
+ 	"0 >= replStart, fail"
+ 	cogit CmpCq: (objectMemory integerObjectOf: 0) R: repStartReg.
+ 	jumpOutOfBounds2 := cogit JumpLess: 0.
+ 
+ 	"--- Pointer object version ---"
+ 	(cogit seemsToBeInstantiating: objectMemory arrayFormat) ifTrue:
+ 		["Are they both array format ?"
+ 		self genGetFormatOf: arrayReg into: TempReg.
+ 		self genGetFormatOf: replReg into: startReg.
+ 		cogit CmpCq: objectMemory arrayFormat R: startReg.
+ 		jumpIncorrectFormat1 := cogit JumpNonZero: 0.
+ 		cogit CmpCq: objectMemory arrayFormat R: TempReg.
+ 		jumpIncorrectFormat2 := cogit JumpNonZero: 0.
+ 	
+ 		"Both objects are arrays,"
+ 		self genGetNumSlotsOf: arrayReg into: TempReg.
+ 		self genConvertSmallIntegerToIntegerInReg: stopReg.
+ 	
+ 		"arr size < stop"
+ 		cogit CmpR: TempReg R: stopReg.
+ 		jumpOutOfBounds3 := cogit JumpGreater: 0.
+ 	
+ 		"rep size < repStart - start + stop"
+ 		self genGetNumSlotsOf: replReg into: TempReg.
+ 		cogit genStackArgAt: 3 into: startReg.
+ 		self genConvertSmallIntegerToIntegerInReg: startReg.
+ 		self genConvertSmallIntegerToIntegerInReg: repStartReg.
+ 		cogit SubR: startReg R: stopReg.
+ 		cogit AddR: repStartReg R: stopReg.
+ 		"stopReg: stop - start + repStart"
+ 		cogit CmpR: TempReg R: stopReg.
+ 		jumpOutOfBounds4 := cogit JumpGreater: 0.
+ 	
+ 		"Everything in bounds"
+ 		"PossibleRemembered object"
+ 		cogit MoveCw: objectMemory storeCheckBoundary R: TempReg.
+ 		cogit CmpR: TempReg R: arrayReg.
+ 		jmpDestYoung := cogit JumpBelow: 0.
+ 		self checkRememberedInTrampoline ifFalse: 
+ 			[jmpAlreadyRemembered := self genCheckRememberedBitOf: arrayReg scratch: TempReg].
+ 		self callStoreCheckTrampoline.
+ 		jmpDestYoung jmpTarget: cogit Label.
+ 		self checkRememberedInTrampoline ifFalse: 
+ 			[jmpAlreadyRemembered jmpTarget: cogit Label].
+ 	
+ 		"Copy the array"
+ 		cogit genStackArgAt: 2 into: stopReg.
+ 		self genConvertSmallIntegerToIntegerInReg: stopReg.
+ 		"shift by baseHeaderSize and then move from 1 relative to zero relative"
+ 		adjust := (objectMemory baseHeaderSize >> objectMemory shiftForWord) - 1. 
+ 		adjust ~= 0 ifTrue: 
+ 			[ cogit AddCq: adjust R: startReg. 
+ 			  cogit AddCq: adjust R: stopReg. 
+ 			  cogit AddCq: adjust R: repStartReg. ].
+ 	
+ 		instr := cogit CmpR: startReg R: stopReg.
+ 		jumpFinished := cogit JumpBelow: 0.
+ 		cogit MoveXwr: repStartReg R: replReg R: TempReg.
+ 		cogit MoveR: TempReg Xwr: startReg R: arrayReg.
+ 		cogit AddCq: 1 R: startReg.
+ 		cogit AddCq: 1 R: repStartReg.
+ 		cogit Jump: instr.
+ 		jumpFinished jmpTarget: (jumpEmpty jmpTarget: cogit genPrimReturn).
+ 	
+ 		"CANNOT REACH by falling though"
+ 	
+ 		jumpIncorrectFormat1 jmpTarget: (jumpIncorrectFormat2 jmpTarget: cogit Label)].
+ 	
+ 	"--- Byte object version ---"
+ 	(cogit seemsToBeInstantiating: objectMemory firstByteFormat) ifTrue:
+ 		["Are they both byte array format ? CompiledMethod excluded"
+ 		self genGetFormatOf: arrayReg into: TempReg.
+ 		self genGetFormatOf: replReg into: startReg.
+ 		cogit CmpCq: objectMemory firstByteFormat R: startReg.
+ 		jumpIncorrectFormat1 := cogit JumpLess: 0.
+ 		cogit CmpCq: objectMemory firstCompiledMethodFormat R: startReg.
+ 		jumpIncorrectFormat2 := cogit JumpGreaterOrEqual: 0.
+ 		cogit CmpCq: objectMemory firstByteFormat R: TempReg.
+ 		jumpIncorrectFormat3 := cogit JumpLess: 0.
+ 		cogit CmpCq: objectMemory firstCompiledMethodFormat R: TempReg.
+ 		jumpIncorrectFormat4 := cogit JumpGreaterOrEqual: 0.
+ 		
+ 		"Both objects are byte arrays"
+ 		self genGetNumSlotsOf: arrayReg into: startReg.
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: startReg).
+ 		cogit AndCq: objectMemory wordSize - 1 R: TempReg R: TempReg.
+ 		cogit SubR: TempReg R: startReg.
+ 		self genConvertSmallIntegerToIntegerInReg: stopReg.
+ 	
+ 		"arr size < stop"
+ 		cogit CmpR: startReg R: stopReg.
+ 		jumpOutOfBounds3 := cogit JumpGreater: 0.
+ 	
+ 		"rep size < repStart - start + stop"
+ 		cogit MoveR: startReg R: TempReg. "TempReg holds repl format"
+ 		cogit genStackArgAt: 3 into: startReg.
+ 		self genConvertSmallIntegerToIntegerInReg: startReg.
+ 		self genConvertSmallIntegerToIntegerInReg: repStartReg.
+ 		cogit SubR: startReg R: stopReg.
+ 		cogit AddR: repStartReg R: stopReg.
+ 		
+ 		self genGetNumSlotsOf: replReg into: startReg.
+ 		(cogit LogicalShiftLeftCq: objectMemory shiftForWord R: startReg).
+ 		cogit AndCq: objectMemory wordSize - 1 R: TempReg R: TempReg.
+ 		cogit SubR: TempReg R: startReg.
+ 		
+ 		"stopReg: stop - start + repStart"
+ 		cogit CmpR: startReg R: stopReg.
+ 		jumpOutOfBounds4 := cogit JumpGreater: 0.
+ 	
+ 		"Everything in bounds"
+ 		"Copy the bytes"
+ 		cogit genStackArgAt: 3 into: startReg.
+ 		self genConvertSmallIntegerToIntegerInReg: startReg.
+ 		cogit genStackArgAt: 2 into: stopReg.
+ 		self genConvertSmallIntegerToIntegerInReg: stopReg.
+ 		"shift by baseHeaderSize and then move from 1 relative to zero relative"
+ 		adjust := objectMemory baseHeaderSize - 1.
+ 		adjust ~= 0 ifTrue: 
+ 			[ cogit AddCq: adjust R: startReg. 
+ 			  cogit AddCq: adjust R: stopReg. 
+ 			  cogit AddCq: adjust R: repStartReg. ].
+ 	
+ 		instr := cogit CmpR: startReg R: stopReg.
+ 		jumpFinished := cogit JumpBelow: 0.
+ 		cogit MoveXbr: repStartReg R: replReg R: TempReg.
+ 		cogit MoveR: TempReg Xbr: startReg R: arrayReg.
+ 		cogit AddCq: 1 R: startReg.
+ 		cogit AddCq: 1 R: repStartReg.
+ 		cogit Jump: instr.
+ 		jumpFinished jmpTarget: (jumpEmpty jmpTarget: cogit genPrimReturn).
+ 	
+ 		"CANNOT REACH by falling though"
+ 	
+ 		jumpIncorrectFormat4 
+ 			jmpTarget: (jumpIncorrectFormat3 
+ 				jmpTarget: (jumpIncorrectFormat2 
+ 					jmpTarget: (jumpIncorrectFormat1 jmpTarget: cogit Label)))].
+ 
+ 	(result := cogit compileInterpreterPrimitive) < 0 ifTrue: [^result].
+ 	
+ 	jumpImm 
+ 		jmpTarget: (jumpNotSmi1
+ 				jmpTarget: (jumpNotSmi2
+ 						jmpTarget: (jumpNotSmi3 jmpTarget: cogit Label))).
+ 	jumpOutOfBounds1 
+ 		jmpTarget: (jumpOutOfBounds2 
+ 			jmpTarget: (jumpOutOfBounds3 
+ 				jmpTarget: (jumpOutOfBounds4 
+ 					jmpTarget: jumpImm getJmpTarget))).
+ 	self
+ 		cppIf: IMMUTABILITY
+ 		ifTrue: [jumpImmutable jmpTarget: jumpImm getJmpTarget].
+ 
+ 	^ CompletePrimitive!

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 := self objectRepresentationClass wordSize = 8
  										ifTrue: [555]
  										ifFalse: [222].
  	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			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 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"
  
  		(159 genPrimitiveHashMultiply 0)
  
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)				"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveImmediateAsInteger 0)	"Character>>value SmallFloat64>>asInteger"
  			
  		"(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:"
  
  		(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)"
  	)!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive (in category 'primitive generators') -----
+ compileInterpreterPrimitive
+ 	<inline: true>
+ 	| primitiveRoutine |
+ 	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)()'>
+ 	primitiveRoutine := coInterpreter
+ 							functionPointerForCompiledMethod: methodObj
+ 							primitiveIndex: primitiveIndex.
+ 	^ self
+ 		compileInterpreterPrimitive: primitiveRoutine
+ 		flags: (coInterpreter primitivePropertyFlags: primitiveIndex)!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genStackArgAt:into: (in category 'simulation stack') -----
+ genStackArgAt: n into: reg 
+ 	<inline: true>
+ 	self
+ 		MoveMw: (self backEnd hasLinkRegister
+ 				ifTrue: [n]
+ 				ifFalse: [n + 1])
+ 				* objectMemory wordSize
+ 		r: SPReg
+ 		R: reg.
+ 	^ 0
+ !

Item was added:
+ ----- Method: SimpleStackBasedCogit>>seemsToBeInstantiating: (in category 'testing') -----
+ seemsToBeInstantiating: format
+ 	"Answers if the code is installed in a class instantiating objects with the format. Used in primitive 
+ 	 generation to make a quick path based on where the method is installed. This method cannot
+ 	 be used as a guarantee as there can be false positive, it's just a heuristic.
+ 	 Tries to interpret the last literal of the method as a behavior (more than 3 fields, 3rd field a Smi).
+ 	 If it can be interpreted as a behavior, answers if instSpec matches the format, else answers false."
+ 	<inline: true>
+ 	^ objectMemory maybeMethodClassOf: methodObj seemsToBeInstantiating: format!

Item was added:
+ ----- Method: SpurMemoryManager>>maybeMethodClassOf:seemsToBeInstantiating: (in category 'object testing') -----
+ maybeMethodClassOf: methodObj seemsToBeInstantiating: format
+ 	"Answers if the code is installed in a class instantiating objects with the format. Used in primitive 
+ 	 generation to make a quick path based on where the method is installed. This method cannot
+ 	 be used as a guarantee as there can be false positive, it's just a heuristic.
+ 	 Tries to interpret the last literal of the method as a behavior (more than 3 fields, 3rd field a Smi).
+ 	 If it can be interpreted as a behavior, answers if instSpec matches the format, else answers false."
+ 	<api>
+ 	| maybeClassObj maybeFormat instSpec|
+ 	maybeClassObj := coInterpreter methodClassOf: methodObj.
+ 	(self isPointersNonImm: maybeClassObj) ifFalse: [^false].
+ 	(self numSlotsOfAny: maybeClassObj) > InstanceSpecificationIndex ifFalse: [^false].
+ 	maybeFormat := self fetchPointer: InstanceSpecificationIndex ofObject: maybeClassObj.
+ 	(self isIntegerObject: maybeFormat) ifFalse: [^false].
+ 	instSpec := self instSpecOfClassFormat: (self integerValueOf: maybeFormat).
+ 	^ instSpec = format!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimReturn (in category 'primitive generators') -----
  genPrimReturn
  	"Generate a return that cuts back the stack to remove the receiver
  	 and arguments after an invocation of a primitive with nargs arguments.
  	 Since all primitives that succeed in the normal way (i.e. don't execute a
  	 method as do genPrimitiveClosureValue and genPrimitivePerform) take only
  	 register arguments, there is nothing to do."
  	<inline: true>
+ 	^methodOrBlockNumArgs <= self numRegArgs
+ 		ifTrue: [self RetN: 0]
+ 		ifFalse: [super genPrimReturn]!
- 	self assert: methodOrBlockNumArgs <= self numRegArgs.
- 	^self RetN: 0!



More information about the Vm-dev mailing list