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

commits at source.squeak.org commits at source.squeak.org
Tue Nov 18 19:27:18 UTC 2014


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

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

Name: VMMaker.oscog-eem.937
Author: eem
Time: 18 November 2014, 11:24:51.075 am
UUID: 93c76c68-ea84-4009-b9b8-7e919ae306a0
Ancestors: VMMaker.oscog-eem.936

Rewrite writeImageFileIO[Simulation] to support 32 and
64 bits.  Nuke memory simulator putLong/Short:toFile:'s.
Comment typos and recategorizations.

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

Item was removed:
- ----- Method: CogVMSimulatorLSB>>putLong:toFile: (in category 'image save/restore') -----
- putLong: n toFile: f
- 	"Append the given 4-byte long word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	| remainingValue |
- 
- 	remainingValue := n.
- 	4 timesRepeat: [
- 		f nextPut: (remainingValue bitAnd: 16rFF).
- 		remainingValue := remainingValue bitShift: -8].
- 
- 	self success: true!

Item was removed:
- ----- Method: CogVMSimulatorLSB>>putShort:toFile: (in category 'image save/restore') -----
- putShort: n toFile: f
- 	"Append the given 2-byte half-word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	| remainingValue |
- 
- 	remainingValue := n.
- 	2 timesRepeat: [
- 		f nextPut: (remainingValue bitAnd: 16rFF).
- 		remainingValue := remainingValue bitShift: -8].
- 
- 	self success: true!

Item was removed:
- ----- Method: NewCoObjectMemorySimulatorLSB>>putLong:toFile: (in category 'image save/restore') -----
- putLong: n toFile: f
- 	"Append the given 4-byte long word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	| remainingValue |
- 
- 	remainingValue := n.
- 	4 timesRepeat: [
- 		f nextPut: (remainingValue bitAnd: 16rFF).
- 		remainingValue := remainingValue bitShift: -8].
- 
- 	self success: true!

Item was removed:
- ----- Method: NewCoObjectMemorySimulatorLSB>>putShort:toFile: (in category 'image save/restore') -----
- putShort: n toFile: f
- 	"Append the given 2-byte half-word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	| remainingValue |
- 
- 	remainingValue := n.
- 	2 timesRepeat: [
- 		f nextPut: (remainingValue bitAnd: 16rFF).
- 		remainingValue := remainingValue bitShift: -8].
- 
- 	self success: true!

Item was removed:
- ----- Method: NewCoObjectMemorySimulatorMSB>>putLong:toFile: (in category 'image save/restore') -----
- putLong: n toFile: f
- 	"Append the given 4-byte long word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	[f nextNumber: 4 put: n]
- 		on: Error
- 		do: [:ex| coInterpreter success: false]!

Item was removed:
- ----- Method: NewCoObjectMemorySimulatorMSB>>putShort:toFile: (in category 'image save/restore') -----
- putShort: n toFile: f
- 	"Append the given 2-byte half-word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	[f nextNumber: 2 put: n]
- 		on: Error
- 		do: [:ex| coInterpreter success: false]!

Item was removed:
- ----- Method: NewObjectMemorySimulatorLSB>>putLong:toFile: (in category 'image save/restore') -----
- putLong: n toFile: f
- 	"Append the given 4-byte long word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	| remainingValue |
- 
- 	remainingValue := n.
- 	4 timesRepeat: [
- 		f nextPut: (remainingValue bitAnd: 16rFF).
- 		remainingValue := remainingValue bitShift: -8].
- 
- 	self success: true!

Item was removed:
- ----- Method: NewObjectMemorySimulatorLSB>>putShort:toFile: (in category 'image save/restore') -----
- putShort: n toFile: f
- 	"Append the given 2-byte half-word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	| remainingValue |
- 
- 	remainingValue := n.
- 	2 timesRepeat: [
- 		f nextPut: (remainingValue bitAnd: 16rFF).
- 		remainingValue := remainingValue bitShift: -8].
- 
- 	self success: true!

Item was removed:
- ----- Method: NewObjectMemorySimulatorMSB>>putLong:toFile: (in category 'image save/restore') -----
- putLong: n toFile: f
- 	"Append the given 4-byte long word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	[f nextNumber: 4 put: n]
- 		on: Error
- 		do: [:ex| coInterpreter success: false]!

