[Vm-dev] Can folks please review carefully the replacement MiscPrimitivePlugin?

David T. Lewis lewis at mail.msen.com
Thu Feb 22 17:43:45 UTC 2018


Hi Eliot,

Attached is IncludedMethodsTest from (old trunk) VMMaker. This is something
I wrote to document the included methods in MiscPrimitivePlugin, so you can
run the tests in e.g. trunk Squeak as a check for presence of the primitives.

Note that some of the primitives are not yet covered by the test, see
#todoForADPCMCodecPlugin.

You may want to consider giving the reimplemented plugin a different class
name, but retain the module name. That would make it easier to keep a copy
of the old plugin (compiled external) that a user can swap in to the runtime
if any problems come up.

It might also be worth considering putting the string, sound, and codec
primitives into separate modules with appropriate names. That would be
harder to manage from the point of view updating primitive references in
the image, but the old MiscPrimitivePlugin is a rather haphazard collection
of functions and this might be a good time to clean that up too.

Dave



On Wed, Feb 21, 2018 at 06:18:53PM -0800, Eliot Miranda wrote:
>  
> Hi All,
> 
>     ignore this.  I'm simulating and finding several problems.  Let me get
> back to you when a simulation progresses without obvious errors.  For those
> that want to play, I've attached what I have so far...
> 
> On Wed, Feb 21, 2018 at 3:06 PM, Eliot Miranda <eliot.miranda at gmail.com>
> wrote:
> 
> > Hi All,
> >
> >     find the first candidate replacement for MiscPrimitivePlugin's
> > translated primitives.  The changes here are not simply cosmetic since the
> > 1-relative indexing in the translated primitives version is clumsy, so I've
> > rewritten to use 0-relative indexing.
> >
> > _,,,^..^,,,_
> > best, Eliot
> >
> 
> 
> 
> -- 
> _,,,^..^,,,_
> best, Eliot


-------------- next part --------------
'From Squeak4.5 of 10 December 2015 [latest update: #1195] on 22 February 2018 at 11:51:09 am'!
TestCase subclass: #IncludedMethodsTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMaker-Tests'!
!IncludedMethodsTest commentStamp: 'dtl 11/9/2010 21:03' prior: 0!
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.
!


!IncludedMethodsTest 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
! !

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

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

!IncludedMethodsTest 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
! !

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

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

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

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

!IncludedMethodsTest 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
! !

!IncludedMethodsTest 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
! !

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

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

!IncludedMethodsTest methodsFor: 'primitives' stamp: 'dtl 11/10/2010 20:36'!
mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: leftVol rightVol: rightVol
	"Play samples from a wave table by stepping a fixed amount through the table on every sample. The table index and increment are scaled to allow fractional increments for greater pitch accuracy."
	"(FMSound pitch: 440.0 dur: 1.0 loudness: 0.5) play"

	<primitive:'primitiveMixFMSound' module:'SoundGenerationPlugin'>
	self primitiveFailed
! !

!IncludedMethodsTest 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! !


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

	^#(testFindSubstringOldVersionWithMissingTypeChecks
		testFindSubstringInWideString)
! !

!IncludedMethodsTest methodsFor: 'testing' stamp: 'dtl 11/15/2013 13:49'!
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
	
! !

!IncludedMethodsTest methodsFor: 'testing' stamp: 'dtl 11/15/2013 13:49'!
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
! !

!IncludedMethodsTest methodsFor: 'testing' stamp: 'dtl 11/15/2013 13:49'!
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!!"
! !


!IncludedMethodsTest methodsFor: 'testing - MiscPrimitivePlugin' 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))
! !

!IncludedMethodsTest methodsFor: 'testing - MiscPrimitivePlugin' 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]! !

!IncludedMethodsTest methodsFor: 'testing - MiscPrimitivePlugin' 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)! !

!IncludedMethodsTest methodsFor: 'testing - MiscPrimitivePlugin' 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)! !

!IncludedMethodsTest methodsFor: 'testing - MiscPrimitivePlugin' 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
! !

!IncludedMethodsTest methodsFor: 'testing - MiscPrimitivePlugin' stamp: 'dtl 11/9/2010 20:14'!
testFindSubstring
	"Verify that primitive exists in the VM and that non byte array arguments cause primitive to fail"

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

!IncludedMethodsTest methodsFor: 'testing - MiscPrimitivePlugin' 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
! !

!IncludedMethodsTest methodsFor: 'testing - MiscPrimitivePlugin' stamp: 'dtl 11/9/2010 20:57'!
testIindexOfAsciiInStringStartingAt

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

!IncludedMethodsTest methodsFor: 'testing - MiscPrimitivePlugin' 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'
! !


!IncludedMethodsTest methodsFor: 'testing - SoundGeneratorPlugin' stamp: 'dtl 11/10/2010 20:45'!
testMixSampleCountIntoStartingAtLeftVolRightVol

	"mixSampleCount: n into: aSoundBuffer startingAt: startIndex leftVol: leftVol rightVol: rightVol"! !

!IncludedMethodsTest methodsFor: 'testing - SoundGeneratorPlugin' stamp: 'dtl 11/9/2010 21:02'!
todoForSoundGeneratorPlugin
	"TODO - write tests for these"

	^#(
		(FMSound mixSampleCount:into:startingAt:leftVol:rightVol:)
		(PluckedSound mixSampleCount:into:startingAt:leftVol:rightVol:)
		(LoopedSampledSound mixSampleCount:into:startingAt:leftVol:rightVol:)
		(SampledSound mixSampleCount:into:startingAt:leftVol:rightVol:)
		(ReverbSound applyReverbTo:startingAt:count:)
		)! !


!IncludedMethodsTest methodsFor: 'testing - ADPCMCodecPlugin' stamp: 'dtl 11/9/2010 21:02'!
todoForADPCMCodecPlugin
	"TODO - write tests for these"

	^#(
		(ADPCMCodec privateDecodeMono:)
		(ADPCMCodec privateDecodeStereo:)
		(ADPCMCodec privateEncodeMono:)
		(ADPCMCodec privateEncodeStereo:)
		(ADPCMCodec indexForDeltaFrom:to:)
		(ADPCMCodec nextBits:)
		(ADPCMCodec nextBits:put:)
		)! !


More information about the Vm-dev mailing list