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

commits at source.squeak.org commits at source.squeak.org
Thu Feb 10 18:40:34 UTC 2022


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

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

Name: VMMaker.oscog-eem.3150
Author: eem
Time: 10 February 2022, 10:40:21.847379 am
UUID: 832f44e4-6d22-4545-ae94-d8453b49d54f
Ancestors: VMMaker.oscog-eem.3149

Spur CoInterpreter: further cleanup of primitive property flags computation.

Fix null-pointer accesses in StackInterpreterTests>>testXXXMemoryAccess tests.

Fix two tests in IncludedMethodsTest. Add error codes to the primitives.

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

Item was changed:
  ----- Method: CoInterpreter>>functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: (in category 'cog jit support') -----
  functionPointerForCompiledMethod: methodObj primitiveIndex: primitiveIndex primitivePropertyFlagsInto: flagsPtr
  	<api>
  	<returnTypeC: 'void (*functionPointerForCompiledMethodprimitiveIndexprimitivePropertyFlagsInto(sqInt methodObj, sqInt primitiveIndex, sqInt *flagsPtr))(void)'>
+ 	<inline: false>
+ 	| flags |
- 	| functionPointer flags |
- 	<var: #functionPointer declareC: #'void (*functionPointer)(void)'>
  	flagsPtr ifNotNil:
  		[flagsPtr at: 0 put: (flags := self primitivePropertyFlags: primitiveIndex numArgs: (self argumentCountOf: methodObj))].
+ 	primitiveIndex == PrimNumberFFICall ifTrue:
- 	functionPointer := self functionPointerFor: primitiveIndex inClass: nil.
- 	functionPointer == #primitiveCalloutToFFI ifTrue:
  		[^self functionForPrimitiveCallout].
