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

commits at source.squeak.org commits at source.squeak.org
Mon Nov 7 18:22:45 UTC 2011


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

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

Name: VMMaker.oscog-eem.136
Author: eem
Time: 7 November 2011, 11:20:47.175 am
UUID: c62e0f35-616c-4547-b4e7-46765111b6a9
Ancestors: VMMaker.oscog-eem.135

Fix error codes for at: and at:put: primitive so that for non-indexable
objects they fail with #'bad receiver', not #'bad index'.

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

Item was changed:
  ----- Method: NewspeakInterpreter>>commonVariable:at:cacheIndex: (in category 'indexing primitive support') -----
  commonVariable: rcvr at: index cacheIndex: atIx 
  	"This code assumes the receiver has been identified at location atIx in the atCache."
  	| stSize fmt fixedFields result |
  
  	stSize := atCache at: atIx+AtCacheSize.
  	((self cCoerce: index to: 'usqInt ') >= 1
  		and: [(self cCoerce: index to: 'usqInt ') <= (self cCoerce: stSize to: 'usqInt ')])
  	ifTrue:
  		[fmt := atCache at: atIx+AtCacheFmt.
  		fmt <= 4 ifTrue:
  			[fixedFields := atCache at: atIx+AtCacheFixedFields.
  			^ self fetchPointer: index + fixedFields - 1 ofObject: rcvr].
  		fmt < 8 ifTrue:  "Bitmap"
  			[result := self fetchLong32: index - 1 ofObject: rcvr.
  			result := self positive32BitIntegerFor: result.
  			^ result].
  		fmt >= 16  "Note fmt >= 16 is an artificial flag for strings"
  			ifTrue: "String"
  				[^ self characterForAscii: (self fetchByte: index - 1 ofObject: rcvr)]
  			ifFalse: "ByteArray"
  				[^ self integerObjectOf: (self fetchByte: index - 1 ofObject: rcvr)]].
  
+ 	self primitiveFailFor: ((self formatOf: rcvr) <= 1
+ 								ifTrue: [PrimErrBadReceiver]
+ 								ifFalse: [PrimErrBadIndex])!
- 	self primitiveFailFor: PrimErrBadIndex!

Item was changed:
  ----- Method: NewspeakInterpreter>>commonVariable:at:put:cacheIndex: (in category 'indexing primitive support') -----
  commonVariable: rcvr at: index put: value cacheIndex: atIx
  	"This code assumes the receiver has been identified at location atIx in the atCache."
  	"It also assumes that all immutability checking has been done by the caller."
  	| stSize fmt fixedFields valToPut |
  	<inline: true>
  
  	stSize := atCache at: atIx+AtCacheSize.
  	((self cCoerce: index to: 'usqInt ') >= 1
  		and: [(self cCoerce: index to: 'usqInt ') <= (self cCoerce: stSize to: 'usqInt ')])
  	ifTrue:
  		[fmt := atCache at: atIx+AtCacheFmt.
  		fmt <= 4 ifTrue:
  			[fixedFields := atCache at: atIx+AtCacheFixedFields.
  			^ self storePointer: index + fixedFields - 1 ofObject: rcvr withValue: value].
  		fmt < 8 ifTrue:  "Bitmap"
  			[valToPut := self positive32BitValueOf: value.
  			self successful ifTrue:
  				[^self storeLong32: index - 1 ofObject: rcvr withValue: valToPut].
  			^ self primitiveFailFor: PrimErrBadArgument].
  		fmt >= 16  "Note fmt >= 16 is an artificial flag for strings"
  			ifTrue: [valToPut := self asciiOfCharacter: value.
  					self successful ifFalse: [^ self primitiveFailFor: PrimErrBadArgument]]
  			ifFalse: [valToPut := value].
  		(self isIntegerObject: valToPut) ifTrue:
  			[valToPut := self integerValueOf: valToPut.
  			((valToPut >= 0) and: [valToPut <= 255]) ifFalse:
  				[^ self primitiveFailFor: PrimErrBadArgument].
  			^ self storeByte: index - 1 ofObject: rcvr withValue: valToPut].
  		^self primitiveFailFor: PrimErrInappropriate].
  
+ 	^self primitiveFailFor: ((self formatOf: rcvr) <= 1
+ 								ifTrue: [PrimErrBadReceiver]
+ 								ifFalse: [PrimErrBadIndex])!
- 	self primitiveFailFor: PrimErrBadIndex!

Item was changed:
  ----- Method: NewspeakInterpreter>>stObject:at: (in category 'indexing primitive support') -----
  stObject: array at: index
  	"Return what ST would return for <obj> at: index."
  
  	| hdr fmt totalLength fixedFields stSize |
  	<inline: false>
  	hdr := self baseHeader: array.
