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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 27 01:13:55 UTC 2014


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

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

Name: VMMaker.oscog-eem.1001
Author: eem
Time: 26 December 2014, 5:11:22.933 pm
UUID: fef56678-07b1-4fca-8300-17d6afc0c6e4
Ancestors: VMMaker.oscog-eem.1000

Mark externalInstVar:ofContext: as not to be inlined
(otherwise it is inined into 64-bit primitiveSlotAtPut !!).

Remove useless initPrimCalls from primitiveFloatAt[Put]
and fix latter for potentially immediate receivers.

Fix off-by-one slips in primitiveSlotAt[Put] and copy new
code down into StackInterpreter, with appropriate
handling of context receivers.


typos

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

Item was changed:
  ----- Method: CoInterpreter>>externalInstVar:ofContext: (in category 'frame access') -----
  externalInstVar: offset ofContext: aContext
  	"Fetch an instance variable from a maybe married context.
  	 If the context is still married compute the value of the
  	 relevant inst var from the spouse frame's state.
  
  	 If the context is single but has a negative instruction pointer
  	 recognise that the instruction pointer is actually into machine
  	 code and convert it to the corresponding bytecode pc."
+ 	<inline: false>
  	| value |
  
  	self assert: (objectMemory isContext: aContext).
  	"method, closureOrNil & receiver need no special handling; only
  	 sender, pc & stackp have to be computed for married contexts."
  	((self isReadMediatedContextInstVarIndex: offset)
  	 and: [self isMarriedOrWidowedContext: aContext]) ifFalse:
  		[value := objectMemory fetchPointer: offset ofObject: aContext.
  		 ^(offset = InstructionPointerIndex
  		    and: [(objectMemory isIntegerObject: value)
  		    and: [value signedIntFromLong < 0]])
  			ifTrue: [self mustMapMachineCodePC: (objectMemory integerValueOf: value)
  						context: aContext]
  			ifFalse: [value]].
  
  	self externalWriteBackHeadFramePointers.
  	^(self isStillMarriedContext: aContext)
  		ifTrue: [self fetchPointer: offset ofMarriedContext: aContext]
  		ifFalse: [objectMemory fetchPointer: offset ofObject: aContext]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFloatAt (in category 'indexing primitives') -----
  primitiveFloatAt
  	"Provide platform-independent access to 32-bit words comprising
  	 a Float.  Map index 1 onto the most significant word and index 2
  	 onto the least significant word."
  	| rcvr index result |
  	<var: #result type: #usqInt>
- 	self initPrimCall.
  	rcvr := self stackValue: 1.
  	index := self stackTop.
  	index = ConstOne ifTrue:
  		[result := self positive32BitIntegerFor:
  					(objectMemory
  						fetchLong32: (VMBIGENDIAN ifTrue: [0] ifFalse: [1])
  						ofFloatObject: rcvr).
  		^self pop: 2 thenPush: result].
  	index = ConstTwo ifTrue:
  		[result := self positive32BitIntegerFor:
  					(objectMemory
  						fetchLong32: (VMBIGENDIAN ifTrue: [1] ifFalse: [0])
  						ofFloatObject: rcvr).
  		^self pop: 2 thenPush: result].
  	self primitiveFailFor: ((objectMemory isIntegerObject: index)
  							ifTrue: [PrimErrBadIndex]
  							ifFalse: [PrimErrBadArgument])!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFloatAtPut (in category 'indexing primitives') -----
  primitiveFloatAtPut
  	"Provide platform-independent access to 32-bit words comprising
  	 a Float.  Map index 1 onto the most significant word and index 2
  	 onto the least significant word."
  	| rcvr index oopToStore valueToStore |
  	<var: #valueToStore type: #usqInt>
- 	self initPrimCall.
  	oopToStore := self stackTop.
  	valueToStore := self positive32BitValueOf: oopToStore.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	rcvr := self stackValue: 2.
  	index := self stackValue: 1.
