Tools_NavigationState.st
author Claus Gittinger <cg@exept.de>
Mon, 14 Feb 2011 18:16:36 +0100
branchinitialV
changeset 9777 82d9e1236f1f
parent 9564 ee5827388b2e
child 10079 d93b4a7b0392
permissions -rw-r--r--
checkin from stx browser

"
 COPYRIGHT (c) 2000 by eXept Software AG
              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' }"

"{ NameSpace: Tools }"

Object subclass:#NavigationState
	instanceVariableNames:'browserLabel codeModifiedHolder categoryList classList
		packageFilter nameSpaceFilter hidePrivateClasses canvasType
		notMetaToggle metaToggle metaToggleLabel organizerMode codeAspect
		codeHolder classDocumentationHolder canvas selectorListGenerator
		protocolListGenerator classListPerNameSpaceGenerator
		classListGenerator categoryListGenerator nameSpaceListGenerator
		projectListGenerator classHierarchyTopClass meta selectedMethods
		selectedProtocols selectedClasses selectedCategories
		selectedProjects selectedNamespaces variableFilter
		filterClassVars sortBy noAllItem autoSearchPattern
		autoSearchIgnoreCase autoSearchAction realModifiedStateHolder
		methodInfo versionDiffApplication selectorListGeneratorArray
		selectedMethodsArray infoLabelHolder packageLabelHolder
		cursorLineLabelHolder cursorColLabelHolder modeLabelHolder
		sortVariablesBy editModeHolder scrollableCodeView specialEditors
		selectedEditorNoteBookTabIndexHolder editorNoteBookListHolder
		editorNoteBookCanvasHolder codeView stringSearchToolView
		noteBookView inheritanceView documentationView'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Browsers-New'
!

!NavigationState class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2000 by eXept Software AG
              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.
"
! !

!NavigationState methodsFor:'accessing'!

autoSearchAction
    ^ autoSearchAction
!

autoSearchAction:something
    autoSearchAction := something.
!

autoSearchIgnoreCase
    "return true if the autSearch is to be case-insensitive"

    ^ autoSearchIgnoreCase
!

autoSearchIgnoreCase:aBoolean
    "change the autSearches case-insensitivenes"

    autoSearchIgnoreCase := aBoolean
!

autoSearchPattern
    "return the automatic search pattern"

    ^ autoSearchPattern
!

autoSearchPattern:aPattern
    "change the automatic search pattern"

    autoSearchPattern := aPattern.
!

browserLabel
    "return the assigned state-label (to be shown in the tab)."

    ^ browserLabel
!

browserLabel:aString
    "set the assigned state-label (to be shown in the tab)."

    browserLabel := aString
!

canvas
    ^ canvas
!

canvas:something
    canvas := something.
    canvasType isNil ifTrue:[
        canvasType := something spec
    ].
!

canvasType
    "return the type of canvas"

    ^ canvasType
!

canvasType:aSpecSymbol
    "set the type of canvas"

    canvasType notNil ifTrue:[
        canvasType ~~ aSpecSymbol ifTrue:[
            self halt:'cannot be changed, once set'.
        ]
    ].
    canvasType := aSpecSymbol
!

codeAspect
    "return the codeAspect; a symbol describing what is shown in the codeView"

    ^ codeAspect

    "Created: / 11.2.2000 / 12:43:29 / cg"
!

codeAspect:aSymbolOrNil
    "set the codeAspect; a symbol describing what is shown in the codeView"

    codeAspect := aSymbolOrNil

    "Created: / 11.2.2000 / 12:43:45 / cg"
!

editorNoteBookCanvasHolder
    editorNoteBookCanvasHolder isNil ifTrue:[
        editorNoteBookCanvasHolder := nil asValue.
    ].
    ^ editorNoteBookCanvasHolder
!

editorNoteBookListHolder
    editorNoteBookListHolder isNil ifTrue:[
        editorNoteBookListHolder := #() asValue.
    ].
    ^ editorNoteBookListHolder
!

environment
    ^ Smalltalk
!

modified
    "check for modified code by asking the editTextView;
     this one returns true if ever modified - even if
     the modifications where undone in the editor
     (i.e. not really modified).
     Use #reallyModified if the contents should be compared
     against the original contents"

    |v|

    self realModifiedState == true ifTrue:[^ true].
    self anySpecialEditorModified ifTrue:[^ true].

    ^ (v := self codeView) notNil and:[v modified]
!