+ 	fmt := self formatOfHeader: hdr.
- 	fmt := (hdr >> 8) bitAnd: 16rF.
  	totalLength := self lengthOf: array baseHeader: hdr format: fmt.
  	fixedFields := self fixedFieldsOf: array format: fmt length: totalLength.
  	(fmt = 3 and: [self isContextHeader: hdr])
  		ifTrue: [stSize := self fetchStackPointerOf: array]
  		ifFalse: [stSize := totalLength - fixedFields].
+ 	((self oop: index isGreaterThanOrEqualTo: 1)
+ 	 and: [self oop: index isLessThanOrEqualTo: stSize]) ifTrue:
+ 		[^self subscript: array with: (index + fixedFields) format: fmt].
+ 	self primitiveFailFor: (fmt <= 1 ifTrue: [PrimErrBadReceiver] ifFalse: [PrimErrBadIndex]).
+ 	^0!
- 	((self cCoerce: index to: 'usqInt ') >= 1
- 		and: [(self cCoerce: index to: 'usqInt ') <= (self cCoerce: stSize to: 'usqInt ')])
- 		ifTrue: [^ self subscript: array with: (index + fixedFields) format: fmt]
- 		ifFalse: [self primitiveFailFor: PrimErrBadIndex.  ^ 0].!

Item was changed:
  ----- Method: NewspeakInterpreter>>stObject:at:put: (in category 'indexing primitive support') -----
  stObject: array at: index put: value
  	"Do what ST would return for <obj> at: index put: value."
  	| hdr fmt totalLength fixedFields stSize |
  	<inline: false>
  	hdr := self baseHeader: array.
+ 	fmt := self formatOfHeader: hdr.
- 	fmt := (hdr >> 8) bitAnd: 16rF.
  	totalLength := self lengthOf: array baseHeader: hdr format: fmt.
  	fixedFields := self fixedFieldsOf: array format: fmt length: totalLength.
  	(fmt = 3 and: [self isContextHeader: hdr])
  		ifTrue: [stSize := self fetchStackPointerOf: array]
  		ifFalse: [stSize := totalLength - fixedFields].
+ 	((self oop: index isGreaterThanOrEqualTo: 1)
+ 	 and: [self oop: index isLessThanOrEqualTo: stSize])
- 	((self cCoerce: index to: 'usqInt ') >= 1
- 		and: [(self cCoerce: index to: 'usqInt ') <= (self cCoerce: stSize to: 'usqInt ')])
  		ifTrue: [self subscript: array with: (index + fixedFields) storing: value format: fmt]
+ 		ifFalse: [self primitiveFailFor: (fmt <= 1 ifTrue: [PrimErrBadReceiver] ifFalse: [PrimErrBadIndex])]!
- 		ifFalse: [self primitiveFailFor: PrimErrBadIndex]!

Item was changed:
  ----- Method: StackInterpreter>>commonVariable:at:cacheIndex: (in category 'indexing primitive support') -----
  commonVariable: rcvr at: index cacheIndex: atIx 
  	"This code assumes the receiver has been identified at location atIx in the atCache."
  	| stSize fmt fixedFields result |
  	<inline: true>
  	stSize := atCache at: atIx+AtCacheSize.
  	((self oop: index isGreaterThanOrEqualTo: 1)
  		and: [self oop: index isLessThanOrEqualTo: stSize])
  	ifTrue:
  		[fmt := atCache at: atIx+AtCacheFmt.
  		fmt <= 4 ifTrue:
  			[self assert: (objectMemory isContextNonInt: rcvr) not.
  			 fixedFields := atCache at: atIx+AtCacheFixedFields.
  			^ objectMemory fetchPointer: index + fixedFields - 1 ofObject: rcvr].
  		fmt < 8 ifTrue:  "Bitmap"
  			[result := objectMemory fetchLong32: index - 1 ofObject: rcvr.
  			 ^self positive32BitIntegerFor: result].
  		fmt >= 16  "Note fmt >= 16 is an artificial flag for strings"
  			ifTrue: "String"
  			[^ self characterForAscii: (objectMemory fetchByte: index - 1 ofObject: rcvr)]
  			ifFalse: "ByteArray"
  			[^ objectMemory integerObjectOf: (objectMemory fetchByte: index - 1 ofObject: rcvr)]].
  
+ 	^self primitiveFailFor: ((objectMemory formatOf: rcvr) <= 1
+ 								ifTrue: [PrimErrBadReceiver]
+ 								ifFalse: [PrimErrBadIndex])!
- 	^self primitiveFailFor: PrimErrBadIndex!

