DictionaryInspectorView.st
author Claus Gittinger <cg@exept.de>
Mon, 02 Feb 2009 17:54:50 +0100
changeset 8527 1f78e8ddae80
parent 8470 2bec16caeefb
child 8973 76f40edc89d3
permissions -rw-r--r--
also show only the first nShown names; much better for big sets.

"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libtool' }"

InspectorView subclass:#DictionaryInspectorView
	instanceVariableNames:'keys hideClassVars hideClasses hideUnloadedClasses hideAliases
		hideNilValues hideLiteralValues'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Inspector'
!

!DictionaryInspectorView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    a modified Inspector for Dictionaries

    [author:]
        Claus Gittinger
"
! !

!DictionaryInspectorView methodsFor:'event handling'!

keyPress:key x:x y:y
    "handle special keys"

    <resource: #keyboard (#Delete #BackSpace)>

    (key == #Delete or:[key == #BackSpace]) ifTrue:[
        self doRemoveKey.
        ^ self.
    ].
    (key == #Insert) ifTrue:[
        self doAddKey.
        ^ self.
    ].

    super keyPress:key x:x y:y
! !

!DictionaryInspectorView methodsFor:'initialization & release'!

initialize
    super initialize.

    hideClassVars := false.
    hideClasses := false.
    hideUnloadedClasses := false.
    hideAliases := false.
    hideLiteralValues := false.
    hideNilValues := false.
! !

!DictionaryInspectorView methodsFor:'menu'!

fieldMenu
    <resource: #programMenu >

    |items m|

    inspectedObject isNameSpace ifTrue:[
        items := #(
                       ('Copy Key'             doCopyKey      )
                       ('-')
                       ('Inspect'              doInspect      )
                       ('Inspect Key'          doInspectKey   )
                       ('BasicInspect'         doBasicInspect )
                       ('Inspect Hierarchical' doNewInspect   )
                       ('-')
                       ('Owners'               showOwners     )
                       ('Ref Chains'           showReferences )
                       ('References to Global' showKeyReferences )
                       ('-')
                       ('Browse'               browse         )
                       ('-')
                       ('Add Key'              doAddKey       )
                       ('Remove Key'           doRemoveKey    )
                       ('-')
                   ).

        hideClassVars == true ifTrue:[
            items := items , #(
                           ('Show ClassVars'   doShowClassVars )
                       ).
        ] ifFalse:[
            items := items , #(
                           ('Hide ClassVars'   doHideClassVars )
                       ).
        ].
        hideClasses == true ifTrue:[
            items := items , #(
                           ('Show Classes'     doShowClasses )
                       ).
        ] ifFalse:[
            items := items , #(
                           ('Hide Classes'     doHideClasses )
                       ).
        ].
        hideUnloadedClasses == true ifTrue:[
            items := items , #(
                           ('Show Unloaded Classes'     doShowUnloadedClasses )
                       ).
        ] ifFalse:[
            items := items , #(
                           ('Hide UnloadedClasses'     doHideUnloadedClasses )
                       ).
        ].
        hideAliases == true ifTrue:[
            items := items , #(
                           ('Show Aliases'     doShowAliases )
                       ).
        ] ifFalse:[
            items := items , #(
                           ('Hide Aliases'     doHideAliases )
                       ).
        ].
        hideLiteralValues == true ifTrue:[
            items := items , #(
                           ('Show Literal Values'  doShowLiteralValues )
                       ).
        ] ifFalse:[
            items := items , #(
                           ('Hide Literal Values'  doHideLiteralValues )
                       ).
        ].
        hideNilValues == true ifTrue:[
            items := items , #(
                           ('Show Nil Values'  doShowNilValues )
                       ).
        ] ifFalse:[
            items := items , #(
                           ('Hide Nil Values'  doHideNilValues )
                       ).
        ].
    ] ifFalse:[
        items := #(
                       ('Copy Key'             doCopyKey      )
                       ('-')
                       ('Inspect'              doInspect      )
                       ('Inspect Key'          doInspectKey   )
                       ('BasicInspect'         doBasicInspect )
                       ('Inspect Hierarchical' doNewInspect   )
                       ('-')
                       ('Owners'               showOwners     )
                       ('Ref Chains'           showReferences )
                       ('-')
                       ('Browse'                       browse                 )
                       ('Browse Class Hierarchy'       browseClassHierarchy   )
                       ('Browse Full Class Protocol'   browseFullClassProtocol)
                       ('-')
                       ('Add Key'              doAddKey       )
                       ('Remove Key'           doRemoveKey    )
                   ).
    ].

    monitorProcess isNil ifTrue:[
        items := items , #(
                       ('-')
                       ('Start Monitor'    doStartMonitor )
                          ).
    ] ifFalse:[
        items := items , #(
                       ('-')
                       ('Stop Monitor'     doStopMonitor  )
                          ).
    ].

    items := items , #(
                   ('-')
                   ('Update'     doUpdate  )
                      ).

    m := PopUpMenu itemList:items resources:resources.

    (inspectedObject isNameSpace or:[inspectedObject isSharedPool]) ifTrue:[
        m disableAll:#( doAddKey doRemoveKey )
    ].

    selectionIndex isNil ifTrue:[
        m disableAll:#(doInspect doInspectKey doBasicInspect doNewInspect
                       doRemoveKey doStartMonitor doStopMonitor doCopyKey
                      )
    ] ifFalse:[
        (self keyIndexForLine:selectionIndex) isNil ifTrue:[
            m disableAll:#(doInspectKey doRemoveKey doCopyKey)
        ]
    ].
    hideLiteralValues == true ifTrue:[
        m disableAll:#( doShowNilValues doHideNilValues )
    ].

    ^ m.

    "Modified: / 29-05-2007 / 19:33:43 / cg"
