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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 20 17:39:21 UTC 2013


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

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

Name: VMMaker.oscog-eem.265
Author: eem
Time: 20 February 2013, 9:36:51.617 am
UUID: c8c5b4d1-706a-4eb6-ad85-566811e2b239
Ancestors: VMMaker.oscog-eem.264

Fix bug in assigning pc which can cause stackPage to not be most
recently used.

Minor cleanups:
Move InterpreterPrimitives primitives that use framePointer and/or
stackPointer down into StackInterpreterPrimitives.
Eliminate obsolete 64-bit check in primitiveBeCursor.
Improve class comments for VM simulators, including current launch
instructions.
Include the AioPlugin in Squeak Cog VM generation.
Fix short frame printing (eliminate an exc=tra newline and use hex
for receiver).

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

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
  	instanceVariableNames: 'enableCog byteCount lastPollCount lastExtPC sendCount printSends traceOn myBitBlt displayForm imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
+ !CogVMSimulator commentStamp: 'eem 2/13/2013 15:33' prior: 0!
+ This class defines basic memory access and primitive simulation so that the CoInterpreter 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.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
- !CogVMSimulator commentStamp: '<historical>' 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
  
  	(CogVMSimulator new openOn: Smalltalk imageName) 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 to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
+ 
+ | opts |
+ CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
+ CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
+ CogVMSimulator new
+ 	desiredNumStackPages: 8;
+ 	openAsMorph;
+ 	run
+ 
+ Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
+ 
+ | cos proc opts |
+ CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
+ CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
+ cos := CogVMSimulator new.
+ "cos initializeThreadSupport." "to test the multi-threaded VM"
+ cos desiredNumStackPages: 8. "to set the size of the stack zone"
+ "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
+ cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
+ "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
+ proc := cos cogit processor.
+ "cos cogit sendTrace: 7." "turn on tracing"
+ "set a complex breakpoint at a specific point in machine code"
+ "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
+ "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
+ "cos cogit setBreakMethod: 16rB38880."
+ cos
+ 	openAsMorph;
+ 	"toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
+ 	halt;
+ 	run!
- 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. You will probably have more luck using InterpreteSimulatorLSB or InterpreterSimulatorMSB as befits your machine.!

Item was changed:
  CogClass subclass: #Cogit
  	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxMethodBefore ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceStoreCheckTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceClosureCopyTrampoline ceCreateNewArrayTrampoline ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceActiveContextTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline cePositive32BitIntegerTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
  	classVariableNames: 'AltBlockCreationBytecodeSize AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxUnitDisplacement MaxUnreportableError MaxX2NDisplacement NotFullyInitialized NumObjRefsInRuntime NumSendTrampolines NumTrampolines ProcessorClass YoungSelectorInPIC'
  	poolDictionaries: 'CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
+ !Cogit commentStamp: 'eem 2/13/2013 15:37' prior: 0!
+ I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
- !Cogit commentStamp: '<historical>' prior: 0!
- I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.
  
+ 	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
+ 
+ I have concrete subclasses that implement different levels of optimization:
+ 	SimpleStackBasedCogit is the simplest code generator.
+ 
+ 	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
+ 	to the stack until necessary and implements a register-based calling convention for low-arity sends.
+ 
+ 	StackToRegisterMappingCogit is an experimental code generator with support for counting
+ 	conditional branches, intended to support adaptive optimization.
+ 
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventuakly teh total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was added:
+ ----- Method: Interpreter>>flushAtCache (in category 'method lookup cache') -----
+ flushAtCache
+ 	"Flush the at cache. The method cache is flushed on every programming change and garbage collect."
+ 
+ 	1 to: AtCacheTotalSize do: [ :i | atCache at: i put: 0 ]!

Item was changed:
  ----- Method: Interpreter>>primitiveBeCursor (in category 'I/O primitives') -----
  primitiveBeCursor
  	"Set the cursor to the given shape. The Mac only supports 16x16 pixel cursors. Cursor offsets are handled by Smalltalk."
  
  	| cursorObj maskBitsIndex maskObj bitsObj extentX extentY depth offsetObj offsetX offsetY cursorBitsIndex ourCursor |
  
