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

David T. Lewis lewis at mail.msen.com
Tue Dec 11 23:30:42 UTC 2018


I put this in the inbox because:

Current generated sources in the squeakvm.org SVN repository are generated
from a Squeak 4.5 image (latest update: #1195).

VMMaker-eem.397 depends on compiler enhancements in recent Squeak trunk,
not available circa Squeak 4.5.

I have not tested code generation from recent Squeak trunk, and it may
have issues related to included methods, e.g. MiscPrimitivePlugin, see
IncludedMethodsTest for verification.

Therefore I put VMMaker-dtl.397 in the inbox until dependencies can be
sorted out.

Dave

On Tue, Dec 11, 2018 at 11:27:09PM +0000, commits at source.squeak.org wrote:
>  
> David T. Lewis uploaded a new version of VMMaker to project VM Maker Inbox:
> http://source.squeak.org/VMMakerInbox/VMMaker-dtl.397.mcz
> 
> ==================== Summary ====================
> 
> Name: VMMaker-dtl.397
> Author: dtl
> Time: 11 December 2018, 6:26:57.684 pm
> UUID: e193904f-770a-4cfe-a44e-98d3c6a3c413
> Ancestors: VMMaker-dtl.396
> 
> Merge Nicolas' fixes for FloatMathPluginTests from oscog. Tests are green with this update.
> 
> Name: VMMaker.oscog-nice.2492
> Author: nice
> Time: 11 December 2018, 10:52:00.075091 pm
> UUID: 8fac9bb8-92b6-41f2-8646-230a75c04ee9
> Ancestors: VMMaker.oscog-eem.2491
> 
> Fix the FloatMathPluginTests and classify them in 'VMMaker-Tests'
> 
> All the reference md5 hash have been produced with specific series of number generated with a specific Park-Miller Pseudo-Random-Number-Generator.
> 
> The tests cannot rely on Random implementation (or should I say random implementation) which happens to change from time to time, so hardcode the PRNG.
> 
> =============== Diff against VMMaker-dtl.396 ===============
> 
> Item was changed:
>   TestCase subclass: #FloatMathPluginTests
> + 	instanceVariableNames: 'seed'
> - 	instanceVariableNames: 'random'
>   	classVariableNames: ''
>   	poolDictionaries: ''
>   	category: 'VMMaker-Tests'!
>   
>   !FloatMathPluginTests commentStamp: '<historical>' prior: 0!
>   FloatMathPluginTests buildSuite run.!
> 
> Item was changed:
>   ----- Method: FloatMathPluginTests>>makeTestData:using:seed:rounds: (in category 'running') -----
>   makeTestData: fileName using: aBlock seed: seed rounds: rounds
>   	| bytes out float result |
>   	bytes := ByteArray new: 8.
>   	out := FileStream newFileNamed: fileName.
>   	[
>   		out binary. 
>   		out nextNumber: 4 put: rounds.
>   		out nextNumber: 4 put: seed.
> + 		self seed: seed.
> - 		random := Random seed: seed.
>   		float := Float basicNew: 2.
>   		'Creating test data for: ', fileName 
>   			displayProgressAt: Sensor cursorPoint 
>   			from: 1 to: rounds during:[:bar|
>   				1 to: rounds do:[:i|
>   					i \\ 10000 = 0 ifTrue:[bar value: i].
> + 					[1 to: 8 do:[:j| bytes at: j put: (self nextInt: 256)-1].
> - 					[1 to: 8 do:[:j| bytes at: j put: (random nextInt: 256)-1].
>   					float basicAt: 1 put: (bytes unsignedLongAt: 1 bigEndian: true).
>   					float basicAt: 2 put: (bytes unsignedLongAt: 5 bigEndian: true).
>   					float isNaN] whileTrue.
>   					result := aBlock value: float.
>   					out nextNumber: 4 put: (result basicAt: 1).
>   					out nextNumber: 4 put: (result basicAt: 2).
>   				].
>   			].
>   	] ensure:[out close].
>   !
> 
> Item was added:
> + ----- Method: FloatMathPluginTests>>nextInt: (in category 'rand') -----
> + nextInt: anInteger
> + 	"Answer a random integer in the interval [1, anInteger]."
> + 
> + 	| a m q r lo hi aLoRHi |
> + 	a := 16r000041A7 asFloat.    " magic constant =      16807 "
> + 	m := 16r7FFFFFFF asFloat.    " magic constant = 2147483647 "
> + 	q := (m quo: a) asFloat.
> + 	r  := (m \\ a) asFloat.
> + 	hi := (seed quo: q) asFloat.
> + 	lo := seed - (hi * q).  " = seed rem: q"  
> + 	aLoRHi := (a * lo) - (r * hi).
> + 	seed := (aLoRHi > 0.0)
> + 		ifTrue:  [aLoRHi]
> + 		ifFalse: [aLoRHi + m].
> + 	^ (seed / m * anInteger) truncated + 1!
> 
> Item was changed:
>   ----- Method: FloatMathPluginTests>>runTest: (in category 'running') -----
>   runTest: aBlock
>   	| bytes out float result |
>   	bytes := ByteArray new: 8.
>   	out := WriteStream on: ByteArray new.
>   	float := Float basicNew: 2.
>   	1 to: 10000 do:[:i|
> + 		[1 to: 8 do:[:j| bytes at: j put: (self nextInt: 256)-1].
> - 		[1 to: 8 do:[:j| bytes at: j put: (random nextInt: 256)-1].
>   		float basicAt: 1 put: (bytes unsignedLongAt: 1 bigEndian: true).
>   		float basicAt: 2 put: (bytes unsignedLongAt: 5 bigEndian: true).
>   		float isNaN] whileTrue.
>   		result := [aBlock value: float] on: Error do:[:ex|
>   			"we convert all errors into NaNs to have a value for testing"
>   			ex return: Float nan.
>   		].
>   		out nextNumber: 4 put: (result basicAt: 1).
>   		out nextNumber: 4 put: (result basicAt: 2).
>   	].
>   	^self md5HashMessage: out contents.!
> 
> Item was added:
> + ----- Method: FloatMathPluginTests>>seed: (in category 'rand') -----
> + seed: anInteger
> + 	seed := anInteger!
> 
> Item was changed:
>   ----- Method: FloatMathPluginTests>>setUp (in category 'running') -----
>   setUp
> + 	self seed: 253213.!
> - 	random := Random seed: 253213.!
> 
> Item was changed:
>   ----- Method: FloatMathPluginTests>>testTimesTwoPower (in category 'tests') -----
>   testTimesTwoPower
>   	| hash |
> + 	hash := self runTest:[:f| self timesTwoPower: f with: (self nextInt: 200) - 100].
> - 	hash := self runTest:[:f| self timesTwoPower: f with: (random nextInt: 200) - 100].
>   	self assert: hash = 278837335583284459890979576373223649870.!
> 
> Item was changed:
>   ----- Method: FloatMathPluginTests>>verifyTestData:using: (in category 'running') -----
>   verifyTestData: fileName using: aBlock
>   	| rounds seed bytes float result in expected count bits |
>   	in := [FileStream readOnlyFileNamed: fileName] 
>   			on: FileDoesNotExistException 
>   			do:[:ex| ex return: nil].
>   	in ifNil:[^nil].
>   	count := bits := 0.
>   	bytes := ByteArray new: 8.
>   	[
>   		in binary.
>   		rounds := in nextNumber: 4.
>   		seed := in nextNumber: 4.
> + 		self seed: seed.
> - 		random := Random seed: seed.
>   		float := Float basicNew: 2.
>   		expected := Float basicNew: 2.
>   		'Verifying test data from: ', fileName 
>   			displayProgressAt: Sensor cursorPoint 
>   			from: 1 to: rounds during:[:bar|
>   				1 to: rounds do:[:i|
>   					i \\ 10000 = 0 ifTrue:[bar value: i].
> + 					[1 to: 8 do:[:j| bytes at: j put: (self nextInt: 256)-1].
> - 					[1 to: 8 do:[:j| bytes at: j put: (random nextInt: 256)-1].
>   					float basicAt: 1 put: (bytes unsignedLongAt: 1 bigEndian: true).
>   					float basicAt: 2 put: (bytes unsignedLongAt: 5 bigEndian: true).
>   					float isNaN] whileTrue.
>   					result := aBlock value: float.
>   					expected basicAt: 1 put: (in nextNumber: 4).
>   					expected basicAt: 2 put: (in nextNumber: 4).
>   					((expected isNaN and:[result isNaN]) or:[expected = result]) ifFalse:[
>   						(expected basicAt: 1) = (result basicAt: 1)
>   							ifFalse:[self error: 'Verification failure'].
>   						count := count + 1.
>   						bits := bits + ((expected basicAt: 2) - (result basicAt: 2)) abs.
>   					].
>   				].
>   			].
>   	] ensure:[in close].
>   	self assert: count = 0. "all the same"!
> 


More information about the Vm-dev mailing list