[Vm-dev] VM Maker: VMMaker.oscog-mt.3135.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jan 11 11:20:45 UTC 2022


Marcel Taeumel uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-mt.3135.mcz

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

Name: VMMaker.oscog-mt.3135
Author: mt
Time: 11 January 2022, 12:20:29.464861 pm
UUID: b93d7116-14bf-5543-8c8d-d06c66d5c1a5
Ancestors: VMMaker.oscog-eem.3134

Fixes an off-by-one bug in #loadZipEncoderFrom: and #primitiveZipSendBlock. 

Thanks to Florin Mateoc and Fabio Niephaus for reporting and testing this bug!

See http://lists.squeakfoundation.org/pipermail/vm-dev/2022-January/037536.html

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

Item was changed:
  ----- Method: DeflatePlugin>>determineSizeOfWriteStream: (in category 'primitive support') -----
  determineSizeOfWriteStream: rcvr
  	"Determine the inst size of the class above DeflateStream or
  	 ZipEncoder by looking for the first class whose inst size is less than 7."
  	| class |
  	class := interpreterProxy fetchClassOf: rcvr.
  	[class ~= interpreterProxy nilObject
  	 and: [(interpreterProxy instanceSizeOf: class) >= 7]] whileTrue:
  		[class := interpreterProxy superclassOf: class].
  	class = interpreterProxy nilObject ifTrue:
  		[^false].
  	writeStreamInstSize := interpreterProxy instanceSizeOf: class.
  	^true
+ 
+ "Possible classes of rcvr and (instSize) as of January 2022:
+ 
+ ZipEncoder (8) <- WriteStream (5)
+   !! determineSizeOfWriteStream
+   primitiveZipSendBlock
+ 
+ ZipWriteStream (20) <- DeflateStream (10) <- WriteStream (5)
+   !! determineSizeOfWriteStream:
+   primitiveDeflateBlock
+ 
+ GZipWriteStream (20) <- ZipWriteStream (20) <- ...
+ "!
- !

Item was changed:
  ----- Method: DeflatePlugin>>loadDeflateStreamFrom: (in category 'primitive support') -----
  loadDeflateStreamFrom: rcvr
  	| oop |
  	<inline: false>
  	((interpreterProxy isPointers: rcvr)
  	 and: [(interpreterProxy slotSizeOf: rcvr) >= 15]) ifFalse:
  		[^false].
  	oop := interpreterProxy fetchPointer: 0 ofObject: rcvr.
  	(interpreterProxy isBytes: oop) ifFalse:
  		[^false].
  	writeStreamInstSize = 0 ifTrue:
  		[(self determineSizeOfWriteStream: rcvr) ifFalse:
  			[^false].
  		 "If the receiver wasn't valid then we derived writeStreamInstSize from an invalid source.  discard it."
  		 (interpreterProxy slotSizeOf: rcvr) < (writeStreamInstSize + 5) ifTrue:
  			[writeStreamInstSize := 0.
  			 ^false]].
  	zipCollection := interpreterProxy firstIndexableField: oop.
  	zipCollectionSize := interpreterProxy byteSizeOf: oop.
  
  	zipPosition := interpreterProxy fetchInteger: 1 ofObject: rcvr.
  	zipReadLimit := interpreterProxy fetchInteger: 2 ofObject: rcvr.
  	"zipWriteLimit := interpreterProxy fetchInteger: 3 ofObject: rcvr."
  
+ 	"hashHead"
  	oop := interpreterProxy fetchPointer: writeStreamInstSize + 0 ofObject: rcvr.
  	((interpreterProxy isWords: oop)
  	 and: [(interpreterProxy slotSizeOf: oop) = DeflateHashTableSize]) ifFalse:
  		[^false].
  	zipHashHead := interpreterProxy firstIndexableField: oop.
+ 	
+ 	"hashTail"
  	oop := interpreterProxy fetchPointer: writeStreamInstSize + 1 ofObject: rcvr.
  	((interpreterProxy isWords: oop)
  	 and: [(interpreterProxy slotSizeOf: oop) = DeflateWindowSize]) ifFalse:
  		[^false].
  	zipHashTail := interpreterProxy firstIndexableField: oop.