- self flag: #Dan.  "This is disabled until we convert bitmaps appropriately"
- BytesPerWord = 8 ifTrue: [self pop: argumentCount. ^nil].
- 
  	argumentCount = 0 ifTrue: [
  		cursorObj := self stackTop.
  		maskBitsIndex := nil].
  	argumentCount = 1 ifTrue: [
  		cursorObj := self stackValue: 1.
  		maskObj := self stackTop].
  	self success: (argumentCount < 2).
  
  	self success: ((self isPointers: cursorObj) and: [(self lengthOf: cursorObj) >= 5]).
  	successFlag ifTrue: [
  		bitsObj := self fetchPointer: 0 ofObject: cursorObj.
  		extentX := self fetchInteger: 1 ofObject: cursorObj.
  		extentY := self fetchInteger: 2 ofObject: cursorObj.
  		depth := self fetchInteger: 3 ofObject: cursorObj.
  		offsetObj := self fetchPointer: 4 ofObject: cursorObj].
  		self success: ((self isPointers: offsetObj) and: [(self lengthOf: offsetObj) >= 2]).
  
  	successFlag ifTrue: [
  		offsetX := self fetchInteger: 0 ofObject: offsetObj.
  		offsetY := self fetchInteger: 1 ofObject: offsetObj.
  
  		(argumentCount = 0 and: [depth = 32])
  			ifTrue: [
  				"Support arbitrary-sized 32 bit ARGB forms --bf 3/1/2007 23:51"
  				self success: ((extentX > 0) and: [extentY > 0]).
  				self success: ((offsetX >= (extentX * -1)) and: [offsetX <= 0]).
  				self success: ((offsetY >= (extentY * -1)) and: [offsetY <= 0]).
  				cursorBitsIndex := bitsObj + BaseHeaderSize.
  				self success: ((self isWords: bitsObj) and: [(self lengthOf: bitsObj) = (extentX * extentY)]).
  				self cCode: '' inSmalltalk:
  					[ourCursor := Cursor
  						extent: extentX @ extentY
  						depth: 32
  						fromArray: ((1 to: extentX * extentY) collect: [:i |
  							self fetchLong32: i-1 ofObject: bitsObj])
  						offset: offsetX  @ offsetY]]
  			ifFalse: [
  				self success: ((extentX = 16) and: [extentY = 16 and: [depth = 1]]).
  				self success: ((offsetX >= -16) and: [offsetX <= 0]).
  				self success: ((offsetY >= -16) and: [offsetY <= 0]).
  				self success: ((self isWords: bitsObj) and: [(self lengthOf: bitsObj) = 16]).
  				cursorBitsIndex := bitsObj + BaseHeaderSize.
  				self cCode: '' inSmalltalk:
  					[ourCursor := Cursor
  						extent: extentX @ extentY
  						fromArray: ((1 to: 16) collect: [:i |
  							((self fetchLong32: i-1 ofObject: bitsObj) >> 16) bitAnd: 16rFFFF])
  						offset: offsetX  @ offsetY]]].
  
  	argumentCount = 1 ifTrue: [
  		self success: ((self isPointers: maskObj) and: [(self lengthOf: maskObj) >= 5]).
  		successFlag ifTrue: [
  			bitsObj := self fetchPointer: 0 ofObject: maskObj.
  			extentX := self fetchInteger: 1 ofObject: maskObj.
  			extentY := self fetchInteger: 2 ofObject: maskObj.
  			depth := self fetchInteger: 3 ofObject: maskObj].
  
  		successFlag ifTrue: [
  			self success: ((extentX = 16) and: [extentY = 16 and: [depth = 1]]).
  			self success: ((self isWords: bitsObj) and: [(self lengthOf: bitsObj) = 16]).
  			maskBitsIndex := bitsObj + BaseHeaderSize]].
  
  
  	successFlag ifTrue: [
  		argumentCount = 0
  			ifTrue: [
  				depth = 32
  					ifTrue: [(self cCode: 'ioSetCursorARGB(cursorBitsIndex, extentX, extentY, offsetX, offsetY)'
  						inSmalltalk: [ourCursor show. Cursor currentCursor == ourCursor])	
  							ifFalse: [^self success: false. ]]
  					ifFalse: [self cCode: 'ioSetCursor(cursorBitsIndex, offsetX, offsetY)'
  						inSmalltalk: [ourCursor show]]]
  			ifFalse: [self cCode: 'ioSetCursorWithMask(cursorBitsIndex, maskBitsIndex, offsetX, offsetY)'
  						inSmalltalk: [cursorBitsIndex == maskBitsIndex. "placate compiler"
  									ourCursor show]].
  		self pop: argumentCount]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveBeCursor (in category 'I/O primitives') -----
  primitiveBeCursor
  	"Set the cursor to the given shape. The Mac only supports 16x16 pixel cursors. Cursor offsets are handled by Smalltalk."
  
  	| cursorObj maskBitsIndex maskObj bitsObj extentX extentY depth offsetObj offsetX offsetY cursorBitsIndex ourCursor |
  