+ 	(objectMemory isImmediateFloat: rcvr) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadReceiver].
  	index = ConstOne ifTrue:
  		[objectMemory storeLong32: (VMBIGENDIAN ifTrue: [0] ifFalse: [1])
  			ofObject: rcvr
  			withValue: valueToStore.
  		^self pop: 3 thenPush: oopToStore].
  	index = ConstTwo ifTrue:
  		[objectMemory storeLong32: (VMBIGENDIAN ifTrue: [1] ifFalse: [0])
  			ofObject: rcvr
  			withValue: valueToStore.
  		^self pop: 3 thenPush: oopToStore].
  	self primitiveFailFor: ((objectMemory isIntegerObject: index)
  							ifTrue: [PrimErrBadIndex]
  							ifFalse: [PrimErrBadArgument])!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSlotAt (in category 'object access primitives') -----
  primitiveSlotAt
  	"Answer a slot in an object.  This numbers all slots from 1, ignoring the distinction between
  	 named and indexed inst vars.  In objects with both named and indexed inst vars, the named
  	 inst vars preceed the indexed ones.  In non-object indexed objects (objects that contain
  	 bits, not object references) this primitive answers the raw integral value at each slot. 
  	 e.g. for Strings it answers the character code, not the Character object at each slot."
  	| index rcvr fmt numSlots |
  	index := self stackTop.
  	rcvr := self stackValue: 1.
  	(objectMemory isIntegerObject: index) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	(objectMemory isImmediate: rcvr) ifTrue:
  		[^self primitiveFailFor: PrimErrBadReceiver].
  	fmt := objectMemory formatOf: rcvr.
