I took the inspector from Pharo20 and I will check if it is working in Pharo.
Then I will
- check EyeInspector from a package perspective (extensions and the rest)
    - make sure that we can remove EyeInspector
    - package the attached file as BasicInspector.

Now if you want to help you are welcome.

Stef
Model subclass: #Inspector
        instanceVariableNames: 'contents object selectionIndex 
timeOfLastListUpdate selectionUpdateTime'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tools-Inspector'!
!Inspector commentStamp: '<historical>' prior: 0!
I represent a query path into the internal representation of an object. As a 
StringHolder, the string I represent is the value of the currently selected 
variable of the observed object.!


!Inspector methodsFor: '*Polymorph-TaskbarIcons' stamp: 'FernandoOlivero 
4/12/2011 09:47'!
taskbarIcon 
        ^ self theme smallInspectItIcon! !


!Inspector methodsFor: '*Shout-Parsing' stamp: 'SeanDeNigris 6/22/2012 18:34'!
shoutParser: anSHParserST80

        anSHParserST80 isMethod: false.! !


!Inspector methodsFor: '*Shout-Styling' stamp: 'GuillermoPolito 1/17/2012 
14:09'!
shoutAboutToStyle: aPluggableShoutMorphOrView 
        aPluggableShoutMorphOrView getTextSelector == self trashSelector 
ifFalse: [ ^false ].
        aPluggableShoutMorphOrView classOrMetaClass: self object class.
        ^ true! !


!Inspector methodsFor: '*necompletion' stamp: 'SeanDeNigris 7/7/2012 22:49'!
guessTypeForName: aString

        self flag: 'we may be able to do something more sophisticated here, but 
needed something to prevent a DNU. Returning nil was taken from AbstractTool. 
See Debugger or Workspace for actual guessing logic'.
        ^ nil.! !

!Inspector methodsFor: '*necompletion' stamp: 'SeanDeNigris 6/22/2012 16:21'!
isCodeCompletionAllowed

        ^ true.! !


!Inspector methodsFor: 'accessing'!
baseFieldList
        "Answer an Array consisting of 'self'
        and the instance variable names of the inspected object."

        ^ (Array with: 'self' with: 'all inst vars')
                        , object class allInstVarNames! !

!Inspector methodsFor: 'accessing' stamp: 'GuillermoPolito 8/12/2010 14:52'!
contents
        ^contents! !

!Inspector methodsFor: 'accessing' stamp: 'GuillermoPolito 8/12/2010 14:52'!
contentsSelection
        "Return the interval of text in the code pane to select when I set the 
pane's contents"

        ^ 1 to: 0  "null selection"! !

!Inspector methodsFor: 'accessing'!
fieldList
        "Answer the base field list plus an abbreviated list of indices."

        object class isVariable ifFalse: [^ self baseFieldList].
        ^ self baseFieldList ,
                (object basicSize <= (self i1 + self i2)
                        ifTrue: [(1 to: object basicSize)
                                                collect: [:i | i printString]]
                        ifFalse: [(1 to: self i1) , (object basicSize-(self 
i2-1) to: object basicSize)
                                                collect: [:i | i 
printString]])! !

!Inspector methodsFor: 'accessing'!
i1
        "This is the max index shown before skipping to the 
        last i2 elements of very long arrays"
        ^ 100! !

!Inspector methodsFor: 'accessing'!
i2
        "This is the number of elements to show at the end
        of very long arrays"
        ^ 10! !

!Inspector methodsFor: 'accessing' stamp: 'al 9/21/2008 19:40'!
initialExtent
        "Answer the desired extent for the receiver when it is first opened on 
the screen.  "

        ^ 350 @ 300! !