Item was changed:
  ----- Method: StackInterpreter>>commonVariable:at:put:cacheIndex: (in category 'indexing primitive support') -----
  commonVariable: rcvr at: index put: value cacheIndex: atIx
  	"This code assumes the receiver has been identified at location atIx in the atCache."
  	| stSize fmt fixedFields valToPut |
  	<inline: true>
  
  	stSize := atCache at: atIx+AtCacheSize.
  	((self oop: index isGreaterThanOrEqualTo: 1)
  		and: [self oop: index isLessThanOrEqualTo: stSize])
  	ifTrue:
  		[fmt := atCache at: atIx+AtCacheFmt.
  		fmt <= 4 ifTrue:
  			[self assert: (objectMemory isContextNonInt: rcvr) not.
  			 fixedFields := atCache at: atIx+AtCacheFixedFields.
  			^ objectMemory storePointer: index + fixedFields - 1 ofObject: rcvr withValue: value].
  		fmt < 8 ifTrue:  "Bitmap"
  			[valToPut := self positive32BitValueOf: value.
  			self successful ifTrue: [objectMemory storeLong32: index - 1 ofObject: rcvr withValue: valToPut].
  			^ nil].
  		fmt >= 16  "Note fmt >= 16 is an artificial flag for strings"
  			ifTrue: [valToPut := self asciiOfCharacter: value.
  					self successful ifFalse: [^ nil]]
  			ifFalse: [valToPut := value].
  		(objectMemory isIntegerObject: valToPut) ifTrue:
  			[valToPut := objectMemory integerValueOf: valToPut.
  			((valToPut >= 0) and: [valToPut <= 255]) ifFalse: [^ self primitiveFail].
  			^ objectMemory storeByte: index - 1 ofObject: rcvr withValue: valToPut]].
  
+ 	^self primitiveFailFor: ((objectMemory formatOf: rcvr) <= 1
+ 								ifTrue: [PrimErrBadReceiver]
+ 								ifFalse: [PrimErrBadIndex])!
- 	^self primitiveFailFor: PrimErrBadIndex!

Item was changed:
  ----- Method: StackInterpreter>>stObject:at: (in category 'indexing primitive support') -----
  stObject: array at: index
  	"Return what ST would return for <obj> at: index."
  
  	| hdr fmt totalLength fixedFields stSize |
  	<inline: false>
  	hdr := objectMemory baseHeader: array.
  	fmt := objectMemory formatOfHeader: hdr.
  	totalLength := objectMemory lengthOf: array baseHeader: hdr format: fmt.
  	fixedFields := objectMemory fixedFieldsOf: array format: fmt length: totalLength.
  	(fmt = 3 and: [objectMemory isContextHeader: hdr])
  		ifTrue:
  			[stSize := self stackPointerForMaybeMarriedContext: array.
  			((self oop: index isGreaterThanOrEqualTo: 1)
  			 and: [(self oop: index isLessThanOrEqualTo: stSize)
  			 and: [self isStillMarriedContext: array]]) ifTrue:
  				[^self noInlineTemporary: index - 1 in: (self frameOfMarriedContext: array)]]
  		ifFalse: [stSize := totalLength - fixedFields].
  	((self oop: index isGreaterThanOrEqualTo: 1)
+ 	 and: [self oop: index isLessThanOrEqualTo: stSize]) ifTrue:
+ 		[^self subscript: array with: (index + fixedFields) format: fmt].
+ 	self primitiveFailFor: (fmt <= 1 ifTrue: [PrimErrBadReceiver] ifFalse: [PrimErrBadIndex]).
+ 	^0!
- 	 and: [self oop: index isLessThanOrEqualTo: stSize])
- 		ifTrue: [^self subscript: array with: (index + fixedFields) format: fmt]
- 		ifFalse: [self primitiveFailFor: PrimErrBadIndex.  ^ 0]!

Item was changed:
  ----- Method: StackInterpreter>>stObject:at:put: (in category 'indexing primitive support') -----
  stObject: array at: index put: value
  	"Do what ST would return for <obj> at: index put: value."
  	| hdr fmt totalLength fixedFields stSize |
  	<inline: false>
  	hdr := objectMemory baseHeader: array.
  	fmt := objectMemory formatOfHeader: hdr.
  	totalLength := objectMemory lengthOf: array baseHeader: hdr format: fmt.
  	fixedFields := objectMemory fixedFieldsOf: array format: fmt length: totalLength.
  	(fmt = 3
  	 and: [objectMemory isContextHeader: hdr])
  		ifTrue:
  			[stSize := self stackPointerForMaybeMarriedContext: array.
  			((self oop: index isGreaterThanOrEqualTo: 1)
  			 and: [(self oop: index isLessThanOrEqualTo: stSize)
  			 and: [self isStillMarriedContext: array]]) ifTrue:
  				[self noInlineTemporary: index - 1 in: (self frameOfMarriedContext: array) put: value.
  				 ^self]]
  		ifFalse: [stSize := totalLength - fixedFields].
  	((self oop: index isGreaterThanOrEqualTo: 1)
  	 and: [self oop: index isLessThanOrEqualTo: stSize])
  		ifTrue: [self subscript: array with: (index + fixedFields) storing: value format: fmt]
+ 		ifFalse: [self primitiveFailFor: (fmt <= 1 ifTrue: [PrimErrBadReceiver] ifFalse: [PrimErrBadIndex])]!
- 		ifFalse: [self primitiveFailFor: PrimErrBadIndex]!



More information about the Vm-dev mailing list