+ 	
  	zipHashValue := interpreterProxy fetchInteger: writeStreamInstSize + 2 ofObject: rcvr.
  	zipBlockPos := interpreterProxy fetchInteger: writeStreamInstSize + 3 ofObject: rcvr.
  	"zipBlockStart := interpreterProxy fetchInteger: writeStreamInstSize + 4 ofObject: rcvr."
+ 	
+ 	"literals"
  	oop := interpreterProxy fetchPointer: writeStreamInstSize + 5 ofObject: rcvr.
  	(interpreterProxy isBytes: oop) ifFalse:
  		[^false].
  	zipLiteralSize := interpreterProxy slotSizeOf: oop.
  	zipLiterals := interpreterProxy firstIndexableField: oop.
  
+ 	"distances"
  	oop := interpreterProxy fetchPointer: writeStreamInstSize + 6 ofObject: rcvr.
  	((interpreterProxy isWords: oop)
  	 and: [(interpreterProxy slotSizeOf: oop) >= zipLiteralSize]) ifFalse:
  		[^false].
  	zipDistances := interpreterProxy firstIndexableField: oop.
  
+ 	"literalFreq"
  	oop := interpreterProxy fetchPointer: writeStreamInstSize + 7 ofObject: rcvr.
  	((interpreterProxy isWords: oop)
  	 and: [(interpreterProxy slotSizeOf: oop) = DeflateMaxLiteralCodes]) ifFalse:
  		[^false].
  	zipLiteralFreq := interpreterProxy firstIndexableField: oop.
  
+ 	"distanceFreq"
  	oop := interpreterProxy fetchPointer: writeStreamInstSize + 8 ofObject: rcvr.
  	((interpreterProxy isWords: oop)
  	 and: [(interpreterProxy slotSizeOf: oop) = DeflateMaxDistanceCodes]) ifFalse:
  		[^false].
  	zipDistanceFreq := interpreterProxy firstIndexableField: oop.
  
  	zipLiteralCount := interpreterProxy fetchInteger: writeStreamInstSize + 9 ofObject: rcvr.
  	zipMatchCount := interpreterProxy fetchInteger: writeStreamInstSize + 10 ofObject: rcvr.
  
  	^interpreterProxy failed not!

Item was changed:
  ----- Method: DeflatePlugin>>loadZipEncoderFrom: (in category 'primitive support') -----
  loadZipEncoderFrom: rcvr
  	| oop |
  	<inline: false>
  	writeStreamInstSize = 0 ifTrue:
  		[(self determineSizeOfWriteStream: rcvr) ifFalse:
  			[^false].
  		 "If the receiver wasn't valid then we derived writeStreamInstSize from an invalid source.  discard it."
  		 (interpreterProxy slotSizeOf: rcvr) < (writeStreamInstSize + 3) ifTrue:
  			[writeStreamInstSize := 0.
  			 ^false]].
  	((interpreterProxy isPointers: rcvr)
  	 and: [(interpreterProxy slotSizeOf: rcvr) >= (writeStreamInstSize + 3)]) ifFalse:
  		[^false].
+ 	
+ 	"collection"
  	oop := interpreterProxy fetchPointer: 0 ofObject: rcvr.
  	(interpreterProxy isBytes: oop) ifFalse:
  		[^interpreterProxy primitiveFail].
  	zipCollection := interpreterProxy firstIndexableField: oop.
  	zipCollectionSize := interpreterProxy byteSizeOf: oop.
  
  	zipPosition := interpreterProxy fetchInteger: 1 ofObject: rcvr.
  	zipReadLimit := interpreterProxy fetchInteger: 2 ofObject: rcvr.
  	"zipWriteLimit := interpreterProxy fetchInteger: 3 ofObject: rcvr."
+ 	
+ 	zipBitBuf := interpreterProxy fetchInteger: writeStreamInstSize + 0 ofObject: rcvr.
+ 	zipBitPos := interpreterProxy fetchInteger: writeStreamInstSize + 1 ofObject: rcvr.
- 	zipBitBuf := interpreterProxy fetchInteger: writeStreamInstSize + 1 ofObject: rcvr.
- 	zipBitPos := interpreterProxy fetchInteger: writeStreamInstSize + 2 ofObject: rcvr.
  
  	^interpreterProxy failed not!