Item was removed:
- ----- Method: NewObjectMemorySimulatorMSB>>putShort:toFile: (in category 'image save/restore') -----
- putShort: n toFile: f
- 	"Append the given 2-byte half-word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	[f nextNumber: 2 put: n]
- 		on: Error
- 		do: [:ex| coInterpreter success: false]!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>numFreeLists (in category 'free space') -----
  numFreeLists
  	"Answer the number of free lists.  We use freeListsMask, a bitmap, to avoid
+ 	 reading empty list heads.  This should fit in a machine word to end up in a
- 	 reading empty list heads.  This hsould fit in a machine word to end up in a
  	 register during free chunk allocation."
  	^32!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>numFreeLists (in category 'free space') -----
  numFreeLists
  	"Answer the number of free lists.  We use freeListsMask, a bitmap, to avoid
+ 	 reading empty list heads.  This should fit in a machine word to end up in a
- 	 reading empty list heads.  This hsould fit in a machine word to end up in a
  	 register during free chunk allocation."
  	^64!

Item was changed:
  ----- Method: SpurMemoryManager>>numFreeLists (in category 'free space') -----
  numFreeLists
  	"Answer the number of free lists.  We use freeListsMask, a bitmap, to avoid
+ 	 reading empty list heads.  This should fit in a machine word to end up in a
- 	 reading empty list heads.  This hsould fit in a machine word to end up in a
  	 register during free chunk allocation."
  	^self subclassResponsibility!

Item was changed:
+ ----- Method: SpurSegmentManager>>initSegmentForInImageCompilationFrom:to: (in category 'simulation only') -----
- ----- Method: SpurSegmentManager>>initSegmentForInImageCompilationFrom:to: (in category 'simulation') -----
  initSegmentForInImageCompilationFrom: base to: limit
  	<doNotGenerate>
  	| bridge |
  	self allocateOrExtendSegmentInfos.
  	numSegments := 1.
  	bridge := manager initSegmentBridgeWithBytes: manager memory byteSize - limit at: limit - manager bridgeSize.
  	segments := {SpurSegmentInfo new
  						segStart: base;
  						segSize: limit - base;
  						yourself}.
  	segments := CArrayAccessor on: segments!

Item was changed:
  ----- Method: StackInterpreter>>putLong:toFile: (in category 'image save/restore') -----
+ putLong: aLong toFile: aFile
+ 	"Append aLong to aFile in this platform's 'natural' byte order.  aLong is either 32 or 64 bits,
+ 	 depending on ObjectMemory.  (Bytes will be swapped, if necessary, when the image is read
+ 	 on a different platform.) Set successFlag to false if the write fails."
- putLong: aWord toFile: aFile
- 	"Append aWord to aFile in this platforms 'natural' byte order.  (Bytes will be swapped, if
- 	necessary, when the image is read on a different platform.) Set successFlag to false if
- 	the write fails."
  
+ 	<var: #aLong type: #long>
  	| objectsWritten |
+ 	<var: #aFile type: #sqImageFile>
- 	<var: #aFile type: 'sqImageFile '>
  
