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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 18 06:13:09 UTC 2012


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

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

Name: VMMaker.oscog-eem.157
Author: eem
Time: 17 April 2012, 11:08:52.202 pm
UUID: 9a11acbe-4a62-43ce-81de-934f351598cc
Ancestors: VMMaker.oscog-eem.156

Stack/CoInterpreter/Cogit:
Implement proper bounds checking for byte access to compiled
methods.  Raise errors for accesses outside initialPC to size.

Simulator:
Nuke an old breakpojnt method in the simulator.

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

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genInnerPrimitiveAt: (in category 'primitive generators') -----
  genInnerPrimitiveAt: retNoffset
+ 	| jumpSI jumpNotSI jumpNotIndexable jumpIsContext jumpBounds jumpFmtGt4 jumpFmtEq2 jumpFmtLt8 jumpFmtGt11 jumpLarge |
- 	| jumpSI jumpNotSI jumpNotIndexable jumpIsContext jumpBounds jumpFmtGt4 jumpFmtEq2 jumpFmtLt8 jumpLarge |
  	"c.f. StackInterpreter>>stSizeOf: lengthOf:baseHeader:format: fixedFieldsOf:format:length:"
  	<var: #jumpSI type: #'AbstractInstruction *'>
  	<var: #jumpNotSI type: #'AbstractInstruction *'>
  	<var: #jumpNotIndexable type: #'AbstractInstruction *'>
  	<var: #jumpIsContext type: #'AbstractInstruction *'>
  	<var: #jumpBounds type: #'AbstractInstruction *'>
  	<var: #jumpFmtGt4 type: #'AbstractInstruction *'>
  	<var: #jumpFmtEq2 type: #'AbstractInstruction *'>
  	<var: #jumpFmtLt8 type: #'AbstractInstruction *'>
+ 	<var: #jumpFmtGt11 type: #'AbstractInstruction *'>
  	<var: #jumpLarge type: #'AbstractInstruction *'>
  	cogit MoveR: ReceiverResultReg R: TempReg.
  	jumpSI := self genJumpSmallIntegerInScratchReg: TempReg.
  	cogit MoveR: Arg0Reg R: TempReg.
  	cogit MoveR: Arg0Reg R: Arg1Reg.
  	jumpNotSI := self genJumpNotSmallIntegerInScratchReg: TempReg.
  	self
  		genGetSizeOf: ReceiverResultReg
  		into: ClassReg
  		formatReg: SendNumArgsReg
  		scratchReg: TempReg
  		abortJumpsInto: [:jnx :jic| jumpNotIndexable := jnx. jumpIsContext := jic].
  	self genConvertSmallIntegerToIntegerInScratchReg: Arg1Reg.
  	cogit SubCq: 1 R: Arg1Reg.
  	cogit CmpR: ClassReg R: Arg1Reg.
  	jumpBounds := cogit JumpAboveOrEqual: 0.
  	"This is tedious.  Because of register pressure on x86 (and the baroque
  	 complexity of the size computation) we have to recompute the format
  	 because it may have been smashed computing the fixed fields.  But at
  	 least we have the fixed fields, if any, in formatReg and recomputing
  	 these is more expensive than recomputing format.  In any case this
  	 should still be faster than the interpreter and we hope this object
  	 representation's days are numbered."
  	cogit
  		MoveMw: 0 r: ReceiverResultReg R: ClassReg;	"self baseHeader: receiver"
  		LogicalShiftRightCq: objectMemory instFormatFieldLSB R: ClassReg;
  		AndCq: self instFormatFieldMask R: ClassReg;	"self formatOfHeader: ClassReg"
  		CmpCq: 4 R: ClassReg.
  	jumpFmtGt4 := cogit JumpGreater: 0.
  	cogit CmpCq: 2 R: ClassReg.	"Common case, e.g. Array, has format = 2"
  	jumpFmtEq2 := cogit JumpZero: 0.
  	cogit AddR: SendNumArgsReg R: Arg1Reg. "Add fixed fields to index"
  	jumpFmtEq2 jmpTarget: cogit Label.
  	cogit "Too lazy [knackered, more like. ed.] to define index with displacement addressing right now"
  		AddCq: BaseHeaderSize / BytesPerWord R: Arg1Reg;
  		MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
  		RetN: retNoffset.
  	jumpFmtGt4 jmpTarget: cogit Label.
+ 	"Byte objects have formats 8 through 15, Compiled methods being 12 through 15;
+ 	 fail for CompiledMethod allowing the CoInterpeter to impose stricter bounds checks."
  	cogit CmpCq: 8 R: ClassReg.
  	jumpFmtLt8 := cogit JumpLess: 0.
