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

Marcel Taeumel marcel.taeumel at hpi.de
Wed Apr 22 16:12:17 UTC 2020


Hi Eliot!

Here is a change set that shows how you would implement that inspetor for CogProcessorAlien in this refactored Inspector framework. :-)


Best,
Marcel
Am 22.04.2020 08:09:13 schrieb Marcel Taeumel <marcel.taeumel at hpi.de>:
Hi Dave.

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

Thank you. :-)

> so I am attaching a change set with suggested comments.

Yeah! Thank you very much!

>  what is the field items menu on an inspector

Yellow/right click on an item in the list of fields. If you happen to have the vertical scroll bar with its menu button visible, you can also click there. Take a look at the attached screenshot.

Best,
Marcel
Am 22.04.2020 03:14:17 schrieb David T. Lewis <lewis at mail.msen.com>:
+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 :
> 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 :
> 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 im Auftrag von St??phane Rollandin
> 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: '' 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" 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 pragma if it had a priority argument!!" self addEtoysItemsTo: aMenu]. ^ aMenu! ! !Inspector methodsFor: 'menu' stamp: 'ct 3/15/2020 20:14'! metaFieldListMenu: aMenu 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 ^ ('' 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 ^ 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
to get 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
to set 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: ''. inspector ensureSelectedField. self assertFieldSelected: ''. 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 --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20200422/2031c555/attachment-0001.html>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: image.png
Type: image/png
Size: 30196 bytes
Desc: not available
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20200422/2031c555/attachment-0001.png>
-------------- next part --------------
An embedded and charset-unspecified text was scrubbed...
Name: cog-processor-alien-inspector-revised.1.cs
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20200422/2031c555/attachment-0001.ksh>


More information about the Squeak-dev mailing list