[Vm-dev] VM Maker: VMMaker-dtl.222.mcz

David T. Lewis lewis at mail.msen.com
Sat Mar 19 17:36:04 UTC 2011


On Sat, Mar 19, 2011 at 04:39:05PM +0100, Igor Stasenko wrote:
>  
> On 19 March 2011 17:09,  <squeak-dev-noreply at lists.squeakfoundation.org> wrote:
> >
> > Dave Lewis uploaded a new version of VMMaker to project VM Maker:
> > http://www.squeaksource.com/VMMaker/VMMaker-dtl.222.mcz
> >
> > ==================== Summary ====================
> >
> > Name: VMMaker-dtl.222
> > Author: dtl
> > Time: 19 March 2011, 11:09:09 am
> > UUID: 809d5eb5-6f73-4e6a-a595-428ed4536dc0
> > Ancestors: VMMaker-dtl.221
> >
> > Fix MiscPrimitivePluginTest to properly test behavior of #primitiveFindSubstring and verify presence of a fix in TMethod>>argConversionExprFor:stackIndex: that performs type checking on string arguments.
> >
> >
> 
> Dave, could you check it for oscog branch too?

Hi Igor,

Actually I was going to reply to your earlier question about
tests that you can run in an image (without VMMaker) that provide
coverage for the VM. But as soon as I looked at it I realized that
I has screwed this one up, so I fixed it and this the change you see
posted here.

There are a number of tests in the VMMaker package, mostly accumlated
during bug fixing but also some stuff to support the work I did
to support 64 and 32 bit images from a single code base (hence not
immediately relevant for inclusion in oscog). The two tests that
might be useful outside of VMMaker are JPEGReadWriter2PluginTest
and MiscPrimitivePluginTest, so I am attaching fileouts for these
two. Have a look and see if you thing they should go in the main
Squeak/Pharo images, or stay in VMMaker(s). These two along with
BitBltSimulationTest would also be suitable to include in oscog.

I have stayed away from committing anything directly to the oscog
branch out of concern that it may lead to confusion between the
two branches if my 'dtl' initials start showing up there. I do
have some changes that can be applied to oscog (mostly to get
rid of cosmetic differences between the two branches that clutter
up the Montecello browser). I've sent a few of these to Eliot but
I don't know if that is the preferred approach going forward.
Advice welcome, as I do want to put some more effort into reconciling
the code bases pretty soon.

Dave

-------------- next part --------------
'From Squeak3.11alpha of 17 March 2011 [latest update: #11148] on 19 March 2011 at 1:09:35 pm'!
TestCase subclass: #JPEGReadWriter2PluginTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMaker-Tests'!
!JPEGReadWriter2PluginTest commentStamp: 'dtl 10/9/2010 12:22' prior: 0!
Unit tests for JPEGReadWriter2Plugin. Initially this is a single test that documents a bug report, other tests may be added over time.
!


!JPEGReadWriter2PluginTest methodsFor: 'testing' stamp: 'dtl 10/9/2010 12:28'!
testPluginPresent

	self assert: JPEGReadWriter2 new isPluginPresent! !

!JPEGReadWriter2PluginTest methodsFor: 'testing' stamp: 'dtl 10/9/2010 14:13'!
testPrimJPEGReadImage

	| form |
	form := JPEGReadWriter2 formFromStream: self formBytes readStream.
	self should: form bits first = 16rFF808080

"[Vm-dev] JPEGReadWriter2Plugin
Bert Freudenberg bert at freudenbergs.de
Mon Sep 27 15:22:43 UTC 2010

Hi,

have there been changes lately to the jpeg plugin?

On a Mac 4.2.4 VM I see an off-by-one error, all pixels are moved to the right, the first pixel is transparent. On a Mac 5.8.1 Cog VM it works as expected though.

Here's my little test:

(JPEGReadWriter2 formFromStream: #[16rFF 16rD8 16rFF 16rE0 16r00 16r10 16r4A 16r46 16r49 16r46 16r00 16r01 16r01 16r01 16r00 16r48 16r00 16r48 16r00 16r00 16rFF 16rDB 16r00 16r43 16r00 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rFF 16rC2 16r00 16r0B 16r08 16r00 16r01 16r00 16r01 16r01 16r01 16r11 16r00 16rFF 16rC4 16r00 16r14 16r10 16r01 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16rFF 16rDA 16r00 16r08 16r01 16r01 16r00 16r01 16r3F 16r10] readStream) bits first hex

On 5.8.11 I get 16rFF808080 as expected, on 4.2.4 I get 0.
"! !

!JPEGReadWriter2PluginTest methodsFor: 'testing' stamp: 'dtl 10/9/2010 14:14'!
testPrimJPEGWriteImage

	| form bytes ws |
	form := JPEGReadWriter2 formFromStream: self formBytes readStream.
	ws := WriteStream on: ByteArray new.
	JPEGReadWriter2 putForm: form onStream: ws.
	bytes := ws contents.
	self should: self formBytes = bytes
! !


!JPEGReadWriter2PluginTest methodsFor: 'private' stamp: 'dtl 11/2/2010 13:15'!
formBytes
	"A jpeg that was generated from Squeak. When written to and from a
	stream, the same bytes should be obtained."

	^ #(255 216 255 224 0 16 74 70 73 70 0 1 1 0 0 1 0 1 0 0 255 219 0 67 0 8 6 6 7 6 5 8 7 7 7 9 9 8 10 12 20 13 12 11 11 12 25 18 19 15 20 29 26 31 30 29 26 28 28 32 36 46 39 32 34 44 35 28 28 40 55 41 44 48 49 52 52 52 31 39 57 61 56 50 60 46 51 52 50 255 219 0 67 1 9 9 9 12 11 12 24 13 13 24 50 33 28 33 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 50 255 192 0 17 8 0 1 0 1 3 1 34 0 2 17 1 3 17 1 255 196 0 31 0 0 1 5 1 1 1 1 1 1 0 0 0 0 0 0 0 0 1 2 3 4 5 6 7 8 9 10 11 255 196 0 181 16 0 2 1 3 3 2 4 3 5 5 4 4 0 0 1 125 1 2 3 0 4 17 5 18 33 49 65 6 19 81 97 7 34 113 20 50 129 145 161 8 35 66 177 193 21 82 209 240 36 51 98 114 130 9 10 22 23 24 25 26 37 38 39 40 41 42 52 53 54 55 56 57 58 67 68 69 70 71 72 73 74 83 84 85 86 87 88 89 90 99 100 101 102 103 104 105 106 115 116 117 118 119 120 121 122 131 132 133 134 135 136 137 138 146 147 148 149 150 151 152 153 154 162 163 164 165 166 167 168 169 170 178 179 180 181 182 183 184 185 186 194 195 196 197 198 199 200 201 202 210 211 212 213 214 215 216 217 218 225 226 227 228 229 230 231 232 233 234 241 242 243 244 245 246 247 248 249 250 255 196 0 31 1 0 3 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 1 2 3 4 5 6 7 8 9 10 11 255 196 0 181 17 0 2 1 2 4 4 3 4 7 5 4 4 0 1 2 119 0 1 2 3 17 4 5 33 49 6 18 65 81 7 97 113 19 34 50 129 8 20 66 145 161 177 193 9 35 51 82 240 21 98 114 209 10 22 36 52 225 37 241 23 24 25 26 38 39 40 41 42 53 54 55 56 57 58 67 68 69 70 71 72 73 74 83 84 85 86 87 88 89 90 99 100 101 102 103 104 105 106 115 116 117 118 119 120 121 122 130 131 132 133 134 135 136 137 138 146 147 148 149 150 151 152 153 154 162 163 164 165 166 167 168 169 170 178 179 180 181 182 183 184 185 186 194 195 196 197 198 199 200 201 202 210 211 212 213 214 215 216 217 218 226 227 228 229 230 231 232 233 234 242 243 244 245 246 247 248 249 250 255 218 0 12 3 1 0 2 17 3 17 0 63 0 40 162 138 0 255 217) asByteArray
! !
-------------- next part --------------
'From Squeak3.11alpha of 17 March 2011 [latest update: #11148] on 19 March 2011 at 1:09:48 pm'!
TestCase subclass: #MiscPrimitivePluginTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMaker-Tests'!
!MiscPrimitivePluginTest commentStamp: 'dtl 11/10/2010 22:04' prior: 0!
Various classes in the image contain methods intended for translation to C for execution as primitives in MiscPrimitivePlugin. MiscPrimitivePluginTest provides tests to validate these methods.
!


!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 2/1/2011 19:49'!
expectedFailures

	^#(testFindSubstringOldVersionWithMissingTypeChecks
		testFindSubstringInWideString)
! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 11/9/2010 20:00'!
testCompareWithCollated
	"Verify that primitive exists in the VM"

	self assert: 3 = (self compare: 'foo' with: 'bar' collated: ((0 to: 255) as: ByteArray))
! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 11/10/2010 08:03'!
testCompressToByteArray

	| bitmap byteArray |
	bitmap := Bitmap with: 16rFFFFFFFF.
	byteArray := ByteArray new:  4.
	self compress: bitmap toByteArray: byteArray.
	self should: byteArray = #[1 5 255 0]! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 11/10/2010 20:14'!
