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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 15 04:28:07 UTC 2015


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

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

Name: VMMaker.oscog-eem.1418
Author: eem
Time: 14 July 2015, 9:26:06.427 pm
UUID: ec9f7a35-a5c8-4eb2-ad7d-c3f0cb2e2e84
Ancestors: VMMaker.oscog-eem.1417

Simulator:
Rename Timothy's StackInterpreterSimulatorFoo classes tosomething a little less of a mouthful.  Plumb his (now) SimulatorEventTransformer into the existing simple simulator UI. (thnks Tmothy!  Sorry I've been so long getting to this)  Copy the event queue code from StackInterpreterSimulator to CogVMSimulator.  Fix Spur64BitMemoryManager>>newInputEventAccessorOfSize: and allow CPluggableAccessor to hard-code the size.

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

Item was changed:
  CArrayAccessor subclass: #CPluggableAccessor
+ 	instanceVariableNames: 'readBlock writeBlock objectSize'
- 	instanceVariableNames: 'readBlock writeBlock'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
  
  !CPluggableAccessor commentStamp: 'tpr 5/5/2003 11:49' prior: 0!
  This class adds generalized block parameter access to C objects for vm simulation!

Item was added:
+ ----- Method: CPluggableAccessor>>objectSize: (in category 'initialize') -----
+ objectSize: n
+ 	objectSize := n!

Item was added:
+ ----- Method: CPluggableAccessor>>size (in category 'accessing') -----
+ size
+ 	^objectSize ifNil: [super size]!

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
+ 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue'
- 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters'
  	classVariableNames: 'ByteCountsPerMicrosecond'
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' 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.
  
  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:
  
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  	desiredNumStackPages: 8;
  	openOn: '/Users/eliot/Cog/startreader.image';
  	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!

Item was changed:
  ----- Method: CogVMSimulator>>initialize (in category 'initialization') -----
  initialize
  	"Initialize the CogVMSimulator when running the interpreter inside Smalltalk.  The
  	 primary responsibility of this method is to allocate Smalltalk Arrays for variables
  	 that will be declared as statically-allocated global arrays in the translated code."
  	super initialize.
  
  	transcript := Transcript.
  
  	objectMemory ifNil:
  		[objectMemory := self class objectMemoryClass simulatorClass new].
  	cogit ifNil:
  		[cogit := self class cogitClass new setInterpreter: self].
  	objectMemory coInterpreter: self cogit: cogit.
  
  	cogit numRegArgs > 0 ifTrue:
  		[debugStackDepthDictionary := Dictionary new].
  
  	cogThreadManager ifNotNil:
  		[super initialize].
  
  	"Note: we must initialize ConstMinusOne & HasBeenReturnedFromMCPC differently
  	 for simulation, due to the fact that the simulator works only with +ve 32-bit values"
  	ConstMinusOne := objectMemory integerObjectOf: -1.
  	HasBeenReturnedFromMCPC := objectMemory integerObjectOf: -1.
  	cogMethodZone := cogit methodZone. "Because Slang can't remove intermediate implicit receivers (cogit methodZone foo doesn't reduce to foo())"
  	enableCog := true.
  
  	methodCache := Array new: MethodCacheSize.
  	nsMethodCache := Array new: NSMethodCacheSize.
  	atCache := Array new: AtCacheTotalSize.
  	self flushMethodCache.
  	cogCompiledCodeCompactionCalledFor := false.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
  	mappedPluginEntries := OrderedCollection new.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[primitiveAccessorDepthTable := Array new: primitiveTable size.
  			 pluginList := {}.
  			 self loadNewPlugin: '']
  		ifFalse:
  			[pluginList := {'' -> self }].
  	desiredNumStackPages := desiredEdenBytes := desiredCogCodeSize := 0.
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := Time totalSeconds * 1000000.
  	maxLiteralCountForCompile := MaxLiteralCountForCompile.
  	minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  	flagInterpretedMethods := false.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := lastPollCount := sendCount := lookupCount := 0.
  	quitBlock := [^ self].
  	traceOn := true.
  	printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
+ 	eventQueue := SharedQueue new.
  	suppressHeartbeatFlag := deferSmash := deferredSmash := false.
  	systemAttributes := Dictionary new.
  	primTraceLog := CArrayAccessor on: (Array new: 256 withAll: 0).
  	primTraceLogIndex := 0.
  	traceLog := CArrayAccessor on: (Array new: TraceBufferSize withAll: 0).
  	traceLogIndex := 0.
  	traceSources := TraceSources.
  	statCodeCompactionCount := 0.
  	statCodeCompactionUsecs := 0.
  	extSemTabSize := 256!

Item was changed:
  ----- Method: CogVMSimulator>>ioGetNextEvent: (in category 'I/O primitives') -----
  ioGetNextEvent: evtBuf
+ 	| evt |
+ 	"SimulatorMorphicModel browse"
+ 	eventQueue ifNil:
+ 		[^self primitiveFail].
+ 	eventQueue isEmpty ifFalse:
+ 		[evt :=  eventQueue next.
+ 		 1 to: evt size do:
+ 			[:i| (evt at: i) ifNotNil: [:val| evtBuf at: (i - 1) put: val]]]!
- 
- 	self primitiveFail.
- !

Item was changed:
  ----- Method: CogVMSimulator>>openAsMorph (in category 'UI') -----
  openAsMorph
  	"Open a morphic view on this simulation."
  	| localImageName borderWidth window |
  	localImageName := imageName
  							ifNotNil: [FileDirectory default localNameFor: imageName]
  							ifNil: [' synthetic image'].
  	window := (SystemWindow labelled: 'Simulation of ', localImageName) model: self.
  
  	window addMorph: (displayView := ImageMorph new image: displayForm)
+ 			frame: (0 at 0 corner: 1 at 0.8).
+ 	displayView activeHand addEventListener: self.
- 		frame: (0 at 0 corner: 1 at 0.8).
  
  	transcript := TranscriptStream on: (String new: 10000).
  	window addMorph: (PluggableTextMorph
  							on: transcript text: nil accept: nil
  							readSelection: nil menu: #codePaneMenu:shifted:)
  			frame: (0 at 0.8 corner: 0.7 at 1).
  	window addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil
  						readSelection: nil menu: #utilitiesMenu:) hideScrollBarsIndefinitely
  			frame: (0.7 at 0.8 corner: 1 at 1).
  
  	borderWidth := [SystemWindow borderWidth] "Squeak 4.1"
  						on: MessageNotUnderstood
  						do: [:ex| 0]. "3.8"
  	borderWidth := borderWidth + window borderWidth.
  	window openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * borderWidth)
  								+ (0 at window labelHeight)
  								* (1@(1/0.8))) rounded.
  	^window!

Item was changed:
  ----- Method: CogVMSimulator>>openAsMorphNoTranscript (in category 'UI') -----
  openAsMorphNoTranscript
  	"Open a morphic view on this simulation."
  	| localImageName borderWidth window |
  	localImageName := FileDirectory default localNameFor: imageName.
  	window := (SystemWindow labelled: 'Simulation of ' , localImageName) model: self.
  
  	window addMorph: (displayView := ImageMorph new image: displayForm)
+ 			frame: (0 at 0 corner: 1 at 0.95).
+ 	displayView activeHand addEventListener: self.
- 		frame: (0 at 0 corner: 1 at 0.95).
  
  	window addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil
  						readSelection: nil menu: #utilitiesMenu:) hideScrollBarsIndefinitely
  		frame: (0 at 0.95 corner: 1 at 1).
  
  	borderWidth := [SystemWindow borderWidth] "Squeak 4.1"
  						on: MessageNotUnderstood
  						do: [:ex| 0]. "3.8"
  	borderWidth := borderWidth + window borderWidth.
  	window openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * borderWidth)
  								+ (0 at window labelHeight)
  								* (1@(1/0.95))) rounded!

Item was added:
+ Object subclass: #SimulatorEventTransformer
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'Default'
+ 	poolDictionaries: 'EventSensorConstants'
+ 	category: 'VMMaker-InterpreterSimulation-Morphic'!
+ 
+ !SimulatorEventTransformer commentStamp: 'eem 7/14/2015 17:05' prior: 0!
+ A SimulatorEventTransformer takes events as wrapped by HandMorph and converts them to a form a StackInterpreterSimulator can deal with.
+ 
+ See HandMorph >> handleEvent to see what the wrapping entails.
+ See HandMorph >> ProcessEvents  or EventSensor >> fetchMoreEvents for examples of what an unwrapped event looks like when given to the system for pre-wrapping.
+ 
+ Instance Variables
+ !

Item was added:
+ ----- Method: SimulatorEventTransformer class>>default (in category 'initialize-release') -----
+ default
+ 	^Default ifNil:[Default := self new]!

Item was added:
+ ----- Method: SimulatorEventTransformer class>>eventTypeMouse (in category 'accessing') -----
+ eventTypeMouse
+ 	^EventTypeMouse!

Item was added:
+ ----- Method: SimulatorEventTransformer>>degenerateEvent: (in category 'event transformation') -----
+ degenerateEvent: aMorphicEvent
+ 	"tty. Bert had mentioned a distinction between events and polling events and that Morphic could handle both.
+ 	I don't know what he is talking about."	
+ 	| evt type |
+ 	self flag:'tty'.
+ 
+ 	evt := nil.	
+ 	type := aMorphicEvent type.
+ "	Transcript show:type;cr."
+ 	(('mouse' charactersExactlyMatching: type asString) > 4)  "mous"
+ 		ifTrue: [^self degenerateMouseEvent: aMorphicEvent].
+ 	(('key' charactersExactlyMatching: type asString) > 2)  "key"
+ 		ifTrue: [^self degenerateKeyboardEvent: aMorphicEvent].
+ "	type = EventTypeDragDropFiles ifTrue: [evt := self generateDropFilesEvent: evtBuf].
+ 	type = EventTypeWindow	ifTrue:[evt := self generateWindowEvent: evtBuf]."
+ 
+ 	^ #(0 0 0 0 0 0 0 0).!

Item was added:
+ ----- Method: SimulatorEventTransformer>>degenerateKeyboardEvent: (in category 'event transformation') -----
+ degenerateKeyboardEvent: aMorphicEvent
+ 	| evt |
+ 	"see HandMorph>>generateKeyboardEvent and EventSensor class comment"
+ 	evt := {2 . 0 . 0 . 0 . 0. 0 . 0 . 0}.
+ 	
+ 	evt at:2 put: aMorphicEvent timeStamp.
+ 	evt at:3 put: aMorphicEvent keyValue.    "<--this is wrong. See Sensor FirstEvt: for what needs to happen. hooo boy"
+ 	evt at:4 put: aMorphicEvent position y.
+ 	evt at:5 put: (aMorphicEvent buttons bitAnd: 7).  "thanks Ron T."
+ 	evt at:6 put: (aMorphicEvent buttons >> 3).     "Thanks dtl"
+ 	^evt
+ 
+ 
+ !

Item was added:
+ ----- Method: SimulatorEventTransformer>>degenerateMouseButtonEvent: (in category 'event transformation') -----
+ degenerateMouseButtonEvent: aMorphicEvent
+ 	| evt |
+ 	"see HandMorph>>generateMouseEvent"
+ 	evt := {1 . 0 . 0 . 0 . 0. 0 . 0 . 0}.
+ 	
+ 	evt at:2 put: aMorphicEvent timeStamp.
+ 	evt at:3 put: aMorphicEvent position x.
+ 	evt at:4 put: aMorphicEvent position y.
+ 	evt at:5 put: (aMorphicEvent buttons bitAnd: 7).  "thanks Ron T."
+ 	evt at:6 put: (aMorphicEvent buttons >> 3).     "Thanks dtl"
+ 	^evt
+ 
+ 
+ !

