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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 15 22:42:58 UTC 2015


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

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

Name: VMMaker.oscog-eem.1420
Author: eem
Time: 15 July 2015, 3:40:39.568 pm
UUID: 694d0e1e-2003-493c-82ab-1d60581cb544
Ancestors: VMMaker.oscog-eem.1419

Simulator:
Get the simulator's event handling to the state where one can do 3+4 ctrl-p and get 7, and bring up halos in the world, rather than the simulator's window.  Move the relinquish processor flashing into the simulator window if it exists.

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

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 eventTransformer 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 eventQueue'
  	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>>handleListenEvent: (in category 'I/O primitives support') -----
  handleListenEvent: aMorphicEvent
+ 	"openAsMorph[NoTranscript] regsitered me for listen events via HandMorph>>addEventListener.
- 	"openAsMorph regsitered me for listen events via HandMorph>>addEventListener.
  	Transform the listen event and add it to my event queue."
+ 	((aMorphicEvent isMouse or: [aMorphicEvent isKeyboard])
+ 	 and: [displayView bounds containsPoint: aMorphicEvent position]) ifTrue:
+ 		[eventTransformer degenerateEvent: aMorphicEvent for: self]!
- 	(aMorphicEvent isMouse or: [aMorphicEvent isKeyboard]) ifFalse:
- 		[^self].
- 	(SimulatorEventTransformer default degenerateEvent: aMorphicEvent) ifNotNil:
- 		[:evtBuf|
- 		 (evtBuf first = SimulatorEventTransformer eventTypeMouse
- 		  and: [displayView bounds containsPoint: aMorphicEvent position]) ifTrue:
- 			[| xtranslated ytranslated |
- 			 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].
- 		 evtBuf at: 8 put: 1. "windowIndex"
- 		 self queueForwardedEvent: evtBuf]!

Item was changed:
  ----- Method: CogVMSimulator>>ioRelinquishProcessorForMicroseconds: (in category 'I/O primitives support') -----
  ioRelinquishProcessorForMicroseconds: microseconds
  	"In the simulator give an indication that we're idling and check for input.
  	 If called from machine code then increment the byte count since the clock
  	 is derived from it and the clock will not advance otherwise.
  	 If we're simulating threading we're in difficulties.  We need a UI process
  	 (to run activities such as fill-in-the-blanks) but we also need an independent
  	 thread of control to run this VM thread.  So we need to fork a new UI process."
+ 	Display reverse: ((displayView
+ 						ifNil: [0 at 0]
+ 						ifNotNil: [displayView bounds origin]) extent: 16 at 16).
- 	Display reverse: (0 at 0 extent: 16 at 16).
  	Sensor peekEvent ifNotNil:
  		[self forceInterruptCheck].
  	Processor activeProcess == Project uiProcess ifTrue:
  		[World doOneCycle].
  	microseconds >= 1000
  		ifTrue: [self isThreadedVM ifTrue:
  					[self forceInterruptCheckFromHeartbeat].
  				(Delay forMilliseconds: microseconds + 999 // 1000) wait]
  		ifFalse: [Processor yield].
  	byteCount := byteCount + (microseconds * ByteCountsPerMicrosecond) - 1.
  	self incrementByteCount!

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 := SimulatorImageMorph new image: displayForm)
- 	window addMorph: (displayView := ImageMorph new image: displayForm)
  			frame: (0 at 0 corner: 1 at 0.8).
  	displayView activeHand addEventListener: self.
+ 	eventTransformer := SimulatorEventTransformer new.
  
  	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 := SimulatorImageMorph new image: displayForm)
- 	window addMorph: (displayView := ImageMorph new image: displayForm)
  			frame: (0 at 0 corner: 1 at 0.95).
  	displayView activeHand addEventListener: self.
+ 	eventTransformer := SimulatorEventTransformer new.
  
  	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 changed:
  Object subclass: #SimulatorEventTransformer
+ 	instanceVariableNames: 'buttons modifiers'
- 	instanceVariableNames: 'buttons'
  	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>>degenerateEvent:for: (in category 'event transformation') -----
+ degenerateEvent: aMorphicEvent for: client
+ 	"Handle ''degenerating'' events for aClient.  This interface gets the client
+ 	 to queue the event via queueForwardedEvent:, and may generate more
+ 	 than one event for the input event (i.e. a fake mouse move before a
+ 	 button down), in addition to filtering-out excessive mouse moves."
+ 	aMorphicEvent isMouse ifTrue:
+ 		[^self degenerateMouseEvent: aMorphicEvent for: client].
+ 	aMorphicEvent isKeyboard ifTrue:
+ 		[^self degenerateKeyboardEvent: aMorphicEvent for: client].
+ 	^self degenerateUnknownEvent: aMorphicEvent for: client!

