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

commits at source.squeak.org commits at source.squeak.org
Tue Oct 8 22:25:14 UTC 2013


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

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

Name: VMMaker.oscog-eem.442
Author: eem
Time: 8 October 2013, 3:20:59.392 pm
UUID: e65a62ab-94da-4d61-934d-e60a36da3791
Ancestors: VMMaker.oscog-eem.441

More uses of allObjectsDo: in place of presumptious open-coded loop.

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

Item was changed:
  ----- Method: CoInterpreter>>ensureAllContextsHaveBytecodePCsOrAreBereaved (in category 'frame access') -----
  ensureAllContextsHaveBytecodePCsOrAreBereaved
  	"Enumerate all contexts preparing them for a snapshot.  Map all native pcs to bytecoded pcs.
  	 Convert widowed contexts to single contexts so that the snapshot contains only single contexts.
  	 This allows the being married test to avoid checking for a context's frame pointer being in bounds
  	 since all frame pointers must have been created in the current system and so be in bounds.
  	 Thanks to Greg Nuyens for this idea."
+ 	objectMemory allObjectsDo:
+ 		[:oop|
+ 		 (objectMemory isContextNonImm: oop) ifTrue:
- 	| oop decodedIP |
- 	oop := objectMemory firstObject.
- 	[oop < objectMemory freeStart] whileTrue:
- 		[((objectMemory isFreeObject: oop) not
- 		   and: [objectMemory isContextNonImm: oop]) ifTrue:
  			[(self isMarriedOrWidowedContext: oop)
  				ifTrue: "The stack pages have already been discarded.  Any remaining married contexts are actually widows."
  					[self markContextAsDead: oop]
  				ifFalse:
+ 					[| decodedIP |
+ 					decodedIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: oop.
- 					[decodedIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: oop.
  					((objectMemory isIntegerObject: decodedIP)
  					 and: [decodedIP signedIntFromLong < 0]) ifTrue:
  						[decodedIP := self mustMapMachineCodePC: (objectMemory integerValueOf: decodedIP)
  											context: oop.
+ 						 objectMemory storePointerUnchecked: InstructionPointerIndex ofObject: oop withValue: decodedIP]]]]!
- 						 objectMemory storePointerUnchecked: InstructionPointerIndex ofObject: oop withValue: decodedIP]]].
- 		 oop := objectMemory objectAfter: oop]!

Item was changed:
  ----- Method: CoInterpreter>>ensureAllContextsWithMethodHaveBytecodePCs: (in category 'frame access') -----
  ensureAllContextsWithMethodHaveBytecodePCs: methodObj
  	"Map all native pcs to bytecoded pcs in all contexts on methodObj.
  	 Used to implement primitiveVoidVMStateForMethod."
+ 	objectMemory allObjectsDo:
+ 		[:oop|
+ 		 ((objectMemory isContextNonImm: oop)
+ 		  and: [(objectMemory fetchPointer: MethodIndex ofObject: oop) = methodObj]) ifTrue:
- 	| oop |
- 	oop := objectMemory firstObject.
- 	[oop < objectMemory freeStart] whileTrue:
- 		[((objectMemory isFreeObject: oop) not
- 		  and: [(objectMemory isContextNonImm: oop)
- 		  and: [(objectMemory fetchPointer: MethodIndex ofObject: oop) = methodObj]]) ifTrue:
  			[(self isMarriedOrWidowedContext: oop)
  				ifTrue:
  					[(self checkIsStillMarriedContext: oop currentFP: stackPage headFP) ifTrue:
  						[self assert: (self isMachineCodeFrame: (self frameOfMarriedContext: oop)) not]]
  				ifFalse:
+ 					[self ensureContextHasBytecodePC: oop]]]!
- 					[self ensureContextHasBytecodePC: oop]].
- 		 oop := objectMemory objectAfter: oop]!

Item was changed:
  ----- Method: CogVMSimulator>>allObjectsSelect: (in category 'debug support') -----
  allObjectsSelect: objBlock
  	"self allObjectsSelect: [:oop | (self baseHeader: oop) = 1234]"
  
+ 	| selected |
- 	| oop selected |
- 	oop := objectMemory firstObject.
  	selected := OrderedCollection new.
+ 	objectMemory allObjectsDo:
+ 		[:oop| (objBlock value: oop) ifTrue: [selected addLast: oop]].
- 	[oop < objectMemory endOfMemory] whileTrue:
- 			[(objectMemory isFreeObject: oop)
- 				ifFalse: [(objBlock value: oop) ifTrue: [selected addLast: oop]].
- 			oop := objectMemory objectAfter: oop].
  	^ selected!

