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

commits at source.squeak.org commits at source.squeak.org
Sat May 3 06:29:23 UTC 2014


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

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

Name: VMMaker.oscog-eem.700
Author: eem
Time: 2 May 2014, 11:24:44.355 pm
UUID: c41a767a-567a-4812-8b38-572c84e18390
Ancestors: VMMaker.oscog-eem.699

Spur:
Fix a mis-write bug in moveARunOfObjectsStartingAt:upTo:.

comment out the high-frequency calls to
checkTraversableSortedFreeList and delete a bogus call of same.

Simulator: toggle the breakpoint on fullDisplayUpdate

Slang: Add a non-spur configurations generator

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

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>moveARunOfObjectsStartingAt:upTo: (in category 'compaction') -----
+ moveARunOfObjectsStartingAt: startAddress upTo: limit
+ 	"startAddress = 175450576 ifTrue: [self halt]."
+ 	^super moveARunOfObjectsStartingAt: startAddress upTo: limit!

Item was changed:
  ----- Method: SpurMemoryManager>>moveARunOfObjectsStartingAt:upTo: (in category 'compaction') -----
  moveARunOfObjectsStartingAt: startAddress upTo: limit 
  	"Move the sequence of movable objects starting at startAddress.  Answer the start
  	 of the next sequence of movable objects after a possible run of unmovable objects,
  	 or the limit, if there are no more movable objects, or 0 if no more compaction can be
  	 done. Compaction is done when the search through the freeList has reached the
  	 address from which objects are being moved from.
  
  	 There are two broad cases to be dealt with here.  One is a run of smallish objects
  	 that can easily be moved into free chunks.  The other is a large object that is unlikely
  	 to fit in the typical free chunk. This second pig needs careful handling; it needs to be
  	 moved to the lowest place it will fit and not cause the scan to skip lots of smaller
  	 free chunks looking in vain for somewhere to put it."
  	| here hereObj hereObjHeader prevPrevFreeChunk prevFreeChunk thisFreeChunk maxFreeChunk |
  	here := startAddress.
  	hereObj := self objectStartingAt: startAddress.
  	hereObjHeader := self atLeastClassIndexHalfHeader: hereObj.
  	prevPrevFreeChunk := prevFreeChunk := 0.
  	thisFreeChunk := maxFreeChunk := firstFreeChunk.
  	[thisFreeChunk ~= 0] whileTrue:
  		[| freeBytes endOfFree nextFree destination there moved |
  
  		 "skip any initial immobile objects"
  		 [(self isMobileObjectHeader: hereObjHeader)] whileFalse:
  			[here := self addressAfter: hereObj.
  			 here >= limit ifTrue:
  				[^maxFreeChunk >= startAddress ifTrue: [0] ifFalse: [limit]].
  			 hereObj := self objectStartingAt: here.
  			 hereObjHeader := self atLeastClassIndexHalfHeader: hereObj].
  
  		 "grab a free chunk, and the following one, because we want to overwrite this one."
  		 self assert: ((self isFreeObject: firstFreeChunk) and: [self isFreeObject: thisFreeChunk]).
  		 freeBytes		:= self bytesInObject: thisFreeChunk.
  		 nextFree		:= self nextInSortedFreeListLink: thisFreeChunk given: prevFreeChunk.
  		 destination	:= self startOfObject: thisFreeChunk.
  		 endOfFree		:= destination + freeBytes.
  		 moved			:= false.
  		 maxFreeChunk	:= maxFreeChunk max: nextFree.
  		 self assert: (nextFree = 0 or: [self isFreeObject: nextFree]).
  
  		"move as many objects as will fit in freeBytes..."
  		 [there := self addressAfter: hereObj.
  		  (self isMobileObjectHeader: hereObjHeader)
  		  and: [there - here < (freeBytes - self allocationUnit)
  			    or: [there - here = freeBytes]]] whileTrue:
  			[moved := true.
  			 self mem: destination cp: here y: there - here.
  			 self forward: hereObj to: destination + (hereObj - here).
  			 destination := destination + (there - here).
  			 freeBytes := freeBytes - (there - here).
  			 hereObj := self objectStartingAt: there.
  			 here := there.
  			 hereObjHeader := self atLeastClassIndexHalfHeader: hereObj].
  
  		 moved
  			ifTrue: "we did overwrite it; we need to repair the free list"
  				[| nextNextFree |
- 				 thisFreeChunk ~= firstFreeChunk ifTrue:
- 					[self checkTraversableSortedFreeList].
  				 nextFree ~= 0 ifTrue:
  					[nextNextFree  := self nextInSortedFreeListLink: nextFree given: thisFreeChunk.
  					 self assert: (self isFreeObject: nextFree)].
  				 (destination > thisFreeChunk "if false couldn't move anything"
  				  and: [destination < endOfFree]) "if false, filled entire free chunk"
  					ifTrue:
  						[thisFreeChunk := self initFreeChunkWithBytes: endOfFree - destination at: destination.
  						 self inSortedFreeListLink: prevFreeChunk to: thisFreeChunk given: prevPrevFreeChunk.
  						 self inSortedFreeListLink: thisFreeChunk to: nextFree given: prevFreeChunk.
  						 nextFree ~= 0 ifTrue:
  							[self inSortedFreeListLink: nextFree to: nextNextFree given: thisFreeChunk].
  						 prevPrevFreeChunk := prevFreeChunk.
  						 prevFreeChunk := thisFreeChunk.
  						 thisFreeChunk := nextFree]
  					ifFalse:
  						[self inSortedFreeListLink: prevFreeChunk to: nextFree given: prevPrevFreeChunk.
  						 nextFree ~= 0 ifTrue:
  							[self inSortedFreeListLink: nextFree to: nextNextFree given: prevFreeChunk].
+ 						 thisFreeChunk := nextFree]]
- 						 thisFreeChunk := nextFree].
- 				 self checkTraversableSortedFreeList]
  			ifFalse: "out of space (or immobile object); move on up the free list..."
  				[prevPrevFreeChunk := prevFreeChunk.
  				 prevFreeChunk := thisFreeChunk.
  				 thisFreeChunk := nextFree].
  
  		 (self isMobileObjectHeader: hereObjHeader) ifFalse:
  			[^maxFreeChunk >= startAddress ifTrue: [0] ifFalse: [there]].
  
  		 "Was the loop stopped by a pig? If so, try and find space for it"
  		 there - here >= (self averageObjectSizeInBytes * 8) ifTrue: "256b in 32 bit, 512b in 64 bit"
  			[| usedChunk |
  			 usedChunk := self tryToMovePig: hereObj at: here end: there.
  			"if it couldn't be moved we need to advance, so always
  			 set here to there whether the pig was moved or not."
  			 hereObj := self objectStartingAt: there.
  			 here := there.
  			 hereObjHeader := self atLeastClassIndexHalfHeader: hereObj.
  			 "In general it's a bad idea to reset the enumeration; it leads to N^2 behaviour
  			  when encountering pigs.  But if the move affected the enumeration this is
  			  simpler than resetting the list pointers."
  			 (usedChunk = prevPrevFreeChunk
  			  or: [usedChunk = prevFreeChunk
+ 			  or: [usedChunk = thisFreeChunk]]) ifTrue:
- 			  or: [usedChunk = thisFreeChunk]]) ifTrue: "a bad idea; leads to N^2 behaviour when encountering pigs"
  				["reset the scan for free space back to the start of the list"
  				 prevPrevFreeChunk := prevFreeChunk := 0.
  				 thisFreeChunk := firstFreeChunk]].
  
  		((here > startAddress and: [there >= limit])
  		 or: [maxFreeChunk >= startAddress]) ifTrue:
  			[^maxFreeChunk >= startAddress ifTrue: [0] ifFalse: [there]]].!

