Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
DemoEllipseSRE
Last updated at 10:11 am UTC on 30 May 2018

A demonstration morph used in BabySRE


'From Squeak3.10.2 of ''5 June 2008'' [latest update: #7179] on 10 May 2018 at 6:46:01 pm'!
EllipseMorph subclass: #DemoEllipseSRE
	instanceVariableNames: 'colorIndex'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'BabySRE-Info'!
!DemoEllipseSRE commentStamp: 'TRee 1/9/2005 11:05' prior: 0!
A morph for demonstrating the BabySRE object diagram. The demo is an ellipse that cycles through a number of colors.

colorIndex - anInteger. The current color index.

	 'DemoEllipseSRE new openInWorld.' doIt to open
Open collaborator tool with halo debug command 'SRE collaboration'
Open object browser with halo debug command 'SRE object browser'
	!


!DemoEllipseSRE methodsFor: 'drawing' stamp: 'TRee 1/13/2005 18:21'!
drawOn: aCanvas 
"	self doOnlyOnce: [self traceRM: self levels: 50]."
" For the adventurous explorer: "
"	self stackSnapshotBrowseOnce: 50. "
	super drawOn: aCanvas. 
" To rearm the one shot execute:
		Smalltalk at: #OneShotArmed put: true. "  
		! !


!DemoEllipseSRE methodsFor: 'experiment' stamp: 'TRee 12/12/2004 11:58'!
nextColor
	| colors |
	colors := {Color red. Color green. Color blue. Color magenta. Color yellow.}.
	colorIndex ifNil: [colorIndex := 1].
	colorIndex := colorIndex + 1 \\ colors size + 1.
	^colors at: colorIndex.
	! !


!DemoEllipseSRE methodsFor: 'stepping and presenter' stamp: 'TRee 1/11/2005 12:36'!
step
"	self doOnlyOnce: [self traceRM: self levels: 50]."
" For the explorer: "
"	self stackSnapshotBrowseOnce: 50. "
	self color: self nextColor.
	" To rearm the one shot execute:
		Smalltalk at: #OneShotArmed put: true. "! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

DemoEllipseSRE class
	instanceVariableNames: ''!

!DemoEllipseSRE class methodsFor: 'class initialization' stamp: 'TRee 6/12/2005 15:31'!
initialize
	" DemoEllipseSRE initialize "
| wsString |
wsString :=

'SRE (Squeak Reverse Engineering)

SRE (Squeak Reverse Engineering) is a set of three tools making Squeak objects visible and tangible:

1) SRE collaboration lets me build a diagram of system objects with the links between them. With this tool, I find that I can master larger systems than I could before.

2) SRE Object Browser gives me a full description of an object with its identity, state, and behavior. I can edit its state as in an Inspector and its behavior as in a class Browser. The
class hierarchy is flattened so that I see the object as a whole. 

3) Object>>traceRM: reportObject 
   Object >>traceRM: reportObject levels: levCount
and other methods in the *BabySRE-traceStack category write debug trace in Transcript with info about levCount number of stack entries from its top.

Taken together, these tools put me in closer contact with the real objects of the image, they
give me better understanding of existing systems and better contol over new ones. It also helps that objects now present themselves by [oop] so that I know the identity of the objects I am dealing with.
	
Installation: Load latest version from SqueakMap.

To reproduce my demo example, run

           DemoEllipseSRE new openInWorld.

   and observe the ellipse with cycling colors appear in the top left corner.
then select it and left-click with ALT-button (Windows) down to open halo. Open debug menu in the white button on the right hand edge.     Choose ''SRE collaboration'' to open a collaboration diagram on the morph.
   Choose ''SRE object browser'' to open an object browser on the morph.

Documentation
See class comment in class 
     ACollaboratorToolSRE


 The demo is described in the document found at
	http://heim.ifi.uio.no/~trygver/2004/babysre/BabySRE.pdf '.

	(Workspace new contents: wsString) openLabel: 'BabySRE: Squeak Reverse Engineering' translated.
	! !


 DemoEllipseSRE initialize!