+ 	cogit CmpCq: 11 R: ClassReg.
+ 	jumpFmtGt11 := cogit JumpGreater: 0.
  	cogit
  		AddCq: BaseHeaderSize R: Arg1Reg;
  		MoveXbr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg.
  	self genConvertIntegerToSmallIntegerInScratchReg: ReceiverResultReg.
  	cogit RetN: retNoffset.
  	jumpFmtLt8 jmpTarget: cogit Label.
  	self assert: BytesPerWord = 4. "documenting my laziness"
  	cogit "Too lazy [knackered, more like. ed.] to define index with displacement addressing right now"
  		AddCq: BaseHeaderSize / BytesPerWord R: Arg1Reg;
  		MoveXwr: Arg1Reg R: ReceiverResultReg R: ReceiverResultReg;
  		CmpCq: 16r3FFFFFFF R: ReceiverResultReg.
  	jumpLarge := cogit JumpAbove: 0.
  	self genConvertIntegerToSmallIntegerInScratchReg: ReceiverResultReg.
  	cogit RetN: retNoffset.
  	jumpLarge jmpTarget: (cogit CallRT: cogit cePositive32BitIntegerTrampoline).
  	cogit
  		MoveR: TempReg R: ReceiverResultReg;
  		RetN: retNoffset.
  	jumpSI jmpTarget:
  	(jumpNotSI jmpTarget:
  	(jumpNotIndexable jmpTarget:
  	(jumpIsContext jmpTarget:
  	(jumpBounds jmpTarget:
+ 	(jumpFmtGt11 jmpTarget:
+ 		cogit Label))))).
- 		cogit Label)))).
  	^0!

Item was removed:
- ----- Method: CogVMSimulator>>install:inAtCache:at:string: (in category 'indexing primitive support') -----
- install: rcvr inAtCache: cache at: atIx string: stringy
- 	(self is: rcvr KindOf: 'BooleanArray') ifTrue: [self halt].
- 	^super install: rcvr inAtCache: cache at: atIx string: stringy!

Item was added:
+ ----- Method: NewObjectMemory>>firstValidIndexOfIndexableObject:withFormat: (in category 'indexing primitive support') -----
+ firstValidIndexOfIndexableObject: obj withFormat: fmt
+ 	"Answer the one-relative index of the first valid index in an indexbale object
+ 	 with the given format.  This is 1 for all objects except compiled methods
+ 	 where the first index is beyond the last literal.
+ 	 Used for safer bounds-checking on methods."
+ 	^fmt >= 12
+ 		ifTrue: [coInterpreter firstByteIndexOfMethod: obj]
+ 		ifFalse: [1]!

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:
- 		and: [self oop: index isLessThanOrEqualTo: stSize])
- 	ifTrue:
  		[fmt := atCache at: atIx+AtCacheFmt.
+ 		 fmt <= 4 ifTrue:
- 		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"
- 			^ 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"
- 		fmt >= 16  "Note fmt >= 16 is an artificial flag for strings"
  			ifTrue: "String"
+ 				[^self characterForAscii: (objectMemory fetchByte: index - 1 ofObject: rcvr)]
+ 			ifFalse:
+ 				[(fmt < 12 "ByteArray"
+ 				  or: [index >= (self firstByteIndexOfMethod: rcvr) "CompiledMethod"]) ifTrue:
+ 					[^objectMemory integerObjectOf: (objectMemory fetchByte: index - 1 ofObject: rcvr)]]].
- 			[^ 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])!

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:
- 		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].
- 			^ 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].
- 			^ nil].
  		fmt >= 16  "Note fmt >= 16 is an artificial flag for strings"
+ 			ifTrue: [(objectMemory
+ 							is: value
+ 							instanceOf: (objectMemory splObj: ClassCharacter)
+ 							compactClassIndex: 0) ifFalse:
+ 						[^self primitiveFailFor: PrimErrBadArgument].
+ 					valToPut := objectMemory fetchPointer: CharacterValueIndex ofObject: value]
+ 			ifFalse:
+ 				[(fmt >= 12 and: [index < (self firstByteIndexOfMethod: rcvr)]) ifTrue: "CompiledMethod"
+ 					[^self primitiveFailFor: PrimErrBadIndex].
+ 				valToPut := value].
- 			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 primitiveFailFor: PrimErrBadArgument].
+ 			^objectMemory storeByte: index - 1 ofObject: rcvr withValue: 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])!

Item was added:
+ ----- Method: StackInterpreter>>firstByteIndexOfMethod: (in category 'compiled methods') -----
+ firstByteIndexOfMethod: methodObj
+ 	"Answer the one-relative index of the first bytecode in methodObj.
+ 	 Used for safer bounds-checking on methods."
+ 	^(self literalCountOf: methodObj) + LiteralStart * BytesPerWord + 1!

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: (objectMemory firstValidIndexOfIndexableObject: array withFormat: fmt))
- 	((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!

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: (objectMemory firstValidIndexOfIndexableObject: array withFormat: fmt))
- 	((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])]!



More information about the Vm-dev mailing list