modified:aBoolean
    |codeView|

    (codeView := self codeView) notNil ifTrue:[
        codeView modified:aBoolean
    ].
    specialEditors notNil ifTrue:[
        specialEditors do:[:anEditor | 
            anEditor application modified:aBoolean
        ].    
    ].
!

noteBookView
    ^ noteBookView
!

noteBookView:something
    noteBookView := something.
!

realModifiedState
    ^ self realModifiedStateHolder value
!

realModifiedState:aBoolean
    self realModifiedStateHolder value:aBoolean
!

realModifiedStateHolder
    realModifiedStateHolder isNil ifTrue:[
        realModifiedStateHolder := ValueHolder new.
    ].
    ^ realModifiedStateHolder
!

selectedEditorNoteBookTabIndexHolder
    selectedEditorNoteBookTabIndexHolder isNil ifTrue:[
        selectedEditorNoteBookTabIndexHolder := 1 asValue.
    ].
    ^ selectedEditorNoteBookTabIndexHolder
!

stringSearchToolView
    ^ stringSearchToolView
!

stringSearchToolView: aStringSearchTool

    stringSearchToolView := aStringSearchTool
! !

!NavigationState methodsFor:'accessing-selection'!

theSingleSelectedClass
    "if only one class is selected, return it.
     Otherwise, return nil"

    |classes|

    classes := self selectedClasses value.
    classes size == 1 ifTrue:[
        ^ classes first
    ].
    ^ nil
!

theSingleSelectedMethod
    "if only one method is selected, return it.
     Otherwise, return nil"

    |methods|

    methods := self selectedMethods value.
    methods size == 1 ifTrue:[
        ^ methods first
    ].
    ^ nil
! !

!NavigationState methodsFor:'accessing-subApps'!

applicationOfComponent:aComponentName
    ^ self applicationOfComponent:aComponentName or:nil

!

applicationOfComponent:aComponentName or:anotherComponentName
    |builder view|

    canvas isNil ifTrue:[^ nil].

    builder := canvas builder.

    view := builder findVisibleComponentAt:aComponentName.
    (view isNil and:[anotherComponentName notNil]) ifTrue:[
        view := builder findVisibleComponentAt:anotherComponentName.
    ].

    view notNil ifTrue:[
        ^ view application
    ].
    ^ nil
!

classCategoryListApplication
    ^ self applicationOfComponent:#ClassCategoryList

!

classHierarchyListApplication
    ^ self applicationOfComponent:#ClassHierarchyList
!

classListApplication
    ^ self applicationOfComponent:#ClassList

!

metaToggleComponent
    ^ canvas builder findComponentAt:#ClassToggle.
!

methodCategoryListApplication
    ^ self applicationOfComponent:#MethodCategoryList
!

methodListApplication
    ^ self applicationOfComponent:#MethodList
!

nameSpaceListApplication
    ^ self applicationOfComponent:#NamespaceList or:#PseudoNamespaceList
!

projectListApplication
    ^ self applicationOfComponent:#ProjectList or:#PseudoProjectList
!

variableListApplication
    ^ self applicationOfComponent:#VariableList 
!

versionDiffApplication
    ^ versionDiffApplication

!

versionDiffApplication:anApplication
    versionDiffApplication := anApplication

! !

!NavigationState methodsFor:'accessing-subViews'!

anySpecialEditorModified
    specialEditors notNil ifTrue:[
        ^ specialEditors contains:[:anEditor | anEditor application isModified].    
    ].
    ^ false
!

codeView
    codeView isNil ifTrue:[
        codeView := self scrollableCodeView scrolledView
    ].
    ^ codeView
!

doSaveInSpecialEditors
    specialEditors notNil ifTrue:[
        specialEditors do:[:anEditor | 
            anEditor application isModified ifTrue:[
                anEditor application save.
                ^ self.
            ]
        ].    
    ].
!

documentationView
    |textView|

    documentationView isNil ifTrue:[
        textView := CodeView new.
        documentationView := HVScrollableView forView:textView.
    ].
    ^ documentationView
!

getCodeView
    ^ codeView
!

inheritanceView
    inheritanceView isNil ifTrue:[
        |classTreeView scrolledView|

        classTreeView := ClassTreeGraphView new.
        scrolledView := HVScrollableView forView:classTreeView.
        classTreeView middleButtonMenu:nil.
        inheritanceView := scrolledView
    ].
    ^ inheritanceView
!

