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

commits at source.squeak.org commits at source.squeak.org
Wed Oct 9 18:18:15 UTC 2013


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

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

Name: VMMaker.oscog-eem.445
Author: eem
Time: 9 October 2013, 11:15:25.262 am
UUID: b08bb261-b9d0-45fc-b81f-43c1b12d7352
Ancestors: VMMaker.oscog-eem.444

Implement writing the segmented Spur image to the snapshot file.

Update class comment of SpurMemoryManager to describe recently
added inst vars.

Update comment of LittleEndianBitmap>>byteAt:put:.

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

Item was changed:
  ----- Method: LittleEndianBitmap>>byteAt:put: (in category 'accessing') -----
  byteAt: byteAddress put: byte
+ 	"Insert a byte into a Bitmap (little-endian version).  N.B. Signedness will be lost since byteAt: answers non-negative values.
+ 	 We can add a signedByteAt: if needed."
- 	"Insert a byte into a Bitmap (little-endian version).  N.B. SIgnedness will be lost since byteAt: ansers non-negative values."
  	| value longWord shift lowBits longAddr |
  	(byte < 0 or:[byte > 255]) ifTrue:[^self errorImproperStore].
  	value := byte < 0
  				ifTrue: [byte < 128 ifTrue:
  							[self errorImproperStore].
  						16rFF bitAnd: byte]
  				ifFalse: [16rFF < byte ifTrue:
  							[self errorImproperStore].
  						byte].
  	lowBits := byteAddress - 1 bitAnd: 3.
  	longWord := self at: (longAddr := (byteAddress - 1 - lowBits) // 4 + 1).
  	shift := lowBits * 8.
  	longWord := longWord
  				- (longWord bitAnd: (16rFF bitShift: shift)) 
  				+ (value bitShift: shift).
  	self at: longAddr put: longWord.
  	^byte!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeSpurObjectRepresentationConstants (in category 'class initialization') -----
  initializeSpurObjectRepresentationConstants
  	"SpurMemoryManager initializeSpurObjectRepresentationConstants"
+ 	BecamePointerObjectFlag := 1.
- 	BecameClassFlag := 1.
  	BecameCompiledMethodFlag := 2.
+ 	"BecameClassFlag := 4" "this turns out not to be actionable"
+ !
- 	BecamePointerObjectFlag := 4!

Item was added:
+ ----- Method: SpurMemoryManager>>baseAddressOfImage (in category 'snapshot') -----
+ baseAddressOfImage
+ 	^newSpaceLimit!

Item was changed:
  ----- Method: SpurMemoryManager>>becomeEffectFlagsFor: (in category 'become implementation') -----
  becomeEffectFlagsFor: objOop
  	"Answer the appropriate become effect flags for objOop, or 0 if none.
  	 The effect flags affect how much work is done after the become in
  	 following forwarding pointers."
  	<inline: false>
  	^(self isPointersNonImm: objOop)
  		ifTrue:
+ 			[BecamePointerObjectFlag
+ 			"older code that identified class objects, but it isn't helpful:"
+ 			"| hash |
- 			[| hash |
  			 (hash := self rawHashBitsOf: objOop) = 0
+ 				ifTrue: ""Can't identify an abstract class by the class table; it may not be there-in.""
- 				ifTrue: "Can't identify an abstract class by the class table; it may not be there-in."
  					[(coInterpreter objCouldBeClassObj: objOop)
  						ifTrue: [BecamePointerObjectFlag + BecameClassFlag]
  						ifFalse: [BecamePointerObjectFlag]]
+ 				ifFalse: ""if an object has a hash and it's a class it must be in the table.""
- 				ifFalse: "if an object has a hash and it's a class it must be in the table."
  					[(self classAtIndex: hash) = objOop
  						ifTrue: [BecamePointerObjectFlag + BecameClassFlag]
+ 						ifFalse: [BecamePointerObjectFlag]]"]
- 						ifFalse: [BecamePointerObjectFlag]]]
  		ifFalse:
  			[(self isCompiledMethod: objOop)
  				ifTrue: [BecameCompiledMethodFlag]
  				ifFalse: [0]]!

Item was added:
+ ----- Method: SpurMemoryManager>>firstSegmentBytes (in category 'snapshot') -----
+ firstSegmentBytes
+ 	<doNotGenerate>
+ 	^segmentManager firstSegmentBytes!

Item was added:
+ ----- Method: SpurMemoryManager>>imageSizeToWrite (in category 'snapshot') -----
+ imageSizeToWrite
+ 	^segmentManager totalBytesInSegments!

Item was added:
+ ----- Method: SpurSegmentInfo>>printOn: (in category 'printing') -----
+ printOn: aStream
+ 	super printOn: aStream.
+ 	self class instVarNames do:
+ 		[:name|
+ 		aStream space; nextPutAll: name; space; print: (self instVarNamed: name)]!

Item was added:
+ ----- Method: SpurSegmentManager>>firstSegmentBytes (in category 'snapshot') -----
+ firstSegmentBytes
+ 	^(segments at: 0) segSize!

Item was added:
+ ----- Method: SpurSegmentManager>>totalBytesInSegments (in category 'snapshot') -----
+ totalBytesInSegments
+ 	| total |
+ 	total := 0.
+ 	0 to: numSegments - 1 do:
+ 		[:i|
+ 		total := total + (segments at: i) segSize].
+ 	^total!

Item was added:
+ ----- Method: SpurSegmentManager>>writeImageToFile: (in category 'snapshot') -----
+ writeImageToFile: aBinaryStream
+ 	| total |
+ 	total := 0.
+ 	0 to: numSegments - 1 do:
+ 		[:i|
+ 		total := total + (self writeSegment: (segments at: i) toFile: aBinaryStream)].
+ 	^total!

Item was added:
+ ----- Method: SpurSegmentManager>>writeSegment:toFile: (in category 'snapshot') -----
+ writeSegment: aSpurSegmentInfo toFile: aBinaryStream
+ 	<var: 'aSpurSegmentInfo' type: 'SpurSegmentInfo *'>
+ 	<var: 'aSpurSegmentInfo' type: #'FILE *'>
+ 	^self cCode:
+ 			[self
+ 				sq: aSpurSegmentInfo start
+ 				Image: aSpurSegmentInfo segSize
+ 				File: 1
+ 				Write: aBinaryStream]
+ 		inSmalltalk:
+ 			[aBinaryStream
+ 				next: aSpurSegmentInfo segSize / 4
+ 				putAll: manager memory
+ 				startingAt: aSpurSegmentInfo start / 4 + 1.
+ 			 aSpurSegmentInfo segSize]!

Item was changed:
  ----- Method: StackInterpreter>>initializeInterpreter: (in category 'initialization') -----
  initializeInterpreter: bytesToShift 
  	"Initialize Interpreter state before starting execution of a new image."
  	interpreterProxy := self sqGetInterpreterProxy.
  	self dummyReferToProxy.
  	objectMemory initializeObjectMemory: bytesToShift.
  	self checkAssumedCompactClasses.
  	primFailCode := 0.
  	self initializeExtraClassInstVarIndices.
  	stackLimit := 0. "This is also the initialization flag for the stack system."
  	stackPage := overflowedPage := 0.
  	extraFramesToMoveOnOverflow := 0.
  	method := newMethod := objectMemory nilObject.
  	self cCode: [self cppIf: MULTIPLEBYTECODESETS ifTrue: [bytecodeSetSelector := 0]]
  		inSmalltalk: [bytecodeSetSelector := 0].
  	methodDictLinearSearchLimit := 8.
  	self flushMethodCache.
  	self flushAtCache.
  	self initialCleanup.
  	highestRunnableProcessPriority := 0.
  	nextProfileTick := 0.
  	profileSemaphore := objectMemory nilObject.
  	profileProcess := objectMemory nilObject.
  	profileMethod := objectMemory nilObject.
  	nextPollUsecs := 0.
  	nextWakeupUsecs := 0.
+ 	tempOop := theUnknownShort := 0.
- 	tempOop := 0.
  	interruptKeycode := 2094. "cmd-. as used for Mac but no other OS"
  	interruptPending := false.
  	inIOProcessEvents := 0.
+ 	fullScreenFlag := 0.
  	deferDisplayUpdates := false.
  	pendingFinalizationSignals := statPendingFinalizationSignals := 0.
  	globalSessionID := 0.
+ 	[globalSessionID = 0] whileTrue:
+ 		[globalSessionID := self
+ 							cCode: [(self time: #NULL) + self ioMSecs]
+ 							inSmalltalk: [(Random new next * SmallInteger maxVal) asInteger]].
- 	[globalSessionID = 0]
- 		whileTrue: [globalSessionID := self
- 						cCode: 'time(NULL) + ioMSecs()'
- 						inSmalltalk: [(Random new next * SmallInteger maxVal) asInteger]].
  	jmpDepth := 0.
  	longRunningPrimitiveStartUsecs :=
  	longRunningPrimitiveStopUsecs := 0.
  	maxExtSemTabSizeSet := false.
  	statForceInterruptCheck := 0.
  	statStackOverflow := 0.
  	statCheckForEvents := 0.
  	statProcessSwitch := 0.
  	statIOProcessEvents := 0.
  	statStackPageDivorce := 0!

Item was changed:
  ----- Method: StackInterpreterSimulator>>writeImageFileIO (in category 'image save/restore') -----
  writeImageFileIO
  	"Write the image to a file as an image snapshot."
  
  	| headerSize file |
  	BytesPerWord = 4 ifFalse: [self error: 'Not rewritten for 64 bits yet'].
  	headerSize := 64.
  
  	(file := FileStream fileNamed: imageName) ifNil:
  		[self primitiveFail.
  		 ^nil].
  	[
  		file binary.
  
  		{
  			self imageFormatVersion.
  			headerSize.
  			objectMemory imageSizeToWrite.
  			objectMemory baseAddressOfImage.
  			objectMemory specialObjectsOop.
  			objectMemory lastHash.
  			self ioScreenSize.
  			self getImageHeaderFlags.
+ 			extraVMMemory ifNil: [0]
- 			extraVMMemory
  		}
  			do: [:long | self putLong: long toFile: file].
  
  		{	desiredNumStackPages. self unknownShortOrCodeSizeInKs } do:
  			[:short| self putShort: short toFile: file].
  
  		self putLong: desiredEdenBytes toFile: file.
  
  		{	maxExtSemTabSizeSet ifTrue: [self ioGetMaxExtSemTableSize] ifFalse: [0]. 0 } do:
  			[:short| self putShort: short toFile: file].
  
  		objectMemory hasSpurMemoryManagerAPI
  			ifTrue:
  				[| bytesWritten |
  				 self putLong: objectMemory firstSegmentBytes toFile: file."Pad the rest of the header."
  				 3 timesRepeat: [self putLong: 0 toFile: file].
  
  				"Position the file after the header."
  				file position: headerSize.
  				bytesWritten := objectMemory segmentManager writeImageToFile: file.
  				self assert: bytesWritten = objectMemory imageSizeToWrite]
  			ifFalse:
  				["Pad the rest of the header."
  				4 timesRepeat: [self putLong: 0 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]]!

Item was changed:
  VMBasicConstants subclass: #VMSpurObjectRepresentationConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BecameCompiledMethodFlag BecamePointerObjectFlag'
- 	classVariableNames: 'BecameClassFlag BecameCompiledMethodFlag BecamePointerObjectFlag'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!



More information about the Vm-dev mailing list