Item was changed:
  ----- Method: SpurMemoryManager>>pigCompact (in category 'compaction') -----
  pigCompact
  	"Traverse the sorted free list, moving objects from the high-end of
  	 memory to the free objects in the low end of memory.  Return when
  	 the address at which objects are being copiecd to meets the address
  	 from which objects are being copied from."
  	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: 'pig compacting...'; flush].
  	self sortedFreeListPairwiseReverseDo:
  		[:low :high| | scanAddress |
  		 self cCode: '' inSmalltalk: [coInterpreter transcript nextPut: $.; flush].
  		 scanAddress := self addressAfter: low.
  		 [scanAddress < high] whileTrue:
  			[scanAddress := self moveARunOfObjectsStartingAt: scanAddress upTo: high.
  			 scanAddress = 0 ifTrue:
+ 				[^self]]].
+ 	self cCode: [] inSmalltalk: [self checkTraversableSortedFreeList]!
- 				[^self]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>tryToMovePig:at:end: (in category 'compaction') -----
  tryToMovePig: pigObj at: pigStart end: pigEnd
  	"Try to move a pig (a largish object) to a free chunk in low memory.
  	 Answer the freeChunk that was used to house the moved pig, or
  	 0 if no free chunk could be found."
  	| freeChunk prevFree prevPrevFree pigBytes nextNext |
  	prevPrevFree := prevFree := 0.
  	freeChunk := firstFreeChunk.
  	pigBytes := pigEnd - pigStart.
  	[freeChunk ~= 0 and: [freeChunk < pigObj]] whileTrue:
  		[| next dest chunkBytes newChunk |
  		 next			:= self nextInSortedFreeListLink: freeChunk given: prevFree.
  		 dest			:= self startOfObject: freeChunk.
  		 chunkBytes	:= (self addressAfter: freeChunk) - dest.
  		 (chunkBytes = pigBytes
  		  or: [chunkBytes - self allocationUnit > pigBytes]) ifTrue:
  			[self mem: dest cp: pigStart y: pigBytes.
  			 self forward: pigObj to: dest + (pigObj - pigStart).
  			 next ~= 0 ifTrue:
  				[nextNext  := self nextInSortedFreeListLink: next given: freeChunk].
  			 "now either shorten the chunk, or remove it, adjusting the links to keep the list sorted."
  			 pigBytes < chunkBytes "if false, filled entire free chunk"
  				ifTrue:
  					[newChunk := self initFreeChunkWithBytes: chunkBytes - pigBytes at: dest + pigBytes.
  					 self inSortedFreeListLink: prevFree to: newChunk given: prevPrevFree.
  					 self inSortedFreeListLink: newChunk to: next given: prevFree.
  					 next ~= 0 ifTrue:
  						[self inSortedFreeListLink: next to: nextNext given: newChunk]]
  				ifFalse:
  					[self inSortedFreeListLink: prevFree to: next given: prevPrevFree.
  					 next ~= 0 ifTrue:
  						[self inSortedFreeListLink: next to: nextNext given: prevFree]].
+ 			 "self checkTraversableSortedFreeList".
- 			 self checkTraversableSortedFreeList.
  			 ^freeChunk].
  		 prevPrevFree := prevFree.
  		 prevFree := freeChunk.
  		 freeChunk := next].
  	^0!

Item was changed:
  ----- Method: StackInterpreterSimulator>>fullDisplayUpdate (in category 'debug support') -----
  fullDisplayUpdate
+ 	"Preserve self successful when call asynchronously from Simulator"
  	| primFailCodeValue |
- 	self break.
  	primFailCodeValue := primFailCode.
  	self initPrimCall.
  	super fullDisplayUpdate.
  	primFailCode := primFailCodeValue!

Item was added:
+ ----- Method: VMMaker class>>generateAllNonSpurConfigurationsUnderVersionControl (in category 'configurations') -----
+ generateAllNonSpurConfigurationsUnderVersionControl
+ 	self generateNewspeakCogVM;
+ 		generateSqueakCogVM;
+ 		generateSqueakCogMTVM;
+ 		generateSqueakStackVM;
+ 		generateSqueakCogSistaVM!



More information about the Vm-dev mailing list