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

commits at source.squeak.org commits at source.squeak.org
Wed May 28 14:47:43 UTC 2014


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

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

Name: VMMaker.oscog-eem.734
Author: eem
Time: 28 May 2014, 7:45:09.663 am
UUID: d6a50836-2b47-4425-a81b-07dcc902faaa
Ancestors: VMMaker.oscog-eem.733

Spur:
Fix bug in sortedFreeListPairwiseReverseDo:.  Post block
evaluation, free cannot be relied upon, so reconstruct the
position in the enumeration from prevPrevFree and
prevFree before moving on.

Cogit:
Make sure genMethodAbortTrampolineFor: has the same
linkRegister code as genMethodAbortTrampoline.

Simulator:
Eliminate the cone inst var.  cloneSimulation is, of course,
fork, so only the parent slot is needed.

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

Item was changed:
  ----- Method: CogVMSimulator>>cloneSimulation (in category 'debug support') -----
  cloneSimulation
  	| savedDisplayView savedDisplayForm savedQuitBlock savedTranscript |
- 	self setClone: nil.
  	savedDisplayView := displayView. displayView := nil.
  	savedDisplayForm := displayForm. displayForm = nil.
  	savedQuitBlock := quitBlock. quitBlock := nil.
  	savedTranscript := transcript. transcript := nil.
  
  	^[| theClone |
  	 Smalltalk garbageCollect.
  	 theClone := self veryDeepCopy.
  	 theClone parent: self; transcript: Transcript.
  	 theClone objectMemory parent: objectMemory.
- 	 self setClone: theClone.
- 	 objectMemory setClone: theClone objectMemory.
  	 theClone]
  		ensure:
  			[displayView := savedDisplayView.
  			 displayForm = savedDisplayForm.
  			 quitBlock := savedQuitBlock.
  			 transcript := savedTranscript]!

Item was changed:
  Spur32BitMemoryManager subclass: #Spur32BitMMLESimulator
+ 	instanceVariableNames: 'parent bootstrapping'
- 	instanceVariableNames: 'clone parent bootstrapping'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManagerSimulation'!

Item was removed:
- ----- Method: Spur32BitMMLESimulator>>getClone (in category 'accessing') -----
- getClone
- 
- 	^ clone!

Item was changed:
  ----- Method: Spur32BitMMLESimulator>>globalGarbageCollect (in category 'gc - global') -----
  globalGarbageCollect
  	"If we're /not/ a clone, clone the VM and push it over the cliff.
  	 If it survives, destroy the clone and continue.  We should be OK until next time."
  	parent ifNil:
  		[[coInterpreter cloneSimulation objectMemory globalGarbageCollect]
  			on: Halt
  			do: [:ex|
  				(ex messageText beginsWith: 'GC number')
  					ifTrue:
  						[Transcript cr; cr; show: ex messageText; cr; cr.
  						 ex resume]
  					ifFalse: [ex pass]].
- 		 coInterpreter setClone: nil.
- 		 self setClone: nil.
  		 Smalltalk garbageCollect].
  	^super globalGarbageCollect!

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

Item was removed:
- ----- Method: Spur32BitMMLESimulator>>setClone: (in category 'accessing') -----
- setClone: aSpurMMSimulator
- 
- 	clone := aSpurMMSimulator!

Item was changed:
  ----- Method: SpurMemoryManager>>sortedFreeListPairwiseReverseDo: (in category 'compaction') -----
  sortedFreeListPairwiseReverseDo: aBinaryBlock
  	"Evaluate aBinaryBlock with adjacent entries in the free list, from
  	 high address to low address.  The second argument is in fact the
  	 start of the next free chunk, not the free chunk itself.  Use
  	 endOfMemory - bridgeSize as the second argument in the first evaluation."
+ 	| free prevFree prevPrevFree |
- 	| free nextFree prevFree prevPrevFree |
  	<inline: true>
  	free := lastFreeChunk.
  	prevPrevFree := prevFree := 0.
  	[free ~= 0] whileTrue:
+ 		[aBinaryBlock value: free value: (prevFree = 0
- 		[nextFree := self nextInSortedFreeListLink: free given: prevFree.
- 		 self assert: (free = 0 or: [self isFreeObject: free]).
- 		 self assert: (prevFree = 0 or: [prevFree > free]).
- 	 	 aBinaryBlock value: free value: (prevFree = 0
  											ifTrue: [endOfMemory - self bridgeSize]
  											ifFalse: [self startOfObject: prevFree]).
+ 		 "post evaluation of aBinaryBlock the value of free may be invalid
+ 		  because moveARunOfObjectsStartingAt:upTo: may have filled it.
+ 		  So reconstruct the position in the enumeration."
+ 		 prevFree = 0
- 		 self assert: (prevFree = 0 or: [self isFreeObject: prevFree]).
- 		 self assert: (prevPrevFree = 0 or: [self isFreeObject: prevPrevFree]).
- 		 (self isFreeObject: free) ifFalse:
- 			[free := self nextInSortedFreeListLink: prevFree given: prevPrevFree].
- 		 (nextFree = 0 or: [self isFreeObject: nextFree])
  			ifTrue:
+ 				[self assert: free = lastFreeChunk.
+ 				 prevFree := lastFreeChunk.
+ 				 free := self nextInSortedFreeListLink: lastFreeChunk given: 0]
- 				[prevPrevFree := prevFree.
- 				 prevFree := free.
- 				 free := prevFree = firstFreeChunk ifTrue: [0] ifFalse: [nextFree]]
  			ifFalse:
+ 				[self assert: (self isFreeObject: prevFree).
+ 				 prevPrevFree = 0
+ 					ifTrue:
+ 						[self assert: free = (self nextInSortedFreeListLink: lastFreeChunk given: 0).
+ 						 prevPrevFree := lastFreeChunk.
+ 						 prevFree := self nextInSortedFreeListLink: lastFreeChunk given: 0]
+ 					ifFalse:
+ 						[self assert: (self isFreeObject: prevPrevFree).
+ 						 free := self nextInSortedFreeListLink: prevFree given: prevPrevFree.
+ 						 prevPrevFree := prevFree.
+ 						 prevFree := free].
+ 				 free := self nextInSortedFreeListLink: prevFree given: prevPrevFree]]
+ 
+ "| labels |
+  labels := Dictionary new.
+  labels
+ 	at: prevPrevFree put: 'ppf';
+ 	at: prevFree put: 'pf';
+ 	at: free put: 'f';
+ 	at: nextFree put: 'f'.
+  self sortedFreeListPairwiseReverseDo: [:a :b|
+ 		Transcript cr; print: a; space.
+ 		(labels at: a ifAbsent: []) ifNotNil: [:l| Transcript nextPutAll: l].
+ 		Transcript flush]"!
- 				[free := lastFreeChunk.
- 				 prevPrevFree := prevFree := 0.
- 				 [free > nextFree] whileTrue:
- 					[nextFree := self nextInSortedFreeListLink: free given: prevFree.
- 					 self assert: (self isFreeObject: nextFree).
- 					 prevPrevFree := prevFree.
- 					 prevFree := free.
- 					 free := nextFree]]]!

Item was changed:
  StackInterpreterPrimitives subclass: #StackInterpreterSimulator
+ 	instanceVariableNames: 'parent bootstrapping byteCount breakCount sendCount printSends printReturns traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES'
- 	instanceVariableNames: 'clone parent bootstrapping byteCount breakCount sendCount printSends printReturns traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
  
  !StackInterpreterSimulator commentStamp: 'eem 9/3/2013 11:05' prior: 0!
  This class defines basic memory access and primitive simulation so that the StackInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(StackInterpreterSimulator new openOn: Smalltalk imageName) test
  
  	((StackInterpreterSimulator newWithOptions: #(NewspeakVM true MULTIPLEBYTECODESETS true))
  		openOn: 'ns101.image') test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example of what Eliot uses to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  | vm |
  vm := StackInterpreterSimulator newWithOptions: #().
  vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
  vm setBreakSelector: #&.
  vm openAsMorph; run!

Item was changed:
  ----- Method: StackInterpreterSimulator>>cloneSimulation (in category 'debug support') -----
  cloneSimulation
  	| savedDisplayView savedDisplayForm savedQuitBlock savedTranscript |
- 	self setClone: nil.
  	savedDisplayView := displayView. displayView := nil.
  	savedDisplayForm := displayForm. displayForm = nil.
  	savedQuitBlock := quitBlock. quitBlock := nil.
  	savedTranscript := transcript. transcript := nil.
  
  	^[| theClone |
  	 Smalltalk garbageCollect.
  	 theClone := self veryDeepCopy.
  	 theClone parent: self; transcript: Transcript.
  	 theClone objectMemory parent: objectMemory.
- 	 self setClone: theClone.
- 	 objectMemory setClone: theClone objectMemory.
  	 theClone]
  		ensure:
  			[displayView := savedDisplayView.
  			 displayForm = savedDisplayForm.
  			 quitBlock := savedQuitBlock.
  			 transcript := savedTranscript]!

Item was removed:
- ----- Method: StackInterpreterSimulator>>getClone (in category 'accessing') -----
- getClone
- 
- 	^ clone!

Item was removed:
- ----- Method: StackInterpreterSimulator>>setClone: (in category 'accessing') -----
- setClone: aSpurMMSimulator
- 
- 	clone := aSpurMMSimulator!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMethodAbortTrampolineFor: (in category 'initialization') -----
+ genMethodAbortTrampolineFor: numArgs
- genMethodAbortTrampolineFor: numArgs 
- 	
  	"Generate the abort for a method.  This abort performs either a call of ceSICMiss:
  	 to handle a single-in-line cache miss or a call of ceStackOverflow: to handle a
  	 stack overflow.  It distinguishes the two by testing ResultReceiverReg.  If the
  	 register is zero then this is a stack-overflow because a) the receiver has already
  	 been pushed and so can be set to zero before calling the abort, and b) the
  	 receiver must always contain an object (and hence be non-zero) on SIC miss."
  	| jumpSICMiss |
  	<var: #jumpSICMiss type: #'AbstractInstruction *'>
  	opcodeIndex := 0.
  	self CmpCq: 0 R: ReceiverResultReg.
  	jumpSICMiss := self JumpNonZero: 0.
+ 	"on machines with a link register, pop the stack if the ReceiverResultReg = 0,
+ 	 i.e. if coming through the stack check abort; frame build has already pushed it."
+ 	backEnd hasLinkRegister ifTrue:
+ 		[self AddCq: BytesPerWord R: SPReg].
+ 
  	self compileTrampolineFor: #ceStackOverflow:
  		callJumpBar: true
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil.
  	jumpSICMiss jmpTarget: self Label.
  	backEnd genPushRegisterArgsForAbortMissNumArgs: numArgs.
  	^self genTrampolineFor: #ceSICMiss:
  		called: (self trampolineName: 'ceMethodAbort' numArgs: (numArgs <= self numRegArgs ifTrue: [numArgs] ifFalse: [-1]))
  		callJumpBar: true
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil
  		appendOpcodes: true!



More information about the Vm-dev mailing list