scrollableCodeView
    scrollableCodeView isNil ifTrue:[
        scrollableCodeView := self setUpScrollableCodeView.
    ].
    ^ scrollableCodeView
!

setUpScrollableCodeView
    |v aScrollableCodeView codeView|

    aScrollableCodeView := HVScrollableView for:CodeView.
    aScrollableCodeView name:'CodeView'.
    aScrollableCodeView horizontalMini:true.
    codeView := aScrollableCodeView scrolledView.
    codeView modifiedChannel:self codeModifiedHolder.
    codeView model: self codeHolder.
    codeView canTab:true.

    UserPreferences current showAcceptCancelBarInBrowser ifTrue:[
        ViewWithAcceptAndCancelBar notNil ifTrue:[
            v := ViewWithAcceptAndCancelBar new.
            v slaveView:aScrollableCodeView.
            v reallyModifiedHolder:self realModifiedStateHolder.
            v cancelAction:[
                    "/ codeView setClipboardText:(codeView contents).   "/ for undo
                    codeView device rememberInCopyBufferHistory:(codeView contents).  "/ for undo
                    codeView application 
                        delayedUpdateCodeWithAutoSearch:false checkModified:false.
                    codeView requestFocus. 
                ].
            v compareAction:[ 
                    codeView application doCompareIn:self.
                    codeView requestFocus 
                ].
            aScrollableCodeView := v.
        ]
    ].
    ^ aScrollableCodeView

    "Modified: / 25-08-2010 / 22:04:07 / cg"
!

specialEditorCanvasClassForResourceType:resourceTypeSymbol
    resourceTypeSymbol == #fileImage ifTrue:[
        ^ nil
    ].
    ^ SystemBrowser resourceEditorClassFor:resourceTypeSymbol
!

specialEditorCanvasForResourceType:resourceTypeSymbol
    |appClass app editorView|

    specialEditors isNil ifTrue:[
        specialEditors := Dictionary new.    
    ].
    editorView := specialEditors at:resourceTypeSymbol ifAbsent:nil.
    editorView isNil ifTrue:[
        appClass := self specialEditorCanvasClassForResourceType:resourceTypeSymbol.
        appClass notNil ifTrue:[
            app := appClass new.
            app masterApplication:self canvas application.
            app isEmbeddedInBrowser:true.
            app infoLabelHolder:(self canvas application infoLabelHolder).

            editorView := ApplicationSubView new.
            editorView buildMenu:true.
            editorView client:app.
            app builder window:editorView.

            specialEditors at:resourceTypeSymbol put:editorView.
        ].
    ].
    ^ editorView
! !

!NavigationState methodsFor:'aspects'!

categoryList
    categoryList isNil ifTrue:[
        categoryList := nil asValue.
    ].
    ^ categoryList

    "Modified: / 25.2.2000 / 01:35:42 / cg"
    "Created: / 25.2.2000 / 01:57:45 / cg"
!

categoryListGenerator
    categoryListGenerator isNil ifTrue:[
        categoryListGenerator := nil asValue.
    ].
    ^ categoryListGenerator

    "Created: / 25.2.2000 / 01:34:30 / cg"
    "Modified: / 25.2.2000 / 01:35:42 / cg"
!

classDocumentationHolder
    classDocumentationHolder isNil ifTrue:[
        classDocumentationHolder := nil asValue.
    ].
    ^ classDocumentationHolder
!

classHierarchyTopClass
    classHierarchyTopClass isNil ifTrue:[
        classHierarchyTopClass := nil asValue.
    ].
    ^ classHierarchyTopClass

!

classList
    classList isNil ifTrue:[
        classList := nil asValue.
    ].
    ^ classList

    "Created: / 25.2.2000 / 01:57:28 / cg"
!

classListGenerator
    classListGenerator isNil ifTrue:[
        classListGenerator := nil asValue.
    ].
    ^ classListGenerator


!

classListPerNameSpaceGenerator
    classListPerNameSpaceGenerator isNil ifTrue:[
        classListPerNameSpaceGenerator := nil asValue.
    ].
    ^ classListPerNameSpaceGenerator

    "Created: / 18.8.2000 / 14:15:34 / cg"
!

codeHolder
    codeHolder isNil ifTrue:[
        codeHolder := nil asValue.
    ].
    ^ codeHolder

!

codeModifiedHolder
    codeModifiedHolder isNil ifTrue:[
        codeModifiedHolder := false asValue.
    ].
    ^ codeModifiedHolder
!

