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

commits at source.squeak.org commits at source.squeak.org
Fri Nov 15 22:45:50 UTC 2013


David T. Lewis uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-dtl.329.mcz

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

Name: VMMaker-dtl.329
Author: dtl
Time: 15 November 2013, 5:44:12.345 pm
UUID: 1050f0cf-ec99-40ca-9fcf-165024cb2735
Ancestors: VMMaker-dtl.328

Merge MiscPrimitivePluginTest into IncludedMethodsTest, and remove MiscPrimitivePluginTest. Various classes in the image contain methods that are intended to be translated to C and executed as primitives. IncludedMethodsTest provides tests to validate these methods.

=============== Diff against VMMaker-dtl.328 ===============

Item was added:
+ ----- Method: IncludedMethodsTest>>expectedFailures (in category 'testing') -----
+ expectedFailures
+ 
+ 	^#(testFindSubstringOldVersionWithMissingTypeChecks
+ 		testFindSubstringInWideString)
+ !

Item was added:
+ ----- Method: IncludedMethodsTest>>hashBytes:startingWith: (in category 'primitives') -----
+ 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
+ !

Item was added:
+ ----- Method: IncludedMethodsTest>>testFindSubstringInByteString (in category 'testing') -----
+ 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 := self
+ 				findSubstring: 'bc'
+ 				in: 'abcdef'
+ 				startingAt: 1
+ 				matchTable: ((0 to: 255)
+ 						as: ByteArray).
+ 	self assert: position = 2.
+ 	self should: [self
+ 				findSubstring: 'bc' asWideString
+ 				in: 'abcdef'
+ 				startingAt: 1
+ 				matchTable: ((0 to: 255)
+ 						as: ByteArray)]
+ 		raise: Error
+ 	
+ !

Item was added:
+ ----- Method: IncludedMethodsTest>>testFindSubstringInWideString (in category 'testing') -----
+ 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 := self
+ 				findSubstring: 'bc'
+ 				in: 'abcdef' asWideString
+ 				startingAt: 1
+ 				matchTable: ((0 to: 255)
+ 						as: ByteArray).
+ 	self assert: position = 0.
+ 	position := self
+ 				findSubstring: 'bc' asWideString
+ 				in: 'abcdef' asWideString
+ 				startingAt: 1
+ 				matchTable: ((0 to: 255)
+ 						as: ByteArray).
+ 	self assert: position = 2
+ !

Item was added:
+ ----- Method: IncludedMethodsTest>>testFindSubstringOldVersionWithMissingTypeChecks (in category 'testing') -----
+ 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 := self
+ 				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 := self
+ 				findSubstring: 'bc' asWideString
+ 				in: 'abcdef'
+ 				startingAt: 1
+ 				matchTable: ((0 to: 255)
+ 						as: ByteArray).
+ 	self assert: position = 0.
+ 
+ 	position := self
+ 				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 := self
+ 				findSubstring: 'bc' asWideString
+ 				in: 'abcdef' asWideString
+ 				startingAt: 1
+ 				matchTable: ((0 to: 255)
+ 						as: ByteArray).
+ 	self assert: position = 5 "Incorrect!!"
+ !

Item was added:
+ ----- Method: IncludedMethodsTest>>testHashBytesStartingWith (in category 'testing - MiscPrimitivePlugin') -----
+ testHashBytesStartingWith
+ 
+ 	| ba result |
+ 	ba := #[1 2 3 4 5 6 7 8 9].
+ 	result := self hashBytes: ba startingWith: 12345.
+ 	self assert: result = 170953102
+ !

Item was removed:
- 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.
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>compare:with:collated: (in category 'primitives') -----
- 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
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>compress:toByteArray: (in category 'primitives') -----
- compress: bm toByteArray: ba
- 
- 	<primitive: 'primitiveCompressToByteArray' module: 'MiscPrimitivePlugin'>
- 	self primitiveFailed!

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>convert8bitSignedFrom:to16Bit: (in category 'primitives') -----
- 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
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>decompress:fromByteArray:at: (in category 'primitives') -----
- decompress: bm fromByteArray: ba at: index
- 
- 	<primitive: 'primitiveDecompressFromByteArray' module: 'MiscPrimitivePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>expectedFailures (in category 'testing') -----
- expectedFailures
- 
- 	^#(testFindSubstringOldVersionWithMissingTypeChecks
- 		testFindSubstringInWideString)
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>findFirstInString:inSet:startingAt: (in category 'primitives') -----
- findFirstInString: aString  inSet: inclusionMap  startingAt: start
- 
- 	<primitive: 'primitiveFindFirstInString' module: 'MiscPrimitivePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>findSubstring:in:startingAt:matchTable: (in category 'primitives') -----
- 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
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>hashBytes:startingWith: (in category 'primitives') -----
- 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
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>indexOfAscii:inString:startingAt: (in category 'primitives') -----
- indexOfAscii: anInteger inString: aString startingAt: start
- 
- 	<primitive: 'primitiveIndexOfAsciiInString' module: 'MiscPrimitivePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testCompareWithCollated (in category 'testing') -----
- testCompareWithCollated
- 	"Verify that primitive exists in the VM"
- 
- 	self assert: 3 = (self compare: 'foo' with: 'bar' collated: ((0 to: 255) as: ByteArray))
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testCompressToByteArray (in category 'testing') -----
- testCompressToByteArray
- 
- 	| bitmap byteArray |
- 	bitmap := Bitmap with: 16rFFFFFFFF.
- 	byteArray := ByteArray new:  4.
- 	self compress: bitmap toByteArray: byteArray.
- 	self should: byteArray = #[1 5 255 0]!

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testConvert8bitSignedFromTo16Bit (in category 'testing') -----
- 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)!

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testDecompressFromByteArrayAt (in category 'testing') -----
- 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)!

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testFindFirstInStringInSetStartingAt (in category 'testing') -----
- 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
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testFindSubstringInByteString (in category 'testing') -----
- 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
- 	
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testFindSubstringInWideString (in category 'testing') -----
- 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
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testFindSubstringOldVersionWithMissingTypeChecks (in category 'testing') -----
- 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!!"
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testHashBytesStartingWith (in category 'testing') -----
- testHashBytesStartingWith
- 
- 	| ba result |
- 	ba := #[1 2 3 4 5 6 7 8 9].
- 	result := self hashBytes: ba startingWith: 12345.
- 	self assert: result = 170953102
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testIindexOfAsciiInStringStartingAt (in category 'testing') -----
- testIindexOfAsciiInStringStartingAt
- 
- 	| position |
- 	position := self indexOfAscii: 50 inString: '012345' startingAt: 1.
- 	self assert: position = 3!

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>testTranslateFromToTable (in category 'testing') -----
- 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'
- !

Item was removed:
- ----- Method: MiscPrimitivePluginTest>>translate:from:to:table: (in category 'primitives') -----
- 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