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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 16 21:55:16 UTC 2014


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

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

Name: VMMaker.oscog-eem.675
Author: eem
Time: 16 April 2014, 2:52:54.853 pm
UUID: 62a9b7df-b999-4552-b597-4b766d97f919
Ancestors: VMMaker.oscog-eem.674

Define the Sista V1 bytecode table for the StackInterpreter.

Include commented-out breakpoint code in simulator context access.

Fix comment typos

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

Item was added:
+ ----- Method: CogVMSimulator>>baseFrameReturn (in category 'return bytecodes') -----
+ baseFrameReturn
+ 	"| contextToReturnTo |
+ 	contextToReturnTo := self frameCallerContext: localFP.
+ 	(self stringOf: (self penultimateLiteralOf: (self fetchPointer: MethodIndex ofObject: contextToReturnTo))) = #indexOf:startingAt:ifAbsent: ifTrue:
+ 		[self halt]."
+ 	^super baseFrameReturn!

Item was changed:
  ----- Method: CogVMSimulator>>ceBaseFrameReturn: (in category 'trampolines') -----
  ceBaseFrameReturn: returnValue
  	"self printCallStackOf: (stackPages longAt: stackPage baseAddress) currentFP: stackPage baseFP.
  	Transcript print: byteCount; tab; print: thisContext; cr.
  	(self confirm: 'continue?') ifFalse: [self returnValue hex]."
  	"returnValue = 16r01934F78 ifTrue: [self halt]."
+ 	"| contextToReturnTo |
+ 	contextToReturnTo := stackPages longAt: stackPage baseAddress.
+ 	(self stringOf: (self penultimateLiteralOf: (self fetchPointer: MethodIndex ofObject: contextToReturnTo))) = #indexOf:startingAt:ifAbsent: ifTrue:
+ 		[self halt]."
  	^super ceBaseFrameReturn: returnValue!

Item was changed:
  ----- Method: CogVMSimulator>>ceCounterTripped: (in category 'cog jit support') -----
  ceCounterTripped: condition
+ 	| counterTrippedSelector |
+ 	self transcript cr; nextPutAll: 'counter tripped in '.
- 	self halt transcript cr; nextPutAll: 'counter tripped in '.
  	self shortPrintFrame: framePointer.
+ 	counterTrippedSelector := objectMemory maybeSplObj: SelectorCounterTripped.
+ 	(counterTrippedSelector isNil
+ 	or: [counterTrippedSelector = objectMemory nilObject]) ifFalse:
+ 		[self halt: 'counter tripped'].
  	^super ceCounterTripped: condition!

Item was changed:
  ----- Method: CogVMSimulator>>externalInstVar:ofContext: (in category 'debugging traps') -----
+ externalInstVar: offset ofContext: aContext
- externalInstVar: offset ofContext: aOnceMarriedContext
  
  	"offset = InstructionPointerIndex ifTrue:
+ 		[transcript nextPutAll: '==================='; cr.
+ 		 self printContext: 16r1715630.
+ 		 self printCallStackOf: aContext currentFP: framePointer.
+ 		 transcript nextPutAll: '==================='; cr.
- 		[Transcript nextPutAll: '==================='; cr.
- 		  self printContext: 16r1715630.
- 		 self printCallStackOf: aOnceMarriedContext currentFP: framePointer.
- 		 Transcript nextPutAll: '==================='; cr.
  		 self halt]."
  
  	| result |
  	"self shortPrintFrameAndCallers: framePointer.
+ 	transcript print: byteCount; tab; print: thisContext; cr.
- 	Transcript print: byteCount; tab; print: thisContext; cr.
  	self print: offset; cr.
+ 	self printContext: aContext.
- 	self printContext: aOnceMarriedContext.
  	(self confirm: 'continue?') ifFalse: [self halt]."
+ 	"result := super externalInstVar: offset ofContext: aContext.
+ 	(offset = InstructionPointerIndex
+ 	and: [(self stringOf: (self penultimateLiteralOf: (self fetchPointer: MethodIndex ofObject: aContext))) = #indexOf:startingAt:ifAbsent:]) ifTrue:
+ 		[transcript space; nextPutAll: '^pc '; nextPutAll: result hex.
+ 		 (objectMemory isIntegerObject: result) ifTrue:
+ 			[transcript space; print: (objectMemory integerValueOf: result)].
+ 		 transcript tab.
+ 		 self shortPrintContext: aContext]."
- 	result := super externalInstVar: offset ofContext: aOnceMarriedContext.
  	"offset = StackPointerIndex ifTrue:
+ 		[transcript nextPutAll: '^stackp ', (self integerValueOf: result) printString; tab.
+ 		 self shortPrintContext: aContext.
+ 		 (#(24205456 24205732) includes: aContext) ifTrue:
+ 		 	[(self checkIsStillMarriedContext: aContext currentFP: framePointer)
+ 				ifTrue: [self printFrame: (self frameOfMarriedContext: aContext) WithSP: (self frameOfMarriedContext: aContext) - 48]
+ 				ifFalse: [self printContext: aContext]]]."
- 		[Transcript nextPutAll: '^stackp ', (self integerValueOf: result) printString; tab.
- 		 self shortPrintContext: aOnceMarriedContext.
- 		 (#(24205456 24205732) includes: aOnceMarriedContext) ifTrue:
- 		 	[(self checkIsStillMarriedContext: aOnceMarriedContext currentFP: framePointer)
- 				ifTrue: [self printFrame: (self frameOfMarriedContext: aOnceMarriedContext) WithSP: (self frameOfMarriedContext: aOnceMarriedContext) - 48]
- 				ifFalse: [self printContext: aOnceMarriedContext]]]."
  	^result!

Item was changed:
  ----- Method: CogVMSimulator>>externalInstVar:ofContext:put: (in category 'frame access') -----
+ externalInstVar: index ofContext: aContext put: anOop
- externalInstVar: index ofContext: maybeMarriedContext put: anOop
  	"self shortPrintFrameAndCallers: framePointer.
  	Transcript print: byteCount; tab; print: thisContext; cr.
  	self print: index; cr.
+ 	self printContext: aContext.
- 	self printContext: maybeMarriedContext.
  	self shortPrintOop: anOop.
  	(self confirm: 'continue?') ifFalse: [self halt]."
+ 	"(self stringOf: (self penultimateLiteralOf: (self fetchPointer: MethodIndex ofObject: aContext))) = #indexOf:startingAt:ifAbsent: ifTrue:
+ 		[self halt]."
+ 	^super externalInstVar: index ofContext: aContext put: anOop!
- 	^super externalInstVar: index ofContext: maybeMarriedContext put: anOop!

Item was changed:
  ----- Method: CogVMSimulator>>instVar:ofContext: (in category 'debugging traps') -----
+ instVar: offset ofContext: aContext
- instVar: offset ofContext: aOnceMarriedContext
  
  	"offset = InstructionPointerIndex ifTrue:
  		[Transcript nextPutAll: '==================='; cr.
  		  self printContext: 16r1715630.
+ 		 self printCallStackOf: aContext currentFP: framePointer.
- 		 self printCallStackOf: aOnceMarriedContext currentFP: framePointer.
  		 Transcript nextPutAll: '==================='; cr.
  		 self halt]."
  
  	| result |
  	"self shortPrintFrameAndCallers: localFP.
  	Transcript print: byteCount; tab; print: thisContext; cr.
  	self print: offset; cr.
+ 	self printContext: aContext.
- 	self printContext: aOnceMarriedContext.
  	(self confirm: 'continue?') ifFalse: [self halt]."
+ 	"result := super instVar: offset ofContext: aContext.
+ 	(offset = InstructionPointerIndex
+ 	and: [(self stringOf: (self penultimateLiteralOf: (self fetchPointer: MethodIndex ofObject: aContext))) = #indexOf:startingAt:ifAbsent:]) ifTrue:
+ 		[transcript space; nextPutAll: '^pc '; nextPutAll: result hex.
+ 		 (objectMemory isIntegerObject: result) ifTrue:
+ 			[transcript space; print: (objectMemory integerValueOf: result)].
+ 		 transcript tab.
+ 		 self shortPrintContext: aContext]."
- 	result := super instVar: offset ofContext: aOnceMarriedContext.
  	"offset = StackPointerIndex ifTrue:
  		[Transcript nextPutAll: '^stackp ', (self integerValueOf: result) printString; tab.
+ 		 self shortPrintContext: aContext.
+ 		 (#(24205456 24205732) includes: aContext) ifTrue:
+ 		 	[(self checkIsStillMarriedContext: aContext currentFP: localFP)
+ 				ifTrue: [self printFrame: (self frameOfMarriedContext: aContext) WithSP: (self frameOfMarriedContext: aContext) - 48]
+ 				ifFalse: [self printContext: aContext]]]."
- 		 self shortPrintContext: aOnceMarriedContext.
- 		 (#(24205456 24205732) includes: aOnceMarriedContext) ifTrue:
- 		 	[(self checkIsStillMarriedContext: aOnceMarriedContext currentFP: localFP)
- 				ifTrue: [self printFrame: (self frameOfMarriedContext: aOnceMarriedContext) WithSP: (self frameOfMarriedContext: aOnceMarriedContext) - 48]
- 				ifFalse: [self printContext: aOnceMarriedContext]]]."
  	^result!

Item was changed:
  ----- Method: CogVMSimulator>>instVar:ofContext:put: (in category 'frame access') -----
  instVar: index ofContext: aMarriedContext put: anOop
  	"self shortPrintFrameAndCallers: localFP.
  	Transcript print: byteCount; tab; print: thisContext; cr.
  	self print: index; cr.
  	self printContext: aMarriedContext.
  	self shortPrintOop: anOop.
  	(self confirm: 'continue?') ifFalse: [self halt]."
+ 	"(self stringOf: (self penultimateLiteralOf: (self fetchPointer: MethodIndex ofObject: aMarriedContext))) = #indexOf:startingAt:ifAbsent: ifTrue:
+ 		[self halt]."
  	^super instVar: index ofContext: aMarriedContext put: anOop!

Item was changed:
  ----- Method: CogVMSimulator>>updateStateOfSpouseContextForFrame:WithSP: (in category 'frame access') -----
  updateStateOfSpouseContextForFrame: theFP WithSP: theSP
  	 "26431360 = (self frameContext: theFP) ifTrue:
  		[self halt]."
+ 	"((self stringOf: (self penultimateLiteralOf: (self frameMethodObject: theFP))) = #indexOf:startingAt:ifAbsent:) ifTrue:
+ 		[self halt]."
  	^super updateStateOfSpouseContextForFrame: theFP WithSP: theSP!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulation;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
  		add: 'print mc/cog frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
  		add: 'short print ext frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		add: 'short print mc/cog frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
  		add: 'long print ext frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  		add: 'long print int frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  		add: 'long print mc/cog frame & callers' action: [self printFrameAndCallers: cogit processor fp SP: cogit processor sp];
  		add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  		add: 'print call stack' action: #printCallStack;
  		add: 'print stack call stack' action: #printStackCallStack;
  		add: 'print stack call stack of...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printStackCallStackOf: fp]];
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print call stack of frame...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printCallStackFP: fp]];
  		add: 'print all stacks' action: #printAllStacks;
  		add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  											self writeBackHeadFramePointers];
  		add: 'write back mc ptrs' action: [stackPointer := cogit processor sp. framePointer := cogit processor fp. instructionPointer := cogit processor eip.
  											self writeBackHeadFramePointers];
  		addLine;
  		add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  		add: 'print register map' action: [cogit printRegisterMapOn: transcript];
  		add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  		add: 'disassemble method/trampoline at pc' action: [cogit disassembleCodeAt: cogit processor pc];
  		add: 'disassemble ext head frame method' action: [cogit disassembleMethod: (self frameMethod: framePointer)];
  		add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  		add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
+ 		add: 'print context...' action: [(self promptHex: 'print context') ifNotNil: [:oop| self printContext: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'inspect cointerpreter' action: #inspect;
  		add: 'inspect cogit' target: cogit action: #inspect;
  		add: 'inspect method zone' target: cogit methodZone action: #inspect.
  	self isThreadedVM ifTrue:
  		[aMenuMorph add: 'inspect thread manager' target: self threadManager action: #inspect].
  	aMenuMorph
  		addLine;
  		add: 'print cog methods' target: cogMethodZone action: #printCogMethods;
  		add: 'print cog methods with prim...' action: [(self promptNum: 'prim index') ifNotNil: [:pix| cogMethodZone printCogMethodsWithPrimitive: pix]];
  		add: 'print trampoline table' target: cogit action: #printTrampolineTable;
  		add: 'print prim trace log' action: #dumpPrimTraceLog;
  		add: 'report recent instructions' target: cogit action: #reportLastNInstructions;
  		add: 'set break pc (', (cogit breakPC isInteger ifTrue: [cogit breakPC hex] ifFalse: [cogit breakPC printString]), ')...' action: [(self promptHex: 'break pc') ifNotNil: [:bpc| cogit breakPC: bpc]];
  		add: (cogit singleStep
  				ifTrue: ['no single step']
  				ifFalse: ['single step'])
  			action: [cogit singleStep: cogit singleStep not];
  		add: (cogit printRegisters
  				ifTrue: ['no print registers each instruction']
  				ifFalse: ['print registers each instruction'])
  			action: [cogit printRegisters: cogit printRegisters not];
  		add: (cogit printInstructions
  				ifTrue: ['no print instructions each instruction']
  				ifFalse: ['print instructions each instruction'])
  			action: [cogit printInstructions: cogit printInstructions not];
  		addLine;
  		add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  											s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
  		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector'.
  											s notEmpty ifTrue: [self setBreakSelector: s]];
  		add: 'set break block...' action: [|s| s := UIManager default request: 'break block' initialAnswer: '[:theCogit| false]'.
  											s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  		add: 'set cogit break method...' action: [(self promptHex: 'cogit breakMethod') ifNotNil: [:bm| cogit setBreakMethod: bm]];
  		add: (printBytecodeAtEachStep
  				ifTrue: ['no print bytecode each bytecode']
  				ifFalse: ['print bytecode each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printBytecodeAtEachStep := printBytecodeAtEachStep not];
  		add: (printFrameAtEachStep
  				ifTrue: ['no print frame each bytecode']
  				ifFalse: ['print frame each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printFrameAtEachStep := printFrameAtEachStep not].
  	^aMenuMorph!

Item was added:
+ ----- Method: StackInterpreter class>>initializeBytecodeTableForSistaV1 (in category 'initialization') -----
+ initializeBytecodeTableForSistaV1
+ 	"See e.g. the cass comment for EncoderForSistaV1"
+ 	"StackInterpreter initializeBytecodeTableForSistaV1"
+ 	"Note: This table will be used to generate a C switch statement."
+ 
+ 	BytecodeTable := Array new: 256.
+ 	self table: BytecodeTable from:
+ 	#(	"1 byte bytecodes"
+ 		(   0  15 pushReceiverVariableBytecode)
+ 		( 16  31 pushLiteralVariable16CasesBytecode)
+ 		( 32  63 pushLiteralConstantBytecode)
+ 		( 64  75 pushTemporaryVariableBytecode)
+ 		( 76	 pushReceiverBytecode)
+ 		( 77	 pushConstantTrueBytecode)
+ 		( 78	 pushConstantFalseBytecode)
+ 		( 79	 pushConstantNilBytecode)
+ 		( 80	 pushConstantZeroBytecode)
+ 		( 81	 pushConstantOneBytecode)
+ 		( 82	 extPushPseudoVariable)
+ 		( 83	 duplicateTopBytecode)
+ 	
+ 		( 84 87	unknownBytecode)
+ 		( 88	returnReceiver)
+ 		( 89	returnTrue)
+ 		( 90	returnFalse)
+ 		( 91	returnNil)
+ 		( 92	returnTopFromMethod)
+ 		( 93	returnNilFromBlock)
+ 		( 94	returnTopFromBlock)
+ 		( 95	extNop)
+ 
+ 		( 96	 bytecodePrimAdd)
+ 		( 97	 bytecodePrimSubtract)
+ 		( 98	 bytecodePrimLessThanSistaV1) "for booleanCheatSistaV1:"
+ 		( 99	 bytecodePrimGreaterThanSistaV1) "for booleanCheatSistaV1:"
+ 		(100	 bytecodePrimLessOrEqualSistaV1) "for booleanCheatSistaV1:"
+ 		(101	 bytecodePrimGreaterOrEqualSistaV1) "for booleanCheatSistaV1:"
+ 		(102	 bytecodePrimEqualSistaV1) "for booleanCheatSistaV1:"
+ 		(103	 bytecodePrimNotEqualSistaV1) "for booleanCheatSistaV1:"
+ 		(104	 bytecodePrimMultiply)
+ 		(105	 bytecodePrimDivide)
+ 		(106	 bytecodePrimMod)
+ 		(107	 bytecodePrimMakePoint)
+ 		(108	 bytecodePrimBitShift)
+ 		(109	 bytecodePrimDiv)
+ 		(110	 bytecodePrimBitAnd)
+ 		(111	 bytecodePrimBitOr)
+ 
+ 		(112	 bytecodePrimAt)
+ 		(113	 bytecodePrimAtPut)
+ 		(114	 bytecodePrimSize)
+ 		(115	 bytecodePrimNext)		 "i.e. a 0 arg special selector"
+ 		(116	 bytecodePrimNextPut)		 "i.e. a 1 arg special selector"
+ 		(117	 bytecodePrimAtEnd)
+ 		(118	 bytecodePrimIdenticalSistaV1) "for booleanCheatSistaV1:"
+ 		(119	 bytecodePrimClass)
+ 		(120	 bytecodePrimSpecialSelector24) "was blockCopy:"
+ 		(121	 bytecodePrimValue)
+ 		(122	 bytecodePrimValueWithArg)
+ 		(123	 bytecodePrimDo)			"i.e. a 1 arg special selector"
+ 		(124	 bytecodePrimNew)			"i.e. a 0 arg special selector"
+ 		(125	 bytecodePrimNewWithArg)	"i.e. a 1 arg special selector"
+ 		(126	 bytecodePrimPointX)		"i.e. a 0 arg special selector"
+ 		(127	 bytecodePrimPointY)		"i.e. a 0 arg special selector"
+ 
+ 		(128 143	sendLiteralSelector0ArgsBytecode)
+ 		(144 159	sendLiteralSelector1ArgBytecode)
+ 		(160 175	sendLiteralSelector2ArgsBytecode)
+ 
+ 		(176 183	shortUnconditionalJump)
+ 		(184 191	shortConditionalJumpTrue)
+ 		(192 199	shortConditionalJumpFalse)
+ 	
+ 		(200 207	storeAndPopReceiverVariableBytecode)
+ 		(208 215	storeAndPopTemporaryVariableBytecode)
+ 		(216		popStackBytecode)
+ 
+ 		(217 223	unknownBytecode)
+ 
+ 		"2 byte bytecodes"
+ 		(224		extABytecode)
+ 		(225		extBBytecode)
+ 
+ 		(226		extPushReceiverVariableBytecode)
+ 		(227		extPushLiteralVariableBytecode)
+ 		(228		extPushLiteralBytecode)
+ 		(229		longPushTemporaryVariableBytecode)
+ 		(230		pushClosureTempsBytecode)
+ 		(231		pushNewArrayBytecode)
+ 		(232		extPushIntegerBytecode)
+ 		(233		extPushCharacterBytecode)
+ 
+ 		(234		extSendBytecode)
+ 		(235		extSendSuperBytecode)
+ 
+ 		(236		extTrapOnBehaviorsBytecode)
+ 
+ 		(237		extUnconditionalJump)
+ 		(238		extJumpIfTrue)
+ 		(239		extJumpIfFalse)
+ 
+ 		(240		extStoreAndPopReceiverVariableBytecode)
+ 		(241		extStoreAndPopLiteralVariableBytecode)
+ 		(242		longStoreAndPopTemporaryVariableBytecode)
+ 
+ 		(243		extStoreReceiverVariableBytecode)
+ 		(244		extStoreLiteralVariableBytecode)
+ 		(245		longStoreTemporaryVariableBytecode)
+ 
+ 		(246 247	unknownBytecode)
+ 
+ 		"3 byte bytecodes"
+ 		(248		callPrimitiveBytecode)
+ 		(249		unknownBytecode) "reserved for Push Float"
+ 
+ 		(250		extPushClosureBytecode)
+ 		(251		pushRemoteTempLongBytecode)
+ 		(252		storeRemoteTempLongBytecode)
+ 		(253		storeAndPopRemoteTempLongBytecode)
+ 
+ 		(254 255	unknownBytecode)
+ 	)!

Item was changed:
  ----- Method: StackInterpreter>>instVar:ofContext: (in category 'frame access') -----
  instVar: offset ofContext: aContext
+ 	"Fetch an instance variable from a maybe married context.
- 	"Fetch an instance avriable from a maybe married context.
  	 If the context is still married compute the value of the
  	 relevant inst var from the spouse frame's state."
  	| spouseFP |
  	<var: #spouseFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theFPAbove type: #'char *'>
  	<inline: true>
  	self assert: offset < MethodIndex.
  	self assert: (objectMemory isContext: aContext).
  	(self isMarriedOrWidowedContext: aContext) ifFalse:
  		[^objectMemory fetchPointer: offset ofObject: aContext].
  
  	self writeBackHeadFramePointers.
  	(self isWidowedContext: aContext) ifTrue:
  		[^objectMemory fetchPointer: offset ofObject: aContext].
  
  	spouseFP := self frameOfMarriedContext: aContext.
  	offset = SenderIndex ifTrue:
  		[^self ensureCallerContext: spouseFP].
  	offset = StackPointerIndex ifTrue:
  		[self assert: ReceiverIndex + (self stackPointerIndexForFrame: spouseFP) < (objectMemory lengthOf: aContext).
  		^objectMemory integerObjectOf: (self stackPointerIndexForFrame: spouseFP)].
  	offset = InstructionPointerIndex ifTrue:
  		[| theIP thePage theFPAbove |
  		 spouseFP = localFP
  			ifTrue: [theIP := self oopForPointer: localIP]
  			ifFalse:
  				[thePage := stackPages stackPageFor: spouseFP.
  				 theFPAbove := self findFrameAbove: spouseFP inPage: thePage.
  				 theIP := theFPAbove == 0
  							ifTrue: [stackPages longAt: thePage headSP]
  							ifFalse:[self oopForPointer: (self frameCallerSavedIP: theFPAbove)]].
  		 ^self contextInstructionPointer: theIP frame: spouseFP].
  	self error: 'bad index'.
  	^0!



More information about the Vm-dev mailing list