Item was changed:
  ----- Method: CogVMSimulator>>objectBefore: (in category 'testing') -----
  objectBefore: addr
+ 	| prev |
+ 	objectMemory allObjectsDo:
+ 		[:oop|
+ 		"look here if debugging prev obj overlapping this one"
+ 		oop >= addr ifTrue: [^prev].
+ 		prev := oop].
- 	| oop prev |
- 	oop := objectMemory firstObject.
- 	[oop < objectMemory endOfMemory] whileTrue:
- 		[prev := oop.  "look here if debugging prev obj overlapping this one"
- 		oop := objectMemory objectAfter: oop.
- 		oop >= addr ifTrue: [^ prev]].
  	^0!

Item was changed:
  ----- Method: StackInterpreter>>printAllStacks (in category 'debug printing') -----
  printAllStacks
  	"Print all the stacks of all running processes, including those that are currently suspended."
  	<api>
+ 	| classObj proc semaphoreClass mutexClass schedLists p processList |
- 	| oop classObj proc semaphoreClass mutexClass schedLists p processList |
  	<inline: false>
  	proc := self activeProcess.
  	self printNameOfClass: (objectMemory fetchClassOf: proc) count: 5; space; printHex: proc.
  	self print: ' priority '; printNum: (self quickFetchInteger: PriorityIndex ofObject: proc); cr.
  	self printCallStackFP: framePointer. "first the current activation"
  	semaphoreClass := objectMemory classSemaphore.
  	mutexClass := objectMemory classMutex.
+ 	objectMemory allObjectsDo:
+ 		[:oop|
+ 		classObj := objectMemory fetchClassOfNonImm: oop.
- 	oop := objectMemory firstObject.
- 	[self oop: oop isLessThan: objectMemory freeStart] whileTrue:
- 		[classObj := objectMemory fetchClassOfNonImm: oop.
  		 (classObj = semaphoreClass
  		  or: [classObj = mutexClass]) ifTrue:
+ 			[self printProcsOnList: oop]].
- 			[self printProcsOnList: oop].
- 		 oop := objectMemory objectAfter: oop].
  	schedLists := objectMemory fetchPointer: ProcessListsIndex ofObject: self schedulerPointer.
  	p := highestRunnableProcessPriority = 0
  			ifTrue: [objectMemory fetchWordLengthOf: schedLists]
  			ifFalse: [highestRunnableProcessPriority].
  	p - 1 to: 0 by: -1 do:
  		[:pri|
  		processList := objectMemory fetchPointer: pri ofObject: schedLists.
  		(self isEmptyList: processList) ifFalse:
  			[self cr; print: 'processes at priority '; printNum: pri + 1.
  			 self printProcsOnList: processList]]!

Item was changed:
  ----- Method: StackInterpreter>>reverseBytesInImage (in category 'image save/restore') -----
  reverseBytesInImage
  	"Byte-swap all words in memory after reading in the entire image file with bulk read. Contributed by Tim Rowledge."
  
  	"First, byte-swap every word in the image. This fixes objects headers."
  	objectMemory reverseBytesFrom: objectMemory startOfMemory to: objectMemory freeStart.
  
+ 	"Second, return the bytes of bytes-type objects to their
+ 	 orginal order, and perform any other format conversions."
+ 	self updateObjectsPostByteSwap!
- 	"Second, return the bytes of bytes-type objects to their orginal order, and perform any
- 	 other format conversions."
- 	self updateObjectsPostByteSwapFrom: objectMemory firstObject to: objectMemory freeStart!