- self flag: #Dan.  "This is disabled until we convert bitmaps appropriately"
- BytesPerWord = 8 ifTrue: [self pop: argumentCount. ^nil].
- 
  	argumentCount = 0 ifTrue: [
  		cursorObj := self stackTop.
  		maskBitsIndex := nil].
  	argumentCount = 1 ifTrue: [
  		cursorObj := self stackValue: 1.
  		maskObj := self stackTop].
  	self success: (argumentCount < 2).
  
  	self success: ((objectMemory isPointers: cursorObj) and: [(objectMemory lengthOf: cursorObj) >= 5]).
  	self successful ifTrue: [
  		bitsObj := objectMemory fetchPointer: 0 ofObject: cursorObj.
  		extentX := self fetchInteger: 1 ofObject: cursorObj.
  		extentY := self fetchInteger: 2 ofObject: cursorObj.
  		depth := self fetchInteger: 3 ofObject: cursorObj.
  		offsetObj := objectMemory fetchPointer: 4 ofObject: cursorObj].
  		self success: ((objectMemory isPointers: offsetObj) and: [(objectMemory lengthOf: offsetObj) >= 2]).
  
  	self successful ifTrue: [
  		offsetX := self fetchInteger: 0 ofObject: offsetObj.
  		offsetY := self fetchInteger: 1 ofObject: offsetObj.
  		(argumentCount = 0 and: [depth = 32])
  			ifTrue: [
  				"Support arbitrary-sized 32 bit ARGB forms --bf 3/1/2007 23:51"
  				self success: ((extentX > 0) and: [extentY > 0]).
  				self success: ((offsetX >= (extentX * -1)) and: [offsetX <= 0]).
  				self success: ((offsetY >= (extentY * -1)) and: [offsetY <= 0]).
  				self success: ((objectMemory isWords: bitsObj) and: [(objectMemory lengthOf: bitsObj) = (extentX * extentY)]).
  				cursorBitsIndex := bitsObj + BaseHeaderSize.
  				self cCode: '' inSmalltalk:
  					[ourCursor := Cursor
  						extent: extentX @ extentY
  						depth: 32
  						fromArray: ((1 to: extentX * extentY) collect: [:i |
  							objectMemory fetchLong32: i-1 ofObject: bitsObj])
  						offset: offsetX  @ offsetY]]
  			ifFalse: [
  				self success: ((extentX = 16) and: [extentY = 16 and: [depth = 1]]).
  				self success: ((offsetX >= -16) and: [offsetX <= 0]).
  				self success: ((offsetY >= -16) and: [offsetY <= 0]).
  				self success: ((objectMemory isWords: bitsObj) and: [(objectMemory lengthOf: bitsObj) = 16]).
  				cursorBitsIndex := bitsObj + BaseHeaderSize.
  				self cCode: '' inSmalltalk:
  					[ourCursor := Cursor
  						extent: extentX @ extentY
  						fromArray: ((1 to: 16) collect: [:i |
  							((objectMemory fetchLong32: i-1 ofObject: bitsObj) >> (BytesPerWord*8 - 16)) bitAnd: 16rFFFF])
  						offset: offsetX  @ offsetY]]].
  
  	argumentCount = 1 ifTrue: [
  		self success: ((objectMemory isPointers: maskObj) and: [(objectMemory lengthOf: maskObj) >= 5]).
  		self successful ifTrue: [
  			bitsObj := objectMemory fetchPointer: 0 ofObject: maskObj.
  			extentX := self fetchInteger: 1 ofObject: maskObj.
  			extentY := self fetchInteger: 2 ofObject: maskObj.
  			depth := self fetchInteger: 3 ofObject: maskObj].
  
  		self successful ifTrue: [
  			self success: ((extentX = 16) and: [extentY = 16 and: [depth = 1]]).
  			self success: ((objectMemory isWords: bitsObj) and: [(objectMemory lengthOf: bitsObj) = 16]).
  			maskBitsIndex := bitsObj + BaseHeaderSize]].
  
  	self successful ifTrue: [
  		argumentCount = 0
  			ifTrue: [
  				depth = 32
  					ifTrue: [(self cCode: 'ioSetCursorARGB(cursorBitsIndex, extentX, extentY, offsetX, offsetY)'
  						inSmalltalk: [ourCursor show. Cursor currentCursor == ourCursor])	
  							ifFalse: [^self success: false]]
  					ifFalse: [self cCode: 'ioSetCursor(cursorBitsIndex, offsetX, offsetY)'
  						inSmalltalk: [ourCursor show]]]
  			ifFalse: [self cCode: 'ioSetCursorWithMask(cursorBitsIndex, maskBitsIndex, offsetX, offsetY)'
  						inSmalltalk: [cursorBitsIndex == maskBitsIndex. "placate compiler"
  									ourCursor show]].
  		self pop: argumentCount]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFindHandlerContext (in category 'control primitives') -----
  primitiveFindHandlerContext
  	"Primitive. Search up the context stack for the next method context marked
  	 for exception handling starting at the receiver. Return nil if none found"
+ 	self subclassResponsibility!
- 	| handlerOrNilOrZero |
- 	self externalWriteBackHeadFramePointers.
- 	handlerOrNilOrZero := self
- 							findMethodWithPrimitive: 199
- 							FromContext: self stackTop
- 							UpToContext: objectMemory nilObject.
- 	handlerOrNilOrZero = 0 ifTrue:
- 		[handlerOrNilOrZero := objectMemory nilObject].
- 	self pop: 1 thenPush: handlerOrNilOrZero!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFindNextUnwindContext (in category 'control primitives') -----
  primitiveFindNextUnwindContext
  	"Primitive. Search up the context stack for the next method context marked for unwind
  	 handling from the receiver up to but not including the argument. Return nil if none found."
