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

commits at source.squeak.org commits at source.squeak.org
Tue Jun 21 20:08:07 UTC 2022


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

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

Name: VMMaker.oscog-eem.3197
Author: eem
Time: 21 June 2022, 1:07:53.905438 pm
UUID: c5f845c2-b1f7-41fc-acd1-9d3054673e01
Ancestors: VMMaker.oscog-eem.3196

Reassign primitive numbers for the new instantiation primitives:

580: pinned new
581: pinned new with arg (I'll implement this now)
582: uninitialized new with arg
(583 reserved for pinned uninitialized new with arg)

Add the 32-bit implementation for primitivePinnedNewWithArg.

Use consistent naming [Pinned|Uninitialized]New[WithArg]. (InOldSpace is redendant so drop it)

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

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveNewPinnedInOldSpace (in category 'object access primitives') -----
- primitiveNewPinnedInOldSpace
- 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
- 		[(argumentCount < 1
- 		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
- 			[^self primitiveFailFor: PrimErrBadArgument]].
- 	objectMemory hasSpurMemoryManagerAPI
- 		ifTrue:
- 			["Allocate a new fixed-size instance.  Fail if the allocation would leave
- 			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
- 			(objectMemory instantiateClass: self stackTop)
- 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
- 				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
- 											ifTrue: [PrimErrNoMemory]
- 											ifFalse: [PrimErrBadReceiver])]]
- 		ifFalse:
- 			["Allocate a new fixed-size instance. Fail if the allocation would leave
- 			  less than lowSpaceThreshold bytes free. May cause a GC."
- 			| spaceOkay |
- 			"The following may cause GC!! Use var for result to permit inlining."
- 			spaceOkay := objectMemory
- 								sufficientSpaceToInstantiate: self stackTop
- 								indexableSize: 0.
- 			spaceOkay
- 				ifTrue:
- 					[self
- 						pop: argumentCount + 1
- 						thenPush: (objectMemory
- 									instantiateClass: self stackTop
- 									indexableSize: 0)]
- 				ifFalse: [self primitiveFailFor: PrimErrNoMemory]]!