! !

!DictionaryInspectorView methodsFor:'menu actions'!

browse
    |cls|

    cls := self selection class theNonMetaclass.
"/    cls isNameSpace ifTrue:[
"/        self halt.
"/    ].
    cls browserClass openInClass:cls selector:nil
!

doAddKey
    "add a key"

    |keyName key val l|

    keyName := Dialog request:'Key to add (storeString):' initialAnswer:''.
    keyName notEmpty ifTrue:[
        key := Object readFrom:keyName onError:[ self information:'Bad input.'. ^ self].
        (inspectedObject includesKey:key) ifFalse:[
            val := Dialog request:'Value to add (storeString):' initialAnswer:''.
            val notNil ifTrue:[
                val := Object readFrom:val onError:[ self information:'Bad input.'. ^ self].
            ].

            inspectedObject at:key put:val.
            selectionIndex := selectedLine := nil.
            inspectedObject changed.
            l := listView firstLineShown.
            self reinspect. "force list update"
            listView scrollToLine:l
        ]
    ]
!

doHideAliases
    hideAliases := true.
    self reinspect
!

doHideClassVars
    hideClassVars := true.
    self reinspect
!

doHideClasses
    hideClasses := true.
    self reinspect
!

doHideLiteralValues
    hideLiteralValues := true.
    self reinspect
!

doHideNilValues
    hideNilValues := true.
    self reinspect
!

doHideUnloadedClasses
    hideUnloadedClasses := true.
    self reinspect
!

doInspectKey
    "inspect selected items key"

    |key|

    key := self selectedKey.
    key notNil ifTrue:[
        key inspect
    ]
!

doRemoveKey
    "remove selected item from keys"

    |key l|

    key := self selectedKey.
    key notNil ifTrue:[
        (inspectedObject includesKey:key) ifTrue:[
            listView cursor:(Cursor wait).
            inspectedObject removeKey:key.
            keys := nil.
            selectionIndex := selectedLine := nil.
            inspectedObject changed.
            listView cursor:(Cursor hand).
            l := listView firstLineShown.
            self reinspect. "force list update"
            listView scrollToLine:l.
        ].
    ]
!

doShowAliases
    hideAliases := false.
    self reinspect
!

doShowClassVars
    hideClassVars := false.
    self reinspect
!

doShowClasses
    hideClasses := false.
    self reinspect
!

doShowLiteralValues
    hideLiteralValues := false.
    self reinspect
!

doShowNilValues
    hideNilValues := false.
    self reinspect
!

doShowUnloadedClasses
    hideUnloadedClasses := false.
    self reinspect
!

showKeyReferences
    "show users of selected key (i.e. global).
     Only useful when inspecting smalltalk"

    |key|

    key := self selectedKey.
    key notNil ifTrue:[
        self topView withWaitCursorDo:[
            UserPreferences systemBrowserClass browseReferendsOf:(key asSymbol)
        ].
    ]
! !

!DictionaryInspectorView methodsFor:'private'!

baseInspectedObjectClass

    (inspectedObject isMemberOf:Dictionary) ifFalse:[
        (inspectedObject class inheritsFrom:Dictionary) ifFalse:[
            "this is true for e.g. MethodDictionary"
            ^ Object
        ]
    ].
    ^ Dictionary

    "Modified: / 23.7.1999 / 10:39:11 / stefan"


!

defaultLabel
    ^ 'Keys'

    "Created: 28.6.1996 / 19:46:51 / cg"
!

indexList
    "return a list of indexes to show in the selectionList.
     Set hasMore to true, if a '...' entry should be added."

    (inspectedObject isNameSpace 
    or:[inspectedObject isSharedPool]) ifTrue:[
        ^ self indexListForNameSpace.
    ].

    "/ do not use 'inspectedObject keys',
    "/ since Sets cannot hold nils (which are now valid keys)
    keys := OrderedCollection new.
    inspectedObject size > nShown ifTrue:[
        keys := (SortedCollection new:nShown) sortBlock:[:a :b | a displayString < b displayString].
        inspectedObject keysDo:[:k | 
            keys add:k.
            keys size >= nShown ifTrue:[ 
                hasMore := true.
                ^ keys
            ].
        ].
    ].

    inspectedObject keysDo:[:k | keys add:k].
    keys := keys asSortedCollection:[:a :b | a displayString < b displayString].
    ^ keys