Item was added:
+ ----- Method: SimulatorEventTransformer>>degenerateMouseEvent: (in category 'event transformation') -----
+ degenerateMouseEvent: aMorphicEvent
+ 	"see HandMorph>>generateMouseEvent"
+ 
+ 	(aMorphicEvent type) = #mouseMove
+ 		ifTrue:[^self degenerateMouseMoveEvent: aMorphicEvent].	
+ 
+ 	((aMorphicEvent type) = #mouseUp) |  ((aMorphicEvent type) = #mouseDown)
+ 		ifTrue:[^self degenerateMouseButtonEvent: aMorphicEvent].	
+ "	(aMorphicEvent type) = #mouseDrag
+ 		ifTrue:[evt := self degenerateMouseDragEvent: aMorphicEvent].	
+ "
+ 	^{0 . 0. 0. 0. 0. 0. 0. 0}.!

Item was added:
+ ----- Method: SimulatorEventTransformer>>degenerateMouseMoveEvent: (in category 'event transformation') -----
+ degenerateMouseMoveEvent: aMorphicEvent
+ 	| evt |
+ 	"see HandMorph>>generateMouseEvent"
+ 	evt := {1 . 0 . 0 . 0 . 0. 0 . 0 . 0}.
+ 	
+ 	evt at:2 put: aMorphicEvent timeStamp.
+ 	evt at:3 put: aMorphicEvent position x.
+ 	evt at:4 put: aMorphicEvent position y.
+ 	evt at:5 put: (aMorphicEvent buttons bitAnd: 7).  "thanks Ron T."
+ 	evt at:6 put: (aMorphicEvent buttons >> 3).     "Thanks dtl"
+ 	^evt
+ 
+ 
+ !

Item was added:
+ ImageMorph subclass: #SimulatorImageMorph
+ 	instanceVariableNames: 'eventForwarder'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-InterpreterSimulation-Morphic'!
+ 
+ !SimulatorImageMorph commentStamp: 'eem 7/14/2015 17:05' prior: 0!
+ A SimulatorImageMorph is an ImageMorph The StackInterpreterSimulator paints its world on me.  If tty can get event forwarding working along the HandMorph->StackInterpreterSimulatorMorphicModel->StackInterpreterSimulator path, then then I don't need to exist.  If event forwarding attempt above fails, then I may need to handle it.
+ 
+ 
+ Instance Variables
+ 
+ !

Item was added:
+ SystemWindow subclass: #SimulatorMorph
+ 	instanceVariableNames: 'loadButton helpButton resetButton stepButton overButton sendButton returnButton runButton toggleTranscriptButton optionsButton transcriptPanel commandPanel contextPanel stackPanel callStackPanel displayForm displayView eventEncoder ioExitButton fullDisplayUpdateButton forceInterruptCheckButton hackButton'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-InterpreterSimulation-Morphic'!
+ 
+ !SimulatorMorph commentStamp: 'eem 7/14/2015 17:06' prior: 0!
+ A SimulatorMorph is a copy of PreferenceBrowserMorph that has been mangled into something that will support the simulator.  I provide some UI features inspired by Bert Freudenberg's Lively Squeak VM at http://lively-web.org/users/bert/squeak.html.
+ 
+ See class protocol 'documentation' for examples of invoking me.
+ 
+ My model is SimulatorMorphicModel. 
+ My model has a reference to the Simulator and itermediates all (?) interaction with it.
+ 
+ The simulator renders the simulated World on a SimulatorImageMorph that I contain. 
+ 
+ There is some cruft (tight coupling via direct references along all three layers UI-Model-VM) in me that exists to support Eliot's original Simulator>>openAsMorph functionality and use-case.
+ Rumors that said cruft is an artifact of tty's rudimentary Morphic skills are entirely credible.
+ 
+ I hold out the barest glimmer of hope that Bert Freudenberg's SqueakJS functionality can be integrated into my functionality as well. 
+ see http://lively-web.org/users/bert/squeak.html for the inspiration.
+ 
+ I am not amenable to Flaps or the WorldMenu as there is a lot of pre-run configuration that is done to the Simulator prior to its being run.
+ Managing that ability with a GUI is counter-productive. If said functionality is desired in the future, then inspiration can be gleaned by cut-n-paste from PreferenceBrowser and PreferenceBrowserModel.!

Item was added:
+ ----- Method: SimulatorMorph class>>ttyOne (in category 'documentation') -----
+ ttyOne
+ "Script tty uses to run the stackIntepreter using this class"
+ | vm |
+ Transcript clear.
+ vm := StackInterpreterSimulator newWithOptions: #(#STACKVM).
+ vm openOn: '/home/tty/usr/src/smalltalk/buildCogDevelopmentImageCog.app/Contents/Resources/targets/Squeak4.5.image'.
+ "vm setBreakSelector: #&."
+ vm 
+ 	openAsSimulatorMorph "; 
+ 	toggleTranscript;
+ 	halt;
+ 	run"
+ !

Item was added:
+ ----- Method: SimulatorMorph class>>withVMSimulator:title:transcript: (in category 'instance creation') -----
+ withVMSimulator: aSimulatorMorphicModel title: aString transcript: aTranscript
+ 	^self new initializeWithVMSimulator: aSimulatorMorphicModel title: aString aTranscript: aTranscript;
+ 		yourself.
+ 		
+ !

Item was added:
+ ----- Method: SimulatorMorph>>basicButton (in category 'submorphs - buttons') -----
+ basicButton
+ 	| button |
+ 	button := SimpleButtonMorph new.
+ 	button
+ 		borderWidth: 2;
+ 		borderColor: #raised;
+ 		on: #mouseEnter send: #value to: [button borderColor: self paneColor];
+ 		on: #mouseLeave send: #value to: [button borderColor: #raised];
+ 		vResizing: #spaceFill;
+ 		useRoundedCorners;
+ 		clipSubmorphs: true;
+ 		color: self paneColor muchLighter;
+ 		target: self model.
+ 	^button!

Item was added:
+ ----- Method: SimulatorMorph>>buttonRowLayoutFrame (in category 'submorphs - buttons') -----
+ buttonRowLayoutFrame 
+ 	^LayoutFrame fractions: (0 at 0 corner: 1 at 0) offsets: (0 at 0 corner: 0@ (TextStyle defaultFont height * 2.5))
+ !

Item was added:
+ ----- Method: SimulatorMorph>>callStackPanel (in category 'submorphs - squeakJS') -----
+ callStackPanel
+ 	"If any Morphic gurus exist, please have at it."
+ 	^callStackPanel ifNil: 
+ 		[callStackPanel :=  (PluggableTextMorph
+ 				on: self model
+ 				text: #processesAndContextStack
+ 				accept: nil
+ 				readSelection: nil
+ 				menu: nil) hideScrollBarsIndefinitely.
+ 		callStackPanel		
+ 			color: Color transparent;
+ 			hResizing: #spaceFill;
+ 			vResizing: #spaceFill;
+ 			cellInset: 5;
+ 			yourself].
+ 
+ !

Item was added:
+ ----- Method: SimulatorMorph>>commandPanel (in category 'submorphs - simulator panel') -----
+ commandPanel
+ 	self flag: 'tty'. "does this hybrid of PreferenceBrowser layout and Simulato openAsMorph stuff make sense?"
+ 	^commandPanel ifNil: 
+ 		[commandPanel :=  (PluggableTextMorph
+ 				on: self model vm
+ 				text: #byteCountText
+ 				accept: nil
+ 				readSelection: nil
+ 				menu: #utilitiesMenu:) hideScrollBarsIndefinitely.
+ 		commandPanel		
+ 			color: Color transparent;
+ 			hResizing: #spaceFill;
+ 			vResizing: #spaceFill;
+ 			cellInset: 5;
+ 			yourself].
+ !

Item was added:
+ ----- Method: SimulatorMorph>>contextPanel (in category 'submorphs - squeakJS') -----
+ contextPanel
+ 	"This should show the currentContext and Special Objects array. as seen at SqueakJS
+ 	  Doing that requires real talent. talent tty is lacking at the moment
+ 							on: [ Array with:  (MorphWithSubmorphsWrapper with: self)  ]	
+ 	Array with: (ObjectExplorerWrapper with: rootObject name: 'root' model: self parent: nil)
+ 	"
+ 	^contextPanel ifNil: 
+ 		[contextPanel := (SimpleHierarchicalListMorph
+ 							on: [ Array with: (ObjectExplorerWrapper with: (self model vm) name: 'root' model: (self model vm) parent: nil) ]
+ 							list: #value
+ 							selected: nil
+ 							changeSelected: nil
+ 							menu: nil
+ 							keystroke: nil) showScrollBarsOnlyWhenNeeded: true.
+ 		contextPanel		
+ 			color: Color transparent;
+ 			hResizing: #spaceFill;
+ 			vResizing: #spaceFill;
+ 			cellInset: 5;
+ 			yourself]
+ 
+ 
+ !

Item was added:
+ ----- Method: SimulatorMorph>>displayView (in category 'submorphs - simulator display view') -----
+ displayView
+ 	"The VM SImulator draws directly on an imageMorph named displayView
+ 	  displayView is housed on a Form named displayForm
+ 	   displayForm is initialized in StackInterpreterSimulator >> initialize.
+ 	  see StackInterpreterSimulator >>openAsMorph for original constructs."
+ 	^displayView ifNil: 
+ 		[displayView :=  SimulatorImageMorph new image: model vm displayForm. 
+ 		self model displayView: displayView.					
+ 		self model morph: displayView. "<-- N.B.. morph bounds are used to filter events in the model. tty"
+ 	      displayView activeHand addEventListener: self model.		
+ 
+  		displayView		
+ 			color: Color transparent;
+ 			hResizing: #spaceFill;
+ 			vResizing: #spaceFill;
+ 			cellInset: 5;
+ 			yourself]!

Item was added:
+ ----- Method: SimulatorMorph>>displayViewLayoutFrame (in category 'submorphs - simulator display view') -----
+ displayViewLayoutFrame 
+ 	| squeakJSFrame buttonFrame simulatorFrame|
+ 	"if any Morphic guru's understand layouts and offsets, please fix this. tty"
+ 	buttonFrame := self buttonRowLayoutFrame.
+ 	squeakJSFrame := self squeakJSRowLayoutFrame.
+ 	simulatorFrame := self simulatorLayoutFrame.
+ 	^LayoutFrame fractions: (0 at 0 corner: 1 at 1) 
+ 				    offsets: (0@(buttonFrame bottomOffset) corner: simulatorFrame leftOffset at squeakJSFrame topOffset)!

Item was added:
+ ----- Method: SimulatorMorph>>extent: (in category 'geometry') -----
+ extent: aPoint
+ 	super extent: aPoint.
+ 	self fullBounds.
+ !

Item was added:
+ ----- Method: SimulatorMorph>>forceInterruptCheckButton (in category 'submorphs - buttons') -----
+ forceInterruptCheckButton
+ 	self flag: 'tty'.
+ 	^forceInterruptCheckButton ifNil: 
+ 		[forceInterruptCheckButton := self basicButton 
+ 						label: 'vm forceInterruptCheck' translated; 
+ 						actionSelector: #forceInterruptCheck;						
+ 						setBalloonText: 
+ 							'Invoke forceInterruptCheck on Simulator.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>fullDisplayUpdateButton (in category 'submorphs - buttons') -----
+ fullDisplayUpdateButton
+ 	self flag: 'tty'.
+ 	^fullDisplayUpdateButton ifNil: 
+ 		[fullDisplayUpdateButton := self basicButton 
+ 						label: 'vm fullDisplayUpdate' translated; 
+ 						actionSelector: #fullDisplayUpdate;						
+ 						setBalloonText: 
+ 							'Invoke fullDisplayUpdate on Simulator.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>hackButton (in category 'submorphs - buttons') -----
+ hackButton
+ 	self flag: 'tty'.
+ 	^hackButton ifNil: 
+ 		[hackButton := self basicButton 
+ 						label: 'Display ImageMorph Bounds' translated; 
+ 						actionSelector: #hack;						
+ 						setBalloonText: 
+ 							'tty needs a hack button.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>helpButton (in category 'submorphs - buttons') -----
+ helpButton
+ 	^helpButton ifNil: 
+ 		[helpButton := self basicButton 
+ 						label: 'help' translated; 
+ 						setBalloonText: 
+ 							'Click here to get some hints on use of me ',
+ 							'Panel' translated;
+ 						actionSelector: #help]!

Item was added:
+ ----- Method: SimulatorMorph>>initializeWithVMSimulator:title:aTranscript: (in category 'initialization') -----
+ initializeWithVMSimulator: aStackInterpreterSimulator title: aString aTranscript: aTranscript
+ 	self flag: 'tty'. "need to get the layout right at this point. resizers and scroll bars would be nice. Layout offsets need a gimlet eye as well"
+ 	self 
+ 		model: (SimulatorMorphicModel on: aStackInterpreterSimulator title: aString transcript: aTranscript);
+ 		clipSubmorphs: true;
+ 		setLabel: self model windowTitle;
+ 		name: aString;
+ 		addMorph: self newButtonRow fullFrame: self buttonRowLayoutFrame;
+ 		addMorph: self squeakJSRow fullFrame: self squeakJSRowLayoutFrame;
+ 		addMorph: self simulatorPanel fullFrame: self simulatorLayoutFrame;
+ 		addMorph: self displayView fullFrame: self displayViewLayoutFrame.	
+ 	^self!

Item was added:
+ ----- Method: SimulatorMorph>>ioExitButton (in category 'submorphs - buttons') -----
+ ioExitButton
+ 	self flag: 'tty'.
+ 	^ioExitButton ifNil: 
+ 		[ioExitButton := self basicButton 
+ 						label: 'vm ioExit' translated; 
+ 						actionSelector: #ioExit;						
+ 						setBalloonText: 
+ 							'Invoke ioExit on Simulator.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>loadButton (in category 'submorphs - buttons') -----
+ loadButton
+ 	^loadButton ifNil: 
+ 		[loadButton := self basicButton 
+ 						label: 'Load Image' translated; 
+ 						actionSelector: #loadImage;						
+ 						setBalloonText: 
+ 							'Select an image to load.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>newButtonRow (in category 'submorphs - buttons') -----
+ newButtonRow
+ 	^BorderedMorph new
+ 		color: Color transparent;
+ 		cellInset: 2;
+ 		layoutInset: 2;
+ 		layoutPolicy: TableLayout new;
+ 		listDirection: #leftToRight;
+ 		listCentering: #topLeft;
+ 		cellPositioning: #topLeft;
+ 		on: #mouseEnter send: #paneTransition: to: self;
+ 		on: #mouseLeave send: #paneTransition: to: self;
+ 		addMorphBack: self hackButton;
+ 		addMorphBack: self newSeparator;
+ 
+ "		addMorphBack: self resetButton;
+ 		addMorphBack: self newSeparator;
+ 		addMorphBack: self forceInterruptCheckButton;
+ 		addMorphBack: self newSeparator;
+ 		addMorphBack: self fullDisplayUpdateButton;
+ 		addMorphBack: self newSeparator;
+ 		addMorphBack: self toggleTranscriptButton;"  
+ 		addMorphBack: self runButton;				
+ 		addMorphBack: self newSeparator; 
+ 		addMorphBack: self ioExitButton;
+ 		addMorphBack: self newTransparentFiller;		
+ 		addMorphBack: self stepButton;
+ 		addMorphBack: self newSeparator;		
+ 		addMorphBack: self overButton;
+ 		addMorphBack: self newSeparator;
+ 		addMorphBack: self newSeparator;		
+ 		addMorphBack: self sendButton;
+ 		addMorphBack: self newSeparator;		
+ 		addMorphBack: self returnButton;		
+ 		addMorphBack: self newTransparentFiller;
+ "		addMorphBack: self loadButton;
+ 		addMorphBack: self newSeparator;				
+ 		addMorphBack: self optionsButton;     too complex to implement now. See StackInterpreterSimulator class comment for examples"										
+ 		addMorphBack: self newTransparentFiller;
+ 		addMorphBack: self helpButton;
+ 		yourself.!

Item was added:
+ ----- Method: SimulatorMorph>>newSeparator (in category 'submorphs - buttons') -----
+ newSeparator
+ 	^BorderedMorph new
+ 		borderWidth: 2;
+ 		borderColor: Color transparent;
+ 		color: self paneColor;
+ 		hResizing: #rigid;
+ 		width: 5;
+ 		vResizing: #spaceFill;
+ 		yourself!

Item was added:
+ ----- Method: SimulatorMorph>>newTransparentFiller (in category 'submorphs - buttons') -----
+ newTransparentFiller
+ 	^Morph new
+ 		color: Color transparent;
+ 		vResizing: #spaceFill;
+ 		hResizing: #spaceFill;
+ 		yourself.!

Item was added:
+ ----- Method: SimulatorMorph>>optionsButton (in category 'submorphs - buttons') -----
+ optionsButton
+ 	^optionsButton ifNil: 
+ 		[optionsButton := self basicButton 
+ 						label: 'VM Options' translated; 
+ 						actionSelector: #options;						
+ 						setBalloonText: 
+ 							'VM Options.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>overButton (in category 'submorphs - buttons') -----
+ overButton
+ 	^overButton ifNil: 
+ 		[overButton := self basicButton 
+ 						label: 'Over' translated; 
+ 						actionSelector: #over;						
+ 						setBalloonText: 
+ 							'Step Over.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>resetButton (in category 'submorphs - buttons') -----
+ resetButton
+ 	^resetButton ifNil: 
+ 		[resetButton := self basicButton 
+ 						label: 'Reset' translated; 
+ 						actionSelector: #reset;						
+ 						setBalloonText: 
+ 							'Reset running simulation.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>returnButton (in category 'submorphs - buttons') -----
+ returnButton
+ 	self flag: 'tty'.
+ 	^returnButton ifNil: 
+ 		[returnButton := self basicButton 
+ 						label: 'Return' translated; 
+ 						actionSelector: #return;						
+ 						setBalloonText: 
+ 							'Return from what?.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>runButton (in category 'submorphs - buttons') -----
+ runButton
+ 	self flag: 'tty'.
+ 	^runButton ifNil: 
+ 		[runButton := self basicButton 
+ 						label: 'vm run' translated; 
+ 						actionSelector: #run;						
+ 						setBalloonText: 
+ 							'Run Simulation.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>sendButton (in category 'submorphs - buttons') -----
+ sendButton
+ 	self flag: 'tty'.
+ 	^sendButton ifNil: 
+ 		[sendButton := self basicButton 
+ 						label: 'Send' translated; 
+ 						actionSelector: #send;						
+ 						setBalloonText: 
+ 							'Send what exactly?.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>simulatorLayoutFrame (in category 'submorphs - simulator panel') -----
+ simulatorLayoutFrame 
+ 	| squeakJSFrame buttonFrame |
+ 	"I don't understand offsets in the LayoutFrame. I just fiddled until it looked ok. If anybody knows what they are doing, please refactor."
+ 	self flag: 'tty'.
+ 	buttonFrame := self buttonRowLayoutFrame.
+ 	squeakJSFrame := self squeakJSRowLayoutFrame.
+ 	^LayoutFrame fractions: (0.7 at 0 corner: 1 at squeakJSFrame topOffset) 
+ 				    offsets: (0@(buttonFrame bottomOffset) corner: 0.70 at squeakJSFrame topOffset)
+ !

Item was added:
+ ----- Method: SimulatorMorph>>simulatorPanel (in category 'submorphs - simulator panel') -----
+ simulatorPanel
+ 	"standard controls from StackInterpreterSimulator >> openAsMorph"
+ 	^BorderedMorph new
+ 		color: Color transparent;
+ 		layoutInset: 10;
+ 		cellInset: 10;
+ 		layoutPolicy: TableLayout new;
+ 		listDirection: #topToBottom;
+ 		listCentering: #topLeft;
+ 		cellPositioning: #topLeft;
+ 		on: #mouseEnter send: #paneTransition: to: self;
+ 		on: #mouseLeave send: #paneTransition: to: self;		
+ 		addMorphBack: self transcriptPanel;
+ 		addMorphBack: self commandPanel;
+ 		yourself.!

Item was added:
+ ----- Method: SimulatorMorph>>squeakJSRow (in category 'submorphs - squeakJS') -----
+ squeakJSRow
+ 	"row fo SqueakJS context, stack and call-stack panels"
+ 	^BorderedMorph new
+ 		color: Color blue;
+ 		cellInset: 2;
+ 		layoutInset: 2;
+ 		layoutPolicy: TableLayout new;
+ 		listDirection: #leftToRight;
+ 		listCentering: #topLeft;
+ 		cellPositioning: #topLeft;
+ 		on: #mouseEnter send: #paneTransition: to: self;
+ 		on: #mouseLeave send: #paneTransition: to: self;
+ 		addMorphBack: self callStackPanel;
+ 		addMorphBack: self contextPanel;
+ 		addMorphBack: self stackPanel;		
+ 		yourself.!

Item was added:
+ ----- Method: SimulatorMorph>>squeakJSRowLayoutFrame (in category 'submorphs - squeakJS') -----
+ squeakJSRowLayoutFrame 
+ 	^LayoutFrame fractions: (0 at 0.8 corner: 1 at 1) offsets: (0 at 0.8 corner: 1@ (TextStyle defaultFont height * 2.5))
+ !

Item was added:
+ ----- Method: SimulatorMorph>>stackPanel (in category 'submorphs - squeakJS') -----
+ stackPanel
+ 	"If any Morphic gurus exist, please have at it."
+ 	^stackPanel ifNil: 
+ 		[stackPanel :=  (PluggableTextMorph
+ 				on: self model
+ 				text: #currentContextStack
+ 				accept: nil
+ 				readSelection: nil
+ 				menu: nil) hideScrollBarsIndefinitely.
+ 		stackPanel		
+ 			color: Color transparent;
+ 			hResizing: #spaceFill;
+ 			vResizing: #spaceFill;
+ 			cellInset: 5;
+ 			yourself].
+ 
+ !

Item was added:
+ ----- Method: SimulatorMorph>>stepButton (in category 'submorphs - buttons') -----
+ stepButton
+ 	self flag: 'tty'.
+ 	^stepButton ifNil: 
+ 		[stepButton := self basicButton 
+ 						label: 'Step' translated; 
+ 						actionSelector: #step;						
+ 						setBalloonText: 
+ 							'Step Into.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>toggleTranscriptButton (in category 'submorphs - buttons') -----
+ toggleTranscriptButton
+ 	"tty I dont like this. I have diabled the button"
+ 	self flag: 'tty'.
+ 	^toggleTranscriptButton ifNil: 
+ 		[toggleTranscriptButton := self basicButton 
+ 						label: 'Toggle Transcript' translated; 
+ 						actionSelector: #toggleTranscript;						
+ 						setBalloonText: 
+ 							'Use External Transcript Instead of Internal.' translated]!

Item was added:
+ ----- Method: SimulatorMorph>>transcriptPanel (in category 'submorphs - simulator panel') -----
+ transcriptPanel
+ 	self flag: 'tty'. "does this hybrid of PreferenceBrowser layout and Simulato openAsMorph stuff make sense?"
+ 	^transcriptPanel ifNil: 
+ 		[transcriptPanel := (PluggableTextMorph
+ 				on:  self model vm transcript
+ 				text: nil
+ 				accept: nil
+ 				readSelection: nil
+ 				menu: #codePaneMenu:shifted:).
+ 		transcriptPanel	
+ 			name: 'transcriptPanel';	
+ 			color: Color transparent;
+ 			hResizing: #spaceFill;
+ 			vResizing: #spaceFill;
+ 			cellInset: 5;
+ 			yourself].
+ !

Item was added:
+ TestCase subclass: #SimulatorMorphicEventTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: 'EventSensorConstants'
+ 	category: 'VMMaker-InterpreterSimulation-Morphic'!

Item was added:
+ ----- Method: SimulatorMorphicEventTests>>testKeyEventDegeneration (in category 'test event') -----
+ testKeyEventDegeneration
+ 	|aMorphicEvent evtBuf type|
+ 	aMorphicEvent := HandMorph new generateKeyboardEvent: {2 . 0. 0. 0. 0. 0. 0. 0}.
+ 	evtBuf := SimulatorEventTransformer default degenerateEvent: aMorphicEvent. 
+ 	type := evtBuf at:1.
+ 	self assert:(type = EventTypeKeyboard).
+ !

Item was added:
+ ----- Method: SimulatorMorphicEventTests>>testMouseEventDegeneration (in category 'test event') -----
+ testMouseEventDegeneration
+ 	|aMorphicEvent evtBuf type|
+ 	"see class comment in EventSensor browse"
+ 	aMorphicEvent := HandMorph new generateMouseEvent: {1 . 0. 0. 0. 0. 0. 0. 0}.
+ 	evtBuf := SimulatorEventTransformer default degenerateEvent: aMorphicEvent. 
+ 	type := evtBuf at:1.
+ 	self assert:(type = EventTypeMouse).
+ !

Item was added:
+ ----- Method: SimulatorMorphicEventTests>>testNullEventDegeneration (in category 'test event') -----
+ testNullEventDegeneration
+ 	|aMorphicEvent evtBuf type|
+ 	"Test a bad morphic event returns a null event"	"see class comment in EventSensor browse"
+ 	aMorphicEvent := UserInputEvent new.
+ 	evtBuf := SimulatorEventTransformer default degenerateEvent: aMorphicEvent. 
+ 	type := evtBuf at:1.
+ 	self assert:(type = EventTypeNone).
+ 
+ !

Item was added:
+ ----- Method: SimulatorMorphicEventTests>>testSimulatorDisplayViewAccess (in category 'test tight coupling') -----
+ testSimulatorDisplayViewAccess
+ 	"There is tight coupling between the morph,model and vm simulator on the simulators displayView variable
+ 	 this test makes sure it is accesible and is an ImageMorph."
+ 	
+ self assert: ((SystemNavigation allImplementorsOf: #displayView localTo: StackInterpreterSimulator) size = 1).
+ self assert: ((SystemNavigation allImplementorsOf: #displayView: localTo: StackInterpreterSimulator)size = 1).
+ 
+ !

Item was added:
+ ----- Method: SimulatorMorphicEventTests>>testStackInterpreterSimulatorDisplayViewAccess (in category 'test tight coupling') -----
+ testStackInterpreterSimulatorDisplayViewAccess
+ 	"There is tight coupling between the morph,model and vm simulator on the simulators displayView variable
+ 	 this test makes sure it is accesible and is an ImageMorph."
+ 	
+ self assert: ((SystemNavigation allImplementorsOf: #displayView localTo: StackInterpreterSimulator) size = 1).
+ self assert: ((SystemNavigation allImplementorsOf: #displayView: localTo: StackInterpreterSimulator)size = 1).
+ 
+ !

Item was added:
+ Model subclass: #SimulatorMorphicModel
+ 	instanceVariableNames: 'vm title stepping morph'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'EventSensorConstants'
+ 	category: 'VMMaker-InterpreterSimulation-Morphic'!
+ 
+ !SimulatorMorphicModel commentStamp: 'eem 7/14/2015 17:07' prior: 0!
+ A SimulatorMorphicModel handles Morphic callbacks and UI  for (some parts of ) the simulator.
+ 
+ I   handle event forwarding management..
+ 
+ Currently, I am a listener to HandMorphs>>addPrimitiveEventListener. 
+ I am added as a listener by SimulatorMorph>>displayView (which probably  needs to change. tty)!

Item was added:
+ ----- Method: SimulatorMorphicModel class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"I want to keep it launchable by script only for now.
+ 	Eliot has a bunch of options that aren't really feasible for a Morphic first approach.
+ 	"
+ 	"self
+ 		registerWindowColor;
+ 		registerInOpenMenu;
+ 		registerInFlaps"!

Item was added:
+ ----- Method: SimulatorMorphicModel class>>on:title:transcript: (in category 'instance creation') -----
+ on: aStackInterpreterSimulator title: aString transcript: aTranscriptStream
+ 	| simmodel |
+ 	simmodel := self new.
+ 	simmodel 
+ 		vm: aStackInterpreterSimulator;
+ 		title: aString;
+ 		transcript: aTranscriptStream.
+ 	^simmodel.	!

Item was added:
+ ----- Method: SimulatorMorphicModel class>>registerInFlaps (in category 'class initialization') -----
+ registerInFlaps
+ "	Flaps 
+ 		registerQuad: 
+ 			{ #StackInterpreterSimulator. 
+ 			#prototypicalToolWindow.
+ 			'StackInterpreter Simulator' translated.
+ 			'A Morphic Wrapper for VM Simulations' translated }
+ 	 	forFlapNamed: 'Tools' translated.
+ 	Flaps replaceToolsFlap"!

Item was added:
+ ----- Method: SimulatorMorphicModel class>>registerInOpenMenu (in category 'class initialization') -----
+ registerInOpenMenu
+ 	(TheWorldMenu respondsTo: #registerOpenCommand:) ifTrue: [
+ 		TheWorldMenu unregisterOpenCommand: 'StackInterpreter Simulator'.
+ 		TheWorldMenu registerOpenCommand: {'StackInterpreter Simulator'. {self. #open}}].
+ 		!

Item was added:
+ ----- Method: SimulatorMorphicModel class>>registerWindowColor (in category 'class initialization') -----
+ registerWindowColor
+ 	(Preferences windowColorFor: self name) = Color white
+ 		ifTrue: [ Preferences setWindowColorFor: self name to: (Color colorFrom: self windowColorSpecification brightColor) ].!

Item was added:
+ ----- Method: SimulatorMorphicModel class>>unload (in category 'class initialization') -----
+ unload
+ 	self 
+ 		unregisterFromOpenMenu;
+ 		unregisterFromFlaps.!

Item was added:
+ ----- Method: SimulatorMorphicModel class>>unregisterFromFlaps (in category 'class initialization') -----
+ unregisterFromFlaps
+ 	"Flaps 
+ 		unregisterQuadsWithReceiver: self;
+ 		replaceToolsFlap"!

Item was added:
+ ----- Method: SimulatorMorphicModel class>>unregisterFromOpenMenu (in category 'class initialization') -----
+ unregisterFromOpenMenu
+ 	 (TheWorldMenu respondsTo: #registerOpenCommand:)
+ 		ifTrue: [TheWorldMenu unregisterOpenCommand: 'StackInterpreter Simulator'].
+ !

Item was added:
+ ----- Method: SimulatorMorphicModel class>>windowColorSpecification (in category 'window color') -----
+ windowColorSpecification
+ 	"Answer a WindowColorSpec object that declares my preference"
+ 
+ 	^ WindowColorSpec classSymbol: self name wording: 'StackInterpreter Simulator' brightColor: #(0.645 1.0 1.0)	pastelColor: #(0.886 1.0 1.0) helpMessage: 'A tool for simulating a Stack Interpreter Virtual Machine.'!

Item was added:
+ ----- Method: SimulatorMorphicModel>>bounds (in category 'accessing') -----
+ bounds
+ 	^morph bounds.!

Item was added:
+ ----- Method: SimulatorMorphicModel>>byteCountText (in category 'user interface') -----
+ byteCountText
+ 	^vm byteCountText!

Item was added:
+ ----- Method: SimulatorMorphicModel>>currentContextStack (in category 'user interface - squeakJS') -----
+ currentContextStack
+ 	self flag: 'tty'.
+ 	^ 'Current Context Stack' printString asText!

Item was added:
+ ----- Method: SimulatorMorphicModel>>displayForm (in category 'accessing') -----
+ displayForm
+ 	^ vm displayForm!

Item was added:
+ ----- Method: SimulatorMorphicModel>>displayView (in category 'accessing') -----
+ displayView
+ 	^ vm displayView!

Item was added:
+ ----- Method: SimulatorMorphicModel>>displayView: (in category 'accessing') -----
+ displayView: anImageMorph
+ 	vm displayView: anImageMorph!

Item was added:
+ ----- Method: SimulatorMorphicModel>>forceInterruptCheck (in category 'buttons callbacks') -----
+ forceInterruptCheck
+ 	vm forceInterruptCheck
+ "^UserDialogBoxMorph inform: 'Toggle Transcript' title: 'TODO:'"!

Item was added:
+ ----- Method: SimulatorMorphicModel>>fullDisplayUpdate (in category 'buttons callbacks') -----
+ fullDisplayUpdate
+ 	vm fullDisplayUpdate
+ "^UserDialogBoxMorph inform: 'Toggle Transcript' title: 'TODO:'"!

Item was added:
+ ----- Method: SimulatorMorphicModel>>hack (in category 'buttons callbacks') -----
+ hack
+ 	UserDialogBoxMorph inform: (morph bounds printString) title: 'Hack:'!

Item was added:
+ ----- Method: SimulatorMorphicModel>>handleListenEvent: (in category 'event-forwarding') -----
+ handleListenEvent: aMorphicEvent
+ "The SimulatorImageMorph  regsitered me (a SimulatorMorphicModel ) with HandMorph>>addEventListener
+ HandMorph then broadcasts events to all registered listeners at this method. See HandMorph>>sendListenPrimitiveEvent
+ "
+ 	| evtBuf xtranslated ytranslated |
+ 	morph ifNotNil:
+ 		[evtBuf := SimulatorEventTransformer default degenerateEvent: aMorphicEvent. 
+ 		 ((evtBuf at: 1) = EventTypeMouse and: [morph bounds containsPoint: aMorphicEvent position]) ifTrue:
+ 			[xtranslated :=  (evtBuf at:3) - (morph bounds left) - 2 .  "<--heh"  
+ 			ytranslated :=  (evtBuf at:4) - (morph bounds top). 
+ 			evtBuf at: 3 put: xtranslated.
+ 			evtBuf at: 4 put: ytranslated.
+ 			vm queueForwardedEvent: evtBuf]]!

Item was added:
+ ----- Method: SimulatorMorphicModel>>help (in category 'buttons callbacks') -----
+ help
+ 	"Open up a workspace with explanatory info in it about the StackInterpreterSimulator"
+ 	Workspace new
+ 		contents: self helpText;
+ 		openLabel: self windowTitle, ' Help'.!

Item was added:
+ ----- Method: SimulatorMorphicModel>>helpText (in category 'buttons callbacks') -----
+ helpText
+ 	^(String streamContents: [:str |
+ 		str nextPutAll:
+ 'Stack Intepreter Simulator Help Contents Go Here.']) translated!

Item was added:
+ ----- Method: SimulatorMorphicModel>>initialExtent (in category 'user interface') -----
+ initialExtent
+ 	^ 1286 at 938!

Item was added:
+ ----- Method: SimulatorMorphicModel>>initialize (in category 'initialize-release') -----
+ initialize
+ 	
+ 	title := 'StackInterpreter Simulator (Beta))'.!

Item was added:
+ ----- Method: SimulatorMorphicModel>>ioExit (in category 'buttons callbacks') -----
+ ioExit
+ 	vm ioExit
+ 	displayView activeHand removeEventListener: self model.	"This is a bug as the user in vm ioExit may have cancelled the confirm t.m."
+ "^UserDialogBoxMorph inform: 'Toggle Transcript' title: 'TODO:'"!

Item was added:
+ ----- Method: SimulatorMorphicModel>>loadImage (in category 'buttons callbacks') -----
+ loadImage
+ 	^UserDialogBoxMorph inform: 'load image' title: 'TODO:'!

Item was added:
+ ----- Method: SimulatorMorphicModel>>morph (in category 'accessing') -----
+ morph
+ 	"I need the bounds of my morph for filtering mouse events.
+        If there is a canned way of doing this besides this tight binding to my SimulatorMorph,
+ 	then please refactor me.
+ 
+       see my protocol event-forwarding for the gory details"
+ 	self flag:'tty'.
+ 	^morph.!

Item was added:
+ ----- Method: SimulatorMorphicModel>>morph: (in category 'accessing') -----
+ morph: aMorph
+ 	"I need the bounds of my morph for filtering mouse events.
+        If there is a canned way of doing this besides this tight binding to my SimulatorMorph,
+ 	then please refactor me.
+ 
+       see my protocol event-forwarding for the gory details"
+ 	self flag:'tty'.
+ 	morph := aMorph.!

Item was added:
+ ----- Method: SimulatorMorphicModel>>onItemClicked: (in category 'user interface - squeakJS') -----
+ onItemClicked: anItem
+ 	"I am an item in the current context display on the SqueakJS tree view".!

Item was added:
+ ----- Method: SimulatorMorphicModel>>options (in category 'buttons callbacks') -----
+ options
+ ^UserDialogBoxMorph inform: 'Options Popup--need checkboxes?' title: 'TODO:'!

Item was added:
+ ----- Method: SimulatorMorphicModel>>over (in category 'buttons callbacks') -----
+ over
+ 	stepping:=true.
+ ^UserDialogBoxMorph inform: 'Step Over' title: 'TODO:'!

Item was added:
+ ----- Method: SimulatorMorphicModel>>processesAndContextStack (in category 'user interface - squeakJS') -----
+ processesAndContextStack
+ 	"just a stub. see top right panel at http://lively-web.org/users/bert/squeak.html  for what I intend to present"
+ 	self flag: 'tty'.
+ 	^ 'Processes and ContextStack' printString asText
+ !

Item was added:
+ ----- Method: SimulatorMorphicModel>>reset (in category 'buttons callbacks') -----
+ reset
+ 	^UserDialogBoxMorph inform: 'Reset' title: 'TODO:'!

Item was added:
+ ----- Method: SimulatorMorphicModel>>return (in category 'buttons callbacks') -----
+ return
+ ^UserDialogBoxMorph inform: 'Return' title: 'TODO:'!

Item was added:
+ ----- Method: SimulatorMorphicModel>>run (in category 'buttons callbacks') -----
+ run
+ 	stepping:=false.
+ 	vm run
+ "^UserDialogBoxMorph inform: 'Run' title: 'TODO:'"!

Item was added:
+ ----- Method: SimulatorMorphicModel>>send (in category 'buttons callbacks') -----
+ send
+ ^UserDialogBoxMorph inform: 'Send' title: 'TODO:'!

Item was added:
+ ----- Method: SimulatorMorphicModel>>specialObjectsAndActiveContext (in category 'user interface - squeakJS') -----
+ specialObjectsAndActiveContext
+ 	"just a stub. see top left panel at http://lively-web.org/users/bert/squeak.html  for what I intend to present"
+ 	self flag: 'tty'.
+ 	^ 'Special Objects and Active Context' printString asText
+ !

Item was added:
+ ----- Method: SimulatorMorphicModel>>step (in category 'buttons callbacks') -----
+ step
+ 	stepping:=true.
+ ^UserDialogBoxMorph inform: 'Step' title: 'TODO:'!

Item was added:
+ ----- Method: SimulatorMorphicModel>>stepping (in category 'accessing') -----
+ stepping
+ 	^stepping!

Item was added:
+ ----- Method: SimulatorMorphicModel>>stepping: (in category 'accessing') -----
+ stepping: aBoolean
+ 	stepping := aBoolean!

Item was added:
+ ----- Method: SimulatorMorphicModel>>title: (in category 'accessing') -----
+ title: aString
+ 	title := aString!

Item was added:
+ ----- Method: SimulatorMorphicModel>>toggleTranscript (in category 'buttons callbacks') -----
+ toggleTranscript
+ 	vm toggleTranscriptForSimulatorMorph: self transcript.
+ "^UserDialogBoxMorph inform: 'Toggle Transcript' title: 'TODO:'"!

Item was added:
+ ----- Method: SimulatorMorphicModel>>transcript (in category 'accessing') -----
+ transcript
+ 	^vm transcript!

Item was added:
+ ----- Method: SimulatorMorphicModel>>transcript: (in category 'accessing') -----
+ transcript: aTranscriptStream
+ 	vm transcript: aTranscriptStream.!

Item was added:
+ ----- Method: SimulatorMorphicModel>>utilitiesMenu: (in category 'user interface') -----
+ utilitiesMenu: aMenuMorph 
+ 	^vm utilitiesMenu: aMenuMorph!

Item was added:
+ ----- Method: SimulatorMorphicModel>>vm (in category 'accessing') -----
+ vm
+ 	^vm!

Item was added:
+ ----- Method: SimulatorMorphicModel>>vm: (in category 'accessing') -----
+ vm: aVMSimulator
+ 	vm := aVMSimulator!

Item was added:
+ ----- Method: SimulatorMorphicModel>>windowTitle (in category 'user interface') -----
+ windowTitle
+ 	^ title translated!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>newInputEventAccessorOfSize: (in category 'simulation') -----
  newInputEventAccessorOfSize: numElements
  	<doNotGenerate>
  	self flag: #endianness.
+ 	^(CPluggableAccessor on: (WordArray new: 16))
+ 		atBlock: [:obj :idx| | v |
+ 				v := (obj at: idx - 1 * 2 + 1) + ((obj at: idx - 1 * 2 + 2) << 32).
+ 				v >> 63 > 0 ifTrue:
+ 					[v := v - (1 << 64)].
+ 				v]
- 	^(CPluggableAccessor on: (IntegerArray new: 16))
- 		atBlock: [:obj :idx| (obj at: idx - 1 * 2) + ((obj at: idx - 1 * 2 + 1) << 32)]
  		atPutBlock: [:obj :idx :val|
+ 					obj at: idx - 1 * 2 + 1 put: (val bitAnd: 16rFFFFFFFF).
+ 					obj at: idx - 1 * 2 + 2 put: (val >> 32 bitAnd: 16rFFFFFFFF).
+ 					val];
+ 		objectSize: 8!
- 					obj at: idx - 1 * 2 put: (val bitAnd: 16rFFFFFFFF).
- 					obj at: idx - 1 * 2 + 1 put: val >> 32.
- 					val]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>handleListenEvent: (in category 'I/O primitives support') -----
+ handleListenEvent: aMorphicEvent
+ 	"openAsMorph regsitered me for listen events via HandMorph>>addEventListener.
+ 	Transform the listen event and add it to my event queue."
+ 	| evtBuf xtranslated ytranslated |
+ 	evtBuf := SimulatorEventTransformer default degenerateEvent: aMorphicEvent.
+ 	(evtBuf first = SimulatorEventTransformer eventTypeMouse
+ 	 and: [displayView bounds containsPoint: aMorphicEvent position]) ifTrue:
+ 		[xtranslated := (evtBuf at:3) - displayView bounds left - 2. "<--heh"
+ 		 ytranslated := (evtBuf at:4) - displayView bounds top.
+ 		 evtBuf at: 3 put: xtranslated.
+ 		 evtBuf at: 4 put: ytranslated].
+ 	self queueForwardedEvent: evtBuf!

Item was changed:
  ----- Method: StackInterpreterSimulator>>ioGetNextEvent: (in category 'I/O primitives') -----
  ioGetNextEvent: evtBuf
  	| evt |
+ 	"SimulatorMorphicModel browse"
- 	"StackInterpreterSimulatorMorphicModel browse"
  	eventQueue ifNil:
  		[^self primitiveFail].
  	eventQueue isEmpty ifFalse:
  		[evt :=  eventQueue next.
+ 		 1 to: evtBuf size do:
- 		 1 to: evt size do:
  			[:i| (evt at: i) ifNotNil: [:val| evtBuf at: (i - 1) put: val]]]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>openAsMorph (in category 'UI') -----
  openAsMorph
  	"Open a morphic view on this simulation."
  	| localImageName borderWidth window |
  	localImageName := imageName
  							ifNotNil: [FileDirectory default localNameFor: imageName]
  							ifNil: [' synthetic image'].
  	window := (SystemWindow labelled: 'Simulation of ', localImageName) model: self.
  
  	window addMorph: (displayView := ImageMorph new image: displayForm)
+ 			frame: (0 at 0 corner: 1 at 0.8).
+ 	displayView activeHand addEventListener: self.
- 		frame: (0 at 0 corner: 1 at 0.8).
  
  	transcript := TranscriptStream on: (String new: 10000).
  	window addMorph: (PluggableTextMorph
  							on: transcript text: nil accept: nil
  							readSelection: nil menu: #codePaneMenu:shifted:)
  			frame: (0 at 0.8 corner: 0.7 at 1).
  	window addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil
  						readSelection: nil menu: #utilitiesMenu:) hideScrollBarsIndefinitely
  			frame: (0.7 at 0.8 corner: 1 at 1).
  
  	borderWidth := [SystemWindow borderWidth] "Squeak 4.1"
  						on: MessageNotUnderstood
  						do: [:ex| 0]. "3.8"
  	borderWidth := borderWidth + window borderWidth.
  	window openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * borderWidth)
  								+ (0 at window labelHeight)
  								* (1@(1/0.8))) rounded.
  	^window!

Item was changed:
  ----- Method: StackInterpreterSimulator>>openAsMorphNoTranscript (in category 'UI') -----
  openAsMorphNoTranscript
  	"Open a morphic view on this simulation."
  	| localImageName borderWidth window |
  	localImageName := FileDirectory default localNameFor: imageName.
  	window := (SystemWindow labelled: 'Simulation of ' , localImageName) model: self.
  
  	window addMorph: (displayView := ImageMorph new image: displayForm)
+ 			frame: (0 at 0 corner: 1 at 0.95).
+ 	displayView activeHand addEventListener: self.
- 		frame: (0 at 0 corner: 1 at 0.95).
  
  	window addMorph: (PluggableTextMorph on: self
  						text: #byteCountText accept: nil
  						readSelection: nil menu: #utilitiesMenu:) hideScrollBarsIndefinitely
  		frame: (0 at 0.95 corner: 1 at 1).
  
  	borderWidth := [SystemWindow borderWidth] "Squeak 4.1"
  						on: MessageNotUnderstood
  						do: [:ex| 0]. "3.8"
  	borderWidth := borderWidth + window borderWidth.
  	window openInWorldExtent: (self desiredDisplayExtent
  								+ (2 * borderWidth)
  								+ (0 at window labelHeight)
  								* (1@(1/0.95))) rounded!

Item was added:
+ ----- Method: StackInterpreterSimulator>>openAsSimulatorMorph (in category 'UI') -----
+ openAsSimulatorMorph
+ 	"Open a morphic view on this simulation. ala Bert Freudenberg's
+ 	SqueakJS http://lively-web.org/users/bert/squeak.html	"
+ 	| localImageName borderWidth window |
+ 	localImageName := imageName
+ 							ifNil: [' synthetic image']
+ 							ifNotNil: [FileDirectory default localNameFor: imageName].
+ 
+ 	transcript := TranscriptStream on: (String new: 10000).
+ 
+ 	window := SimulatorMorph	
+ 					withVMSimulator: self 
+ 					title: 'Simulation of ' , localImageName, ' (beta)'
+ 					transcript: transcript.				
+ 
+ 	borderWidth := [SimulatorMorph borderWidth] "Squeak 4.1"
+ 						on: MessageNotUnderstood
+ 						do: [:ex | 0].
+ 	"3.8"
+ 	borderWidth := borderWidth + window borderWidth.
+ 	window openInWorldExtent: (self desiredDisplayExtent + (2 * borderWidth) + (0 @ window labelHeight) * (1 @ (1 / 0.8))) rounded.
+ 	^window!

Item was removed:
- ----- Method: StackInterpreterSimulator>>openAsStackInterpreterSimulatorMorph (in category 'UI') -----
- openAsStackInterpreterSimulatorMorph
- 	"Open a morphic view on this simulation. ala Bert Freudenberg's
- 	SqueakJS http://lively-web.org/users/bert/squeak.html	"
- 	| localImageName borderWidth window |
- 	localImageName := imageName
- 				ifNil: [' synthetic image']
- 				ifNotNil: [FileDirectory default localNameFor: imageName].
- 
- 	transcript := TranscriptStream
- 				on: (String new: 10000).
- 
- 	window := StackInterpreterSimulatorMorph	
- 					withVMSimulator: self 
- 					title: 'Simulation of ' , localImageName, ' (beta)'
- 					transcript: transcript.				
- 
- 	borderWidth := [StackInterpreterSimulatorMorph borderWidth
- 			"Squeak 4.1"]
- 				on: MessageNotUnderstood
- 				do: [:ex | 0].
- 	"3.8"
- 	borderWidth := borderWidth + window borderWidth.
- 	window openInWorldExtent: (self desiredDisplayExtent + (2 * borderWidth) + (0 @ window labelHeight) * (1 @ (1 / 0.8))) rounded.
- 	^ window!

Item was changed:
+ ----- Method: StackInterpreterSimulator>>queueForwardedEvent: (in category 'I/O primitives support') -----
+ queueForwardedEvent: event
+ 	eventQueue ifNil:
+ 		[eventQueue := SharedQueue new].
+ 	eventQueue nextPut: event!
- ----- Method: StackInterpreterSimulator>>queueForwardedEvent: (in category 'event forwarding') -----
- queueForwardedEvent:evt
- 	eventQueue isNil
- 		ifTrue:[eventQueue := SharedQueue new].
- 	eventQueue nextPut: evt.!

Item was removed:
- Object subclass: #StackInterpreterSimulatorEventTransformer
- 	instanceVariableNames: ''
- 	classVariableNames: 'Default'
- 	poolDictionaries: 'EventSensorConstants'
- 	category: 'VMMaker-InterpreterSimulation-Morphic'!
- 
- !StackInterpreterSimulatorEventTransformer commentStamp: 'tty 2/8/2014 12:54' prior: 0!
- A StackInterpreterSimulatorEventUnwrapper takes events as wrapped by HandMorph and converts them to a form a StackInterpreterSimulator can deal with.
- 
- See HandMorph >> handleEvent to see what the wrapping entails.
- See HandMorph >> ProcessEvents  or EventSensor >> fetchMoreEvents for examples of what an unwrapped event looks like when given to the system
- 
- 
- for pre-wrapping
- 
- Instance Variables
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorEventTransformer class>>default (in category 'initialize-release') -----
- default
- 	^Default ifNil:[Default := self new]!

Item was removed:
- ----- Method: StackInterpreterSimulatorEventTransformer>>degenerateEvent: (in category 'event transformation') -----
- degenerateEvent: aMorphicEvent
- 	"tty. Bert had mentioned a distinction between events and polling events and that Morphic could handle both.
- 	I don't know what he is talking about."	
- 	| evt type |
- 	self flag:'tty'.
- 
- 	evt := nil.	
- 	type := aMorphicEvent type.
- "	Transcript show:type;cr."
- 	(('mouse' charactersExactlyMatching: type asString) > 4)  "mous"
- 		ifTrue: [^self degenerateMouseEvent: aMorphicEvent].
- 	(('key' charactersExactlyMatching: type asString) > 2)  "key"
- 		ifTrue: [^self degenerateKeyboardEvent: aMorphicEvent].
- "	type = EventTypeDragDropFiles ifTrue: [evt := self generateDropFilesEvent: evtBuf].
- 	type = EventTypeWindow	ifTrue:[evt := self generateWindowEvent: evtBuf]."
- 
- 	^ #(0 0 0 0 0 0 0 0).!

Item was removed:
- ----- Method: StackInterpreterSimulatorEventTransformer>>degenerateKeyboardEvent: (in category 'event transformation') -----
- degenerateKeyboardEvent: aMorphicEvent
- 	| evt |
- 	"see HandMorph>>generateKeyboardEvent and EventSensor class comment"
- 	evt := {2 . 0 . 0 . 0 . 0. 0 . 0 . 0}.
- 	
- 	evt at:2 put: aMorphicEvent timeStamp.
- 	evt at:3 put: aMorphicEvent keyValue.    "<--this is wrong. See Sensor FirstEvt: for what needs to happen. hooo boy"
- 	evt at:4 put: aMorphicEvent position y.
- 	evt at:5 put: (aMorphicEvent buttons bitAnd: 7).  "thanks Ron T."
- 	evt at:6 put: (aMorphicEvent buttons >> 3).     "Thanks dtl"
- 	^evt
- 
- 
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorEventTransformer>>degenerateMouseButtonEvent: (in category 'event transformation') -----
- degenerateMouseButtonEvent: aMorphicEvent
- 	| evt |
- 	"see HandMorph>>generateMouseEvent"
- 	evt := {1 . 0 . 0 . 0 . 0. 0 . 0 . 0}.
- 	
- 	evt at:2 put: aMorphicEvent timeStamp.
- 	evt at:3 put: aMorphicEvent position x.
- 	evt at:4 put: aMorphicEvent position y.
- 	evt at:5 put: (aMorphicEvent buttons bitAnd: 7).  "thanks Ron T."
- 	evt at:6 put: (aMorphicEvent buttons >> 3).     "Thanks dtl"
- 	^evt
- 
- 
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorEventTransformer>>degenerateMouseEvent: (in category 'event transformation') -----
- degenerateMouseEvent: aMorphicEvent
- 	"see HandMorph>>generateMouseEvent"
- 
- 	(aMorphicEvent type) = #mouseMove
- 		ifTrue:[^self degenerateMouseMoveEvent: aMorphicEvent].	
- 
- 	((aMorphicEvent type) = #mouseUp) |  ((aMorphicEvent type) = #mouseDown)
- 		ifTrue:[^self degenerateMouseButtonEvent: aMorphicEvent].	
- "	(aMorphicEvent type) = #mouseDrag
- 		ifTrue:[evt := self degenerateMouseDragEvent: aMorphicEvent].	
- "
- 	^{0 . 0. 0. 0. 0. 0. 0. 0}.!

Item was removed:
- ----- Method: StackInterpreterSimulatorEventTransformer>>degenerateMouseMoveEvent: (in category 'event transformation') -----
- degenerateMouseMoveEvent: aMorphicEvent
- 	| evt |
- 	"see HandMorph>>generateMouseEvent"
- 	evt := {1 . 0 . 0 . 0 . 0. 0 . 0 . 0}.
- 	
- 	evt at:2 put: aMorphicEvent timeStamp.
- 	evt at:3 put: aMorphicEvent position x.
- 	evt at:4 put: aMorphicEvent position y.
- 	evt at:5 put: (aMorphicEvent buttons bitAnd: 7).  "thanks Ron T."
- 	evt at:6 put: (aMorphicEvent buttons >> 3).     "Thanks dtl"
- 	^evt
- 
- 
- !

Item was removed:
- ImageMorph subclass: #StackInterpreterSimulatorImageMorph
- 	instanceVariableNames: 'eventForwarder'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-InterpreterSimulation-Morphic'!
- 
- !StackInterpreterSimulatorImageMorph commentStamp: 'tty 2/5/2014 12:28' prior: 0!
- A StackInterpreterSimulatorImageMorph is an ImageMorph The StackInterpreterSimulator paints its world on me.
- 
- If tty can get event forwarding working along the HandMorph->StackInterpreterSimulatorMorphicModel->StackInterpreterSimulator path, then then I don't need to exist.
- 
- If event forwarding attempt above fails, then I may need to handle it.
- 
- 
- Instance Variables
- 
- !

Item was removed:
- SystemWindow subclass: #StackInterpreterSimulatorMorph
- 	instanceVariableNames: 'loadButton helpButton resetButton stepButton overButton sendButton returnButton runButton toggleTranscriptButton optionsButton transcriptPanel commandPanel contextPanel stackPanel callStackPanel displayForm displayView eventEncoder ioExitButton fullDisplayUpdateButton forceInterruptCheckButton hackButton'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-InterpreterSimulation-Morphic'!
- 
- !StackInterpreterSimulatorMorph commentStamp: 'tty 2/5/2014 12:11' prior: 0!
- A StackInterpreterSimulatorMorph is a copy of PreferenceBrowserMorph that has been mangled into something that will support the StackInterpreterSimulator.
- 
- I provide some UI features inspired by  Bert Freudenberg's Lively Squeak VM at http://lively-web.org/users/bert/squeak.html
- 
- See class protocol 'documentation' for examples of invoking me.
- 
- My model is StackInterpreterSimulatorMorphicModel. 
- My model has a reference to the StackInterpreterSimulator and itermediates all (?) interaction with it.
- 
- The StackInterpreterSimulator renders the simulated World on a StackInterpreterSimulatorImageMorph that I contain. 
- 
- There is some cruft (tight coupling via direct references along all three layers UI-Model-VM )in me that exists to support Eliot's original StackInterpreterSimulator>>openAsMorph functionality and use-case.
- Rumors that said cruft is an artifact of tty's rudimentary Morphic skills are entirely credible.
- 
- I hold out the barest glimmer of hope that Bert Freudenberg's SqueakJS functionality can be integrated into my functionality as well. 
- see http://lively-web.org/users/bert/squeak.html for the inspiration.
- 
- I am not amenable to Flaps or the WorldMenu as there is a lot of pre-run configuration that is done to the Simulator prior to its being run.
- Managing that ability with a GUI is counter-productive. If said functionality is desired in the future, then inspiration can be gleaned by cut-n-paste from PreferenceBrowser and PreferenceBrowserModel.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph class>>ttyOne (in category 'documentation') -----
- ttyOne
- "Script tty uses to run the stackIntepreter using this class"
- | vm |
- Transcript clear.
- vm := StackInterpreterSimulator newWithOptions: #(#STACKVM).
- vm openOn: '/home/tty/usr/src/smalltalk/buildCogDevelopmentImageCog.app/Contents/Resources/targets/Squeak4.5.image'.
- "vm setBreakSelector: #&."
- vm 
- 	openAsStackInterpreterSimulatorMorph "; 
- 	toggleTranscript;
- 	halt;
- 	run"
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph class>>withVMSimulator:title:transcript: (in category 'instance creation') -----
- withVMSimulator: aStackInterpreterSimulatorMorphicModel title: aString transcript: aTranscript
- 	^self new initializeWithVMSimulator: aStackInterpreterSimulatorMorphicModel title: aString aTranscript: aTranscript;
- 		yourself.
- 		
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>basicButton (in category 'submorphs - buttons') -----
- basicButton
- 	| button |
- 	button := SimpleButtonMorph new.
- 	button
- 		borderWidth: 2;
- 		borderColor: #raised;
- 		on: #mouseEnter send: #value to: [button borderColor: self paneColor];
- 		on: #mouseLeave send: #value to: [button borderColor: #raised];
- 		vResizing: #spaceFill;
- 		useRoundedCorners;
- 		clipSubmorphs: true;
- 		color: self paneColor muchLighter;
- 		target: self model.
- 	^button!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>buttonRowLayoutFrame (in category 'submorphs - buttons') -----
- buttonRowLayoutFrame 
- 	^LayoutFrame fractions: (0 at 0 corner: 1 at 0) offsets: (0 at 0 corner: 0@ (TextStyle defaultFont height * 2.5))
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>callStackPanel (in category 'submorphs - squeakJS') -----
- callStackPanel
- 	"If any Morphic gurus exist, please have at it."
- 	^callStackPanel ifNil: 
- 		[callStackPanel :=  (PluggableTextMorph
- 				on: self model
- 				text: #processesAndContextStack
- 				accept: nil
- 				readSelection: nil
- 				menu: nil) hideScrollBarsIndefinitely.
- 		callStackPanel		
- 			color: Color transparent;
- 			hResizing: #spaceFill;
- 			vResizing: #spaceFill;
- 			cellInset: 5;
- 			yourself].
- 
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>commandPanel (in category 'submorphs - simulator panel') -----
- commandPanel
- 	self flag: 'tty'. "does this hybrid of PreferenceBrowser layout and Simulato openAsMorph stuff make sense?"
- 	^commandPanel ifNil: 
- 		[commandPanel :=  (PluggableTextMorph
- 				on: self model vm
- 				text: #byteCountText
- 				accept: nil
- 				readSelection: nil
- 				menu: #utilitiesMenu:) hideScrollBarsIndefinitely.
- 		commandPanel		
- 			color: Color transparent;
- 			hResizing: #spaceFill;
- 			vResizing: #spaceFill;
- 			cellInset: 5;
- 			yourself].
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>contextPanel (in category 'submorphs - squeakJS') -----
- contextPanel
- 	"This should show the currentContext and Special Objects array. as seen at SqueakJS
- 	  Doing that requires real talent. talent tty is lacking at the moment
- 							on: [ Array with:  (MorphWithSubmorphsWrapper with: self)  ]	
- 	Array with: (ObjectExplorerWrapper with: rootObject name: 'root' model: self parent: nil)
- 	"
- 	^contextPanel ifNil: 
- 		[contextPanel := (SimpleHierarchicalListMorph
- 							on: [ Array with: (ObjectExplorerWrapper with: (self model vm) name: 'root' model: (self model vm) parent: nil) ]
- 							list: #value
- 							selected: nil
- 							changeSelected: nil
- 							menu: nil
- 							keystroke: nil) showScrollBarsOnlyWhenNeeded: true.
- 		contextPanel		
- 			color: Color transparent;
- 			hResizing: #spaceFill;
- 			vResizing: #spaceFill;
- 			cellInset: 5;
- 			yourself]
- 
- 
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>displayView (in category 'submorphs - simulator display view') -----
- displayView
- 	"The VM SImulator draws directly on an imageMorph named displayView
- 	  displayView is housed on a Form named displayForm
- 	   displayForm is initialized in StackInterpreterSimulator >> initialize.
- 	  see StackInterpreterSimulator >>openAsMorph for original constructs.
- 	"
- 	^displayView ifNil: 
- 		[displayView :=  (StackInterpreterSimulatorImageMorph new image: (model vm displayForm)). 
- 		(self model) displayView: displayView.					
- 		(self model) morph: displayView. "<-- N.B.. morph bounds are used to filter events in the model. tty"
- 	      displayView activeHand addEventListener: self model.		
- 					
-  		displayView		
- 			color: Color transparent;
- 			hResizing: #spaceFill;
- 			vResizing: #spaceFill;
- 			cellInset: 5;
- 			yourself
- 			].
- 
- 
- 	
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>displayViewLayoutFrame (in category 'submorphs - simulator display view') -----
- displayViewLayoutFrame 
- 	| squeakJSFrame buttonFrame simulatorFrame|
- 	"if any Morphic guru's understand layouts and offsets, please fix this. tty"
- 	buttonFrame := self buttonRowLayoutFrame.
- 	squeakJSFrame := self squeakJSRowLayoutFrame.
- 	simulatorFrame := self simulatorLayoutFrame.
- 	^LayoutFrame fractions: (0 at 0 corner: 1 at 1) 
- 				    offsets: (0@(buttonFrame bottomOffset) corner: simulatorFrame leftOffset at squeakJSFrame topOffset)!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>extent: (in category 'geometry') -----
- extent: aPoint
- 	super extent: aPoint.
- 	self fullBounds.
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>forceInterruptCheckButton (in category 'submorphs - buttons') -----
- forceInterruptCheckButton
- 	self flag: 'tty'.
- 	^forceInterruptCheckButton ifNil: 
- 		[forceInterruptCheckButton := self basicButton 
- 						label: 'vm forceInterruptCheck' translated; 
- 						actionSelector: #forceInterruptCheck;						
- 						setBalloonText: 
- 							'Invoke forceInterruptCheck on Simulator.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>fullDisplayUpdateButton (in category 'submorphs - buttons') -----
- fullDisplayUpdateButton
- 	self flag: 'tty'.
- 	^fullDisplayUpdateButton ifNil: 
- 		[fullDisplayUpdateButton := self basicButton 
- 						label: 'vm fullDisplayUpdate' translated; 
- 						actionSelector: #fullDisplayUpdate;						
- 						setBalloonText: 
- 							'Invoke fullDisplayUpdate on Simulator.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>hackButton (in category 'submorphs - buttons') -----
- hackButton
- 	self flag: 'tty'.
- 	^hackButton ifNil: 
- 		[hackButton := self basicButton 
- 						label: 'Display ImageMorph Bounds' translated; 
- 						actionSelector: #hack;						
- 						setBalloonText: 
- 							'tty needs a hack button.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>helpButton (in category 'submorphs - buttons') -----
- helpButton
- 	^helpButton ifNil: 
- 		[helpButton := self basicButton 
- 						label: 'help' translated; 
- 						setBalloonText: 
- 							'Click here to get some hints on use of me ',
- 							'Panel' translated;
- 						actionSelector: #help]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>initializeWithVMSimulator:title:aTranscript: (in category 'initialization') -----
- initializeWithVMSimulator: aStackInterpreterSimulator title: aString aTranscript: aTranscript
- 	|model|
- 	self flag: 'tty'. "need to get the layout right at this point. resizers and scroll bars would be nice. Layout offsets need a gimlet eye as well"
- 	model := StackInterpreterSimulatorMorphicModel on: aStackInterpreterSimulator title: aString transcript: aTranscript. 
- 	self 
- 		model: model;
- 		clipSubmorphs: true;
- 		setLabel: self model windowTitle;
- 		name: aString;
- 		addMorph: self newButtonRow fullFrame: self buttonRowLayoutFrame;
- 		addMorph: self squeakJSRow fullFrame: self squeakJSRowLayoutFrame;
- 		addMorph: self simulatorPanel fullFrame: self simulatorLayoutFrame;
- 		addMorph: self displayView fullFrame: self displayViewLayoutFrame.	
- 	^self		!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>ioExitButton (in category 'submorphs - buttons') -----
- ioExitButton
- 	self flag: 'tty'.
- 	^ioExitButton ifNil: 
- 		[ioExitButton := self basicButton 
- 						label: 'vm ioExit' translated; 
- 						actionSelector: #ioExit;						
- 						setBalloonText: 
- 							'Invoke ioExit on Simulator.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>loadButton (in category 'submorphs - buttons') -----
- loadButton
- 	^loadButton ifNil: 
- 		[loadButton := self basicButton 
- 						label: 'Load Image' translated; 
- 						actionSelector: #loadImage;						
- 						setBalloonText: 
- 							'Select an image to load.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>newButtonRow (in category 'submorphs - buttons') -----
- newButtonRow
- 	^BorderedMorph new
- 		color: Color transparent;
- 		cellInset: 2;
- 		layoutInset: 2;
- 		layoutPolicy: TableLayout new;
- 		listDirection: #leftToRight;
- 		listCentering: #topLeft;
- 		cellPositioning: #topLeft;
- 		on: #mouseEnter send: #paneTransition: to: self;
- 		on: #mouseLeave send: #paneTransition: to: self;
- 		addMorphBack: self hackButton;
- 		addMorphBack: self newSeparator;
- 
- "		addMorphBack: self resetButton;
- 		addMorphBack: self newSeparator;
- 		addMorphBack: self forceInterruptCheckButton;
- 		addMorphBack: self newSeparator;
- 		addMorphBack: self fullDisplayUpdateButton;
- 		addMorphBack: self newSeparator;
- 		addMorphBack: self toggleTranscriptButton;"  
- 		addMorphBack: self runButton;				
- 		addMorphBack: self newSeparator; 
- 		addMorphBack: self ioExitButton;
- 		addMorphBack: self newTransparentFiller;		
- 		addMorphBack: self stepButton;
- 		addMorphBack: self newSeparator;		
- 		addMorphBack: self overButton;
- 		addMorphBack: self newSeparator;
- 		addMorphBack: self newSeparator;		
- 		addMorphBack: self sendButton;
- 		addMorphBack: self newSeparator;		
- 		addMorphBack: self returnButton;		
- 		addMorphBack: self newTransparentFiller;
- "		addMorphBack: self loadButton;
- 		addMorphBack: self newSeparator;				
- 		addMorphBack: self optionsButton;     too complex to implement now. See StackInterpreterSimulator class comment for examples"										
- 		addMorphBack: self newTransparentFiller;
- 		addMorphBack: self helpButton;
- 		yourself.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>newSeparator (in category 'submorphs - buttons') -----
- newSeparator
- 	^BorderedMorph new
- 		borderWidth: 2;
- 		borderColor: Color transparent;
- 		color: self paneColor;
- 		hResizing: #rigid;
- 		width: 5;
- 		vResizing: #spaceFill;
- 		yourself!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>newTransparentFiller (in category 'submorphs - buttons') -----
- newTransparentFiller
- 	^Morph new
- 		color: Color transparent;
- 		vResizing: #spaceFill;
- 		hResizing: #spaceFill;
- 		yourself.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>optionsButton (in category 'submorphs - buttons') -----
- optionsButton
- 	^optionsButton ifNil: 
- 		[optionsButton := self basicButton 
- 						label: 'VM Options' translated; 
- 						actionSelector: #options;						
- 						setBalloonText: 
- 							'VM Options.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>overButton (in category 'submorphs - buttons') -----
- overButton
- 	^overButton ifNil: 
- 		[overButton := self basicButton 
- 						label: 'Over' translated; 
- 						actionSelector: #over;						
- 						setBalloonText: 
- 							'Step Over.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>resetButton (in category 'submorphs - buttons') -----
- resetButton
- 	^resetButton ifNil: 
- 		[resetButton := self basicButton 
- 						label: 'Reset' translated; 
- 						actionSelector: #reset;						
- 						setBalloonText: 
- 							'Reset running simulation.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>returnButton (in category 'submorphs - buttons') -----
- returnButton
- 	self flag: 'tty'.
- 	^returnButton ifNil: 
- 		[returnButton := self basicButton 
- 						label: 'Return' translated; 
- 						actionSelector: #return;						
- 						setBalloonText: 
- 							'Return from what?.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>runButton (in category 'submorphs - buttons') -----
- runButton
- 	self flag: 'tty'.
- 	^runButton ifNil: 
- 		[runButton := self basicButton 
- 						label: 'vm run' translated; 
- 						actionSelector: #run;						
- 						setBalloonText: 
- 							'Run Simulation.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>sendButton (in category 'submorphs - buttons') -----
- sendButton
- 	self flag: 'tty'.
- 	^sendButton ifNil: 
- 		[sendButton := self basicButton 
- 						label: 'Send' translated; 
- 						actionSelector: #send;						
- 						setBalloonText: 
- 							'Send what exactly?.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>simulatorLayoutFrame (in category 'submorphs - simulator panel') -----
- simulatorLayoutFrame 
- 	| squeakJSFrame buttonFrame |
- 	"I don't understand offsets in the LayoutFrame. I just fiddled until it looked ok. If anybody knows what they are doing, please refactor."
- 	self flag: 'tty'.
- 	buttonFrame := self buttonRowLayoutFrame.
- 	squeakJSFrame := self squeakJSRowLayoutFrame.
- 	^LayoutFrame fractions: (0.7 at 0 corner: 1 at squeakJSFrame topOffset) 
- 				    offsets: (0@(buttonFrame bottomOffset) corner: 0.70 at squeakJSFrame topOffset)
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>simulatorPanel (in category 'submorphs - simulator panel') -----
- simulatorPanel
- 	"standard controls from StackInterpreterSimulator >> openAsMorph"
- 	^BorderedMorph new
- 		color: Color transparent;
- 		layoutInset: 10;
- 		cellInset: 10;
- 		layoutPolicy: TableLayout new;
- 		listDirection: #topToBottom;
- 		listCentering: #topLeft;
- 		cellPositioning: #topLeft;
- 		on: #mouseEnter send: #paneTransition: to: self;
- 		on: #mouseLeave send: #paneTransition: to: self;		
- 		addMorphBack: self transcriptPanel;
- 		addMorphBack: self commandPanel;
- 		yourself.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>squeakJSRow (in category 'submorphs - squeakJS') -----
- squeakJSRow
- 	"row fo SqueakJS context, stack and call-stack panels"
- 	^BorderedMorph new
- 		color: Color blue;
- 		cellInset: 2;
- 		layoutInset: 2;
- 		layoutPolicy: TableLayout new;
- 		listDirection: #leftToRight;
- 		listCentering: #topLeft;
- 		cellPositioning: #topLeft;
- 		on: #mouseEnter send: #paneTransition: to: self;
- 		on: #mouseLeave send: #paneTransition: to: self;
- 		addMorphBack: self callStackPanel;
- 		addMorphBack: self contextPanel;
- 		addMorphBack: self stackPanel;		
- 		yourself.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>squeakJSRowLayoutFrame (in category 'submorphs - squeakJS') -----
- squeakJSRowLayoutFrame 
- 	^LayoutFrame fractions: (0 at 0.8 corner: 1 at 1) offsets: (0 at 0.8 corner: 1@ (TextStyle defaultFont height * 2.5))
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>stackPanel (in category 'submorphs - squeakJS') -----
- stackPanel
- 	"If any Morphic gurus exist, please have at it."
- 	^stackPanel ifNil: 
- 		[stackPanel :=  (PluggableTextMorph
- 				on: self model
- 				text: #currentContextStack
- 				accept: nil
- 				readSelection: nil
- 				menu: nil) hideScrollBarsIndefinitely.
- 		stackPanel		
- 			color: Color transparent;
- 			hResizing: #spaceFill;
- 			vResizing: #spaceFill;
- 			cellInset: 5;
- 			yourself].
- 
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>stepButton (in category 'submorphs - buttons') -----
- stepButton
- 	self flag: 'tty'.
- 	^stepButton ifNil: 
- 		[stepButton := self basicButton 
- 						label: 'Step' translated; 
- 						actionSelector: #step;						
- 						setBalloonText: 
- 							'Step Into.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>toggleTranscriptButton (in category 'submorphs - buttons') -----
- toggleTranscriptButton
- 	"tty I dont like this. I have diabled the button"
- 	self flag: 'tty'.
- 	^toggleTranscriptButton ifNil: 
- 		[toggleTranscriptButton := self basicButton 
- 						label: 'Toggle Transcript' translated; 
- 						actionSelector: #toggleTranscript;						
- 						setBalloonText: 
- 							'Use External Transcript Instead of Internal.' translated]!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorph>>transcriptPanel (in category 'submorphs - simulator panel') -----
- transcriptPanel
- 	self flag: 'tty'. "does this hybrid of PreferenceBrowser layout and Simulato openAsMorph stuff make sense?"
- 	^transcriptPanel ifNil: 
- 		[transcriptPanel := (PluggableTextMorph
- 				on:  self model vm transcript
- 				text: nil
- 				accept: nil
- 				readSelection: nil
- 				menu: #codePaneMenu:shifted:).
- 		transcriptPanel	
- 			name: 'transcriptPanel';	
- 			color: Color transparent;
- 			hResizing: #spaceFill;
- 			vResizing: #spaceFill;
- 			cellInset: 5;
- 			yourself].
- !

Item was removed:
- TestCase subclass: #StackInterpreterSimulatorMorphicEventTests
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: 'EventSensorConstants'
- 	category: 'VMMaker-InterpreterSimulation-Morphic'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicEventTests>>testKeyEventDegeneration (in category 'test event') -----
- testKeyEventDegeneration
- 	|aMorphicEvent evtBuf type|
- 	aMorphicEvent := HandMorph new generateKeyboardEvent: {2 . 0. 0. 0. 0. 0. 0. 0}.
- 	evtBuf := (StackInterpreterSimulatorEventTransformer default) degenerateEvent: aMorphicEvent. 
- 	type := evtBuf at:1.
- 	self assert:(type = EventTypeKeyboard).
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicEventTests>>testMouseEventDegeneration (in category 'test event') -----
- testMouseEventDegeneration
- 	|aMorphicEvent evtBuf type|
- 	"see class comment in EventSensor browse"
- 	aMorphicEvent := HandMorph new generateMouseEvent: {1 . 0. 0. 0. 0. 0. 0. 0}.
- 	evtBuf := (StackInterpreterSimulatorEventTransformer default) degenerateEvent: aMorphicEvent. 
- 	type := evtBuf at:1.
- 	self assert:(type = EventTypeMouse).
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicEventTests>>testNullEventDegeneration (in category 'test event') -----
- testNullEventDegeneration
- 	|aMorphicEvent evtBuf type|
- 	"Test a bad morphic event returns a null event"	"see class comment in EventSensor browse"
- 	aMorphicEvent := UserInputEvent new.
- 	evtBuf := (StackInterpreterSimulatorEventTransformer default) degenerateEvent: aMorphicEvent. 
- 	type := evtBuf at:1.
- 	self assert:(type = EventTypeNone).
- 
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicEventTests>>testStackInterpreterSimulatorDisplayViewAccess (in category 'test tight coupling') -----
- testStackInterpreterSimulatorDisplayViewAccess
- 	"There is tight coupling between the morph,model and vm simulator on the simulators displayView variable
- 	 this test makes sure it is accesible and is an ImageMorph."
- 	
- self assert: ((SystemNavigation allImplementorsOf: #displayView localTo: StackInterpreterSimulator) size = 1).
- self assert: ((SystemNavigation allImplementorsOf: #displayView: localTo: StackInterpreterSimulator)size = 1).
- 
- !

Item was removed:
- Model subclass: #StackInterpreterSimulatorMorphicModel
- 	instanceVariableNames: 'vm title stepping morph'
- 	classVariableNames: ''
- 	poolDictionaries: 'EventSensorConstants'
- 	category: 'VMMaker-InterpreterSimulation-Morphic'!
- 
- !StackInterpreterSimulatorMorphicModel commentStamp: 'tty 2/6/2014 09:43' prior: 0!
- A StackInterpreterSimulatorMorphicModel handles Morphic callbacks and UI  for (some parts of ) the StackInterpreterSimulator.
- 
- I   handle event forwarding management..
- 
- Currently, I am a listener to HandMorphs>>addPrimitiveEventListener. 
- I am added as a listener by StackInterpreterSimulatorMorph>>displayView (which probably  needs to change. tty)
- 
- 
- instance vars:
- 
- stepping   when true the vm is running, but the user is stepping throught the stack--like a debugger. (not implemented: tty)
- 
- 
- sharedPools: EventSensorConstants!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel class>>initialize (in category 'class initialization') -----
- initialize
- 	"I want to keep it launchable by script only for now.
- 	Eliot has a bunch of options that aren't really feasible for a Morphic first approach.
- 	"
- 	"self
- 		registerWindowColor;
- 		registerInOpenMenu;
- 		registerInFlaps"!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel class>>on:title:transcript: (in category 'instance creation') -----
- on: aStackInterpreterSimulator title: aString transcript: aTranscriptStream
- 	| simmodel |
- 	simmodel := self new.
- 	simmodel 
- 		vm: aStackInterpreterSimulator;
- 		title: aString;
- 		transcript: aTranscriptStream.
- 	^simmodel.	!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel class>>registerInFlaps (in category 'class initialization') -----
- registerInFlaps
- "	Flaps 
- 		registerQuad: 
- 			{ #StackInterpreterSimulator. 
- 			#prototypicalToolWindow.
- 			'StackInterpreter Simulator' translated.
- 			'A Morphic Wrapper for VM Simulations' translated }
- 	 	forFlapNamed: 'Tools' translated.
- 	Flaps replaceToolsFlap"!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel class>>registerInOpenMenu (in category 'class initialization') -----
- registerInOpenMenu
- 	(TheWorldMenu respondsTo: #registerOpenCommand:) ifTrue: [
- 		TheWorldMenu unregisterOpenCommand: 'StackInterpreter Simulator'.
- 		TheWorldMenu registerOpenCommand: {'StackInterpreter Simulator'. {self. #open}}].
- 		!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel class>>registerWindowColor (in category 'class initialization') -----
- registerWindowColor
- 	(Preferences windowColorFor: self name) = Color white
- 		ifTrue: [ Preferences setWindowColorFor: self name to: (Color colorFrom: self windowColorSpecification brightColor) ].!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel class>>unload (in category 'class initialization') -----
- unload
- 	self 
- 		unregisterFromOpenMenu;
- 		unregisterFromFlaps.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel class>>unregisterFromFlaps (in category 'class initialization') -----
- unregisterFromFlaps
- 	"Flaps 
- 		unregisterQuadsWithReceiver: self;
- 		replaceToolsFlap"!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel class>>unregisterFromOpenMenu (in category 'class initialization') -----
- unregisterFromOpenMenu
- 	 (TheWorldMenu respondsTo: #registerOpenCommand:)
- 		ifTrue: [TheWorldMenu unregisterOpenCommand: 'StackInterpreter Simulator'].
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel class>>windowColorSpecification (in category 'window color') -----
- windowColorSpecification
- 	"Answer a WindowColorSpec object that declares my preference"
- 
- 	^ WindowColorSpec classSymbol: self name wording: 'StackInterpreter Simulator' brightColor: #(0.645 1.0 1.0)	pastelColor: #(0.886 1.0 1.0) helpMessage: 'A tool for simulating a Stack Interpreter Virtual Machine.'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>bounds (in category 'accessing') -----
- bounds
- 	^morph bounds.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>byteCountText (in category 'user interface') -----
- byteCountText
- 	^vm byteCountText!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>currentContextStack (in category 'user interface - squeakJS') -----
- currentContextStack
- 	self flag: 'tty'.
- 	^ 'Current Context Stack' printString asText!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>displayForm (in category 'accessing') -----
- displayForm
- 	^ vm displayForm!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>displayView (in category 'accessing') -----
- displayView
- 	^ vm displayView!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>displayView: (in category 'accessing') -----
- displayView: anImageMorph
- 	vm displayView: anImageMorph!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>forceInterruptCheck (in category 'buttons callbacks') -----
- forceInterruptCheck
- 	vm forceInterruptCheck
- "^UserDialogBoxMorph inform: 'Toggle Transcript' title: 'TODO:'"!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>fullDisplayUpdate (in category 'buttons callbacks') -----
- fullDisplayUpdate
- 	vm fullDisplayUpdate
- "^UserDialogBoxMorph inform: 'Toggle Transcript' title: 'TODO:'"!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>hack (in category 'buttons callbacks') -----
- hack
- 	UserDialogBoxMorph inform: (morph bounds printString) title: 'Hack:'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>handleListenEvent: (in category 'event-forwarding') -----
- handleListenEvent: aMorphicEvent
- "The StackInterpreterSimulatorImageMorph  regsitered me (a StackInterpreterSimulatorMorphicModel ) with HandMorph>>addEventListener
- HandMorph then broadcasts events to all registered listeners at this method. See HandMorph>>sendListenPrimitiveEvent
- "
- 	|evtBuf xtranslated ytranslated|
- 	morph
- 		ifNotNil:[
- 			evtBuf := (StackInterpreterSimulatorEventTransformer default) degenerateEvent: aMorphicEvent. 
- 			((evtBuf at: 1) = EventTypeMouse) & (morph bounds containsPoint: aMorphicEvent position)
- 				ifTrue:[
- 						xtranslated :=  (evtBuf at:3) - (morph bounds left) - 2 .  "<--heh"  
- 						ytranslated :=  (evtBuf at:4) - (morph bounds top). 
- 						evtBuf at: 3 put: xtranslated.
- 						evtBuf at: 4 put: ytranslated.
- 						vm queueForwardedEvent: evtBuf]]
- 
- 
- 
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>help (in category 'buttons callbacks') -----
- help
- 	"Open up a workspace with explanatory info in it about the StackInterpreterSimulator"
- 	Workspace new
- 		contents: self helpText;
- 		openLabel: self windowTitle, ' Help'.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>helpText (in category 'buttons callbacks') -----
- helpText
- 	^(String streamContents: [:str |
- 		str nextPutAll:
- 'Stack Intepreter Simulator Help Contents Go Here.']) translated!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>initialExtent (in category 'user interface') -----
- initialExtent
- 	^ 1286 at 938!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>initialize (in category 'initialize-release') -----
- initialize
- 	
- 	title := 'StackInterpreter Simulator (Beta))'.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>ioExit (in category 'buttons callbacks') -----
- ioExit
- 	vm ioExit
- 	displayView activeHand removeEventListener: self model.	"This is a bug as the user in vm ioExit may have cancelled the confirm t.m."
- "^UserDialogBoxMorph inform: 'Toggle Transcript' title: 'TODO:'"!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>loadImage (in category 'buttons callbacks') -----
- loadImage
- 	^UserDialogBoxMorph inform: 'load image' title: 'TODO:'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>morph (in category 'accessing') -----
- morph
- 	"I need the bounds of my morph for filtering mouse events.
-        If there is a canned way of doing this besides this tight binding to my StackInterpreterSimulatorMorph,
- 	then please refactor me.
- 
-       see my protocol event-forwarding for the gory details"
- 	self flag:'tty'.
- 	^morph.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>morph: (in category 'accessing') -----
- morph: aMorph
- 	"I need the bounds of my morph for filtering mouse events.
-        If there is a canned way of doing this besides this tight binding to my StackInterpreterSimulatorMorph,
- 	then please refactor me.
- 
-       see my protocol event-forwarding for the gory details"
- 	self flag:'tty'.
- 	morph := aMorph.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>onItemClicked: (in category 'user interface - squeakJS') -----
- onItemClicked: anItem
- 	"I am an item in the current context display on the SqueakJS tree view".!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>options (in category 'buttons callbacks') -----
- options
- ^UserDialogBoxMorph inform: 'Options Popup--need checkboxes?' title: 'TODO:'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>over (in category 'buttons callbacks') -----
- over
- 	stepping:=true.
- ^UserDialogBoxMorph inform: 'Step Over' title: 'TODO:'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>processesAndContextStack (in category 'user interface - squeakJS') -----
- processesAndContextStack
- 	"just a stub. see top right panel at http://lively-web.org/users/bert/squeak.html  for what I intend to present"
- 	self flag: 'tty'.
- 	^ 'Processes and ContextStack' printString asText
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>reset (in category 'buttons callbacks') -----
- reset
- 	^UserDialogBoxMorph inform: 'Reset' title: 'TODO:'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>return (in category 'buttons callbacks') -----
- return
- ^UserDialogBoxMorph inform: 'Return' title: 'TODO:'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>run (in category 'buttons callbacks') -----
- run
- 	stepping:=false.
- 	vm run
- "^UserDialogBoxMorph inform: 'Run' title: 'TODO:'"!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>send (in category 'buttons callbacks') -----
- send
- ^UserDialogBoxMorph inform: 'Send' title: 'TODO:'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>specialObjectsAndActiveContext (in category 'user interface - squeakJS') -----
- specialObjectsAndActiveContext
- 	"just a stub. see top left panel at http://lively-web.org/users/bert/squeak.html  for what I intend to present"
- 	self flag: 'tty'.
- 	^ 'Special Objects and Active Context' printString asText
- !

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>step (in category 'buttons callbacks') -----
- step
- 	stepping:=true.
- ^UserDialogBoxMorph inform: 'Step' title: 'TODO:'!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>stepping (in category 'accessing') -----
- stepping
- 	^stepping!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>stepping: (in category 'accessing') -----
- stepping: aBoolean
- 	stepping := aBoolean!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>title: (in category 'accessing') -----
- title: aString
- 	title := aString!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>toggleTranscript (in category 'buttons callbacks') -----
- toggleTranscript
- 	vm toggleTranscriptForSimulatorMorph: self transcript.
- "^UserDialogBoxMorph inform: 'Toggle Transcript' title: 'TODO:'"!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>transcript (in category 'accessing') -----
- transcript
- 	^vm transcript!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>transcript: (in category 'accessing') -----
- transcript: aTranscriptStream
- 	vm transcript: aTranscriptStream.!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>utilitiesMenu: (in category 'user interface') -----
- utilitiesMenu: aMenuMorph 
- 	^vm utilitiesMenu: aMenuMorph!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>vm (in category 'accessing') -----
- vm
- 	^vm!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>vm: (in category 'accessing') -----
- vm: aVMSimulator
- 	vm := aVMSimulator!

Item was removed:
- ----- Method: StackInterpreterSimulatorMorphicModel>>windowTitle (in category 'user interface') -----
- windowTitle
- 	^ title translated!



More information about the Vm-dev mailing list