Item was removed:
- ----- Method: InterpreterPrimitives>>primitiveNewWithArgUninitialized (in category 'object access primitives') -----
- primitiveNewWithArgUninitialized
- 	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
- 	| size spaceOkay instSpec |
- 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
- 		[(argumentCount < 2
- 		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
- 			[^self primitiveFailFor: PrimErrBadArgument]].
- 	size := self positiveMachineIntegerValueOf: self stackTop.
- 	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
- 		[^self primitiveFailFor: PrimErrBadArgument].
- 	objectMemory hasSpurMemoryManagerAPI
- 		ifTrue:
- 			[(objectMemory instantiateUninitializedClass: (self stackValue: 1) indexableSize: size)
- 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
- 				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
- 					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
- 											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
- 												ifTrue: [PrimErrNoMemory]
- 												ifFalse: [PrimErrBadReceiver])]]
- 		ifFalse:
- 			[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
- 			 spaceOkay
- 				ifTrue:
- 					[self
- 						pop: argumentCount + 1
- 						thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
- 				ifFalse:
- 					[self primitiveFailFor: PrimErrNoMemory]]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitivePinnedNew (in category 'object access primitives') -----
+ primitivePinnedNew
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 1
+ 		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			["Allocate a new fixed-size instance.  Fail if the allocation would leave
+ 			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
+ 			(objectMemory inOldSpaceInstantiatePinnedClass: self stackTop)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
+ 											ifTrue: [PrimErrNoMemory]
+ 											ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			[self primitiveFailFor: PrimErrUnsupported]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitivePinnedNewWithArg (in category 'object access primitives') -----
+ primitivePinnedNewWithArg
+ 	"Allocate a new pinned indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free."
+ 	| size instSpec |
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 2
+ 		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
+ 	size := self positiveMachineIntegerValueOf: self stackTop.
+ 	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[(objectMemory inOldSpaceInstantiatePinnedClass: (self stackValue: 1) indexableSize: size)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
+ 					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
+ 											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
+ 												ifTrue: [PrimErrNoMemory]
+ 												ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			[self primitiveFailFor: PrimErrUnsupported]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveUninitializedNewWithArg (in category 'object access primitives') -----
+ primitiveUninitializedNewWithArg
+ 	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
+ 	| size instSpec |
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 2
+ 		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
+ 	size := self positiveMachineIntegerValueOf: self stackTop.
+ 	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[(objectMemory instantiateUninitializedClass: (self stackValue: 1) indexableSize: size)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
+ 					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
+ 											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
+ 												ifTrue: [PrimErrNoMemory]
+ 												ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			[self primitiveFailFor: PrimErrUnsupported]!

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.
- 	MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8
- 										ifTrue: [580]
- 										ifFalse: [580].
  	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 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)"
- 		(575 genPrimitiveHighBit			0)
- 		(580 genPrimitiveUninitializedNewWithArg             1)
  	)!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>inOldSpaceInstantiatePinnedClass:indexableSize: (in category 'instantiation') -----
+ inOldSpaceInstantiatePinnedClass: classObj indexableSize: nElements
+ 	<api>
+ 	<var: #nElements type: #usqInt>
+ 	"Allocate an instance of a variable class, excepting CompiledMethod."
+ 	| instSpec classFormat numSlots classIndex newObj fillValue |
+ 	classFormat := self formatOfClass: classObj.
+ 	instSpec := self instSpecOfClassFormat: classFormat.
+ 	classIndex := self rawHashBitsOf: classObj.
+ 	fillValue := 0.
+ 	instSpec caseOf: {
+ 		[self arrayFormat]	->
+ 			[numSlots := nElements.
+ 			 fillValue := nilObj].
+ 		[self indexablePointersFormat]	->
+ 			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
+ 			 fillValue := nilObj].
+ 		[self weakArrayFormat]	->
+ 			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
+ 			 fillValue := nilObj].
+ 		[self sixtyFourBitIndexableFormat]	->
+ 			[nElements > (self maxSlotsForAlloc / 2) ifTrue:
+ 				[coInterpreter primitiveFailFor: PrimErrUnsupported.
+ 				 ^nil].
+ 			 numSlots := nElements * 2].
+ 		[self firstLongFormat]	->
+ 			[(classIndex = ClassFloatCompactIndex and: [nElements ~= 2]) ifTrue:
+ 				[coInterpreter primitiveFailFor: PrimErrBadReceiver.
+ 				 ^nil].
+ 			 numSlots := nElements].
+ 		[self firstShortFormat]	->
+ 			[numSlots := nElements + 1 // 2.
+ 			 instSpec := instSpec + (nElements bitAnd: 1)].
+ 		[self firstByteFormat]	->
+ 			[numSlots := nElements + 3 // 4.
+ 			 instSpec := instSpec + (4 - nElements bitAnd: 3)] }
+ 		otherwise: "non-indexable"
+ 			["Some Squeak images include funky fixed subclasses of abstract variable
+ 			  superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
+ 			  The (Threaded)FFIPlugin expects to be able to instantiate ExternalData via
+ 			  this method.
+ 			  Hence allow fixed classes to be instantiated here iff nElements = 0."
+ 			 (nElements ~= 0 or: [instSpec > self lastPointerFormat]) ifTrue:
+ 				[^nil].
+ 			 numSlots := self fixedFieldsOfClassFormat: classFormat.
+ 			 fillValue := nilObj].
+ 	classIndex = 0 ifTrue:
+ 		[classIndex := self ensureBehaviorHash: classObj.
+ 		 classIndex < 0 ifTrue:
+ 			[coInterpreter primitiveFailFor: classIndex negated.
+ 			 ^nil]].
+ 	numSlots > self maxSlotsForAlloc ifTrue:
+ 		[coInterpreter primitiveFailFor: PrimErrUnsupported.
+ 		 ^nil].
+ 	newObj := self 
+ 					allocateSlotsForPinningInOldSpace: numSlots 
+ 					bytes: (self objectBytesForSlots: numSlots) 
+ 					format: instSpec 
+ 					classIndex: classIndex.
+ 	newObj ifNotNil:
+ 		[self fillObj: newObj numSlots: numSlots with: fillValue].
+ 	^newObj!

Item was changed:
  ----- Method: SpurMemoryManager>>maxSlotsForNewSpaceAlloc (in category 'instantiation') -----
  maxSlotsForNewSpaceAlloc
  	"Almost entirely arbitrary, but we dont want 1Mb bitmaps allocated in eden.
  	 But this choice means no check for numSlots > maxSlotsForNewSpaceAlloc
  	 for non-variable allocations."
+ 	<api>
  	^self fixedFieldsOfClassFormatMask!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)



More information about the Vm-dev mailing list