+ 	objectsWritten := self
+ 						cCode: [self sq: (self addressOf: aLong) Image: (self sizeof: #long) File: 1 Write: aFile]
+ 						inSmalltalk:
+ 							[| value |
+ 							 value := aLong.
+ 							 objectMemory wordSize timesRepeat:
+ 								[aFile nextPut: (value bitAnd: 16rFF).
+ 								 value := value >> 8].
+ 							 1].
+ 	self success: objectsWritten = 1!
- 	objectsWritten := self cCode: 'sqImageFileWrite(&aWord, sizeof(aWord), 1, aFile)'.
- 	self success: objectsWritten = 1.
- !

Item was changed:
  ----- Method: StackInterpreter>>putShort:toFile: (in category 'image save/restore') -----
  putShort: aShort toFile: aFile
+ 	"Append the 16-bit aShort to aFile in this platform's 'natural' byte order.
- 	"Append the 16-bit aShort to aFile in this platforms 'natural' byte order.
  	 (Bytes will be swapped, if necessary, when the image is read on a
  	 different platform.) Set successFlag to false if the write fails."
  
  	| objectsWritten |
+ 	<var: #aFile type: #sqImageFile>
- 	<var: #aFile type: 'sqImageFile '>
  
+ 	objectsWritten := self
+ 						cCode: [self sq: (self addressOf: aShort) Image: (self sizeof: #short) File: 1 Write: aFile]
+ 						inSmalltalk:
+ 							[aFile
+ 								nextPut: (aShort bitAnd: 16rFF);
+ 								nextPut: (aShort >> 8 bitAnd: 16rFF).
+ 							 1].
+ 	self success: objectsWritten = 1!
- 	objectsWritten := self cCode: 'sqImageFileWrite(&aShort, sizeof(short), 1, aFile)'.
- 	self success: objectsWritten = 1.
- !

Item was added:
+ ----- Method: StackInterpreter>>putWord32:toFile: (in category 'image save/restore') -----
+ putWord32: aWord32 toFile: aFile
+ 	"Append aWord32 to aFile in this platform's 'natural' byte order.  aWord32 is 32 bits,
+ 	 depending on ObjectMemory.  (Bytes will be swapped, if necessary, when the image is read
+ 	 on a different platform.) Set successFlag to false if the write fails."
+ 
+ 	<var: #aWord32 type: #int>
+ 	| objectsWritten |
+ 	<var: #aFile type: #sqImageFile>
+ 
+ 	objectsWritten := self
+ 						cCode: [self sq: (self addressOf: aWord32) Image: 4 File: 1 Write: aFile]
+ 						inSmalltalk:
+ 							[| value |
+ 							 value := aWord32.
+ 							 4 timesRepeat:
+ 								[aFile nextPut: (value bitAnd: 16rFF).
+ 								 value := value >> 8].
+ 							 1].
+ 	self success: objectsWritten = 1!

Item was changed:
  ----- Method: StackInterpreter>>writeImageFileIO (in category 'image save/restore') -----
  writeImageFileIO
+ 	"Write the image header and heap contents to imageFile for snapshot. c.f. writeImageFileIOSimulation.
+ 	 The game below is to maintain 64-bit alignment for all putLong:toFile: occurrences."
- 	"Write the image header and heap contents to imageFile for snapshot."
  	| imageName headerStart headerSize f imageBytes bytesWritten sCWIfn okToWrite |
  	<var: #f type: #sqImageFile>
  	<var: #headerStart type: #squeakFileOffsetType>
  	<var: #sCWIfn type: #'void *'>
  	<var: #imageName declareC: 'extern char imageName[]'>
  
  	self cCode: [] inSmalltalk: [imageName := 'sooth compiler'. ^self writeImageFileIOSimulation].
  
  	"If the security plugin can be loaded, use it to check for write permission.
  	 If not, assume it's ok"
  	sCWIfn := self ioLoadFunction: 'secCanWriteImage' From: 'SecurityPlugin'.
  	sCWIfn ~= 0 ifTrue:
  		[okToWrite := self cCode: '((sqInt (*)(void))sCWIfn)()'.
  		 okToWrite ifFalse:[^self primitiveFail]].
  	
  	"local constants"
  	headerStart := 0.  
+ 	headerSize := objectMemory wordSize = 4 ifTrue: [64] ifFalse: [128].  "header size in bytes; do not change!!"
- 	headerSize := 64.  "header size in bytes; do not change!!"
  
  	f := self sqImageFile: imageName Open: 'wb'.
  	f = nil ifTrue: "could not open the image file for writing"
  		[^self primitiveFail].
  
  	imageBytes := objectMemory imageSizeToWrite.
  	headerStart := self sqImage: f File: imageName StartLocation: headerSize + imageBytes.
  	self cCode: '/* Note: on Unix systems one could put an exec command here, padded to 512 bytes */'.
  	"position file to start of header"
  	self sqImageFile: f Seek: headerStart.
  
+ 	self putWord32: self imageFormatVersion toFile: f.
+ 	self putWord32: headerSize toFile: f.
- 	self putLong: self imageFormatVersion toFile: f.
- 	self putLong: headerSize toFile: f.
  	self putLong: imageBytes toFile: f.
  	self putLong: objectMemory baseAddressOfImage toFile: f.
  	self putLong: objectMemory specialObjectsOop toFile: f.
  	self putLong: objectMemory newObjectHash toFile: f.
  	self putLong: self ioScreenSize toFile: f.
  	self putLong: self getImageHeaderFlags toFile: f.
+ 	self putWord32: extraVMMemory toFile: f.
- 	self putLong: extraVMMemory toFile: f.
  	self putShort: desiredNumStackPages toFile: f.
  	self putShort: self unknownShortOrCodeSizeInKs toFile: f.
+ 	self putWord32: desiredEdenBytes toFile: f.
- 	self putLong: desiredEdenBytes toFile: f.
  	self putShort: (maxExtSemTabSizeSet ifTrue: [self ioGetMaxExtSemTableSize] ifFalse: [0]) toFile: f.
  	self putShort: the2ndUnknownShort toFile: f.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[self putLong: objectMemory firstSegmentBytes toFile: f.
  			 self putLong: objectMemory bytesLeftInOldSpace toFile: f.
  			 1 to: 2 do: [:i| self putLong: 0 toFile: f]	"Pad the rest of the header."]
  		ifFalse:
+ 			[1 to: 4 do: [:i| self putLong: 0 toFile: f]].  "Pad the rest of the header."
+ 
+ 	 objectMemory wordSize = 8 ifTrue:
+ 		[3 timesRepeat: [self putLong: 0 toFile: f]]. "Pad the rest of the header."
+ 
+ 	self assert: headerStart + headerSize = (self sqImageFilePosition: f).
- 			[1 to: 4 do: [:i| self putLong: 0 toFile: f]].  "fill remaining header words with zeros"
  	"position file after the header"
  	self sqImageFile: f Seek: headerStart + headerSize.
  
  	self successful ifFalse: "file write or seek failure"
  		[self sqImageFileClose: f.
  		 ^nil].
  
  	"write the image data"
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[bytesWritten := objectMemory writeImageSegmentsToFile: f]
  		ifFalse:
  			[bytesWritten := self sq: (self pointerForOop: objectMemory baseAddressOfImage)
  								Image: (self sizeof: #char)
  								File: imageBytes
  								Write: f].
  	self success: bytesWritten = imageBytes.
  	self sqImageFileClose: f!

Item was changed:
  ----- Method: StackInterpreter>>writeImageFileIOSimulation (in category 'image save/restore') -----
  writeImageFileIOSimulation
  	"Write the image header and heap contents to imageFile for snapshot.
+ 	 c.f. writeImageFileIO.  The game below is to maintain 64-bit alignment
+ 	 for all putLong:toFile: occurrences."
- 	 c.f. writeImageFileIO"
  	<doNotGenerate>
  	| headerSize file |
+ 	headerSize := objectMemory wordSize = 4 ifTrue: [64] ifFalse: [128].
- 	objectMemory wordSize = 4 ifFalse: [self error: 'Not rewritten for 64 bits yet'].
- 	headerSize := 64.
  
  	(file := FileStream fileNamed: self imageName) ifNil:
  		[self primitiveFail.
  		 ^nil].
+ 	[file binary.
+ 	 self putWord32: self imageFormatVersion toFile: file.
+ 	 self putWord32: headerSize toFile: file.
+ 	 {
+ 		objectMemory imageSizeToWrite.
+ 		objectMemory baseAddressOfImage.
+ 		objectMemory specialObjectsOop.
+ 		objectMemory lastHash.
+ 		self ioScreenSize.
+ 		self getImageHeaderFlags
+ 	 }
+ 		do: [:long | self putLong: long toFile: file].
- 	[
- 		file binary.
  
+ 	 self putWord32: (extraVMMemory ifNil: [0]) toFile: file.
+ 	 {	desiredNumStackPages. self unknownShortOrCodeSizeInKs } do:
+ 		[:short| self putShort: short toFile: file].
- 		{
- 			self imageFormatVersion.
- 			headerSize.
- 			objectMemory imageSizeToWrite.
- 			objectMemory baseAddressOfImage.
- 			objectMemory specialObjectsOop.
- 			objectMemory lastHash.
- 			self ioScreenSize.
- 			self getImageHeaderFlags.
- 			extraVMMemory ifNil: [0]
- 		}
- 			do: [:long | self putLong: long toFile: file].
  
+ 	 self putWord32: desiredEdenBytes toFile: file.
- 		{	desiredNumStackPages. self unknownShortOrCodeSizeInKs } do:
- 			[:short| self putShort: short toFile: file].
  
+ 	 {	maxExtSemTabSizeSet ifTrue: [self ioGetMaxExtSemTableSize] ifFalse: [0]. 0 } do:
+ 		[:short| self putShort: short toFile: file].
- 		self putLong: desiredEdenBytes toFile: file.
  
+ 	 objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[| bytesWritten |
+ 			 self putLong: objectMemory firstSegmentBytes toFile: file.
+ 			 self putLong: objectMemory bytesLeftInOldSpace toFile: file.
+ 			 2 timesRepeat: [self putLong: 0 toFile: file] "Pad the rest of the header.".
+ 			 objectMemory wordSize = 8 ifTrue:
+ 				[3 timesRepeat: [self putLong: 0 toFile: file]].
- 		{	maxExtSemTabSizeSet ifTrue: [self ioGetMaxExtSemTableSize] ifFalse: [0]. 0 } do:
- 			[:short| self putShort: short toFile: file].
  
+ 			 self assert: file position = headerSize.
+ 			"Position the file after the header."
+ 			file position: headerSize.
+ 			bytesWritten := objectMemory writeImageSegmentsToFile: file.
+ 			self assert: bytesWritten = objectMemory imageSizeToWrite]
+ 		ifFalse:
+ 			["Pad the rest of the header."
+ 			 4 timesRepeat: [self putLong: 0 toFile: file].
+ 			 objectMemory wordSize = 8 ifTrue:
+ 				[3 timesRepeat: [self putLong: 0 toFile: file]].
- 		objectMemory hasSpurMemoryManagerAPI
- 			ifTrue:
- 				[| bytesWritten |
- 				 self putLong: objectMemory firstSegmentBytes toFile: file.
- 				 self putLong: objectMemory bytesLeftInOldSpace toFile: file.
- 				 2 timesRepeat: [self putLong: 0 toFile: file "Pad the rest of the header."].
  
+ 			 self assert: file position = headerSize.
+ 			 "Position the file after the header."
+ 			 file position: headerSize.
- 				"Position the file after the header."
- 				file position: headerSize.
- 				bytesWritten := objectMemory writeImageSegmentsToFile: file.
- 				self assert: bytesWritten = objectMemory imageSizeToWrite]
- 			ifFalse:
- 				["Pad the rest of the header."
- 				4 timesRepeat: [self putLong: 0 toFile: file].
  
+ 			 "Write the object memory."
+ 			 objectMemory baseAddressOfImage // 4 + 1
+ 				to: objectMemory baseAddressOfImage + objectMemory imageSizeToWrite // 4
+ 				do: [:index |
+ 					self
+ 						putLong: (objectMemory memory at: index)
+ 						toFile: file]].
- 				"Position the file after the header."
- 				file position: headerSize.
- 
- 				"Write the object memory."
- 				objectMemory baseAddressOfImage // 4 + 1
- 					to: objectMemory baseAddressOfImage + objectMemory imageSizeToWrite // 4
- 					do: [:index |
- 						self
- 							putLong: (objectMemory memory at: index)
- 							toFile: file]].
  	
+ 	 self success: true]
+ 		 ensure: [file ifNotNil: [file close]]!
- 		self success: true
- 	]
- 		ensure: [file ifNotNil: [file close]]!

Item was removed:
- ----- Method: StackInterpreterSimulatorLSB>>putLong:toFile: (in category 'image save/restore') -----
- putLong: n toFile: f
- 	"Append the given 4-byte long word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	| remainingValue |
- 
- 	remainingValue := n.
- 	4 timesRepeat: [
- 		f nextPut: (remainingValue bitAnd: 16rFF).
- 		remainingValue := remainingValue bitShift: -8].
- 
- 	self success: true!

Item was removed:
- ----- Method: StackInterpreterSimulatorLSB>>putShort:toFile: (in category 'image save/restore') -----
- putShort: n toFile: f
- 	"Append the given 2-byte half-word to the given file in my byte order. (Bytes will be swapped, if necessary, when the image is read on a different platform.) Set successFlag to false if the write fails."
- 
- 	| remainingValue |
- 
- 	remainingValue := n.
- 	2 timesRepeat: [
- 		f nextPut: (remainingValue bitAnd: 16rFF).
- 		remainingValue := remainingValue bitShift: -8].
- 
- 	self success: true!



More information about the Vm-dev mailing list