+ 	self subclassResponsibility!
- 	| stopContext calleeContext handlerOrNilOrZero |
- 	<var: #theFP type: #'char *'>
- 	stopContext := self stackTop.
- 	calleeContext := self stackValue: 1.
- 	(stopContext = objectMemory nilObject or: [self isContext: stopContext]) ifFalse:
- 		[^self primitiveFail].
- 	self externalWriteBackHeadFramePointers.
- 	(self isStillMarriedContext: calleeContext)
- 		ifTrue:
- 			[| theFP |
- 			 theFP := self frameOfMarriedContext: calleeContext.
- 			 (self isBaseFrame: theFP)
- 				ifTrue:
- 					[handlerOrNilOrZero := self findMethodWithPrimitive: 198
- 												FromContext: (self frameCallerContext: theFP)
- 												UpToContext: stopContext]
- 				ifFalse:
- 					[handlerOrNilOrZero :=  self findMethodWithPrimitive: 198
- 												FromFP: (self frameCallerFP: theFP)
- 												UpToContext: stopContext]]
- 		ifFalse:
- 			[| startContext |
- 			 startContext := objectMemory fetchPointer: SenderIndex ofObject: calleeContext.
- 			 (self isContext: startContext)
- 				ifTrue:
- 					[handlerOrNilOrZero := self findMethodWithPrimitive: 198
- 												FromContext: startContext
- 												UpToContext: stopContext]
- 				ifFalse:
- 					[handlerOrNilOrZero := 0]].
- 	handlerOrNilOrZero = 0 ifTrue:
- 		[handlerOrNilOrZero := objectMemory nilObject].
- 	self pop: 2 thenPush: handlerOrNilOrZero!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveFullGC (in category 'memory space primitives') -----
  primitiveFullGC
  	"Do a full garbage collection and return the number of bytes available (including swap space if dynamic memory management is supported)."
  
  	objectMemory fullGCLock > 0 ifTrue:
  		[^self primitiveFailFor: PrimErrInappropriate].