!Inspector methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'!
modelWakeUpIn: aWindow
        | newText |
        self updateListsAndCodeIn: aWindow.
        newText := self contentsIsString
                ifTrue: [newText := self selection]
                ifFalse: ["keep it short to reduce time to compute it"
                        self selectionPrintString ].
        newText = contents ifFalse:
                [contents := newText.
                self changed: #contents]! !

!Inspector methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'!
noteSelectionIndex: anInteger for: aSymbol
        aSymbol == #fieldList
                ifTrue:
                        [selectionIndex := anInteger]! !

!Inspector methodsFor: 'accessing'!
object
        "Answer the object being inspected by the receiver."

        ^object! !

!Inspector methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'!
object: anObject 
        "Set anObject to be the object being inspected by the receiver."

        | oldIndex |
        anObject == object
                ifTrue: [self update]
                ifFalse:
                        [oldIndex := selectionIndex <= 2 ifTrue: 
[selectionIndex] ifFalse: [0].
                        self inspect: anObject.
                        oldIndex := oldIndex min: self fieldList size.
                        self changed: #inspectObject.
                        oldIndex > 0
                                ifTrue: [self toggleIndex: oldIndex].
                        self changed: #fieldList.
                        self changed: #contents]! !

!Inspector methodsFor: 'accessing' stamp: 'tk 4/18/1998 15:37'!
selectedClass
        "Answer the class of the receiver's current selection"

        self selectionUnmodifiable ifTrue: [^ object class].
        ^ self selection class! !

!Inspector methodsFor: 'accessing' stamp: 'MarcusDenker 4/14/2011 10:52'!
selectedClassOrMetaClass

        ^ self selectedClass! !

!Inspector methodsFor: 'accessing' stamp: 'sma 6/15/2000 16:48'!
stepTimeIn: aSystemWindow
        ^ (selectionUpdateTime ifNil: [0]) * 10 max: 1000! !

!Inspector methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'!
timeOfLastListUpdate
        ^ timeOfLastListUpdate ifNil: [timeOfLastListUpdate := 0]! !

!Inspector methodsFor: 'accessing' stamp: 'GuillermoPolito 8/12/2010 14:53'!
trash
        "What should be displayed if a trash pane is restored to initial state"

        ^ ''! !

!Inspector methodsFor: 'accessing' stamp: 'tk 6/11/1998 22:23'!
trash: newText
        "Don't save it"
        ^ true! !

!Inspector methodsFor: 'accessing' stamp: 'GuillermoPolito 1/17/2012 14:11'!
trashSelector
        "It is the selector to access the trash in the inspector"
        ^#trash! !

!Inspector methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'!
update
        "Reshow contents, assuming selected value may have changed."

        selectionIndex = 0
                ifFalse:
                        [self contentsIsString
                                ifTrue: [contents := self selection]
                                ifFalse: [contents := self 
selectionPrintString].
                        self changed: #contents.
                        self changed: #selection.
                        self changed: #selectionIndex]! !

!Inspector methodsFor: 'accessing' stamp: 'di 1/13/1999 14:36'!
wantsSteps
        ^ true! !


!Inspector methodsFor: 'as yet unclassified' stamp: 'IgorStasenko 9/2/2012 
17:03'!
exploreStrongPointers
        self selectionIndex = 0 ifTrue: [^ self changed: #flash].
        Smalltalk tools strongPointerExplorer openOn: self selection! !


!Inspector methodsFor: 'code'!
doItReceiver
        "Answer the object that should be informed of the result of evaluating a
        text selection."

        ^object! !


!Inspector methodsFor: 'initialization' stamp: 'CamilloBruni 2/28/2012 11:44'!
initialize
        
        selectionIndex := 1.
        super initialize! !

!Inspector methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:27'!
inspect: anObject 
        "Initialize the receiver so that it is inspecting anObject. There is no 
current selection.
        
        Normally the receiver will be of the correct class (as defined by 
anObject inspectorClass),
        because it will have just been created by sedning 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.  Care should be taken if this method is 
overridden to
        ensure that the overriding code calls 'super inspect: anObject', or 
otherwise ensures that 
        the class of these embedded inspectors are changed back."

        | c |
        c := anObject inspectorClass.
        (self class ~= c and: [self class format = c format]) ifTrue: [
                self primitiveChangeClassTo: c basicNew].
        
        "Set 'object' before sending the initialize message, because some 
implementations
        of initialize (e.g., in DictionaryInspector) require 'object' to be 
non-nil."
        
        object := anObject. 
        self initialize! !


!Inspector methodsFor: 'menu commands' stamp: 'BenjaminVanRyseghem 2/8/2012 
17:08'!
browseClass
        "Open an class browser on this class and method"

        ^ self selectedClassOrMetaClass ifNotNil: [
                Smalltalk tools browser newOnClass: self 
selectedClassOrMetaClass ]! !

!Inspector methodsFor: 'menu commands' stamp: 'DiegoFernandez 6/9/2011 19:32'!
browseClassRefs

        | class |
        class := self selectedClass theNonMetaClass ifNil: [^self].
        class isTrait 
                ifTrue: [self systemNavigation browseAllUsersOfTrait: class]
                ifFalse: [self systemNavigation browseAllCallsOnClass: class]! !

!Inspector methodsFor: 'menu commands' stamp: 'CamilloBruni 8/1/2012 16:01'!
browseClassVariables
        "Browse the class variables of the selected class."
        | cls |
        cls := self selectedClass.
        (cls notNil and: [cls isTrait not])
                ifTrue: [self systemNavigation  browseClassVariables: cls]
! !

!Inspector methodsFor: 'menu commands' stamp: 'DiegoFernandez 6/9/2011 19:33'!
browseInstVarDefs 

        | cls |
        cls := self selectedClassOrMetaClass.
        (cls notNil and: [cls isTrait not])
                ifTrue: [self systemNavigation browseInstVarDefs: cls]
! !

!Inspector methodsFor: 'menu commands' stamp: 'DiegoFernandez 6/9/2011 19:34'!
browseInstVarRefs
        "1/26/96 sw: real work moved to class, so it can be shared"
        | cls |
        cls := self selectedClassOrMetaClass.
        (cls notNil and: [cls isTrait not])
                ifTrue: [self systemNavigation browseInstVarRefs: cls]! !

!Inspector methodsFor: 'menu commands' stamp: 'MarcusDenker 7/12/2012 18:00'!
browseMethodFull

        self selectedClassOrMetaClass 
                ifNotNil: [:selectedClass | SystemNavigation new browseClass: 
selectedClass]! !

!Inspector methodsFor: 'menu commands' stamp: 'DiegoFernandez 6/9/2011 19:07'!
classHierarchy
        "Create and schedule a class list browser on the receiver's hierarchy."

        self systemNavigation
                browseHierarchy: self selectedClassOrMetaClass ! !

!Inspector methodsFor: 'menu commands' stamp: 'tk 4/10/1998 17:53'!
classOfSelection
        "Answer the class of the receiver's current selection"

        self selectionUnmodifiable ifTrue: [^ object class].
        ^ self selection class! !

!Inspector methodsFor: 'menu commands' stamp: 'sd 11/20/2005 21:27'!
classVarRefs
        "Request a browser of methods that store into a chosen instance 
variable"

        | aClass |
        (aClass := self classOfSelection) ifNotNil:
                [self systemNavigation  browseClassVarRefs: aClass].
! !

!Inspector methodsFor: 'menu commands' stamp: 'EstebanLorenzano 1/31/2013 
19:24'!
codePaneMenu: aMenu shifted: shifted 
        "Note that unless we override perform:orSendTo:, 
        PluggableTextController will respond to all menu items in a 
        text pane"
        | donorMenu |
        donorMenu := shifted
                ifTrue: [SmalltalkEditor shiftedYellowButtonMenu]
                ifFalse: [SmalltalkEditor yellowButtonMenu].
        ^ aMenu addAllFrom: donorMenu! !

!Inspector methodsFor: 'menu commands' stamp: 'sd 11/20/2005 21:27'!
copyName
        "Copy the name of the current variable, so the user can paste it into 
the 
        window below and work with is. If collection, do (xxx at: 1)."
        | sel aClass variableNames |
        self selectionUnmodifiable
                ifTrue: [^ self changed: #flash].
        aClass := self object class.
        variableNames := aClass allInstVarNames.
        (aClass isVariable and: [selectionIndex > (variableNames size + 2)])
                ifTrue: [sel := '(self basicAt: ' , (selectionIndex - 
(variableNames size + 2)) asString , ')']
                ifFalse: [sel := variableNames at: selectionIndex - 2].
        (self selection isKindOf: Collection)
                ifTrue: [sel := '(' , sel , ' at: 1)'].
        Clipboard clipboardText: sel asText! !

!Inspector methodsFor: 'menu commands' stamp: 'sd 11/20/2005 21:27'!
defsOfSelection
        "Open a browser on all defining references to the selected instance 
variable, if that's what currently selected. "
        | aClass sel |

        self selectionUnmodifiable ifTrue: [^ self changed: #flash].
        (aClass := self object class) isVariable ifTrue: [^ self changed: 
#flash].

        sel := aClass allInstVarNames at: self selectionIndex - 2.
        self systemNavigation  browseAllStoresInto: sel from: aClass! !

!Inspector methodsFor: 'menu commands' stamp: 'GuillermoPolito 8/13/2010 00:12'!
doItContext
        "Answer the context in which a text selection can be evaluated."

        ^nil! !

!Inspector methodsFor: 'menu commands' stamp: 'IgorStasenko 1/22/2012 14:40'!
explorePointers
        self selectionIndex = 0 ifTrue: [^ self changed: #flash].
        Smalltalk tools pointerExplorer openOn: self selection! !

!Inspector methodsFor: 'menu commands' stamp: 'sw 9/21/1999 12:16'!
exploreSelection

        self selectionIndex = 0 ifTrue: [^ self changed: #flash].
        ^ self selection explore! !

!Inspector methodsFor: 'menu commands' stamp: 'EstebanLorenzano 1/31/2013 
19:25'!
fieldListMenu: aMenu
        "Arm the supplied menu with items for the field-list of the receiver"

        aMenu addStayUpItemSpecial.
        ^aMenu addAllFromPragma: 'inspectorFieldListMenu' target: self.
! !

!Inspector methodsFor: 'menu commands' stamp: 'tk 4/12/1998 08:49'!
inspectBasic
        "Bring up a non-special inspector"

        selectionIndex = 0 ifTrue: [^ object basicInspect].
        self selection basicInspect! !

!Inspector methodsFor: 'menu commands' stamp: 'StephaneDucasse 5/28/2011 13:40'!
inspectElement
        "Create and schedule an Inspector on an element of the receiver's 
model's currently selected collection."
        | sel selSize countString count nameStrs |
        self selectionIndex = 0 ifTrue: [ ^ self changed: #flash ].
        ((sel := self selection) isKindOf: SequenceableCollection) ifFalse: 
                [ (sel isKindOf: MorphExtension) ifTrue: [ ^ sel inspectElement 
].
                ^ sel inspect ].
        (selSize := sel size) = 1 ifTrue: [ ^ sel first inspect ].
        selSize <= 20 ifTrue: 
                [ nameStrs := (1 to: selSize) asArray collect: 
                        [ :ii | 
                        ii printString , '   ' , (((sel at: ii) 
printStringLimitedTo: 25) 
                                        replaceAll: Character cr
                                        with: Character space) ].
                count := UIManager default 
                        chooseFrom: nameStrs substrings
                        title: 'which element?'.
                count = 0 ifTrue: [ ^ self ].
                ^ (sel at: count) inspect ].
        countString := UIManager default 
                request: 'Which element? (1 to ' , selSize printString , ')'
                initialAnswer: '1'.
        countString isEmptyOrNil ifTrue: [ ^ self ].
        count := Integer readFrom: countString readStream.
        (count > 0 and: [ count <= selSize ]) 
                ifTrue: [ (sel at: count) inspect ]
                ifFalse: [ Beeper beep ]! !

!Inspector methodsFor: 'menu commands' stamp: 'apb 7/14/2004 13:16'!
inspectSelection
        "Create and schedule an Inspector on the receiver's model's currently 
selected object."

        self selectionIndex = 0 ifTrue: [^ self changed: #flash].
        self selection inspect.
        ^ self selection! !

!Inspector methodsFor: 'menu commands' stamp: 'MarcusDenker 5/7/2012 15:12'!
inspectorKey: aChar from: view
        "Respond to a Command key issued while the cursor is over my field list"

        aChar == $i ifTrue: [^ self selection inspect].
        aChar == $I ifTrue: [^ self selection explore].
        aChar == $b ifTrue:     [^ self browseMethodFull].
        aChar == $h ifTrue:     [^ self classHierarchy].
        aChar == $c ifTrue: [^ self copyName].
        aChar == $N ifTrue: [^ self browseClassRefs].

        ^ false! !

!Inspector methodsFor: 'menu commands' stamp: 'CamilloBruni 8/1/2012 16:15'!
referencesToSelection
        "Open a browser on all references to the selected instance variable, if 
that's what currently selected."
        | aClass sel |

        self selectionUnmodifiable ifTrue: [^ self changed: #flash].
        (aClass := self object class) isVariable ifTrue: [^ self changed: 
#flash].

        sel := aClass allInstVarNames at: self selectionIndex - 2.
        self systemNavigation   browseAllAccessesTo: sel from: aClass! !


!Inspector methodsFor: 'selecting' stamp: 'damiencassou 5/30/2008 16:29'!
accept: aString 
        | result |
        result := self doItReceiver class evaluatorClass new 
                evaluate: aString readStream
                in: self doItContext
                to: self doItReceiver
                notifying: nil
                ifFail: 
                        [ "fix this"
                        self changed: #flash.
                        ^ false ].
        result == #failedDoit ifTrue: [ ^ false ].
        self replaceSelectionValue: result.
        self changed: #contents.
        ^ true! !

!Inspector methodsFor: 'selecting' stamp: 'di 9/22/1998 21:24'!
contentsIsString
        "Hacked so contents empty when deselected and = long printString when 
item 2"

        ^ (selectionIndex = 2) | (selectionIndex = 0)! !

!Inspector methodsFor: 'selecting' stamp: 'nice 11/8/2009 15:17'!
replaceSelectionValue: anObject 
        "The receiver has a list of variables of its inspected object. One of 
these 
        is selected. The value of the selected variable is set to the value, 
        anObject."
        | basicIndex si instVarIndex |
        selectionIndex <= 2 ifTrue: [
                self toggleIndex: (si := selectionIndex).  
                self toggleIndex: si.
                ^ object].
        instVarIndex := selectionIndex - 2.
        instVarIndex > object class instSize
                ifFalse: [^ object instVarAt: instVarIndex put: anObject].
        object class isVariable or: [self error: 'Cannot replace selection'].
        basicIndex := selectionIndex - 2 - object class instSize.
        (object basicSize <= (self i1 + self i2)  or: [basicIndex <= self i1])
                ifTrue: [^object basicAt: basicIndex put: anObject]
                ifFalse: [^object basicAt: object basicSize - (self i1 + self 
i2) + basicIndex
                                        put: anObject]! !

!Inspector methodsFor: 'selecting' stamp: 'eem 5/21/2008 11:46'!
selectedSlotName

        ^ self fieldList at: self selectionIndex ifAbsent: []! !

!Inspector methodsFor: 'selecting' stamp: 'sd 11/20/2005 21:27'!
selection
        "The receiver has a list of variables of its inspected object.
        One of these is selected. Answer the value of the selected variable."
        | basicIndex |
        selectionIndex = 0 ifTrue: [^ ''].
        selectionIndex = 1 ifTrue: [^ object].
        selectionIndex = 2 ifTrue: [^ object longPrintStringLimitedTo: 20000].
        (selectionIndex - 2) <= object class instSize
                ifTrue: [^ object instVarAt: selectionIndex - 2].
        basicIndex := selectionIndex - 2 - object class instSize.
        (object basicSize <= (self i1 + self i2)  or: [basicIndex <= self i1])
                ifTrue: [^ object basicAt: basicIndex]
                ifFalse: [^ object basicAt: object basicSize - (self i1 + self 
i2) + basicIndex]! !

!Inspector methodsFor: 'selecting'!
selectionIndex
        "The receiver has a list of variables of its inspected object. One of 
these 
        is selected. Answer the index into the list of the selected variable."

        ^selectionIndex! !

!Inspector methodsFor: 'selecting' stamp: 'apb 8/20/2004 22:03'!
selectionPrintString
        | text |
        selectionUpdateTime := [text := [self selection printStringLimitedTo: 
5000]
                                                on: Error
                                                do: [text := self 
printStringErrorText.
                                                        text
                                                                addAttribute: 
TextColor red
                                                                from: 1
                                                                to: text size.
                                                        text]] timeToRun.
        ^ text! !

!Inspector methodsFor: 'selecting' stamp: 'PHK 6/30/2004 11:50'!
selectionUnmodifiable
        "Answer if the current selected variable is modifiable via acceptance 
in the code pane.  For most inspectors, no selection and a selection of 'self' 
(selectionIndex = 1) and 'all inst vars' (selectionIndex = 2) are unmodifiable"

        ^ selectionIndex <= 2! !

!Inspector methodsFor: 'selecting' stamp: 'sd 11/20/2005 21:27'!
toggleIndex: anInteger
        "The receiver has a list of variables of its inspected object. One of 
these 
        is selected. If anInteger is the index of this variable, then deselect 
it. 
        Otherwise, make the variable whose index is anInteger be the selected 
        item."

        selectionUpdateTime := 0.
        selectionIndex = anInteger
                ifTrue: 
                        ["same index, turn off selection"
                        selectionIndex := 0.
                        contents := '']
                ifFalse:
                        ["different index, new selection"
                        selectionIndex := anInteger.
                        self contentsIsString
                                ifTrue: [contents := self selection]
                                ifFalse: [contents := self 
selectionPrintString]].
        self changed: #selection.
        self changed: #contents.
        self changed: #selectionIndex.! !


!Inspector methodsFor: 'stepping' stamp: 'AlainPlantec 12/1/2009 22:37'!
stepAt: millisecondClockValue in: aWindow
        | newText |

        (CodeHolder smartUpdating and: [(millisecondClockValue - self 
timeOfLastListUpdate) > 8000]) "Not more often than once every 8 seconds"
                ifTrue:
                        [self updateListsAndCodeIn: aWindow.
                        timeOfLastListUpdate := millisecondClockValue].

        newText := self contentsIsString
                ifTrue: [self selection]
                ifFalse: ["keep it short to reduce time to compute it"
                        self selectionPrintString ].
        newText = contents ifFalse:
                [contents := newText.
                self changed: #contents]! !


!Inspector methodsFor: 'theme' stamp: 'MarcusDenker 4/14/2011 10:46'!
theme   
        ^ UITheme current! !


!Inspector methodsFor: 'private' stamp: 'ClementBera 11/15/2012 09:10'!
numberOfFixedFields
        ^ 2 + object class instSize! !

!Inspector methodsFor: 'private' stamp: 'sd 11/20/2005 21:27'!
printStringErrorText
        | nm |
        nm := self selectionIndex < 3
                                        ifTrue: ['self']
                                        ifFalse: [self selectedSlotName].
        ^ ('<error in printString: evaluate "' , nm , ' printString" to 
debug>') asText.! !

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

Inspector class
        instanceVariableNames: ''!

!Inspector class methodsFor: '*Polymorph-TaskbarIcons' stamp: 'FernandoOlivero 
4/12/2011 09:47'!
taskbarIcon
        "Answer the icon for the receiver in a task bar."

        ^self theme smallInspectItIcon! !


!Inspector class methodsFor: 'instance creation' stamp: 'al 9/21/2008 19:41'!
horizontalDividerProportion
        ^ 0.4! !

!Inspector class methodsFor: 'instance creation' stamp: 'PHK 7/22/2004 17:04'!
inspect: anObject 
        "Answer an instance of me to provide an inspector for anObject."
        
        "We call basicNew to avoid a premature initialization; the instance 
method 
        inspect: anObject will do a self initialize."

        ^self basicNew inspect: anObject! !

!Inspector class methodsFor: 'instance creation' stamp: 'BenjaminVanRyseghem 
10/25/2012 15:30'!
openAsMorphOn: anObject withEvalPane: withEval withLabel: label valueViewClass: 
valueViewClass
        "Note: for now, this always adds an eval pane, and ignores the 
valueViewClass"

        UsersManager default currentUser canInspect ifFalse: [ ^ self ].
        ^ (self openAsMorphOn: anObject withLabel: label) openInWorld! !

!Inspector class methodsFor: 'instance creation' stamp: 'MarcusDenker 11/2/2012 
15:08'!
openAsMorphOn: anObject withLabel: aLabel 
        "(Inspector openAsMorphOn: SystemOrganization withLabel: 'Test') 
openInWorld"
        | window inspector |
        inspector := self inspect: anObject.
        window := (SystemWindow labelled: aLabel)
                                model: inspector.
        window
                addMorph: ((PluggableListMorph new doubleClickSelector: 
#inspectSelection;
                                
                                on: inspector
                                list: #fieldList
                                selected: #selectionIndex
                                changeSelected: #toggleIndex:
                                menu: #fieldListMenu:
                                keystroke: #inspectorKey:from:) 
                                autoDeselect: false )
                                "For doubleClick to work best disable 
autoDeselect"
                frame: (0 @ 0 corner: self horizontalDividerProportion @ self 
verticalDividerProportion).
        window
                addMorph: (PluggableTextMorph
                                on: inspector
                                text: #contents
                                accept: #accept:
                                readSelection: #contentsSelection
                                menu: #codePaneMenu:shifted:)
                frame: (self horizontalDividerProportion @ 0 corner: 1 @ self 
verticalDividerProportion).
        window
                addMorph: ((PluggableTextMorph
                                on: inspector
                                text: inspector trashSelector
                                accept: inspector trashSelector asMutator
                                readSelection: #contentsSelection
                                menu: #codePaneMenu:shifted:)
                                askBeforeDiscardingEdits: false;
                                font: StandardFonts codeFont)
                frame: (0 @ self verticalDividerProportion corner: 1 @ 1).
        window setUpdatablePanesFrom: #(#fieldList ).
        window position: 16 @ 0.
        "Room for scroll bar."
        ^ window

! !

!Inspector class methodsFor: 'instance creation' stamp: 'ar 9/27/2005 18:30'!
openOn: anObject
        "Create and schedule an instance of me on the model, anInspector. "

        ^ self openOn: anObject withEvalPane: true! !

!Inspector class methodsFor: 'instance creation'!
openOn: anObject withEvalPane: withEval 
        "Create and schedule an instance of me on the model, anInspector. "

        ^ self openOn: anObject withEvalPane: withEval withLabel: anObject 
defaultLabelForInspector! !

!Inspector class methodsFor: 'instance creation' stamp: 'alain.plantec 
6/10/2008 18:35'!
openOn: anObject withEvalPane: withEval withLabel: label 
        ^ self
                openAsMorphOn: anObject
                withEvalPane: withEval
                withLabel: label
                valueViewClass: nil! !

!Inspector class methodsFor: 'instance creation' stamp: 'sw 1/19/1999 14:38'!
verticalDividerProportion
        ^ 0.7! !


!Inspector class methodsFor: 'menu' stamp: 'EstebanLorenzano 1/31/2013 18:32'!
menuFieldList: aBuilder
        <contextMenu>
        <inspectorFieldListMenu>
        
        | target selection |
        
        target := aBuilder model.
        selection := target selection.
        
        (aBuilder item: #'Inspect')
                keyText: 'i';
                selector: #inspectSelection;
                icon: UITheme current smallInspectItIcon.
        (aBuilder item: #'Explore')
                keyText: 'I';
                selector: #exploreSelection;
                icon: UITheme current smallInspectItIcon.
                
        (((selection isMemberOf: Array) or: [selection isMemberOf: 
                OrderedCollection]) and: [ selection size > 0]) 
                ifTrue: [
                        (aBuilder item: #'Inspect element...')
                                selector: #inspectElement ].

        (selection isKindOf: MorphExtension) 
                ifTrue: [
                        (aBuilder item: #'Inspect property...')
                                selector: #inspectElement ].
                                                        
        aBuilder withSeparatorAfter.            
        (aBuilder item: #'Method refs to this inst var')
                selector: #referencesToSelection.
        (aBuilder item: #'Methods storing into this inst var')
                selector: #defsOfSelection.
        (aBuilder item: #'Explore pointers')
                selector: #explorePointers.
        (aBuilder item: #'Explore strong pointers')
                selector: #exploreStrongPointers;
                withSeparatorAfter.
                
        (aBuilder item: #'Browse full')
                keyText: 'b';
                selector: #browseMethodFull.
        (aBuilder item: #'Browse class')
                selector: #browseClass.
        (aBuilder item: #'Browse hierarchy')
                keyText: 'h';
                selector: #classHierarchy;
                withSeparatorAfter.
                
        (aBuilder item: #'Inst var refs...')
                selector: #browseInstVarRefs.
        (aBuilder item: #'Inst var defs...')
                selector: #browseInstVarDefs.
        (aBuilder item: #'Class var refs...')
                selector: #classVarRefs.
        (aBuilder item: #'Class variables')
                selector: #browseClassVariables.
        (aBuilder item: #'Class refs')
                keyText: 'N';
                selector: #browseClassRefs;
                withSeparatorAfter.
                
        (aBuilder item: #'Copy name')
                keyText: 'c';
                selector: #copyName.
        (aBuilder item: #'Basic inspect')
                selector: #inspectBasic.
! !


!Inspector class methodsFor: 'tools registry' stamp: 'IgorStasenko 2/19/2011 
02:58'!
registerToolsOn: registry
        "Add ourselves to registry. See [Smalltalk tools]" 
        registry register: self as: #inspector
! !

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

!CompiledMethodInspector methodsFor: 'accessing' stamp: 'sd 11/20/2005 21:27'!
fieldList

        | keys |
        keys := OrderedCollection new.
        keys add: 'self'.
        keys add: 'all bytecodes'.
        keys add: 'header'.
        1 to: object numLiterals do: [ :i |
                keys add: 'literal', i printString ].
        object initialPC to: object size do: [ :i |
                keys add: i printString ].
        ^ keys asArray
        ! !


!CompiledMethodInspector methodsFor: 'selecting' stamp: 'ajh 3/20/2003 00:17'!
contentsIsString
        "Hacked so contents empty when deselected"
 
        ^ #(0 2 3) includes: selectionIndex! !

!CompiledMethodInspector methodsFor: 'selecting' stamp: 'sd 11/20/2005 21:27'!
selection

        | bytecodeIndex |
        selectionIndex = 0 ifTrue: [^ ''].
        selectionIndex = 1 ifTrue: [^ object ].
        selectionIndex = 2 ifTrue: [^ object symbolic].
        selectionIndex = 3 ifTrue: [^ object headerDescription].
        selectionIndex <= (object numLiterals + 3) 
                ifTrue: [ ^ object objectAt: selectionIndex - 2 ].
        bytecodeIndex := selectionIndex - object numLiterals - 3.
        ^ object at: object initialPC + bytecodeIndex - 1! !

!CompiledMethodInspector methodsFor: 'selecting' stamp: 'ajh 3/20/2001 11:56'!
selectionUnmodifiable
        "Answer if the current selected variable is unmodifiable via acceptance 
in the code pane.  For most inspectors, no selection and a selection of self 
(selectionIndex = 1) are unmodifiable"
 
        ^ true! !

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

CompiledMethodInspector class
        instanceVariableNames: ''!

!CompiledMethodInspector class methodsFor: 'as yet unclassified' stamp: 
'IgorStasenko 2/20/2011 15:12'!
registerToolsOn: registry
        "Register ourselves as inspector for CompiledMethod"
        
         
        registry registerInspector: self for: CompiledMethod
! !


Inspector subclass: #IntegerInspector
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tools-Inspector'!
!IntegerInspector commentStamp: '<historical>' prior: 0!
I am IntegerInspector.
I am an Inspector.

I am a specialized Inspector for Integers.
I add extra representations (hex, octal, binary) of the Integer object that I 
am inspecting.!


!IntegerInspector methodsFor: 'accessing' stamp: 'SvenVanCaekenberghe 
11/26/2012 14:08'!
binary
        "Answer a binary representation of the Integer object I am inspecting"

        ^ self printStringBase: 2! !

!IntegerInspector methodsFor: 'accessing' stamp: 'SvenVanCaekenberghe 
11/26/2012 14:07'!
fieldList
        "Answer the base field list plus our custom representations."

        ^ self baseFieldList , self representations! !

!IntegerInspector methodsFor: 'accessing' stamp: 'SvenVanCaekenberghe 
11/26/2012 14:08'!
hex
        "Answer a hexadecimal representation of the Integer object I am 
inspecting"

        ^ self printStringBase: 16! !

!IntegerInspector methodsFor: 'accessing' stamp: 'SvenVanCaekenberghe 
11/26/2012 14:08'!
octal
        "Answer an octal representation of the Integer object I am inspecting"

        ^ self printStringBase: 8! !

!IntegerInspector methodsFor: 'accessing' stamp: 'SvenVanCaekenberghe 
11/26/2012 14:09'!
printStringBase: base
        "Answer a representation of the Integer object I am inspecting in the 
given base."

        ^ String streamContents: [ :stream | object printOn: stream base: base 
showRadix: true ]! !

!IntegerInspector methodsFor: 'accessing' stamp: 'SvenVanCaekenberghe 
11/26/2012 14:09'!
representations
        "Return the list of representations that I support.
        For each of these there must be a corresponding method."
        
        ^ #( hex octal binary )! !


!IntegerInspector methodsFor: 'selecting' stamp: 'SvenVanCaekenberghe 
11/26/2012 14:19'!
replaceSelectionValue: anObject
        "The receiver has a list of variables of its inspected object. One of 
these 
        is selected. The value of the selected variable is set to the value, 
anObject."

        selectionIndex <= self numberOfFixedFields
                ifTrue: [ ^ super replaceSelectionValue: anObject ]     
        "My own fields are readonly"! !

!IntegerInspector methodsFor: 'selecting' stamp: 'SvenVanCaekenberghe 
11/26/2012 14:03'!
selection
        "The receiver has a list of variables of its inspected object.
        One of these is selected. Answer the value of the selected variable."

        ^ self selectionIndex <= self numberOfFixedFields
                ifTrue: [ super selection ]
                ifFalse: [ self perform: (self representations at: self 
selectionIndex - self numberOfFixedFields) ]! !


Inspector subclass: #SetInspector
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tools-Inspector'!
!SetInspector commentStamp: '<historical>' prior: 0!
A verison of the Inspector specialized for inspecting Sets.  It displays 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.!


!SetInspector methodsFor: 'accessing' stamp: 'PHK 6/29/2004 14:50'!
fieldList
        object
                ifNil: [^ Set new].
        ^ self baseFieldList
                , (object array
                                withIndexCollect: [:each :i | each ifNotNil: [i 
printString]])
                  select: [:each | each notNil]! !


!SetInspector methodsFor: 'menu' stamp: 'EstebanLorenzano 1/31/2013 19:25'!
fieldListMenu: aMenu
        ^aMenu addAllFromPragma: 'setInspectorFieldListMenu' target: self.
! !

!SetInspector methodsFor: 'menu' stamp: 'sd 11/20/2005 21:27'!
removeSelection
        (selectionIndex <= object class instSize) ifTrue: [^ self changed: 
#flash].
        object remove: self selection.
        selectionIndex := 0.
        contents := ''.
        self changed: #inspectObject.
        self changed: #fieldList.
        self changed: #selection.
        self changed: #selectionIndex.! !


!SetInspector methodsFor: 'menu commands' stamp: 'ClementBera 11/15/2012 09:14'!
copyName
        "Copy the name of the current variable, so the user can paste it into 
the 
        window below and work with is. If collection, do (xxx at: 1)."
        | sel |
        self selectionIndex <= self numberOfFixedFields
                ifTrue: [super copyName]
                ifFalse: [sel := '(self array at: '
                                                , (String streamContents: 
                                                        [:strm | self 
arrayIndexForSelection storeOn: strm]) , ')'.
                        Clipboard clipboardText: sel asText]! !


!SetInspector methodsFor: 'selecting' stamp: 'PHK 6/29/2004 15:33'!
arrayIndexForSelection
        ^ (self fieldList at: selectionIndex) asInteger! !

!SetInspector methodsFor: 'selecting' stamp: 'PHK 6/29/2004 15:38'!
replaceSelectionValue: anObject
        ^ object array at: self arrayIndexForSelection put: anObject! !

!SetInspector methodsFor: 'selecting' stamp: 'ClementBera 11/15/2012 09:15'!
selection
        selectionIndex = 0 ifTrue: [^ ''].
        selectionIndex = 1 ifTrue: [^ object].
        selectionIndex = 2 ifTrue: [^ object longPrintString].
        selectionIndex <= self numberOfFixedFields
                ifTrue: [^ object instVarAt: selectionIndex - 2].

        ^ object array at: self arrayIndexForSelection! !

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

SetInspector class
        instanceVariableNames: ''!

!SetInspector class methodsFor: 'menu' stamp: 'EstebanLorenzano 1/31/2013 
18:32'!
menuDictionaryFieldList: aBuilder
        <contextMenu>
        <setInspectorFieldListMenu>
        
        (aBuilder item: #'Inspect')
                selector: #inspectSelection.
        (aBuilder item: #'Copy name')
                selector: #copyName.
        (aBuilder item: #'Refresh view')
                selector: #update.
        (aBuilder item: #'Remove')
                selector: #removeSelection.
        (aBuilder item: #'Basic inspect')
                selector: #inspectBasic.
! !


!SetInspector class methodsFor: 'tools registry' stamp: 'IgorStasenko 2/20/2011 
15:15'!
registerToolsOn: registry
        "Register ourselves as inspector for Set"
        
         
        registry registerInspector: self for: Set
! !


SetInspector subclass: #WeakSetInspector
        instanceVariableNames: 'flagObject'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tools-Inspector'!
!WeakSetInspector commentStamp: '<historical>' prior: 0!
A verison of the SetInspector specialized for inspecting WeakSets.  It knows 
about the flag object used to indicate empty locations in the hash table.!


!WeakSetInspector methodsFor: 'accessing' stamp: 'nice 12/15/2007 11:59'!
fieldList
        | slotIndices |
        object ifNil: [^ Set new].
        
        "Implementation note: do not use objectArray withIndexCollect: as super
        because this might collect indices in a WeakArray, leading to 
constantly changing fieldList
        as explained at http://bugs.squeak.org/view.php?id=6812";
        
        slotIndices := (Array new: object size) writeStream.
        object array withIndexDo: [:each :i |
                (each notNil and: [each ~= flagObject]) ifTrue: [slotIndices 
nextPut: i printString]].
        
        ^ self baseFieldList
                , slotIndices contents! !


!WeakSetInspector methodsFor: 'initialization' stamp: 'sd 11/20/2005 21:27'!
initialize
        super initialize.
        flagObject := object instVarNamed: 'flag'. ! !

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

WeakSetInspector class
        instanceVariableNames: ''!

!WeakSetInspector class methodsFor: 'tools registry' stamp: 'IgorStasenko 
2/20/2011 15:15'!
registerToolsOn: registry
        "Register ourselves as inspector for WeakSet"
        
         
        registry registerInspector: self for: WeakSet
! !

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

!OrderedCollectionInspector methodsFor: 'as yet unclassified' stamp: 
'MikeRoberts 8/23/2011 18:03'!
fieldList
        object ifNil: [ ^ OrderedCollection new].

        "Guard against incomplete object. You can not ask its size."
        (object instVarAt: 3) "lastIndex"
                ifNil: [^self baseFieldList].
                
        ^ self baseFieldList ,
                (object size <= (self i1 + self i2)
                        ifTrue: [(1 to: object size)
                                                collect: [:i | i printString]]
                        ifFalse: [(1 to: self i1) , (object size-(self i2-1) 
to: object size)
                                                collect: [:i | i printString]])
"
OrderedCollection new inspect
(OrderedCollection newFrom: #(3 5 7 123)) inspect
(OrderedCollection newFrom: (1 to: 1000)) inspect
"! !

!OrderedCollectionInspector methodsFor: 'as yet unclassified' stamp: 
'ClementBera 11/15/2012 09:13'!
replaceSelectionValue: anObject 
        "The receiver has a list of variables of its inspected object. One of 
these 
        is selected. The value of the selected variable is set to the value, 
anObject."

        selectionIndex <= self numberOfFixedFields
                ifTrue: [^ super replaceSelectionValue: anObject].
        object at: self selectedObjectIndex put: anObject! !

!OrderedCollectionInspector methodsFor: 'as yet unclassified' stamp: 
'ClementBera 11/15/2012 09:13'!
selectedObjectIndex
        "Answer the index of the inspectee's collection that the current 
selection refers to."

        | basicIndex |
        basicIndex := selectionIndex - self numberOfFixedFields.
        ^ (object size <= (self i1 + self i2)  or: [basicIndex <= self i1])
                ifTrue: [basicIndex]
                ifFalse: [object size - (self i1 + self i2) + basicIndex]! !

!OrderedCollectionInspector methodsFor: 'as yet unclassified' stamp: 
'ClementBera 11/15/2012 09:14'!
selection
        "The receiver has a list of variables of its inspected object.
        One of these is selected. Answer the value of the selected variable."

        selectionIndex <= self numberOfFixedFields
                ifTrue: [^ super selection].
        ^ object at: self selectedObjectIndex! !

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

OrderedCollectionInspector class
        instanceVariableNames: ''!

!OrderedCollectionInspector class methodsFor: 'tools registry' stamp: 
'IgorStasenko 2/20/2011 15:14'!
registerToolsOn: registry
        "Register ourselves as inspector for OrderedCollection"
        
         
        registry registerInspector: self for: OrderedCollection
! !


Inspector subclass: #DictionaryInspector
        instanceVariableNames: 'keyArray'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tools-Inspector'!
!DictionaryInspector commentStamp: 'LaurentLaffont 3/4/2011 22:44' prior: 0!
I provide a custom inspector for classes of type Dictionary.
These customizations are tools to interactively manipulate the Dictionary I'm 
inspecting and they are accessed in the context menu of the currently selected 
association.

The customizations that I provide are as follows:
inspect -> Create and schedule an Inspector on my currently selected association
copy name -> copy the name of my currently selected association so that it can 
be pasted somewhere else
references -> Create a browser on all references to the association of the 
current selection
objects pointing to this value -> Open a list inspector on all the objects that 
point to the value of the selected instance variable, if any.
senders of this key -> Create a browser on all senders of the selected key
refresh view
add key
rename key
remove
basic inspect -> Bring up a non-special inspector
!


!DictionaryInspector methodsFor: 'accessing' stamp: 'apb 8/20/2004 23:06'!
fieldList
        ^ self baseFieldList
                , (keyArray collect: [:key | key printString])! !


!DictionaryInspector methodsFor: 'initialization' stamp: 'PHK 7/21/2004 18:00'!
initialize
        super initialize.
        self calculateKeyArray! !


!DictionaryInspector methodsFor: 'menu' stamp: 'jb 7/1/2011 10:51'!
addEntry
        | newKey aKey |

        newKey := UIManager default request:
'Enter new key, then type RETURN.
(Expression will be evaluated for value.)
Examples:  #Fred    ''a string''   3+4'.
        aKey := self class evaluatorClass evaluate: newKey.
        object at: aKey put: nil.
        self calculateKeyArray.
        selectionIndex := self numberOfFixedFields + (keyArray indexOf: aKey).
        self changed: #inspectObject.
        self changed: #selectionIndex.
        self changed: #fieldList.
        self update! !

!DictionaryInspector methodsFor: 'menu' stamp: 'apb 8/20/2004 21:19'!
copyName
        "Copy the name of the current variable, so the user can paste it into 
the 
        window below and work with is. If collection, do (xxx at: 1)."
        | sel |
        self selectionIndex <= self numberOfFixedFields
                ifTrue: [super copyName]
                ifFalse: [sel := String streamContents: [:strm | 
                                                        strm nextPutAll: '(self 
at: '.
                                                        (keyArray at: 
selectionIndex - self numberOfFixedFields)
                                                                storeOn: strm.
                                                        strm nextPutAll: ')'].
                        Clipboard clipboardText: sel asText                     
"no undo allowed"]! !

!DictionaryInspector methodsFor: 'menu' stamp: 'EstebanLorenzano 1/31/2013 
19:25'!
fieldListMenu: aMenu
        ^aMenu addAllFromPragma: 'dictionaryInspectorFieldListMenu' target: 
self.! !

!DictionaryInspector methodsFor: 'menu' stamp: 'sd 11/20/2005 21:27'!
removeSelection
        selectionIndex = 0 ifTrue: [^ self changed: #flash].
        object removeKey: (keyArray at: selectionIndex - self 
numberOfFixedFields).
        selectionIndex := 0.
        contents := ''.
        self calculateKeyArray.
        self changed: #inspectObject.
        self changed: #selectionIndex.
        self changed: #fieldList.
        self changed: #selection.! !

!DictionaryInspector methodsFor: 'menu' stamp: 'jb 7/1/2011 10:51'!
renameEntry
        | newKey aKey value |

        value := object at: (keyArray at: selectionIndex - self 
numberOfFixedFields).
        newKey := UIManager default request: 
'Enter new key, then type RETURN.
(Expression will be evaluated for value.)
Examples:  #Fred    ''a string''   3+4'
                 initialAnswer: (keyArray at: selectionIndex - self 
numberOfFixedFields) printString.
        newKey isNil ifFalse: [
                aKey := self class evaluatorClass evaluate: newKey.
                object removeKey: (keyArray at: selectionIndex - self 
numberOfFixedFields).
                object at: aKey put: value.
                self calculateKeyArray.
                selectionIndex := self numberOfFixedFields + (keyArray indexOf: 
aKey).
                self changed: #selectionIndex.
                self changed: #inspectObject.
                self changed: #fieldList.
                self update ]! !

!DictionaryInspector methodsFor: 'menu' stamp: 'ar 10/31/2004 17:26'!
selectionReferences
        "Create a browser on all references to the association of the current 
selection."

        self selectionIndex = 0 ifTrue: [^ self changed: #flash].
        object class == MethodDictionary ifTrue: [^ self changed: #flash].
        self systemNavigation browseAllCallsOn: (object associationAt: 
(keyArray at: selectionIndex  - self numberOfFixedFields)).
! !

!DictionaryInspector methodsFor: 'menu' stamp: 'MarcusDenker 7/12/2012 18:00'!
sendersOfSelectedKey
        "Create a browser on all senders of the selected key"
        | aKey |
        self selectionIndex = 0
                ifTrue: [^ self changed: #flash].
        ((aKey := keyArray at: selectionIndex  - self numberOfFixedFields) 
isSymbol)
                ifFalse: [^ self changed: #flash].
        SystemNavigation new browseAllCallsOn: aKey! !


!DictionaryInspector methodsFor: 'selecting' stamp: 'sd 11/20/2005 21:27'!
addEntry: aKey
        object at: aKey put: nil.
        self calculateKeyArray.
        selectionIndex := self numberOfFixedFields + (keyArray indexOf: aKey).
        self changed: #inspectObject.
        self changed: #selectionIndex.
        self changed: #fieldList.
        self update! !

!DictionaryInspector methodsFor: 'selecting' stamp: 'CamilloBruni 2/28/2012 
11:44'!
calculateKeyArray
        "Recalculate the KeyArray from the object being inspected"

        keyArray := object keysSortedSafely asArray.
        selectionIndex := 1.
! !

!DictionaryInspector methodsFor: 'selecting' stamp: 'di 9/22/1998 21:25'!
contentsIsString
        "Hacked so contents empty when deselected"

        ^ (selectionIndex = 0)! !

!DictionaryInspector methodsFor: 'selecting' stamp: 'sd 11/20/2005 21:27'!
refreshView
        | i |
        i := selectionIndex.
        self calculateKeyArray.
        selectionIndex := i.
        self changed: #fieldList.
        self changed: #contents.! !

!DictionaryInspector methodsFor: 'selecting' stamp: 'apb 8/20/2004 22:37'!
replaceSelectionValue: anObject 
        selectionIndex <= self numberOfFixedFields
                ifTrue: [^ super replaceSelectionValue: anObject].
        ^ object
                at: (keyArray at: selectionIndex - self numberOfFixedFields)
                put: anObject! !

!DictionaryInspector methodsFor: 'selecting' stamp: 'apb 8/20/2004 21:55'!
selection

        selectionIndex <= (self numberOfFixedFields) ifTrue: [^ super 
selection].
        ^ object at: (keyArray at: selectionIndex - self numberOfFixedFields) 
ifAbsent:[nil]! !

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

DictionaryInspector class
        instanceVariableNames: ''!

!DictionaryInspector class methodsFor: 'menu' stamp: 'EstebanLorenzano 
1/31/2013 18:32'!
menuDictionaryFieldList: aBuilder
        <contextMenu>
        <dictionaryInspectorFieldListMenu>
        
        (aBuilder item: #'Inspect')
                selector: #inspectSelection.
        (aBuilder item: #'Copy name')
                selector: #copyName.
        (aBuilder item: #'References')
                selector: #selectionReferences.
        (aBuilder item: #'Senders of this key')
                selector: #sendersOfSelectedKey.
        (aBuilder item: #'Refresh view')
                selector: #refreshView.
        (aBuilder item: #'Add key')
                selector: #addEntry;
                withSeparatorAfter.
                
        (aBuilder item: #'Rename key')
                selector: #renameEntry.
        (aBuilder item: #'Remove')
                selector: #removeSelection.
        (aBuilder item: #'Basic inspect')
                selector: #inspectBasic.
! !


!DictionaryInspector class methodsFor: 'tools registry' stamp: 'IgorStasenko 
2/20/2011 15:12'!
registerToolsOn: registry
        "Register ourselves as inspector for Dictionary (and its subclasses)"
        
         
        registry registerInspector: self for: Dictionary
! !

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

!BasicInspector methodsFor: 'as yet unclassified' stamp: 'CamilloBruni 
2/28/2012 11:44'!
inspect: anObject 
        "Initialize the receiver so that it is inspecting anObject."

        self initialize.
        object := anObject.
        selectionIndex := 1.
        contents := ''! !

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

BasicInspector class
        instanceVariableNames: ''!

!BasicInspector class methodsFor: 'tools registry' stamp: 'IgorStasenko 
2/19/2011 02:59'!
registerToolsOn: registry
        "Add ourselves to registry. See [Smalltalk tools]" 
        registry register: self as: #basicInspector
! !


Inspector subclass: #FloatInspector
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Tools-Inspector'!
!FloatInspector commentStamp: '<historical>' prior: 0!
I am FloatInspector.
I am an Inspector.

I am a specialized Inspector for Floats.
I add extra elements (sign, significand, exponent) of the Float object that I 
am inspecting.

Note that these should be interpreted as

sign * significand * (2 raisedToInteger: exponent)!


!FloatInspector methodsFor: 'accessing' stamp: 'SvenVanCaekenberghe 11/26/2012 
15:50'!
elements
        "Return the list of elements or aspects about Floats that we want to 
show.
        Note that each of these should name a Float method."
        
        ^ #( sign significand exponent )! !

!FloatInspector methodsFor: 'accessing' stamp: 'SvenVanCaekenberghe 11/26/2012 
14:32'!
fieldList
        "Answer the super field list plus our custom elements."

        ^ super fieldList , self elements! !


!FloatInspector methodsFor: 'selecting' stamp: 'SvenVanCaekenberghe 11/26/2012 
15:50'!
numberOfFixedFields
        "Overridden to take into account the two word indexable fields of Float"

        ^ super numberOfFixedFields + 2! !

!FloatInspector methodsFor: 'selecting' stamp: 'SvenVanCaekenberghe 11/26/2012 
15:48'!
replaceSelectionValue: anObject
        "The receiver has a list of variables of its inspected object. One of 
these 
        is selected. The value of the selected variable is set to the value, 
anObject."

        selectionIndex <= self numberOfFixedFields
                ifTrue: [ ^ super replaceSelectionValue: anObject ]
        "My own fields are readonly"! !

!FloatInspector methodsFor: 'selecting' stamp: 'SvenVanCaekenberghe 11/26/2012 
14:23'!
selection
        "The receiver has a list of variables of its inspected object.
        One of these is selected. Answer the value of the selected variable."

        ^ self selectionIndex <= self numberOfFixedFields
                ifTrue: [ super selection ]
                ifFalse: [ object perform: (self elements at: self 
selectionIndex - self numberOfFixedFields) ]! !

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

!ContextInspector methodsFor: 'accessing' stamp: 'StephaneDucasse 8/21/2010 
20:48'!
fieldList
        "Answer the base field list plus an abbreviated list of indices."

        ^ self baseFieldList , (object tempNames collect: [:t| '[',t,']'])! !

!ContextInspector methodsFor: 'accessing' stamp: 'ClementBera 11/15/2012 09:12'!
selection
        "The receiver has a list of variables of its inspected object.
        One of these is selected. Answer the value of the selected variable."
        
        | basicIndex |
        selectionIndex = 0 ifTrue: [^ ''].
        selectionIndex = 1 ifTrue: [^ object].
        selectionIndex = 2 ifTrue: [^ object longPrintStringLimitedTo: 20000].
        selectionIndex <= self numberOfFixedFields
                ifTrue: [^ object instVarAt: selectionIndex - 2].
        basicIndex := selectionIndex - self numberOfFixedFields.
        ^object debuggerMap namedTempAt: basicIndex in: object
! !

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

ContextInspector class
        instanceVariableNames: ''!

!ContextInspector class methodsFor: 'as yet unclassified' stamp: 'IgorStasenko 
2/20/2011 15:13'!
registerToolsOn: registry
        "Register ourselves as inspector for MethodContext"
        
         
        registry registerInspector: self for: MethodContext
! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Number methodsFor: '*Tools-Inspector'!
defaultLabelForInspector
        "Answer the default label to be used for an Inspector window on the 
receiver."

        ^ super defaultLabelForInspector, ': ', self printString! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Float methodsFor: '*Tools-Inspector' stamp: 'SvenVanCaekenberghe 11/26/2012 
14:23'!
inspectorClass
        ^ FloatInspector! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Object methodsFor: '*Tools-Inspector' stamp: 'SeanDeNigris 1/23/2013 22:36'!
doExpiredInspectCount
        Halt disableHaltOnce.
        "self removeHaltCount."
        self inspect! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Object methodsFor: '*Tools-Inspector' stamp: 'IgorStasenko 4/26/2011 16:58'!
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."

        ^ Smalltalk tools inspector! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Object methodsFor: '*Tools-Inspector' stamp: 'SeanDeNigris 1/23/2013 22:37'!
inspectUntilCount: int 
        ^ Halt isHaltOnceEnabled ifTrue: [ 
                        Halt isCounting
                                ifTrue: [
                                        Halt callsUntilHaltOnCount: Halt 
callsUntilHaltOnCount - 1.
                                        Halt callsUntilHaltOnCount > 0
                                                ifTrue: [self inspect]
                                                ifFalse: [ Halt disableHaltOnce 
] ]
                                ifFalse: [
                                        int = 1
                                                ifTrue: [self 
doExpiredInspectCount]
                                                ifFalse: [
                                                        Halt 
callsUntilHaltOnCount: int - 1.
                                                        self inspect]]]! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Object methodsFor: '*Tools-Inspector' stamp: 'CamilloBruni 9/21/2012 13:53'!
inspect
        "Create and schedule an Inspector in which the user can examine the 
receiver's variables."
        ^ Smalltalk tools inspect: self! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Object methodsFor: '*Tools-Inspector' stamp: 'IgorStasenko 4/15/2011 17:30'!
inspectWithLabel: aLabel
        "Create and schedule an Inspector in which the user can examine the 
receiver's variables."
        ^Smalltalk tools inspect: self label: aLabel! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Object methodsFor: '*Tools-Inspector'!
defaultLabelForInspector
        "Answer the default label to be used for an Inspector window on the 
receiver."

        ^ self class name! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Object methodsFor: '*Tools-Inspector' stamp: 'IgorStasenko 1/22/2012 14:35'!
basicInspect
        "Create and schedule an Inspector in which the user can examine the 
        receiver's variables. This method should not be overriden."
        ^Smalltalk tools basicInspector openOn: self! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Object methodsFor: '*Tools-Inspector' stamp: 'SeanDeNigris 1/23/2013 22:22'!
inspectOnce
        "Inspect unless we have already done it once."
        
        Halt isHaltOnceEnabled ifTrue: [
                Halt disableHaltOnce.
                ^ self inspect ].! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Object methodsFor: '*Tools-Inspector' stamp: 'SeanDeNigris 1/23/2013 22:45'!
inspectOnCount: int 
        
        Halt isHaltOnceEnabled
                ifTrue: [
                        Halt isCounting
                                ifTrue: [
                                        Halt callsUntilHaltOnCount: Halt 
callsUntilHaltOnCount - 1.
                                        Halt callsUntilHaltOnCount = 0
                                                ifTrue: [self 
doExpiredInspectCount]]
                                ifFalse: [
                                        int = 1
                                                ifTrue: [self 
doExpiredInspectCount]
                                                ifFalse: [Halt 
callsUntilHaltOnCount: int - 1]]]! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!WeakSet methodsFor: '*Tools-Inspector' stamp: 'ar 9/27/2005 18:33'!
inspectorClass 
        ^ WeakSetInspector! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Integer methodsFor: '*Tools-Inspector' stamp: 'SvenVanCaekenberghe 11/26/2012 
13:52'!
inspectorClass
        ^ IntegerInspector ! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!SystemDictionary methodsFor: '*Tools-Inspector' stamp: 'IgorStasenko 1/22/2012 
14:49'!
inspectGlobals
        "Smalltalk globals  inspectGlobals"
        
        | associations aDict |
        associations := ((self  keys select: [:aKey | ((self  at: aKey) 
isKindOf: Class) not]) asArray sort 
                                                                                
                                        collect: [:aKey | self associationAt: 
aKey]).
        aDict := IdentityDictionary new.
        associations do: [:as | aDict add: as].
        aDict inspectWithLabel: 'The Globals'! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!OrderedCollection methodsFor: '*Tools-Inspector' stamp: 'ar 9/27/2005 18:33'!
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."

        ^OrderedCollectionInspector! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Behavior methodsFor: '*Tools-Inspector' stamp: 'CamilloBruni 8/1/2012 16:10'!
inspectAllInstances 
        "Inspect all instances of the receiver."

        | all allSize prefix |
        all := self allInstances.
        (allSize := all size) isZero ifTrue: [^ self inform: 'There are no 
instances of ', self name].
        prefix := allSize = 1
                ifTrue:         ['The lone instance']
                ifFalse:        ['The ', allSize printString, ' instances'].
        
        all asArray inspectWithLabel: (prefix, ' of ', self name)! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Behavior methodsFor: '*Tools-Inspector' stamp: 'CamilloBruni 8/1/2012 16:10'!
inspectSubInstances 
        "Inspect all instances of the receiver and all its subclasses.  CAUTION 
- don't do this for something as generic as Object!!"

        | all allSize prefix |
        all := self allSubInstances.
        (allSize := all size) isZero ifTrue: [^ self inform: 'There are no 
instances of ', self name, '
or any of its subclasses'].
        prefix := allSize = 1
                ifTrue:         ['The lone instance']
                ifFalse:        ['The ', allSize printString, ' instances'].
        
        all asArray inspectWithLabel: (prefix, ' of ', self name, ' & its 
subclasses')! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Set methodsFor: '*Tools-Inspector' stamp: 'ar 9/27/2005 18:33'!
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."

        ^ SetInspector! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!MethodContext methodsFor: '*Tools-Inspector' stamp: 'StephaneDucasse 8/21/2010 
20:49'!
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."

        ^ ContextInspector! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!Dictionary methodsFor: '*Tools-Inspector' stamp: 'ar 9/27/2005 18:32'!
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."

        ^ DictionaryInspector! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!SystemNavigation methodsFor: '*Tools-Inspector' stamp: 'BenjaminVanRyseghem 
4/4/2011 14:28'!
classFromPattern: pattern withCaption: aCaption
        "If there is a class whose name exactly given by pattern, return it.
        If there is only one class in the system whose name matches pattern, 
return it.
        Otherwise, put up a menu offering the names of all classes that match 
pattern, and return the class chosen, else nil if nothing chosen.
        This method ignores tab, space, & cr characters in the pattern"

        | toMatch potentialClassNames classNames exactMatch index |
        (toMatch := pattern
                copyWithoutAll:
                        {(Character space).
                        (Character cr).
                        (Character tab)}) isEmpty
                ifTrue: [ ^ nil ].
        Symbol
                hasInterned: toMatch
                ifTrue: [ :patternSymbol | 
                        self environment
                                at: patternSymbol
                                ifPresent: [ :maybeClass | 
                                        ((maybeClass isKindOf: Class) or: [ 
maybeClass isKindOf: Trait ])
                                                ifTrue: [ ^ maybeClass ] ] ].
        toMatch := (toMatch copyWithout: $.) asLowercase.
        potentialClassNames := (self environment classNames , self environment 
traitNames) asOrderedCollection.
        classNames := pattern last = $.
                ifTrue: [ potentialClassNames select: [ :nm | nm asLowercase = 
toMatch ] ]
                ifFalse: [ potentialClassNames select: [ :n | n 
includesSubstring: toMatch caseSensitive: false ] ].
        classNames isEmpty
                ifTrue: [ ^ nil ].
        exactMatch := classNames detect: [ :each | each asLowercase = toMatch ] 
ifNone: [ nil ].
        index := classNames size = 1
                ifTrue: [ 1 ]
                ifFalse: [ 
                        exactMatch
                                ifNil: [ UIManager default chooseFrom: 
classNames lines: #() title: aCaption ]
                                ifNotNil: [ 
                                        classNames addFirst: exactMatch.
                                        UIManager default chooseFrom: 
classNames lines: #(1) title: aCaption ] ].
        index = 0
                ifTrue: [ ^ nil ].
        ^ self environment at: (classNames at: index) asSymbol  "
        self default classFromPattern: 'znak' withCaption: ''
        self default classFromPattern: 'orph' withCaption: ''
        self default classFromPattern: 'TCompil' withCaption: ''
"! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!SystemNavigation methodsFor: '*Tools-Inspector' stamp: 'StephaneDucasse 
10/4/2010 19:35'!
showMenuOf: selectorCollection withFirstItem: firstItem ifChosenDo: choiceBlock 
withCaption: aCaption
        "Show a sorted menu of the given selectors, preceded by firstItem, and 
all abbreviated to 40 characters.  Use aCaption as the menu title, if it is not 
nil.  Evaluate choiceBlock if a message is chosen."
 
        | index menuLabels sortedList |
        sortedList := selectorCollection asSortedCollection.
        menuLabels := Array streamContents: 
                [:strm | strm nextPut: (firstItem contractTo: 40).
                        sortedList do: [:sel | strm nextPut: (sel contractTo: 
40)]].
        index := UIManager default chooseFrom: menuLabels lines: #(1).  
        index = 1 ifTrue: [choiceBlock value: firstItem].
        index > 1 ifTrue: [choiceBlock value: (sortedList at: index - 1)]! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!SystemNavigation methodsFor: '*Tools-Inspector' stamp: 'sd 4/15/2003 15:34'!
showMenuOf: selectorCollection withFirstItem: firstItem ifChosenDo: choiceBlock
        "Show a sorted menu of the given selectors, preceded by firstItem, and 
all
        abbreviated to 40 characters.  Evaluate choiceBlock if a message is 
chosen."

        ^ self showMenuOf: selectorCollection withFirstItem: firstItem 
ifChosenDo: choiceBlock withCaption: nil! !
'From Pharo2.0 of 7 March 2013 [Latest update: #20619] on 27 August 2016 at 
10:42:53 am'!

!SystemNavigation methodsFor: '*Tools-Inspector' stamp: 'StephaneDucasse 
8/9/2011 17:57'!
confirmRemovalOf: aSelector on: aClass 
        "Determine if it is okay to remove the given selector. Answer 1 if it  
        should be removed, 2 if it should be removed followed by a senders  
        browse, and 3 if it should not be removed."
        | count answer caption allCalls |
        allCalls := self allCallsOn: aSelector.
        (count := allCalls size) = 0
                ifTrue: [^ 1].
        "no senders -- let the removal happen without warning"
        count = 1
                ifTrue: [(allCalls first actualClass == aClass
                                        and: [allCalls first selector == 
aSelector])
                                ifTrue: [^ 1]].
        "only sender is itself"
        caption := 'The message ', aSelector printString ,' has ' , count 
printString , ' sender'.
        count > 1
                ifTrue: [caption := caption copyWith: $s].
        answer := UIManager default 
                chooseFrom: #('Remove it'
                                'Remove, then browse senders'
                                'Don''t remove, but show me those senders'
                                'Forget it -- do nothing -- sorry I asked') 
title: caption.
        answer = 3
                ifTrue: [self
                                browseMessageList: allCalls
                                name: 'Senders of ' , aSelector
                                autoSelect: aSelector keywords first].
        answer = 0
                ifTrue: [answer := 3].
        "If user didn't answer, treat it as cancel"
        ^ answer min: 3! !

Reply via email to