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

commits at source.squeak.org commits at source.squeak.org
Tue Jun 26 16:29:40 UTC 2012


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

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

Name: VMMaker.oscog-eem.172
Author: eem
Time: 26 June 2012, 9:27:13.912 am
UUID: c6173744-0587-45bd-9e94-4f7996c90e47
Ancestors: VMMaker.oscog-eem.171

Finish moving add of bytecodeSetSelector to fetchNextBytecode from
interpret.  Various simulation print/debug routines need to change
or revert.

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

Item was changed:
  ----- Method: CogVMSimulator>>logOfBytesVerify:fromFileNamed:fromStart: (in category 'testing') -----
  logOfBytesVerify: nBytes fromFileNamed: fileName fromStart: loggingStart
  	"Verify a questionable interpreter against a successful run"
  	"self logOfBytesVerify: 10000 fromFileNamed: 'clone32Bytecodes.log' "
  	
  	| logFile rightWord prevCtxt |
  	logFile := (FileStream readOnlyFileNamed: fileName) binary.
  	transcript clear.
  	byteCount := 0.
  	quitBlock := [^ self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	prevCtxt := 0.  prevCtxt := prevCtxt.
  	[byteCount < nBytes] whileTrue:
  		[
  "
  byteCount > 14560 ifTrue:
  [self externalizeIPandSP.
  prevCtxt = activeContext ifFalse:
   [prevCtxt := activeContext.
   transcript cr; nextPutAll: (self printTop: 2); endEntry].
  transcript cr; print: byteCount; nextPutAll: ': ' , (activeContext hex); space;
   print: (instructionPointer - method - (BaseHeaderSize - 2));
   nextPutAll: ': <' , (self byteAt: localIP) hex , '>'; space;
   nextPutAll: (self symbolic: currentBytecode at: localIP inMethod: method); space;
   print: (self stackPointerIndex - TempFrameStart + 1); endEntry.
  byteCount = 14590 ifTrue: [self halt]].
  "
  		loggingStart >= byteCount ifTrue:
  			[rightWord := logFile nextWord.
+ 			 currentBytecode = rightWord ifFalse:
- 			 currentBytecode + bytecodeSetSelector = rightWord ifFalse:
  				[self halt: 'halt at ', byteCount printString]].
+ 		self dispatchOn: currentBytecode in: BytecodeTable.
- 		self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		self incrementByteCount].
  	self externalizeIPandSP.
  	logFile close.
  	self inform: nBytes printString , ' bytecodes verfied.'!

Item was changed:
  ----- Method: CogVMSimulator>>logOfBytesWrite:toFileNamed:fromStart: (in category 'testing') -----
  logOfBytesWrite: nBytes toFileNamed: fileName fromStart: loggingStart
  	"Write a log file for testing a flaky interpreter on the same image"
  	"self logOfBytesWrite: 10000 toFileNamed: 'clone32Bytecodes.log' "
  	
  	| logFile |
  	logFile := (FileStream newFileNamed: fileName) binary.
  	transcript clear.
  	byteCount := 0.
  	quitBlock := [^ self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[byteCount < nBytes] whileTrue:
  		[byteCount >= loggingStart ifTrue:
+ 			[logFile nextWordPut: currentBytecode].
+ 		self dispatchOn: currentBytecode in: BytecodeTable.
- 			[logFile nextWordPut: currentBytecode + bytecodeSetSelector].
- 		self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		self incrementByteCount].
  	self externalizeIPandSP.
  	logFile close!

Item was changed:
  ----- Method: CogVMSimulator>>logOfSendsVerify:fromFileNamed:fromStart: (in category 'testing') -----
  logOfSendsVerify: nSends fromFileNamed: fileName fromStart: loggingStart
  	"Write a log file for testing a flaky interpreter on the same image"
  	"self logOfSendsWrite: 10000 toFileNamed: 'clone32Messages.log' "
  	
  	| logFile priorFrame rightSelector prevCtxt |
  	logFile := FileStream readOnlyFileNamed: fileName.
  	transcript clear.
  	byteCount := 0.
  	sendCount := 0.
  	priorFrame := localFP.
  	quitBlock := [^ self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	prevCtxt := 0.  prevCtxt := prevCtxt.
  	[sendCount < nSends] whileTrue:
  		[
  "
  byteCount>500 ifTrue:
  [byteCount>550 ifTrue: [self halt].
  self externalizeIPandSP.
  prevCtxt = localFP ifFalse:
   [prevCtxt := localFP.
   transcript cr; nextPutAll: (self printTop: 2); endEntry].
  transcript cr; print: byteCount; nextPutAll: ': ' , (localFP hex); space;
   print: (instructionPointer - method - (BaseHeaderSize - 2));
   nextPutAll: ': <' , (self byteAt: localIP) hex , '>'; space;
   nextPutAll: (self symbolic: currentBytecode at: localIP inMethod: method); space;
   print: (self stackPointerIndex - TempFrameStart + 1); endEntry.
  ].
  "
+ 		self dispatchOn: currentBytecode in: BytecodeTable.
+ 		localFP = priorFrame ifFalse:
- 		self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
- 		localFP == priorFrame ifFalse:
  			[sendCount := sendCount + 1.
  			 loggingStart >= sendCount ifTrue:
  				[rightSelector := logFile nextLine.
  				 (self stringOf: messageSelector) = rightSelector ifFalse:
  					[self halt: 'halt at ', sendCount printString]].
  			priorFrame := localFP].
  		self incrementByteCount].
  	self externalizeIPandSP.
  	logFile close.
  	self inform: nSends printString , ' sends verfied.'!

Item was changed:
  ----- Method: CogVMSimulator>>logOfSendsWrite:toFileNamed:fromStart: (in category 'testing') -----
  logOfSendsWrite: nSends toFileNamed: fileName fromStart: loggingStart
  	"Write a log file for testing a flaky interpreter on the same image"
  	"self logOfSendsWrite: 10000 toFileNamed: 'clone32Messages.log' fromStart: 2500"
  	
  	| logFile priorFrame |
  	logFile := FileStream newFileNamed: fileName.
  	transcript clear.
  	byteCount := 0.
  	sendCount := 0.
  	priorFrame := localFP.
  	quitBlock := [^ self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[sendCount < nSends] whileTrue:
+ 		[self dispatchOn: currentBytecode in: BytecodeTable.
- 		[self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		localFP == priorFrame ifFalse:
  			[sendCount >= loggingStart ifTrue:
  				[sendCount := sendCount + 1.
  				 logFile nextPutAll: (self stringOf: messageSelector); cr].
  			priorFrame := localFP].
  		self incrementByteCount].
  	self externalizeIPandSP.
  	logFile close!

Item was changed:
  ----- Method: CogVMSimulator>>printCurrentBytecodeOn: (in category 'debug printing') -----
  printCurrentBytecodeOn: aStream
  	| code |
  	code := currentBytecode radix: 16.
  	aStream ensureCr; print: localIP - method - 3; tab.
  	bytecodeSetSelector > 0 ifTrue:
  		[aStream nextPutAll: 'ALT '].
  	aStream
  		nextPut: (code size < 2
  					ifTrue: [$0]
  					ifFalse: [code at: 1]);
  		nextPut: code last; space;
+ 		nextPutAll: (BytecodeTable at: currentBytecode + 1);
- 		nextPutAll: (BytecodeTable at: currentBytecode + bytecodeSetSelector + 1);
  		space;
  		nextPut: $(; print: byteCount + 1; nextPut: $)!

Item was changed:
  ----- Method: StackInterpreterSimulator>>logOfBytesVerify:fromFileNamed:fromStart: (in category 'testing') -----
  logOfBytesVerify: nBytes fromFileNamed: fileName fromStart: loggingStart
  	"Verify a questionable interpreter against a successful run"
  	"self logOfBytesVerify: 10000 fromFileNamed: 'clone32Bytecodes.log' "
  	
  	| logFile rightWord prevCtxt |
  	logFile := (FileStream readOnlyFileNamed: fileName) binary.
  	transcript clear.
  	byteCount := 0.
  	quitBlock := [^ self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	prevCtxt := 0.  prevCtxt := prevCtxt.
  	[byteCount < nBytes] whileTrue:
  		[
  "
  byteCount > 14560 ifTrue:
  [self externalizeIPandSP.
  prevCtxt = activeContext ifFalse:
   [prevCtxt := activeContext.
   transcript cr; nextPutAll: (self printTop: 2); endEntry].
  transcript cr; print: byteCount; nextPutAll: ': ' , (activeContext hex); space;
   print: (instructionPointer - method - (BaseHeaderSize - 2));
   nextPutAll: ': <' , (self byteAt: localIP) hex , '>'; space;
   nextPutAll: (self symbolic: currentBytecode at: localIP inMethod: method); space;
   print: (self stackPointerIndex - TempFrameStart + 1); endEntry.
  byteCount = 14590 ifTrue: [self halt]].
  "
  		loggingStart >= byteCount ifTrue:
  			[rightWord := logFile nextWord.
  			 currentBytecode = rightWord ifFalse:
  				[self halt: 'halt at ', byteCount printString]].
+ 		self dispatchOn: currentBytecode in: BytecodeTable.
- 		self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		self incrementByteCount].
  	self externalizeIPandSP.
  	logFile close.
  	self inform: nBytes printString , ' bytecodes verfied.'!

Item was changed:
  ----- Method: StackInterpreterSimulator>>logOfBytesWrite:toFileNamed:fromStart: (in category 'testing') -----
  logOfBytesWrite: nBytes toFileNamed: fileName fromStart: loggingStart
  	"Write a log file for testing a flaky interpreter on the same image"
  	"self logOfBytesWrite: 10000 toFileNamed: 'clone32Bytecodes.log' "
  	
  	| logFile |
  	logFile := (FileStream newFileNamed: fileName) binary.
  	transcript clear.
  	byteCount := 0.
  	quitBlock := [^ self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[byteCount < nBytes] whileTrue:
  		[byteCount >= loggingStart ifTrue:
+ 			[logFile nextWordPut: currentBytecode].
+ 		self dispatchOn: currentBytecode in: BytecodeTable.
- 			[logFile nextWordPut: currentBytecode + bytecodeSetSelector].
- 		self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		self incrementByteCount].
  	self externalizeIPandSP.
  	logFile close!

Item was changed:
  ----- Method: StackInterpreterSimulator>>logOfSendsVerify:fromFileNamed:fromStart: (in category 'testing') -----
  logOfSendsVerify: nSends fromFileNamed: fileName fromStart: loggingStart
  	"Write a log file for testing a flaky interpreter on the same image"
  	"self logOfSendsWrite: 10000 toFileNamed: 'clone32Messages.log' "
  	
  	| logFile priorFrame rightSelector prevCtxt |
  	logFile := FileStream readOnlyFileNamed: fileName.
  	transcript clear.
  	byteCount := 0.
  	sendCount := 0.
  	priorFrame := localFP.
  	quitBlock := [^ self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	prevCtxt := 0.  prevCtxt := prevCtxt.
  	[sendCount < nSends] whileTrue:
  		[
  "
  byteCount>500 ifTrue:
  [byteCount>550 ifTrue: [self halt].
  self externalizeIPandSP.
  prevCtxt = localFP ifFalse:
   [prevCtxt := localFP.
   transcript cr; nextPutAll: (self printTop: 2); endEntry].
  transcript cr; print: byteCount; nextPutAll: ': ' , (localFP hex); space;
   print: (instructionPointer - method - (BaseHeaderSize - 2));
   nextPutAll: ': <' , (self byteAt: localIP) hex , '>'; space;
   nextPutAll: (self symbolic: currentBytecode at: localIP inMethod: method); space;
   print: (self stackPointerIndex - TempFrameStart + 1); endEntry.
  ].
  "
+ 		self dispatchOn: currentBytecode in: BytecodeTable.
- 		self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		localFP = priorFrame ifFalse:
  			[sendCount := sendCount + 1.
  			 loggingStart >= sendCount ifTrue:
  				[rightSelector := logFile nextLine.
  				 (self stringOf: messageSelector) = rightSelector ifFalse:
  					[self halt: 'halt at ', sendCount printString]].
  			priorFrame := localFP].
  		self incrementByteCount].
  	self externalizeIPandSP.
  	logFile close.
  	self inform: nSends printString , ' sends verfied.'!

Item was changed:
  ----- Method: StackInterpreterSimulator>>logOfSendsWrite:toFileNamed:fromStart: (in category 'testing') -----
  logOfSendsWrite: nSends toFileNamed: fileName fromStart: loggingStart
  	"Write a log file for testing a flaky interpreter on the same image"
  	"self logOfSendsWrite: 10000 toFileNamed: 'clone32Messages.log' "
  	
  	| logFile priorFrame |
  	logFile := FileStream newFileNamed: fileName.
  	transcript clear.
  	byteCount := 0.
  	sendCount := 0.
  	priorFrame := localFP.
  	quitBlock := [^ self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[sendCount < nSends] whileTrue:
+ 		[self dispatchOn: currentBytecode in: BytecodeTable.
- 		[self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		localFP = priorFrame ifFalse:
  			[sendCount >= loggingStart ifTrue:
  				[sendCount := sendCount + 1.
  				logFile nextPutAll: (self stringOf: messageSelector); cr].
  			priorFrame := localFP].
  		self incrementByteCount].
  	self externalizeIPandSP.
  	logFile close!

Item was changed:
  ----- Method: StackInterpreterSimulator>>printCurrentBytecodeOn: (in category 'debug printing') -----
  printCurrentBytecodeOn: aStream
  	| code |
  	code := currentBytecode radix: 16.
  	aStream ensureCr; print: localIP - method - 3; tab.
  	bytecodeSetSelector > 0 ifTrue:
  		[aStream nextPutAll: 'ALT '].
  	aStream
  		nextPut: (code size < 2
  					ifTrue: [$0]
  					ifFalse: [code at: 1]);
  		nextPut: code last; space;
+ 		nextPutAll: (BytecodeTable at: currentBytecode + 1);
- 		nextPutAll: (BytecodeTable at: currentBytecode + bytecodeSetSelector + 1);
  		space;
  		nextPut: $(; print: byteCount + 1; nextPut: $)!

Item was changed:
  ----- Method: StackInterpreterSimulator>>run (in category 'testing') -----
  run
  	"Just run"
+ 	quitBlock := [| topWindow |
+ 				  
+ 				   (displayView notNil
+ 				   and: [topWindow := displayView outermostMorphThat:
+ 									[:m| m isSystemWindow and: [World submorphs includes: m]].
+ 						topWindow notNil
+ 				   and: [UIManager default confirm: 'close?']]) ifTrue:
+ 					[topWindow delete].
- 	quitBlock := [([transcript dependents anyOne outermostMorphThat: [:m| m isSystemWindow]]
- 					on: Error
- 					do: [:ex| nil])
- 						ifNotNil: [:window| (UIManager default confirm: 'close?') ifTrue: [window delete]].
  				  ^self].
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
  		 atEachStepBlock value. "N.B. may be nil"
+ 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		 self incrementByteCount].
  	localIP := localIP - 1.
  	"undo the pre-increment of IP before returning"
  	self externalizeIPandSP!

Item was changed:
  ----- Method: StackInterpreterSimulator>>runAtEachStep: (in category 'testing') -----
  runAtEachStep: aBlock
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
  		 aBlock value: currentBytecode.
+ 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		 self incrementByteCount].
  	localIP := localIP - 1.
  	"undo the pre-increment of IP before returning"
  	self externalizeIPandSP!

Item was changed:
  ----- Method: StackInterpreterSimulator>>runAtEachStep:breakCount: (in category 'testing') -----
  runAtEachStep: aBlock breakCount: breakCount
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
  		 aBlock value: currentBytecode.
+ 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		 self incrementByteCount.
  		 byteCount = breakCount ifTrue:
  			[self halt]].
  	localIP := localIP - 1.
  	"undo the pre-increment of IP before returning"
  	self externalizeIPandSP!

Item was changed:
  ----- Method: StackInterpreterSimulator>>runForNBytes: (in category 'testing') -----
  runForNBytes: nBytecodes 
  	"Do nByteCodes more bytecode dispatches.
  	Keep byteCount up to date.
  	This can be run repeatedly."
  	| endCount |
  	self initStackPages.
  	self loadInitialContext.
  	endCount := byteCount + nBytecodes.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[byteCount < endCount] whileTrue:
+ 		[self dispatchOn: currentBytecode in: BytecodeTable.
- 		[self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		 self incrementByteCount].
  	localIP := localIP - 1.
  	"undo the pre-increment of IP before returning"
  	self externalizeIPandSP!

Item was changed:
  ----- Method: StackInterpreterSimulator>>runWithBreakCount: (in category 'testing') -----
  runWithBreakCount: theBreakCount
  	"Just run, halting when byteCount is reached"
+ 	quitBlock := [| topWindow |
+ 				  
+ 				   (displayView notNil
+ 				   and: [topWindow := displayView outermostMorphThat:
+ 									[:m| m isSystemWindow and: [World submorphs includes: m]].
+ 						topWindow notNil
+ 				   and: [UIManager default confirm: 'close?']]) ifTrue:
+ 					[topWindow delete].
- 	quitBlock := [(displayView notNil
- 				   and: [UIManager default confirm: 'close?']) ifTrue:
- 					[(displayView outermostMorphThat: [:m| m isSystemWindow]) ifNotNil:
- 						[:topWindow| topWindow delete]].
  				  ^self].
  	breakCount := theBreakCount.
  	self initStackPages.
  	self loadInitialContext.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
+ 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		 self incrementByteCount].
  	localIP := localIP - 1.
  	"undo the pre-increment of IP before returning"
  	self externalizeIPandSP!

Item was changed:
  ----- Method: StackInterpreterSimulator>>test (in category 'testing') -----
  test
  	self initStackPages.
  	self loadInitialContext.
  	transcript clear.
  	byteCount := 0.
  	breakCount := -1.
  	quitBlock := [^self].
  	printSends := printReturns := true.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
  		 printFrameAtEachStep ifTrue:
  			[self printFrame: localFP WithSP: localSP].
  		 printBytecodeAtEachStep ifTrue:
  			[self printCurrentBytecodeOn: Transcript.
  			 Transcript cr; flush].
+ 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		 self incrementByteCount.
  		 byteCount = breakCount ifTrue:
  			["printFrameAtEachStep :=" printBytecodeAtEachStep := true.
  			 self halt: 'hit breakCount break-point']].
  	self externalizeIPandSP!

Item was changed:
  ----- Method: StackInterpreterSimulator>>test1 (in category 'testing') -----
  test1
  	self initStackPages.
  	self loadInitialContext.
  	transcript clear.
  	byteCount := 0.
  	breakCount := -1.
  	self setBreakSelector: #blockCopy:.
  	quitBlock := [^self].
  	printSends := printReturns := true.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
  		 "byteCount >= 22283 ifTrue:
  			[(self checkIsStillMarriedContext: 22186072 currentFP: localFP) ifFalse:
  				[self halt]]."
  		 (printBytecodeAtEachStep
  		  "and: [self isMarriedOrWidowedContext: 22189568]") ifTrue:
  			["| thePage |
  			 thePage := stackPages stackPageFor: (self frameOfMarriedContext: 22189568).
  			 thePage == stackPage
  				ifTrue: [self shortPrintFrameAndCallers: localFP SP: localSP]
  				ifFalse: [self shortPrintFrameAndCallers: thePage headFrameFP SP: thePage headFrameSP]."
  			 self printCurrentBytecodeOn: Transcript.
  			 Transcript cr; flush].
  
+ 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		 self incrementByteCount.
  		 byteCount = breakCount ifTrue:
  			["printFrameAtEachStep := true."
  			 printSends := printBytecodeAtEachStep := true.
  			 self halt: 'hit breakCount break-point']].
  	self externalizeIPandSP!

Item was changed:
  ----- Method: StackInterpreterSimulator>>testBreakCount:printSends:printFrames:printBytecodes: (in category 'testing') -----
  testBreakCount: breakCount printSends: shouldPrintSends printFrames: shouldPrintFrames printBytecodes: shouldPrintBytecodes
  	self initStackPages.
  	self loadInitialContext.
  	transcript clear.
  	byteCount := 0.
  	quitBlock := [^self].
  	printSends := true & shouldPrintSends. "true & foo allows evaluating printFoo := true in the debugger"
  	printFrameAtEachStep := true & shouldPrintFrames.
  	printBytecodeAtEachStep := true & shouldPrintBytecodes.
  	self internalizeIPandSP.
  	self fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
  		 printFrameAtEachStep ifTrue:
  			[self printFrame: localFP WithSP: localSP].
  		 printBytecodeAtEachStep ifTrue:
  			[self printCurrentBytecodeOn: Transcript.
  			 Transcript cr; flush].
+ 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		 self incrementByteCount.
  		 byteCount = breakCount ifTrue:
  			["printFrameAtEachStep :=" printBytecodeAtEachStep := true.
  			 self halt: 'hit breakCount break-point']].
  	self externalizeIPandSP!



More information about the Vm-dev mailing list