- 	self externalWriteBackHeadFramePointers.
  	objectMemory incrementalGC.  "maximimize space for forwarding table"
  	objectMemory fullGC.
  	self pop: 1 thenPushInteger: (objectMemory bytesLeft: true).!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveIncrementalGC (in category 'memory space primitives') -----
  primitiveIncrementalGC
  	"Do a quick, incremental garbage collection and return the number of bytes immediately available.
  	 (Note: more space may be made available by doing a full garbage collection."
  
- 	self externalWriteBackHeadFramePointers.
  	objectMemory incrementalGC.
  	self pop: 1 thenPushInteger: (objectMemory bytesLeft: false)!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveInstVarAt (in category 'object access primitives') -----
  primitiveInstVarAt
  	| index rcvr hdr fmt totalLength fixedFields value |
  	index := self stackIntegerValue: 0.
  	rcvr := self stackValue: 1.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
+ 	hdr := self baseHeader: rcvr.
- 	hdr := objectMemory baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: hdr.
+ 	totalLength := self lengthOf: rcvr baseHeader: hdr format: fmt.
+ 	fixedFields := self fixedFieldsOf: rcvr format: fmt length: totalLength.
- 	totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
- 	fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
  	(index >= 1 and: [index <= fixedFields]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
+ 	value := self subscript: rcvr with: index format: fmt.
- 	(fmt = 3
- 	 and: [objectMemory isContextHeader: hdr])
- 		ifTrue: [value := self externalInstVar: index - 1 ofContext: rcvr]
- 		ifFalse: [value := self subscript: rcvr with: index format: fmt].
  	self pop: argumentCount + 1 thenPush: value!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveInstVarAtPut (in category 'object access primitives') -----
  primitiveInstVarAtPut
  	| newValue index rcvr hdr fmt totalLength fixedFields |
  	newValue := self stackTop.
  	index := self stackIntegerValue: 1.
  	rcvr := self stackValue: 2.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	hdr := objectMemory baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: hdr.
  	totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
  	fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
  	(index >= 1 and: [index <= fixedFields]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
+ 	self subscript: rcvr with: index storing: newValue format: fmt.
- 	(fmt = 3
- 	 and: [objectMemory isContextHeader: hdr])
- 		ifTrue: [self externalInstVar: index - 1 ofContext: rcvr put: newValue]
- 		ifFalse: [self subscript: rcvr with: index storing: newValue format: fmt].
  	self pop: argumentCount + 1 thenPush: newValue!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveObjectPointsTo (in category 'object access primitives') -----
  primitiveObjectPointsTo
+ 	| rcvr thang lastField |
- 	"This primitive is assumed to be fast (see e.g. MethodDictionary>>includesKey:) so make it so.
- 	 N.B.  Written to use literalHeaderOf: so that in Cog subclasses cogged methods (whose headers
- 	 point to the machine code method) are still correctly scanned, for the header as well as literals."
- 	| rcvr thang header fmt lastField methodHeader |
  	thang := self stackTop.
  	rcvr := self stackValue: 1.
  	(objectMemory isIntegerObject: rcvr) ifTrue:
  		[^self pop: 2 thenPushBool: false].
  
+ 	lastField := self lastPointerOf: rcvr.
- 	"Inlined version of lastPointerOf: for speed in determining if rcvr is a context."
- 	header := objectMemory baseHeader: rcvr.
- 	fmt := objectMemory formatOfHeader: header.
- 	fmt <= 4
- 		ifTrue:
- 			[(fmt = 3
- 			  and: [objectMemory isContextHeader: header]) 
- 				ifTrue:
- 	 				[(self isMarriedOrWidowedContext: rcvr) ifTrue:
- 						[self externalWriteBackHeadFramePointers.
- 						 (self isStillMarriedContext: rcvr) ifTrue:
- 							[^self pop: 2
- 									thenPushBool: (self marriedContext: rcvr
- 														pointsTo: thang
- 														stackDeltaForCurrentFrame: 2)]].
- 					"contexts end at the stack pointer"
- 					lastField := CtxtTempFrameStart + (self fetchStackPointerOf: rcvr) * BytesPerWord]
- 				ifFalse:
- 					[lastField := (objectMemory sizeBitsOfSafe: rcvr) - BaseHeaderSize]]
- 		ifFalse:
- 			[fmt < 12 "no pointers" ifTrue:
- 				[^self pop: 2 thenPushBool: false].
- 			"CompiledMethod: contains both pointers and bytes:"
- 			methodHeader := self headerOf: rcvr.
- 			methodHeader = thang ifTrue: [^self pop: 2 thenPushBool: true].
- 			lastField := ((self literalCountOfHeader: methodHeader) + 1) * BytesPerWord].
- 
  	BaseHeaderSize to: lastField by: BytesPerWord do:
  		[:i |
  		(self longAt: rcvr + i) = thang ifTrue:
  			[^self pop: 2 thenPushBool: true]].
  	self pop: 2 thenPushBool: false!

Item was changed:
  ----- Method: NewspeakInterpreter>>primitiveBeCursor (in category 'I/O primitives') -----
  primitiveBeCursor
  	"Set the cursor to the given shape. The Mac only supports 16x16 pixel cursors. Cursor offsets are handled by Smalltalk."
  
  	| cursorObj maskBitsIndex maskObj bitsObj extentX extentY depth offsetObj offsetX offsetY cursorBitsIndex ourCursor |
  
- self flag: #Dan.  "This is disabled until we convert bitmaps appropriately"
- BytesPerWord = 8 ifTrue: [^ self pop: argumentCount].
- 
  	argumentCount = 0 ifTrue: [
  		cursorObj := self stackTop.
  		maskBitsIndex := nil].
  	argumentCount = 1 ifTrue: [
  		cursorObj := self stackValue: 1.
  		maskObj := self stackTop].
  	self success: (argumentCount < 2).
  
  	self success: ((self isPointers: cursorObj) and: [(self lengthOf: cursorObj) >= 5]).
  	self successful ifTrue: [
  		bitsObj := self fetchPointer: 0 ofObject: cursorObj.
  		extentX := self fetchInteger: 1 ofObject: cursorObj.
  		extentY := self fetchInteger: 2 ofObject: cursorObj.
  		depth := self fetchInteger: 3 ofObject: cursorObj.
  		offsetObj := self fetchPointer: 4 ofObject: cursorObj].
  		self success: ((self isPointers: offsetObj) and: [(self lengthOf: offsetObj) >= 2]).
  
  	self successful ifTrue: [
  		offsetX := self fetchInteger: 0 ofObject: offsetObj.
  		offsetY := self fetchInteger: 1 ofObject: offsetObj.
  		self success: ((extentX = 16) and: [extentY = 16 and: [depth = 1]]).
  		self success: ((offsetX >= -16) and: [offsetX <= 0]).
  		self success: ((offsetY >= -16) and: [offsetY <= 0]).
  		self success: ((self isWords: bitsObj) and: [(self lengthOf: bitsObj) = 16]).
  		cursorBitsIndex := bitsObj + BaseHeaderSize.
  		self cCode: '' inSmalltalk:
  			[ourCursor := Cursor
  				extent: extentX @ extentY
  				fromArray: ((1 to: 16) collect: [:i |
  					((self fetchLong32: i-1 ofObject: bitsObj) >> (BytesPerWord*8 - 16)) bitAnd: 16rFFFF])
  				offset: offsetX  @ offsetY]].
  
  	argumentCount = 1 ifTrue: [
  		self success: ((self isPointers: maskObj) and: [(self lengthOf: maskObj) >= 5]).
  		self successful ifTrue: [
  			bitsObj := self fetchPointer: 0 ofObject: maskObj.
  			extentX := self fetchInteger: 1 ofObject: maskObj.
  			extentY := self fetchInteger: 2 ofObject: maskObj.
  			depth := self fetchInteger: 3 ofObject: maskObj].
  
  		self successful ifTrue: [
  			self success: ((extentX = 16) and: [extentY = 16 and: [depth = 1]]).
  			self success: ((self isWords: bitsObj) and: [(self lengthOf: bitsObj) = 16]).
  			maskBitsIndex := bitsObj + BaseHeaderSize]].
  
  	self successful ifTrue: [
  		argumentCount = 0
  			ifTrue: [self cCode: 'ioSetCursor(cursorBitsIndex, offsetX, offsetY)'
  						inSmalltalk: [ourCursor show]]
  			ifFalse: [self cCode: 'ioSetCursorWithMask(cursorBitsIndex, maskBitsIndex, offsetX, offsetY)'
  						inSmalltalk: [ourCursor show]].
  		self pop: argumentCount].
  !

Item was changed:
  ----- Method: StackInterpreter>>instVar:ofContext:put: (in category 'frame access') -----
  instVar: index ofContext: aMarriedContext put: anOop
  	| theFP |
  	"Assign the field of a married context.  The important case to optimize is
  	 assigning the sender.  We could also consider optimizing assiging the IP but
  	 typically that is followed by an assignment to the stack pointer and we can't
  	 efficiently assign the stack pointer because it involves moving frames around."
  	<inline: true>
  	self assert: (self isMarriedOrWidowedContext: aMarriedContext).
  	self writeBackHeadFramePointers.
  	(self isStillMarriedContext: aMarriedContext) ifFalse:
  		[objectMemory storePointer: index ofObject: aMarriedContext withValue: anOop.
  		 index = StackPointerIndex ifTrue:
  			[self ensureContextIsExecutionSafeAfterAssignToStackPointer: aMarriedContext].
  		 ^nil].
  	theFP := self frameOfMarriedContext: aMarriedContext.
  	index == SenderIndex ifTrue:
  		[| thePage onCurrentPage |
  		 thePage := stackPages stackPageFor: theFP.
  		 self assert: stackPage = stackPages mostRecentlyUsedPage.
  		 onCurrentPage := thePage = stackPage.
  		 self storeSenderOfFrame: theFP withValue: anOop.
  		 onCurrentPage
  			ifTrue:
  				[localFP := stackPage headFP.
  				 localSP := stackPage headSP]
  			ifFalse:
  				[stackPages markStackPageMostRecentlyUsed: stackPage].
  		 ^nil].
  	self externalizeIPandSP.
  	self externalDivorceFrame: theFP andContext: aMarriedContext.
+ 	objectMemory storePointer: index ofObject: aMarriedContext withValue: anOop.
- 	objectMemory storePointer: index ofObject: aMarriedContext withValue: anOop..
  	index = StackPointerIndex ifTrue:
  		[self ensureContextIsExecutionSafeAfterAssignToStackPointer: aMarriedContext].
+ 	self internalizeIPandSP.
+ 	"Assigning various fields can force a divorce which can change the stackPage."
+ 	stackPages markStackPageMostRecentlyUsed: stackPage.
+ 	self assertValidExecutionPointe: localIP r: localFP s: localSP imbar: true!
- 	self internalizeIPandSP!

Item was changed:
  ----- Method: StackInterpreter>>printFrameAndCallers:SP:short: (in category 'debug printing') -----
  printFrameAndCallers: theFP SP: theSP short: printShort
  	<inline: false>
  	<var: #theFP type: #'char *'>
  	<var: #theSP type: #'char *'>
  	(stackPages couldBeFramePointer: theFP) ifFalse: [^nil].
  	(self isBaseFrame: theFP) ifFalse:
  		[self printFrameAndCallers: (self frameCallerFP: theFP)
  			SP: (self frameCallerSP: theFP)
  			short: printShort].
+ 	printShort ifTrue:
+ 		[self shortPrintFrame: theFP.
+ 		 ^nil].
  	self cr.
+ 	self printFrame: theFP WithSP: theSP!
- 	printShort
- 		ifTrue: [self shortPrintFrame: theFP]
- 		ifFalse: [self printFrame: theFP WithSP: theSP]!

Item was changed:
  ----- Method: StackInterpreter>>shortPrintOop: (in category 'debug printing') -----
  shortPrintOop: oop
  	<inline: false>
+ 	self printHex: oop.
- 	self printNum: oop.
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[^self cCode: 'printf("=%ld\n", (long)integerValueOf(oop))' inSmalltalk: [self print: (self shortPrint: oop); cr]].
  	(oop between: objectMemory startOfMemory and: objectMemory freeStart) ifFalse:
  		[self printHex: oop; print: ' is not on the heap'; cr.
  		 ^nil].
  	(oop bitAnd: (BytesPerWord - 1)) ~= 0 ifTrue:
  		[self printHex: oop; print: ' is misaligned'; cr.
  		 ^nil].
  	self print: ': a(n) '.
  	self printNameOfClass: (objectMemory fetchClassOf: oop) count: 5.
  	self cr!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveFindHandlerContext (in category 'control primitives') -----
+ primitiveFindHandlerContext
+ 	"Primitive. Search up the context stack for the next method context marked
+ 	 for exception handling starting at the receiver. Return nil if none found"
+ 	| handlerOrNilOrZero |
+ 	self externalWriteBackHeadFramePointers.
+ 	handlerOrNilOrZero := self
+ 							findMethodWithPrimitive: 199
+ 							FromContext: self stackTop
+ 							UpToContext: objectMemory nilObject.
+ 	handlerOrNilOrZero = 0 ifTrue:
+ 		[handlerOrNilOrZero := objectMemory nilObject].
+ 	self pop: 1 thenPush: handlerOrNilOrZero!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveFindNextUnwindContext (in category 'control primitives') -----
+ primitiveFindNextUnwindContext
+ 	"Primitive. Search up the context stack for the next method context marked for unwind
+ 	 handling from the receiver up to but not including the argument. Return nil if none found."
+ 	| stopContext calleeContext handlerOrNilOrZero |
+ 	<var: #theFP type: #'char *'>
+ 	stopContext := self stackTop.
+ 	calleeContext := self stackValue: 1.
+ 	(stopContext = objectMemory nilObject or: [self isContext: stopContext]) ifFalse:
+ 		[^self primitiveFail].
+ 	self externalWriteBackHeadFramePointers.
+ 	(self isStillMarriedContext: calleeContext)
+ 		ifTrue:
+ 			[| theFP |
+ 			 theFP := self frameOfMarriedContext: calleeContext.
+ 			 (self isBaseFrame: theFP)
+ 				ifTrue:
+ 					[handlerOrNilOrZero := self findMethodWithPrimitive: 198
+ 												FromContext: (self frameCallerContext: theFP)
+ 												UpToContext: stopContext]
+ 				ifFalse:
+ 					[handlerOrNilOrZero :=  self findMethodWithPrimitive: 198
+ 												FromFP: (self frameCallerFP: theFP)
+ 												UpToContext: stopContext]]
+ 		ifFalse:
+ 			[| startContext |
+ 			 startContext := objectMemory fetchPointer: SenderIndex ofObject: calleeContext.
+ 			 (self isContext: startContext)
+ 				ifTrue:
+ 					[handlerOrNilOrZero := self findMethodWithPrimitive: 198
+ 												FromContext: startContext
+ 												UpToContext: stopContext]
+ 				ifFalse:
+ 					[handlerOrNilOrZero := 0]].
+ 	handlerOrNilOrZero = 0 ifTrue:
+ 		[handlerOrNilOrZero := objectMemory nilObject].
+ 	self pop: 2 thenPush: handlerOrNilOrZero!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveFullGC (in category 'memory space primitives') -----
+ primitiveFullGC
+ 	"Do a full garbage collection and return the number of bytes available (including swap space if dynamic memory management is supported)."
+ 
+ 	objectMemory fullGCLock > 0 ifTrue:
+ 		[^self primitiveFailFor: PrimErrInappropriate].
+ 	self externalWriteBackHeadFramePointers.
+ 	objectMemory incrementalGC.  "maximimize space for forwarding table"
+ 	objectMemory fullGC.
+ 	self pop: 1 thenPushInteger: (objectMemory bytesLeft: true).!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveIncrementalGC (in category 'memory space primitives') -----
+ primitiveIncrementalGC
+ 	"Do a quick, incremental garbage collection and return the number of bytes immediately available.
+ 	 (Note: more space may be made available by doing a full garbage collection."
+ 
+ 	self externalWriteBackHeadFramePointers.
+ 	objectMemory incrementalGC.
+ 	self pop: 1 thenPushInteger: (objectMemory bytesLeft: false)!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveInstVarAt (in category 'object access primitives') -----
+ primitiveInstVarAt
+ 	| index rcvr hdr fmt totalLength fixedFields value |
+ 	index := self stackIntegerValue: 0.
+ 	rcvr := self stackValue: 1.
+ 	self successful ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	hdr := objectMemory baseHeader: rcvr.
+ 	fmt := objectMemory formatOfHeader: hdr.
+ 	totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
+ 	fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
+ 	(index >= 1 and: [index <= fixedFields]) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadIndex].
+ 	(fmt = 3
+ 	 and: [objectMemory isContextHeader: hdr])
+ 		ifTrue: [value := self externalInstVar: index - 1 ofContext: rcvr]
+ 		ifFalse: [value := self subscript: rcvr with: index format: fmt].
+ 	self pop: argumentCount + 1 thenPush: value!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveInstVarAtPut (in category 'object access primitives') -----
+ primitiveInstVarAtPut
+ 	| newValue index rcvr hdr fmt totalLength fixedFields |
+ 	newValue := self stackTop.
+ 	index := self stackIntegerValue: 1.
+ 	rcvr := self stackValue: 2.
+ 	self successful ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	hdr := objectMemory baseHeader: rcvr.
+ 	fmt := objectMemory formatOfHeader: hdr.
+ 	totalLength := objectMemory lengthOf: rcvr baseHeader: hdr format: fmt.
+ 	fixedFields := objectMemory fixedFieldsOf: rcvr format: fmt length: totalLength.
+ 	(index >= 1 and: [index <= fixedFields]) ifFalse:
+ 		[^self primitiveFailFor: PrimErrBadIndex].
+ 	(fmt = 3
+ 	 and: [objectMemory isContextHeader: hdr])
+ 		ifTrue: [self externalInstVar: index - 1 ofContext: rcvr put: newValue]
+ 		ifFalse: [self subscript: rcvr with: index storing: newValue format: fmt].
+ 	self pop: argumentCount + 1 thenPush: newValue!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveObjectPointsTo (in category 'object access primitives') -----
+ primitiveObjectPointsTo
+ 	"This primitive is assumed to be fast (see e.g. MethodDictionary>>includesKey:) so make it so.
+ 	 N.B.  Written to use literalHeaderOf: so that in Cog subclasses cogged methods (whose headers
+ 	 point to the machine code method) are still correctly scanned, for the header as well as literals."
+ 	| rcvr thang header fmt lastField methodHeader |
+ 	thang := self stackTop.
+ 	rcvr := self stackValue: 1.
+ 	(objectMemory isIntegerObject: rcvr) ifTrue:
+ 		[^self pop: 2 thenPushBool: false].
+ 
+ 	"Inlined version of lastPointerOf: for speed in determining if rcvr is a context."
+ 	header := objectMemory baseHeader: rcvr.
+ 	fmt := objectMemory formatOfHeader: header.
+ 	fmt <= 4
+ 		ifTrue:
+ 			[(fmt = 3
+ 			  and: [objectMemory isContextHeader: header]) 
+ 				ifTrue:
+ 	 				[(self isMarriedOrWidowedContext: rcvr) ifTrue:
+ 						[self externalWriteBackHeadFramePointers.
+ 						 (self isStillMarriedContext: rcvr) ifTrue:
+ 							[^self pop: 2
+ 									thenPushBool: (self marriedContext: rcvr
+ 														pointsTo: thang
+ 														stackDeltaForCurrentFrame: 2)]].
+ 					"contexts end at the stack pointer"
+ 					lastField := CtxtTempFrameStart + (self fetchStackPointerOf: rcvr) * BytesPerWord]
+ 				ifFalse:
+ 					[lastField := (objectMemory sizeBitsOfSafe: rcvr) - BaseHeaderSize]]
+ 		ifFalse:
+ 			[fmt < 12 "no pointers" ifTrue:
+ 				[^self pop: 2 thenPushBool: false].
+ 			"CompiledMethod: contains both pointers and bytes:"
+ 			methodHeader := self headerOf: rcvr.
+ 			methodHeader = thang ifTrue: [^self pop: 2 thenPushBool: true].
+ 			lastField := ((self literalCountOfHeader: methodHeader) + 1) * BytesPerWord].
+ 
+ 	BaseHeaderSize to: lastField by: BytesPerWord do:
+ 		[:i |
+ 		(self longAt: rcvr + i) = thang ifTrue:
+ 			[^self pop: 2 thenPushBool: true]].
+ 	self pop: 2 thenPushBool: false!

Item was changed:
  StackInterpreterPrimitives subclass: #StackInterpreterSimulator
  	instanceVariableNames: 'byteCount breakCount sendCount printSends printReturns traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
  
+ !StackInterpreterSimulator commentStamp: 'eem 2/13/2013 15:23' prior: 0!
- !StackInterpreterSimulator commentStamp: '<historical>' 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
  
+ 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 |
+ StackInterpreter initializeWithOptions: (Dictionary newFromPairs: #()).
+ vm := StackInterpreterSimulator new.
+ vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
+ vm setBreakSelector: #&.
+ vm openAsMorph; run!
- 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. You will probably have more luck using InterpreteSimulatorLSB or InterpreterSimulatorMSB as befits your machine.!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakCogVM (in category 'configurations') -----
  generateSqueakCogVM
  	^VMMaker
  		generate: (Smalltalk at: ([:choices| choices at: (UIManager default chooseFrom: choices) ifAbsent: [^self]]
  									value: #(CoInterpreter CoInterpreterMT)))
  		and: StackToRegisterMappingCogit
  		with: #(	MULTIPLEBYTECODESETS false
  				NewspeakVM false)
  		to: (FileDirectory default pathFromURI: 'oscogvm/src')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
+ 		including:#(	AioPlugin ADPCMCodecPlugin AsynchFilePlugin BalloonEnginePlugin B3DAcceleratorPlugin
- 		including:#(	ADPCMCodecPlugin AsynchFilePlugin BalloonEnginePlugin B3DAcceleratorPlugin
  					BMPReadWriterPlugin BitBltSimulation BochsIA32Plugin CroquetPlugin DSAPlugin
  					DeflatePlugin DropPlugin FT2Plugin FFTPlugin FileCopyPlugin FilePlugin FloatArrayPlugin
  					FloatMathPlugin GeniePlugin HostWindowPlugin IA32ABIPlugin InternetConfigPlugin
  					JPEGReadWriter2Plugin JPEGReaderPlugin JoystickTabletPlugin KlattSynthesizerPlugin
  					LargeIntegersPlugin LocalePlugin MIDIPlugin MacMenubarPlugin Matrix2x3Plugin
  					MiscPrimitivePlugin Mpeg3Plugin QuicktimePlugin RePlugin SecurityPlugin SerialPlugin
  					SocketPlugin SoundCodecPlugin SoundGenerationPlugin SoundPlugin ThreadedIA32FFIPlugin
  					StarSqueakPlugin UUIDPlugin UnixOSProcessPlugin Win32OSProcessPlugin VMProfileMacSupportPlugin)!



More information about the Vm-dev mailing list