+ 	index := (objectMemory integerValueOf: index) - 1.
- 	index := objectMemory integerValueOf: index.
  
  	fmt <= objectMemory lastPointerFormat ifTrue:
  		[numSlots := objectMemory numSlotsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[self pop: argumentCount + 1 thenPush: (objectMemory fetchPointer: index ofObject: rcvr).
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	fmt >= objectMemory firstByteFormat ifTrue:
  		[fmt >= objectMemory firstCompiledMethodFormat ifTrue:
  			[^self primitiveFailFor: PrimErrUnsupported].
  		 numSlots := objectMemory numBytesOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[self pop: argumentCount + 1 thenPushInteger: (objectMemory fetchByte: index ofObject: rcvr).
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	(objectMemory hasSpurMemoryManagerAPI
  	 and: [fmt >= objectMemory firstShortFormat]) ifTrue:
  		[numSlots := objectMemory num16BitUnitsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[self pop: argumentCount + 1 thenPushInteger: (objectMemory fetchShort16: index ofObject: rcvr).
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	fmt = objectMemory sixtyFourBitIndexableFormat ifTrue:
  		[numSlots := objectMemory num64BitUnitsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[self pop: argumentCount + 1
  				thenPush: (self positive64BitIntegerFor: (objectMemory fetchLong64: index ofObject: rcvr)).
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	fmt >= objectMemory firstLongFormat ifTrue:
  		[numSlots := objectMemory num32BitUnitsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[self pop: argumentCount + 1
  				thenPush: (objectMemory bytesPerOop = 8
  							ifTrue: [objectMemory integerObjectOf: (objectMemory fetchLong32: index ofObject: rcvr)]
  							ifFalse: [self positive32BitIntegerFor: (objectMemory fetchLong32: index ofObject: rcvr)]).
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	^self primitiveFailFor: PrimErrBadReceiver!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSlotAtPut (in category 'object access primitives') -----
  primitiveSlotAtPut
  	"Assign a slot in an object.  This numbers all slots from 1, ignoring the distinction between
  	 named and indexed inst vars.  In objects with both named and indexed inst vars, the named
  	 inst vars preceed the indexed ones.  In non-object indexed objects (objects that contain
  	 bits, not object references) this primitive assigns a raw integral value at each slot."
  	| newValue index rcvr fmt numSlots value |
  	newValue := self stackTop.
  	index := self stackValue: 1.
  	rcvr := self stackValue: 2.
  	(objectMemory isIntegerObject: index) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	(objectMemory isImmediate: rcvr) ifTrue:
  		[^self primitiveFailFor: PrimErrBadReceiver].
  	fmt := objectMemory formatOf: rcvr.
+ 	index := (objectMemory integerValueOf: index) - 1.
- 	index := objectMemory integerValueOf: index.
  
  	fmt <= objectMemory lastPointerFormat ifTrue:
  		[numSlots := objectMemory numSlotsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[objectMemory storePointer: index ofObject: rcvr withValue: newValue.
  			 self pop: argumentCount + 1 thenPush: newValue.
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	value := self positiveMachineIntegerValueOf: newValue.
  	self failed ifTrue:
  		[primFailCode := PrimErrBadArgument.
  		^0].
  
  	fmt >= objectMemory firstByteFormat ifTrue:
  		[fmt >= objectMemory firstCompiledMethodFormat ifTrue:
  			[^self primitiveFailFor: PrimErrUnsupported].
  		 (self asUnsigned: value) > 16rFF ifTrue:
  			[^self primitiveFailFor: PrimErrBadArgument].
  		 numSlots := objectMemory numBytesOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[objectMemory storeByte: index ofObject: rcvr withValue: value.
  			 self pop: argumentCount + 1 thenPush: newValue.
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	(objectMemory hasSpurMemoryManagerAPI
  	 and: [fmt >= objectMemory firstShortFormat]) ifTrue:
  		[(self asUnsigned: value) > 16rFFFF ifTrue:
  			[^self primitiveFailFor: PrimErrBadArgument].
  		 numSlots := objectMemory num16BitUnitsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[objectMemory storeShort16: index ofObject: rcvr withValue: value.
  			 self pop: argumentCount + 1 thenPush: newValue.
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	(objectMemory bytesPerOop = 8
  	 and: [fmt = objectMemory sixtyFourBitIndexableFormat]) ifTrue:
  		[numSlots := objectMemory num64BitUnitsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[objectMemory storeLong64: index ofObject: rcvr withValue: value.
  			 self pop: argumentCount + 1 thenPush: newValue.
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	fmt >= objectMemory firstLongFormat ifTrue:
  		[(objectMemory wordSize > 4
  		  and: [(self asUnsigned: value) > 16rFFFFFFFF]) ifTrue:
  			[^self primitiveFailFor: PrimErrBadArgument].
  		 numSlots := objectMemory num32BitUnitsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[objectMemory storeLong32: index ofObject: rcvr withValue: value.
  			 self pop: argumentCount + 1 thenPush: newValue.
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
  
  	^self primitiveFailFor: PrimErrBadReceiver!

Item was changed:
  ----- Method: Spur32BitCoMemoryManager>>ifAProxy:updateCopy: (in category 'image segment in/out') -----
  ifAProxy: objOop updateCopy: copy
+ 	"If the object being copied to the segment is weird and has exotic state,
- 	"If the obejct being copied to the segment is weird and has exotic state,
  	 i.e. a married context or a jitted method, update the copy with the vanilla state."
  
  	super ifAProxy: objOop updateCopy: copy.
  	(self isCompiledMethod: objOop) ifTrue:
  		[| methodHeader |
  		 methodHeader := coInterpreter rawHeaderOf: objOop.
  		 (coInterpreter isCogMethodReference: methodHeader) ifTrue:
  			[self storePointerUnchecked: HeaderIndex
  				ofObject: copy
  				withValue: (coInterpreter cCoerceSimple: methodHeader to: #'CogMethod *') methodHeader]]!

Item was changed:
  ----- Method: Spur64BitCoMemoryManager>>ifAProxy:updateCopy: (in category 'image segment in/out') -----
  ifAProxy: objOop updateCopy: copy
+ 	"If the object being copied to the segment is weird and has exotic state,
- 	"If the obejct being copied to the segment is weird and has exotic state,
  	 i.e. a married context or a jitted method, update the copy with the vanilla state."
  
  	super ifAProxy: objOop updateCopy: copy.
  	(self isCompiledMethod: objOop) ifTrue:
  		[| methodHeader |
  		 methodHeader := coInterpreter rawHeaderOf: objOop.
  		 (coInterpreter isCogMethodReference: methodHeader) ifTrue:
  			[self storePointerUnchecked: HeaderIndex
  				ofObject: copy
  				withValue: (coInterpreter cCoerceSimple: methodHeader to: #'CogMethod *') methodHeader]]!

Item was changed:
  ----- Method: SpurMemoryManager>>ifAProxy:updateCopy: (in category 'image segment in/out') -----
  ifAProxy: objOop updateCopy: copy
+ 	"If the object being copied to the segment is weird and has exotic state,
- 	"If the obejct being copied to the segment is weird and has exotic state,
  	 i.e. a married context or a jitted method, update the copy with the vanilla state."
  
  	((self isContext: objOop)
  	 and: [coInterpreter isMarriedOrWidowedContext: objOop]) ifTrue:
  		[| numMediatedSlots |
  		 "Since the context is here via objectsReachableFromRoots: we know it cannot be divorced.
  		  I'd like to assert coInterpreter checkIsStillMarriedContext: objOop currentFP: framePointer,
  		  here but that requires access to framePointer."
  		 numMediatedSlots := coInterpreter numSlotsOfMarriedContext: objOop.
  		 0 to: numMediatedSlots - 1 do:
  			[:i| | oop |
  			 oop := coInterpreter fetchPointer: i ofMarriedContext: objOop.
  			 self storePointerUnchecked: i ofObject: copy withValue: oop].
  		 "And make sure to nil the slots beyond the top of stack..."
  		 numMediatedSlots to: (self numSlotsOf: objOop) - 1 do:
  			[:i|
  			self storePointerUnchecked: i ofObject: copy withValue: nilObj]]!

Item was changed:
  ----- Method: StackInterpreter>>externalInstVar:ofContext: (in category 'frame access') -----
  externalInstVar: offset ofContext: aContext
  	"Fetch an instance variable from a maybe married context.
  	 If the context is still married compute the value of the
  	 relevant inst var from the spouse frame's state."
+ 	<inline: false>
  	self assert: (objectMemory isContext: aContext).
  	"method, closureOrNil & receiver need no special handling; only
  	 sender, pc & stackp have to be computed for married contexts."
  	((self isReadMediatedContextInstVarIndex: offset)
  	 and: [self isMarriedOrWidowedContext: aContext]) ifFalse:
  		[^objectMemory fetchPointer: offset ofObject: aContext].
  
  	self externalWriteBackHeadFramePointers.
  	^(self isStillMarriedContext: aContext)
  		ifTrue: [self fetchPointer: offset ofMarriedContext: aContext]
  		ifFalse: [objectMemory fetchPointer: offset ofObject: aContext]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveSlotAt (in category 'object access primitives') -----
  primitiveSlotAt
+ 	"Answer a slot in an object.  This numbers all slots from 1, ignoring the distinction between
+ 	 named and indexed inst vars.  In objects with both named and indexed inst vars, the named
+ 	 inst vars preceed the indexed ones.  In non-object indexed objects (objects that contain
+ 	 bits, not object references) this primitive answers the raw integral value at each slot. 
+ 	 e.g. for Strings it answers the character code, not the Character object at each slot."
+ 	| index rcvr fmt numSlots |
- 	| index rcvr numSlots value |
  	index := self stackTop.
  	rcvr := self stackValue: 1.
  	(objectMemory isIntegerObject: index) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	(objectMemory isImmediate: rcvr) ifTrue:
  		[^self primitiveFailFor: PrimErrBadReceiver].
+ 	fmt := objectMemory formatOf: rcvr.
+ 	index := (objectMemory integerValueOf: index) - 1.
+ 
+ 	fmt <= objectMemory lastPointerFormat ifTrue:
- 	index := objectMemory integerValueOf: index.
- 	(objectMemory isPointersNonImm: rcvr) ifTrue:
  		[numSlots := objectMemory numSlotsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[| value numLiveSlots |
+ 			 (objectMemory isContextNonImm: rcvr)
+ 				ifTrue:
+ 					[self externalWriteBackHeadFramePointers.
+ 					 numLiveSlots := (self stackPointerForMaybeMarriedContext: rcvr) + CtxtTempFrameStart.
+ 					 value := (self asUnsigned: index) < numLiveSlots
+ 								ifTrue: [self externalInstVar: index ofContext: rcvr]
+ 								ifFalse: [objectMemory nilObject]]
+ 				ifFalse:
+ 					[value := objectMemory fetchPointer: index ofObject: rcvr].
- 			[(objectMemory isContextNonImm: rcvr)
- 							ifTrue: [value := self externalInstVar: index ofContext: rcvr]
- 							ifFalse: [value := objectMemory fetchPointer: index ofObject: rcvr].
  			 self pop: argumentCount + 1 thenPush: value.
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	fmt >= objectMemory firstByteFormat ifTrue:
+ 		[fmt >= objectMemory firstCompiledMethodFormat ifTrue:
+ 			[^self primitiveFailFor: PrimErrUnsupported].
+ 		 numSlots := objectMemory numBytesOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[self pop: argumentCount + 1 thenPushInteger: (objectMemory fetchByte: index ofObject: rcvr).
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	(objectMemory hasSpurMemoryManagerAPI
+ 	 and: [fmt >= objectMemory firstShortFormat]) ifTrue:
+ 		[numSlots := objectMemory num16BitUnitsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[self pop: argumentCount + 1 thenPushInteger: (objectMemory fetchShort16: index ofObject: rcvr).
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	fmt = objectMemory sixtyFourBitIndexableFormat ifTrue:
+ 		[numSlots := objectMemory num64BitUnitsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[self pop: argumentCount + 1
+ 				thenPush: (self positive64BitIntegerFor: (objectMemory fetchLong64: index ofObject: rcvr)).
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	fmt >= objectMemory firstLongFormat ifTrue:
+ 		[numSlots := objectMemory num32BitUnitsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[self pop: argumentCount + 1
+ 				thenPush: (objectMemory bytesPerOop = 8
+ 							ifTrue: [objectMemory integerObjectOf: (objectMemory fetchLong32: index ofObject: rcvr)]
+ 							ifFalse: [self positive32BitIntegerFor: (objectMemory fetchLong32: index ofObject: rcvr)]).
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
- 	"for now just fail for non-pointer objects; the issue here is should
- 	 strings answer characters and if so how do we efficiently identify strings?"
  	^self primitiveFailFor: PrimErrBadReceiver!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveSlotAtPut (in category 'object access primitives') -----
  primitiveSlotAtPut
+ 	"Assign a slot in an object.  This numbers all slots from 1, ignoring the distinction between
+ 	 named and indexed inst vars.  In objects with both named and indexed inst vars, the named
+ 	 inst vars preceed the indexed ones.  In non-object indexed objects (objects that contain
+ 	 bits, not object references) this primitive assigns a raw integral value at each slot."
+ 	| newValue index rcvr fmt numSlots value |
- 	| newValue index rcvr numSlots |
  	newValue := self stackTop.
  	index := self stackValue: 1.
  	rcvr := self stackValue: 2.
  	(objectMemory isIntegerObject: index) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	(objectMemory isImmediate: rcvr) ifTrue:
  		[^self primitiveFailFor: PrimErrBadReceiver].
+ 	fmt := objectMemory formatOf: rcvr.
+ 	index := (objectMemory integerValueOf: index) - 1.
+ 
+ 	fmt <= objectMemory lastPointerFormat ifTrue:
- 	index := objectMemory integerValueOf: index.
- 	(objectMemory isPointersNonImm: rcvr) ifTrue:
  		[numSlots := objectMemory numSlotsOf: rcvr.
  		 (self asUnsigned: index) < numSlots ifTrue:
  			[(objectMemory isContextNonImm: rcvr)
  				ifTrue: [self externalInstVar: index ofContext: rcvr put: newValue]
  				ifFalse: [objectMemory storePointer: index ofObject: rcvr withValue: newValue].
  			 self pop: argumentCount + 1 thenPush: newValue.
  			 ^0].
  		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	value := self positiveMachineIntegerValueOf: newValue.
+ 	self failed ifTrue:
+ 		[primFailCode := PrimErrBadArgument.
+ 		^0].
+ 
+ 	fmt >= objectMemory firstByteFormat ifTrue:
+ 		[fmt >= objectMemory firstCompiledMethodFormat ifTrue:
+ 			[^self primitiveFailFor: PrimErrUnsupported].
+ 		 (self asUnsigned: value) > 16rFF ifTrue:
+ 			[^self primitiveFailFor: PrimErrBadArgument].
+ 		 numSlots := objectMemory numBytesOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[objectMemory storeByte: index ofObject: rcvr withValue: value.
+ 			 self pop: argumentCount + 1 thenPush: newValue.
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	(objectMemory hasSpurMemoryManagerAPI
+ 	 and: [fmt >= objectMemory firstShortFormat]) ifTrue:
+ 		[(self asUnsigned: value) > 16rFFFF ifTrue:
+ 			[^self primitiveFailFor: PrimErrBadArgument].
+ 		 numSlots := objectMemory num16BitUnitsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[objectMemory storeShort16: index ofObject: rcvr withValue: value.
+ 			 self pop: argumentCount + 1 thenPush: newValue.
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	(objectMemory bytesPerOop = 8
+ 	 and: [fmt = objectMemory sixtyFourBitIndexableFormat]) ifTrue:
+ 		[numSlots := objectMemory num64BitUnitsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[objectMemory storeLong64: index ofObject: rcvr withValue: value.
+ 			 self pop: argumentCount + 1 thenPush: newValue.
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
+ 	fmt >= objectMemory firstLongFormat ifTrue:
+ 		[(objectMemory wordSize > 4
+ 		  and: [(self asUnsigned: value) > 16rFFFFFFFF]) ifTrue:
+ 			[^self primitiveFailFor: PrimErrBadArgument].
+ 		 numSlots := objectMemory num32BitUnitsOf: rcvr.
+ 		 (self asUnsigned: index) < numSlots ifTrue:
+ 			[objectMemory storeLong32: index ofObject: rcvr withValue: value.
+ 			 self pop: argumentCount + 1 thenPush: newValue.
+ 			 ^0].
+ 		 ^self primitiveFailFor: PrimErrBadIndex].
+ 
- 	"for now just fail for non-pointer objects; the issue here is should
- 	 strings answer characters and if so how do we efficiently identify strings?"
  	^self primitiveFailFor: PrimErrBadReceiver!



More information about the Vm-dev mailing list