Item was changed:
  ----- Method: DeflatePlugin>>primitiveZipSendBlock (in category 'primitives') -----
  primitiveZipSendBlock
  	| distTree litTree distStream litStream rcvr result |
  	<export: true>
  	interpreterProxy methodArgumentCount = 4 
  		ifFalse:[^interpreterProxy primitiveFail].
  	distTree := interpreterProxy stackObjectValue: 0.
  	litTree := interpreterProxy stackObjectValue: 1.
  	distStream := interpreterProxy stackObjectValue: 2.
  	litStream := interpreterProxy stackObjectValue: 3.
  	rcvr := interpreterProxy stackObjectValue: 4.
  	interpreterProxy failed ifTrue:[^nil].
  	(self loadZipEncoderFrom: rcvr)
  		ifFalse:[^interpreterProxy primitiveFail].
  	((interpreterProxy isPointers: distTree) and:[
  		(interpreterProxy slotSizeOf: distTree) >= 2])
  			ifFalse:[^interpreterProxy primitiveFail].
  	((interpreterProxy isPointers: litTree) and:[
  		(interpreterProxy slotSizeOf: litTree) >= 2])
  			ifFalse:[^interpreterProxy primitiveFail].
  	((interpreterProxy isPointers: litStream) and:[
  		(interpreterProxy slotSizeOf: litStream) >= 3])
  			ifFalse:[^interpreterProxy primitiveFail].
  	((interpreterProxy isPointers: distStream) and:[
  		(interpreterProxy slotSizeOf: distStream) >= 3])
  			ifFalse:[^interpreterProxy primitiveFail].
  	self cCode:'' inSmalltalk:[
  		zipMatchLengthCodes := CArrayAccessor on: ZipWriteStream matchLengthCodes.
  		zipDistanceCodes := CArrayAccessor on: ZipWriteStream distanceCodes.
  		zipExtraLengthBits := CArrayAccessor on: ZipWriteStream extraLengthBits.
  		zipExtraDistanceBits := CArrayAccessor on: ZipWriteStream extraDistanceBits.
  		zipBaseLength := CArrayAccessor on: ZipWriteStream baseLength.
  		zipBaseDistance := CArrayAccessor on: ZipWriteStream baseDistance].
  	result := self sendBlock: litStream with: distStream with: litTree with: distTree.
  	interpreterProxy failed ifFalse:[
  		interpreterProxy storeInteger: 1 ofObject: rcvr withValue: zipPosition.
+ 		interpreterProxy storeInteger: readStreamInstSize + 0 ofObject: rcvr withValue: zipBitBuf.
+ 		interpreterProxy storeInteger: readStreamInstSize + 1 ofObject: rcvr withValue: zipBitPos.
- 		interpreterProxy storeInteger: readStreamInstSize + 1 ofObject: rcvr withValue: zipBitBuf.
- 		interpreterProxy storeInteger: readStreamInstSize + 2 ofObject: rcvr withValue: zipBitPos.
  	].
  	interpreterProxy failed ifFalse:[
  		interpreterProxy pop: 5. "rcvr + args"
  		interpreterProxy pushInteger: result.
  	].!

Item was changed:
  ----- Method: InflatePlugin>>determineSizeOfReadStream: (in category 'primitive support') -----
  determineSizeOfReadStream: rcvr
+ 	"Determine the inst size of the class above InflateStream by
- 	"Determine the inst size of the class above DeflateStream by
  	 looking for the first class whose inst size is less than 13."
  	| class |
  	class := interpreterProxy fetchClassOf: rcvr.
  	[class ~= interpreterProxy nilObject
  	 and: [(interpreterProxy instanceSizeOf: class) >= 13]] whileTrue:
  		[class := interpreterProxy superclassOf: class].
  	class = interpreterProxy nilObject ifTrue:
  		[^false].
  	readStreamInstSize := interpreterProxy instanceSizeOf: class.
+ 	^true
+ 	
+ "Possible classes of rcvr and (instSize) as of January 2022:
+ 
+ FastInflateStream (14) <- InflateStream (14) <- ReadStream (4)
+   !! determineSizeOfReadStream:
+   primitiveInflateDecompressBlock
+ 
+ GZipReadStream (14) <- FastInflateStream (14) <- ...
+ ZipReadStream (15) <- FastInflateStream (14) <- ...
+ ZLibReadStream (14) <- FastInflateStream (14) <- ...
+ "!
- 	^true!



More information about the Vm-dev mailing list