cursorColLabelHolder
    cursorColLabelHolder isNil ifTrue:[
"/        self codeView isNil ifTrue:[^ nil].

        cursorColLabelHolder := BlockValue 
                                    with:[:v | v printString]
                                    argument:self codeView cursorColHolder.
    ].
    ^ cursorColLabelHolder
!

cursorLineLabelHolder
    cursorLineLabelHolder isNil ifTrue:[
"/        self codeView isNil ifTrue:[^ nil].

        cursorLineLabelHolder := BlockValue 
                                    with:[:v | v printString]
                                    argument:self codeView cursorLineHolder.
    ].
    ^ cursorLineLabelHolder
!

editModeHolder
    editModeHolder isNil ifTrue:[
        editModeHolder := self codeView editModeHolder.
    ].
    ^ editModeHolder
!

filterClassVars
    filterClassVars isNil ifTrue:[
        filterClassVars := false asValue.
    ].
    ^ filterClassVars

    "Created: / 24.2.2000 / 23:45:28 / cg"
!

hidePrivateClasses
    hidePrivateClasses isNil ifTrue:[
        hidePrivateClasses := false asValue.
    ].
    ^ hidePrivateClasses

    "Created: / 24.2.2000 / 16:17:02 / cg"
!

infoLabelHolder 
    infoLabelHolder isNil ifTrue:[
        infoLabelHolder := '' asValue.
    ].
    ^ infoLabelHolder
!

meta
    meta isNil ifTrue:[
        meta := false asValue.
    ].
    ^ meta


!

metaToggleLabelHolder
    metaToggleLabel isNil ifTrue:[
        metaToggleLabel := 'Class' asValue.
    ].
    ^ metaToggleLabel
!

methodInfo
    methodInfo isNil ifTrue:[
        methodInfo := nil asValue.
    ].
    ^ methodInfo

!

methodList
    |methodListApplication|

    methodListApplication := self methodListApplication.
    methodListApplication isNil ifTrue:[^ nil].

    ^ methodListApplication methodList
!

modeLabelHolder
    modeLabelHolder isNil ifTrue:[
        modeLabelHolder := self codeView modeLabelHolder.
    ].
    ^ modeLabelHolder
!

nameSpaceFilter
    nameSpaceFilter isNil ifTrue:[
        nameSpaceFilter := nil asValue.
    ].
    ^ nameSpaceFilter

    "Created: / 18.8.2000 / 14:25:24 / cg"
!

nameSpaceListGenerator
    nameSpaceListGenerator isNil ifTrue:[
        nameSpaceListGenerator := nil asValue.
    ].
    ^ nameSpaceListGenerator

    "Created: / 18.8.2000 / 14:26:19 / cg"
    "Modified: / 18.8.2000 / 14:27:59 / cg"
!

noAllItem
    noAllItem isNil ifTrue:[
        noAllItem := nil asValue.
    ].
    ^ noAllItem
!

