[Vm-dev] VM Maker: VMMaker.oscog-eem.2296.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Dec 20 08:36:49 UTC 2017


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2296.mcz

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

Name: VMMaker.oscog-eem.2296
Author: eem
Time: 20 December 2017, 12:36:23.101265 am
UUID: e510f7d2-9ec9-4fa5-bee1-db1f59227058
Ancestors: VMMaker.oscog-eem.2295

Fix bugs in DoubleWordArray>>[unsigned]long64At:
 which failed to exclude extraneous bytes in the upper word of unaligned accesses.  These along with the fix to hackBits: in Graphics-eem.389 fix simulating 64-bit images in 64-bits, ensuring that the display is visible.

Add tests for hackBits: and signed access answering neghative values.  Fix a comment typo.

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

Item was changed:
  ----- Method: DoubleWordArray>>long64At: (in category '*VMMaker-JITSimulation') -----
  long64At: byteIndex
  	| lowBits wordIndex value high low |
  	wordIndex := byteIndex - 1 // 8 + 1.
  	(lowBits := byteIndex - 1 \\ 8) = 0
  		ifTrue:
  			[value := self at: wordIndex]
  		ifFalse:
+ 			[high := ((self at: wordIndex + 1) bitAnd: (1 bitShift: lowBits * 8) - 1) bitShift: 8 - lowBits * 8.
- 			[high := (self at: wordIndex + 1) bitShift: 8 - lowBits * 8.
  			 low := (self at: wordIndex) bitShift: lowBits * -8.
  			 high = 0 ifTrue:
  				[^low].
  			 value := high + low].
  	 ^(value bitShift: -56) <= 127
  		ifTrue: [value]
  		ifFalse: [value - 16r10000000000000000]!

Item was changed:
  ----- Method: DoubleWordArray>>unsignedLong64At: (in category '*VMMaker-JITSimulation') -----
  unsignedLong64At: byteIndex
  	"Compatiblity with the ByteArray & Alien methods of the same name."
  	| wordIndex lowBits high low |
  	wordIndex := byteIndex - 1 // 8 + 1.
  	(lowBits := byteIndex - 1 bitAnd: 7) = 0 ifTrue:
  		[^self at: wordIndex].
+ 	high := ((self at: wordIndex + 1) bitAnd: (1 bitShift: lowBits * 8) - 1) bitShift: 8 - lowBits * 8.
- 	high := (self at: wordIndex + 1) bitShift: 8 - lowBits * 8.
  	low := (self at: wordIndex) bitShift: lowBits * -8.
  	^high = 0 ifTrue: [low] ifFalse: [high + low]!

Item was changed:
  ----- Method: MemoryTests>>testLittleEndian32BitLongAccessFor: (in category 'test support') -----
  testLittleEndian32BitLongAccessFor: aClass
  	"Test that ByteArray provides big-endian access for 32-bit accessors"
  	"memory copy changeClassTo: ByteArray"
  	| memory |
  	memory := aClass new: 64 / (aClass new: 0) bytesPerElement.
  	"signed access"
  	0 to: 30 do:
  		[:shift|
  		#(-1 1) do:
  			[:initial| | value |
  			value := initial bitShift: shift.
  			memory longAt: 1 put: value.
  			self assert: value equals: (memory longAt: 1).
  			"aligned store"
  			memory
  				longAt: 5 put: 16r55550000;
  				longAt: 9 put: 16r00005555.
  			self assert: 16r55555555 equals: (memory longAt: 7).
  			memory longAt: 7 put: value.
  			self assert: value equals: (memory longAt: 7).
  			"check bytes either side have not been changed"
  			5 to: 6 do:
  				[:i| self assert: 0 equals: (memory byteAt: i)].
  			11 to: 15 do:
  				[:i| self assert: 0 equals: (memory byteAt: i)].
  			"unaligned store"
  			memory
  				longAt: 6 put: 16r55550000;
  				longAt: 10 put: 16r00005555.
  			self assert: 16r55555555 equals: (memory longAt: 8).
  			memory longAt: 8 put: value.
  			self assert: value equals: (memory longAt: 8).
  			"check bytes either side have not been changed"
  			5 to: 7 do:
  				[:i| self assert: 0 equals: (memory byteAt: i)].
  			12 to: 15 do:
  				[:i| self assert: 0 equals: (memory byteAt: i)]]].
+ 	memory
+ 		unsignedLongAt: 49 put: 16rAAAAAAAA;
+ 		unsignedLongAt: 53 put: 16rAAAAAAAA.
+ 	49 to: 52 do:
+ 		[:i|
+ 		 self assert: -1431655766 equals: (memory longAt: i)].
  	"unsigned access"
  	0 to: 31 do:
  		[:shift| | value |
  		value := 1 bitShift: shift.
  		memory unsignedLongAt: 1 put: value.
  		self assert: value equals: (memory unsignedLongAt: 1).
  		"aligned store"
  		memory
  			longAt: 5 put: 16r55550000;
  			longAt: 9 put: 16r00005555.
  		self assert: 16r55555555 equals: (memory unsignedLongAt: 7).
  		memory unsignedLongAt: 7 put: value.
  		self assert: value equals: (memory unsignedLongAt: 7).
  		"check bytes either side have not been changed"
  		5 to: 6 do:
  			[:i| self assert: 0 equals: (memory byteAt: i)].
  		11 to: 15 do:
  			[:i| self assert: 0 equals: (memory byteAt: i)].
  		"unaligned store"
  		memory
  			longAt: 6 put: 16r55550000;
  			longAt: 10 put: 16r00005555.
  		self assert: 16r55555555 equals: (memory unsignedLongAt: 8).
  		memory unsignedLongAt: 8 put: value.
  		self assert: value equals: (memory unsignedLongAt: 8).
  		"check bytes either side have not been changed"
  		5 to: 7 do:
  			[:i| self assert: 0 equals: (memory byteAt: i)].
  		12 to: 15 do:
  			[:i| self assert: 0 equals: (memory byteAt: i)]]!

Item was changed:
  ----- Method: MemoryTests>>testLittleEndian64BitLongAccessFor: (in category 'test support') -----
  testLittleEndian64BitLongAccessFor: aClass
  	"Test that the given class provides little-endian access for 64-bit accessors"
  	"memory copy changeClassTo: ByteArray"
  	| memory |
  	memory := aClass new: 64 / (aClass new: 0) bytesPerElement.
  	"signed access"
  	0 to: 62 do:
  		[:shift|
  		#(-1 1) do:
  			[:initial| | value |
  			value := initial bitShift: shift.
  			memory long64At: 1 put: value.
  			self assert: value equals: (memory long64At: 1).
  			"aligned store"
  			memory
  				long64At: 9 put: 16r5555550000000000;
  				long64At: 17 put: 16r0000005555555555.
  			self assert: 16r5555555555555555 equals: (memory long64At: 14).
  			memory long64At: 14 put: value.
  			self assert: value equals: (memory long64At: 14).
  			"check bytes either side have not been changed"
  			9 to: 13 do:
  				[:i| self assert: 0 equals: (memory byteAt: i)].
  			22 to: 31 do:
  				[:i| self assert: 0 equals: (memory byteAt: i)].
  			"unaligned store"
  			memory
  				long64At: 10 put: 16r5555550000000000;
  				long64At: 18 put: 16r0000005555555555.
  			self assert: 16r5555555555555555 equals: (memory long64At: 15).
  			memory long64At: 15 put: value.
  			self assert: value equals: (memory long64At: 15).
  			"check bytes either side have not been changed"
  			9 to: 14 do:
  				[:i| self assert: 0 equals: (memory byteAt: i)].
  			23 to: 31 do:
  				[:i| self assert: 0 equals: (memory byteAt: i)]]].
+ 	memory
+ 		unsignedLong64At: 49 put: 16rAAAAAAAAAAAAAAAA;
+ 		unsignedLong64At: 57 put: 16rAAAAAAAAAAAAAAAA.
+ 	49 to: 56 do:
+ 		[:i|
+ 		 self assert: -6148914691236517206 equals: (memory long64At: i)].
  	"unsigned access"
  	0 to: 63 do:
  		[:shift| | value |
  		value := 1 bitShift: shift.
  		memory unsignedLong64At: 1 put: value.
  		self assert: value equals: (memory unsignedLong64At: 1).
  		"aligned store"
  		memory
  			unsignedLong64At: 9 put: 16r5555550000000000;
  			unsignedLong64At: 17 put: 16r0000005555555555.
  		self assert: 16r5555555555555555 equals: (memory unsignedLong64At: 14).
  		memory unsignedLong64At: 14 put: value.
  		self assert: value equals: (memory unsignedLong64At: 14).
  		"check bytes either side have not been changed"
  		9 to: 13 do:
  			[:i| self assert: 0 equals: (memory byteAt: i)].
  		22 to: 31 do:
  			[:i| self assert: 0 equals: (memory byteAt: i)].
  		"unaligned store"
  		memory
  			unsignedLong64At: 10 put: 16r5555550000000000;
  			unsignedLong64At: 18 put: 16r0000005555555555.
  		self assert: 16r5555555555555555 equals: (memory unsignedLong64At: 15).
  		memory unsignedLong64At: 15 put: value.
  		self assert: value equals: (memory unsignedLong64At: 15).
  		"check bytes either side have not been changed"
  		9 to: 14 do:
  			[:i| self assert: 0 equals: (memory byteAt: i)].
  		23 to: 31 do:
  			[:i| self assert: 0 equals: (memory byteAt: i)]]!

Item was changed:
  ----- Method: Spur64BitMMLESimulatorFor64Bits>>long64At: (in category 'memory access') -----
  long64At: byteAddress
+ 	"memory is a DoubleWordArray, a 64-bit indexable array of bits"
- 	"memory is a DobleWordArray, a 64-bit indexable array of bits"
  	byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
  	^memory at: byteAddress // 8 + 1!

Item was added:
+ ----- Method: StackInterpreterSimulatorTests>>testHackBits (in category 'tests') -----
+ testHackBits
+ 	"Test that the hackBits plumbing, used for display update in the
+ 	 simulated ioShow:D:i:s:p:l:a:y:, works for the underlying memory classes."
+ 	| mem32 mem64 disp32 disp64 hack32 hack64 |
+ 	mem32 := LittleEndianBitmap new: 65536 / 4.
+ 	mem64 := DoubleWordArray new: 65536 / 8.
+ 	1 to: 65536 by: 8 do:
+ 		[:i|
+ 		mem32
+ 			unsignedLong64At: i
+ 			put: ((i // 8) even
+ 					ifTrue: [16r5555555555555555]
+ 					ifFalse: [16rAAAAAAAAAAAAAAAA]).
+ 		mem64
+ 			unsignedLong64At: i
+ 			put: ((i // 8) even
+ 					ifTrue: [16r5555555555555555]
+ 					ifFalse: [16rAAAAAAAAAAAAAAAA])].
+ 	self assert: (mem32 copy changeClassTo: ByteArray) = (mem64 copy changeClassTo: ByteArray).
+ 	hack32 := Form new hackBits: mem32.
+ 	hack64 := Form new hackBits: mem64.
+ 	disp32 := Form new hackBits: (ByteArray new: 65536).
+ 	disp64 := Form new hackBits: (ByteArray new: 65536).
+ 	disp32
+ 		copy: (0 @ 0 extent: 4 @ (65536 / 4))
+ 		from: 0 @ 0
+ 		in: hack32
+ 		rule: Form over.
+ 	disp64
+ 		copy: (0 @ 0 extent: 4 @ (65536 / 4))
+ 		from: 0 @ 0
+ 		in: hack64
+ 		rule: Form over.
+ 	1 to: 65536 by: 8 do:
+ 		[:i|
+ 		self assert: ((i // 8) even
+ 						ifTrue: [16r5555555555555555]
+ 						ifFalse: [16rAAAAAAAAAAAAAAAA])
+ 			equals: (disp32 bits unsignedLong64At: i).
+ 		self assert: ((i // 8) even
+ 						ifTrue: [16r5555555555555555]
+ 						ifFalse: [16rAAAAAAAAAAAAAAAA])
+ 			equals: (disp64 bits unsignedLong64At: i)]
+ 	!



More information about the Vm-dev mailing list