!

indexListForNameSpace
    "return a list of indexes to show in the selectionList.
     Set hasMore to true, if a '...' entry should be added."

    keys := SortedCollection new:1000.

    inspectedObject keysDo:[:k |
        |hidden i o|

        hidden := false.
        hideClassVars == true ifTrue:[
            (i := k lastIndexOf:$:) ~~ 0 ifTrue:[
                (i > 1 and:[(k at:i-1) ~~ $:]) ifTrue:[
                    hidden := true
                ].
            ].
        ].
        (hidden not and:[hideNilValues == true]) ifTrue:[
            o isNil ifTrue:[ o := inspectedObject at:k ifAbsent:nil ].
            o isNil ifTrue:[
                hidden := true
            ].
        ].
        (hidden not and:[hideClasses == true]) ifTrue:[
            o isNil ifTrue:[ o := inspectedObject at:k ifAbsent:nil ].
            o isBehavior ifTrue:[
                inspectedObject == Smalltalk ifTrue:[
                    o name == k ifTrue:[
                        hidden := true
                    ]
                ] ifFalse:[
                    o nameWithoutNameSpacePrefix = k ifTrue:[
                        hidden := true
                    ]
                ]
            ].
        ].
        (hidden not and:[hideAliases == true]) ifTrue:[
            o isNil ifTrue:[ o := inspectedObject at:k ifAbsent:nil ].
            o isBehavior ifTrue:[
                inspectedObject == Smalltalk ifTrue:[
                    o name ~~ k ifTrue:[
                        hidden := true
                    ]
                ] ifFalse:[
                    o nameWithoutNameSpacePrefix ~= k ifTrue:[
                        hidden := true
                    ].
                ].
            ].
        ].
        (hidden not and:[hideLiteralValues == true]) ifTrue:[
self breakPoint:#cg.
            o isNil ifTrue:[ o := inspectedObject at:k ifAbsent:nil ].
            o isLiteral ifTrue:[
                hidden := true
            ].
        ].

        hidden ifFalse:[keys add:k]
    ].
    ^ keys
!

indexedFieldList 
    "return a list of indexed-variable names to show in the selectionList.
     Set hasMore to true, if a '...' entry should be added."

    |keys|

    keys := self indexList.
    ^ keys 
        collect:[:k | 
            k isSymbol 
                ifTrue:[
                    k printString] 
                ifFalse:[
                    k displayString]].
!

instVarIndexForLine:lineNr
    "helper - return the index for a named instVar;
     nil, if self or a keyed instvar is selected."

    (inspectedObject isNameSpace or:[inspectedObject isSharedPool]) ifTrue:[
        ^ nil
    ].
    ^ super instVarIndexForLine:lineNr
!

keyIndexForLine:lineNr
    "helper - return the index of the key-list"

    |firstRealIndex idx line|

    (inspectedObject isNameSpace or:[inspectedObject isSharedPool]) ifTrue:[
        (self hasSelfEntry
        and:[lineNr == 1 or:[lineNr isNil]]) ifTrue:[
            ^ nil "/ self selected
        ].
        firstRealIndex := 1.
        idx := lineNr.
        [line := listView at:firstRealIndex. 
         (line startsWith:'-') and:[line size < 2 or:[line second isDigit not]]] whileTrue:[
            firstRealIndex := firstRealIndex + 1.
            idx := idx - 1.
        ].

        ^ idx   
    ].
    ^ super keyIndexForLine:lineNr
!

namedFieldList 
    "return a list of instVar names to show in the selectionList."

    (inspectedObject isNameSpace or:[inspectedObject isSharedPool]) ifTrue:[
        "/ empty ...
        ^ OrderedCollection new
    ].
    ^ super namedFieldList
!

release 
    "release inspected object"

    keys := nil.
    super release
!

selectedKey
    "selected items key or nil"

    |idx|

    idx := self keyIndexForLine:selectionIndex.
    idx notNil ifTrue:[
        ^ (keys at:idx)
    ].
    ^ nil.
! !

!DictionaryInspectorView methodsFor:'user interaction'!

indexedValueAtIndex:idx
    |key|

    key := keys at:idx.
    ^ inspectedObject at:key ifAbsent:nil.

!

indexedValueAtIndex:idx put:newValue
    |key|

    key := keys at:idx.
    inspectedObject at:key put:newValue.
! !

!DictionaryInspectorView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/DictionaryInspectorView.st,v 1.66 2009-02-02 16:54:50 cg Exp $'
! !