organizerMode
    "return the organizerMode holder; 
     holding a symbol describing how things are organized
     (#category, #hierarchy, #project or #namespace)"

    organizerMode isNil ifTrue:[
        organizerMode := OrganizerCanvas organizerModeCategory asValue.
    ].
    ^ organizerMode

    "Created: / 18.2.2000 / 13:33:55 / cg"
    "Modified: / 18.8.2000 / 18:37:22 / cg"
!

packageFilter
    packageFilter isNil ifTrue:[
        packageFilter := nil asValue.
    ].
    ^ packageFilter

    "Created: / 24.2.2000 / 23:45:28 / cg"
!

packageLabelHolder
    packageLabelHolder isNil ifTrue:[
        packageLabelHolder := '' asValue.
    ].
    ^ packageLabelHolder
!

projectListGenerator
    projectListGenerator isNil ifTrue:[
        projectListGenerator := nil asValue.
    ].
    ^ projectListGenerator

    "Modified: / 25.2.2000 / 01:35:42 / cg"
    "Created: / 25.2.2000 / 02:43:26 / cg"
!

protocolListGenerator
    protocolListGenerator isNil ifTrue:[
        protocolListGenerator := nil asValue.
    ].
    ^ protocolListGenerator

!

selectedCategories
    selectedCategories isNil ifTrue:[
        selectedCategories := nil asValue.
    ].
    ^ selectedCategories

!

selectedClasses
    selectedClasses isNil ifTrue:[
        selectedClasses := "SpecialValueHolder with:nil." nil asValue.
    ].
    ^ selectedClasses
!

selectedMethods
    selectedMethods isNil ifTrue:[
        selectedMethods := nil asValue.
    ].
    ^ selectedMethods

!

selectedMethodsArrayAt:index
    |holder|

    selectedMethodsArray isNil ifTrue:[
        selectedMethodsArray := OrderedCollection new 
    ].
    index > selectedMethodsArray size ifTrue:[
        selectedMethodsArray grow:index
    ].
    holder := selectedMethodsArray at:index.
    holder isNil ifTrue:[
        selectedMethodsArray at:index put:(holder := ValueHolder new)
    ].
    ^ holder.
!

selectedNamespaces
    selectedNamespaces isNil ifTrue:[
        selectedNamespaces := nil asValue.
    ].
    ^ selectedNamespaces

!

selectedProjects
    selectedProjects isNil ifTrue:[
        selectedProjects := nil asValue.
    ].
    ^ selectedProjects

!

selectedProtocols
    selectedProtocols isNil ifTrue:[
        selectedProtocols := nil asValue.
    ].
    ^ selectedProtocols

!

selectorListGenerator
    selectorListGenerator isNil ifTrue:[
        selectorListGenerator := nil asValue.
    ].
    ^ selectorListGenerator

!

selectorListGeneratorArray
    self halt:'should not be invoked'.
!

selectorListGeneratorArrayAt:index
    |holder|

    selectorListGeneratorArray isNil ifTrue:[
        selectorListGeneratorArray := OrderedCollection new 
    ].
    index > selectorListGeneratorArray size ifTrue:[
        selectorListGeneratorArray grow:index
    ].
    holder := selectorListGeneratorArray at:index.
    holder isNil ifTrue:[
        selectorListGeneratorArray at:index put:(holder := ValueHolder new)
    ].
    ^ holder.
!

sortBy
    sortBy isNil ifTrue:[
        sortBy := nil asValue.
    ].
    ^ sortBy
!

variableFilter
    variableFilter isNil ifTrue:[
        variableFilter := nil asValue.
    ].
    ^ variableFilter

    "Created: / 24.2.2000 / 23:45:28 / cg"
! !

!NavigationState methodsFor:'aspects-kludges'!

metaToggle
    metaToggle isNil ifTrue:[
        metaToggle := PluggableAdaptor on:(self meta).
        metaToggle
            getBlock:[:m | m value == true]
            putBlock:[:m :newValue | m value:(newValue ? false)]
            updateBlock:[:m :aspect :param | true].
    ].
    ^ metaToggle
!

notMetaToggle
    notMetaToggle isNil ifTrue:[
        notMetaToggle := PluggableAdaptor on:(self meta).
        notMetaToggle
            getBlock:[:m | m value == false]
            putBlock:[:m :newValue | m value:(newValue ? false) not]
            updateBlock:[:m :aspect :param | true].
    ].
    ^ notMetaToggle
! !

!NavigationState methodsFor:'printing & storing'!

colorizeForModifiedBuffer:someString
    ^ someString asText emphasisAllAdd:(UserPreferences current emphasisForModifiedBuffer)
!

nameString
    "a descriptive string of what this state shows"

    |s|

    s := self rawNameStringOrNil ? 'nothing selected'.

    (self realModifiedState == true) ifTrue:[
        ^ self colorizeForModifiedBuffer:s string
    ].
    ^ s
!

nameStringOrNil
    "a descriptive string of what this state shows"

    |s "codeView"|

    s := self rawNameStringOrNil.
    s notNil ifTrue:[
        self realModifiedState == true 
"/    ((codeView := self codeView) notNil
"/    and:[codeView modified]) 
        ifTrue:[
            ^ self colorizeForModifiedBuffer:s string
        ].
    ].
    ^ s
!

rawNameStringForCategory
    |categories theCategory|

    categories := self selectedCategories value.
    categories size == 1 ifTrue:[
        theCategory := categories first.
        theCategory notNil ifTrue:[
            ^ theCategory string, ' [Category]'
        ].
    ].
    ^ nil

    "Created: / 18.8.2000 / 19:42:42 / cg"
!

rawNameStringForNameSpace
    |namespaces theNamespace nsName s|

    namespaces := self selectedNamespaces value.
    namespaces size == 1 ifTrue:[
        theNamespace := namespaces first
    ].
    theNamespace notNil ifTrue:[
        theNamespace isNameSpace ifTrue:[
            nsName := theNamespace name
        ] ifFalse:[
            nsName := theNamespace
        ].
        s := nsName , ' [NameSpace]'.
        (self isNameSpaceBrowser or:[self isNameSpaceFullBrowser]) ifTrue:[
            ^ LabelAndIcon icon:(NewSystemBrowser nameSpaceIcon) string:s.
        ].
        ^ s
    ].
    ^ nil

    "Created: / 18.8.2000 / 20:15:02 / cg"
!

rawNameStringForProject
    |projects theProject s|

    projects := self selectedProjects value.
    projects size == 1 ifTrue:[
        theProject := projects first
    ].
    theProject notNil ifTrue:[
        s := theProject , ' [Project]'.
        (self isProjectBrowser or:[self isProjectFullBrowser]) ifTrue:[
            ^ LabelAndIcon icon:(NewSystemBrowser packageIcon) string:s.
        ].
        ^ s
    ].
    ^ nil

    "Created: / 18.8.2000 / 20:18:34 / cg"
!

rawNameStringOrNil
    "a descriptive string of what this state shows; nil, if nothing is selected"

    ^ self rawNameStringOrNilWantShort:false
!

rawNameStringOrNilWantShort:shortName
    "a descriptive string of what this state shows; nil, if nothing is selected"

    |lbl nr numClasses numMethods numCategories cats classes theClass   
     "protocols theProtocol" 
     methods theSingleMethod projects theProject longName nm methodName suffix cls|

    browserLabel notNil ifTrue:[
        "/ add the number of selected methods
        ((canvasType == #singleFullProtocolBrowserSpec)
        or:[canvasType == #methodListBrowserSpec]) ifTrue:[
            nr := self selectedMethods value size.
            nr > 5 ifTrue:[
                ^ browserLabel string , ' - ' , nr printString , ' methods'
            ].
        ].
        ^ browserLabel
    ].

    suffix := ''.

    self isProtocolOrFullProtocolBrowser ifTrue:[
        lbl := self rawNameStringForProject.
        lbl notNil ifTrue:[^ lbl].
        suffix := ' [Protocol]'.
    ].

    self isCategoryBrowser ifTrue:[
        lbl := self rawNameStringForCategory.
        lbl notNil ifTrue:[^ lbl].
        suffix := ' [Category]'.
    ].

    self isNameSpaceBrowser ifTrue:[
        lbl := self rawNameStringForNameSpace.
        lbl notNil ifTrue:[^ lbl].
        suffix := ' [NameSpace]'.
    ].

    self isProjectBrowser ifTrue:[
        projects := self selectedProjects value.
        projects size == 1 ifTrue:[
            theProject := projects first
        ].
        suffix := ' [Project]'.
        theProject notNil ifTrue:[
            ^ theProject , suffix
        ]
    ].

    classes := self selectedClasses value.
    classes size == 1 ifTrue:[
        theClass := classes first.
        theClass notNil ifTrue:[
            theClass := theClass theNonMetaclass
        ]
    ].

    self isClassBrowser ifTrue:[
        suffix := ' [Class]'.
        theClass notNil ifTrue:[
            ^ theClass name , suffix
        ]
    ].

"/    protocols := self selectedProtocols value.
"/    protocols size == 1 ifTrue:[
"/        theProtocol := protocols first
"/    ].

    methods := self selectedMethods value.
    methods size == 1 ifTrue:[
        theSingleMethod := methods first
    ].

    theSingleMethod notNil ifTrue:[
        methodName := theSingleMethod selector.
        theSingleMethod isJavaMethod ifTrue:[
            methodName := theSingleMethod printStringForBrowserWithSelector:methodName.
        ].
    ].

    self isMethodBrowser ifTrue:[
        suffix := ' [Selector]'.

        theSingleMethod notNil ifTrue:[
            theSingleMethod mclass isNil ifTrue:[
                ^ '???'
            ].
            ^ theSingleMethod mclass name , ' ' , methodName , suffix
        ]
    ].

    self isCategoryBrowser ifTrue:[
        suffix :=  ' [Category]'.
    ] ifFalse:[
        self isFullClassSourceBrowser ifTrue:[
            suffix :=  ' [Full]'.
        ] ifFalse:[
            self isClassDocumentationBrowser ifTrue:[
                suffix :=  ' [Doc]'.
            ] ifFalse:[
                self isProjectBrowser ifTrue:[
                    suffix :=  ' [Project]'.
                ]
            ]
        ]
    ].

    nm := nil.
    (numClasses := classes size) > 0 ifTrue:[
        numClasses > 1 ifTrue:[
            methods size > 0 ifTrue:[
                theSingleMethod notNil ifTrue:[
                    cls := theSingleMethod mclass.
                    cls isNil ifTrue:[ 
                        "/ oops - unbound
                        nm := '???'
                    ] ifFalse:[
                        longName := nm := cls nameInBrowser.
                        shortName ifTrue:[
                            nm := cls nameWithoutPrefix.
                            cls isPrivate ifTrue:[
                                nm := ':' , nm
                            ]
                        ].
                    ].
                    nm := nm , ' ', (methodName ? '???')
                ] ifFalse:[
                    nm := methods size printString , ' methods'.
                    numClasses := (methods collect:[:each | each mclass]) asIdentitySet size.
                    numClasses > 1 ifTrue:[
                        nm := nm , ' in ' , numClasses printString , ' classes'.
                    ].
                ].
                ^ nm , suffix.
            ].

            nm := numClasses printString , ' classes in '.
            "/ cats := self selectedCategories value
            cats := (classes collect:[:each | each category]) asSet.
            (numCategories := cats size) == 1 ifTrue:[
                nm := nm , cats first
            ] ifFalse:[
                nm := nm , numCategories printString , ' categories'
            ]
        ] ifFalse:[
            cls := theClass theNonMetaclass.
            longName := nm := cls nameInBrowser.
            shortName ifTrue:[
                nm := cls nameWithoutPrefix.
                cls isPrivate ifTrue:[
                    nm := ':' , nm
                ]
            ].
            methods := self selectedMethods value.
            (numMethods := methods size) > 0 ifTrue:[
                numMethods == 1 ifTrue:[
                    theSingleMethod := methods first.
                    nm := nm , ' ', (methodName ? '???')
                ] ifFalse:[
                    nm := numMethods printString , ' methods in ' , nm
                ]
            ]
        ]
    ] ifFalse:[
        (self isNameSpaceBrowser 
        or:[self isNameSpaceFullBrowser
        or:[organizerMode value == OrganizerCanvas organizerModeNamespace]]) ifTrue:[
            lbl := self rawNameStringForNameSpace.
            lbl notNil ifTrue:[^ lbl].
            suffix := ' [NameSpace]'.
        ] ifFalse:[
            (self isProjectBrowser 
            or:[self isProjectFullBrowser
            or:[organizerMode value == OrganizerCanvas organizerModeProject]]) ifTrue:[
                lbl := self rawNameStringForProject.
                lbl notNil ifTrue:[^ lbl].
                suffix := ' [Project]'.
            ] ifFalse:[
                cats := self selectedCategories value.
                cats size == 1 ifTrue:[
                    nm := cats first string
                ]
            ]
        ].
    ].
    nm isNil ifTrue:[ ^ nil ].
    ^ nm , suffix.

    "Created: / 11.2.2000 / 13:32:16 / cg"
    "Modified: / 18.8.2000 / 21:06:35 / cg"
!

shortNameString
    "a descriptive string of what this state shows"

    |s|

    s := (self rawNameStringOrNilWantShort:true) ? 'nothing selected'.

    (self realModifiedState == true) ifTrue:[
        ^ self colorizeForModifiedBuffer:s string
    ].
    ^ s
! !

!NavigationState methodsFor:'queries'!

isCategoryBrowser
    ^ canvasType == #categoryBrowserSpec
      or:[ canvasType == #singleCategoryBrowserSpec
      or:[ canvasType == #multipleCategoryBrowserSpec ]]

    "Modified: / 25.2.2000 / 01:17:02 / cg"
!

isChainBrowser
    ^ canvasType == #chainBrowserSpec    
!

isCheckOutputBrowser
    ^ canvasType == #multipleClassWithInfoAndMethodWithInfoBrowserSpec
      or:[canvasType == #multipleMethodWithInfoBrowserSpec
      or:[canvasType == #multipleClassWithInfoBrowserSpec]]
!

isClassBrowser
    ^ canvasType == #classBrowserSpec
      or:[ canvasType == #singleClassBrowserSpec
      or:[ canvasType == #multipleClassBrowserSpec ]]

    "Modified: / 25.2.2000 / 00:38:07 / cg"
!

isClassDocumentationBrowser
    ^ canvasType == #classDocumentationBrowserSpec

    "Created: / 24.2.2000 / 14:54:40 / cg"
!

isClassExtensionBrowser
    ^ canvasType == #multipleClassExtensionBrowserSpec

    "Created: / 24.2.2000 / 14:54:40 / cg"
!

isFullBrowser
    ^ canvasType == #fullBrowserSpec
!

isFullClassSourceBrowser
    ^ canvasType == #fullClassSourceBrowserSpec

    "Created: / 24.2.2000 / 14:54:40 / cg"
!

isFullProtocolBrowser
    ^ canvasType == #singleFullProtocolBrowserSpec
      or:[ canvasType == #multipleFullProtocolBrowserSpec ]

    "Created: / 24.2.2000 / 21:32:09 / cg"
    "Modified: / 25.2.2000 / 03:11:00 / cg"
!

isMethodBrowser
    ^ canvasType == #methodListBrowserSpec
      or:[ canvasType == #singleMethodBrowserSpec
      or:[ canvasType == #multipleMethodBrowserSpec
      or:[ canvasType == #multipleMethodWithInfoBrowserSpec ]]]

    "Modified: / 1.3.2000 / 13:35:12 / cg"
!

isMethodListBrowser
    canvasType == #methodListBrowserSpec ifTrue:[^ true].
    canvasType == #multipleMethodBrowserSpec ifTrue:[^ true].
    canvasType == #singleProtocolBrowserSpec ifTrue:[^ true].
    ^ false.
!

isNameSpaceBrowser
    ^ canvasType == #singleNameSpaceBrowserSpec
      or:[ canvasType == #multipleNameSpaceBrowserSpec]

    "Modified: / 18.8.2000 / 16:12:34 / cg"
!

isNameSpaceFullBrowser
    ^ canvasType == #singleNameSpaceFullBrowserSpec
      or:[ canvasType == #multipleNameSpaceFullBrowserSpec ]

    "Created: / 18.8.2000 / 14:58:36 / cg"
!

isProjectBrowser
    ^ canvasType == #singleProjectBrowserSpec
      or:[ canvasType == #multipleProjectBrowserSpec ]

    "Created: / 24.2.2000 / 21:32:09 / cg"
    "Modified: / 25.2.2000 / 03:11:00 / cg"
!

isProjectFullBrowser
    ^ canvasType == #singleProjectFullBrowserSpec
      or:[ canvasType == #multipleProjectFullBrowserSpec ]

    "Created: / 18.8.2000 / 19:02:49 / cg"
!

isProtocolBrowser
    ^ canvasType == #singleProtocolBrowserSpec
      or:[ canvasType == #multipleProtocolBrowserSpec ]

    "Created: / 24.2.2000 / 21:32:09 / cg"
    "Modified: / 25.2.2000 / 03:11:00 / cg"
!

isProtocolOrFullProtocolBrowser
    ^ self isProtocolBrowser
      or:[ self isFullProtocolBrowser ]
!

isSingleCategoryBrowser
    ^ canvasType == #singleCategoryBrowserSpec    
!

isSingleClassBrowser
    ^ canvasType == #singleClassBrowserSpec    
!

isSingleFullProtocolBrowser
    ^ canvasType == #singleFullProtocolBrowserSpec    
!

isSingleMethodBrowser
    ^ canvasType == #singleMethodBrowserSpec

    "Created: / 1.3.2000 / 13:35:52 / cg"
!

isSingleNamespaceBrowser
    ^ canvasType == #singleNameSpaceBrowserSpec
!

isSingleNamespaceFullBrowser
    ^ canvasType == #singleNameSpaceFullBrowserSpec
!

isSingleProjectBrowser
    ^ canvasType == #singleProjectBrowserSpec

    "Created: / 24.2.2000 / 21:32:09 / cg"
    "Modified: / 25.2.2000 / 03:11:00 / cg"
!

isSingleProjectFullBrowser
    ^ canvasType == #singleProjectFullBrowserSpec

    "Created: / 24.2.2000 / 21:32:09 / cg"
    "Modified: / 25.2.2000 / 03:11:00 / cg"
!

isSingleProtocolBrowser
    ^ canvasType == #singleProtocolBrowserSpec    
!

isVersionDiffBrowser
    ^ canvasType == #multipleClassRepositoryDiffBrowserSpec
! !

!NavigationState class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/Tools_NavigationState.st,v 1.33 2010-08-25 20:06:22 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libtool/Tools_NavigationState.st,v 1.33 2010-08-25 20:06:22 cg Exp $'
! !