[squeak-dev] Please try out | Inspector Refactoring =)

David T. Lewis lewis at mail.msen.com
Wed Apr 22 01:14:04 UTC 2020


+1 for merging to trunk.

This looks like a very good set of changes to improve inspectors.

Some of the new inspector classes could do with class comments, so
I am attaching a change set with suggested comments.

This is a dumb question, but what is the field items menu on an
inspector? A MorphInspector adds menu picks for openScreenshotInHand
and openScreenshotInWorld, but I don't know how to open the actual
menu. In other words, when I inspect a Morph with the new changes
applied, I am using a MorphInspector to display the morph. It shows
all of the morph properties (very nice), but I don't know what mouse
button and/or keyboard keys to use to get a menu with the new selections.

Yes I know this question belongs on the beginners list :-/

Dave


On Tue, Apr 21, 2020 at 06:37:51PM +0200, Marcel Taeumel wrote:
> Hi all!
> 
> Please find attached a slightly updated version of this Inspector Refactoring:
> 
> - Stef's bug fixed
> - InspectorBrowser cleaned up a little bit
> - some MVC-related bugs fixed
> - BasicInspector more robust; no #expectedFailures anymore in the BasicInspectorTests
> 
> Happy try out! If you don't have further concerns with this, I will merge it into Trunk tomorrow or the day after.
> 
> Best,
> Marcel
> Am 20.04.2020 16:19:12 schrieb Marcel Taeumel <marcel.taeumel at hpi.de>:
> Hi Stef,
> 
> thank you for testing and finding this bug. I think we can just factor out #okToDiscardCustomFields from #okToClose and then trigger that confirmation manually in #replaceInspectorWithExplorer. So we can re-use the confirmation dialog and properly react to the user's decision.
> 
> Best,
> Marcel
> Am 18.04.2020 01:18:26 schrieb Thiede, Christoph <christoph.thiede at student.hpi.uni-potsdam.de>:
> Hi Stef, many thanks for trying out the changeset and finding??the bug! :-)
> 
> I'm not sure if there is already??a better pattern to fix this, but the following patch resolved the issue for me:
> 
> Inspector >??replaceInspectorWithExplorer
> "Switch to an explorer tool."
> | window currentBounds |
> self changed: #acceptChanges. "We copy the current state anyway. See below."
> currentBounds := ToolBuilder default class getBoundsForWindow: self containingWindow.
> 
> "Close first because MVC fiddles around with processes."
> +?? self myDependents ifNil: [self myDependents: #()].
> self changed: #close.
> +?? self myDependents ifNotNil: [
> +?? "View resisted??to release, aborting"
> +?? ^ self].
> self changed: #close.??
> window := ToolSet explore: self object.
> "---- In MVC, the lines after this will not be executed ---"
> 
> window model setExpression: self expression.
> ToolBuilder default class setBoundsForWindow: window to: currentBounds.
> 
> Hm, maybe we should extract this into Model >> #close ... see also the flag??in Debugger >> #close for reference.
> (And thinking more generally, I would like to move the whole logic somewhere into the UIManager/ToolBuilder. But that's stuff for another refactoring :-))
> 
> Best,
> Christoph
> 
> 
> Von: Squeak-dev <squeak-dev-bounces at lists.squeakfoundation.org> im Auftrag von St??phane Rollandin <lecteur at zogotounga.net>
> Gesendet: Samstag, 18. April 2020 00:58 Uhr
> An: squeak-dev at lists.squeakfoundation.org
> Betreff: Re: [squeak-dev] Please try out | Inspector Refactoring =)
> ??
> > *2. Custom Fields*
> >
> > You can now add custom fields during your inspector session. Invoke the
> > field-list menu and choose "add field..." at the bottom.
> 
> If, after having added a field, one swaps to the explorer via the
> bottom-right button, a dialog appears warning that the field will be
> discarded. This dialog has a 'yes' and a 'no' button, but both lead to
> the same behavior: the explorer is installed.
> 
> Stef
> 

> 'From Squeak6.0alpha of 19 January 586155 [latest update: #19594] on 21 April 2020 at 6:22:15 pm'!
"Change Set:		inspector-refactoring
Date:			15 April 2020
Author:			Marcel Taeumel"
			
Project current isMorphic ifTrue: [
	| windows |
	windows := SystemWindow
		windowsIn: Project current world
		satisfying: [:window | window visible and: [window model isKindOf: Inspector] ].
	Smalltalk globals
		at: #ObjectsUnderInspection
		put: (windows collect: [:ea | ea model object]).
	windows do: [:window | [window delete] valueSupplyingAnswer: true]].!

StringHolder subclass: #Inspector
	instanceVariableNames: 'object selectionIndex timeOfLastListUpdate selectionUpdateTime context expression shouldStyleValuePane contentsTyped fieldListStyler customFields fields '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!Inspector commentStamp: 'mt 4/6/2020 15:16' prior: 0!
I am a tool that allows to inspect and modify the internal representation of an object. As a StringHolder, the string I represent is the value of the currently selected inspector field, which may be an instance variable, of the observed object.

Beside the #contents in my value pane, I have an extra code pane that holds an #expression to be evaluated on the inspected object -- not the currently selected inspector field.

Take a look at my "fields ..." protocols as well as InspectorField.

(Note that the idea of "elements" from the CollectionInspector bleeds a little bit down into this interface to simplify the implementation of field truncation as well as #inspectOne. Sorry for that. Usually, the inspected object will only produce "fields" to display, and maybe "items" in a pop-up menu. Only collections have "elements".)!


!BasicInspector commentStamp: 'mt 3/30/2020 14:38' prior: 0!
I am an Inspector that sends as few messages as possible to collect information about the inspected object. For example, use me to inspect proxies, which are typically subclasses of ProtoObject and hence understand only little messages but make heay use of #doesNotUnderstand:.!

Inspector subclass: #ClassInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!ClassInspector commentStamp: 'mt 3/30/2020 14:47' prior: 0!
I am an Inspector that is specialized for inspecting Class objects. I show fields for my class variables and the shared pools I use.!

Inspector subclass: #CollectionInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!CollectionInspector commentStamp: 'mt 3/31/2020 10:18' prior: 0!
I am an Inspector that is specialized for inspecting collections. I provide extended access to the inspected collection's items, such as adding and removing items.

Note that I can directly inspect instances of ArrayedCollection and alike.!

CollectionInspector subclass: #BitsetInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!
Smalltalk renameClassNamed: #CompiledMethodInspector as: #CompiledCodeInspector!

!CompiledCodeInspector commentStamp: 'ct 1/12/2020 15:21' prior: 0!
I am an inspector specialized for inspecting CompiledMethods.!

CompiledCodeInspector subclass: #CompiledMethodInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: '60Deprecated-Tools-Inspector'!

!CompiledMethodInspector commentStamp: 'mt 4/6/2020 08:30' prior: 0!
Deprecated since CompiledCodeInspector can inspect both CompiledBlock and CompiledMethod.!


!ContextInspector commentStamp: 'ct 1/12/2020 15:26' prior: 0!
I am an Inspector that is specialized for inspecting Contexts.!

ContextInspector subclass: #ContextVariablesInspector
	instanceVariableNames: 'fieldList '
	classVariableNames: 'ShowStackVariables '
	poolDictionaries: ''
	category: 'Tools-Debugger'!

!ContextVariablesInspector commentStamp: 'mt 3/25/2020 16:32' prior: 0!
I am an inspector that is specialized to inspecting the variables of a Context. I am typically displayed as part of a Debugger, where I sit besides an inspector for the receiver object. That's why a traditional Contextinspector would not work because it makes "ThisContext" be "self".

At some point, this should subclass from Contextinspector.!

CollectionInspector subclass: #DictionaryInspector
	instanceVariableNames: 'keyArray '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!DictionaryInspector commentStamp: 'ct 1/12/2020 15:26' prior: 0!
I am an Inspector that is specialized for inspecting Dictionarys.!

DictionaryInspector subclass: #BagInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!BagInspector commentStamp: 'mt 4/2/2020 10:32' prior: 0!
I am an inspector for bags. I specialize the inspector for dictionaries because I expose the internal dictionary all bags use.!

Model subclass: #InspectorBrowser
	instanceVariableNames: 'browser inspector '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!InspectorBrowser commentStamp: 'tcj 3/12/2018 07:55' prior: 0!
I am an inspector that also shows all messages the inspected objects can understand. I combine inspector and code browser.

InspectorBrowser openOn: Smalltalk!

Object subclass: #InspectorField
	instanceVariableNames: 'key valueGetter valueGetterExpression valueSetter valueSetterExpression name shouldStyleName shouldStyleValue shouldPrintValueAsIs type inspector'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!InspectorField commentStamp: 'mt 3/9/2020 14:34' prior: 0!
I represent a single field of an Inspector in which I am composed.

I am basically a pair of #key and #value, but may have an extra human-readable #name to be shown in the Inspector's views. My #value can only be accessed in scope of an Inspector because I need an #object to work with.!

Smalltalk renameClassNamed: #AbstractInspectorTest as: #InspectorTest!
ClassTestCase subclass: #InspectorTest
	instanceVariableNames: 'inspector'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
InspectorTest subclass: #BasicInspectorTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
InspectorTest subclass: #ClassInspectorTest
	instanceVariableNames: ''
	classVariableNames: 'InnerTestObject'
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
Smalltalk renameClassNamed: #OrderedCollectionInspectorTest as: #CollectionInspectorTest!
InspectorTest subclass: #CollectionInspectorTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
Smalltalk renameClassNamed: #CompiledMethodInspectorTest as: #CompiledCodeInspectorTest!
InspectorTest subclass: #CompiledCodeInspectorTest
	instanceVariableNames: ''
	classVariableNames: 'InnerTestObject'
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
InspectorTest subclass: #ContextInspectorTest
	instanceVariableNames: ''
	classVariableNames: 'InnerTestObject'
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
ContextInspectorTest subclass: #ContextVariablesInspectorTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolsTests-Debugger'!
CollectionInspectorTest subclass: #DictionaryInspectorTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
Inspector variableSubclass: #InspectorTestInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
Object variableSubclass: #InspectorTestObject
	instanceVariableNames: 'apple orange'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
Inspector subclass: #MorphInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolBuilder-Morphic-Tools'!
CollectionInspector subclass: #OrderedCollectionInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: '60Deprecated-Tools-Inspector'!

!OrderedCollectionInspector commentStamp: 'mt 4/6/2020 08:30' prior: 0!
I am an Inspector that is specialized for inspecting OrderedCollections. Deprecated since regular CollectionInspector can add and remove elements.!

CollectionInspector subclass: #SetInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!SetInspector commentStamp: 'ct 1/12/2020 15:21' prior: 0!
I am an inspector that is specialized for inspecting Sets. I display the elements of the set like elements of an array. Note that the indices, being phyical locations in the hash table, are not meaningful outside of the set.!

CollectionInspectorTest subclass: #SetInspectorTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!
SetInspector subclass: #WeakSetInspector
	instanceVariableNames: 'flagObject '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!
SetInspectorTest subclass: #WeakSetInspectorTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ToolsTests-Inspector'!

!FutureMaker methodsFor: '*Tools-Inspector' stamp: 'das 9/7/2005 10:09'!
defaultLabelForInspector
	"Answer the default label to be used for an Inspector window on the receiver."
	^self class name! !

!FutureMaker methodsFor: '*Tools-Inspector' stamp: 'das 9/7/2005 10:09'!
inspectorClass
	"Answer the class of the inspector to be used on the receiver.  Called by inspect; 
	use basicInspect to get a normal (less useful) type of inspector."

	^ Inspector! !


!Object methodsFor: '*Etoys-tiles' stamp: 'ct 1/4/2020 16:46'!
tearOffTile

	| tile |
	tile := TileMorph new referTo: self.
	self currentHand attachMorph: tile.
	^ tile! !

!Object methodsFor: '*Tools-Inspector' stamp: 'mt 4/5/2018 10:24'!
basicInspect
	"Create and schedule an Inspector in which the user can examine the 
	receiver's variables. This method should not be overriden."
	ToolSet basicInspect: self! !

!Object methodsFor: '*Tools-Inspector' stamp: 'mt 4/5/2018 10:24'!
inspect
	"Create and schedule an Inspector in which the user can examine the receiver's variables."
	ToolSet inspect: self! !

!Object methodsFor: '*Tools-Inspector' stamp: 'mt 4/5/2018 10:24'!
inspectWithLabel: aLabel
	"Create and schedule an Inspector in which the user can examine the receiver's variables."
	ToolSet inspect: self label: aLabel! !

!Object methodsFor: '*Tools-Inspector' stamp: 'apb 7/14/2004 12:19'!
inspectorClass
	"Answer the class of the inspector to be used on the receiver.  Called by inspect; 
	use basicInspect to get a normal (less useful) type of inspector."

	^ Inspector! !


!Class methodsFor: '*Tools-Inspector' stamp: 'ct 1/4/2020 14:54'!
inspectorClass

	^ ClassInspector! !


!ClassTest methodsFor: 'tests' stamp: 'mt 4/6/2020 08:27'!
testChangeClassOf
	"Exercise primitiveChangeClass (primitive 115) for a common use case. This should pass
	for any Squeak image format (but failed for image format 68002 prior to VM fix)"

	self shouldnt: [Inspector new primitiveChangeClassTo: CompiledCodeInspector new] raise: Error! !


!Collection methodsFor: '*Tools-Inspector' stamp: 'mt 3/31/2020 10:23'!
inspectorClass

	^ CollectionInspector! !


!Bag methodsFor: '*Tools-Inspector' stamp: 'mt 3/31/2020 11:52'!
inspectorClass

	^ BagInspector! !


!Bitset methodsFor: '*Tools-Inspector' stamp: 'mt 4/2/2020 10:41'!
inspectorClass

	^ BitsetInspector! !

!Bitset methodsFor: 'printing' stamp: 'mt 4/2/2020 10:48'!
printElementsOn: aStream separatedBy: delimiter
	"Overridden to always inform about the entire set of bits."

	(0 to: self capacity-1)
		do: [:index | aStream print: (self bitAt: index)]
		separatedBy: [aStream nextPutAll: delimiter asString].! !


!Compiler methodsFor: 'public access' stamp: 'ct 2/14/2020 16:42'!
compiledMethodFor: textOrStream in: aContext to: receiver environment: anEnvironment notifying: aRequestor ifFail: failBlock
	"Compiles the sourceStream into a parse tree, then generates code into a method, and answers it.  If receiver is not nil, then the text can refer to instance variables of that receiver (tools such as Inspector use this). If aContext is not nil, the text can refer to temporaries in that context (tools such as Debugger use this).  If anEnvironment is not nil, then all global bindings in the text are resolved in that environment instead of the current environment.  If aRequestor is not nil, then it will receive a notify:at: message before the attempt to evaluate is aborted."

	| methodNode method |
	methodNode := self
		compileNoPattern: textOrStream
		in: (self classForReceiver: receiver context: aContext)
		context: aContext
		environment: anEnvironment
		notifying: aRequestor
		ifFail: [^failBlock value].
	method := self interactive
		ifTrue: [ methodNode generateWithTempNames ] 
		ifFalse: [ methodNode generate ].
	^method! !

!Compiler methodsFor: 'public access' stamp: 'ct 2/16/2020 15:51'!
compiledMethodFor: textOrStream in: aContext to: receiver notifying: aRequestor ifFail: failBlock

	^ self compiledMethodFor: textOrStream in: aContext to: receiver environment: receiver class environment notifying: aRequestor ifFail: failBlock! !


!Context methodsFor: '*Tools-Inspector' stamp: 'ct 9/27/2019 16:59'!
inspectorClass

	^ ContextInspector! !


!Debugger methodsFor: '*60Deprecated-accessing' stamp: 'mt 3/25/2020 12:01'!
receiverInspectorObject: obj context: ctxt
	"set context before object so it can refer to context when building field list"

	self deprecated: 'Talk to #receiverInspector directly.'.

	receiverInspector context: ctxt.
	receiverInspector inspect: obj.
! !

!Debugger methodsFor: 'initialize' stamp: 'ct 1/3/2020 19:08'!
initializeFull
	"Expand the stack for the full debugger. Create inspectors."
	
	| oldIndex |
	oldIndex := contextStackIndex.
	contextStackIndex := 0.
	
	self expandStack.

	receiverInspector := Inspector on: nil.
	contextVariablesInspector := ContextVariablesInspector on: nil.
	
	self toggleContextStackIndex: oldIndex.! !

!Debugger methodsFor: 'private' stamp: 'mt 3/25/2020 12:01'!
contextStackIndex: anInteger oldContextWas: oldContext 
	"Change the context stack index to anInteger, perhaps in response to user selection."

	| isNewMethod |
	self saveReceiverInspectorState.
	self saveContextVariablesInspectorState.
	contextStackIndex := anInteger.
	anInteger = 0 ifTrue:
		[currentCompiledMethod := contents := nil.
		 self changed: #contextStackIndex.
		 self decorateButtons.
		 self contentsChanged.
		 contextVariablesInspector object: nil.
		 receiverInspector context: nil; inspect: self receiver.
		 ^self].
	isNewMethod := oldContext isNil
		or: [oldContext method ~~ (currentCompiledMethod := self selectedContext method)].
	isNewMethod ifTrue:
		[contents := self selectedMessage.
		 self contentsChanged.
		 self pcRange].
	self changed: #contextStackIndex.
	self decorateButtons.
	contextVariablesInspector object: self selectedContext.
	self restoreContextVariablesInspectorState.
	receiverInspector context: self selectedContext; inspect: self receiver.
	self restoreReceiverInspectorState.
	isNewMethod ifFalse:
		[self changed: #contentsSelection]! !

!Debugger methodsFor: 'user interface' stamp: 'mt 11/29/2019 11:15'!
restoreContextVariablesInspectorState
	"For the user's convenience. Save field selection and user-typed content in the context-variables inspector. See #saveContextVariablesInspectorState."

	contextVariablesInspectorState ifNotNil: [:stateForAll |
		self keyForContextVariablesInspectorState ifNotNil: [:keyForState |
			stateForAll 
				at: keyForState
				ifPresent: [:state |
					self contextVariablesInspector selectFieldNamed: state first.
					state second ifNotNil: [:contentsTyped |
						self contextVariablesInspector
							setContentsTyped: contentsTyped]]]].! !

!Debugger methodsFor: 'user interface' stamp: 'mt 11/29/2019 11:11'!
restoreReceiverInspectorState
	"For the user's convenience. Restore field selection and user-typed content in the receiver inspector. See #saveReceiverInspectorState."
	
	receiverInspectorState ifNotNil: [:stateForAll |
		self keyForReceiverInspectorState ifNotNil: [:keyForState |
			stateForAll 
				at: keyForState
				ifPresent: [:state |
					self receiverInspector selectFieldNamed: state first.
					state second ifNotNil: [:contentsTyped |
						self receiverInspector
							setContentsTyped: contentsTyped]]]].! !

!Debugger methodsFor: 'user interface' stamp: 'ct 1/13/2020 13:33'!
saveContextVariablesInspectorState
	"For the user's convenience. Save field selection and user-typed content in the context-variables inspector. See #restoreContextVariablesInspectorState."
	
	| stateToSave keyForState |
	self flag: #duplication.
	(keyForState := self keyForContextVariablesInspectorState)
		ifNil: [^ self].
	contextVariablesInspectorState
		ifNil: [contextVariablesInspectorState := IdentityDictionary new].
	stateToSave := {
		self contextVariablesInspector selectedFieldName.
		self contextVariablesInspector contentsTyped }.
	contextVariablesInspectorState
		at: keyForState
		put: stateToSave.! !

!Debugger methodsFor: 'user interface' stamp: 'ct 1/13/2020 13:33'!
saveReceiverInspectorState
	"For the user's convenience. Save field selection and user-typed content in the receiver inspector. See #restoreReceiverInspectorState."

	| stateToSave keyForState |
	self flag: #duplication.
	(keyForState := self keyForReceiverInspectorState)
		ifNil: [^ self].
	receiverInspectorState
		ifNil: [receiverInspectorState := IdentityDictionary new].
	stateToSave := {
		self receiverInspector selectedFieldName.
		self receiverInspector contentsTyped }.
	receiverInspectorState
		at: keyForState
		put: stateToSave.! !


!FormInspectView class methodsFor: 'instance creation' stamp: 'ct 1/13/2020 13:15'!
openOn: aFormDictionary withLabel: aLabel
	"open a graphical dictionary in a window having the label aLabel. 
     aFormDictionary should be a dictionary containing as value a form."

     ^ aFormDictionary inspectWithLabel: aLabel
! !


!HtmlEntity methodsFor: 'user interface' stamp: 'ct 9/27/2019 21:44'!
inspectorClass

	^ HtmlEntityInspector! !


!Inspector methodsFor: 'accessing - contents' stamp: 'mt 3/31/2020 10:54'!
contents: aString notifying: aController
	"Try to change the contents of the selected field. This is the usual callback for all string holders."
	
	| result |
	result := self object class evaluatorClass new
		evaluate: aString
		in: self doItContext
		to: self doItReceiver
		notifying: aController
		ifFail: [^ false].
	
	^ self replaceSelectionValue: result! !

!Inspector methodsFor: 'accessing - contents' stamp: 'mt 3/10/2020 07:39'!
expression
	"The code string in the code pane. Recorded for Inspector/Explorer switching. See #replaceInspectorWithExplorer."

	^ expression ifNil: ['']! !

!Inspector methodsFor: 'accessing - contents' stamp: 'mt 3/10/2020 07:39'!
expression: aStringOrText
	"The code string in the code pane. Recorded for Inspector/Explorer switching. See #replaceInspectorWithExplorer."

	expression := aStringOrText.! !

!Inspector methodsFor: 'accessing' stamp: 'mt 3/25/2020 12:04'!
context

	^ context! !

!Inspector methodsFor: 'accessing' stamp: 'mt 3/25/2020 12:03'!
context: ctxt
	"Set the context of inspection, which is used for syntax highlighting and code evaluation."

	context := ctxt.! !

!Inspector methodsFor: 'accessing' stamp: 'mt 3/11/2020 11:19'!
customFields
	
	^ customFields! !

!Inspector methodsFor: 'accessing' stamp: 'mt 3/25/2020 12:04'!
doItContext
	"Answer the context in which a text selection can be evaluated."

	^ self context! !

!Inspector methodsFor: 'accessing' stamp: 'ct 1/5/2020 22:05'!
doItReceiver
	"Answer the object that should be informed of the result of evaluating a text selection."

	^ self object! !

!Inspector methodsFor: 'accessing' stamp: 'mt 3/11/2020 16:42'!
fields

	 ^ fields ifNil: [#()]! !

!Inspector methodsFor: 'accessing' stamp: 'mt 4/14/2020 15:57'!
object: anObject
	"Set anObject to be the object being inspected by the receiver. The current contents, including edits, in the value pane become void because the new object is likely to have new fields with different contents."

	self object == anObject ifTrue: [^ self].
	self resetContents.
	
	object := anObject.
	self changed: #object.
	
	self changed: #windowTitle.

	self updateFields.! !

!Inspector methodsFor: 'accessing' stamp: 'ct 9/19/2019 02:20'!
selectionIndex

	^ selectionIndex! !

!Inspector methodsFor: 'accessing' stamp: 'mt 4/1/2020 11:00'!
selectionIndex: anInteger
	"Changes the index to determine the currently selected field. If the field is already selected, update the fields contents in the value pane."

	self selectionIndex = anInteger
		ifTrue: [^ self updateContentsSafely].
	
	selectionIndex := anInteger.
	self changed: #selectionIndex.
	
	self updateContentsSafely.! !

!Inspector methodsFor: 'initialization' stamp: 'mt 3/11/2020 11:09'!
fieldClass

	^ InspectorField! !

!Inspector methodsFor: 'initialization' stamp: 'mt 4/12/2015 16:06'!
initialExtent
	"Answer the desired extent for the receiver when it is first opened on the screen.  "

	^ 350 @ 250! !

!Inspector methodsFor: 'initialization' stamp: 'ct 3/11/2020 19:07'!
initialize

	super initialize.
	
	customFields := OrderedCollection new.
	selectionIndex := 0.
	
	fieldListStyler := (Smalltalk classNamed: 'SHTextStylerST80')
		ifNotNil: [:class | class new].! !

!Inspector methodsFor: 'initialization' stamp: 'ct 1/6/2020 01:13'!
inspect: anObject 
	"Reinitialize the receiver so that it is inspecting anObject. Become an instance of the appropriate inspectorClass.
	
	Normally the receiver will be of the correct class (as defined by anObject inspectorClass), because it will have just been created by sending inspect to anObject.  However, the debugger uses two embedded inspectors, which are re-targetted on the current receiver each time the stack frame changes.  The left-hand inspector in the debugger has its class changed by the code here."

	| inspectorClass |
	inspectorClass := anObject inspectorClass.
	self class ~= inspectorClass ifTrue: [
		self class format = inspectorClass format
			ifTrue: [self primitiveChangeClassTo: inspectorClass basicNew]
			ifFalse: [self becomeForward: (self as: inspectorClass)]].
	
	self object: anObject.! !

!Inspector methodsFor: 'initialization' stamp: 'mt 3/25/2020 11:45'!
resetContents

	self setContents: nil.! !

!Inspector methodsFor: 'initialization' stamp: 'mt 4/1/2020 11:31'!
resetFields

	"1) Discard existing fields."
	fields ifNotNil: [
		fields do: [:field | field removeDependent: self].
		fields := nil "Just in case there is an error in the following calls."].
	
	"2a) Create new fields."
	fields := Array streamContents: [:stream |
		| workBlock |
		workBlock := [self streamFieldsOn: stream].
		workBlock ifError: [self streamErrorDoing: workBlock on: stream]].
	
	"2b) Establish field dependency."
	fields do: [:field | field addDependent: self].
	
	"3) Tell the views."
	self updateFieldList.! !

!Inspector methodsFor: 'initialization' stamp: 'mt 3/10/2020 13:15'!
setContents: aStringOrText
	"Do not style the value pane anymore. Clear the #contentsTyped buffer."

	shouldStyleValuePane := false.
	super setContents: aStringOrText.
	self contentsTyped: nil.! !

!Inspector methodsFor: 'initialization' stamp: 'mt 3/10/2020 13:21'!
setContentsTyped: aStringOrText
	"Simulate typing."
	
	shouldStyleValuePane := true.
	self contentsTyped: aStringOrText.
	
	self flag: #refactor. "mt: #changed: is not able to specify the receiver ..."
	self valuePane ifNotNil: [:pane |
		pane update: #editString with: aStringOrText].! !

!Inspector methodsFor: 'initialization' stamp: 'mt 3/10/2020 07:39'!
setExpression: aString
	"Set the code string in the code pane after switching between Inspector/Explorer. See #replaceInspectorWithExplorer."

	self expression: aString.
	self changed: #expression.! !

!Inspector methodsFor: 'menu - private' stamp: 'mt 4/6/2020 15:26'!
elementAt: indexOrKey
	"Backstop to simplify #inspectOne for all kinds of inspectors."

	^ (self elementGetterAt: indexOrKey) value: self object! !

!Inspector methodsFor: 'menu - private' stamp: 'mt 4/6/2020 15:04'!
elementGetterAt: indexOrKey
	"Backstop to simplify #inspectOne for all kinds of inspectors."

	^ [:object | (self fields detect: [:field | field key = indexOrKey]) getValueFor: self] ! !

!Inspector methodsFor: 'menu - commands' stamp: 'ct 1/4/2020 15:26'!
browseClass
	"Open a full browser on the class of the selected item"

	^ ToolSet browseClass: self classOfSelection! !

!Inspector methodsFor: 'menu - commands' stamp: 'ct 3/17/2020 00:26'!
browseClassHierarchy
	"Open a class list browser on the receiver's hierarchy."

	^ self systemNavigation browseHierarchy: self classOfSelection! !

!Inspector methodsFor: 'menu - commands' stamp: 'ct 1/3/2020 22:14'!
browseVariableAssignments

	^ self selectedInstVarName
		ifNotNil: [:instVar | self systemNavigation
			browseAllStoresInto: instVar 
			from: self object class]
		ifNil: [self systemNavigation browseVariableAssignments: self object class]! !

!Inspector methodsFor: 'menu - commands' stamp: 'ct 1/3/2020 22:14'!
browseVariableReferences

	^ self selectedInstVarName
		ifNotNil: [:instVar | self systemNavigation
			browseAllAccessesTo: instVar 
			from: self object class]
		ifNil: [self systemNavigation browseVariableReferences: self object class]! !

!Inspector methodsFor: 'menu - commands' stamp: 'ct 2/16/2020 14:40'!
chaseSelectionPointers

	| selected saved |
	self hasSelection ifFalse: [^ self changed: #flash].
	selected := self selectionOrObject.
	saved := self object.
	self object: nil.
	^ [(selected respondsTo: #chasePointers)
		flag: #ct "Do we indeed need to isolate Tools-Inspector and Tools-Debugger?";
		flag: #ct "ToolSet";
		ifTrue: [selected chasePointers]
		ifFalse: [selected inspectPointers]]
			ensure: [self object: saved]! !

!Inspector methodsFor: 'menu - commands' stamp: 'mt 3/25/2020 16:07'!
copyExpression
	"From the selected field, copy the code expression that returns the contents of the value pane into the clipboard."

	(self expressionForField: self selectedField)
		ifNil: [self error: 'Cannot determine field expression' translated]
		ifNotNil: [:fieldExpression | Clipboard clipboardText: fieldExpression].! !

!Inspector methodsFor: 'menu - commands' stamp: 'mt 3/25/2020 16:07'!
copyName
	"Copy the name of the selected field into clipboard."

	self selectedFieldName
		ifNil: [self error: 'Cannot determine field name.' translated]
		ifNotNil: [:name | Clipboard clipboardText: name].! !

!Inspector methodsFor: 'menu - commands' stamp: 'ct 9/14/2019 20:44'!
exploreSelection

	^ self selectionOrObject explore! !

!Inspector methodsFor: 'menu - commands' stamp: 'ct 1/3/2020 22:22'!
exploreSelectionPointers

	^ self selectionOrObject explorePointers! !

!Inspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 15:45'!
inspectOne
	"This is the most generic case to inspect a specific element from the inspected object. Since trunction of fields is a generic feature, support lookup for those truncated objects also for non-collections."

	self inspectOneOf: (
		self fields
			select: [:field | field key notNil]
			thenCollect: [:field | field key]).! !

!Inspector methodsFor: 'menu - commands' stamp: 'mt 4/15/2020 11:48'!
inspectOneOf: someKeys

	| elements labels choice |
	someKeys size = 0 ifTrue: [^ self inform: 'Nothing to inspect.' translated].
	someKeys size = 1 ifTrue: [^ (self elementAt: someKeys first) inspect].
	someKeys size > 50 ifTrue: [^ self inspectOneOfFrom: someKeys first to: someKeys last].
	
	elements := someKeys collect: [:key | [self elementAt: key] ifError: ['<???>']].
	labels := someKeys with: elements collect: [:key :element |
		'{1} -> {2}' format: {
			key printString.
			[element printString withoutLineEndings withBlanksCondensed truncateWithElipsisTo: 75]
				ifError: ['<???>']}].
	choice := Project uiManager chooseFrom: labels title: 'Inspect which field?'.
	choice = 0 ifTrue: [^ self].
	
	(elements at: choice) inspect.! !

!Inspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 15:42'!
inspectOneOfFrom: firstKey to: lastKey
	"Let the user specify the desired field's key in the form of a Smalltalk literal or otherwise simple code expression."

	| choiceString |
	choiceString := Project uiManager
		request: ('Enter the name of the field to inspect.\Names range from {1} to {2}.' translated withCRs
			format: {firstKey storeString. lastKey storeString})
		initialAnswer: firstKey storeString.
	choiceString isEmptyOrNil ifTrue: [^ self].

	(self elementAt: (Compiler evaluate: choiceString)) inspect.! !

!Inspector methodsFor: 'menu - commands' stamp: 'ct 12/10/2019 09:09'!
inspectSelection
	"Create and schedule an Inspector on the receiver's model's currently selected object."

	self hasSelection ifFalse: [^ self changed: #flash].
	^ self selectionOrObject inspect! !

!Inspector methodsFor: 'menu - commands' stamp: 'mt 4/1/2020 10:39'!
inspectSelectionBasic
	"Bring up an inspector that focuses on the very basics of an object."

	^ ToolSet basicInspect: self selectionOrObject! !

!Inspector methodsFor: 'menu - commands' stamp: 'ct 1/3/2020 22:30'!
objectReferencesToSelection
	"Open a list inspector on all the objects that point to the value of the selected object."

	^ self systemNavigation
		browseAllObjectReferencesTo: self selectionOrObject
		except: (Array with: self with: self object)
		ifNone: [:obj | self changed: #flash]! !

!Inspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 17:16'!
removeSelection
	"In general, we can always remove custom fields. Specialized inspectors can offer to remove other fields such as those representing collection elements."

	self selectedField ifNotNil: [:field |
		field isCustom ifTrue: [self removeCustomField: field]].! !

!Inspector methodsFor: 'updating - steps' stamp: 'mt 3/9/2020 11:36'!
modelWakeUpIn: aWindow
	
	self updateFields.! !

!Inspector methodsFor: 'updating - steps' stamp: 'mt 3/31/2020 11:04'!
stepAt: millisecondClockValue in: aWindow

	self updateFields.! !

!Inspector methodsFor: 'updating - steps' stamp: 'mt 4/21/2020 17:50'!
stepTimeIn: aWindow
	"Minimum step time is 1 second. If the fetching of contents takes more than 100 milliseconds, increase the step time accordingly to keep the system responsive."
	
	^ (selectionUpdateTime ifNil: [0]) * 10 max: 1000! !

!Inspector methodsFor: 'updating - steps' stamp: 'mt 3/9/2020 11:37'!
updateListsAndCodeIn: aWindow
	"Not needed. We have everything in place to update from here. See #updateFields. No need to update through views."! !

!Inspector methodsFor: 'updating - steps' stamp: 'mt 3/9/2020 11:38'!
wantsStepsIn: aWindow
	"Independent of #smartUpdating preference".
	
	^ true! !

!Inspector methodsFor: 'fields - error handling' stamp: 'mt 4/7/2020 16:40'!
contentsForErrorDoing: aBlock

	^ 'An error occurred while inspecting this object. {1} to debug the error.'
			translated asText format: {
				Text
					string: 'Click here' translated
					attributes: { TextEmphasis bold. PluggableTextAttribute evalBlock: aBlock }}! !

!Inspector methodsFor: 'fields - error handling' stamp: 'mt 3/31/2020 11:42'!
emphasizeError: errorMessage

	^ ('<{1}>' asText format: { errorMessage })
		addAttribute: self textColorForError;
		yourself! !

!Inspector methodsFor: 'fields - error handling' stamp: 'mt 3/31/2020 11:42'!
streamError: aMessageString on: aStream

	aStream nextPut: ((self newFieldForType: #error)
		name: (Text
			string: '<error>' translated
			attribute: self textColorForError);
		valueGetter: [:object | self emphasizeError: aMessageString];
		printValueAsIs;
		yourself)! !

!Inspector methodsFor: 'fields - error handling' stamp: 'mt 3/31/2020 11:29'!
streamErrorDoing: aBlock on: aStream

	self
		streamError: (self contentsForErrorDoing: aBlock)
		on: aStream.! !

!Inspector methodsFor: 'toolbuilder' stamp: 'mt 3/31/2020 10:57'!
buildCodePaneWith: builder
	"Overridden. Note that I do not hold #contents in my code pane. See my value pane for that."
	
	^ builder pluggableCodePaneSpec new
		model: self;
		getText: #expression; 
		editText: #expression:;
		help: 'Evaluate expressions on inspected object' translated;
		menu: #codePaneMenu:shifted:;
		askBeforeDiscardingEdits: false;
		yourself! !

!Inspector methodsFor: 'toolbuilder' stamp: 'mt 3/9/2020 08:59'!
buildExploreButtonWith: builder
	
	^ builder pluggableButtonSpec new
		model: self;
		label: 'explore' translated;
		action: #replaceInspectorWithExplorer;
		help: 'Switch to an explorer tool' translated;
		yourself! !

!Inspector methodsFor: 'toolbuilder' stamp: 'mt 4/2/2020 19:12'!
buildFieldListWith: builder

	^ builder pluggableListSpec new
		model: self;
		list: #fieldList;
		getIndex: #selectionIndex;
		setIndex: #selectionIndex:;
		autoDeselect: true;
		menu: #fieldListMenu:shifted:;
		dragItem: #dragFromFieldList:;
		dropItem: #dropOnFieldList:at:shouldCopy:;
		keyPress: #inspectorKey:from:;
		yourself! !

!Inspector methodsFor: 'toolbuilder' stamp: 'mt 3/31/2020 10:56'!
buildValuePaneWith: builder
	"The value pane holds this StringHolder's contents."

	^ builder pluggableCodePaneSpec new
		model: self;
		name: #valuePane;
		getText: #contents;
		setText: #contents:notifying:;
		editText: #typeValue:; "Turn on code styling as you type."
		help: 'Selected field''s value' translated;
		menu: #codePaneMenu:shifted:; "Share the menu with the code pane."
		yourself! !

!Inspector methodsFor: 'toolbuilder' stamp: 'mt 3/6/2020 09:21'!
buildWith: builder
	"Inspector openOn: SystemOrganization"
	
	| windowSpec buttonOffset |
	buttonOffset := (Preferences standardButtonFont widthOfString: 'explore') * 3/2.
	windowSpec := self buildWindowWith: builder specs: {
		(0 at 0 corner: 0.3 at 0.71)
			-> [self buildFieldListWith: builder].
		(0.3 at 0.0 corner: 1 at 0.71)
			-> [self buildValuePaneWith: builder].
		(LayoutFrame fractions: (0 at 0.71 corner: 1 at 1) offsets: (0 at 0 corner: buttonOffset negated at 0))
			-> [self buildCodePaneWith: builder].
		(LayoutFrame fractions: (1 at 0.71 corner: 1 at 1) offsets: (buttonOffset negated at 0 corner: 0 @ 0))
			-> [self buildExploreButtonWith: builder].
	}.
	^ builder build: windowSpec! !

!Inspector methodsFor: 'toolbuilder' stamp: 'mt 4/20/2020 16:21'!
replaceInspectorWithExplorer
	"Switch to an explorer tool. If there are custom fields, the user can choose to not discard them, which will just spawn a new explorer tool besides this inspector."
	
	| window currentBounds |
	self okToDiscardCustomFields
		ifFalse: [^ self object explore].
	
	self customFields removeAll.
	self changed: #acceptChanges. "We copy the current state anyway. See below."
	currentBounds := ToolBuilder default class getBoundsForWindow: self containingWindow.

	"Close first because MVC fiddles around with processes."
	self changed: #close. 
		
	window := ToolSet explore: self object.
	
	"---- In MVC, the lines after this will not be executed ---"

	window model setExpression: self expression.
	ToolBuilder default class setBoundsForWindow: window to: currentBounds.! !

!Inspector methodsFor: '*Protocols-Tools' stamp: 'ct 1/5/2020 22:01'!
browseFullProtocol
	"Open up a protocol-category browser on the value of the receiver's current selection.  If in mvc, an old-style protocol browser is opened instead."

	self flag: #ct "ToolSet?".
	Smalltalk isMorphic ifFalse: [^ self spawnProtocol].
	^ InstanceBrowser new openOnObject: self selectionOrObject showingSelector: nil! !

!Inspector methodsFor: '*Protocols-Tools' stamp: 'mt 4/1/2020 10:40'!
spawnFullProtocol
	"Spawn a window showing full protocol for the receiver's selection"

	^ ProtocolBrowser openFullProtocolForClass: self classOfSelection! !

!Inspector methodsFor: '*Protocols-Tools' stamp: 'mt 4/1/2020 10:40'!
spawnProtocol
	"Spawn a protocol on browser on the receiver's selection"

	^ ProtocolBrowser openSubProtocolForClass: self classOfSelection! !

!Inspector methodsFor: '*Etoys-menu commands' stamp: 'ct 1/4/2020 16:38'!
tearOffTile
	"Tear off a tile that refers to the receiver's selection, and place it in the mophic hand"

	self currentHand attachMorph: (TileMorph new referTo: self selectionOrObject)! !

!Inspector methodsFor: 'fields - drag and drop' stamp: 'mt 4/2/2020 18:41'!
dragFromFieldList: index

	^ (self fields at: index ifAbsent: [nil])
		ifNotNil: [:fieldToDrag | fieldToDrag rememberInspector]! !

!Inspector methodsFor: 'fields - drag and drop' stamp: 'mt 4/2/2020 18:41'!
dropOnFieldList: anObjectOrField at: index shouldCopy: shouldCopyField
	"Drop an object to change a field's value or drop a field to add it to the list of custom fields."
	
	(shouldCopyField and: [anObjectOrField isKindOf: self fieldClass])
		ifTrue: [
			self flag: #refactor. "mt: Instead of abusing #shouldCopy, write a separate hook for dropping fields between list items to insert fields."
			self addCustomField: anObjectOrField forgetInspector copy]
		ifFalse: [
			self selectionIndex: index.
			self replaceSelectionValue: anObjectOrField value].! !

!Inspector methodsFor: 'user interface - styling' stamp: 'mt 4/7/2020 14:11'!
aboutToStyle: aStyler requestor: anObject
	"We have two text fields in this tool: code pane and value pane. Do always style the code pane."
	
	self updateStyler: aStyler requestor: anObject.
	
	^ (anObject knownName = #valuePane)
		==> [shouldStyleValuePane == true
			"Fields can override styling so that contents are always styled."
			or: [self selectedField notNil ==> [self selectedField shouldStyleValue]]]! !

!Inspector methodsFor: 'user interface - styling' stamp: 'mt 3/9/2020 09:15'!
fieldListStyler
	"This is an extra styler to style the items in the field list. Note that both code and value pane use their own styler."
	
	^ fieldListStyler! !

!Inspector methodsFor: 'user interface - styling' stamp: 'mt 3/10/2020 08:44'!
typeValue: aTextOrString
	"Style field value contents only after the user typed."
	
	contentsTyped := aTextOrString.

	shouldStyleValuePane == true ifFalse: [
		shouldStyleValuePane := true.
		self changed: #style].! !

!Inspector methodsFor: 'user interface - styling' stamp: 'mt 4/7/2020 14:13'!
updateStyler: aStyler
	
	self updateStyler: aStyler requestor: self.! !

!Inspector methodsFor: 'user interface - styling' stamp: 'mt 4/7/2020 14:11'!
updateStyler: aStyler requestor: anObject
	"Use this method to update our fieldListStyler and all view stylers."
	
	aStyler
		environment: self environment;
		classOrMetaClass: self doItReceiver class;
		context: self doItContext;
		parseAMethod: false.! !

!Inspector methodsFor: '*60Deprecated-toolbuilder' stamp: 'mt 3/9/2020 08:59'!
exploreObject
	
	self deprecated.
	self replaceInspectorWithExplorer.! !

!Inspector methodsFor: 'user interface - window' stamp: 'mt 3/31/2020 10:30'!
labelString
	"See #windowTitle. All tools chose to implement #labelString."
	
	^ '{1}{2}' format: {
		self object defaultLabelForInspector.
		self object isReadOnlyObject
			ifTrue: [' (read-only)']
			ifFalse: ['']}! !

!Inspector methodsFor: 'user interface - window' stamp: 'mt 4/20/2020 16:15'!
okToClose

	^ super okToClose and: [self okToDiscardCustomFields]! !

!Inspector methodsFor: 'user interface - window' stamp: 'mt 4/20/2020 16:15'!
okToDiscardCustomFields

	^ self hasCustomFields ==> [self confirm: (String streamContents: [:s |
		s nextPutAll: 'All custom fields will be discarded:' translated.
		self customFields do: [:field | 
			s crtab; nextPutAll: field name] ])]! !

!Inspector methodsFor: 'user interface' stamp: 'mt 4/1/2020 11:32'!
applyUserInterfaceTheme

	super applyUserInterfaceTheme.

	self fieldListStyler ifNotNil: [:styler |
		styler reset.
		self updateFieldList].! !

!Inspector methodsFor: 'user interface' stamp: 'mt 3/26/2020 13:08'!
fieldList
	"Return a list of texts that identify the fields for the object under inspection so that the user can make an informed decision on what to inspect."
	
	^ self fieldListStyler
		ifNil: [self fields collect: [:field | field name]]
		ifNotNil: [:styler |
			self updateStyler: styler.
			self fields collect: [:field |
				field shouldStyleName
					ifTrue: [styler styledTextFor: field name asText]
					ifFalse: [field name]]]! !

!Inspector methodsFor: 'user interface' stamp: 'mt 3/11/2020 15:03'!
getContents
	
	| newContents |
	selectionUpdateTime := 0.

	self hasSelection ifFalse: [^ ''].
	
	selectionUpdateTime := [
		newContents := self selection in: [:object |
			self selectedField shouldPrintValueAsIs
				ifTrue: [object asStringOrText] "Show strings and texts without quoting and without ellipsis."
				ifFalse: [object printString]].
	] timeToRun.

	^ newContents! !

!Inspector methodsFor: 'user interface' stamp: 'ct 9/19/2019 02:12'!
representsSameBrowseeAs: anotherInspector

	^ self object == anotherInspector object! !

!Inspector methodsFor: 'user interface' stamp: 'mt 3/31/2020 11:11'!
textColorForError

	^ TextColor color: ((self userInterfaceTheme get: #errorColor for: #TestRunner) ifNil: [Color red])! !

!Inspector methodsFor: 'user interface' stamp: 'mt 3/11/2020 09:37'!
valuePane
	"Private. This is a workaround to interact with the value pane directly and not interfere with the code pane."

	^ self dependents
		detect: [:object | object knownName = #valuePane]
		ifNone: []! !

!Inspector methodsFor: 'selection - convenience' stamp: 'ct 1/4/2020 15:26'!
classOfSelection
	"Answer the class of the receiver's current selection"

	^ self selectionOrObject class! !

!Inspector methodsFor: 'selection - convenience' stamp: 'ct 1/5/2020 22:19'!
selectedClass

	^ self object class! !

!Inspector methodsFor: 'selection - convenience' stamp: 'mt 3/11/2020 16:25'!
selectedInstVarName

	^ self selectedField ifNotNil: [:field |
		field type = #instVar
			ifTrue: [field key]
			ifFalse: [nil]].! !

!Inspector methodsFor: 'selection - convenience' stamp: 'mt 3/9/2020 15:26'!
selectionIsReadOnly
	"Answer if the current selected variable is not modifiable via acceptance in the code pane.  For example, a selection of 'all inst vars' is unmodifiable."

	^ self selectedField
		ifNil: [true]
		ifNotNil: [:field | field isReadOnly]! !

!Inspector methodsFor: 'selection - convenience' stamp: 'mt 3/10/2020 17:15'!
selectionOrObject
	"My selection. If nothing useful is selected, return the inspected object instead."

	self hasSelection ifFalse: [^ self object].
	self typeOfSelection = #ellipsis ifTrue: [^ self object].

	^ self selection! !

!Inspector methodsFor: 'selection - convenience' stamp: 'mt 3/10/2020 08:07'!
typeOfSelection

	^ self selectedField ifNotNil: [:field | field type]! !

!Inspector methodsFor: 'selection' stamp: 'mt 3/25/2020 11:19'!
ensureSelectedField
	"If there is no field selected, try to select the first one."

	self hasSelection
		ifFalse: [self selectionIndex: 1].

	^ self selectedField! !

!Inspector methodsFor: 'selection' stamp: 'mt 3/11/2020 16:41'!
hasSelection
	"Use #selectedField instead of #selectionIndex to guard against invalid #selectionIndex. Can happen, for example, when adding elements to sets."
	
	^ self selectedField notNil! !

!Inspector methodsFor: 'selection' stamp: 'mt 3/11/2020 11:23'!
noteSelectionIndex: anInteger for: aSymbol
	
	self flag: #mvcOnly.
	aSymbol == #fieldList ifTrue:
		[selectionIndex := anInteger].! !

!Inspector methodsFor: 'selection' stamp: 'mt 4/6/2020 15:58'!
replaceSelectionValue: anObject 
	"Set the value of the selected field to anObject. We have to answer whether this replacement worked or not."
	
	| target |
	(target := self ensureSelectedField) ifNil: [^ false].
	
	target type = #self ifTrue: [
		^ (self confirm: 'This will exchange the inspected object.' translated)
			ifTrue: [self inspect: anObject. true]
			ifFalse: [false]].

	target isReadOnly ifTrue: [
		self inform: 'You cannot replace the selected field because\it is read-only. Try to add a field setter.' withCRs.
		^ false].

	self contentsTyped: nil. "Ensure to refresh the contents view."

	target
		setValueFor: self
		to: anObject.
		
	^ true! !

!Inspector methodsFor: 'selection' stamp: 'mt 3/9/2020 10:28'!
selectField: aField 

	self selectionIndex: (self fields indexOf: aField ifAbsent: [0])! !

!Inspector methodsFor: 'selection' stamp: 'mt 4/3/2020 15:50'!
selectFieldNamed: aString
	"Select the field that is labeled aFieldName, or nothing, is there is no match."

	self selectFieldSuchThat: [:field | field name = aString].! !

!Inspector methodsFor: 'selection' stamp: 'mt 4/3/2020 15:49'!
selectFieldSuchThat: aBlock
	"Select the first field for which aBlock evaluates to true."

	self selectionIndex: (self fields findFirst: aBlock).! !

!Inspector methodsFor: 'selection' stamp: 'ct 1/3/2020 21:56'!
selectedField

	^ self fields
		at: self selectionIndex
		ifAbsent: [nil]! !

!Inspector methodsFor: 'selection' stamp: 'mt 3/9/2020 10:27'!
selectedFieldName

	^ self selectedField ifNotNil: [:field | field name]! !

!Inspector methodsFor: 'selection' stamp: 'ct 2/15/2020 20:31'!
selection
	"Answer the value of the selected variable slot, that is an object."

	^ self selectedField getValueFor: self! !

!Inspector methodsFor: 'menu - construction' stamp: 'ct 3/17/2020 00:26'!
addClassItemsTo: aMenu

	aMenu addTranslatedList: #(
		-
		('browse full (b)'			browseClass)
		('browse hierarchy (h)'		browseClassHierarchy)
		('browse protocol (p)'		browseFullProtocol)).

	self typeOfSelection = #self ifFalse: [^ self].
	
	aMenu addTranslatedList: #(
		-
		('references... (r)'			browseVariableReferences)
		('assignments... (a)'		browseVariableAssignments)
		('class refs (N)'				browseClassRefs)).! !

!Inspector methodsFor: 'menu - construction' stamp: 'mt 4/15/2020 11:46'!
addCollectionItemsTo: aMenu

	aMenu
		add: 'inspect element...' translated
		target: self
		selector: #inspectOne.! !

!Inspector methodsFor: 'menu - construction' stamp: 'mt 3/11/2020 16:15'!
addEtoysItemsTo: aMenu

	aMenu addLine; addTranslatedList: {
		{ 'tile for this value (t)'.		[self selectionOrObject tearOffTile] }.
		{ 'viewer for this value (v)'. [self selectionOrObject beViewed] }}.! !

!Inspector methodsFor: 'menu - construction' stamp: 'mt 3/30/2020 14:19'!
addFieldItemsTo: aMenu

	aMenu addTranslatedList: #(
		-
		('copy name (c)'	copyName)
		('copy expression'	copyExpression		'Copy a code snippet that returns the field''s value when evaluated on the inspected object.')).! !

!Inspector methodsFor: 'menu - construction' stamp: 'mt 3/11/2020 16:13'!
addInstVarItemsTo: aMenu

	aMenu addTranslatedList: #(
		-
		('references (r)'			browseVariableReferences)
		('assignments (a)'		browseVariableAssignments)).! !

!Inspector methodsFor: 'menu - construction' stamp: 'mt 3/26/2020 15:09'!
addObjectItemsTo: aMenu
	"The following menu items trigger actions appropricate to all kinds of objects."

	self typeOfSelection = #ellipsis ifTrue: [^ self].

	aMenu addTranslatedList: {
		{'inspect (i)'.		#inspectSelection}.
		{'explore (I)'.		#exploreSelection}.
		{'basic inspect'.	#inspectSelectionBasic.
			'Inspect all instvars of the object, regardless of\any possible specialized Inspector for this type' withCRs}}.

	aMenu addTranslatedList: {
		#-.
		{'inspect pointers'.		#objectReferencesToSelection. 'objects pointing to this value'}.
		{'chase pointers'.		#chaseSelectionPointers}.
		{'explore pointers'.		#exploreSelectionPointers} }.! !

!Inspector methodsFor: 'menu' stamp: 'topa 3/16/2015 17:31'!
fieldListMenu: aMenu
	"Arm the supplied menu with items for the field-list of the receiver"
	^ self menu: aMenu for: #(fieldListMenu fieldListMenuShifted:)
! !

!Inspector methodsFor: 'menu' stamp: 'ct 1/18/2020 19:17'!
fieldListMenu: aMenu shifted: shifted
	"Arm the supplied menu with items for the field-list of the receiver"
	^ self
		menu: aMenu
		for: #(fieldListMenu fieldListMenuShifted:)
		shifted: shifted! !

!Inspector methodsFor: 'menu' stamp: 'mt 3/26/2020 14:13'!
inspectorKey: aChar from: view
	"Respond to a Command key issued while the cursor is over my field list"

	^ aChar
		caseOf: {
			[$x]	->	[self removeSelection].
			
			[$i]		->	[self inspectSelection].
			[$I]		->	[self exploreSelection].
			[$b]	->	[self browseClass].
			[$h]	->	[self browseClassHierarchy].
			[$p]	->	[self browseFullProtocol].
			[$r]		->	[self browseVariableReferences].
			[$a]	->	[self browseVariableAssignments].
			[$N]	->	[self browseClassRefs].
			[$c]	->	[self copyName].
			[$t]		->	[self tearOffTile].
			[$v]	->	[self viewerForValue] }
		otherwise:	[self arrowKey: aChar from: view]! !

!Inspector methodsFor: 'menu' stamp: 'mt 4/7/2020 19:05'!
mainFieldListMenu: aMenu
	"Arm the supplied menu with items for the field-list of the receiver"
	<fieldListMenu>
	aMenu addStayUpItemSpecial.
	
	self addObjectItemsTo: aMenu.
	
	(#(self ellipsis element nil) includes: self typeOfSelection)
		ifTrue: [self addCollectionItemsTo: aMenu].

	self typeOfSelection = #instVar
		ifTrue: [self addInstVarItemsTo: aMenu].

	self addFieldItemsTo: aMenu.
	self addClassItemsTo: aMenu.
	
	Smalltalk isMorphic ifTrue: [
		self flag: #refactor. "mt: Extract Etoys-specific extension."
		"ct: We could use the <fieldListMenu> pragma if it had a priority argument!!"
		self addEtoysItemsTo: aMenu].

	^ aMenu! !

!Inspector methodsFor: 'menu' stamp: 'ct 3/15/2020 20:14'!
metaFieldListMenu: aMenu
	<fieldListMenu"Shifted: true">
	self flag: #ct "we need keyboard support for shifted menus. Maybe add an item 'More...'?".

	aMenu addLine.
	aMenu addTranslatedList: #(
		('add field...'	#addCustomField)).
	self selectedField ifNotNil: [:field |
		field isCustom ifTrue: [
			field addCustomItemsFor: self to: aMenu]].
	^ aMenu! !

!Inspector methodsFor: 'updating' stamp: 'mt 3/9/2020 10:50'!
update
	"For convenience."

	self updateFields.! !

!Inspector methodsFor: 'updating' stamp: 'mt 4/1/2020 11:29'!
update: what

	what = #field ifTrue: [
		self updateFieldList.
		self updateContentsSafely].
	
	^ super update: what! !

!Inspector methodsFor: 'updating' stamp: 'mt 3/11/2020 16:49'!
update: what with: parameter

	what = #deleteField
		ifTrue: [self removeCustomField: parameter].
	
	^ super update: what with: parameter! !

!Inspector methodsFor: 'updating' stamp: 'mt 3/31/2020 11:42'!
updateContentsSafely
	"Force update contents of selected field. Do not style the contents anymore. Discard unaccepted changes in text fields."
	
	| workBlock |
	workBlock := [self getContents].
	self setContents: (workBlock
		ifError: [self emphasizeError: (self contentsForErrorDoing: workBlock)]).! !

!Inspector methodsFor: 'updating' stamp: 'mt 4/1/2020 11:57'!
updateFieldList

	self changed: #fieldList.
	self changed: #selectionIndex. "In case a field got renamed, tell the view that the selection did not change at all. The view would otherwise assume it is gone after updating the list and clear the selection. That's a little interference with the built-in list filtering mechanism in the view."! !

!Inspector methodsFor: 'updating' stamp: 'mt 4/1/2020 11:35'!
updateFields
	"Reset the collection of fields. Since amount and content my change, try to keep the current selection by field identity or field name."

	| field edits |
	field := self hasSelection ifTrue: [self selectedField]. "Save user selection"
	edits := self contentsTyped. "Save user edits"
	
	self resetFields.

	"Restore user selection"
	field ifNotNil: [
		(self fields identityIncludes: field)
			ifTrue: [self selectField: field]
			ifFalse: [self selectFieldNamed: field name]].

	"Restore user edits only if selection was restored."
	(edits notNil and: [self selectedField = field or: [self selectedFieldName = field name]])
		ifTrue: [self setContentsTyped: edits].
! !

!Inspector methodsFor: 'fields - truncation' stamp: 'mt 4/7/2020 16:40'!
contentsForTruncationOf: truncatedKeys

	^ ('<Fields named {1} to {2} are not shown. {3} to inspect one of those fields or select "inspect element" from any field''s menu.>' translated asText
		addAttribute: TextEmphasis italic;
		format: {
			truncatedKeys first storeString.
			truncatedKeys last storeString. 
			'Click here' translated asText
				addAttribute: (PluggableTextAttribute evalBlock: [self inspectOneOf: truncatedKeys]);
				yourself. })! !

!Inspector methodsFor: 'fields - truncation' stamp: 'mt 4/2/2020 11:46'!
streamOn: aStream truncate: aList collectFields: aBlock

	^ self
		streamOn: aStream
		truncate: aList
		collectFields: aBlock
		ellipsisFrom: [:truncatedObjects | (self newFieldForType: #ellipsis)
			name: '...';
			valueGetter: [:object | self contentsForTruncationOf: truncatedObjects];
			printValueAsIs;
			yourself]! !

!Inspector methodsFor: 'fields - truncation' stamp: 'mt 4/3/2020 16:06'!
streamOn: aStream truncate: someObjects collectFields: fieldBlock ellipsisFrom: ellipsisBlock
	"Create fields for someObjects using fieldBlock. Using the current #truncationLimit, create an extra ellipsis field to hide objects that go beyond this limit."

	(someObjects size <= self truncationLimit or: [self truncationLimit < 0])
		ifTrue: [^ aStream nextPutAll: (someObjects collect: [:each | fieldBlock value: each])].
		
	someObjects readStream in: [:readStream |
		aStream
			nextPutAll: ((readStream next: self truncationLimit - self truncationTail - 1)
				collect: [:each | fieldBlock value: each]);
			nextPut: (ellipsisBlock value: (readStream upToPosition: readStream size - self truncationTail));
			nextPutAll: (readStream upToEnd
				collect: [:each | fieldBlock value: each])].! !

!Inspector methodsFor: 'fields - truncation' stamp: 'mt 4/3/2020 16:07'!
truncationLimit
	"The maximum number of fields to show when truncating a list of objects. For example, collections can have a very big number of indexed variables and the inspecter would become slow without this limit. Keep the system responsive. Note that there is an extra ellipsis field for the truncated items so that users can manually select the (truncated) indexed variable to inspect.
	
	Choose a limit < 0 to not truncate any fields."

	^ 100! !

!Inspector methodsFor: 'fields - truncation' stamp: 'mt 3/11/2020 13:52'!
truncationTail
	"The number of fields to show at the end of a truncated field run."

	^ 10! !

!Inspector methodsFor: 'fields - streaming' stamp: 'ct 1/5/2020 22:53'!
streamBaseFieldsOn: aStream

	aStream
		nextPut: self fieldSelf;
		nextPut: self fieldAllInstVars.! !

!Inspector methodsFor: 'fields - streaming' stamp: 'mt 3/11/2020 11:28'!
streamCustomFieldsOn: aStream

	aStream nextPutAll: self customFields.! !

!Inspector methodsFor: 'fields - streaming' stamp: 'mt 3/10/2020 17:53'!
streamFieldsOn: aStream

	self
		streamBaseFieldsOn: aStream;
		streamVariableFieldsOn: aStream;
		streamCustomFieldsOn: aStream.! !

!Inspector methodsFor: 'fields - streaming' stamp: 'mt 3/26/2020 14:02'!
streamIndexedVariablesOn: aStream
	"Truncate indexed variables if there are too many of them."
	
	self
		streamOn: aStream
		truncate: (1 to: self object basicSize)
		collectFields: [:index |
			(self newFieldForType: #indexed key: index)
				valueGetter: [:object | object basicAt: index];
				valueSetter: [:object :value | object basicAt: index put: value];
				yourself]! !

!Inspector methodsFor: 'fields - streaming' stamp: 'mt 3/10/2020 17:46'!
streamInstanceVariablesOn: aStream

	self object class allInstVarNames doWithIndex: [:name :index |		
		aStream nextPut: ((self newFieldForType: #instVar key: name)
			shouldStyleName: true;
			valueGetter: [:object | object instVarNamed: name];
			valueSetter: [:object :value | object instVarNamed: name put: value];
			yourself)].! !

!Inspector methodsFor: 'fields - streaming' stamp: 'mt 3/10/2020 17:53'!
streamVariableFieldsOn: aStream

	self
		streamInstanceVariablesOn: aStream;
		streamIndexedVariablesOn: aStream.! !

!Inspector methodsFor: '*60Deprecated-menu' stamp: 'ct 3/17/2020 00:26'!
classHierarchy

	self deprecated.
	^ self browseClassHierarchy! !

!Inspector methodsFor: 'fields' stamp: 'mt 4/6/2020 18:25'!
expressionForField: anInspectorField
	"Subclasses can override this to configure the way to retrieve the source-code expression for the field."

	^ anInspectorField valueGetterExpression! !

!Inspector methodsFor: 'fields' stamp: 'mt 3/11/2020 16:17'!
fieldAllInstVars

	^ (self newFieldForType: #all key: #allInstVars)
		name: 'all inst vars' translated; emphasizeName;
		valueGetter: [:object | object longPrintString]; printValueAsIs;
		yourself! !

!Inspector methodsFor: 'fields' stamp: 'mt 4/20/2020 09:45'!
fieldSelf

	^ (self newFieldForType: #self key: #self)
		shouldStyleName: true;
		valueGetter: [:object | object];
		valueSetter: [:object :value | self object: value]; "Switch to another object-under-inspection."
		yourself! !

!Inspector methodsFor: 'fields' stamp: 'mt 3/11/2020 11:09'!
newFieldForType: aSymbol

	^ self fieldClass type: aSymbol! !

!Inspector methodsFor: 'fields' stamp: 'mt 3/11/2020 11:09'!
newFieldForType: aSymbol key: anObject

	^ self fieldClass type: aSymbol key: anObject! !

!Inspector methodsFor: 'fields - custom' stamp: 'mt 4/21/2020 18:13'!
addCustomField

	^ self addCustomField: (self requestCustomFieldOrCancel: [^ self])! !

!Inspector methodsFor: 'fields - custom' stamp: 'mt 4/2/2020 19:07'!
addCustomField: aField

	aField type: #custom.
	self customFields add: aField.
	self updateFields.
	self selectField: aField.! !

!Inspector methodsFor: 'fields - custom' stamp: 'mt 3/11/2020 11:20'!
hasCustomFields

	^ self customFields notEmpty! !

!Inspector methodsFor: 'fields - custom' stamp: 'mt 4/6/2020 18:26'!
newCustomField

	^ (self newFieldForType: #custom)
		valueGetterExpression: 'self yourself';
		yourself! !

!Inspector methodsFor: 'fields - custom' stamp: 'ct 3/15/2020 20:15'!
removeCustomField: aField

	aField isCustom
		ifFalse: [^ self changed: #flash].
	(self customFields includes: aField)
		ifFalse: [^ self changed: #flash].

	(self confirm: ('Do you really want to remove the field ''{1}''?' translated format: {aField name}))
		ifFalse: [^ self].

	self customFields remove: aField.
	self updateFields.! !

!Inspector methodsFor: 'fields - custom' stamp: 'mt 3/11/2020 11:10'!
requestCustomFieldOrCancel: aBlock

	^ self newCustomField
		requestCustomFor: self
		orCancel: aBlock! !


!BasicInspector methodsFor: 'initialization' stamp: 'mt 3/26/2020 14:59'!
basicObjectPrintString

	^ 'a {1}({2})' format: {thisContext objectClass: object. object identityHash}! !

!BasicInspector methodsFor: 'initialization' stamp: 'ct 1/6/2020 01:16'!
inspect: anObject 
	"We don't want to change the inspector class. Only set anObject as the inspectee."
	self object: anObject! !

!BasicInspector methodsFor: 'initialization' stamp: 'mt 3/31/2020 10:44'!
labelString

	^ '{1} {2}{3}' format: {
		'[basic]'.
		self basicObjectPrintString.
		(self object isReadOnlyObject
			ifTrue: [' (read-only)']
			ifFalse: [''])}! !

!BasicInspector methodsFor: 'fields' stamp: 'mt 4/20/2020 09:51'!
fieldObjectClass

	^ (self newFieldForType: #proto key: #class)
		name: 'class'; emphasizeName;
		valueGetter: [:object | thisContext objectClass: object];
		valueGetterExpression: 'thisContext objectClass: self';
		yourself! !

!BasicInspector methodsFor: 'fields' stamp: 'mt 4/20/2020 09:51'!
fieldObjectSize

	^ (self newFieldForType: #proto key: #size)
		name: 'size'; emphasizeName;
		valueGetter: [:object | thisContext objectSize: object];
		valueGetterExpression: 'thisContext objectSize: self';
		yourself! !

!BasicInspector methodsFor: 'fields' stamp: 'mt 4/20/2020 09:53'!
fieldSelf

	^ (self newFieldForType: #self key: #self)
		name: 'self'; emphasizeName;
		valueGetter: [:object | self basicObjectPrintString]; printValueAsIs;
		valueGetterExpression: 'self';
		valueSetter: [:object :value | self object: value];  "Switch to another object-under-inspection."
		yourself! !

!BasicInspector methodsFor: 'fields - streaming' stamp: 'mt 3/26/2020 15:14'!
streamBaseFieldsOn: aStream

	aStream
		nextPut: self fieldSelf;
		nextPut: self fieldObjectClass;
		nextPut: self fieldObjectSize.! !

!BasicInspector methodsFor: 'fields - streaming' stamp: 'mt 4/20/2020 09:50'!
streamIndexedVariablesOn: aStream
	"Truncate indexed variables if there are too many of them."
	
	self
		streamOn: aStream
		truncate: (1 to: (thisContext objectSize: self object))
		collectFields: [:index |
			(self newFieldForType: #indexed key: index)
				name: index asString;
				valueGetter: [:object | thisContext object: object basicAt: index];
				valueGetterExpression: ('thisContext object: {1} basicAt: {2}' format: { 'self'. index }); 
				valueSetter: [:object :value | thisContext object: object basicAt: index put: value];
				yourself]! !

!BasicInspector methodsFor: 'fields - streaming' stamp: 'mt 4/20/2020 09:52'!
streamInstanceVariablesOn: aStream

	(thisContext objectClass: self object) allInstVarNames doWithIndex: [:name :index |		
		aStream nextPut: ((self newFieldForType: #instVar key: name)
			name: name asString;
			shouldStyleName: true;
			valueGetter: [:object | thisContext object: object instVarAt: index];
			valueGetterExpression: ('thisContext object: {1} instVarAt: {2}' format: { 'self'. index }); 
			valueSetter: [:object :value | thisContext object: object instVarAt: index put: value];
			yourself)].! !


!ClassInspector methodsFor: 'fields - streaming' stamp: 'mt 3/11/2020 15:26'!
streamClassVariablesOn: aStream
	
	self object classVarNames do: [:name |
		aStream nextPut: ((self newFieldForType: #classVar key: name)
			shouldStyleName: true;
			valueGetter: [:object | object classPool at: name];
			valueSetter: [:object :value | object classPool at: name put: value];
			yourself)]! !

!ClassInspector methodsFor: 'fields - streaming' stamp: 'mt 3/11/2020 15:26'!
streamSharedPoolsOn: aStream

	self object sharedPools doWithIndex: [:pool :index |
		aStream nextPut: ((self newFieldForType: #poolDictionary key: (self environment keyAtIdentityValue: pool))
			shouldStyleName: true;
			valueGetter: [:object | object sharedPools at: index];
			valueSetter: [:object :value | object sharedPools at: index put: value];
			yourself)].! !

!ClassInspector methodsFor: 'fields - streaming' stamp: 'mt 3/11/2020 15:27'!
streamVariableFieldsOn: aStream
	"Add fields for class variables and pool dictionaries."
	
	super streamVariableFieldsOn: aStream.
	self
		streamClassVariablesOn: aStream;
		streamSharedPoolsOn: aStream.! !


!CollectionInspector methodsFor: 'menu - construction' stamp: 'mt 4/6/2020 09:56'!
addCollectionItemsTo: aMenu

	aMenu addLine.
	super addCollectionItemsTo: aMenu.
	
	self object isReadOnlyObject ifTrue: [^ self].
	aMenu addTranslatedList: #(
		('refresh list view'			updateFields) "--- useful in non-stepping debugger").
	
	self canAddOrRemoveElements ifFalse: [^ self].
	aMenu addTranslatedList: #(
		-
		('add element...'		addElement)).
					
	self typeOfSelection = #element ifFalse: [^ self].
	aMenu addTranslatedList: #(
		('remove element (x)'	removeSelection)).! !

!CollectionInspector methodsFor: 'menu' stamp: 'ct 1/11/2020 23:23'!
inspectorKey: aChar from: view

	^ aChar = $x
		ifTrue: [self removeSelection]
		ifFalse: [super inspectorKey: aChar from: view].! !

!CollectionInspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 17:20'!
addElement

	self addElement: (
		self
			requestObject: 'Enter expression for new object' translated
			orCancel: [^ self]).! !

!CollectionInspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 10:01'!
addElement: anObject

	self object add: anObject.

	self updateFields.
	self selectFieldSuchThat: [:field | [(field getValueFor: self) == anObject] ifError: [false]].
	self hasSelection ifFalse: [self inform: ('The new element {1} was added.\\Yet, the list of fields is quite long. The new field\got truncated and is thus not visible.' translated withCRs format: {anObject printString})].! !

!CollectionInspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 14:59'!
inspectOne
	"Only list the collection's elements. Ignore any other fields."
	
	self inspectOneOf: self elementIndices.! !

!CollectionInspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 18:06'!
removeSelectedElement
	
	self object remove: self selection.! !

!CollectionInspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 08:33'!
removeSelection
	"Keep the selection stable to support subsequent removals. Be robust against collections that do not allow elements to be removed such as arrays."
	
	| priorSelectionIndex |
	super removeSelection.
	
	self assertElementSelectedOr: [^ self changed: #flash].
	priorSelectionIndex := self selectionIndex.
	
	[self removeSelectedElement]
		ifError: [^ self changed: #flash].
		
	self updateFields.
	self selectionIndex: (priorSelectionIndex min: self fields size).! !

!CollectionInspector methodsFor: 'private' stamp: 'mt 4/6/2020 08:33'!
assertElementSelectedOr: aBlock

	^ self typeOfSelection = #element
		or: [aBlock cull: self selectedField]! !

!CollectionInspector methodsFor: 'private' stamp: 'mt 4/6/2020 09:54'!
canAddOrRemoveElements
	"For simplicity, treat those properties together. There are no collections that support addition but deny removal of elements."
	
	^ #(add: remove:ifAbsent:) noneSatisfy: [:selector |
		(self object class lookupSelector: selector) hasLiteral: #shouldNotImplement]! !

!CollectionInspector methodsFor: 'private' stamp: 'mt 4/2/2020 16:02'!
elementGetterAt: index

	^ [:collection | collection at: index] ! !

!CollectionInspector methodsFor: 'private' stamp: 'mt 4/6/2020 08:32'!
elementIndices

	^ 1 to: self objectSize! !

!CollectionInspector methodsFor: 'private' stamp: 'mt 4/2/2020 16:03'!
elementSetterAt: index

	^ [:collection :element | collection at: index put: element] ! !

!CollectionInspector methodsFor: 'private' stamp: 'mt 3/11/2020 15:09'!
objectSize
	"For robustness. Partially initialized collections may fail to report their size. Useful for the debugger's inspectors."

	^ [self object size] ifError: [0]! !

!CollectionInspector methodsFor: 'ui requests' stamp: 'ct 1/18/2020 19:28'!
requestObject: aMessageString initialAnswer: anAnswerString orCancel: aBlock

	| input |
	input := Project uiManager
		request: aMessageString
		initialAnswer: anAnswerString.
	input isEmptyOrNil ifTrue: [^ aBlock value].
	^ Compiler evaluate: input for: self object! !

!CollectionInspector methodsFor: 'ui requests' stamp: 'ct 1/11/2020 14:57'!
requestObject: aMessageString orCancel: aBlock

	^ self
		requestObject: aMessageString
		initialAnswer: String empty
		orCancel: aBlock! !

!CollectionInspector methodsFor: 'fields - streaming' stamp: 'mt 4/6/2020 08:32'!
streamElementsOn: aStream
	"Create a field for each element in the collection. Use the index' #printString (and not #asString) to reveal the nature of the key, which are usually integers (1, 2, 3, ...), but can be symbols (#apple, #tree, ...) or other objects (aMorph, aSocket, ...) in dictionary-like collections. Maybe #storeString would be even better but can be very expensive to compute."

	self
		streamOn: aStream
		truncate: self elementIndices
		collectFields: [:index |
			(self newFieldForType: #element key: index)
				name: index printString;
				valueGetter: (self elementGetterAt: index);
				valueSetter: (self elementSetterAt: index);
				yourself]! !

!CollectionInspector methodsFor: 'fields - streaming' stamp: 'mt 4/3/2020 15:57'!
streamIndexedVariablesOn: aStream
	"Override to rename 'index variables' to the collection's 'elements'."
	
	self streamElementsOn: aStream.! !

!CollectionInspector methodsFor: 'selection' stamp: 'mt 4/3/2020 16:10'!
selectElementAt: index

	self selectFieldSuchThat: [:field | field type = #element and: [field key = index]].! !

!CollectionInspector methodsFor: 'selection' stamp: 'mt 4/6/2020 08:34'!
selectedElementIndex

	self assertElementSelectedOr: [^ nil].
	^ self selectedField key! !


!BitsetInspector methodsFor: 'fields' stamp: 'mt 4/2/2020 10:52'!
fieldSize

	^ (self newFieldForType: #misc key: #size)
		name: 'num 1 bits' translated; emphasizeName;
		valueGetter: [:bitset | bitset size];
		yourself! !

!BitsetInspector methodsFor: 'private' stamp: 'mt 4/6/2020 08:32'!
elementIndices

	^ 0 to: self objectSize - 1! !

!BitsetInspector methodsFor: 'private' stamp: 'mt 4/2/2020 10:43'!
objectSize

	^ self object capacity! !

!BitsetInspector methodsFor: 'fields - streaming' stamp: 'mt 4/2/2020 10:52'!
streamBaseFieldsOn: aStream

	super streamBaseFieldsOn: aStream.
	aStream nextPut: self fieldSize.! !

!BitsetInspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 18:10'!
addElement: anInteger
	"Flip the specified bit to 1 and select it. Note that there is no need to #updateFields here because of the bitset's semantics for #add:."

	self object add: anInteger.
	self selectElementAt: anInteger.! !

!BitsetInspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 18:08'!
removeSelectedElement
	"Flip the selected bit back to 0."

	self selectedField setValueFor: self to: 0.! !


!CompiledCodeInspector methodsFor: 'fields - streaming' stamp: 'mt 4/7/2020 14:09'!
streamBaseFieldsOn: aStream
	"Instead of 'all inst vars' show all byte codes and header summary."
	
	aStream
		nextPut: self fieldSelf;
		nextPut: self fieldSource;
		nextPut: self fieldDecompile;
		nextPut: self fieldByteCodes;
		nextPut: self fieldHeader.! !

!CompiledCodeInspector methodsFor: 'fields - streaming' stamp: 'mt 4/6/2020 08:29'!
streamByteCodesOn: aStream

	self
		streamOn: aStream
		truncate: (self object initialPC to: self object size)
		collectFields: [:pc |
			(self newFieldForType: #bytecode key: pc)
				valueGetter: [:compiledCode | compiledCode at: pc];
				flag: #dangerous; "mt: We might want to disallow inadvertent changes here..."
				valueSetter: [:compiledCode :bytecode | compiledCode at: pc put: bytecode; voidCogVMState];
				yourself]! !

!CompiledCodeInspector methodsFor: 'fields - streaming' stamp: 'mt 3/11/2020 13:43'!
streamIndexedVariablesOn: aStream
	"Separate all indexed variables in literals and byte codes."
	
	self
		streamLiteralsOn: aStream;
		streamByteCodesOn: aStream.! !

!CompiledCodeInspector methodsFor: 'fields - streaming' stamp: 'mt 4/6/2020 08:29'!
streamLiteralsOn: aStream

	self flag: #decompile. "mt: Use #to: and #do: instead of #to:do: to avoid inlining to preserve bindings in enumeration block for later decompilation. See InspectorField."
	(1 to: self object numLiterals) do: [:index |
		aStream nextPut: ((self newFieldForType: #literal key: index)
			name: 'literal' , index;
			valueGetter: [:compiledCode | compiledCode literalAt: index];
			flag: #dangerous; "mt: We might want to disallow inadvertent changes here..."
			valueSetter: [:compiledCode :literal | compiledCode literalAt: index put: literal; voidCogVMState];
			yourself)].! !

!CompiledCodeInspector methodsFor: 'fields' stamp: 'mt 3/11/2020 16:17'!
fieldByteCodes

	^ (self newFieldForType: #all key: #byteCodes)
		name: 'all bytecodes' translated; emphasizeName;
		valueGetter: [:object | object symbolic]; printValueAsIs;
		yourself! !

!CompiledCodeInspector methodsFor: 'fields' stamp: 'mt 4/7/2020 14:47'!
fieldDecompile

	^ (self newFieldForType: #code key: #decompile)
		name: 'decompiled' translated; emphasizeName;
		valueGetter: [:compiledCode | compiledCode decompile decompileString]; printValueAsIs;
		yourself! !

!CompiledCodeInspector methodsFor: 'fields' stamp: 'mt 3/26/2020 13:32'!
fieldHeader

	^ (self newFieldForType: #misc key: #header)
		name: 'header' translated; emphasizeName;
		valueGetter: [:object | object headerDescription]; printValueAsIs;
		yourself! !

!CompiledCodeInspector methodsFor: 'fields' stamp: 'mt 4/7/2020 14:21'!
fieldSource

	^ (self newFieldForType: #code key: #source)
		name: 'source code' translated; emphasizeName;
		valueGetter: [:compiledCode | '"{1}"\{2}' withCRs format: {compiledCode methodClass. compiledCode getSource}]; printValueAsIs;
		shouldStyleValue: true;
		yourself! !

!CompiledCodeInspector methodsFor: 'user interface - styling' stamp: 'mt 4/7/2020 14:18'!
updateStyler: aStyler requestor: anObject
	"Overridden to configure the styler to parse method source code correctly."
	
	| parseAMethod classOrMetaClass |
	self selectedField
		ifNil: [super updateStyler: aStyler requestor: anObject]
		ifNotNil: [:field |
			(anObject knownName = #valuePane and: [field type = #code])
				ifTrue: [parseAMethod := true. classOrMetaClass := self object methodClass]
				ifFalse: [parseAMethod := false. classOrMetaClass := self doItReceiver class].
			
			aStyler
				environment: self environment;
				classOrMetaClass: classOrMetaClass;
				context: self doItContext;
				parseAMethod: parseAMethod].
	
! !


!ContextInspector methodsFor: 'fields - streaming' stamp: 'ct 3/14/2020 20:18'!
streamFieldsOn: aStream

	self object ifNil: [
		^ self streamError: 'Cannot inspect a nil context' translated on: aStream].
	self object method ifNil: [
		^ self streamError: 'Cannot inspect a context with nil method' translated on: aStream].
	
	super streamFieldsOn: aStream.! !

!ContextInspector methodsFor: 'fields - streaming' stamp: 'ct 3/16/2020 08:50'!
streamIndexedVariablesOn: aStream
	"Just show (indexed) stack variables to the list."
	
	self streamStackVariablesOn: aStream.! !

!ContextInspector methodsFor: 'fields - streaming' stamp: 'mt 3/11/2020 17:22'!
streamInstanceVariablesOn: aStream
	"Add (named) temporary variables to the list."

	super streamInstanceVariablesOn: aStream.
	self streamTemporaryVariablesOn: aStream.! !

!ContextInspector methodsFor: 'fields - streaming' stamp: 'mt 3/26/2020 13:26'!
streamStackVariablesOn: aStream
	"If this context's stack pointer is not valid, silently skip streaming fields for stack variables. Do not stream an error field because freshly created or terminated contexts can be like this."

	self object stackPtr ifNil: [^ self].

	self flag: #decompile. "mt: Use #to: and #do: instead of #to:do: to avoid inlining to preserve bindings in enumeration block for later decompilation. See InspectorField."
	(self object numTemps + 1 to: self object stackPtr) do: [:index |
		aStream nextPut: ((self newFieldForType: #stackItem key: index)
			name: 'stack', index; deEmphasizeName;
			valueGetter: [:object | object at: index];
			valueSetter: [:object :value | object at: index put: value];
			yourself)]! !

!ContextInspector methodsFor: 'fields - streaming' stamp: 'mt 4/15/2020 10:19'!
streamTemporaryVariablesOn: aStream

	| tempNames |
	tempNames := [self object tempNames] ifError: [
		^ self streamError: 'Invalid temporaries' translated on: aStream].
	
	tempNames doWithIndex: [:name :index |
		aStream nextPut: ((self newFieldForType: #tempVar key: name)
			name: ('[{1}]' format: {name});
			valueGetter: [:context | context namedTempAt: index];
			valueSetter: [:context :value | context namedTempAt: index put: value];
			yourself)]! !


!ContextVariablesInspector methodsFor: 'fields - streaming' stamp: 'mt 3/11/2020 17:14'!
streamBaseFieldsOn: aStream

	self object ifNil: [^ self].
	aStream
		nextPut: self fieldSelf;
		nextPut: self fieldStackTop;
		nextPut: self fieldAllTempVars.! !

!ContextVariablesInspector methodsFor: 'fields - streaming' stamp: 'mt 4/15/2020 10:14'!
streamIndexedVariablesOn: aStream

	self class showStackVariables ifTrue: [
		self streamStackVariablesOn: aStream].! !

!ContextVariablesInspector methodsFor: 'fields - streaming' stamp: 'mt 3/25/2020 16:45'!
streamInstanceVariablesOn: aStream
	"Just show the (named) temporary variables to the list. Hide internals. The receiver is in the debugger's companion inspector."

	self streamTemporaryVariablesOn: aStream.! !

!ContextVariablesInspector methodsFor: 'fields - streaming' stamp: 'mt 4/15/2020 10:19'!
streamTemporaryVariablesOn: aStream
	"Overwritten to change the visuals of temps in debuggers."
	
	| tempNames |
	tempNames := [self object tempNames] ifError: [
		^ self streamError: 'Invalid temporaries' translated on: aStream].
	
	tempNames doWithIndex: [:name :index |
		aStream nextPut: ((self newFieldForType: #tempVar key: name)
			shouldStyleName: true;
			valueGetter: [:context | context namedTempAt: index];
			valueSetter: [:context :value | context namedTempAt: index put: value];
			yourself)].! !

!ContextVariablesInspector methodsFor: 'fields' stamp: 'mt 3/11/2020 17:02'!
fieldAllTempVars

	^ (self newFieldForType: #all key: #allTempVars)
		name: 'all temp vars' translated; emphasizeName;
		valueGetter: [:object | object tempsAndValues]; printValueAsIs;
		yourself! !

!ContextVariablesInspector methodsFor: 'fields' stamp: 'mt 3/9/2020 15:16'!
fieldSelf

	^ super fieldSelf
		name: 'thisContext';
		yourself! !

!ContextVariablesInspector methodsFor: 'fields' stamp: 'mt 4/15/2020 10:21'!
fieldStackTop
	"Note that #valueGetter returns the actual printString to not confuse an empty stack top with nil or an empty string. So the value pane will just stay empty if there is no stack top and it will show 'nil' or '''' otherwise."
	
	^ (self newFieldForType: #stackTop key: #stackTop)
		name: 'stack top' translated; emphasizeName;
		valueGetter: [:context | context actualStackSize > 0 ifTrue: [context top printString] ifFalse: ['']];
		printValueAsIs;
		valueGetterExpression: 'ThisContext top';
		yourself! !

!ContextVariablesInspector methodsFor: 'private' stamp: 'mt 3/25/2020 16:18'!
expressionForField: anInspectorField
	"Use #ThisContext instead of #self. Note the capital 'T' to not refer to the special keyword #thisContext, which would return the current execution context but not the one we are currently inspecting."
	
	^ anInspectorField expressionWithReceiverName: #ThisContext! !


!DictionaryInspector methodsFor: 'menu - construction' stamp: 'mt 4/3/2020 18:14'!
addFieldItemsTo: aMenu

	super addFieldItemsTo: aMenu.

	self typeOfSelection = #element ifFalse: [^ self].
	
	aMenu addLine.
	
	self selectedKey isSymbol ifTrue: [
		aMenu addTranslatedList: #(
			('senders of this key'		sendersOfSelectedKey))].
	
	aMenu addTranslatedList: #(
			('inspect key'				inspectKey)
			('rename key'				renameKey)).
							
	self isBindingSelected ifTrue: [
		aMenu addTranslatedList: #(
			-
			('references to binding'		usersOfSelectedBinding		'Browse all users of this binding.'))].! !

!DictionaryInspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 17:06'!
addElement

	self addElement: (self requestKeyOrCancel: [^ self]).! !

!DictionaryInspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 17:05'!
addElement: aKey

	self object at: aKey put: nil.
	self updateFields.
	
	self selectKey: aKey.
	self hasSelection ifFalse: [self inform: ('The new key {1} was added.\\Yet, the list of fields is quite long. The new field\got truncated and is thus not visible.' translated withCRs format: {aKey printString})].! !

!DictionaryInspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 08:34'!
inspectKey
	"Create and schedule an Inspector on the receiver's model's currently selected key."

	self assertElementSelectedOr: [^ self].
	self selectedKey inspect.! !

!DictionaryInspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 18:06'!
removeSelectedElement

	self object removeKey: self selectedKey.! !

!DictionaryInspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 08:34'!
renameKey

	self assertElementSelectedOr: [^ self changed: #flash].
	self renameKey: (
		self
			requestKeyInitialAnswer: self selectedKey storeString
			orCancel: [^ self]).! !

!DictionaryInspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 08:34'!
renameKey: aKey

	self assertElementSelectedOr: [^ self changed: #flash].

	(self object includesKey: aKey)
		ifTrue: [(self confirm: 'The target key exists. Do you want to replace it?' translated)
			ifFalse: [^ self]].

	self object
		at: aKey put: self selection;
		removeKey: self selectedKey.
	self updateFields.
	
	self selectKey: aKey.
	self hasSelection ifFalse: [self inform: ('The selected key was renamed to {1}.\\Yet, the list of fields is quite long. The new field\got truncated and is thus not visible.' translated withCRs format: {aKey printString})].! !

!DictionaryInspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 16:55'!
sendersOfSelectedKey
	"Create a browser on all senders of the selected key"

	| aKey |
	((aKey := self selectedKey) isSymbol)
		ifFalse: [^ self changed: #flash].
	self systemNavigation browseAllCallsOn: aKey! !

!DictionaryInspector methodsFor: 'menu - commands' stamp: 'mt 4/3/2020 16:53'!
usersOfSelectedBinding
	"Create a browser on all references to the association of the current selection."

	self selectedBinding ifNotNil: [:binding |
		self systemNavigation browseAllCallsOn: binding].! !

!DictionaryInspector methodsFor: 'bindings' stamp: 'mt 4/3/2020 16:51'!
isBindingSelected
	"Whether the currently selection association is a binding to a class or global."
	
	^ self selectedKey ifNil: [false] ifNotNil: [:key |
		(self object associationAt: key) isKindOf: Binding]! !

!DictionaryInspector methodsFor: 'bindings' stamp: 'mt 4/3/2020 16:51'!
selectedBinding
	
	^ self selectedKey
		ifNotNil: [:key | self object associationAt: key]! !

!DictionaryInspector methodsFor: 'ui requests' stamp: 'mt 4/6/2020 08:36'!
requestKeyInitialAnswer: anAnswerString orCancel: aBlock

	^ self
		requestObject: ('Enter an expression for the new key\such as #tree, ''apple'', and 3+4.' translated withCRs)
		initialAnswer: anAnswerString
		orCancel: aBlock! !

!DictionaryInspector methodsFor: 'ui requests' stamp: 'ct 1/11/2020 14:56'!
requestKeyOrCancel: aBlock

	^ self
		requestKeyInitialAnswer: String empty
		orCancel: aBlock! !

!DictionaryInspector methodsFor: 'selection' stamp: 'mt 4/3/2020 16:11'!
selectKey: aKey
	"Overriden to make clear that a dictionary's indices are called 'keys'."
	
	self selectElementAt: aKey.! !

!DictionaryInspector methodsFor: 'selection' stamp: 'mt 4/3/2020 16:11'!
selectedKey
	"Overriden to make clear that a dictionary's indices are called 'keys'."

	^ self selectedElementIndex! !

!DictionaryInspector methodsFor: '*60Deprecated-menu commands' stamp: 'mt 4/3/2020 16:36'!
refreshView

	self deprecated: 'Use #update instead.'.
	^ self update! !

!DictionaryInspector methodsFor: '*60Deprecated-menu commands' stamp: 'mt 4/3/2020 16:54'!
selectionReferences

	self deprecated: 'Use #usersOfSelectedBinding.'.
	self usersOfSelectedBinding.! !

!DictionaryInspector methodsFor: 'private' stamp: 'mt 4/14/2020 17:27'!
canAddOrRemoveElements
	"Due to a strange reason, #add: is supported in Dictionary but #remove:ifAbsent: is not."

	^ true! !

!DictionaryInspector methodsFor: 'private' stamp: 'mt 4/6/2020 08:32'!
elementIndices

	^ [ self object keysInOrder ] ifError: [
		"Can occur when debugging Dictionary new"
		Array empty]! !


!BagInspector methodsFor: 'private' stamp: 'mt 4/2/2020 16:06'!
elementGetterAt: element
	"Return a way to access the number of occurrences in the bag for the given element."
	
	^ [:bag | (bag instVarNamed: #contents) at: element]! !

!BagInspector methodsFor: 'private' stamp: 'mt 4/2/2020 16:06'!
elementSetterAt: element
	"Change the number of occurrences for the given element."
	
	^ [:bag :count | (bag instVarNamed: #contents) at: element put: count]! !

!BagInspector methodsFor: 'menu commands' stamp: 'mt 4/3/2020 17:06'!
addElement: anObject

	self object add: anObject.
	self updateFields.
	self selectElementAt: anObject.! !

!BagInspector methodsFor: 'menu commands' stamp: 'mt 4/3/2020 18:06'!
removeSelectedElement

	self object remove: self selectedKey.! !

!BagInspector methodsFor: 'initialization' stamp: 'mt 4/6/2020 08:31'!
elementIndices

	^ [ (object instVarNamed: #contents) keysInOrder ] ifError: [
		"Can occur when debugging Bag new"
		Array empty ].! !

!BagInspector methodsFor: 'bindings' stamp: 'mt 4/3/2020 18:13'!
isBindingSelected

	^ false! !


!ExternalStructureInspector methodsFor: 'fields' stamp: 'mt 3/9/2020 15:15'!
fieldSelf

	^ super fieldSelf
		name: 'self: ', object defaultLabelForInspector;
		yourself! !

!ExternalStructureInspector methodsFor: 'fields' stamp: 'mt 3/11/2020 09:20'!
fieldsRecordsOn: aStream

	self recordFieldList do: [:field |
		aStream nextPut: ((self newFieldForType: #record key: field)
			valueGetter: [:object | object perform: field];
			valueSetter: [:object :value | (field, ':') asSymbol with: value];
			yourself)].! !

!ExternalStructureInspector methodsFor: 'fields' stamp: 'ct 1/5/2020 23:28'!
streamFieldsOn: aStream

	self
		streamBaseFieldsOn: aStream;
		fieldsRecordsOn: aStream.! !


!HtmlEntityInspector methodsFor: 'toolbuilder' stamp: 'ls 7/24/1998 01:40'!
initialExtent
	"Answer the desired extent for the receiver when it is first opened on the screen.  "

	^ 300 @ 300! !

!HtmlEntityInspector methodsFor: 'fields' stamp: 'mt 3/9/2020 16:53'!
fieldHtml

	^ (self newFieldForType: #custom key: #html)
		name: 'asHtml'; emphasizeName;
		valueGetter: [:object | object asHtml];
		yourself! !

!HtmlEntityInspector methodsFor: 'fields' stamp: 'ct 1/5/2020 22:54'!
streamFieldsOn: aStream

	super streamFieldsOn: aStream.
	aStream nextPut: self fieldHtml.! !


!Inspector class methodsFor: 'instance creation' stamp: 'ct 1/18/2020 18:57'!
inspect: anObject 
	"Answer a new (sub)instance of me to provide an inspector for anObject."

	^ self new inspect: anObject! !

!Inspector class methodsFor: 'instance creation' stamp: 'ct 1/18/2020 18:57'!
on: anObject 
	"Answer a new instance of me to provide an inspector for anObject."
	
	^ self new object: anObject! !

!Inspector class methodsFor: 'instance creation' stamp: 'mt 3/31/2020 10:33'!
openOn: anObject
	"Open an inspector for anObject."
	
	^ ToolBuilder open: (self on: anObject)! !

!Inspector class methodsFor: 'instance creation' stamp: 'mt 3/30/2020 14:52'!
openOn: anObject withLabel: label
	"Open an inspector with a specific label. Use this to set the inspector into context to explain why that object is inspected."

	^ ToolBuilder open: (self on: anObject) label: label! !

!Inspector class methodsFor: '*Etoys-Squeakland-instance creation' stamp: 'ct 9/19/2019 00:13'!
horizontalDividerProportion
	self deprecated.
	^ 0.4! !


!BasicInspector class methodsFor: 'as yet unclassified' stamp: 'mt 3/26/2020 14:36'!
openOn: anObject withLabel: label
	"Ignore label."
	
	^ ToolBuilder open: (self on: anObject)! !


!ContextVariablesInspector class methodsFor: 'preferences' stamp: 'mt 4/15/2020 10:17'!
showStackVariables
	<preference: 'Show stack variables in debugger'
		category: #debug
		description: 'When true, append the unnamed stack variables (if any) below the named temps in the debugger''s context inspector.'
		type: #Boolean>
	^ ShowStackVariables ifNil: [false]! !

!ContextVariablesInspector class methodsFor: 'preferences' stamp: 'mt 4/15/2020 10:13'!
showStackVariables: aBoolean

	ShowStackVariables := aBoolean.! !


!InspectorBrowser methodsFor: 'initialization' stamp: 'mt 4/21/2020 17:56'!
initialExtent

	^ (inspector initialExtent x max: browser initialExtent x)
		@ ((inspector initialExtent y * 2/3) + browser initialExtent y)! !

!InspectorBrowser methodsFor: 'initialization' stamp: 'mt 4/21/2020 18:02'!
initialize

	super initialize.
	
	self setInspectorClass: Inspector.
	self setBrowserClass: Browser.! !

!InspectorBrowser methodsFor: 'initialization' stamp: 'mt 4/21/2020 17:58'!
inspect: anObject
	"Reinitialize the inspector so that it is inspecting anObject."

	inspector inspect: anObject.
	browser setClass: anObject class.! !

!InspectorBrowser methodsFor: 'initialization' stamp: 'mt 4/21/2020 18:02'!
setBrowserClass: aClass

	browser := aClass new.! !

!InspectorBrowser methodsFor: 'initialization' stamp: 'mt 4/21/2020 18:01'!
setInspectorClass: aClass

	inspector := aClass new.
	inspector addDependent: self.! !

!InspectorBrowser methodsFor: 'toolbuilder' stamp: 'ct 12/16/2019 20:43'!
buildWith: builder

	| windowSpec |
	windowSpec := self buildWindowWith: builder specs: {
		(0 at 0 corner: 0.3 at 0.3) -> [inspector buildFieldListWith: builder].
		(0.3 at 0 corner: 1.0 at 0.3) -> [inspector buildValuePaneWith: builder].
		(0 at 0.3 corner: 0.3 at 1.0) -> [browser buildMessageListWith: builder].
		(0.3 at 0.3 corner: 1.0 at 1.0) -> [browser buildCodePaneWith: builder].
	}.
	^ builder build: windowSpec! !

!InspectorBrowser methodsFor: 'toolbuilder' stamp: 'mt 4/21/2020 18:18'!
labelString
	"The window title"

	^ 'Inspector Browser: ', inspector labelString! !

!InspectorBrowser methodsFor: 'accessing' stamp: 'mt 4/21/2020 18:12'!
object

	^ inspector object! !

!InspectorBrowser methodsFor: 'accessing' stamp: 'mt 4/21/2020 17:58'!
object: anObject
	"Set anObject to be the object being inspected by the receiver."

	inspector object: anObject.
	browser setClass: anObject class.! !

!InspectorBrowser methodsFor: 'stepping' stamp: 'mt 4/21/2020 17:53'!
modelWakeUpIn: aWindow

	inspector modelWakeUpIn: aWindow.
	browser modelWakeUpIn: aWindow.! !

!InspectorBrowser methodsFor: 'stepping' stamp: 'ct 12/16/2019 20:44'!
stepAt: millisecondClockValue in: aWindow
	
	inspector stepAt: millisecondClockValue in: aWindow.
	browser stepAt: millisecondClockValue in: aWindow.! !

!InspectorBrowser methodsFor: 'stepping' stamp: 'mt 4/21/2020 17:50'!
stepTimeIn: aWindow

	^ (inspector stepTimeIn: aWindow)
		max: (browser stepTimeIn: aWindow)! !

!InspectorBrowser methodsFor: 'stepping' stamp: 'mt 4/21/2020 17:53'!
updateListsAndCodeIn: aWindow

	inspector updateListsAndCodeIn: aWindow.
	browser updateListsAndCodeIn: aWindow.! !

!InspectorBrowser methodsFor: 'stepping' stamp: 'mt 4/21/2020 17:51'!
wantsStepsIn: aWindow

	^ (inspector wantsStepsIn: aWindow)
		or: [browser wantsStepsIn: aWindow]! !

!InspectorBrowser methodsFor: 'updating' stamp: 'mt 4/21/2020 18:16'!
update: anAspect
	"When the inspector exchanges the object-under-inspection, reset the class of my browser."
	
	anAspect = #object ifTrue: [
		browser setClass: inspector object class].
	anAspect = #windowTitle ifTrue: [
		self changed: #windowTitle].
	super update: anAspect.! !


!InspectorBrowser class methodsFor: 'inspector compatibility' stamp: 'mt 4/21/2020 18:09'!
basicInspect: anObject 
	"ToolBuilder open: (self basicInspect: Morph new)"
	
	^ self new
		setInspectorClass: BasicInspector;
		object: anObject;
		yourself! !

!InspectorBrowser class methodsFor: 'inspector compatibility' stamp: 'mt 4/21/2020 18:09'!
inspect: anObject 
	"ToolBuilder open: (self inspect: 42)"

	^ self new inspect: anObject! !

!InspectorBrowser class methodsFor: 'instance creation' stamp: 'mt 4/21/2020 18:11'!
on: anObject 
	"We have to call #inspect: instead of #object: to choose the correct #inspectorClass."
	
	^ self new inspect: anObject! !

!InspectorBrowser class methodsFor: 'instance creation' stamp: 'ct 3/15/2020 20:26'!
openOn: anObject

	^ ToolBuilder open: (self on: anObject)! !

!InspectorBrowser class methodsFor: 'instance creation' stamp: 'mt 4/21/2020 18:06'!
openOn: anObject withLabel: label

	^ ToolBuilder open: (self on: anObject) label: label! !


!InspectorField methodsFor: 'menu - construction' stamp: 'mt 4/6/2020 15:57'!
addCustomItemsFor: anInspector to: aMenu
	
	aMenu
		addLine;
		add: 'edit field name...' translated target: self selector: #editName;
		add: 'edit field getter...' translated target: self selector: #editGetterFor: argument: anInspector;
		add: (self valueSetter ifNil: ['add field setter...' translated] ifNotNil: ['edit field setter...' translated])
			target: self selector: #editSetterFor: argument: anInspector;
		addLine;
		add: ('remove field ''{1}'' (x)' translated format: {self name}) target: self selector: #delete.! !

!InspectorField methodsFor: 'accessing' stamp: 'mt 3/9/2020 14:56'!
key

	^ key! !

!InspectorField methodsFor: 'accessing' stamp: 'mt 3/9/2020 15:11'!
key: anObject

	self key = anObject ifTrue: [^ self].
	key := anObject.
	self changed: #field.! !

!InspectorField methodsFor: 'accessing' stamp: 'mt 4/14/2020 11:15'!
name
	"Answers most human-readable name for this field. Not that the key can be any kind of object but this message should answer something that is already printable such as String or Text. If the sender could not rely on this, quoted strings could be confused with regular strings."
	
	^ name ifNil: [valueGetterExpression ifNil: [key ifNil: [''] ifNotNil: [key asString]]]! !

!InspectorField methodsFor: 'accessing' stamp: 'mt 3/9/2020 15:51'!
name: aString

	name = aString ifTrue: [^ self].
	name := aString.
	self changed: #field.! !

!InspectorField methodsFor: 'accessing' stamp: 'ct 1/4/2020 14:55'!
type

	^ type! !

!InspectorField methodsFor: 'accessing' stamp: 'ct 1/4/2020 14:55'!
type: aSymbol

	type := aSymbol! !

!InspectorField methodsFor: 'accessing' stamp: 'mt 3/9/2020 14:31'!
value
	"For convenience only. If you have an #inspector, call #getValueFor: directly. It may be faster."

	^ self getValueFor: self inspector! !

!InspectorField methodsFor: 'accessing' stamp: 'mt 3/9/2020 14:32'!
value: anObject
	"For convenience only. If you have an #inspector, call #setValueFor:to: directly. It may be faster."

	^ self setValueFor: self inspector to: anObject! !

!InspectorField methodsFor: 'custom - actions' stamp: 'mt 3/11/2020 16:46'!
delete
	"Request the deletion of this field in my inspector's list of (custom) fields."
	
	self changed: #deleteField with: self.! !

!InspectorField methodsFor: 'custom - actions' stamp: 'ct 2/14/2020 15:07'!
editGetterFor: aStringHolder

	^ self editGetterFor: aStringHolder orCancel: []! !

!InspectorField methodsFor: 'custom - actions' stamp: 'mt 4/6/2020 18:24'!
editGetterFor: anInspector orCancel: aBlock

	| code |
	code := Project uiManager
		request: 'Please enter an evaluable expression<br>to <b>get</b> this field''s value:' translated asTextFromHtml
		initialAnswer: self valueGetterExpression.
	code isEmptyOrNil ifTrue: [^ aBlock value].
	
	^ self setGetterFor: anInspector to: code ifFail: aBlock! !

!InspectorField methodsFor: 'custom - actions' stamp: 'mt 3/9/2020 14:51'!
editName

	^ self editNameOrCancel: []! !

!InspectorField methodsFor: 'custom - actions' stamp: 'mt 4/6/2020 17:54'!
editNameOrCancel: aBlock

	| newTitle |
	newTitle := Project uiManager
		request: 'Please enter a new name for this field:' translated withCRs
		initialAnswer: self name asString.
	newTitle isEmptyOrNil ifTrue: [^ aBlock value].
	self name: newTitle; emphasizeName.
	self changed: #field.! !

!InspectorField methodsFor: 'custom - actions' stamp: 'mt 4/6/2020 17:57'!
editSetterFor: anInspector

	^ self editSetterFor: anInspector orCancel: []! !

!InspectorField methodsFor: 'custom - actions' stamp: 'mt 4/6/2020 18:35'!
editSetterFor: anInspector orCancel: aBlock

	| code |
	code := Project uiManager
		request: 'Please enter an evaluable expression<br>to <b>set</b> this field''s value:' translated asTextFromHtml
		initialAnswer: (self valueSetterExpression ifNil: '[:value | self ___: value]').
	code isEmptyOrNil ifTrue: [^ aBlock value].
	^ self setSetterFor: anInspector to: code ifFail: aBlock! !

!InspectorField methodsFor: 'custom' stamp: 'mt 4/21/2020 18:21'!
requestCustomFor: anInspector orCancel: aBlock

	self setGetterFor: anInspector to: 'self yourself' ifFail: [^ self].
	self editGetterFor: anInspector orCancel: aBlock.
	self emphasizeName.! !

!InspectorField methodsFor: 'custom' stamp: 'mt 4/6/2020 18:28'!
setGetterFor: anInspector to: code ifFail: aBlock

	| getter |
	getter := Compiler new
		compiledMethodFor: code
		in: anInspector doItContext
		to: anInspector doItReceiver
		environment: anInspector environment
		notifying: nil
		ifFail: [^ aBlock value].

	self valueGetterExpression: code.	
	self valueGetter: getter.
	
	self changed: #field.! !

!InspectorField methodsFor: 'custom' stamp: 'mt 4/6/2020 18:29'!
setSetterFor: anInspector to: code ifFail: aBlock

	| setter |
	setter := Compiler new
		evaluate: code
		in: anInspector doItContext
		to: anInspector doItReceiver
		environment: anInspector environment
		notifying: nil
		ifFail: [^ aBlock value]
		logged: false.
	
	self
		flag: #experimental; "ct: We might want to change this when input-request dialogs can work with source code. See also http://forum.world.st/Changeset-requestCode-cs-td5110502.html for this proposal."
		assert: [setter respondsTo: #value:]
		description: 'Setter must be evaluable like a block with one argument' translated.
	
	self valueSetterExpression: code.	
	self valueSetter: [:object :value | setter value: value].
	
	self changed: #field.! !

!InspectorField methodsFor: 'private' stamp: 'mt 4/2/2020 18:40'!
forgetInspector

	inspector := nil.! !

!InspectorField methodsFor: 'private' stamp: 'mt 4/2/2020 18:40'!
inspector

	^ inspector ifNil: [self dependents
		detect: [:object | object isKindOf: Inspector]
		ifNone: [nil]]! !

!InspectorField methodsFor: 'private' stamp: 'mt 4/2/2020 18:40'!
rememberInspector

	inspector := self inspector.! !

!InspectorField methodsFor: 'evaluating' stamp: 'mt 4/6/2020 10:16'!
getValueFor: anInspector

	^ self valueGetter isCompiledCode
		ifTrue: [ "precompiled user code"
			self valueGetter
				valueWithReceiver: anInspector doItReceiver
				arguments: ({anInspector doItContext} first: self valueGetter numArgs)]
		ifFalse: [ "evaluable"
			self valueGetter value: anInspector object ]! !

!InspectorField methodsFor: 'evaluating' stamp: 'mt 4/6/2020 10:16'!
setValueFor: anInspector to: value

	self valueSetter isCompiledCode
		ifTrue: [ "precompiled user code"
			self valueSetter
				valueWithReceiver: anInspector doItReceiver
				arguments: ({value. anInspector doItContext} first: self valueSetter numArgs)]
		ifFalse: [ "evaluable"
			self valueSetter value: anInspector object value: value ].
	self changed: #field.! !

!InspectorField methodsFor: 'initialization' stamp: 'mt 3/26/2020 13:25'!
deEmphasizeName

	self flag: #hardcoded.
	self name: (self name asText
		addAttribute: (TextColor color: (self userInterfaceTheme get: #balloonTextColor for: #PluggableTextMorphPlus));
		yourself).! !

!InspectorField methodsFor: 'initialization' stamp: 'mt 3/26/2020 13:31'!
emphasizeName

	| regularEmphasis customEmphasis |

	self flag: #hardcoded.
	regularEmphasis := TextEmphasis italic.
	customEmphasis := TextColor color: ((self userInterfaceTheme get: #highlightTextColor for: #SimpleHierarchicalListMorph) ifNil: [Color red]).

	self name: (self name asText
		addAttribute: (self isCustom ifTrue: [customEmphasis] ifFalse: [regularEmphasis]);
		yourself).! !

!InspectorField methodsFor: 'initialization' stamp: 'mt 3/11/2020 11:38'!
printValueAsIs

	self shouldPrintValueAsIs: true.! !

!InspectorField methodsFor: 'testing' stamp: 'ct 3/15/2020 20:15'!
isCustom

	^ self type = #custom! !

!InspectorField methodsFor: 'testing' stamp: 'mt 3/9/2020 16:56'!
isReadOnly

	^ self valueSetter isNil! !

!InspectorField methodsFor: 'printing' stamp: 'mt 3/10/2020 16:46'!
printOn: aStream

	super printOn: aStream.
	aStream
		nextPut: $<;
		print: self type;
		nextPut: $>.
	aStream
		nextPutAll: ' named ';
		print: self name asString.! !

!InspectorField methodsFor: 'accessing - code' stamp: 'mt 4/6/2020 18:23'!
expressionWithReceiverName: receiverName
	"The code string to run for getting the receiver's value. The receiver's name, which is usually #self, can be replaced to fit specific debugging scenarios such as ThisContext."

	^ valueGetterExpression ifNil: [
		self valueGetter isCompiledCode
			ifTrue: [ "precompiled user code"
				self valueGetter getSource ]
			ifFalse: [ "evaluable"
				self class
					generateExpressionFrom: self valueGetter
					argumentNames: {receiverName} ] ]! !

!InspectorField methodsFor: 'accessing - code' stamp: 'ct 3/15/2020 21:29'!
valueGetter
	"The valueGetter will be used to fetch a value for this field. See comment in #valueGetter:."

	^ valueGetter! !

!InspectorField methodsFor: 'accessing - code' stamp: 'ct 3/15/2020 21:30'!
valueGetter: evaluable
	"The valueGetter will be used to fetch a value for this field. The corresponding inspctor will provide an object to fetch the value from.
	
	Here are some examples:
	
		[:object | object size] -- The most basic case.
		#negated --- A convenient shortcut.
		[:object | self print: object] --- A closured helper to fetch the value.
	
	It is also possible to store a compiled method as a valueGetter. Then, the corresponding inspector will provide both #doItReceiver and #doItContext to execute that method to fetch the value for this field. So, this is like storing a compiled do-it expression."

	valueGetter := evaluable.! !

!InspectorField methodsFor: 'accessing - code' stamp: 'mt 4/6/2020 18:22'!
valueGetterExpression
	"The code string to run for getting the receiver's value."

	^ self expressionWithReceiverName: #self! !

!InspectorField methodsFor: 'accessing - code' stamp: 'mt 4/6/2020 18:22'!
valueGetterExpression: aString

	valueGetterExpression := aString.! !

!InspectorField methodsFor: 'accessing - code' stamp: 'ct 3/15/2020 21:46'!
valueSetter
	"The valueSetter will be used to manipulate the value for this field. See comment in #valueSetter:."

	^ valueSetter! !

!InspectorField methodsFor: 'accessing - code' stamp: 'mt 4/6/2020 10:12'!
valueSetter: oneArgEvaluable
	"The valueSetter will be used to manipulate the value for this field. It follows the same semantics as the valueGetter, but expects one more argument, which is the new value to set. See also comment in #valueGetter:.
	
	Here are some examples:
	
		[:object :value | object someProperty: value] -- The most basic case.
		#someProperty: --- A convenient shortcut.
		[:object :value | self setProperty: value in: object] --- A closured helper to set the value."

	valueSetter := oneArgEvaluable! !

!InspectorField methodsFor: 'accessing - code' stamp: 'mt 4/6/2020 18:22'!
valueSetterExpression

	^ valueSetterExpression! !

!InspectorField methodsFor: 'accessing - code' stamp: 'mt 4/6/2020 18:22'!
valueSetterExpression: aString

	valueSetterExpression := aString.! !

!InspectorField methodsFor: 'accessing - printing' stamp: 'ct 3/15/2020 21:23'!
shouldPrintValueAsIs
	"Whether to call #asString or #printString on this field's value."

	^ shouldPrintValueAsIs ifNil: [false]! !

!InspectorField methodsFor: 'accessing - printing' stamp: 'ct 3/15/2020 21:23'!
shouldPrintValueAsIs: aBoolean
	"Whether to call #asString or #printString on this field's value."

	shouldPrintValueAsIs := aBoolean.! !

!InspectorField methodsFor: 'accessing - printing' stamp: 'mt 3/9/2020 15:00'!
shouldStyleName

	^ shouldStyleName ifNil: [false]! !

!InspectorField methodsFor: 'accessing - printing' stamp: 'mt 3/9/2020 15:01'!
shouldStyleName: aBoolean

	self shouldStyleName = aBoolean ifTrue: [^ self].
	shouldStyleName := aBoolean.
	self changed: #field.! !

!InspectorField methodsFor: 'accessing - printing' stamp: 'mt 3/9/2020 15:06'!
shouldStyleValue
	
	^ shouldStyleValue ifNil: [false]! !

!InspectorField methodsFor: 'accessing - printing' stamp: 'mt 3/9/2020 15:06'!
shouldStyleValue: aBoolean

	self shouldStyleValue = aBoolean ifTrue: [^ self].
	shouldStyleValue := aBoolean.
	self changed: #field.! !


!InspectorField class methodsFor: 'support' stamp: 'mt 3/30/2020 14:13'!
generateExpressionFrom: aBlock argumentNames: argumentNames

	| blockNode arguments variables context receiver |
	self flag: #experimental.
	blockNode := aBlock decompile veryDeepCopy. "some literals are singletons, see #becomeForward: below"
	arguments := blockNode arguments collect: #name.
	variables := Dictionary new.
	variables
		at: #true put: true;
		at: #false put: false;
		at: #nil put: nil.
	receiver := aBlock receiver.
	receiver class allInstVarNames
		withIndexDo: [:name :index |
			variables at: name put: (receiver instVarAt: index)].
	context := aBlock outerContext.
	context tempNames
		withIndexDo: [:name :index |
			variables at: name put: (context namedTempAt: index)].
	blockNode nodesDo: [:node |
		self flag: #ct. "Should we introduce #nodesCollect: instead of using dangerous #becomeForward:?"
		{
			[node isVariableNode not].
			[| argumentIndex |
			argumentIndex := arguments indexOf: node name.
			argumentIndex isZero
				ifFalse: [node name: (argumentNames at: argumentIndex)];
				not].
			[variables at: node name
				ifPresent: [:value |
					value isLiteral
						ifTrue: [node becomeForward: (LiteralNode new key: value)];
						yourself]
				ifAbsent: [^ nil]].
		} detect: #value ifNone: [^ nil]].
	^ String streamContents: [:stream |
		blockNode
			printStatementsOn: stream
			indent: 0].! !

!InspectorField class methodsFor: 'instance creation' stamp: 'ct 1/4/2020 14:57'!
type: aSymbol

	^ self new
		type: aSymbol;
		yourself! !

!InspectorField class methodsFor: 'instance creation' stamp: 'ct 1/4/2020 14:59'!
type: aSymbol key: anObject

	^ (self type: aSymbol)
		key: anObject
		yourself! !


!InspectorTest methodsFor: 'assertions - ui' stamp: 'mt 4/14/2020 12:44'!
assertFieldSelected: fieldName
	"Looking at the inspector's #fieldList, which contains the list of labels visible to the user, check whether that list contains fieldName, which is the label the user is looking for."

	self
		assert: (self inspector selectionIndex
			between: 1
			and: self inspector fieldList size);
		assert: fieldName 
		matches: (self inspector fieldList at: self inspector selectionIndex) asString.! !

!InspectorTest methodsFor: 'assertions - ui' stamp: 'mt 4/14/2020 11:48'!
assertFieldVisible: fieldNameOrPattern

	self assert: (self inspector fieldList anySatisfy: [:label |
					label asString = fieldNameOrPattern
						or: [fieldNameOrPattern match: label] ]).! !

!InspectorTest methodsFor: 'assertions - ui' stamp: 'mt 4/8/2020 10:35'!
assertNoFieldSelected

	self assert: self inspector selectionIndex = 0.! !

!InspectorTest methodsFor: 'assertions - ui' stamp: 'mt 4/7/2020 17:54'!
assertValuePaneShows: contents

	self assert: contents matches: self inspector contents.! !

!InspectorTest methodsFor: 'assertions - ui' stamp: 'mt 4/7/2020 17:54'!
denyFieldSelected: fieldName

	self deny: (self inspector fieldList at: self inspector selectionIndex) asString = fieldName.! !

!InspectorTest methodsFor: 'assertions - ui' stamp: 'mt 4/7/2020 17:54'!
denyFieldVisible: fieldName

	self assert: (self inspector fieldList noneSatisfy: [:label |
					label asString = fieldName]).! !

!InspectorTest methodsFor: 'assertions - ui' stamp: 'mt 4/8/2020 10:35'!
denyNoFieldSelected

	self assert: self inspector selectionIndex > 0.! !

!InspectorTest methodsFor: 'assertions - ui' stamp: 'mt 4/7/2020 17:54'!
denyValuePaneShows: contents

	self deny: contents matches: self inspector contents.! !

!InspectorTest methodsFor: 'support' stamp: 'mt 4/7/2020 18:39'!
fieldListMenu

	^ self inspector fieldListMenu: MenuMorph new! !

!InspectorTest methodsFor: 'support' stamp: 'mt 4/15/2020 09:11'!
fieldTypeOfIndexedVariable

	^ #indexed! !

!InspectorTest methodsFor: 'assertions - matching' stamp: 'ct 1/3/2020 23:55'!
assert: pattern matches: actual

	self
		assert: [(actual isString or: [actual isText]) and: [pattern match: actual]]
		description: [self comparingStringBetweenMatch: pattern and: actual]! !

!InspectorTest methodsFor: 'assertions - matching' stamp: 'ct 1/12/2020 17:08'!
comparingStringBetweenMatch: pattern and: actual

	^ 'Pattern {1} is not matched by actual {2}' format: (
		{pattern. actual} collect: [:arg | arg printStringLimitedTo: 10])! !

!InspectorTest methodsFor: 'assertions - matching' stamp: 'ct 2/14/2020 17:49'!
deny: pattern matches: actual

	self
		deny: [(actual isString or: [actual isText]) and: [pattern match: actual]]
		description: ['Actually matches {1}' format: {pattern}]! !

!InspectorTest methodsFor: 'assertions' stamp: 'mt 4/8/2020 11:03'!
assertMenuWorks

	| aMenu |
	aMenu := self fieldListMenu.
	self
		assert: aMenu items notEmpty;
		assert: (aMenu items allSatisfy: [:item | item contents notEmpty]).! !

!InspectorTest methodsFor: 'assertions' stamp: 'mt 4/14/2020 15:10'!
assertValuePaneWorks

	^ self denyValuePaneShows: '<*error*debug*>'! !

!InspectorTest methodsFor: 'assertions' stamp: 'mt 4/14/2020 11:26'!
denyValuePaneWorks

	^ self assertValuePaneShows: '*error*debug*'! !

!InspectorTest methodsFor: 'assertions' stamp: 'mt 4/7/2020 16:14'!
shouldntRaiseWhileDebugging: aBlock

	aBlock newProcess runUntil: [:ctxt |
		self
			shouldnt: [inspector inspect: ctxt receiver]
			raise: Error, Warning, Halt.
		false].! !

!InspectorTest methodsFor: 'accessing' stamp: 'mt 4/7/2020 17:22'!
inspector

	^ inspector! !

!InspectorTest methodsFor: 'accessing' stamp: 'mt 4/7/2020 17:21'!
object

	^ self inspector object! !

!InspectorTest methodsFor: 'support - ui' stamp: 'mt 4/14/2020 15:43'!
during: block confirm: boolean
	"When evaluating the block, there will be a dialog showing up that requests the user to confirm something. Simulate that interaction here."

	block valueSupplyingAnswer: {'*'. boolean}.! !

!InspectorTest methodsFor: 'support - ui' stamp: 'mt 4/8/2020 10:39'!
during: block type: expression
	"When evaluating the block, there will be a dialog showing up that requests the user to type something. Simulate that interaction here."

	block valueSupplyingAnswer: {'*'. expression}.! !

!InspectorTest methodsFor: 'support - ui' stamp: 'mt 4/8/2020 10:40'!
inValuePaneTypeAndAccept: aString
	"The user types aString in the value pane and accepts those contents."

	self inspector contents: aString notifying: nil.! !

!InspectorTest methodsFor: 'support - ui' stamp: 'mt 4/14/2020 16:38'!
simulateStepping

	self inspector stepAt: 0 in: nil.! !

!InspectorTest methodsFor: 'failures' stamp: 'mt 4/14/2020 12:04'!
expectedFieldExpressionFailures
	"List all fields whose 'Get field expression' feature does not yet work."

	^ #()! !

!InspectorTest methodsFor: 'running' stamp: 'mt 4/7/2020 17:51'!
createObject

	^ InspectorTestObject new
		apple: #discovery;
		orange: #navel;
		yourself! !

!InspectorTest methodsFor: 'running' stamp: 'mt 4/15/2020 09:09'!
createObjectWithTruncation
	"Create an object that will surely trigger truncation of inspector fields when being inspected."

	^ (InspectorTestObject new: 500)
		apple: #discovery;
		orange: #navel;
		yourself! !

!InspectorTest methodsFor: 'running' stamp: 'mt 4/7/2020 17:27'!
setUp

	super setUp.
	inspector := self targetClass on: self createObject.! !

!InspectorTest methodsFor: 'support - error' stamp: 'mt 4/8/2020 14:25'!
makeObjectInvalid
	"Violate some contract so that the inspector cannot call #printString on some field anymore without getting an error."

	self object beInvalid.! !

!InspectorTest methodsFor: 'support - error' stamp: 'mt 4/8/2020 14:41'!
selectInvalidField

	self inspector selectFieldNamed: 'self'.! !

!InspectorTest methodsFor: 'tests - special' stamp: 'mt 4/15/2020 09:10'!
testFieldListError
	"Choose an inspector that messes up field streaming. Check whether the field list shows still something informative."

	self class == InspectorTest ifFalse: [^ self "Pass the test automatically."].
	
	inspector := InspectorTestInspector on: Object new.
	
	self assertFieldVisible: '<error>'.
	inspector ensureSelectedField.
	self assertFieldSelected: '<error>'.
	self assertValuePaneShows: '*error*debug*'.! !

!InspectorTest methodsFor: 'tests - special' stamp: 'mt 4/15/2020 09:09'!
testObjectChanged
	
	self class == InspectorTest ifFalse: [^ self "Pass the test automatically."].
	
	self inspector selectFieldNamed: 'self'.
	self denyValuePaneShows: '*ontario*'.
	
	self object apple: #ontario.
	self denyValuePaneShows: '*ontario*'.
	
	self simulateStepping.
	self assertValuePaneShows: '*ontario*'.! !

!InspectorTest methodsFor: 'tests - special' stamp: 'mt 4/14/2020 16:04'!
testTruncationEllipsis
	"Even the most generic inspector supports truncation of indexed variables."

	| ellipsis |
	(self class includesSelector: #createObjectWithTruncation)
		ifFalse: [^ self "Run this test only if explicitely refined."].
	
	self inspector object: self createObjectWithTruncation.
	self assert: self inspector class = self targetClass. "No change."
	
	self assert: self inspector fields size >= self inspector truncationLimit.
	self assertFieldVisible: '...'.

	self inspector selectFieldSuchThat: [:field | field type = #ellipsis].
	ellipsis := self inspector selectedField.

	self assert: '*...*' matches: ellipsis name.
	self assertValuePaneShows: '*not shown*'.
	
	self inspector fields do: [:field |
		"All visible elements are from that object."
		self assert: (field type = #element) ==> [self inspector object includes: field value]].! !

!InspectorTest methodsFor: 'tests - special' stamp: 'mt 4/14/2020 11:38'!
testTruncationEllipsisMenu

	(self class includesSelector: #createObjectWithTruncation)
		ifFalse: [^ self "Run this test only if explicitely refined."].
		
	self inspector object: self createObjectWithTruncation.
	self inspector selectFieldSuchThat: [:field | field type = #ellipsis].
	self assertMenuWorks.! !

!InspectorTest methodsFor: 'tests - special' stamp: 'mt 4/15/2020 09:12'!
testTruncationTail

	| ellipsisIndex firstElementIndex |
	(self class includesSelector: #createObjectWithTruncation)
		ifFalse: [^ self "Run this test only if explicitely refined."].
		
	self inspector object: self createObjectWithTruncation.
	
	firstElementIndex := self inspector fields
		findFirst: [:field | field type = self fieldTypeOfIndexedVariable].
	ellipsisIndex := self inspector fields
		findFirst: [:field | field type = #ellipsis].

	self
		assert: self inspector truncationLimit
		equals: ellipsisIndex - firstElementIndex + 1 + self inspector truncationTail;
		assert: self inspector truncationTail
		equals: self inspector fields size - ellipsisIndex.! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/7/2020 17:53'!
testCustomField

	self
		during: [self inspector addCustomField]
		type: 'self fruits'.
	
	self assertFieldVisible: 'self fruits'.
	self assertFieldSelected: 'self fruits'.
	self assertValuePaneShows: '*discovery*navel*'.! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 15:43'!
testCustomFieldRemove

	self assert: 0 equals: self inspector customFields size.
	self during: [self inspector addCustomField] type: 'self'.
	self assert: 1 equals: self inspector customFields size.

	self assert: self inspector selectedField type = #custom.
	self during: [self inspector removeSelection] confirm: true.
	self assert: 0 equals: self inspector customFields size.! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/7/2020 17:31'!
testDebugConstruction

	self shouldntRaiseWhileDebugging: [
		self createObject]! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 12:03'!
testExpressions
	"All fields should provide an evaluable expression to be evaluated on the inspected objects to retrieve that field's value. Try to test that by re-setting that expression as a getter and compare the resulting values."

	self inspector fields
		reject: [:field | self expectedFieldExpressionFailures includes: field name asString]
		thenDo: [:field |
			| expression content |
			(expression := self inspector expressionForField: field) ifNil: [self fail].
			content := field getValueFor: self inspector. 		
			field setGetterFor: self inspector to: expression ifFail: [self fail].
			self assert: content equals: (field getValueFor: self inspector)].! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 11:39'!
testFieldList
	"Check whether the most important fields are visible."
	
	#(self 'all inst vars' apple orange) do: [:label |
		self assertFieldVisible: label].! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 11:20'!
testFieldListMenu
	"Select one field after another and check whether the menu can be invoked."

	self assertNoFieldSelected.
	self assertMenuWorks.

	1 to: self inspector fieldList size do: [:index |
		self inspector selectionIndex: index.
		self denyNoFieldSelected.
		self assertMenuWorks].
	! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 14:24'!
testFieldSelf
	"There should be at least one field pointing to the inspected object itself."

	self assert: (self inspector fields anySatisfy: [:field | field value == self object]).! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/8/2020 10:28'!
testInspectorClass
	"Be sure to use the correct inspector for our object-under-inspection. If this test fails, #targetClass or #setUp might be wrong."

	| previousInspectorClass |
	previousInspectorClass := self inspector class.
	self inspector inspect: self object.
	self assert: previousInspectorClass equals: self inspector class.! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 11:37'!
testValuePane
	"Select one field after another and check whether the value pane shows non-error contents."

	self assertNoFieldSelected.
	self assertValuePaneWorks.

	1 to: self inspector fieldList size do: [:index |
		self inspector selectionIndex: index.
		self denyNoFieldSelected.
		self assertValuePaneWorks].! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 11:27'!
testValuePaneError

	self makeObjectInvalid.
	self assertValuePaneWorks.
	
	self selectInvalidField.
	self denyValuePaneWorks.! !

!InspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 15:02'!
testValuePaneModify

	self inspector selectFieldNamed: #apple.

	self deny: #ontario equals: self object apple.
	self assertValuePaneShows: '#discovery'.
		
	self inValuePaneTypeAndAccept: '#ontario'.

	self assert: #ontario equals: self object apple.
	self assertValuePaneShows: '#ontario'.! !


!BasicInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 14:21'!
testFieldList

	#(self 'class' 'size') do: [:label |
		self assertFieldVisible: label].! !

!BasicInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 14:41'!
testFieldSelf
	"The basic inspector sends as little messages as possible to the object-under-inspector. So, just look for the correct class name in a field's contents."

	| namePattern |
	namePattern := '*{1}*' format: { (thisContext objectClass: self object) name }.
	self assert: (self inspector fields anySatisfy: [:field | namePattern match: field value]).! !

!BasicInspectorTest methodsFor: 'support - error' stamp: 'mt 4/14/2020 14:49'!
selectInvalidField
	"Create a custom field. The existing fields will all work because the basic inspector shows only minimal information about the object."
	
	self
		during: [self inspector addCustomField]
		type: 'self printString'.! !

!BasicInspectorTest methodsFor: 'failures' stamp: 'mt 4/20/2020 09:47'!
expectedFieldExpressionFailures

	^ #('self')! !


!ClassInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 15:07'!
testCustomField

	self
		during: [self inspector addCustomField]
		type: 'self packageInfo'.
	
	self assertFieldVisible: 'self packageInfo'.
	self assertFieldSelected: 'self packageInfo'.
	self assertValuePaneShows: '*ToolsTests*'.! !

!ClassInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 14:58'!
testFieldList
	
	#(self 'all inst vars' superclass InnerTestObject) do: [:label |
		self assertFieldVisible: label].! !

!ClassInspectorTest methodsFor: 'tests' stamp: 'mt 4/15/2020 09:59'!
testPoolDictionaries
	"All class inspectors should list the referenced pool dictionaries. Use an existing class from the base system that is known to rely of such a pool. If we would add our own references, loading these tests could raise extra dialog prompts."

	self denyFieldVisible: 'TextConstants'.
	self inspector object: TextStyle.
	self assertFieldVisible: 'TextConstants'.! !

!ClassInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 15:31'!
testValuePaneModify

	self inspector selectFieldNamed: 'InnerTestObject'.
	self assertFieldSelected: 'InnerTestObject'.
	
	self deny: 42 equals: InnerTestObject.
	self inValuePaneTypeAndAccept: '42'.
	self assert: 42 equals: InnerTestObject.! !

!ClassInspectorTest methodsFor: 'running' stamp: 'mt 4/14/2020 14:57'!
createObject

	InnerTestObject := super createObject.
	^ self class! !

!ClassInspectorTest methodsFor: 'running' stamp: 'mt 4/14/2020 15:03'!
tearDown

	InnerTestObject := nil.
	super tearDown.! !

!ClassInspectorTest methodsFor: 'support - error' stamp: 'mt 4/14/2020 15:04'!
makeObjectInvalid

	InnerTestObject beInvalid.! !

!ClassInspectorTest methodsFor: 'support - error' stamp: 'mt 4/14/2020 15:05'!
selectInvalidField

	self inspector selectFieldSuchThat: [:field |
		field type = #classVar and: [field value == InnerTestObject]].! !


!CollectionInspectorTest methodsFor: 'running' stamp: 'mt 4/8/2020 14:45'!
createObject

	^ OrderedCollection new
		addAll: #(discovery navel smith);
		yourself! !

!CollectionInspectorTest methodsFor: 'running' stamp: 'mt 4/7/2020 18:32'!
createObjectWithTruncation

	^ (1 to: 500) asOrderedCollection! !

!CollectionInspectorTest methodsFor: 'support' stamp: 'mt 4/15/2020 09:11'!
fieldTypeOfIndexedVariable

	^ #element! !

!CollectionInspectorTest methodsFor: 'support - error' stamp: 'mt 4/14/2020 16:45'!
makeObjectInvalid

	self object at: 1 put: InspectorTestObject newInvalid.
	self simulateStepping.! !

!CollectionInspectorTest methodsFor: 'support - error' stamp: 'mt 4/14/2020 15:35'!
selectInvalidField
	
	self inspector selectFieldNamed: '1'.! !

!CollectionInspectorTest methodsFor: 'tests - special' stamp: 'mt 4/14/2020 16:13'!
testAddElementError
	"Not all collections support addition or removal of elements."

	self class == CollectionInspectorTest ifFalse: [^ self "Pass the test automatically"].

	self inspector object: Array new.
	self
		should: [self inspector addElement: 1]
		raise: Error.! !

!CollectionInspectorTest methodsFor: 'tests - special' stamp: 'mt 4/15/2020 10:00'!
testAddElementMenuHidden

	| testMenuEntry |
	self class == CollectionInspectorTest ifFalse: [^ self "Pass the test automatically"].

	testMenuEntry := [self fieldListMenu items anySatisfy: [:item | '*add*element*' match: item contents ]].

	self inspector object: Array new.
	self deny: testMenuEntry.! !

!CollectionInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 15:36'!
testAddElement
	"Add a new element through the Smalltalk expression '6 * 7' and check whether the field representing that new element will be selected automatically."

	| objectSize |
	objectSize := self object size.
	
	self assertFieldVisible: objectSize asString.
	self deny: (self object includes: 42).
	
	self
		during: [self inspector addElement]
		type: '6 * 7'. "42"

	self assert: (self object includes: 42).
		
	self assertFieldVisible: (objectSize + 1) asString.
	self assertFieldSelected: (objectSize + 1) asString.
	self assertValuePaneShows: '42'.! !

!CollectionInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 16:15'!
testAddElementMenu

	| testMenuEntry |
	testMenuEntry := [self fieldListMenu items anySatisfy: [:item | '*add*element*' match: item contents ]].

	self inspector selectField: nil.
	self assert: testMenuEntry.
	self inspector ensureSelectedField.
	self assert: testMenuEntry.! !

!CollectionInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 15:59'!
testCustomField

	self
		during: [self inspector addCustomField]
		type: 'self take: 5'.
	
	self assertFieldVisible: 'self take: 5'.
	self assertFieldSelected: 'self take: 5'.
	self assertValuePaneShows: '*navel*'.! !

!CollectionInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 15:38'!
testFieldList

	#(self 'all inst vars') do: [:label | self assertFieldVisible: label].
	1 to: self object size do: [:index | self assertFieldVisible: index printString].! !

!CollectionInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 15:52'!
testRemoveElement
	"Remove an element from the collection-under-inspection by selecting any element's field first and then removing that selected element."
	
	| element |
	self assert: self object size > 1.
	self inspector selectFieldSuchThat: [:field | field type = #element].

	element := self inspector selection.
	self assert: (self object includes: element).
	
	self inspector removeSelection.
	self deny: (self object includes: element).

	"The next remaining element will automatically be selected."
	self assert: #element equals: self inspector selectedField type.
	self assert: (self object includes: self inspector selection).! !

!CollectionInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 17:47'!
testUninitialized
	"Single stepping through a debugger can observe the object state after creation but before initialization. Thus 'object size' may throw an exception for trying to do arithmetic on nil."
	
	self inspector selectFieldNamed: 'self'.
	self assertFieldSelected: 'self'.
	self assertValuePaneWorks.
	
	self inspector object: self object class basicNew.
	self assertFieldSelected: 'self'.
	self denyValuePaneWorks. "It's okay because the inspector is still working."! !

!CollectionInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 17:52'!
testValuePaneModify

	| overwrittenElement |
	self inspector selectFieldSuchThat: [:field | field type = #element].
	overwrittenElement := self inspector selection.

	self assert: (self object includes: overwrittenElement).
	self deny: (self object includes: #ontario).
		
	self inValuePaneTypeAndAccept: '#ontario'.
	self assertValuePaneShows: '#ontario'.
	
	self deny: (self object includes: overwrittenElement).
	self assert: (self object includes: #ontario).! !


!CompiledCodeInspectorTest methodsFor: 'failures' stamp: 'mt 4/14/2020 12:05'!
expectedFieldExpressionFailures

	^ #('source code')! !

!CompiledCodeInspectorTest methodsFor: 'running' stamp: 'mt 4/14/2020 11:32'!
createObject
	"Note that we cannot return the block directly but require the indirection of #evaluate: because the resulting block will be modified during the tests. A block directly embedded in this #createObject method, however, would be re-used across test runs."
	
	InnerTestObject := super createObject.
	^ Compiler new
		evaluate: '[String withAll: #[67 97 114 112 101] "Carpe", #Squeak, InnerTestObject printString] compiledBlock'
		in: nil
		to: self "Required for access to InnerTestObject"! !

!CompiledCodeInspectorTest methodsFor: 'running' stamp: 'mt 4/14/2020 11:32'!
evaluateObject

	^ (FullBlockClosure
		receiver: nil
		outerContext: nil
		method: self object
		copiedValues: nil) value! !

!CompiledCodeInspectorTest methodsFor: 'running' stamp: 'mt 4/8/2020 14:35'!
tearDown

	InnerTestObject := nil.
	super tearDown.! !

!CompiledCodeInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 11:35'!
testCustomField

	self
		during: [self inspector addCustomField]
		type: 'self allLiterals'.
	
	self assertFieldVisible: 'self allLiterals'.
	self assertFieldSelected: 'self allLiterals'.
	self assertValuePaneShows: '*#[*]*Squeak*'.! !

!CompiledCodeInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 11:49'!
testFieldList
	
	#(self '*bytecodes*' 'header' 'literal*') do: [:label |
		self assertFieldVisible: label].! !

!CompiledCodeInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 14:28'!
testValuePaneModify
	"Overridden to specify the kind of value to modify in a compiled-code object: the bytecodes. Looking at #createObject, we try to replace the pushConstant of the byte array at 34 with the one at 35. So, the beginning of the resulting string will change from 'CarpeSqueak' to 'SqueakSqueak'."
	
	self assert: 35 equals: (self object at: 38). "pushConstant: #[ ... ]"
	self assert: 36 equals: (self object at: 39). 	"pushConstant: #Squeak"
	self assert: (self evaluateObject beginsWith: 'CarpeSqueak').
		
	self inspector selectFieldNamed: '38'. "pushConstant: #[ ... ]"
	self assertFieldSelected: '38'.
	self inValuePaneTypeAndAccept: '36'. "pushConstant: #Squeak"

	self assert: 36 equals: (self object at: 38). "pushConstant: #Squeak"
	self assert: 36 equals: (self object at: 39). "pushConstant: #Squeak"	
	self assert: (self evaluateObject beginsWith: 'SqueakSqueak').! !

!CompiledCodeInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 14:28'!
testValuePaneModifyLiteral

	self inspector selectFieldSuchThat: [:field |
		field type = #literal and: [field value = #Squeak]].

	self assert: (self evaluateObject beginsWith: 'CarpeSqueak').
	self inValuePaneTypeAndAccept: '#Smalltalk'.	
	self assert: (self evaluateObject beginsWith: 'CarpeSmalltalk').! !

!CompiledCodeInspectorTest methodsFor: 'support - error' stamp: 'mt 4/8/2020 14:36'!
makeObjectInvalid

	InnerTestObject beInvalid.! !

!CompiledCodeInspectorTest methodsFor: 'support - error' stamp: 'mt 4/15/2020 10:02'!
selectInvalidField

	self inspector selectFieldSuchThat: [:field |
		field type = #literal and: [field value "binding" value == InnerTestObject]].! !


!ContextInspectorTest methodsFor: 'support - error' stamp: 'mt 4/8/2020 15:03'!
makeObjectInvalid

	InnerTestObject beInvalid.! !

!ContextInspectorTest methodsFor: 'support - error' stamp: 'mt 4/14/2020 12:26'!
selectInvalidField

	self inspector selectFieldSuchThat: [:field |
		field type = #tempVar and: [field value == InnerTestObject]].! !

!ContextInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 12:50'!
testCustomField

	self
		during: [self inspector addCustomField]
		type: 'self isDead'.
	
	self assertFieldVisible: 'self isDead'.
	self assertFieldSelected: 'self isDead'.
	self assertValuePaneShows: 'false'.! !

!ContextInspectorTest methodsFor: 'tests' stamp: 'ct 1/6/2020 00:48'!
testDebugConstruction

	self shouldntRaiseWhileDebugging: [
		[| foo | (foo := self) yourself] asContext]! !

!ContextInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 12:20'!
testFieldList
	"No need to look for the fields for temporaries because those will be covered in other tests, which is more useful. Only list the mandatory fields here."

	#(self 'all inst vars' 'sender' 'pc' 'stackp' 'method' 'closureOrNil' 'receiver')
		do: [:label | self assertFieldVisible: label].! !

!ContextInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 14:28'!
testValuePaneModify
	"Try to change the values of all arguments and temporary variables. Check if the object-under-inspection receives those changes."

	| testObjectFound |
	testObjectFound := false.
	
	self object tempNames doWithIndex: [:temp :index |
		| prior current input |
		self inspector selectFieldSuchThat: [:field | field type = #tempVar and: [field key = temp]].
		self assertFieldSelected: '*', temp, '*'. "allow bells and whistles"
		
		prior := self object namedTempAt: index.
		self assert: (prior isNumber or: [prior == InnerTestObject]).

		testObjectFound := testObjectFound or: [prior == InnerTestObject].
		current := (prior isNumber ifTrue: [prior + 1] ifFalse: [#smith]).
		input := prior isNumber ifTrue: [self inspector contents, ' +1'] ifFalse: ['#smith'].
		
		self deny: current equals: (self object namedTempAt: index).
		self inValuePaneTypeAndAccept: input.
		self assert: current equals: (self object namedTempAt: index)].
	
	self assert: testObjectFound.! !

!ContextInspectorTest methodsFor: 'running' stamp: 'mt 4/14/2020 12:26'!
createObject

	InnerTestObject := super createObject.
	[[:arg1 :arg2 |
		| temp1 temp2 |
		temp1 := arg1 printString size - 1.
		temp2 := arg2 - 1.
		temp1 / temp2]
	value: InnerTestObject value: 1]
		on: Error do: [:error |
			^ error signalerContext sender copy
				push: 42;
				yourself].
	self error: 'Failed to set up context to inspect'! !

!ContextInspectorTest methodsFor: 'running' stamp: 'mt 4/8/2020 15:01'!
tearDown

	InnerTestObject := nil.
	super tearDown.! !


!ContextVariablesInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 18:23'!
testCustomField

	self
		during: [self inspector addCustomField]
		type: 'thisContext isDead'.
	
	self assertFieldVisible: 'thisContext isDead'.
	self assertFieldSelected: 'thisContext isDead'.
	self assertValuePaneShows: 'false'.! !

!ContextVariablesInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 18:14'!
testFieldList

	#(thisContext 'stack top' 'all temp vars' '*arg*' '*temp*')
		do: [:label | self assertFieldVisible: label].! !

!ContextVariablesInspectorTest methodsFor: 'tests' stamp: 'mt 4/15/2020 10:05'!
testInspectorClass
	"This is inspector is a variation of regular context inspectors and is used in debuggers. So, after calling #inspect: the inspector class will indeed change to the regular one."
	
	| previousInspectorClass |
	self assert: self object inspectorClass ~~ self inspector class.
	previousInspectorClass := self inspector class.
	self inspector inspect: self object.
	self deny: previousInspectorClass equals: self inspector class.
	self assert: self object inspectorClass equals: self inspector class.! !

!ContextVariablesInspectorTest methodsFor: 'failures' stamp: 'mt 4/14/2020 18:26'!
expectedFieldExpressionFailures

	^ #('stack top')! !


!DictionaryInspectorTest methodsFor: 'running' stamp: 'mt 4/15/2020 09:16'!
createObject

	^ Dictionary withAll: {
		1 -> #discovery.
		7 -> #navel.
		11 -> #smith }! !

!DictionaryInspectorTest methodsFor: 'running' stamp: 'mt 4/15/2020 09:18'!
createObjectWithTruncation

	^ (1 to: 150)
		collect: [:number | number -> #genericApple]
		as: Dictionary! !

!DictionaryInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 17:29'!
testAddElement
	"The user will add a new key to the dictionary, not a value behind that key. That value needs to be set separatedly."

	self deny: (self object includesKey: 9).
	
	self
		during: [self inspector addElement]
		type: '3 ** 2'. "9"
	
	self assert: (self object includesKey: 9).
	
	self assertFieldVisible: '9'.
	self assertFieldSelected: '9'.
	
	self assertValuePaneShows: 'nil'.
	self inValuePaneTypeAndAccept: '#ontario'.
	self assertValuePaneShows: '#ontario'.
	
	self assert: #ontario equals: (self object at: 9).! !

!DictionaryInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 16:21'!
testFieldList
	"Check whether the most important fields are visible."
	
	#(self 'all inst vars' tally array) do: [:label |
		self assertFieldVisible: label].
	
	self object keysDo: [:key | self assertFieldVisible: key printString].! !

!DictionaryInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 17:29'!
testObjectChanged

	"1) Add a new key, which adds a new field to the list of fields."
	self denyFieldVisible: '9'.
	self object at: 9 put: nil.
	self denyFieldVisible: '9'.
	self simulateStepping.
	self assertFieldVisible: '9'.

	"2) Change the value behind the key, which changes the value-pane's contents."
	self inspector selectFieldNamed: '9'.
	self assertFieldSelected: '9'.
	self assertValuePaneShows: 'nil'.
	self object at: 9 put: #ontario.
	self assertValuePaneShows: 'nil'.
	self simulateStepping.
	self assertValuePaneShows: '#ontario'.! !


!InspectorTest class methodsFor: 'testing' stamp: 'ct 12/13/2019 17:24'!
shouldInheritSelectors

	^ true! !


!InspectorTestInspector methodsFor: 'fields - streaming' stamp: 'mt 4/8/2020 14:27'!
streamFieldsOn: aStream
	
	self error.! !


!InspectorTestObject methodsFor: 'printing' stamp: 'mt 4/7/2020 17:48'!
printOn: aStream

	aStream nextPutAll: 'Today''s offers: '.
	self fruits do: [:fruit | aStream print: fruit].! !

!InspectorTestObject methodsFor: 'initialization' stamp: 'mt 4/8/2020 14:25'!
beInvalid

	self apple: 5.! !

!InspectorTestObject methodsFor: 'accessing' stamp: 'mt 4/7/2020 17:46'!
apple

	^ apple! !

!InspectorTestObject methodsFor: 'accessing' stamp: 'mt 4/8/2020 14:06'!
apple: aSymbol

	apple := aSymbol.! !

!InspectorTestObject methodsFor: 'accessing' stamp: 'mt 4/7/2020 17:49'!
fruits

	^ {self apple. self orange} select: [:fruit | fruit notNil and: [fruit size > 0]]! !

!InspectorTestObject methodsFor: 'accessing' stamp: 'mt 4/7/2020 17:46'!
orange

	^ orange! !

!InspectorTestObject methodsFor: 'accessing' stamp: 'mt 4/8/2020 14:07'!
orange: aSymbol

	orange := aSymbol.! !


!InspectorTestObject class methodsFor: 'instance creation' stamp: 'mt 4/8/2020 14:25'!
newInvalid
	"Creates an instance that cannot #printOn: without raising an error."

	^ self new
		beInvalid;
		yourself! !


!InstanceBrowser methodsFor: 'private' stamp: 'tfel 9/23/2016 13:13'!
setClassAndSelectorIn: csBlock
	| cm |
	super setClassAndSelectorIn: [:class :selector |
		(class notNil and: [selector notNil]) ifTrue: [^ csBlock value: class value: selector].
		cm := targetClass
					lookupSelector: (self selection asString findTokens: Character space) first asSymbol.
		cm ifNotNil: [^ csBlock value: (cm methodClass ifNil: [targetClass]) value: cm selector]].
	^ csBlock value: nil value: nil! !


!Morph methodsFor: '*Tools-Inspector' stamp: 'mt 4/2/2020 16:39'!
inspectorClass

	^ MorphInspector! !


!MorphExtension methodsFor: '*60Deprecated-other' stamp: 'mt 4/6/2020 09:28'!
inspectElement

	self deprecated: 'Use MorphInspector. Also see Inspector >> #inspectOne'.! !


!MorphInspector methodsFor: 'fields' stamp: 'mt 4/2/2020 16:41'!
fieldExtent

	^ (self newFieldForType: #misc key: #extent)
		name: 'extent' translated; emphasizeName;
		valueGetter: [:morph | morph extent];
		valueSetter: [:morph :newExtent | morph extent: newExtent];
		yourself! !

!MorphInspector methodsFor: 'fields - streaming' stamp: 'mt 4/2/2020 16:42'!
streamBaseFieldsOn: aStream

	super streamBaseFieldsOn: aStream.
	aStream nextPut: self fieldExtent.! !

!MorphInspector methodsFor: 'fields - streaming' stamp: 'mt 4/6/2020 08:51'!
streamInstanceVariablesOn: aStream

	super streamInstanceVariablesOn: aStream.
	self streamPropertiesOn: aStream.! !

!MorphInspector methodsFor: 'fields - streaming' stamp: 'mt 4/6/2020 18:55'!
streamPropertiesOn: aStream
	"Prepend all properties with # (hash) so that users can distinguish them from regular instance variables. Trigger both #layoutChanged and #changed to be sure that any value changes yield the expected visual updates. Note that this is required because we invade the morph's privacy by exposing its extension object this way; normal updates are handled only through the morph's public interface. For example, compare Morph >> #visible: with MorphExtension >> #visible:."
	
	| extension field |
	(extension := self object extension) ifNil: [^ self].
	
	extension sortedPropertyNames do: [:property |
		(extension respondsTo: property)
			ifTrue: [field := (self newFieldForType: #property key: property)
				name: property printString;
				valueGetter: [:morph | morph extension perform: property];
				valueSetter: [:morph :value |
					morph extension perform: property asSimpleSetter with: value.
					morph layoutChanged; changed];
				yourself]
			ifFalse: [field := (self newFieldForType: #property key: property)
				name: property printString;
				valueGetter: [:morph | morph extension valueOfProperty: property];
				valueSetter: [:morph :value |
					morph extension setProperty: property toValue: value.
					morph layoutChanged; changed];
				yourself].
			
		aStream nextPut: field].! !

!MorphInspector methodsFor: 'morphs' stamp: 'mt 4/6/2020 10:05'!
isMorphSelected

	^ [self selectionOrObject isMorph] ifError: [false]! !

!MorphInspector methodsFor: 'morphs' stamp: 'mt 4/6/2020 09:18'!
selectedMorph

	^ self selectionOrObject! !

!MorphInspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 09:18'!
openScreenshotInHand

	^ self selectedMorph imageForm asMorph openInHand! !

!MorphInspector methodsFor: 'menu - commands' stamp: 'mt 4/6/2020 09:19'!
openScreenshotInWorld

	^ self selectedMorph imageForm asMorph openInWorld! !

!MorphInspector methodsFor: 'menu - construction' stamp: 'mt 4/6/2020 09:17'!
addFieldItemsTo: aMenu

	super addFieldItemsTo: aMenu.

	self isMorphSelected ifFalse: [^ self].
	
	aMenu addLine.
	
	aMenu addTranslatedList: #(
			('open screenshot in hand'			openScreenshotInHand)
			('open screenshot in world'			openScreenshotInWorld)).! !


!ParagraphEditor methodsFor: 'do-its' stamp: 'mt 3/26/2020 15:32'!
inspectIt
	self evaluateSelectionAndDo: [:result | ToolSet inspect: result].
! !


!ProcessBrowser methodsFor: 'process actions' stamp: 'mt 4/3/2020 18:25'!
inspectPointers
	| tc pointers |
	tc := thisContext.
	pointers := PointerFinder
		pointersTo: selectedProcess
		except: { 
			self processList.
			tc.
			self}.
	pointers isEmpty ifTrue: [^ self].
	ToolSet 
		inspect: pointers
		label: 'Objects pointing to ' , selectedProcess browserPrintString! !


!CompiledCode methodsFor: '*Tools-Inspector' stamp: 'mt 4/6/2020 08:27'!
inspectorClass
	"Answer the class of the inspector to be used on the receiver.  Called by inspect; 
	use basicInspect to get a normal (less useful) type of inspector."

	^ CompiledCodeInspector! !


!SetInspector methodsFor: 'private' stamp: 'mt 4/2/2020 16:29'!
elementGetterAt: index

	^ [:set | (set array at: index) enclosedSetElement]! !

!SetInspector methodsFor: 'private' stamp: 'mt 4/6/2020 08:32'!
elementIndices
	"In the set's internal array, extract the indices that point to actual elements."
	
	| numIndices |
	(numIndices := self objectSize) = 0
		ifTrue: [^#()].
	
	^ Array
		new: numIndices
		streamContents: [:stream |
			self object array doWithIndex: [:element :index |
				(self isElementValid: element) ifTrue: [stream nextPut: index]]]! !

!SetInspector methodsFor: 'private' stamp: 'mt 4/14/2020 18:02'!
elementSetterAt: index
	"Because of sets are hashed collections, we have to use the public interface, which means removing the element the index is pointing to first -- and only then can we add the new element."

	^ [:set :element | 
			set remove: (set array at: index) enclosedSetElement.
			set add: element]! !

!SetInspector methodsFor: 'private' stamp: 'mt 4/3/2020 18:43'!
isElementValid: anElement

	^ anElement notNil! !

!SetInspector methodsFor: 'selection' stamp: 'mt 4/14/2020 18:11'!
replaceSelectionValue: anObject
	"After replacing the value, we have to scan for the field that now contains anObject."
	
	(super replaceSelectionValue: anObject) ifTrue: [
		self updateFields.
		self selectFieldSuchThat: [:field | [(field getValueFor: self) == anObject] ifError: [false] ]].! !


!SetInspectorTest methodsFor: 'support - error' stamp: 'mt 4/14/2020 17:45'!
makeObjectInvalid

	self object add: InspectorTestObject newInvalid.
	self simulateStepping.! !

!SetInspectorTest methodsFor: 'support - error' stamp: 'mt 4/14/2020 17:46'!
selectInvalidField

	self inspector selectFieldSuchThat: [:field |
		field type = #element and: [field value class == InspectorTestObject]].! !

!SetInspectorTest methodsFor: 'running' stamp: 'mt 4/14/2020 17:37'!
createObject

	^ Set new
		addAll: #(navel discovery smith boskoop);
		yourself
! !

!SetInspectorTest methodsFor: 'running' stamp: 'mt 4/15/2020 09:19'!
createObjectWithTruncation

	^ (1 to: 150) asSet! !

!SetInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 17:35'!
testAddElement
	"Like super implementation but not checking the field names since we cannot now the exact indices of a set's internal array."

	self deny: (self object includes: 42).
	
	self
		during: [self inspector addElement]
		type: '6 * 7'. "42"

	self assert: (self object includes: 42).
	self assertValuePaneShows: '42'.! !

!SetInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 17:45'!
testFieldList

	#(self 'all inst vars') do: [:label | self assertFieldVisible: label].

	self object do: [:element | self assert: (
		self inspector fields anySatisfy: [:field |
			field type =#element and: [field value == element]] )]! !

!SetInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 17:40'!
testNil
	"Check proper use of a set's enclosed elements."

	self deny: (self object includes: nil).
	self deny: (self inspector fields anySatisfy: [:field | field value isNil]).
	
	self object add: nil.
	self simulateStepping.
	
	self assert: (self inspector fields anySatisfy: [:field | field value isNil]).! !


!StandardToolSet class methodsFor: 'inspecting' stamp: 'ct 1/3/2020 21:33'!
basicInspect: anObject
	"Open a basic inspector on the given object."
	^ BasicInspector openOn: anObject! !


!TextEditor methodsFor: 'do-its' stamp: 'mt 3/26/2020 15:31'!
inspectIt

	 self evaluateSelectionAndDo: [:result |
		(model respondsTo: #inspectIt:result:)
			ifTrue: [model
				perform: #inspectIt:result:
				with: self selection
				with: result]
			ifFalse: [ToolSet inspect: result]].! !


!WeakSet methodsFor: '*Tools-Inspector' stamp: 'ar 9/27/2005 18:33'!
inspectorClass 
	^ WeakSetInspector! !


!WeakSetInspector methodsFor: 'private' stamp: 'mt 4/3/2020 18:49'!
isElementValid: anElement
	"Consider the #flag object, which is used to mark GC'ed elements in the WeakSet."

	^ anElement notNil and: [anElement ~~ (self object instVarNamed: #flag)]! !


!WeakSetInspectorTest methodsFor: 'tests' stamp: 'mt 4/14/2020 18:07'!
testDebugConstruction
	"Ignore."! !

!WeakSetInspectorTest methodsFor: 'tests' stamp: 'mt 4/15/2020 09:57'!
testSymbolTableM6812
	"This test is related to http://bugs.squeak.org/view.php?id=6812. Check whether field selection and garbage collection are somehow interfering."
	
	| getRandomSymbol symbols priorContents currentContents currentIndex |
	self object removeAll.
	
	getRandomSymbol := [ 
		| token |
		token := (1 to: 10) collect: [:ea | ($a to: $z) atRandom] as: String.
		(Symbol lookup: token) ifNil: [token asSymbol] ifNotNil: [nil]].

	symbols := OrderedCollection new.
	10 timesRepeat: [
		getRandomSymbol value ifNotNil: [:symbol | symbols add: symbol]].	

	self object addAll: symbols.
	Smalltalk garbageCollect.
	self assert: symbols size equals: self object size.
	self assert: symbols notEmpty.
	
	1 to: symbols size do: [:round |
		currentIndex := 1.
		symbols removeLast.

		[(currentIndex := currentIndex + 1) <= self inspector fieldList size]
			whileTrue: [
				self inspector selectionIndex: currentIndex.
				self assert: priorContents ~= (currentContents := self inspector contents).
				priorContents := currentContents.

				Smalltalk garbageCollect. "Removes symbol from weak set"
				self simulateStepping. "Removes field from weak-set inspector"]].
	
	self assert: symbols isEmpty.
	self assert: self object isEmpty.! !

!WeakSetInspectorTest methodsFor: 'running' stamp: 'mt 4/14/2020 18:09'!
createObject

	| weakSet |
	weakSet := WeakSet withAll: super createObject.
	Smalltalk garbageCollect.
	^ weakSet! !

WeakSetInspectorTest removeSelector: #createTarget!
WeakSetInspector removeSelector: #arrayWithIndicesDo:!
WeakSetInspector removeSelector: #fieldList!
WeakSetInspector removeSelector: #initialize!
SetInspector subclass: #WeakSetInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!WeakSetInspector reorganize!
('private' isElementValid:)
!

SetInspectorTest removeSelector: #createTacreateObjectrget!
SetInspectorTest removeSelector: #createTarget!
SetInspectorTest removeSelector: #testAddEntry!
SetInspectorTest removeSelector: #testDebugConstruction!
SetInspectorTest removeSelector: #testEllipsis!
SetInspectorTest removeSelector: #testEnclosedSetElements!
SetInspectorTest removeSelector: #testPrintStringError!
SetInspectorTest removeSelector: #testRemoveSelection!
SetInspectorTest removeSelector: #testUninitialized!
SetInspectorTest removeSelector: #testValuePane!

!SetInspectorTest reorganize!
('support - error' makeObjectInvalid selectInvalidField)
('running' createObject createObjectWithTruncation)
('tests' testAddElement testFieldList testNil)
!

SetInspector removeSelector: #arrayIndexForSelection!
SetInspector removeSelector: #arrayWithIndicesDo:!
SetInspector removeSelector: #copyName!
SetInspector removeSelector: #fieldList!
SetInspector removeSelector: #fieldsItemsOn:!
SetInspector removeSelector: #inspectorOverflowText!
SetInspector removeSelector: #itemIndices!
SetInspector removeSelector: #mainFieldListMenu:!
SetInspector removeSelector: #removeSelection!
SetInspector removeSelector: #selection!
SetInspector removeSelector: #streamElementsOn:!

!SetInspector reorganize!
('private' elementGetterAt: elementIndices elementSetterAt: isElementValid:)
('selection' replaceSelectionValue:)
!

OrderedCollection removeSelector: #inspectorClass!

!OrderedCollection reorganize!
('accessing' at: at:ifAbsentPut: at:put: capacity first indexOf:startingAt: last size)
('adding' add: add:after: add:afterIndex: add:before: add:beforeIndex: addAll: addAllFirst: addAllFirstUnlessAlreadyPresent: addAllLast: addFirst: addLast:)
('copying' copyEmpty copyFrom:to: copyReplaceFrom:to:with: copyWith: postCopy postCopyFrom:to:)
('enumerating' collect: collect:from:to: do: occurrencesOf: replace: reverseDo: select: with:collect: withIndexCollect:)
('removing' remove:ifAbsent: removeAll removeAllSuchThat: removeAt: removeFirst removeFirst: removeLast removeLast: reset resetTo:)
('private' collector errorNoSuchElement errorNotEnoughElements find: growAtFirst growAtLast insert:before: makeRoomAtFirst makeRoomAtLast removeIndex: setCollection: setContents:)
('sorting' isSorted isSortedBetween:and: isSortedBy: isSortedBy:between:and: sort sort: sorted:)
('*Morphic-Explorer' hasContentsInExplorer)
('converting' asArray)
('testing' isEmpty)
!

FloatArray removeSelector: #inspectorClass!
CompiledMethod removeSelector: #inspectorClass!
SequenceableCollection removeSelector: #inspectField!

!SequenceableCollection reorganize!
('accessing' after: after:ifAbsent: allButFirst allButFirst: allButLast allButLast: any: anyOne at:ifPresent:ifAbsent: atAllPut: atAll: atAll:putAll: atAll:put: atLast: atLast:ifAbsent: atLast:put: atPin: atRandom: atWrap: atWrap:put: at:ifAbsent: at:incrementBy: before: before:ifAbsent: eighth fifth first first: fourth from:to:put: identityIndexOf: identityIndexOf:ifAbsent: identityIndexOf:startingAt: identityIndexOf:startingAt:ifAbsent: indexOf:startingAt: indexOfAnyOf: indexOfAnyOf:ifAbsent: indexOfAnyOf:startingAt: indexOfAnyOf:startingAt:ifAbsent: indexOfSubCollection: indexOfSubCollection:startingAt: indexOfSubCollection:startingAt:ifAbsent: indexOf: indexOf:ifAbsent: indexOf:startingAt:ifAbsent: integerAt: integerAt:put: last lastIndexOf: lastIndexOf:ifAbsent: lastIndexOf:startingAt: lastIndexOf:startingAt:ifAbsent: last: lastIndexOfAnyOf: lastIndexOfAnyOf:ifAbsent: lastIndexOfAnyOf:startingAt: lastIndexOfAnyOf:startingAt:ifAbsent: middle ninth replaceAll:with: replaceFrom:to:with: replaceFrom:to:with:startingAt: second seventh sixth size swap:with: third)
('comparing' hasEqualElements: hash =)
('printing' joinOn: joinOn:separatedBy:)
('converting' asArray asByteArray asColorArray asFloatArray asIntegerArray asStringWithCr asWordArray concatenation flatten flattened join joinSeparatedBy: readStream reverse reverseInPlace reversed writeStream @)
('copying' copyAfterLast: copyAfter: copyEmpty copyFrom:to: copyLast: copyReplaceAll:with: copyReplaceFrom:to:with: copyUpThrough: copyUpToLast: copyUpTo: copyWithFirst: copyWithoutFirst copyWithoutIndex: copyWith: forceTo:paddingStartWith: forceTo:paddingWith: grownBy: , withoutDuplicates)
('enumerating' allButFirstDo: allButLastDo: asDigitsToPower:do: collectWithIndex: collect: collect:from:to: combinations:atATimeDo: doWithIndex: do: do:separatedBy: do:without: findBinary:do:ifNone: findBinaryIndex: findBinaryIndex:do:ifNone: findBinaryIndex:ifNone: findBinary: findBinary:ifNone: findFirst: findFirst:ifNone: findLast: findLast:startingAt: findNearbyBinaryIndex: from:to:do: groupsDo: groupsOf:atATimeCollect: groupsOf:atATimeDo: keysAndValuesDo: nextToLast overlappingPairsCollect: overlappingPairsDo: overlappingPairsWithIndexDo: paddedWith:do: pairsCollect: pairsDo: permutationsDo: piecesCutWhere: piecesCutWhere:do: polynomialEval: replace: reverseDo: reverseWith:do: select: splitBy: splitBy:do: upTo: withIndexCollect: withIndexDo: with:collect: with:do:)
('removing' remove:ifAbsent:)
('testing' beginsWith: beginsWithAnyOf: endsWith: endsWithAnyOf: includes: isSequenceable)
('*services-base' startsWith:)
('*Traits' asTraitComposition)
('private' asDigitsAt:in:do: checkedAt: combinationsAt:in:after:do: copyReplaceAll:with:asTokens: errorFirstObject: errorLastObject: errorOutOfBounds permutationsStartingAt:do:)
('*Morphic-NewCurves-cubic support' asCubic assertSlopesWith:from:to: changeInSlopes: changeOfChangesInSlopes: closedCubicSlopes closedCubicSlopes: closedFillinList cubicPointPolynomialAt: naturalCubicSlopes naturalCubicSlopes: naturalFillinList nilTransitions segmentedSlopes slopesWith:from:to: transitions transitions:)
('*Morphic-fliprotate' flipRotated:)
('*Morphic-Explorer' explorerContents)
('filter streaming' putOn:)
('shuffling' shuffle shuffleBy: shuffled shuffledBy:)
('*Balloon' asPointArray)
('adding' addAllFirstTo:)
('*Etoys-Squeakland-accessing' customizeExplorerContents)
!

OrderedCollectionInspector removeSelector: #fieldList!
OrderedCollectionInspector removeSelector: #fieldsItemsOn:!
OrderedCollectionInspector removeSelector: #objectSize!
OrderedCollectionInspector removeSelector: #replaceSelectionValue:!
OrderedCollectionInspector removeSelector: #selectedObjectIndex!
OrderedCollectionInspector removeSelector: #selection!

!OrderedCollectionInspector reorganize!
('as yet unclassified')
!


!MorphInspector reorganize!
('fields' fieldExtent)
('fields - streaming' streamBaseFieldsOn: streamInstanceVariablesOn: streamPropertiesOn:)
('morphs' isMorphSelected selectedMorph)
('menu - commands' openScreenshotInHand openScreenshotInWorld)
('menu - construction' addFieldItemsTo:)
!

MorphExtension removeSelector: #inspectField!

!MorphExtension reorganize!
('accessing' actorState actorState: balloonText balloonTextSelector balloonTextSelector: balloonText: eventHandler eventHandler: externalName: locked locked: player player: sticky sticky: visible visible:)
('accessing - layout properties' layoutFrame layoutFrame: layoutPolicy layoutPolicy: layoutProperties layoutProperties:)
('accessing - other properties' assureOtherProperties hasOtherProperties hasProperty: initializeOtherProperties otherProperties privateOtherProperties: removeOtherProperties removeProperty: setProperty:toValue: sortedPropertyNames valueOfProperty: valueOfProperty:ifAbsentPut: valueOfProperty:ifAbsent:)
('*60Deprecated-other' inspectElement)
('connectors-copying' copyWeakly propertyNamesNotCopied veryDeepFixupWith: veryDeepInner:)
('initialization' initialize)
('objects from disk' comeFullyUpOnReload:)
('other' isDefault)
('printing' printOn:)
('viewer' externalName)
('*MorphicExtras-copying' updateReferencesUsing:)
('*MorphicExtras-Undo' removeUndoCommands)
('parts bin' isPartsDonor isPartsDonor:)
('*Etoys-Squeakland-inspecting' inspectAllPropertiesOf: inspectElementFor:)
!


!InspectorTestObject reorganize!
('printing' printOn:)
('initialization' beInvalid)
('accessing' apple apple: fruits orange orange:)
!


!InspectorTestInspector reorganize!
('fields - streaming' streamFieldsOn:)
!

InspectorTest class removeSelector: #isAbstract!
DictionaryInspectorTest removeSelector: #createTarget!
DictionaryInspectorTest removeSelector: #testAddElementMenu!
DictionaryInspectorTest removeSelector: #testAddEntry!
DictionaryInspectorTest removeSelector: #testDebugConstruction!
DictionaryInspectorTest removeSelector: #testEllipsis!
DictionaryInspectorTest removeSelector: #testPrintStringError!
DictionaryInspectorTest removeSelector: #testRemoveSelection!
DictionaryInspectorTest removeSelector: #testUpdate!
DictionaryInspectorTest removeSelector: #testValuePane!
ContextVariablesInspectorTest removeSelector: #inspect:!
ContextVariablesInspectorTest removeSelector: #testPrintStringError!
ContextVariablesInspectorTest removeSelector: #testValuePane!

!ContextVariablesInspectorTest reorganize!
('tests' testCustomField testFieldList testInspectorClass)
('failures' expectedFieldExpressionFailures)
!

ContextInspectorTest removeSelector: #createTarget!
ContextInspectorTest removeSelector: #testModifyArg!
ContextInspectorTest removeSelector: #testModifyValue!
ContextInspectorTest removeSelector: #testPrintStringError!
ContextInspectorTest removeSelector: #testValuePane!

!ContextInspectorTest reorganize!
('support - error' makeObjectInvalid selectInvalidField)
('tests' testCustomField testDebugConstruction testFieldList testValuePaneModify)
('running' createObject tearDown)
!

CompiledCodeInspectorTest removeSelector: #createTarget!
CompiledCodeInspectorTest removeSelector: #testDebugConstruction!
CompiledCodeInspectorTest removeSelector: #testModifyArg!
CompiledCodeInspectorTest removeSelector: #testModifyLiteral!
CompiledCodeInspectorTest removeSelector: #testModifyValue!
CompiledCodeInspectorTest removeSelector: #testPrintStringError!

!CompiledCodeInspectorTest reorganize!
('failures' expectedFieldExpressionFailures)
('running' createObject evaluateObject tearDown)
('tests' testCustomField testFieldList testValuePaneModify testValuePaneModifyLiteral)
('support - error' makeObjectInvalid selectInvalidField)
!

CollectionInspectorTest removeSelector: #createTarget!
CollectionInspectorTest removeSelector: #testAddEntry!
CollectionInspectorTest removeSelector: #testDebugConstruction!
CollectionInspectorTest removeSelector: #testEllipsis!
CollectionInspectorTest removeSelector: #testPrintStringError!
CollectionInspectorTest removeSelector: #testRemoveSelection!
CollectionInspectorTest removeSelector: #testValuePane!
CollectionInspectorTest removeSelector: #typeOfIndexedVariable!

!CollectionInspectorTest reorganize!
('running' createObject createObjectWithTruncation)
('support' fieldTypeOfIndexedVariable)
('support - error' makeObjectInvalid selectInvalidField)
('tests - special' testAddElementError testAddElementMenuHidden)
('tests' testAddElement testAddElementMenu testCustomField testFieldList testRemoveElement testUninitialized testValuePaneModify)
!

ClassInspectorTest removeSelector: #createTarget!
ClassInspectorTest removeSelector: #testModifyValue!
ClassInspectorTest removeSelector: #testPrintStringError!
ClassInspectorTest removeSelector: #testValuePane!

!ClassInspectorTest reorganize!
('tests' testCustomField testFieldList testPoolDictionaries testValuePaneModify)
('running' createObject tearDown)
('support - error' makeObjectInvalid selectInvalidField)
!

BasicInspectorTest removeSelector: #createObject!
BasicInspectorTest removeSelector: #createTarget!
BasicInspectorTest removeSelector: #expectedFailures!
BasicInspectorTest removeSelector: #inspect:!
BasicInspectorTest removeSelector: #testValuePane!

!BasicInspectorTest reorganize!
('tests' testFieldList testFieldSelf)
('support - error' selectInvalidField)
('failures' expectedFieldExpressionFailures)
!

InspectorTest removeSelector: #createTarget!
InspectorTest removeSelector: #inspect:!
InspectorTest removeSelector: #inspectorClass!
InspectorTest removeSelector: #setTarget:!
InspectorTest removeSelector: #shouldValuePaneContain:!
InspectorTest removeSelector: #shouldntValuePaneContain:!
InspectorTest removeSelector: #testCustomFieldError!
InspectorTest removeSelector: #testEllipsis!
InspectorTest removeSelector: #testMenus!
InspectorTest removeSelector: #testModifyValue!
InspectorTest removeSelector: #testMorphic!
InspectorTest removeSelector: #testMvc!
InspectorTest removeSelector: #testPrintStringError!
InspectorTest removeSelector: #testPrintStringErrorSetting:!
InspectorTest removeSelector: #typeOfIndexedVariable!
InspectorTest removeSelector: #update:!
InspectorTest removeSelector: #valuePaneContents!

!InspectorTest reorganize!
('assertions - ui' assertFieldSelected: assertFieldVisible: assertNoFieldSelected assertValuePaneShows: denyFieldSelected: denyFieldVisible: denyNoFieldSelected denyValuePaneShows:)
('support' fieldListMenu fieldTypeOfIndexedVariable)
('assertions - matching' assert:matches: comparingStringBetweenMatch:and: deny:matches:)
('assertions' assertMenuWorks assertValuePaneWorks denyValuePaneWorks shouldntRaiseWhileDebugging:)
('accessing' inspector object)
('support - ui' during:confirm: during:type: inValuePaneTypeAndAccept: simulateStepping)
('failures' expectedFieldExpressionFailures)
('running' createObject createObjectWithTruncation setUp)
('support - error' makeObjectInvalid selectInvalidField)
('tests - special' testFieldListError testObjectChanged testTruncationEllipsis testTruncationEllipsisMenu testTruncationTail)
('tests' testCustomField testCustomFieldRemove testDebugConstruction testExpressions testFieldList testFieldListMenu testFieldSelf testInspectorClass testValuePane testValuePaneError testValuePaneModify)
!

InspectorField class removeSelector: #requestCustomFor:!
InspectorField class removeSelector: #requestCustomFor:orCancel:!
InspectorField removeSelector: #addCustomItemsForInspector:to:!
InspectorField removeSelector: #addEtoysItemsFor:to:!
InspectorField removeSelector: #addObjectItemsFor:to:!
InspectorField removeSelector: #beSpecial!
InspectorField removeSelector: #beVerySpecial!
InspectorField removeSelector: #editTitle!
InspectorField removeSelector: #editTitleOrCancel:!
InspectorField removeSelector: #expression!
InspectorField removeSelector: #expression:!
InspectorField removeSelector: #generateExpressionFrom:argumentNames:!
InspectorField removeSelector: #instVarName!
InspectorField removeSelector: #isCustomFIeld!
InspectorField removeSelector: #isModifiable!
InspectorField removeSelector: #isProtected!
InspectorField removeSelector: #isProtected:!
InspectorField removeSelector: #isSpecial!
InspectorField removeSelector: #isTitleStylable!
InspectorField removeSelector: #isVerySpecial!
InspectorField removeSelector: #makeTitleStylable!
InspectorField removeSelector: #makeTitleStylable:!
InspectorField removeSelector: #requestCode:initialAnswer:orCancel:!
InspectorField removeSelector: #requestCode:orCancel:!
InspectorField removeSelector: #specialTitle:!
InspectorField removeSelector: #stringGetter:!
InspectorField removeSelector: #stylableTitle:!
InspectorField removeSelector: #title!
InspectorField removeSelector: #title:!
InspectorField removeSelector: #titleStyledWith:!
InspectorField removeSelector: #valueBeString!
InspectorField removeSelector: #valueIsString!
InspectorField removeSelector: #valueIsString:!

!InspectorField reorganize!
('menu - construction' addCustomItemsFor:to:)
('accessing' key key: name name: type type: value value:)
('custom - actions' delete editGetterFor: editGetterFor:orCancel: editName editNameOrCancel: editSetterFor: editSetterFor:orCancel:)
('custom' requestCustomFor:orCancel: setGetterFor:to:ifFail: setSetterFor:to:ifFail:)
('private' forgetInspector inspector rememberInspector)
('evaluating' getValueFor: setValueFor:to:)
('initialization' deEmphasizeName emphasizeName printValueAsIs)
('testing' isCustom isReadOnly)
('printing' printOn:)
('accessing - code' expressionWithReceiverName: valueGetter valueGetter: valueGetterExpression valueGetterExpression: valueSetter valueSetter: valueSetterExpression valueSetterExpression:)
('accessing - printing' shouldPrintValueAsIs shouldPrintValueAsIs: shouldStyleName shouldStyleName: shouldStyleValue shouldStyleValue:)
!


!InspectorBrowser class reorganize!
('inspector compatibility' basicInspect: inspect:)
('instance creation' on: openOn: openOn:withLabel:)
!

InspectorBrowser removeSelector: #browser!
InspectorBrowser removeSelector: #release!
InspectorBrowser removeSelector: #updateBrowser!
Model subclass: #InspectorBrowser
	instanceVariableNames: 'inspector browser'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!InspectorBrowser reorganize!
('initialization' initialExtent initialize inspect: setBrowserClass: setInspectorClass:)
('toolbuilder' buildWith: labelString)
('accessing' object object:)
('stepping' modelWakeUpIn: stepAt:in: stepTimeIn: updateListsAndCodeIn: wantsStepsIn:)
('updating' update:)
!

HtmlEntityInspector removeSelector: #fieldList!
HtmlEntityInspector removeSelector: #selection!
ExternalStructureInspector removeSelector: #fieldList!
ExternalStructureInspector removeSelector: #replaceSelectionValue:!
ExternalStructureInspector removeSelector: #selection!

!ExternalStructureInspector reorganize!
('accessing' recordFieldList)
('fields' fieldSelf fieldsRecordsOn: streamFieldsOn:)
!

BagInspector removeSelector: #addEntry:!
BagInspector removeSelector: #calculateKeyArray!
BagInspector removeSelector: #itemIndices!
BagInspector removeSelector: #removeSelection!
BagInspector removeSelector: #streamElementsOn:!

!BagInspector reorganize!
('private' elementGetterAt: elementSetterAt:)
('menu commands' addElement: removeSelectedElement)
('initialization' elementIndices)
('bindings' isBindingSelected)
!

DictionaryInspector removeSelector: #addEntry!
DictionaryInspector removeSelector: #addEntry:!
DictionaryInspector removeSelector: #basicTextForTruncationOf:!
DictionaryInspector removeSelector: #calculateKeyArray!
DictionaryInspector removeSelector: #contentsIsString!
DictionaryInspector removeSelector: #copyName!
DictionaryInspector removeSelector: #fieldList!
DictionaryInspector removeSelector: #fieldsItemsOn:!
DictionaryInspector removeSelector: #initialize!
DictionaryInspector removeSelector: #initializeObject!
DictionaryInspector removeSelector: #isSelectionBinding!
DictionaryInspector removeSelector: #itemIndices!
DictionaryInspector removeSelector: #mainFieldListMenu:!
DictionaryInspector removeSelector: #numberOfFixedFields!
DictionaryInspector removeSelector: #removeSelection!
DictionaryInspector removeSelector: #renameEntry!
DictionaryInspector removeSelector: #renameEntry:!
DictionaryInspector removeSelector: #replaceSelectionValue:!
DictionaryInspector removeSelector: #resetFields!
DictionaryInspector removeSelector: #selection!
DictionaryInspector removeSelector: #streamElementsOn:!
DictionaryInspector removeSelector: #updateEntries!
CollectionInspector subclass: #DictionaryInspector
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!DictionaryInspector reorganize!
('menu - construction' addFieldItemsTo:)
('menu - commands' addElement addElement: inspectKey removeSelectedElement renameKey renameKey: sendersOfSelectedKey usersOfSelectedBinding)
('bindings' isBindingSelected selectedBinding)
('ui requests' requestKeyInitialAnswer:orCancel: requestKeyOrCancel:)
('selection' selectKey: selectedKey)
('*60Deprecated-menu commands' refreshView selectionReferences)
('private' canAddOrRemoveElements elementIndices)
!

ContextVariablesInspector removeSelector: #aboutToStyle:requestor:!
ContextVariablesInspector removeSelector: #contentsIsString!
ContextVariablesInspector removeSelector: #defaultIntegerBase!
ContextVariablesInspector removeSelector: #fieldList!
ContextVariablesInspector removeSelector: #fieldsTempVarsOn:!
ContextVariablesInspector removeSelector: #inspect:!
ContextVariablesInspector removeSelector: #replaceSelectionValue:!
ContextVariablesInspector removeSelector: #selection!
ContextVariablesInspector removeSelector: #streamFieldsOn:!
ContextVariablesInspector removeSelector: #streamStackVariablesOn:!
ContextVariablesInspector removeSelector: #tempsAndValues!
ContextInspector subclass: #ContextVariablesInspector
	instanceVariableNames: ''
	classVariableNames: 'ShowStackVariables'
	poolDictionaries: ''
	category: 'Tools-Debugger'!

!ContextVariablesInspector reorganize!
('code' doItContext doItReceiver)
('fields - streaming' streamBaseFieldsOn: streamIndexedVariablesOn: streamInstanceVariablesOn: streamTemporaryVariablesOn:)
('fields' fieldAllTempVars fieldSelf fieldStackTop)
('private' expressionForField:)
!

ContextInspector removeSelector: #fieldList!
ContextInspector removeSelector: #fieldsStackOn:!
ContextInspector removeSelector: #fieldsTempVarsOn:!
ContextInspector removeSelector: #selection!

!ContextInspector reorganize!
('fields - streaming' streamFieldsOn: streamIndexedVariablesOn: streamInstanceVariablesOn: streamStackVariablesOn: streamTemporaryVariablesOn:)
!

CompiledCodeInspector removeSelector: #contentsIsString!
CompiledCodeInspector removeSelector: #fieldList!
CompiledCodeInspector removeSelector: #fieldsItemsOn:!
CompiledCodeInspector removeSelector: #fieldsLiteralsOn:!
CompiledCodeInspector removeSelector: #selection!
CompiledCodeInspector removeSelector: #selectionUnmodifiable!
CompiledCodeInspector removeSelector: #streamFieldsOn:!

!CompiledCodeInspector reorganize!
('fields - streaming' streamBaseFieldsOn: streamByteCodesOn: streamIndexedVariablesOn: streamLiteralsOn:)
('fields' fieldByteCodes fieldDecompile fieldHeader fieldSource)
('user interface - styling' updateStyler:requestor:)
!

BitsetInspector removeSelector: #itemIndices!
BitsetInspector removeSelector: #removeSelection!
BitsetInspector removeSelector: #streamElementsOn:!

!BitsetInspector reorganize!
('fields' fieldSize)
('private' elementIndices objectSize)
('fields - streaming' streamBaseFieldsOn:)
('menu - commands' addElement: removeSelectedElement)
!

CollectionInspector removeSelector: #addEntry!
CollectionInspector removeSelector: #addEntry:!
CollectionInspector removeSelector: #addFieldItemsTo:!
CollectionInspector removeSelector: #arrayWithIndicesDo:!
CollectionInspector removeSelector: #assertItemSelectedOr:!
CollectionInspector removeSelector: #chooseElement!
CollectionInspector removeSelector: #inspectOneFrom:to:!
CollectionInspector removeSelector: #inspectSingleElement!
CollectionInspector removeSelector: #itemIndices!
CollectionInspector removeSelector: #numberOfFixedFields!
CollectionInspector removeSelector: #streamFieldsOn:!
CollectionInspector removeSelector: #truncatedObjectAt:!
CollectionInspector removeSelector: #truncationGetterAt:!

!CollectionInspector reorganize!
('menu - construction' addCollectionItemsTo:)
('menu' inspectorKey:from:)
('menu - commands' addElement addElement: inspectOne removeSelectedElement removeSelection)
('private' assertElementSelectedOr: canAddOrRemoveElements elementGetterAt: elementIndices elementSetterAt: objectSize)
('ui requests' requestObject:initialAnswer:orCancel: requestObject:orCancel:)
('fields - streaming' streamElementsOn: streamIndexedVariablesOn:)
('fields - truncation')
('selection' selectElementAt: selectedElementIndex)
!

ClassInspector removeSelector: #fieldsClassVarsOn:!
ClassInspector removeSelector: #fieldsPoolDictionariesOn:!
ClassInspector removeSelector: #streamFieldsOn:!
BasicInspector removeSelector: #fieldClass!
BasicInspector removeSelector: #fieldSize!

!BasicInspector reorganize!
('initialization' basicObjectPrintString inspect: labelString)
('fields' fieldObjectClass fieldObjectSize fieldSelf)
('fields - streaming' streamBaseFieldsOn: streamIndexedVariablesOn: streamInstanceVariablesOn:)
!

Inspector removeSelector: #accept:!
Inspector removeSelector: #accept:notifying:!
Inspector removeSelector: #baseFieldList!
Inspector removeSelector: #basicTextForTruncationOf:!
Inspector removeSelector: #chasePointers!
Inspector removeSelector: #chooseObjectField!
Inspector removeSelector: #contentsForError!
Inspector removeSelector: #contentsIsString!
Inspector removeSelector: #convertToCurrentVersion:refStream:!
Inspector removeSelector: #createFields!
Inspector removeSelector: #defaultIntegerBase!
Inspector removeSelector: #defsOfSelection!
Inspector removeSelector: #disableValuePaneStyling!
Inspector removeSelector: #dropOnFieldList:at:!
Inspector removeSelector: #emphasizeErrorContents:!
Inspector removeSelector: #enableValuePaneStyling!
Inspector removeSelector: #explorePointers!
Inspector removeSelector: #expressionWithBracketsForField:!
Inspector removeSelector: #fieldsInstVarsOn:!
Inspector removeSelector: #fieldsItemsOn:!
Inspector removeSelector: #generateContentsString!
Inspector removeSelector: #helpText!
Inspector removeSelector: #i1!
Inspector removeSelector: #i2!
Inspector removeSelector: #initializeObject!
Inspector removeSelector: #inspectBasic!
Inspector removeSelector: #inspectElement!
Inspector removeSelector: #inspectObjectField!
Inspector removeSelector: #inspectOneFrom:to:!
Inspector removeSelector: #inspectOneThreshold!
Inspector removeSelector: #inspectSingleElement!
Inspector removeSelector: #maximumIndicesSize!
Inspector removeSelector: #minimumLastIndicesSize!
Inspector removeSelector: #preserveSelectionAndEditsAround:!
Inspector removeSelector: #printStringErrorText!
Inspector removeSelector: #privateToggleIndex:!
Inspector removeSelector: #referencesToSelection!
Inspector removeSelector: #removeSelectedField!
Inspector removeSelector: #requestCode:initialAnswer:orCancel:!
Inspector removeSelector: #requestCode:orCancel:!
Inspector removeSelector: #requestCompiledCode:initialAnswer:orCancel:!
Inspector removeSelector: #requestCompiledCode:orCancel:!
Inspector removeSelector: #restoreSelectionAfter:!
Inspector removeSelector: #selectionIsSpecial!
Inspector removeSelector: #selectionIsVerySpecial!
Inspector removeSelector: #selectionOrObjectField!
Inspector removeSelector: #selectionPrintString!
Inspector removeSelector: #selectionUnmodifiable!
Inspector removeSelector: #shouldStyleValuePane!
Inspector removeSelector: #streamError:doing:on:!
Inspector removeSelector: #streamOn:from:collectFields:!
Inspector removeSelector: #streamOn:truncate:collectFields:ellipsisFromText:!
Inspector removeSelector: #styler!
Inspector removeSelector: #textForTruncationOf:!
Inspector removeSelector: #timeOfLastListUpdate!
Inspector removeSelector: #toggleIndex:!
Inspector removeSelector: #trash!
Inspector removeSelector: #trash:!
Inspector removeSelector: #truncatedObjectAt:!
Inspector removeSelector: #truncationGetterAt:!
Inspector removeSelector: #updateContents!
Inspector removeSelector: #updateEntries!
Inspector removeSelector: #viewerForValue!
Inspector removeSelector: #wantsDropOnFieldList:type:source:!
Inspector removeSelector: #wantsSteps!
StringHolder subclass: #Inspector
	instanceVariableNames: 'object context fields customFields selectionIndex expression contentsTyped fieldListStyler shouldStyleValuePane selectionUpdateTime'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tools-Inspector'!

!Inspector reorganize!
('accessing - contents' contents:notifying: contentsTyped contentsTyped: expression expression:)
('accessing' context context: customFields doItContext doItReceiver fields object object: selectionIndex selectionIndex:)
('initialization' fieldClass initialExtent initialize inspect: resetContents resetFields setContents: setContentsTyped: setExpression:)
('menu - private' elementAt: elementGetterAt:)
('menu - commands' browseClass browseClassHierarchy browseVariableAssignments browseVariableReferences chaseSelectionPointers copyExpression copyName exploreSelection exploreSelectionPointers inspectOne inspectOneOf: inspectOneOfFrom:to: inspectSelection inspectSelectionBasic objectReferencesToSelection removeSelection)
('*60Deprecated-selecting' selectedSlotName)
('updating - steps' modelWakeUpIn: stepAt:in: stepTimeIn: updateListsAndCodeIn: wantsStepsIn:)
('fields - error handling' contentsForErrorDoing: emphasizeError: streamError:on: streamErrorDoing:on:)
('toolbuilder' buildCodePaneWith: buildExploreButtonWith: buildFieldListWith: buildValuePaneWith: buildWith: replaceInspectorWithExplorer)
('*Protocols-Tools' browseFullProtocol spawnFullProtocol spawnProtocol)
('*Etoys-menu commands' tearOffTile)
('fields - drag and drop' dragFromFieldList: dropOnFieldList:at:shouldCopy:)
('user interface - styling' aboutToStyle:requestor: fieldListStyler typeValue: updateStyler: updateStyler:requestor:)
('*60Deprecated-toolbuilder' exploreObject)
('user interface - window' labelString okToClose okToDiscardCustomFields)
('user interface' applyUserInterfaceTheme fieldList getContents representsSameBrowseeAs: textColorForError valuePane)
('selection - convenience' classOfSelection selectedClass selectedInstVarName selectionIsReadOnly selectionOrObject typeOfSelection)
('selection' ensureSelectedField hasSelection noteSelectionIndex:for: replaceSelectionValue: selectField: selectFieldNamed: selectFieldSuchThat: selectedField selectedFieldName selection)
('menu - construction' addClassItemsTo: addCollectionItemsTo: addEtoysItemsTo: addFieldItemsTo: addInstVarItemsTo: addObjectItemsTo:)
('menu' fieldListMenu: fieldListMenu:shifted: inspectorKey:from: mainFieldListMenu: metaFieldListMenu:)
('updating' update update: update:with: updateContentsSafely updateFieldList updateFields)
('fields - truncation' contentsForTruncationOf: streamOn:truncate:collectFields: streamOn:truncate:collectFields:ellipsisFrom: truncationLimit truncationTail)
('fields - streaming' streamBaseFieldsOn: streamCustomFieldsOn: streamFieldsOn: streamIndexedVariablesOn: streamInstanceVariablesOn: streamVariableFieldsOn:)
('*60Deprecated-menu' classHierarchy)
('fields' expressionForField: fieldAllInstVars fieldSelf newFieldForType: newFieldForType:key:)
('fields - custom' addCustomField addCustomField: hasCustomFields newCustomField removeCustomField: requestCustomFieldOrCancel:)
!

HtmlEntity removeSelector: #inspect!
HtmlEntity removeSelector: #inspectWithLabel:!

!Debugger reorganize!
('accessing' contents contents:notifying: contextStackTop contextVariablesInspector debuggerMap doNothing: interruptedContext interruptedProcess labelString labelString: proceedValue proceedValue: receiver receiverInspector)
('*60Deprecated-context stack menu' abandon: proceed:)
('*60Deprecated-private' lowSpaceChoices)
('*60Deprecated-accessing' receiverInspectorObject:context:)
('class list' selectedClass selectedClassOrMetaClass)
('code pane' aboutToStyle: codePaneSelectionInterval contentsSelection doItContext doItReceiver pc pcRange)
('code pane menu' debuggerCodePaneMenu: perform:orSendTo: runToSelection: runUntil)
('actions - convenience' showFullStack showWhere stepInto stepOver stepThrough)
('context stack menu' abandon browseMessages browseSendersOfMessages browseVersions contextStackKey:from: contextStackMenu:shifted: copyBugReportToClipboard debugProceedMenu: doStep down fullStack handleLabelUpdatesIn:whenExecuting: mailOutBugReport mainContextStackMenu: messageListMenu:shifted: peelToFirst proceed removeMessage restart returnValue selectPC send shiftedContextStackMenu: stepIntoBlock tryRestartFrom: up where)
('context stack - message list' contextStackIndex contextStackList expandNotifierStack expandStack fullyExpandStack messageHelpAt: messageIconAt: messageListIndex selectedMessage selectedMessageName toggleContextStackIndex:)
('stepping - morphic' step updateInspectors wantsSteps)
('initialize' close context: customButtonSpecs initialExtent initialExtentForNotifier initialize initializeFull openFullFromNotifier: openFullNoSuspendLabel: openNotifierNoSuspendContents:label: preDebugButtonQuads process:context: windowIsClosing)
('testing' interruptedProcessIsActive interruptedProcessShouldResume isFull isNotifier)
('message category list' selectedMessageCategoryName)
('notifier menu' debug sendReport storeLog)
('toolbuilder' browseClassHierarchy buildCodePaneWith: buildControlButtonsWith: buildFullWith: buildNotifierWith:label:message: buildWith: contextStackFrame controlButtonsFrame optionalButtonsFrame preDebugButtonQuadFrame preDebugMessageString receiverClass textFrame wantsAnnotationPane wantsCodeProvenanceButton wantsOptionalButtons)
('private' checkContextSelection contextStackIndex:oldContextWas: cutBackExecutionToSenderContext externalInterrupt: newStack: pushStubMethodOnStack:inClass:inCategory: resetContext: resetContext:changeContents: resumeProcess: selectedContext)
('notifier support' askForCategoryIn:default: askForSuperclassOf:toImplement:ifCancel: askForSuperclassOf:upTo:toImplement:ifCancel: implementMissingMethod:inClass: implementMissingMethod:inClass:inCategory: implementOverridingMethod:inClass:inCategory:)
('notifier buttons' createImplementingMethod createMethod createOverridingMethod debugAt:)
('tally support' getSelectedText tally)
('self-updating' updateCodePaneIfNeeded)
('user interface' defaultWindowColor keyForContextVariablesInspectorState keyForReceiverInspectorState restoreContextVariablesInspectorState restoreReceiverInspectorState saveContextVariablesInspectorState saveReceiverInspectorState)
('*Etoys-Squeakland-initialize' buttonRowForPreDebugWindow: preDebugNotifierContentsFrom:)
('context stack (message list)' findCleanHomeBelow:)
('*60Deprecated-toolbuilder' classHierarchy)
!


!Bitset reorganize!
('comparing' = hash)
('adding' add:)
('accessing' at: at:put: capacity size)
('*Tools-Inspector' inspectorClass)
('bit manipulation' bitAt: bitAt:put: clearBitAt: setBitAt:)
('private' bytes initialize:)
('enumerating' do: occurrencesOf:)
('testing' includes: isEmpty)
('copying' postCopy)
('removing' remove:ifAbsent: removeAll)
('printing' printElementsOn:separatedBy:)
!

Object removeSelector: #inspectFieldOrSelf!
"Postscript:"

(Smalltalk globals at: #ObjectsUnderInspection ifAbsent: [#()])
	do: [:objectUnderInspection |
		ToolSet inspect: objectUnderInspection].
Smalltalk globals removeKey: #ObjectsUnderInspection.!

> 

-------------- next part --------------
'From Squeak6.0alpha of 19 January 586155 [latest update: #19595] on 21 April 2020 at 9:00:47 pm'!"Change Set:		InspectorRefactoringComments-dtlDate:			21 April 2020Author:			David T LewisSome class comments to go along with the new inspector refactoring."!!BitsetInspector commentStamp: 'dtl 4/21/2020 19:13' prior: 0!I am an inspector for bit sets. I display bits with zero based indexing corresponding to the bit numbering conventions of a bit field.!!HtmlEntityInspector commentStamp: 'dtl 4/21/2020 20:00' prior: 0!I am an inspector for HTML entities.!!MorphInspector commentStamp: 'dtl 4/21/2020 19:57' prior: 0!I am an inspector for morphs. In addition to field values I display properties of the morph, and add additional selections to the field item menu.!!HtmlEntityInspector reorganize!('toolbuilder' initialExtent)('fields' fieldHtml streamFieldsOn:)!


More information about the Squeak-dev mailing list