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

commits at source.squeak.org commits at source.squeak.org
Sat Nov 19 18:01:14 UTC 2016


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

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

Name: VMMaker.oscog-eem.1996
Author: eem
Time: 19 November 2016, 10:00:32.110085 am
UUID: 5494face-981d-4da2-bb0a-d10df419ec65
Ancestors: VMMaker.oscog-eem.1995

Simulation:
Add support for 64-bit simulation using DoubleWordArray as the memroy class.

Rewrite the byte and short accessors to use arithmetic rather than caseOf:.

Move write-protect and convertToArray memory access into the Objectmemory classes out of StackInterpreter.

Provide a cCoerceSimple:to: to allow the LargeIntegersPlugin to simulate.

Provide memory tests for short and byte access in the object memory simulators.

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

Item was removed:
- ----- Method: CogVMSimulator>>convertToArray (in category 'initialization') -----
- convertToArray
- 	"This won't work for the Cog VM because the processor simulators need raw bytes for the memory."
- 	
- 	self shouldNotImplement!

Item was changed:
  ----- Method: CogVMSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"CogVMSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
  	  headerFlags firstSegSize heapSize
  	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize
  	  hdrCogCodeSize stackZoneSize methodCacheSize primTraceLogSize allocationReserve |
  	"open image file and read the header"
  
  	f := FileStream readOnlyFileNamed: fileName.
  	f ifNil: [^self error: 'no image found'].
  
  	"Set the image name and the first argument; there are
  	 no arguments during simulation unless set explicitly."
  	systemAttributes at: 1 put: fileName; at: 2 put: nil.
  
  	["begin ensure block..."
  	imageName := f fullName.
  	f binary.
  
  	version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := version byteSwap32) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getWord32FromFile: f swap: swapBytes.
  	dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	stackZoneSize := self computeStackZoneSize.
  	"This slot holds the size of the native method zone in 1k units. (pad to word boundary)."
  	hdrCogCodeSize := (self getShortFromFile: f swap: swapBytes) * 1024.
  	cogCodeSize := desiredCogCodeSize ~= 0
  						ifTrue: [desiredCogCodeSize]
  						ifFalse:
  							[hdrCogCodeSize = 0
  									ifTrue: [cogit defaultCogCodeSize]
  									ifFalse: [hdrCogCodeSize]].
  	desiredCogCodeSize := hdrCogCodeSize.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
  	hdrEdenBytes	:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (desiredEdenBytes ~= 0
  						ifTrue: [desiredEdenBytes]
  						ifFalse:
  							[hdrEdenBytes = 0
  									ifTrue: [objectMemory defaultEdenBytes]
  									ifFalse: [hdrEdenBytes]]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]).
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"For Open PICs to be able to probe the method cache during
  	 simulation the methodCache must be relocated to memory."
  	methodCacheSize := methodCache size * objectMemory wordSize.
  	primTraceLogSize := primTraceLog size * objectMemory wordSize.
  	"allocate interpreter memory. This list is in address order, low to high.
  	 In the actual VM the stack zone exists on the C stack."
  	heapBase := (Cogit guardPageSize
  				+ cogCodeSize
  				+ stackZoneSize
  				+ methodCacheSize
  				+ primTraceLogSize
  				+ self rumpCStackSize) roundUpTo: objectMemory allocationUnit.
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
  						   dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  dataSize
  						+ extraBytes
  						+ objectMemory newSpaceBytes
  						+ (extraBytes > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])].
  	heapBase := objectMemory
  					setHeapBase: heapBase
  					memoryLimit:  heapBase + heapSize
  					endOfMemory: heapBase + dataSize.
  
  	self assert: cogCodeSize \\ 4 = 0.
  	self assert: objectMemory memoryLimit \\ 4 = 0.
  	self assert: self rumpCStackSize \\ 4 = 0.
+ 	objectMemory allocateMemoryOfSize: objectMemory memoryLimit.
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
- 	objectMemory memory: ((cogit processor endianness == #little
- 					ifTrue: [LittleEndianBitmap]
- 					ifFalse: [Bitmap]) new: objectMemory memoryLimit // 4).
  	count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
+ 	count ~= dataSize ifTrue: [self halt]]
- 	count ~= dataSize ifTrue: [self halt].
- 	]
  		ensure: [f close].
  	self moveMethodCacheToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize.
  	self movePrimTraceLogToMemoryAt: objectMemory cogCodeBase + cogCodeSize + stackZoneSize + methodCacheSize.
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	Utilities
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift].
  	self initializeCodeGenerator!

Item was changed:
  ----- Method: CogVMSimulator>>withMemoryProtectionDo: (in category 'debug printing') -----
  withMemoryProtectionDo: aBlock
+ 	objectMemory writeProtectMemory.
- 	self writeProtectMemory.
  	stackPages writeProtectMemory.
  	^aBlock ensure:
+ 		[objectMemory writeEnableMemory.
- 		[self writeEnableMemory.
  		 stackPages writeEnableMemory]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>initialize (in category 'initialize-release') -----
  initialize
- 	memory := (VMBIGENDIAN
- 					ifTrue: [Bitmap]
- 					ifFalse: [LittleEndianBitmap]) new: 1024*1024/4.
  	objectMemory := self class objectMemoryClass simulatorClass new.
+ 	objectMemory allocateMemoryOfSize: 1024*1024.
- 	objectMemory memory: memory.
  	objectMemory
  		initializeFreeSpaceForFacadeFrom: self startOfMemory
  		to: self variablesBase.
+ 	memory := objectMemory memory.
  	coInterpreter := CoInterpreter new.
  	coInterpreter
  		instVarNamed: 'objectMemory'
  			put: objectMemory;
  		instVarNamed: 'primitiveTable'
  			put: (CArrayAccessor on: CoInterpreter primitiveTable copy).
  	variables := Dictionary new!

Item was added:
+ ----- Method: InterpreterPlugin>>cCoerceSimple:to: (in category 'simulation') -----
+ cCoerceSimple: value to: cType
+ 	"Coercion without type mapping.  Don't even bother to check for valid types..."
+ 	^value!

Item was removed:
- ----- Method: InterpreterSimulator>>convertToArray (in category 'initialization') -----
- convertToArray
- 	"I dont believe it -- this *just works*"
- 	
- 	memory := memory as: Array!

Item was added:
+ ----- Method: NewObjectMemory>>allocateMemoryOfSize: (in category 'simulation') -----
+ allocateMemoryOfSize: limit
+ 	<doNotGenerate>
+ 	super allocateMemoryOfSize: limit.
+ 	freeStart := memoryLimit!

Item was added:
+ ----- Method: ObjectMemory>>convertToArray (in category 'simulation') -----
+ convertToArray
+ 	<doNotGenerate>
+ 	"I dont believe it -- this *just works*"
+ 
+ 	memory:= memory as: Array!

Item was added:
+ ----- Method: ObjectMemory>>writeEnableMemory (in category 'simulation') -----
+ writeEnableMemory
+ 	<doNotGenerate>
+ 	memory class == ReadOnlyArrayWrapper ifTrue:
+ 		[memory := memory array]!

Item was added:
+ ----- Method: ObjectMemory>>writeProtectMemory (in category 'simulation') -----
+ writeProtectMemory
+ 	<doNotGenerate>
+ 	memory class ~~ ReadOnlyArrayWrapper ifTrue:
+ 		[memory := ReadOnlyArrayWrapper around: memory]!

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>byteAt: (in category 'memory access') -----
  byteAt: byteAddress
+ 	| lowBits long32 |
- 	| lowBits long |
  	lowBits := byteAddress bitAnd: 3.
+ 	long32 := self long32At: byteAddress - lowBits.
+ 	^(long32 bitShift: -8 * lowBits) bitAnd: 16rFF!
- 	long := self longAt: byteAddress - lowBits.
- 	^(lowBits caseOf: {
- 		[0] -> [ long ].
- 		[1] -> [ long bitShift: -8  ].
- 		[2] -> [ long bitShift: -16 ].
- 		[3] -> [ long bitShift: -24 ]
- 	}) bitAnd: 16rFF!

Item was changed:
  ----- Method: Spur32BitMMLECoSimulator>>byteAt:put: (in category 'memory access') -----
  byteAt: byteAddress put: byte
+ 	| lowBits long32 longAddress mask value |
- 	| lowBits long longAddress |
  	lowBits := byteAddress bitAnd: 3.
  	longAddress := byteAddress - lowBits.
+ 	long32 := self long32At: longAddress.
+ 	mask := (16rFF bitShift: 8 * lowBits) bitInvert.
+ 	value := byte bitShift: 8 * lowBits.
+ 	self long32At: longAddress put: ((long32 bitAnd: mask) bitOr: value).
- 	long := self longAt: longAddress.
- 	long := (lowBits caseOf: {
- 		[0] -> [ (long bitAnd: 16rFFFFFF00) bitOr: byte ].
- 		[1] -> [ (long bitAnd: 16rFFFF00FF) bitOr: (byte bitShift: 8) ].
- 		[2] -> [ (long bitAnd: 16rFF00FFFF) bitOr: (byte bitShift: 16)  ].
- 		[3] -> [ (long bitAnd: 16r00FFFFFF) bitOr: (byte bitShift: 24)  ]
- 	}).
- 	self longAt: longAddress put: long.
  	^byte!

Item was changed:
  ----- Method: Spur32BitMMLESimulator>>byteAt: (in category 'memory access') -----
  byteAt: byteAddress
+ 	| lowBits long32 |
- 	| lowBits long |
  	lowBits := byteAddress bitAnd: 3.
+ 	long32 := self long32At: byteAddress - lowBits.
+ 	^(long32 bitShift: -8 * lowBits) bitAnd: 16rFF!
- 	long := self longAt: byteAddress - lowBits.
- 	^(lowBits caseOf: {
- 		[0] -> [ long ].
- 		[1] -> [ long bitShift: -8  ].
- 		[2] -> [ long bitShift: -16 ].
- 		[3] -> [ long bitShift: -24 ]
- 	}) bitAnd: 16rFF!

Item was changed:
  ----- Method: Spur32BitMMLESimulator>>byteAt:put: (in category 'memory access') -----
  byteAt: byteAddress put: byte
+ 	| lowBits long32 longAddress mask value |
- 	| lowBits long longAddress |
  	lowBits := byteAddress bitAnd: 3.
  	longAddress := byteAddress - lowBits.
+ 	long32 := self long32At: longAddress.
+ 	mask := (16rFF bitShift: 8 * lowBits) bitInvert.
+ 	value := byte bitShift: 8 * lowBits.
+ 	self long32At: longAddress put: ((long32 bitAnd: mask) bitOr: value).
- 	long := self longAt: longAddress.
- 	long := (lowBits caseOf: {
- 		[0] -> [ (long bitAnd: 16rFFFFFF00) bitOr: byte ].
- 		[1] -> [ (long bitAnd: 16rFFFF00FF) bitOr: (byte bitShift: 8) ].
- 		[2] -> [ (long bitAnd: 16rFF00FFFF) bitOr: (byte bitShift: 16)  ].
- 		[3] -> [ (long bitAnd: 16r00FFFFFF) bitOr: (byte bitShift: 24)  ]
- 	}).
- 	self longAt: longAddress put: long.
  	^byte!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>memoryClass (in category 'simulation') -----
+ memoryClass
+ 	<doNotGenerate>
+ 	^self endianness == #little
+ 		ifTrue: [LittleEndianBitmap]
+ 		ifFalse: [Bitmap]!

Item was changed:
  ----- Method: Spur64BitMMLECoSimulator>>byteAt: (in category 'memory access') -----
  byteAt: byteAddress
  	| lowBits long32 |
  	lowBits := byteAddress bitAnd: 3.
  	long32 := self long32At: byteAddress - lowBits.
+ 	^(long32 bitShift: -8 * lowBits) bitAnd: 16rFF!
- 	^(lowBits caseOf: {
- 		[0] -> [ long32 ].
- 		[1] -> [ long32 bitShift: -8  ].
- 		[2] -> [ long32 bitShift: -16 ].
- 		[3] -> [ long32 bitShift: -24 ].
- 	}) bitAnd: 16rFF!

Item was changed:
  ----- Method: Spur64BitMMLECoSimulator>>byteAt:put: (in category 'memory access') -----
  byteAt: byteAddress put: byte
+ 	| lowBits long32 longAddress mask value |
- 	| lowBits long32 longAddress |
  	lowBits := byteAddress bitAnd: 3.
  	longAddress := byteAddress - lowBits.
  	long32 := self long32At: longAddress.
+ 	mask := (16rFF bitShift: 8 * lowBits) bitInvert.
+ 	value := byte bitShift: 8 * lowBits.
+ 	self long32At: longAddress put: ((long32 bitAnd: mask) bitOr: value).
- 	long32 := (lowBits caseOf: {
- 		[0] -> [ (long32 bitAnd: 16rFFFFFF00) bitOr: byte ].
- 		[1] -> [ (long32 bitAnd: 16rFFFF00FF) bitOr: (byte bitShift: 8) ].
- 		[2] -> [ (long32 bitAnd: 16rFF00FFFF) bitOr: (byte bitShift: 16) ].
- 		[3] -> [ (long32 bitAnd: 16r00FFFFFF) bitOr: (byte bitShift: 24) ].
- 	}).
- 	self long32At: longAddress put: long32.
  	^byte!

Item was added:
+ Spur64BitMMLECoSimulator subclass: #Spur64BitMMLECoSimulatorFor64Bits
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManagerSimulation'!

Item was added:
+ ----- Method: Spur64BitMMLECoSimulatorFor64Bits>>byteAt: (in category 'memory access') -----
+ byteAt: byteAddress
+ 	| lowBits long64 |
+ 	lowBits := byteAddress bitAnd: 7.
+ 	long64 := self long64At: byteAddress - lowBits.
+ 	^(long64 bitShift: -8 * lowBits) bitAnd: 16rFF!

Item was added:
+ ----- Method: Spur64BitMMLECoSimulatorFor64Bits>>byteAt:put: (in category 'memory access') -----
+ byteAt: byteAddress put: byte
+ 	| lowBits long64 longAddress mask value |
+ 	lowBits := byteAddress bitAnd: 7.
+ 	longAddress := byteAddress - lowBits.
+ 	long64 := self long64At: longAddress.
+ 	mask := (16rFF bitShift: 8 * lowBits) bitInvert.
+ 	value := byte bitShift: 8 * lowBits.
+ 	self long64At: longAddress put: ((long64 bitAnd: mask) bitOr: value).
+ 	^byte!

Item was added:
+ ----- Method: Spur64BitMMLECoSimulatorFor64Bits>>long32At: (in category 'memory access') -----
+ long32At: byteAddress
+ 	"Answer the 32-bit word at byteAddress which must be a multiple of four."
+ 	| lowBits long |
+ 	lowBits := byteAddress bitAnd: 4.
+ 	long := self long64At: byteAddress - lowBits.
+ 	^lowBits = 4
+ 		ifTrue: [long bitShift: -32]
+ 		ifFalse: [long bitAnd: 16rFFFFFFFF]!

Item was added:
+ ----- Method: Spur64BitMMLECoSimulatorFor64Bits>>long32At:put: (in category 'memory access') -----
+ long32At: byteAddress put: a32BitValue
+  	"Store the 32-bit word at byteAddress which must be a multiple of four."
+ 	| lowBits long longAddress |
+ 	lowBits := byteAddress bitAnd: 4.
+ 	lowBits = 0
+ 		ifTrue: "storing into LS word"
+ 			[long := self long64At: byteAddress.
+ 			 self long64At: byteAddress
+ 				put: ((long bitAnd: 16rFFFFFFFF00000000) bitOr: a32BitValue)]
+ 		ifFalse: "storing into MS word"
+ 			[longAddress := byteAddress - 4.
+ 			long := self long64At: longAddress.
+ 			self long64At: longAddress
+ 				put: ((long bitAnd: 16rFFFFFFFF) bitOr: (a32BitValue bitShift: 32))].
+ 	^a32BitValue!

Item was added:
+ ----- Method: Spur64BitMMLECoSimulatorFor64Bits>>long64At: (in category 'memory access') -----
+ long64At: byteAddress
+ 	"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: Spur64BitMMLECoSimulatorFor64Bits>>long64At:put: (in category 'memory access') -----
+ long64At: byteAddress put: a64BitValue
+ 	"memory is a DobleWordArray, a 64-bit indexable array of bits"
+ 	byteAddress \\ 8 ~= 0 ifTrue: [self unalignedAccessError].
+ 	^memory at: byteAddress // 8 + 1 put: a64BitValue!

Item was added:
+ ----- Method: Spur64BitMMLECoSimulatorFor64Bits>>memoryClass (in category 'simulation') -----
+ memoryClass
+ 	"Answer the class to use for the memory inst var in simulation.
+ 	 Answer nil if a suitable class isn't available.  This version uses a 64-bit element class if available."
+ 	<doNotGenerate>
+ 	^Smalltalk classNamed: #DoubleWordArray!

Item was added:
+ ----- Method: Spur64BitMMLECoSimulatorFor64Bits>>shortAt: (in category 'memory access') -----
+ shortAt: byteAddress
+ 	| lowBits long64 |
+ 	lowBits := byteAddress bitAnd: 6.
+ 	long64 := self long64At: byteAddress - lowBits.
+ 	^(long64 bitShift: -8 * lowBits) bitAnd: 16rFFFF!

Item was added:
+ ----- Method: Spur64BitMMLECoSimulatorFor64Bits>>shortAt:put: (in category 'memory access') -----
+ shortAt: byteAddress put: short
+ 	| lowBits long64 longAddress mask value |
+ 	lowBits := byteAddress bitAnd: 6.
+ 	longAddress := byteAddress - lowBits.
+ 	long64 := self long64At: longAddress.
+ 	mask := (16rFFFF bitShift: 8 * lowBits) bitInvert.
+ 	value := short bitShift: 8 * lowBits.
+ 	self long64At: longAddress put: ((long64 bitAnd: mask) bitOr: value).
+ 	^short!

Item was changed:
  ----- Method: Spur64BitMMLESimulator>>byteAt: (in category 'memory access') -----
  byteAt: byteAddress
  	| lowBits long32 |
  	lowBits := byteAddress bitAnd: 3.
  	long32 := self long32At: byteAddress - lowBits.
+ 	^(long32 bitShift: -8 * lowBits) bitAnd: 16rFF!
- 	^(lowBits caseOf: {
- 		[0] -> [ long32 ].
- 		[1] -> [ long32 bitShift: -8  ].
- 		[2] -> [ long32 bitShift: -16 ].
- 		[3] -> [ long32 bitShift: -24 ].
- 	}) bitAnd: 16rFF!

Item was changed:
  ----- Method: Spur64BitMMLESimulator>>byteAt:put: (in category 'memory access') -----
  byteAt: byteAddress put: byte
+ 	| lowBits long32 longAddress mask value |
- 	| lowBits long32 longAddress |
  	lowBits := byteAddress bitAnd: 3.
  	longAddress := byteAddress - lowBits.
  	long32 := self long32At: longAddress.
+ 	mask := (16rFF bitShift: 8 * lowBits) bitInvert.
+ 	value := byte bitShift: 8 * lowBits.
+ 	self long32At: longAddress put: ((long32 bitAnd: mask) bitOr: value).
- 	long32 := (lowBits caseOf: {
- 		[0] -> [ (long32 bitAnd: 16rFFFFFF00) bitOr: byte ].
- 		[1] -> [ (long32 bitAnd: 16rFFFF00FF) bitOr: (byte bitShift: 8) ].
- 		[2] -> [ (long32 bitAnd: 16rFF00FFFF) bitOr: (byte bitShift: 16) ].
- 		[3] -> [ (long32 bitAnd: 16r00FFFFFF) bitOr: (byte bitShift: 24) ].
- 	}).
- 	self long32At: longAddress put: long32.
  	^byte!

Item was added:
+ Spur64BitMMLESimulator subclass: #Spur64BitMMLESimulatorFor64Bits
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManagerSimulation'!

Item was added:
+ ----- Method: Spur64BitMMLESimulatorFor64Bits>>byteAt: (in category 'memory access') -----
+ byteAt: byteAddress
+ 	| lowBits long64 |
+ 	lowBits := byteAddress bitAnd: 7.
+ 	long64 := self long64At: byteAddress - lowBits.
+ 	^(long64 bitShift: -8 * lowBits) bitAnd: 16rFF!

Item was added:
+ ----- Method: Spur64BitMMLESimulatorFor64Bits>>byteAt:put: (in category 'memory access') -----
+ byteAt: byteAddress put: byte
+ 	| lowBits long64 longAddress mask value |
+ 	lowBits := byteAddress bitAnd: 7.
+ 	longAddress := byteAddress - lowBits.
+ 	long64 := self long64At: longAddress.
+ 	mask := (16rFF bitShift: 8 * lowBits) bitInvert.
+ 	value := byte bitShift: 8 * lowBits.
+ 	self long64At: longAddress put: ((long64 bitAnd: mask) bitOr: value).
+ 	^byte!

Item was added:
+ ----- Method: Spur64BitMMLESimulatorFor64Bits>>long32At: (in category 'memory access') -----
+ long32At: byteAddress
+ 	"Answer the 32-bit word at byteAddress which must be a multiple of four."
+ 	| lowBits long |
+ 	lowBits := byteAddress bitAnd: 4.
+ 	long := self long64At: byteAddress - lowBits.
+ 	^lowBits = 4
+ 		ifTrue: [long bitShift: -32]
+ 		ifFalse: [long bitAnd: 16rFFFFFFFF]!

Item was added:
+ ----- Method: Spur64BitMMLESimulatorFor64Bits>>long32At:put: (in category 'memory access') -----
+ long32At: byteAddress put: a32BitValue
+  	"Store the 32-bit word at byteAddress which must be a multiple of four."
+ 	| lowBits long longAddress |
+ 	lowBits := byteAddress bitAnd: 4.
+ 	lowBits = 0
+ 		ifTrue: "storing into LS word"
+ 			[long := self long64At: byteAddress.
+ 			 self long64At: byteAddress
+ 				put: ((long bitAnd: 16rFFFFFFFF00000000) bitOr: a32BitValue)]
+ 		ifFalse: "storing into MS word"
+ 			[longAddress := byteAddress - 4.
+ 			long := self long64At: longAddress.
+ 			self long64At: longAddress
+ 				put: ((long bitAnd: 16rFFFFFFFF) bitOr: (a32BitValue bitShift: 32))].
+ 	^a32BitValue!

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

Item was added:
+ ----- Method: Spur64BitMMLESimulatorFor64Bits>>memoryClass (in category 'simulation') -----
+ memoryClass
+ 	"Answer the class to use for the memory inst var in simulation.
+ 	 Answer nil if a suitable class isn't available.  This version uses a 64-bit element class if available."
+ 	<doNotGenerate>
+ 	^Smalltalk classNamed: #DoubleWordArray!

Item was added:
+ ----- Method: Spur64BitMMLESimulatorFor64Bits>>shortAt: (in category 'memory access') -----
+ shortAt: byteAddress
+ 	| lowBits long64 |
+ 	lowBits := byteAddress bitAnd: 6.
+ 	long64 := self long64At: byteAddress - lowBits.
+ 	^(long64 bitShift: -8 * lowBits) bitAnd: 16rFFFF!

Item was added:
+ ----- Method: Spur64BitMMLESimulatorFor64Bits>>shortAt:put: (in category 'memory access') -----
+ shortAt: byteAddress put: short
+ 	| lowBits long64 longAddress mask value |
+ 	lowBits := byteAddress bitAnd: 6.
+ 	longAddress := byteAddress - lowBits.
+ 	long64 := self long64At: longAddress.
+ 	mask := (16rFFFF bitShift: 8 * lowBits) bitInvert.
+ 	value := short bitShift: 8 * lowBits.
+ 	self long64At: longAddress put: ((long64 bitAnd: mask) bitOr: value).
+ 	^short!

Item was changed:
  ----- Method: Spur64BitMemoryManager class>>simulatorClass (in category 'simulation only') -----
  simulatorClass
+ 	^Spur64BitMMLESimulatorFor64Bits basicNew memoryClass
+ 		ifNil: [Spur64BitMMLESimulator]
+ 		ifNotNil: [Spur64BitMMLESimulatorFor64Bits]!
- 	^Spur64BitMMLESimulator!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>memoryClass (in category 'simulation') -----
+ memoryClass
+ 	"Answer the class to use for the memory inst var in simulation.
+ 	 Answer nil if a suitable class isn't available.  This version emulates 64-bit access given a 32-bit element array."
+ 	<doNotGenerate>
+ 	^self endianness == #little
+ 		ifTrue: [LittleEndianBitmap]
+ 		ifFalse: [Bitmap]!

Item was added:
+ ----- Method: SpurMemoryManager class>>simulatorClass (in category 'simulation only') -----
+ simulatorClass
+ 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateMemoryOfSize: (in category 'testing') -----
+ allocateMemoryOfSize: memoryBytes
- allocateMemoryOfSize: limit
  	<doNotGenerate>
+ 	| bytesPerElement |
+ 	bytesPerElement := (self memoryClass basicNew: 0) bytesPerElement.
+ 	memory := self memoryClass new: memoryBytes + bytesPerElement - 1 // bytesPerElement!
- 	memory := (self endianness == #little
- 					ifTrue: [LittleEndianBitmap]
- 					ifFalse: [Bitmap]) new: limit // 4!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateMemoryOfSize:newSpaceSize:stackSize:codeSize: (in category 'spur bootstrap') -----
  allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes stackSize: stackBytes codeSize: codeBytes
  	"Intialize the receiver for bootsraping an image.
  	 Set up a large oldSpace and an empty newSpace and set-up freeStart and scavengeThreshold
  	 to allocate in oldSpace.  Later on (in initializePostBootstrap) freeStart and scavengeThreshold
  	 will be set to sane values."
  	<doNotGenerate>
  	self assert: (memoryBytes \\ self allocationUnit = 0
  				and: [newSpaceBytes \\ self allocationUnit = 0
  				and: [codeBytes \\ self allocationUnit = 0]]).
+ 	self allocateMemoryOfSize: memoryBytes + newSpaceBytes + codeBytes + stackBytes.
- 	memory := (self endianness == #little
- 					ifTrue: [LittleEndianBitmap]
- 					ifFalse: [Bitmap]) new: (memoryBytes + newSpaceBytes + codeBytes + stackBytes) // 4.
  	newSpaceStart := codeBytes + stackBytes.
  	endOfMemory := freeOldSpaceStart := memoryBytes + newSpaceBytes + codeBytes + stackBytes.
  	"leave newSpace empty for the bootstrap"
  	freeStart := newSpaceBytes + newSpaceStart.
  	oldSpaceStart := newSpaceLimit := newSpaceBytes + newSpaceStart.
+ 	scavengeThreshold := memory size * memory bytesPerElement. "i.e. /don't/ scavenge."
- 	scavengeThreshold := memory size * 4. "Bitmap is a 4-byte per word array"
  	scavenger := SpurGenerationScavengerSimulator new.
  	scavenger manager: self.
  	scavenger newSpaceStart: newSpaceStart
  				newSpaceBytes: newSpaceBytes
  				survivorBytes: newSpaceBytes // self scavengerDenominator!

Item was added:
+ ----- Method: SpurMemoryManager>>convertToArray (in category 'simulation') -----
+ convertToArray
+ 	<doNotGenerate>
+ 	"I dont believe it -- this *just works*"
+ 
+ 	memory:= memory as: Array!

Item was added:
+ ----- Method: SpurMemoryManager>>memoryClass (in category 'simulation') -----
+ memoryClass
+ 	"Answer the class to use for the memory inst var in simulation.
+ 	 Answer nil if a suitable class isn't available."
+ 	<doNotGenerate>
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>positiveMachineIntegerFor: (in category 'simulation only') -----
+ positiveMachineIntegerFor: integerValue
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	<doNotGenerate>
+ 	^coInterpreter positiveMachineIntegerFor: integerValue!

Item was added:
+ ----- Method: SpurMemoryManager>>positiveMachineIntegerValueOf: (in category 'simulation only') -----
+ positiveMachineIntegerValueOf: integerValue
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	<doNotGenerate>
+ 	^coInterpreter positiveMachineIntegerValueOf: integerValue!

Item was changed:
  ----- Method: SpurMemoryManager>>sqAllocateMemorySegmentOfSize:Above:AllocatedSizeInto: (in category 'simulation only') -----
  sqAllocateMemorySegmentOfSize: segmentSize Above: minAddress AllocatedSizeInto: allocSizePtrOrBlock
  	<doNotGenerate>
  	"Simulate heap growth by growing memory by segmentSize + a delta.
  	 To test bridges alternate the delta between 0 bytes and 1M bytes
  	 depending on the number of segments.
  	 The delta will be the distance between segments to be bridged."
  	| delta newMemory start |
+ 	self assert: segmentSize \\ memory bytesPerElement = 0.
  	delta := segmentManager numSegments odd ifTrue: [1024 * 1024] ifFalse: [0].
  	"A previous shrink may have freed up memory.  Don't bother to grow if there's already room."
+ 	segmentManager lastSegment segLimit + segmentSize + delta <= (memory size * memory bytesPerElement) ifTrue:
- 	segmentManager lastSegment segLimit + segmentSize + delta <= (memory size * 4) ifTrue:
  		[allocSizePtrOrBlock value: segmentSize.
  		 ^minAddress + delta].
+ 	start := memory size * memory bytesPerElement + delta.
+ 	newMemory := memory class new: memory size + (segmentSize + delta / memory bytesPerElement).
- 	start := memory size * 4 + delta.
- 	newMemory := memory class new: memory size + (segmentSize + delta / 4).
  	newMemory replaceFrom: 1 to: memory size with: memory startingAt: 1.
  	memory := newMemory.
  	allocSizePtrOrBlock value: segmentSize.
  	^start!

Item was added:
+ ----- Method: SpurMemoryManager>>writeEnableMemory (in category 'simulation') -----
+ writeEnableMemory
+ 	<doNotGenerate>
+ 	memory class == ReadOnlyArrayWrapper ifTrue:
+ 		[memory := memory array]!

Item was added:
+ ----- Method: SpurMemoryManager>>writeProtectMemory (in category 'simulation') -----
+ writeProtectMemory
+ 	<doNotGenerate>
+ 	memory class ~~ ReadOnlyArrayWrapper ifTrue:
+ 		[memory := ReadOnlyArrayWrapper around: memory]!

Item was changed:
  ----- Method: SpurSegmentManager>>readHeapFrom:at:dataBytes: (in category 'private') -----
  readHeapFrom: f at: location dataBytes: numBytes
  	"Read numBytes from f into mmory at location.  Answer the number of bytes read."
  	^self cCode:
  			[self
  				sq: (self pointerForOop: location)
  				Image: (self sizeof: #char)
  				File: numBytes
  				Read: f]
  		inSmalltalk:
+ 			[| bytesPerElement |
+ 			 bytesPerElement := manager memory bytesPerElement.
+ 			 (f	readInto: manager memory
+ 				startingAt: location // bytesPerElement + 1
+ 				count: numBytes // bytesPerElement)
+ 			  * bytesPerElement]!
- 			[(f	readInto: manager memory
- 				startingAt: location // 4 + 1
- 				count: numBytes // 4)
- 			 * 4]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>byteAt: (in category 'memory access') -----
  byteAt: byteAddress
+ 	self deprecated.
  	^objectMemory byteAt: byteAddress!

Item was changed:
  ----- Method: StackInterpreterSimulator>>byteAt:put: (in category 'memory access') -----
  byteAt: byteAddress put: byte
+ 	self deprecated.
  	^objectMemory byteAt: byteAddress put: byte!

Item was removed:
- ----- Method: StackInterpreterSimulator>>convertToArray (in category 'initialization') -----
- convertToArray
- 	"I dont believe it -- this *just works*"
- 
- 	objectMemory memory: (objectMemory memory as: Array)!

Item was changed:
  ----- Method: StackInterpreterSimulator>>integerAt: (in category 'memory access') -----
  integerAt: byteAddress
  	"Note: Adjusted for Smalltalk's 1-based array indexing."
  
+ 	self deprecated.
  	^objectMemory memory integerAt: (byteAddress // 4) + 1!

Item was changed:
  ----- Method: StackInterpreterSimulator>>integerAt:put: (in category 'memory access') -----
  integerAt: byteAddress put: a32BitValue
  	"Note: Adjusted for Smalltalk's 1-based array indexing."
  
+ 	self deprecated.
  	^objectMemory memory integerAt: (byteAddress // 4) + 1 put: a32BitValue!

Item was changed:
  ----- Method: StackInterpreterSimulator>>longAt: (in category 'memory access') -----
  longAt: byteAddress
+ 	self deprecated.
  	^objectMemory longAt: byteAddress!

Item was changed:
  ----- Method: StackInterpreterSimulator>>longAt:put: (in category 'memory access') -----
  longAt: byteAddress put: a32BitValue
+ 	self deprecated.
  	^objectMemory longAt: byteAddress put: a32BitValue!

Item was changed:
  ----- Method: StackInterpreterSimulator>>openOn:extraMemory: (in category 'initialization') -----
  openOn: fileName extraMemory: extraBytes
  	"StackInterpreterSimulator new openOn: 'clone.im' extraMemory: 100000"
  
  	| f version headerSize dataSize count oldBaseAddr bytesToShift swapBytes
  	  headerFlags heapBase firstSegSize heapSize
  	  hdrNumStackPages hdrEdenBytes hdrMaxExtSemTabSize allocationReserve |
  	"open image file and read the header"
  
  	f := FileStream readOnlyFileNamed: fileName.
  	f ifNil: [^self error: 'no image found'].
  
  	"Set the image name and the first argument; there are
  	 no arguments during simulation unless set explicitly."
  	systemAttributes at: 1 put: fileName; at: 2 put: nil.
  
  	["begin ensure block..."
  	imageName := f fullName.
  	f binary.
  
  	version := self getWord32FromFile: f swap: false.  "current version: 16r1968 (=6504) vive la revolucion!!"
  	(self readableFormat: version)
  		ifTrue: [swapBytes := false]
  		ifFalse: [(version := objectMemory byteSwapped: version) = self imageFormatVersion
  					ifTrue: [swapBytes := true]
  					ifFalse: [self error: 'incomaptible image format']].
  	headerSize := self getWord32FromFile: f swap: swapBytes.
  	dataSize := self getLongFromFile: f swap: swapBytes.  "length of heap in file"
  	oldBaseAddr := self getLongFromFile: f swap: swapBytes.  "object memory base address of image"
  	objectMemory specialObjectsOop: (self getLongFromFile: f swap: swapBytes).
  	objectMemory lastHash: (self getLongFromFile: f swap: swapBytes).  "Should be loaded from, and saved to the image header"
  
  	savedWindowSize	:= self getLongFromFile: f swap: swapBytes.
  	headerFlags		:= self getLongFromFile: f swap: swapBytes.
  	self setImageHeaderFlagsFrom: headerFlags.
  	extraVMMemory	:= self getWord32FromFile: f swap: swapBytes.
  	hdrNumStackPages	:= self getShortFromFile: f swap: swapBytes.
  	"4 stack pages is small.  Should be able to run with as few as
  	 three. 4 should be comfortable but slow.  8 is a reasonable
  	 default. Can be changed via vmParameterAt: 43 put: n"
  	numStackPages := desiredNumStackPages ~= 0
  						ifTrue: [desiredNumStackPages]
  						ifFalse: [hdrNumStackPages = 0
  									ifTrue: [self defaultNumStackPages]
  									ifFalse: [hdrNumStackPages]].
  	desiredNumStackPages := hdrNumStackPages.
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 It is used for the cog code size in Cog.  Preserve it to be polite to other VMs."
  	theUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [40] ifFalse: [64]).
  	hdrEdenBytes		:= self getWord32FromFile: f swap: swapBytes.
  	objectMemory edenBytes: (hdrEdenBytes = 0
  							ifTrue: [objectMemory defaultEdenBytes]
  							ifFalse: [hdrEdenBytes]).
  	desiredEdenBytes := hdrEdenBytes.
  	hdrMaxExtSemTabSize := self getShortFromFile: f swap: swapBytes.
  	hdrMaxExtSemTabSize ~= 0 ifTrue:
  		[self setMaxExtSemSizeTo: hdrMaxExtSemTabSize].
  	"pad to word boundary.  This slot can be used for anything else that will fit in 16 bits.
  	 Preserve it to be polite to other VMs."
  	the2ndUnknownShort	:= self getShortFromFile: f swap: swapBytes.
  	self assert: f position = (objectMemory wordSize = 4 ifTrue: [48] ifFalse: [72]).
  	firstSegSize := self getLongFromFile: f swap: swapBytes.
  	objectMemory firstSegmentSize: firstSegSize.
  	"compare memory requirements with availability"
  	allocationReserve := self interpreterAllocationReserveBytes.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[| freeOldSpaceInImage headroom |
  			 freeOldSpaceInImage := self getLongFromFile: f swap: swapBytes.
  			 headroom := objectMemory
  							initialHeadroom: extraVMMemory
  							givenFreeOldSpaceInImage: freeOldSpaceInImage.
  			 heapSize := objectMemory roundUpHeapSize:
  						   dataSize
  						+ headroom
  						+ objectMemory newSpaceBytes
  						+ (headroom > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])]
  		ifFalse:
  			[heapSize :=  dataSize
  						+ extraBytes
  						+ objectMemory newSpaceBytes
  						+ (extraBytes > allocationReserve
  							ifTrue: [0]
  							ifFalse: [allocationReserve])].
  	"allocate interpreter memory"
  	heapBase := objectMemory startOfMemory.
  	objectMemory
  		setHeapBase: heapBase
  		memoryLimit: heapBase + heapSize
  		endOfMemory: heapBase + dataSize. "bogus for Spur"
+ 	objectMemory allocateMemoryOfSize: objectMemory memoryLimit.
- 	objectMemory memory: ((objectMemory endianness == #little 
- 					ifTrue: [LittleEndianBitmap]
- 					ifFalse: [Bitmap]) new: objectMemory memoryLimit // 4).
- 
  	"read in the image in bulk, then swap the bytes if necessary"
  	f position: headerSize.
  	count := objectMemory readHeapFromImageFile: f dataBytes: dataSize.
+ 	count ~= dataSize ifTrue: [self halt]]
- 	count ~= dataSize ifTrue: [self halt].
- 	]
  		ensure: [f close].
  
  	self ensureImageFormatIsUpToDate: swapBytes.
  
  	bytesToShift := objectMemory memoryBaseForImageRead - oldBaseAddr.  "adjust pointers for zero base address"
  	Utilities
  		informUser: 'Relocating object pointers...'
  		during: [self initializeInterpreter: bytesToShift]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>withMemoryProtectionDo: (in category 'debug printing') -----
  withMemoryProtectionDo: aBlock
+ 	objectMemory writeProtectMemory.
- 	self writeProtectMemory.
  	stackPages writeProtectMemory.
  	^aBlock ensure:
+ 		[objectMemory writeEnableMemory.
- 		[self writeEnableMemory.
  		 stackPages writeEnableMemory]!

Item was removed:
- ----- Method: StackInterpreterSimulator>>writeEnableMemory (in category 'debug printing') -----
- writeEnableMemory
- 	objectMemory memory: objectMemory memory array!

Item was removed:
- ----- Method: StackInterpreterSimulator>>writeProtectMemory (in category 'debug printing') -----
- writeProtectMemory
- 	objectMemory memory: (ReadOnlyArrayWrapper around: objectMemory memory)!

Item was added:
+ ----- 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.
+ 	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.
+ 	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.
+ 		 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 added:
+ ----- 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.
+ 	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.
+ 	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.
+ 		 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: 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 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: 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 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: 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 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]!
- 	self assert: (om unalignedLongAt: 3) equals: 16r1122334455667788.!




More information about the Vm-dev mailing list