Item was added:
+ ----- Method: StackInterpreter>>updateObjectsPostByteSwap (in category 'image save/restore') -----
+ updateObjectsPostByteSwap
+ 	"Byte-swap the words of all bytes objects in the image, including Strings, ByteArrays,
+ 	 and CompiledMethods. This returns these objects to their original byte ordering
+ 	 after blindly byte-swapping the entire image. For compiled  methods, byte-swap
+ 	 only their bytecodes part. Ensure floats are in platform-order."
+ 	| swapFloatWords |
+ 	swapFloatWords := objectMemory vmEndianness ~= imageFloatsBigEndian.
+ 	self assert: ClassFloatCompactIndex ~= 0.
+ 	objectMemory allObjectsDo:
+ 		[:oop| | fmt wordAddr methodHeader temp |
+ 		fmt := objectMemory formatOf: oop.
+ 		 fmt >= self firstByteFormat ifTrue: "oop contains bytes"
+ 			[wordAddr := oop + BaseHeaderSize.
+ 			fmt >= self firstCompiledMethodFormat ifTrue: "compiled method; start after methodHeader and literals"
+ 				[methodHeader := self longAt: oop + BaseHeaderSize.
+ 				 wordAddr := wordAddr + (((self literalCountOfHeader: methodHeader) + LiteralStart) * BytesPerWord)].
+ 			objectMemory reverseBytesFrom: wordAddr to: oop + (objectMemory sizeBitsOf: oop)].
+ 		 fmt = self firstLongFormat ifTrue: "Bitmap, Float etc"
+ 			[(swapFloatWords
+ 			  and: [(objectMemory compactClassIndexOf: oop) = ClassFloatCompactIndex])
+ 				ifTrue:
+ 					[temp := self longAt: oop + BaseHeaderSize.
+ 					 self longAt: oop + BaseHeaderSize put: (self longAt: oop + BaseHeaderSize + 4).
+ 					 self longAt: oop + BaseHeaderSize + 4 put: temp]
+ 				ifFalse:
+ 					[BytesPerWord = 8 ifTrue: "Object contains 32-bit half-words packed into 64-bit machine words."
+ 						[wordAddr := oop + BaseHeaderSize.
+ 						 objectMemory reverseWordsFrom: wordAddr to: oop + (objectMemory sizeBitsOf: oop)]]]]!

Item was removed:
- ----- Method: StackInterpreter>>updateObjectsPostByteSwapFrom:to: (in category 'image save/restore') -----
- updateObjectsPostByteSwapFrom: startOop to: stopAddr 
- 	"Byte-swap the words of all bytes objects in a range of the 
- 	 image, including Strings, ByteArrays, and CompiledMethods.
- 	 This returns these objects to their original byte ordering 
- 	 after blindly byte-swapping the entire image. For compiled 
- 	 methods, byte-swap only their bytecodes part.
- 	 Ensure floats are in platform-order."
- 	| oop fmt wordAddr methodHeader swapFloatWords temp |
- 	swapFloatWords := objectMemory vmEndianness ~= imageFloatsBigEndian.
- 	self assert: ClassFloatCompactIndex ~= 0.
- 	oop := startOop.
- 	[self oop: oop isLessThan: stopAddr] whileTrue:
- 		[(objectMemory isFreeObject: oop) ifFalse:
- 			[fmt := objectMemory formatOf: oop.
- 			 fmt >= self firstByteFormat ifTrue: "oop contains bytes"
- 				[wordAddr := oop + BaseHeaderSize.
- 				fmt >= self firstCompiledMethodFormat ifTrue: "compiled method; start after methodHeader and literals"
- 					[methodHeader := self longAt: oop + BaseHeaderSize.
- 					 wordAddr := wordAddr + BytesPerWord + ((methodHeader >> 10 bitAnd: 255) * BytesPerWord)].
- 				objectMemory reverseBytesFrom: wordAddr to: oop + (objectMemory sizeBitsOf: oop)].
- 			 fmt = self firstLongFormat ifTrue: "Bitmap, Float etc"
- 				[(swapFloatWords
- 				  and: [(objectMemory compactClassIndexOf: oop) = ClassFloatCompactIndex])
- 					ifTrue:
- 						[temp := self longAt: oop + BaseHeaderSize.
- 						 self longAt: oop + BaseHeaderSize put: (self longAt: oop + BaseHeaderSize + 4).
- 						 self longAt: oop + BaseHeaderSize + 4 put: temp]
- 					ifFalse:
- 						[BytesPerWord = 8 ifTrue: "Object contains 32-bit half-words packed into 64-bit machine words."
- 							[wordAddr := oop + BaseHeaderSize.
- 							 objectMemory reverseWordsFrom: wordAddr to: oop + (objectMemory sizeBitsOf: oop)]]]].
- 			oop := objectMemory objectAfter: oop]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>objectBefore: (in category 'testing') -----
  objectBefore: addr
+ 	| prev |
+ 	objectMemory allObjectsDo:
+ 		[:oop|
+ 		"look here if debugging prev obj overlapping this one"
+ 		oop >= addr ifTrue: [^prev].
+ 		prev := oop].
- 	| oop prev |
- 	oop := objectMemory firstObject.
- 	[oop < objectMemory endOfMemory] whileTrue:
- 		[prev := oop.  "look here if debugging prev obj overlapping this one"
- 		oop := objectMemory objectAfter: oop.
- 		oop >= addr ifTrue: [^ prev]].
  	^0!



More information about the Vm-dev mailing list