testConvert8bitSignedFromTo16Bit
	"SampledSound class>>convert8bitSignedFrom:to16Bit:"


	| aByteArray aSoundBuffer |
	aByteArray := #[1 2 3 4 5 6 7 8 9].
	aSoundBuffer := SoundBuffer newMonoSampleCount: aByteArray size.
	self convert8bitSignedFrom: aByteArray to16Bit: aSoundBuffer.
	self assert: aSoundBuffer = ((SoundBuffer new: 10) at: 1 put: 256; at: 2 put: 512;
		at: 3 put: 768; at: 4 put: 1024; at: 5 put: 1280; at: 6 put: 1536; at: 7 put: 1792;
		at: 8 put: 2048; at: 9 put: 2304; at: 10 put: 0; yourself)! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 11/10/2010 20:00'!
testDecompressFromByteArrayAt

	| bitmap byteArray s size |
	byteArray := #(1 5 255  0) asByteArray.
	s := ReadStream on: byteArray.
	size := Bitmap decodeIntFrom: s.
	bitmap := Bitmap new: size.
	self decompress: bitmap fromByteArray: byteArray at: s position + 1.
	self should: bitmap = ((Bitmap new: 1) at: 1 put: 4294967295; yourself)! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 11/9/2010 20:54'!
testFindFirstInStringInSetStartingAt

	| position set |
	set := ((0 to: 255) collect: [:e | (e \\ 2) + $0 asciiValue]) asByteArray.
	position := self findFirstInString: 'abcdef' inSet: set startingAt: 1.
	self assert: position = 1
! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 3/19/2011 00:31'!
testFindSubstringInByteString
	"Verify that primitive exists in the VM and works as expected for byte
	sized string and key. If key is a WideString, as may be the case if testing
	for a WideString as substring of a byte sized string, then the primitive
	should fail. Earlier version of the primitive would accept the non-bytes
	parameter, leading to incorrect results, as documented in
	testFindSubstringOldVersionWithMissingTypeChecks"

	| position |
	position := MiscPrimitivePluginTest new
				findSubstring: 'bc'
				in: 'abcdef'
				startingAt: 1
				matchTable: ((0 to: 255)
						as: ByteArray).
	self assert: position = 2.
	self should: [MiscPrimitivePluginTest new
				findSubstring: 'bc' asWideString
				in: 'abcdef'
				startingAt: 1
				matchTable: ((0 to: 255)
						as: ByteArray)]
		raise: Error
	
! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 3/17/2011 22:40'!
testFindSubstringInWideString
	"The primitive will fail if invoked on a non-byte receiver. WideString does
	not call the primitive, so this is an expected failure."

	| position |
	position := MiscPrimitivePluginTest new
				findSubstring: 'bc'
				in: 'abcdef' asWideString
				startingAt: 1
				matchTable: ((0 to: 255)
						as: ByteArray).
	self assert: position = 0.
	position := MiscPrimitivePluginTest new
				findSubstring: 'bc' asWideString
				in: 'abcdef' asWideString
				startingAt: 1
				matchTable: ((0 to: 255)
						as: ByteArray).
	self assert: position = 2
! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 3/18/2011 08:52'!
testFindSubstringOldVersionWithMissingTypeChecks
	"Verify that primitive exists in the VM. This test documents the behavior of older versions
	of the primitive that did not perform type checking on to fail on WideString parameters.
	Newer versions of the primitive handle this properly, hence this test is an expectedFailure.
	The fix for this issue (by Andreas Raab) is in TMethod>>argConversionExprFor:stackIndex:
	which was added to VMMaker in VMMaker-dtl.202.
	
	If this test passes, it is an indication that the TMethod>>argConversionExprFor:stackIndex:
	update is missing from the VMMaker code generator that produced the VM."
	
	"(MiscPrimitivePluginTest selector: #testArgsAsFlatArrayAndOffsets) run"

	| position |
	"If both receiver and argument are byte size, the primitive performs correctly"
	position := MiscPrimitivePluginTest new
				findSubstring: 'bc'
				in: 'abcdef'
				startingAt: 1
				matchTable: ((0 to: 255)
						as: ByteArray).
	self assert: position = 2.

	"Plugin accepts wide string argument, but should not do so."
	position := MiscPrimitivePluginTest new
				findSubstring: 'bc' asWideString
				in: 'abcdef'
				startingAt: 1
				matchTable: ((0 to: 255)
						as: ByteArray).
	self assert: position = 0.

	position := MiscPrimitivePluginTest new
				findSubstring: 'bc'
				in: 'abcdef' asWideString
				startingAt: 1
				matchTable: ((0 to: 255)
						as: ByteArray).
	self assert: position = 0.

	"Older versions of the plugin produce incorrect results here"
	position := MiscPrimitivePluginTest new
				findSubstring: 'bc' asWideString
				in: 'abcdef' asWideString
				startingAt: 1
				matchTable: ((0 to: 255)
						as: ByteArray).
	self assert: position = 5 "Incorrect!!"
! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 11/10/2010 21:48'!
testHashBytesStartingWith

	| ba result |
	ba := #[1 2 3 4 5 6 7 8 9].
	result := self hashBytes: ba startingWith: 12345.
	self assert: result = 170953102
! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 11/9/2010 20:57'!
testIindexOfAsciiInStringStartingAt

	| position |
	position := self indexOfAscii: 50 inString: '012345' startingAt: 1.
	self assert: position = 3! !

!MiscPrimitivePluginTest methodsFor: 'testing' stamp: 'dtl 11/9/2010 20:33'!
testTranslateFromToTable
	"Verify that primitive exists in the VM"

	| s t |
	s := 'foo' copy. "copy so string is instantiated each time"
	t := ByteArray withAll: ((1 to: 255) as: ByteArray).
	self translate: s from: 1 to: 3 table: t.
	self assert: s = 'gpp'
! !


!MiscPrimitivePluginTest methodsFor: 'primitives' stamp: 'dtl 11/9/2010 19:48'!
compare: string1 with: string2 collated: order
	"Return 1, 2 or 3, if string1 is <, =, or > string2, with the collating order of characters given by the order array."

	<primitive: 'primitiveCompareString' module: 'MiscPrimitivePlugin'>
	self primitiveFailed
! !

!MiscPrimitivePluginTest methodsFor: 'primitives' stamp: 'dtl 11/10/2010 19:42'!
compress: bm toByteArray: ba

	<primitive: 'primitiveCompressToByteArray' module: 'MiscPrimitivePlugin'>
	self primitiveFailed! !

!MiscPrimitivePluginTest methodsFor: 'primitives' stamp: 'dtl 11/10/2010 20:03'!
convert8bitSignedFrom: aByteArray to16Bit: aSoundBuffer
	"Copy the contents of the given array of signed 8-bit samples into the given array of 16-bit signed samples."

	<primitive: 'primitiveConvert8BitSigned' module: 'MiscPrimitivePlugin'>
	self primitiveFailed
! !

!MiscPrimitivePluginTest methodsFor: 'primitives' stamp: 'dtl 11/10/2010 19:42'!
decompress: bm fromByteArray: ba at: index

	<primitive: 'primitiveDecompressFromByteArray' module: 'MiscPrimitivePlugin'>
	self primitiveFailed
! !

!MiscPrimitivePluginTest methodsFor: 'primitives' stamp: 'dtl 11/10/2010 20:03'!
findFirstInString: aString  inSet: inclusionMap  startingAt: start

	<primitive: 'primitiveFindFirstInString' module: 'MiscPrimitivePlugin'>
	self primitiveFailed
! !

!MiscPrimitivePluginTest methodsFor: 'primitives' stamp: 'dtl 11/9/2010 19:38'!
findSubstring: key in: body startingAt: start matchTable: matchTable
	"Answer the index in the string body at which the substring key first occurs, at or beyond start.  The match is determined using matchTable, which can be used to effect, eg, case-insensitive matches.  If no match is found, zero will be returned."

	<primitive: 'primitiveFindSubstring' module: 'MiscPrimitivePlugin'>
	self primitiveFailed
! !

!MiscPrimitivePluginTest methodsFor: 'primitives' stamp: 'dtl 11/10/2010 21:36'!
hashBytes: aByteArray startingWith: speciesHash
	"Answer the hash of a byte-indexed collection,
	using speciesHash as the initial value.
	See SmallInteger>>hashMultiply.

	The primitive should be renamed at a
	suitable point in the future"

	<primitive: 'primitiveStringHash' module: 'MiscPrimitivePlugin'>
	self primitiveFailed
! !

!MiscPrimitivePluginTest methodsFor: 'primitives' stamp: 'dtl 11/10/2010 20:03'!
indexOfAscii: anInteger inString: aString startingAt: start

	<primitive: 'primitiveIndexOfAsciiInString' module: 'MiscPrimitivePlugin'>
	self primitiveFailed
! !

!MiscPrimitivePluginTest methodsFor: 'primitives' stamp: 'dtl 11/10/2010 20:03'!
translate: aString from: start  to: stop  table: table
	"translate the characters in the string by the given table, in place"

	<primitive: 'primitiveTranslateStringWithTable' module: 'MiscPrimitivePlugin'>
	self primitiveFailed! !


More information about the Vm-dev mailing list