+ 	primitiveIndex == PrimNumberExternalCall ifTrue:
- 	functionPointer == #primitiveExternalCall ifTrue:
  		[| lit |
  		 lit := self attemptToLinkExternalPrimitive: methodObj.
  		 flagsPtr ifNotNil:
+ 			["N.B. We only support the FastCPrimitiveFlag on Spur because Spur will not run a GC to
+ 			  satisfy an allocation in a primitive. The V3 ObjectMemory will and hence the depth of
+ 			  stack needed in a V3 primitive is probably too large to safely execute on a stack page."
+ 			 objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 				[| metadata metadataFlags |
+ 				 metadata := objectMemory fetchPointer: ExternalCallLiteralFlagsIndex ofObject: lit.
+ 			 	 (objectMemory isIntegerObject: metadata) ifTrue:
+ 					[metadataFlags := (objectMemory integerValueOf: metadata) bitAnd: SpurPrimitiveFlagsMask.
+ 					 "combine the specific external primitive's flags with the base flags.
+ 					  Hence e.g. if profiling is in effect (as indicated by PrimCallCollectsProfileSamples
+ 					  in the base flags) it remains in effect after combining the specific flags."
+ 					 flags := flags bitOr: metadataFlags]].
+ 			 (self externalCallLiteralModuleIsVM: lit) ifTrue:
+ 				[flags := flags bitOr: PrimCallIsInternalPrim].
- 			 ["N.B. We only support the FastCPrimitiveFlag on Spur because Spur
- 			  will *not* run a GC to satisfy an allocation in a primitive. The V3
- 			  ObjectMemory will and hence the depth of stack needed in a V3
- 			  primitive is probably too large to safely execute on a stack page."
- 			  objectMemory hasSpurMemoryManagerAPI ifTrue:
- 				[| metadataFlags shiftedMetadataFlags |
- 				 metadataFlags := objectMemory fetchPointer: ExternalCallLiteralFlagsIndex ofObject: lit.
- 			 	 (objectMemory isIntegerObject: metadataFlags) ifTrue:
- 					[shiftedMetadataFlags := (objectMemory integerValueOf: metadataFlags)
- 												bitAnd: SpurPrimitiveFlagsMask.
- 					 shiftedMetadataFlags > 0 ifTrue:
- 						["Intentionally clear all other flags if there are Spur metadata flags..."
- 						 flags := shiftedMetadataFlags].
- 					 (self externalCallLiteralModuleIsVM: lit) ifTrue:
- 						[flags := flags bitOr: PrimCallIsInternalPrim]]].
- 			 (self object: (objectMemory fetchPointer: ExternalCallLiteralTargetFunctionIndex ofObject: lit)
- 					equalsString: 'primitiveProfileSemaphore') ifTrue:
- 				[flags := flags bitOr: PrimCallMayEndureCodeCompaction].
- 			 profileSemaphore ~= objectMemory nilObject ifTrue:
- 				[flags := flags bitOr: PrimCallCollectsProfileSamples].
  			 flagsPtr at: 0 put: flags].
  		 ^self functionForPrimitiveExternalCall: methodObj].
+ 	^self functionPointerFor: primitiveIndex inClass: nil!
- 	^functionPointer!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveProfileSemaphore (in category 'process primitives') -----
  primitiveProfileSemaphore
  	"Primitive. Install the semaphore to be used for profiling, 
  	or nil if no semaphore should be used.
  	See also primitiveProfileStart."
- 	| sema flushState |
  	<export: true>
+ 	<primitiveMetadata: #PrimCallMayEndureCodeCompaction>
+ 	| sema flushState |
  	sema := self stackValue: 0.
  	sema = objectMemory nilObject
  		ifTrue:
  			[flushState := profileSemaphore ~= objectMemory nilObject]
  		ifFalse:
  			[flushState := profileSemaphore = objectMemory nilObject.
  			 (objectMemory isSemaphoreOop: sema) ifFalse:
  				[^self primitiveFailFor: PrimErrBadArgument]].
  	profileSemaphore := sema.
  	profileProcess := profileMethod := objectMemory nilObject.
  	"If we've switched profiling on or off we must void machine code
  	 (and machine code pcs in contexts) since we will start or stop
  	 testing the profile clock in machine code primitive invocations,
  	 and so generate slightly different code from here on in."
  	flushState
  		ifTrue: [self flushExternalPrimitives]
  		ifFalse: [self methodReturnReceiver]!

Item was changed:
  ----- Method: CogVMSimulator>>initStackPagesForTests (in category 'test support') -----
  initStackPagesForTests
  	numStackPages := 8.
- 	stackPages := self stackPagesClass new.
  	objectMemory allocateMemoryOfSize: 1024 * 1024.
+ 	cogCodeSize := effectiveCogCodeSize := 0.
- 	cogCodeSize := 0.
  	heapBase := self methodCacheSize
  				+ self primTraceLogSize
  				+ self rumpCStackSize
  				+ self computeStackZoneSize.
+ 	cogit instVarNamed: 'codeBase' put: 0.
  	self initStackPages!

Item was changed:
  ----- Method: FullSimulationTest>>testSimulate2MillionBytecodes (in category 'as yet unclassified') -----
  testSimulate2MillionBytecodes
  	<timeout: 120>
  	| vm om |
  	vm := StackInterpreterSimulator newWithOptions: (Smalltalk isRunningSpur
  		ifTrue: [Smalltalk wordSize = 4
+ 			ifTrue: [#(#ObjectMemory #Spur32BitMemoryManager MULTIPLEBYTECODESETS true)]
+ 			ifFalse: [#(#ObjectMemory #Spur64BitMemoryManager MULTIPLEBYTECODESETS true)]]
- 			ifTrue: [#(#ObjectMemory #Spur32BitMemoryManager )]
- 			ifFalse: [#(#ObjectMemory #Spur64BitMemoryManager )]]
  		ifFalse: [#(#ObjectMemory)]).
  	om := vm objectMemory.
  	vm desiredNumStackPages: 8. "Makes simulation faster by creating fewer stack pages."
  	vm openOn: Smalltalk imageName.
  	vm instVarNamed: 'assertVEPAES' put: false. "This makes the simulation faster by turning off some expensive asserts"
  	[[vm runForNBytes: 1500000]
  		on: Halt , ProvideAnswerNotification "This exception handler ignores some halts and confirmers occurring during simulation"
  		do: [:ex | 
  			ex messageText == #primitiveExecuteMethodArgsArray
  				ifTrue: [ex resume].
  			ex messageText = 'clear transcript?'
  				ifTrue: [ex resume: false].
  			ex pass]] ensure: [Display restore].!

Item was changed:
  ----- Method: IncludedMethodsTest>>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' error: ec>
- 	<primitive: 'primitiveCompareString' module: 'MiscPrimitivePlugin'>
  	self primitiveFailed
  !

Item was changed:
  ----- Method: IncludedMethodsTest>>compress:toByteArray: (in category 'primitives') -----
  compress: bm toByteArray: ba
  
+ 	<primitive: 'primitiveCompressToByteArray' module: 'MiscPrimitivePlugin' error: ec>
- 	<primitive: 'primitiveCompressToByteArray' module: 'MiscPrimitivePlugin'>
  	self primitiveFailed!

Item was changed:
  ----- Method: IncludedMethodsTest>>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' error: ec>
- 	<primitive: 'primitiveConvert8BitSigned' module: 'MiscPrimitivePlugin'>
  	self primitiveFailed
  !

Item was changed:
  ----- Method: IncludedMethodsTest>>decompress:fromByteArray:at: (in category 'primitives') -----
  decompress: bm fromByteArray: ba at: index
  
+ 	<primitive: 'primitiveDecompressFromByteArray' module: 'MiscPrimitivePlugin' error: ec>
- 	<primitive: 'primitiveDecompressFromByteArray' module: 'MiscPrimitivePlugin'>
  	self primitiveFailed
  !

Item was changed:
  ----- Method: IncludedMethodsTest>>findFirstInString:inSet:startingAt: (in category 'primitives') -----
  findFirstInString: aString  inSet: inclusionMap  startingAt: start
  
+ 	<primitive: 'primitiveFindFirstInString' module: 'MiscPrimitivePlugin' error: ec>
- 	<primitive: 'primitiveFindFirstInString' module: 'MiscPrimitivePlugin'>
  	self primitiveFailed
  !

Item was changed:
  ----- Method: IncludedMethodsTest>>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' error: ec>
- 	<primitive: 'primitiveFindSubstring' module: 'MiscPrimitivePlugin'>
  	self primitiveFailed
  !

Item was changed:
  ----- Method: IncludedMethodsTest>>indexOfAscii:inString:startingAt: (in category 'primitives') -----
  indexOfAscii: anInteger inString: aString startingAt: start
  
+ 	<primitive: 'primitiveIndexOfAsciiInString' module: 'MiscPrimitivePlugin' error: ec>
- 	<primitive: 'primitiveIndexOfAsciiInString' module: 'MiscPrimitivePlugin'>
  	self primitiveFailed
  !

Item was changed:
  ----- Method: IncludedMethodsTest>>mixSampleCount:into:startingAt:leftVol:rightVol: (in category 'primitives') -----
  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' error: ec>
- 	<primitive:'primitiveMixFMSound' module:'SoundGenerationPlugin'>
  	self primitiveFailed
  !

Item was changed:
  ----- Method: IncludedMethodsTest>>testCompressToByteArray (in category 'testing - MiscPrimitivePlugin') -----
  testCompressToByteArray
  
  	| bitmap byteArray |
  	bitmap := Bitmap with: 16rFFFFFFFF.
+ 	byteArray := ByteArray new: 12. "minimum size given by (bitmap size * 4) + 7 + (bitmap size // 1984 * 3)"
- 	byteArray := ByteArray new:  4.
  	self compress: bitmap toByteArray: byteArray.
+ 	self should: byteArray = #[1 5 255 0 0 0 0 0 0 0 0 0]!
- 	self should: byteArray = #[1 5 255 0]!

Item was changed:
  ----- Method: IncludedMethodsTest>>testTranslateFromToTable (in category 'testing - MiscPrimitivePlugin') -----
  testTranslateFromToTable
  	"Verify that primitive exists in the VM"
  
  	| s t |
  	s := 'foo' copy. "copy so string is instantiated each time"
+ 	t := (1 to: 255), #(0) as: ByteArray.
- 	t := ByteArray withAll: ((1 to: 255) as: ByteArray).
  	self translate: s from: 1 to: 3 table: t.
  	self assert: s = 'gpp'
  !

Item was changed:
  ----- Method: IncludedMethodsTest>>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' error: ec>
- 	<primitive: 'primitiveTranslateStringWithTable' module: 'MiscPrimitivePlugin'>
  	self primitiveFailed!

Item was added:
+ ----- Method: PrintfFormatStringTest class>>expectedFailures (in category '*VMMaker-anomalies') -----
+ expectedFailures
+ 	"VMMaker redefined %P to mean ``print a pointer in capitals'', according to modern printf implementations.  This breaks the use of %P as ``print a Point''"
+ 	^#(testOnePrintString)!

Item was changed:
  ----- Method: StackInterpreterTests>>testByteMemoryAccess (in category 'tests') -----
  testByteMemoryAccess
  	"self new testByteMemoryAccess"
  	| om |
  	om := NewCoObjectMemorySimulator new allocateMemoryOfSize: 16.
  	om byteAt: 0 put: 16r11.
  	om byteAt: 1 put: 16r22.
  	om byteAt: 2 put: 16r33.
  	om byteAt: 3 put: 16r44.
  	self assert: (om longAt: 0) equals: 16r44332211.
  	self assert: (om byteAt: 0) equals: 16r11.
  	self assert: (om byteAt: 1) equals: 16r22.
  	self assert: (om byteAt: 2) equals: 16r33.
  	self assert: (om byteAt: 3) equals: 16r44.
  	om := Spur32BitMMLECoSimulator new allocateMemoryOfSize: 16.
+ 	self should: [om byteAt: 0 put: 16r11] raise: Error.
+ 	om byteAt: 4 put: 16r11.
+ 	om byteAt: 5 put: 16r22.
+ 	om byteAt: 6 put: 16r33.
+ 	om byteAt: 7 put: 16r44.
+ 	self should: [om longAt: 0] raise: Error.
+ 	self assert: (om longAt: 4) equals: 16r44332211.
+ 	self assert: (om byteAt: 4) equals: 16r11.
+ 	self assert: (om byteAt: 5) equals: 16r22.
+ 	self assert: (om byteAt: 6) equals: 16r33.
+ 	self assert: (om byteAt: 7) equals: 16r44.
- 	om byteAt: 0 put: 16r11.
- 	om byteAt: 1 put: 16r22.
- 	om byteAt: 2 put: 16r33.
- 	om byteAt: 3 put: 16r44.
- 	self assert: (om longAt: 0) equals: 16r44332211.
- 	self assert: (om byteAt: 0) equals: 16r11.
- 	self assert: (om byteAt: 1) equals: 16r22.
- 	self assert: (om byteAt: 2) equals: 16r33.
- 	self assert: (om byteAt: 3) equals: 16r44.
  	om := Spur64BitMMLECoSimulator new allocateMemoryOfSize: 32.
+ 	self should: [om byteAt: 0 put: 16r11] raise: Error.
+ 	om byteAt: 8 put: 16r11.
+ 	om byteAt: 9 put: 16r22.
+ 	om byteAt: 10 put: 16r33.
+ 	om byteAt: 11 put: 16r44.
+ 	om byteAt: 12 put: 16r55.
+ 	om byteAt: 13 put: 16r66.
+ 	om byteAt: 14 put: 16r77.
+ 	om byteAt: 15 put: 16r88.
+ 	self should: [om longAt: 0] raise: Error.
+ 	self assert: (om longAt: 8) equals: 16r8877665544332211.
+ 	self assert: (om byteAt: 8) equals: 16r11.
+ 	self assert: (om byteAt: 9) equals: 16r22.
+ 	self assert: (om byteAt: 10) equals: 16r33.
+ 	self assert: (om byteAt: 11) equals: 16r44.
+ 	self assert: (om byteAt: 12) equals: 16r55.
+ 	self assert: (om byteAt: 13) equals: 16r66.
+ 	self assert: (om byteAt: 14) equals: 16r77.
+ 	self assert: (om byteAt: 15) equals: 16r88.
- 	om byteAt: 0 put: 16r11.
- 	om byteAt: 1 put: 16r22.
- 	om byteAt: 2 put: 16r33.
- 	om byteAt: 3 put: 16r44.
- 	om byteAt: 4 put: 16r55.
- 	om byteAt: 5 put: 16r66.
- 	om byteAt: 6 put: 16r77.
- 	om byteAt: 7 put: 16r88.
- 	self assert: (om longAt: 0) equals: 16r8877665544332211.
- 	self assert: (om byteAt: 0) equals: 16r11.
- 	self assert: (om byteAt: 1) equals: 16r22.
- 	self assert: (om byteAt: 2) equals: 16r33.
- 	self assert: (om byteAt: 3) equals: 16r44.
- 	self assert: (om byteAt: 4) equals: 16r55.
- 	self assert: (om byteAt: 5) equals: 16r66.
- 	self assert: (om byteAt: 6) equals: 16r77.
- 	self assert: (om byteAt: 7) equals: 16r88.
  	(Smalltalk classNamed: #DoubleWordArray) ifNotNil:
  		[om := Spur64BitMMLECoSimulatorFor64Bits new allocateMemoryOfSize: 32.
+ 		 self should: [om byteAt: 0 put: 16r11] raise: Error.
+ 		 om byteAt: 8 put: 16r11.
+ 		 om byteAt: 9 put: 16r22.
+ 		 om byteAt: 10 put: 16r33.
+ 		 om byteAt: 11 put: 16r44.
+ 		 om byteAt: 12 put: 16r55.
+ 		 om byteAt: 13 put: 16r66.
+ 		 om byteAt: 14 put: 16r77.
+ 		 om byteAt: 15 put: 16r88.
+ 		 self should: [om longAt: 0] raise: Error.
+ 		 self assert: (om longAt: 8) equals: 16r8877665544332211.
+ 		 self assert: (om byteAt: 8) equals: 16r11.
+ 		 self assert: (om byteAt: 9) equals: 16r22.
+ 		 self assert: (om byteAt: 10) equals: 16r33.
+ 		 self assert: (om byteAt: 11) equals: 16r44.
+ 		 self assert: (om byteAt: 12) equals: 16r55.
+ 		 self assert: (om byteAt: 13) equals: 16r66.
+ 		 self assert: (om byteAt: 14) equals: 16r77.
+ 		 self assert: (om byteAt: 15) equals: 16r88]!
- 		 om byteAt: 0 put: 16r11.
- 		 om byteAt: 1 put: 16r22.
- 		 om byteAt: 2 put: 16r33.
- 		 om byteAt: 3 put: 16r44.
- 		 om byteAt: 4 put: 16r55.
- 		 om byteAt: 5 put: 16r66.
- 		 om byteAt: 6 put: 16r77.
- 		 om byteAt: 7 put: 16r88.
- 		 self assert: (om longAt: 0) equals: 16r8877665544332211.
- 		 self assert: (om byteAt: 0) equals: 16r11.
- 		 self assert: (om byteAt: 1) equals: 16r22.
- 		 self assert: (om byteAt: 2) equals: 16r33.
- 		 self assert: (om byteAt: 3) equals: 16r44.
- 		 self assert: (om byteAt: 4) equals: 16r55.
- 		 self assert: (om byteAt: 5) equals: 16r66.
- 		 self assert: (om byteAt: 6) equals: 16r77.
- 		 self assert: (om byteAt: 7) equals: 16r88]!

Item was changed:
  ----- Method: StackInterpreterTests>>testShortMemoryAccess (in category 'tests') -----
  testShortMemoryAccess
  	"self new testShortMemoryAccess"
  	| om |
  	om := NewCoObjectMemorySimulator new allocateMemoryOfSize: 16.
  	om shortAt: 0 put: 16r2211.
  	om shortAt: 2 put: 16r4433.
  	self assert: (om longAt: 0) equals: 16r44332211.
  	self assert: (om shortAt: 0) equals: 16r2211.
  	self assert: (om shortAt: 2) equals: 16r4433.
  	om := Spur32BitMMLECoSimulator new allocateMemoryOfSize: 16.
+ 	self should: [om shortAt: 0 put: 16r2211] raise: Error.
+ 	om shortAt: 4 put: 16r2211.
+ 	om shortAt: 6 put: 16r4433.
+ 	self should: [om shortAt: 0] raise: Error.
+ 	self assert: (om longAt: 4) equals: 16r44332211.
+ 	self assert: (om shortAt: 4) equals: 16r2211.
+ 	self assert: (om shortAt: 6) equals: 16r4433.
- 	om shortAt: 0 put: 16r2211.
- 	om shortAt: 2 put: 16r4433.
- 	self assert: (om longAt: 0) equals: 16r44332211.
- 	self assert: (om shortAt: 0) equals: 16r2211.
- 	self assert: (om shortAt: 2) equals: 16r4433.
  	om := Spur64BitMMLECoSimulator new allocateMemoryOfSize: 32.
+ 	self should: [om shortAt: 0 put: 16r2211] raise: Error.
+ 	om shortAt: 8 put: 16r2211.
+ 	om shortAt: 10 put: 16r4433.
+ 	om shortAt: 12 put: 16r6655.
+ 	om shortAt: 14 put: 16r8877.
+ 	self should: [om shortAt: 0] raise: Error.
+ 	self assert: (om longAt: 8) equals: 16r8877665544332211.
+ 	self assert: (om shortAt: 8) equals: 16r2211.
+ 	self assert: (om shortAt: 10) equals: 16r4433.
+ 	self assert: (om shortAt: 12) equals: 16r6655.
+ 	self assert: (om shortAt: 14) equals: 16r8877.
- 	om shortAt: 0 put: 16r2211.
- 	om shortAt: 2 put: 16r4433.
- 	om shortAt: 4 put: 16r6655.
- 	om shortAt: 6 put: 16r8877.
- 	self assert: (om longAt: 0) equals: 16r8877665544332211.
- 	self assert: (om shortAt: 0) equals: 16r2211.
- 	self assert: (om shortAt: 2) equals: 16r4433.
- 	self assert: (om shortAt: 4) equals: 16r6655.
- 	self assert: (om shortAt: 6) equals: 16r8877.
  	(Smalltalk classNamed: #DoubleWordArray) ifNotNil:
  		[om := Spur64BitMMLECoSimulatorFor64Bits new allocateMemoryOfSize: 32.
+ 		 self should: [om shortAt: 0 put: 16r2211] raise: Error.
+ 		 om shortAt: 8 put: 16r2211.
+ 		 om shortAt: 10 put: 16r4433.
+ 		 om shortAt: 12 put: 16r6655.
+ 		 om shortAt: 14 put: 16r8877.
+ 		 self should: [om shortAt: 0] raise: Error.
+ 		 self assert: (om longAt: 8) equals: 16r8877665544332211.
+ 		 self assert: (om shortAt: 8) equals: 16r2211.
+ 		 self assert: (om shortAt: 10) equals: 16r4433.
+ 		 self assert: (om shortAt: 12) equals: 16r6655.
+ 		 self assert: (om shortAt: 14) equals: 16r8877]!
- 		 om shortAt: 0 put: 16r2211.
- 		 om shortAt: 2 put: 16r4433.
- 		 om shortAt: 4 put: 16r6655.
- 		 om shortAt: 6 put: 16r8877.
- 		 self assert: (om longAt: 0) equals: 16r8877665544332211.
- 		 self assert: (om shortAt: 0) equals: 16r2211.
- 		 self assert: (om shortAt: 2) equals: 16r4433.
- 		 self assert: (om shortAt: 4) equals: 16r6655.
- 		 self assert: (om shortAt: 6) equals: 16r8877]!

Item was changed:
  ----- Method: StackInterpreterTests>>testUnalignedMemoryAccess (in category 'tests') -----
  testUnalignedMemoryAccess
  	"self new testUnalignedMemoryAccess"
  	| om |
  	om := NewCoObjectMemorySimulator new allocateMemoryOfSize: 16.
  	om unalignedLongAt: 1 put: 16r11223344.
  	self assert: (om unalignedLongAt: 0) equals: 16r22334400.
  	self assert: (om unalignedLongAt: 4) equals: 16r11.
  	self assert: (om unalignedLongAt: 1) equals: 16r11223344.
  	om longAt: 0 put: 16rAAAAAAAA.
  	om longAt: 4 put: 16rAAAAAAAA.
  	om unalignedLongAt: 1 put: 16r11223344.
  	self assert: (om unalignedLongAt: 0) equals: 16r223344AA.
  	self assert: (om unalignedLongAt: 4) equals: 16rAAAAAA11.
  	self assert: (om unalignedLongAt: 1) equals: 16r11223344.
  	om := Spur32BitMMLECoSimulator new allocateMemoryOfSize: 16.
+ 	om unalignedLongAt: 7 put: 16r11223344.
+ 	self assert: (om unalignedLongAt: 4) equals: 16r44000000.
+ 	self assert: (om unalignedLongAt: 8) equals: 16r112233.
+ 	self assert: (om unalignedLongAt: 7) equals: 16r11223344.
- 	om unalignedLongAt: 3 put: 16r11223344.
- 	self assert: (om unalignedLongAt: 0) equals: 16r44000000.
- 	self assert: (om unalignedLongAt: 4) equals: 16r112233.
- 	self assert: (om unalignedLongAt: 3) equals: 16r11223344.
- 	om longAt: 0 put: 16rAAAAAAAA.
  	om longAt: 4 put: 16rAAAAAAAA.
+ 	om longAt: 8 put: 16rAAAAAAAA.
+ 	om unalignedLongAt: 7 put: 16r11223344.
+ 	self assert: (om unalignedLongAt: 4) equals: 16r44AAAAAA.
+ 	self assert: (om unalignedLongAt: 8) equals: 16rAA112233.
+ 	self assert: (om unalignedLongAt: 7) equals: 16r11223344.
- 	om unalignedLongAt: 3 put: 16r11223344.
- 	self assert: (om unalignedLongAt: 0) equals: 16r44AAAAAA.
- 	self assert: (om unalignedLongAt: 4) equals: 16rAA112233.
- 	self assert: (om unalignedLongAt: 3) equals: 16r11223344.
  	om := Spur64BitMMLECoSimulator new allocateMemoryOfSize: 32.
+ 	om unalignedLongAt: 11 put: 16r1122334455667788.
+ 	self assert: (om unalignedLongAt: 8) equals: 16r4455667788000000.
+ 	self assert: (om unalignedLongAt: 16) equals: 16r112233.
+ 	self assert: (om unalignedLongAt: 11) equals: 16r1122334455667788.
- 	om unalignedLongAt: 3 put: 16r1122334455667788.
- 	self assert: (om unalignedLongAt: 0) equals: 16r4455667788000000.
- 	self assert: (om unalignedLongAt: 8) equals: 16r112233.
- 	self assert: (om unalignedLongAt: 3) equals: 16r1122334455667788.
- 	om longAt: 0 put: 16rAAAAAAAAAAAAAAAA.
  	om longAt: 8 put: 16rAAAAAAAAAAAAAAAA.
+ 	om longAt: 16 put: 16rAAAAAAAAAAAAAAAA.
+ 	om unalignedLongAt: 11 put: 16r1122334455667788.
+ 	self assert: (om unalignedLongAt: 8) equals: 16r4455667788AAAAAA.
+ 	self assert: (om unalignedLongAt: 16) equals: 16rAAAAAAAAAA112233.
+ 	self assert: (om unalignedLongAt: 11) equals: 16r1122334455667788.
- 	om unalignedLongAt: 3 put: 16r1122334455667788.
- 	self assert: (om unalignedLongAt: 0) equals: 16r4455667788AAAAAA.
- 	self assert: (om unalignedLongAt: 8) equals: 16rAAAAAAAAAA112233.
- 	self assert: (om unalignedLongAt: 3) equals: 16r1122334455667788.
  	(Smalltalk classNamed: #DoubleWordArray) ifNotNil:
  		[om := Spur64BitMMLECoSimulatorFor64Bits new allocateMemoryOfSize: 32.
+ 		 om unalignedLongAt: 11 put: 16r1122334455667788.
+ 		 self assert: (om unalignedLongAt: 8) equals: 16r4455667788000000.
+ 		 self assert: (om unalignedLongAt: 16) equals: 16r112233.
+ 		 self assert: (om unalignedLongAt: 11) equals: 16r1122334455667788.
- 		 om unalignedLongAt: 3 put: 16r1122334455667788.
- 		 self assert: (om unalignedLongAt: 0) equals: 16r4455667788000000.
- 		 self assert: (om unalignedLongAt: 8) equals: 16r112233.
- 		 self assert: (om unalignedLongAt: 3) equals: 16r1122334455667788.
- 		 om longAt: 0 put: 16rAAAAAAAAAAAAAAAA.
  		 om longAt: 8 put: 16rAAAAAAAAAAAAAAAA.
+ 		 om longAt: 16 put: 16rAAAAAAAAAAAAAAAA.
+ 		 om unalignedLongAt: 11 put: 16r1122334455667788.
+ 		 self assert: (om unalignedLongAt: 8) equals: 16r4455667788AAAAAA.
+ 		 self assert: (om unalignedLongAt: 16) equals: 16rAAAAAAAAAA112233.
+ 		 self assert: (om unalignedLongAt: 11) equals: 16r1122334455667788]!
- 		 om unalignedLongAt: 3 put: 16r1122334455667788.
- 		 self assert: (om unalignedLongAt: 0) equals: 16r4455667788AAAAAA.
- 		 self assert: (om unalignedLongAt: 8) equals: 16rAAAAAAAAAA112233.
- 		 self assert: (om unalignedLongAt: 3) equals: 16r1122334455667788]!



More information about the Vm-dev mailing list