Item was changed:
  ----- Method: SimulatorEventTransformer>>degenerateKeyboardEvent: (in category 'event transformation') -----
  degenerateKeyboardEvent: aMorphicEvent
  	"see HandMorph>>generateKeyboardEvent and EventSensor class comment"
  	^{	2.
  		aMorphicEvent timeStamp.
  		aMorphicEvent keyValue.		"<--this is wrong. See Sensor FirstEvt: for what needs to happen. hooo boy"
  		aMorphicEvent type caseOf: {
  					[#keyDown]	->	[EventKeyDown].
  					[#keyUp]		->	[EventKeyUp].
  					[#keystroke]	->	[EventKeyChar] }.
+ 		modifiers.
- 		aMorphicEvent buttons bitAnd: 7.
  		aMorphicEvent keyValue.
  		0.
  		0 }!

Item was added:
+ ----- Method: SimulatorEventTransformer>>degenerateKeyboardEvent:for: (in category 'event transformation') -----
+ degenerateKeyboardEvent: aMorphicEvent for: aClient
+ 	"Convert the keyboard event into a low-level event for the VM simulator (aClient).
+ 	 See HandMorph>>generateKeyboardEvent and EventSensor class comment"
+ 	aClient queueForwardedEvent:
+ 		{	2.
+ 			aMorphicEvent timeStamp.
+ 			aMorphicEvent keyValue.		"<--this is wrong. See Sensor FirstEvt: for what needs to happen. hooo boy"
+ 			aMorphicEvent type caseOf: {
+ 						[#keyDown]	->	[EventKeyDown].
+ 						[#keyUp]		->	[EventKeyUp].
+ 						[#keystroke]	->	[EventKeyChar] }.
+ 			modifiers.
+ 			aMorphicEvent keyValue.
+ 			0.
+ 			self windowIndex }!

Item was changed:
  ----- Method: SimulatorEventTransformer>>degenerateMouseEvent: (in category 'event transformation') -----
  degenerateMouseEvent: aMorphicEvent
  	"see HandMorph>>generateMouseEvent"
  
+ 	modifiers := aMorphicEvent buttons >> 3. "Sad, but modifiers come in on mouse move events..."
  	aMorphicEvent type == #mouseMove
  		ifTrue: [buttons = 0 ifTrue: [^nil]] "filter-out mouse moves unless buttons are pressed, so simulation doersn't get window leave events when we leave its window"
  		ifFalse: [buttons := aMorphicEvent buttons].
  	^{	1.
  		aMorphicEvent timeStamp.
  		aMorphicEvent position x.
  		aMorphicEvent position y.
  		buttons bitAnd: 7.  "thanks Ron T."
  		buttons >> 3.     "Thanks dtl"
  		0.
  		0 }!

Item was added:
+ ----- Method: SimulatorEventTransformer>>degenerateMouseEvent:for: (in category 'event transformation') -----
+ degenerateMouseEvent: aMorphicEvent for: aClient
+ 	"Convert the mouse event into low-level events for the VM simulator (aClient).  Filter-out mouse moves,
+ 	 and generate a fake mouse move before each button press.
+ 	 See HandMorph>>generateMouseEvent"
+ 	| translated |
+ 	translated := aMorphicEvent position - aClient displayView bounds origin.
+ 	modifiers := aMorphicEvent buttons >> 3. "Sad, but modifiers come in on mouse move events..."
+ 
+ 	aMorphicEvent type == #mouseMove
+ 		ifTrue: "filter-out mouse moves unless buttons are pressed, so simulation doersn't get window leave events when we leave its window"
+ 			[buttons = 0 ifTrue: [^nil]]
+ 		ifFalse:"If the buttons are going down, make sure to add a mouse move event to the current position before the buttons are pressed."
+ 			[((buttons bitAnd: 7) = 0 and: [(aMorphicEvent buttons bitAnd: 7) ~= 0]) ifTrue:
+ 				[aClient queueForwardedEvent:
+ 							{	1.
+ 								aMorphicEvent timeStamp.
+ 								translated x.
+ 								translated y.
+ 								0.
+ 								buttons >> 3.     "Thanks dtl"
+ 								0.
+ 								self windowIndex }].
+ 				 buttons := aMorphicEvent buttons].
+ 	aClient queueForwardedEvent:
+ 			{	1.
+ 				aMorphicEvent timeStamp.
+ 				translated x.
+ 				translated y.
+ 				buttons bitAnd: 7.  "thanks Ron T."
+ 				buttons >> 3.     "Thanks dtl"
+ 				0.
+ 				self windowIndex }!

Item was changed:
  ----- Method: SimulatorEventTransformer>>initialize (in category 'initialize-release') -----
  initialize
+ 	buttons := modifiers := 0!
- 	buttons := 0!

Item was added:
+ ----- Method: SimulatorEventTransformer>>windowIndex (in category 'event transformation') -----
+ windowIndex
+ 	^1!

Item was changed:
  ImageMorph subclass: #SimulatorImageMorph
+ 	instanceVariableNames: ''
- 	instanceVariableNames: 'eventForwarder'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation-Morphic'!
  
+ !SimulatorImageMorph commentStamp: 'eem 7/15/2015 09:48' prior: 0!
+ A SimulatorImageMorph is an ImageMorph that suppresses halos.!
- !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:
+ ----- Method: SimulatorImageMorph>>handleMouseDown: (in category 'event handling') -----
+ handleMouseDown: anEvent
+ 	anEvent wasHandled: true!

Item was added:
+ ----- Method: SimulatorImageMorph>>handleMouseEnter: (in category 'event handling') -----
+ handleMouseEnter: anEvent
+ 	anEvent wasHandled: true!

Item was added:
+ ----- Method: SimulatorImageMorph>>handleMouseLeave: (in category 'event handling') -----
+ handleMouseLeave: anEvent
+ 	^super handleMouseLeave: anEvent!

Item was added:
+ ----- Method: SimulatorImageMorph>>handleMouseOver: (in category 'event handling') -----
+ handleMouseOver: anEvent
+ 	anEvent wasHandled: true!

Item was added:
+ ----- Method: SimulatorImageMorph>>handleMouseUp: (in category 'event handling') -----
+ handleMouseUp: anEvent
+ 	anEvent wasHandled: true!

Item was added:
+ ----- Method: SimulatorImageMorph>>handlerForMouseDown: (in category 'event handling') -----
+ handlerForMouseDown: anEvent
+ 	"Override all mouse button shenanigans like halos by handling any and all mouse down events."
+ 	^self!

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

Item was changed:
  ----- Method: StackInterpreterSimulator>>handleListenEvent: (in category 'I/O primitives support') -----
  handleListenEvent: aMorphicEvent
+ 	"openAsMorph[NoTranscript] regsitered me for listen events via HandMorph>>addEventListener.
- 	"openAsMorph regsitered me for listen events via HandMorph>>addEventListener.
  	Transform the listen event and add it to my event queue."
+ 	((aMorphicEvent isMouse or: [aMorphicEvent isKeyboard])
+ 	 and: [displayView bounds containsPoint: aMorphicEvent position]) ifTrue:
+ 		[eventTransformer degenerateEvent: aMorphicEvent for: self]!
- 	(aMorphicEvent isMouse or: [aMorphicEvent isKeyboard]) ifFalse:
- 		[^self].
- 	(SimulatorEventTransformer default degenerateEvent: aMorphicEvent) ifNotNil:
- 		[:evtBuf|
- 		 (evtBuf first = SimulatorEventTransformer eventTypeMouse
- 		  and: [displayView bounds containsPoint: aMorphicEvent position]) ifTrue:
- 			[| xtranslated ytranslated |
- 			 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].
- 		 evtBuf at: 8 put: 1. "windowIndex"
- 		 self queueForwardedEvent: evtBuf]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>ioRelinquishProcessorForMicroseconds: (in category 'I/O primitives support') -----
  ioRelinquishProcessorForMicroseconds: microseconds
  	"In the simulator give an indication that we're idling and check for input."
+ 	Display reverse: ((displayView
+ 						ifNil: [0 at 0]
+ 						ifNotNil: [displayView bounds origin]) extent: 16 at 16).
- 	Display reverse: (0 at 0 extent: 16 at 16).
  	Sensor peekEvent ifNotNil:
  		[self forceInterruptCheck].
  	Processor activeProcess == Project uiProcess ifTrue:
  		[World doOneCycle].
  	microseconds >= 1000
  		ifTrue: [(Delay forMilliseconds: microseconds + 999 // 1000) wait]
  		ifFalse: [Processor yield].
  	"And increase the byteCount form which the microsecond clock is derived..."
  	byteCount := byteCount + microseconds - 1.
  	self incrementByteCount!

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 := SimulatorImageMorph new image: displayForm)
- 	window addMorph: (displayView := ImageMorph new image: displayForm)
  			frame: (0 at 0 corner: 1 at 0.8).
  	displayView activeHand addEventListener: self.
+ 	eventTransformer := SimulatorEventTransformer new.
  
  	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 := SimulatorImageMorph new image: displayForm)
- 	window addMorph: (displayView := ImageMorph new image: displayForm)
  			frame: (0 at 0 corner: 1 at 0.95).
  	displayView activeHand addEventListener: self.
+ 	eventTransformer := SimulatorEventTransformer new.
  
  	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!



More information about the Vm-dev mailing list