SBrowser.st
author Claus Gittinger <cg@exept.de>
Sat, 18 May 1996 17:47:03 +0200
changeset 553 b67caadfe334
parent 550 c8d443ad8a96
child 573 e32bd3e46a72
permissions -rw-r--r--
showCr: -> showCR:

"
 COPYRIGHT (c) 1989 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.
"

ApplicationModel subclass:#SystemBrowser
	instanceVariableNames:'currentClass currentMethodCategory currentMethod currentSelector
		showInstance actualClasslastMethodCategory aspect lockUpdates
		autoSearch myLabel acceptClass'
	classVariableNames:'CheckForInstancesWhenRemovingClasses'
	poolDictionaries:''
	category:'Interface-Browsers'
!

!SystemBrowser class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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
"
    this class implements all kinds of class browsers.
    Typically, it is started with 'SystemBrowser open', but there are many other 
    startup messages, to launch special browsers.
    See the categories 'startup' and 'special search startup' in the classes
    protocol.

    Alse, see the extra document 'doc/misc/sbrowser.doc' or the HTML online doc
    for how to use the browser.

    written winter 89 by claus.

    Notice: SystemBrowser is currently being rewritten to be an instance
    of ApplicationModel - this transition is not yet complete and you see
    here an intermediate version. The instance variables defined here are NOT
    currently used - instead, everything is really done in the BrowserView
    which (currently) keeps the real state of the browser.
    This will certainly change ...

    [author:]
        Claus Gittinger

"
! !

!SystemBrowser class methodsFor:'initialization'!

initialize
    "Browser configuration;
     (values can be changed from your private startup file)"

"/    self classResources.

    "
     setting this to false, the removeClass function will remove
     classes WITHOUT checking for instances. Otherwise,
     it will check and let you confirm in case there are instances.
     Checking for instances may be a bit time consuming, though.
     The default is true - therefore, it will check
    "
    CheckForInstancesWhenRemovingClasses := true

    "
     CheckForInstancesWhenRemovingClasses := true
     CheckForInstancesWhenRemovingClasses := false

     SystemBrowser initialize
    "
! !

!SystemBrowser class methodsFor:'instance creation'!

open
    "launch a standard browser"

    ^ self openOnDevice:(Screen current) 

    "
     SystemBrowser open
    "
!

openInClass:aClass
    "launch a standard browser which immediately switches
     to aClass"

    ^ self openInClass:aClass selector:nil

    "
     SystemBrowser openInClass:Object
    "

    "Created: 30.4.1996 / 14:43:45 / cg"
!

openInClass:aClass selector:aSelector
    "launch a standard browser which immediately switches
     to aClass>>aSelector."

    |brwsr cls|

    brwsr := self openOnDevice:(Screen current).
    brwsr waitUntilVisible.
    cls := aClass.
    cls notNil ifTrue:[
	cls isMeta ifTrue:[
	    cls := aClass soleInstance
	].
	brwsr switchToClassNamed:cls name. 
	brwsr updateClassCategoryList.
	aClass isMeta ifTrue:[
	    brwsr instanceProtocol:false
	].
	brwsr updateMethodCategoryList.
	aSelector notNil ifTrue:[
	    brwsr switchToMethodNamed:aSelector.
	]
    ].
    ^ brwsr

    "
     SystemBrowser openInClass:Object selector:#at:put:
     SystemBrowser openInClass:Object selector:nil
     SystemBrowser openInClass:nil selector:nil
    "

    "Created: 22.11.1995 / 21:04:50 / cg"
!

openOnDevice:aDisplay
    "launch a standard browser on another display."

    ^ self newWithLabel:(self classResources string:'System Browser')
	     setupBlock:[:browser | browser setupForAll]
	      onDevice:aDisplay

    "|d|

     d := XWorkstation new initializeFor:'porty:0'.
     d startDispatch.
     SystemBrowser openOnDevice:d
    "
! !

!SystemBrowser class methodsFor:'private helpers'!

showNoneFound
    super warn:(self classResources string:'None found').
!

showNoneFound:what
    super warn:(self classResources string:(what , '...\\... none found') withCRs).
! !

!SystemBrowser class methodsFor:'private instance creation'!

newWithLabel:aString setupBlock:aBlock
    "common helper method for all creation methods"

    ^ self newWithLabel:aString setupBlock:aBlock onDevice:Screen current
!

newWithLabel:aString setupBlock:aBlock onDevice:aWorkstation
    "common helper method for all creation methods"

    |newBrowser|

    newBrowser := BrowserView onDevice:aWorkstation.
    newBrowser title:aString.
    aBlock value:newBrowser.

    newBrowser open.
    ^ newBrowser
!

newWithLabel:aString setupSelector:aSymbol arg:arg
    "common helper method for all creation methods"

    ^ self newWithLabel:aString setupSelector:aSymbol arg:arg onDevice:Screen current 
!

newWithLabel:aString setupSelector:aSymbol arg:arg onDevice:aWorkstation
    "common helper method for all creation methods"

    |newBrowser|

    newBrowser := BrowserView onDevice:aWorkstation.
    newBrowser title:aString.
    newBrowser perform:aSymbol with:arg.
    newBrowser open.
    ^ newBrowser
! !

!SystemBrowser class methodsFor:'special search startup'!

aproposSearch:aString
    "browse all methods, which have aString in their selector or
     in the methods comment.
     This is relatively slow, since all source must be processed."

    ^ self aproposSearch:aString in:(Smalltalk allClasses)

!

aproposSearch:aString in:aCollectionOfClasses
    "browse all methods, which have aString in their selector or
     in the methods comment.
     This is relatively slow, since all source must be processed."

    |matchString list s searchBlock browser|

    matchString := '*' , aString , '*'.

    list := OrderedCollection new.

    (aString includesMatchCharacters) ifTrue:[
        s := '*' , aString , '*'.
        "a matchString"
        searchBlock := [:text | (text asCollectionOfLinesfindFirst:[:line | s match:line]) ~~ 0].
    ] ifFalse:[
        searchBlock := [:source | (source findString:aString) ~~ 0]
    ].

    browser := self browseMethodsIn:aCollectionOfClasses 
                     where:[:class :method :sel |
                                |comment|

                                Processor yield.
                                (searchBlock value:sel) ifTrue:[
                                    true
                                ] ifFalse:[
                                    comment := method comment.
                                    comment notNil 
                                    and:[searchBlock value:method comment]
                                ].
                           ]
                     title:(ClassResources string:'apropos: %1' with:aString).

    browser notNil ifTrue:[
        browser autoSearch:aString 
    ].
    ^ browser

    "
     SystemBrowser aproposSearch:'append' in:(Collection withAllSubclasses)
     SystemBrowser aproposSearch:'add'    in:(Collection withAllSubclasses)
     SystemBrowser aproposSearch:'sort'   in:(Collection withAllSubclasses)
     SystemBrowser aproposSearch:'[Aa]bsent' in:(Collection withAllSubclasses)
    "

    "Created: 9.12.1995 / 18:02:36 / cg"
!

browseAllCallsOn:aSelectorString
    "launch a browser for all senders of aSelector"

    ^ self browseAllCallsOn:aSelectorString 
                         in:(Smalltalk allClasses)
                      title:(self classResources string:'senders of: %1' with:aSelectorString)

    "
     SystemBrowser browseAllCallsOn:#+
    "

    "Created: 9.12.1995 / 18:00:41 / cg"
    "Modified: 9.12.1995 / 18:10:57 / cg"
!

browseAllCallsOn:aSelectorString in:aCollectionOfClasses title:title
    "launch a browser for all senders of aSelector in aCollectionOfClasses"

    |sel browser searchBlock|

    ((aSelectorString ~= '*') and:[aSelectorString includesMatchCharacters]) ifTrue:[
	"a matchString"
	searchBlock := [:class :method :s |
			    |lits found|

			    lits := method literals.
			    found := false.
			    lits notNil ifTrue:[
				lits do:[:aLiteral |
				    found ifFalse:[
					(aLiteral isMemberOf:Symbol) ifTrue:[
					    found := (aSelectorString match:aLiteral)
					]
				    ]
				]
			    ].
			    found
		       ].
    ] ifFalse:[
	sel := aSelectorString asSymbolIfInterned.
	sel isNil ifTrue:[
"
	    Transcript showCR:'none found.'.
"
	    self showNoneFound:title.
	    ^ nil
	].
	searchBlock := [:class :method :s | method sends:sel].
    ].
    browser := self browseMethodsIn:aCollectionOfClasses
			      where:searchBlock
			      title:title.

    browser notNil ifTrue:[
	|s|

	"
	 kludge for now, if its a multipart selector,
	 no easy search is (as yet) possible
	"
	s := aSelectorString.
	(s includes:$:) ifTrue:[
	    s := s copyTo:(s indexOf:$:)
	].
	browser autoSearch:s 
    ].
    ^ browser
!

browseCallsOn:aSelectorString under:aClass
    "launch a browser for all senders of aSelector in aClass and subclasses"

    ^ self browseAllCallsOn:aSelectorString
                         in:(aClass withAllSubclasses)
                      title:(self classResources string:'senders of: %1 (in and below %2)'
                                       with:aSelectorString 
                                       with:aClass name)

    "
     SystemBrowser browseCallsOn:#+ under:Number
    "

    "Created: 9.12.1995 / 17:59:57 / cg"
    "Modified: 9.12.1995 / 18:11:10 / cg"
!

browseClassRefsTo:aString in:aCollectionOfClasses modificationsOnly:modsOnly
    "launch a browser for all methods in aClass where the classVar named
     aString is referenced; if modsOnly is true, browse only methods where the
     classvar is modified"

    ^ self browseRefsTo:aString classVars:true in:aCollectionOfClasses modificationsOnly:modsOnly
!

browseClassRefsTo:varName in:aCollectionOfClasses modificationsOnly:modsOnly title:title
    "launch a browser for all methods in aCollectionOfClasses,
     where the classVar named aString is referenced; 
     if modsOnly is true, browse only methods where the classvar is modified"

    ^ self browseRefsTo:varName classVars:true in:aCollectionOfClasses modificationsOnly:modsOnly title:title
!

browseClassRefsTo:aString under:aClass modificationsOnly:modsOnly
    "launch a browser for all methods in aClass and subclasses
     where the classVar named aString is referenced; 
     if modsOnly is true, browse only methods where the classvar is modified"

    ^ self browseClassRefsTo:aString in:(aClass withAllSubclasses) modificationsOnly:modsOnly

!

browseForString:aString
    "launch a browser for all methods containing a string in their source.
     This may be slow, since source-code has to be scanned."

    ^ self browseForString:aString in:(Smalltalk allClasses)
!

browseForString:aString in:aCollectionOfClasses
    "launch a browser for all methods in aCollectionOfClasses  
     containing a string in their source.
     This may be slow, since source-code has to be scanned."

    |browser searchBlock title s|

    title := self classResources string:'methods containing: %1' with:aString displayString.

    (aString includesMatchCharacters) ifTrue:[
        s := '*' , aString , '*'.
        "a matchString"
        searchBlock := [:c :m :sel | 
                            |src|       
                            src := m source.
                            src isNil ifTrue:['no source' printNL. false]
                            ifFalse:[s match:m source]
                       ]
    ] ifFalse:[
        searchBlock := [:c :m :sel | 
                            |src|

                            src := m source.
                            src isNil ifTrue:['no source' printNL. false]
                            ifFalse:[ (m source findString:aString) ~~ 0 ]
                       ]
    ].
    browser := self browseMethodsIn:aCollectionOfClasses where:searchBlock title:title.

    browser notNil ifTrue:[
        browser autoSearch:aString
    ].
    ^ browser

    "
     SystemBrowser browseForString:'all' in:(Array with:Object)
     SystemBrowser browseForString:'should' in:(Array with:Object)
     SystemBrowser browseForString:'[eE]rror' in:(Array with:Object)
    "

    "Created: 9.12.1995 / 18:03:12 / cg"
    "Modified: 12.4.1996 / 19:03:29 / cg"
!

browseForSymbol:aSymbol
    "launch a browser for all methods referencing aSymbol"

    ^ self browseForSymbol:aSymbol title:(self classResources string:'users of: %1' with:aSymbol) warnIfNone:true

    "Created: 9.12.1995 / 18:04:34 / cg"
    "Modified: 9.12.1995 / 18:11:22 / cg"
!

browseForSymbol:aSymbol title:title warnIfNone:doWarn
    "launch a browser for all methods referencing aSymbol"

    |browser searchBlock sym|

    (aSymbol includesMatchCharacters) ifTrue:[
        "a matchString"
        searchBlock := [:c :m :s |
                            |found lits|

                            lits := m literals.
                            found := false.
                            lits notNil ifTrue:[
                                lits do:[:aLiteral |
                                    found ifFalse:[
                                        (aLiteral isMemberOf:Symbol) ifTrue:[
                                            found := (aSymbol match:aLiteral)
                                        ]
                                    ]
                                ]
                            ].
                            found
                       ].
    ] ifFalse:[
        "
         can do a faster search
        "
        sym := aSymbol asSymbolIfInterned.
        sym isNil ifTrue:[
            self showNoneFound:title.
            ^ nil
        ].

        searchBlock := [:c :m :s |
                            |found lits|

                            lits := m literals.
                            found := false.
                            lits notNil ifTrue:[
                                lits do:[:aLiteral |
                                    found ifFalse:[
                                        (aLiteral isMemberOf:Symbol) ifTrue:[
                                            found := (sym == aLiteral)
                                        ]
                                    ]
                                ]
                            ].
                            found
                       ].
    ].
    doWarn ifFalse:[
        WarningSignal ignoreIn:[
            browser := self browseMethodsWhere:searchBlock title:title.
        ]
    ] ifTrue:[
        browser := self browseMethodsWhere:searchBlock title:title.
    ].
    browser notNil ifTrue:[
        browser autoSearch:aSymbol
    ].
    ^ browser

    "Modified: 20.2.1996 / 20:25:42 / cg"
!

browseImplementorsOf:aSelectorString
    "launch a browser for all implementors of aSelector"

    ^ self browseImplementorsOf:aSelectorString
                             in:(Smalltalk allClasses)
                          title:(self classResources string:'implementors of: %1' with:aSelectorString)

    "
     SystemBrowser browseImplementorsOf:#+
    "

    "Created: 9.12.1995 / 18:01:18 / cg"
    "Modified: 9.12.1995 / 18:11:28 / cg"
!

browseImplementorsOf:aSelectorString in:aCollectionOfClasses title:title
    "launch a browser for all implementors of aSelector in
     the classes contained in aCollectionOfClasses and its metaclasses"

    |list sel|

    list := Set new.

    ((aSelectorString ~= '*') and:[aSelectorString includesMatchCharacters]) ifTrue:[
        "a matchString"

        aCollectionOfClasses do:[:aClass |
            |nm|

            nm := aClass name.
            aClass selectorArray do:[:aSelector |
                (aSelectorString match:aSelector) ifTrue:[
                    list add:(nm , ' ' , aSelector)
                ]
            ].
            aClass isMeta ifFalse:[
                aClass class selectorArray do:[:aSelector |
                    (aSelectorString match:aSelector) ifTrue:[
                        list add:(nm , 'class ' , aSelector)
                    ]
                ]
            ]
        ]
    ] ifFalse:[
        "can do a faster search"

        sel := aSelectorString asSymbolIfInterned.
        sel isNil ifTrue:[
            self showNoneFound:title.
            ^ nil
        ].

        aCollectionOfClasses do:[:aClass |
            |nm|

            nm := aClass name.
            (aClass implements:sel) ifTrue:[
                list add:(nm , ' ' , aSelectorString)
            ].
            aClass isMeta ifFalse:[
                (aClass class implements:sel) ifTrue:[
                    list add:(nm , 'class ' , aSelectorString)
                ]
            ]
        ]
    ].
    ^ self browseMethods:list asOrderedCollection title:title

    "
     SystemBrowser browseImplementorsOf:#+
                                     in:(Array with:Number
                                               with:Float
                                               with:SmallInteger)
                                  title:'some implementors of +'
    "

    "Modified: 4.9.1995 / 17:33:39 / claus"
    "Modified: 10.12.1995 / 16:59:03 / cg"
!

browseImplementorsOf:aSelectorString under:aClass
    "launch a browser for all implementors of aSelector in aClass
     and its subclasses"

    ^ self browseImplementorsOf:aSelectorString
                             in:(aClass withAllSubclasses)
                          title:(self classResources string:'implementors of: %1 (in and below %2)' 
                                                with:aSelectorString
                                                with:aClass name)

    "
     SystemBrowser browseImplementorsOf:#+ under:Integer
    "

    "Created: 9.12.1995 / 18:06:09 / cg"
    "Modified: 9.12.1995 / 18:11:38 / cg"
!

browseInstRefsTo:aString in:aCollectionOfClasses modificationsOnly:modsOnly
    "launch a browser for all methods in aClass where the instVar named
     aString is referenced; if modsOnly is true, browse only methods where the
     instvar is modified"

    ^ self browseRefsTo:aString classVars:false in:aCollectionOfClasses modificationsOnly:modsOnly
!

browseInstRefsTo:varName in:aCollectionOfClasses modificationsOnly:modsOnly title:title
    "launch a browser for all methods in aClass where the instVar named
     varName is referenced; if modsOnly is true, browse only methods where the
     instvar is modified"

    ^ self browseRefsTo:varName classVars:false in:aCollectionOfClasses modificationsOnly:modsOnly title:title
!

browseInstRefsTo:aString under:aClass modificationsOnly:modsOnly
    "launch a browser for all methods in aClass and subclasses
     where the instVar named aString is referenced; 
     if modsOnly is true, browse only methods where the instvar is modified"

    ^ self browseInstRefsTo:aString in:(aClass withAllSubclasses) modificationsOnly:modsOnly
!

browseReferendsOf:aGlobalName
    "launch a browser for all methods referencing a global
     named aGlobalName.
    "

    ^ self browseReferendsOf:aGlobalName warnIfNone:true 

   "
    Browser browseReferendsOf:#Transcript
   "

!

browseReferendsOf:aGlobalName warnIfNone:doWarn
    "launch a browser for all methods referencing a global
     named aGlobalName.
    "

    ^ self browseForSymbol:aGlobalName title:(self classResources string:'users of: %1' with:aGlobalName) warnIfNone:doWarn

    "Created: 9.12.1995 / 18:06:34 / cg"
    "Modified: 9.12.1995 / 18:11:45 / cg"
!

browseRefsTo:aString classVars:classVars in:aCollectionOfClasses modificationsOnly:modsOnly
    "launch a browser for all methods in aClass where the instVar/classVar named
     aString is referenced; if modsOnly is true, browse only methods where the
     instvar is modified"

    |title|

    modsOnly ifTrue:[
        title := 'modifications of: %1'
    ] ifFalse:[
        title := 'references to: %1 '
    ].
    ^ self 
        browseRefsTo:aString 
        classVars:classVars 
        in:aCollectionOfClasses 
        modificationsOnly:modsOnly 
        title:(self classResources string:title with:aString)

    "Created: 9.12.1995 / 18:07:05 / cg"
    "Modified: 9.12.1995 / 18:11:49 / cg"
!

browseRefsTo:varName classVars:classVars in:aCollectionOfClasses modificationsOnly:modsOnly title:title
    "launch a browser for all methods in aClass where the instVar/classVar named
     varName is referenced; if modsOnly is true, browse only methods where the
     instvar is modified"

    |filter browser pattern|

    filter := self filterToSearchRefsTo:varName classVars:classVars modificationsOnly:modsOnly.
    browser := self browseMethodsIn:aCollectionOfClasses 
			inst:true class:classVars where:filter title:title.

    browser notNil ifTrue:[
	modsOnly ifTrue:[
	    pattern := varName , ' :='
	] ifFalse:[
	    pattern := varName
	].
	browser autoSearch:pattern 
    ].
    ^ browser
!

browseSuperCallsIn:aCollectionOfClasses title:title
    "launch a browser for all super sends in aCollectionOfClasses"

    |sel browser searchBlock|

    searchBlock := [:class :method :s | 
        |src parser|

        src := method source.
        (src findString:'super') ~~ 0 ifTrue:[
            parser := Parser 
                        parseMethod:method source 
                        in:class 
                        ignoreErrors:true 
                        ignoreWarnings:true.

            parser notNil and:[parser usesSuper]
        ] ifFalse:[
            false
        ]
    ].

    browser := self browseMethodsIn:aCollectionOfClasses
                              where:searchBlock
                              title:title.

    browser notNil ifTrue:[
        browser autoSearch:'super' 
    ].
    ^ browser

    "
     SystemBrowser
         browseSuperCallsIn:(Array with:SortedCollection)
                      title:'superSends in SortedCollection'
    "

    "Created: 23.11.1995 / 14:08:55 / cg"
    "Modified: 24.4.1996 / 13:25:31 / cg"
!

browseSuperCallsUnder:aClass
    "launch a browser for all supersends in aClass and subclasses"

    ^ self browseSuperCallsIn:(aClass withAllSubclasses)
                        title:(self classResources string:'supersends (in and below %1)' with:aClass name)

    "
     SystemBrowser browseSuperCallsUnder:Number
    "

    "Created: 23.11.1995 / 12:06:06 / cg"
    "Modified: 9.12.1995 / 18:11:59 / cg"
!

browseUsesOf:aClass
    |dict owners offsets
     sz  "{ Class: SmallInteger }"
     n   "{ Class: SmallInteger }"
     removeSet newDict|

    owners := ObjectMemory whoReferencesInstancesOf:aClass.

    "
     collect set of offsets in dict; key is class
    "
    dict := IdentityDictionary new.
    owners do:[:someObject |
	|cls create|

	someObject isContext ifFalse:[
	    "
	     someObject refers to an instance of aClass;
	     find out, which instVar(s)
	    "
	    cls := someObject class.
	    cls ~~ Array ifTrue:[
		n := cls instSize.
		create := [|s| s := Set new. dict at:cls put:s. s].

		1 to:n do:[:i |
		    |ref|

		    ref := someObject instVarAt:i.
		    (ref isMemberOf:aClass) ifTrue:[
			offsets := dict at:cls ifAbsent:create.
			offsets add:i.
		    ]
		].
		cls isVariable ifTrue:[
		    cls isPointers ifTrue:[
			| idx "{ Class: SmallInteger }" |

			sz := someObject basicSize.
			idx := 1.
			[idx <= sz] whileTrue:[
			    |ref|

			    ref := someObject basicAt:idx.
			    (ref isMemberOf:aClass) ifTrue:[
				offsets := dict at:cls ifAbsent:create.
				offsets add:0.
				idx := sz
			    ].
			    idx := idx + 1
			]
		    ]        
		]
	    ]
	]
    ].

    "
     merge with superclass refs
    "
    dict keysAndValuesDo:[:cls :set |
	cls allSuperclasses do:[:aSuperclass |
	    |superSet|

	    superSet := dict at:aSuperclass ifAbsent:[].
	    superSet notNil ifTrue:[
		|removeSet|

		superSet := dict at:aSuperclass.
		removeSet := Set new.
		set do:[:offset |
		    (superSet includes:offset) ifTrue:[
			removeSet add:offset
		    ]
		].
		set removeAll:removeSet
	    ]
	]
    ].

    "
     remove empty ones
    "
    removeSet := Set new.
    dict keysAndValuesDo:[:cls :set |
	set isEmpty ifTrue:[
	    removeSet add:cls
	]
    ].
    removeSet do:[:cls |
	dict removeKey:cls
    ].

    "
     replace the indices by real names
    "
    newDict := IdentityDictionary new.
    dict keysAndValuesDo:[:cls :set |
	|newSet names|

	names := cls allInstVarNames.
	newSet := set collect:[:index | 
		index == 0 ifTrue:['*indexed*'] ifFalse:[names at:index].
	].
	newDict at:cls put:newSet
    ].

    newDict inspect


!

filterToSearchRefsTo:varName classVars:classVars modificationsOnly:modsOnly
    "return a searchblock for variable references"

    |searchBlock|

    searchBlock := [:c :m :s |
        |src result parser vars needMatch|

        needMatch := varName includesMatchCharacters.

        src := m source.
        src isNil ifTrue:[
            result := false
        ] ifFalse:[
            needMatch ifFalse:[
                "
                 before doing a slow parse, quickly scan the
                 methods source for the variables name ...
                "
                result := (src findString:varName) ~~ 0.
            ] ifTrue:[
                result := true.
            ].
            result ifTrue:[
                result := false.
                parser := Parser
                                parseMethod:src 
                                in:c 
                                ignoreErrors:true 
                                ignoreWarnings:true.

                (parser notNil and:[parser ~~ #Error]) ifTrue:[
                    classVars ifFalse:[
                        modsOnly ifTrue:[
                            vars := parser modifiedInstVars
                        ] ifFalse:[
                            vars := parser usedInstVars
                        ].
                    ] ifTrue:[    
                        modsOnly ifTrue:[
                            vars := parser modifiedClassVars
                        ] ifFalse:[
                            vars := parser usedClassVars
                        ].
                    ].
                    vars notNil ifTrue:[
                        needMatch ifTrue:[
                            vars do:[:cv |
                                (varName match:cv) ifTrue:[result := true]
                            ]
                        ] ifFalse:[
                            result := vars includes:varName
                        ]
                    ]
                ].
            ].
        ].
        Processor yield.
        result
    ].
    ^ searchBlock

    "Modified: 24.4.1996 / 13:21:12 / cg"
! !

!SystemBrowser class methodsFor:'startup'!

browseAllSelect:aBlock
    "launch a browser for all methods where aBlock returns true.
     The block is called with 3 arguments, class, method and seelctor."

    ^ self browseMethodsWhere:aBlock title:'selected messages'

    "
     SystemBrowser browseAllSelect:[:aClass :aMethod :selector | selector numArgs == 3]
    "
!

browseClass:aClass
    "launch a browser for aClass"

    ^ self 
	newWithLabel:aClass name
	setupSelector:#setupForClass:
	arg:aClass

    "SystemBrowser browseClass:Object"
!

browseClass:aClass methodCategory:aCategory
    "launch a browser for all methods under aCategory in aClass"

    ^ self newWithLabel:(aClass name , ' ' , aCategory)
	  setupBlock:[:browser | browser setupForClass:aClass methodCategory:aCategory]

    "SystemBrowser browseClass:String methodCategory:'copying'"
!

browseClass:aClass selector:selector
    "launch a browser for the method at selector in aClass"

    ^ self 
	newWithLabel:(aClass name , ' ' , selector , ' ' , selector)
	setupBlock:[:newBrowser | newBrowser setupForClass:aClass selector:selector]

    "
     SystemBrowser browseClass:Object selector:#printString
    "
!

browseClassCategory:aClassCategory
    "launch a browser for all classes under aCategory"

    ^ self 
	newWithLabel:aClassCategory
	setupSelector:#setupForClassCategory:
	arg:aClassCategory

    "SystemBrowser browseClassCategory:'Kernel-Objects'"
!

browseClassHierarchy:aClass
    "launch a browser for aClass and all its superclasses.
     this is different from the fullProtocol browser."

    ^ self 
	newWithLabel:(aClass name , '-' , 'hierarchy')
	setupSelector:#setupForClassHierarchy:
	arg:aClass

    "
     SystemBrowser browseClassHierarchy:Number
    "
!

browseClasses:aList title:title
    "launch a browser for all classes in aList"

    ^ self 
	newWithLabel:title
	setupSelector:#setupForClassList:
	arg:aList

    "
     SystemBrowser browseClasses:(Array with:Object
					with:Float)
			   title:'two classes'
    "
!

browseFullClassProtocol:aClass
    "launch a browser for aClasses full protocol.
     This is different from hierarchy browsing."

    ^ self 
	newWithLabel:(aClass name , '-' , 'full protocol')
	setupSelector:#setupForFullClassProtocol:
	arg:aClass

    "
     SystemBrowser browseFullClassProtocol:Number
    "
!

browseFullClasses
    "launch a browser showing all methods at once"

    ^ self 
	newWithLabel:'Full Class Browser'
	setupBlock:[:newBrowser | newBrowser setupForFullClass]

    "SystemBrowser browseFullClasses"
!

browseInstMethodsFrom:aClass where:aBlock title:title
    "launch a browser for all instance methods in aClass and all subclasses
     where aBlock evaluates to true"

    ^ self browseMethodsIn:(aClass withAllSubclasses) inst:true class:false where:aBlock title:title
!

browseInstMethodsIn:aCollectionOfClasses where:aBlock title:title
    "launch a browser for all instance methods of all classes in
     aCollectionOfClasses where aBlock evaluates to true"

    ^ self browseMethodsIn:aCollectionOfClasses inst:true class:false 
		     where:aBlock title:title
!

browseInstMethodsOf:aClass where:aBlock title:title
    "launch a browser for all instance methods in aClass
     where aBlock evaluates to true"

    ^ self browseMethodsIn:(Array with:aClass) inst:true class:false where:aBlock title:title
!

browseMethodCategory:aCategory
    "launch a browser for all methods where category = aCategory"

    |searchBlock|

    aCategory includesMatchCharacters ifTrue:[
	searchBlock := [:c :m :s | aCategory match:m category].
    ] ifFalse:[
	searchBlock := [:c :m :s | m category = aCategory]
    ].

    self browseMethodsWhere:searchBlock title:('all methods with category of ' , aCategory)

    "
     SystemBrowser browseMethodCategory:'printing & storing'
     SystemBrowser browseMethodCategory:'print*'
    "
!

browseMethods:aList title:aString
    "launch a browser for an explicit list of class/selectors.
     Each entry in the list can be either a method, or a string
     consisting of the classes name and the selector, separated by spaces. 
     For class methods, the string 'class' must be appended to the classname."

    |l|

    (aList size == 0) ifTrue:[
        self showNoneFound:aString.
        ^ nil
    ].
    l := aList asOrderedCollection.
    l := l collect:[:entry |
        |who|

        entry isString ifTrue:[
            entry
        ] ifFalse:[
            |who|

            who := entry who.
            (who at:1) name , ' ' , (who at:2)
        ]
      ].
        
    l sort.
    ^ self 
        newWithLabel:aString
        setupSelector:#setupForList:
        arg:l 

    "
     SystemBrowser 
        browseMethods:#('Object printOn:' 'Collection add:')
        title:'some methods'

     SystemBrowser 
        browseMethods:#('Behavior new:' 'Setclass new:')
        title:'some new: methods'

     SystemBrowser 
        browseMethods:(Array with:(Object compiledMethodAt:#printOn:)
                             with:(Collection compiledMethodAt:#add:)
                             with:(Object class compiledMethodAt:#initialize))
        title:'some methods'

    "

    "Modified: 12.12.1995 / 16:34:27 / cg"
!

browseMethodsFrom:aClass where:aBlock title:title
    "launch a browser for all instance- and classmethods in aClass
     and all its subclasses where aBlock evaluates to true.
     The block is called with 3 arguments, class, method and seelctor."

    ^ self browseMethodsIn:(aClass withAllSubclasses) where:aBlock title:title
!

browseMethodsIn:aCollectionOfClasses inst:wantInst class:wantClass where:aBlock title:title
    "launch a browser for all instance- (if wantInst is true) and/or
     classmethods (if wantClass is true) from classes in aCollectionOfClasses,
     where aBlock evaluates to true.
     The block is called with 3 arguments, class, method and selector."

    |list|

    "
     since this may take a long time, lower my priority ...
    "
    Processor activeProcess withLowerPriorityDo:[
        |checkedClasses checkBlock|

        checkedClasses := IdentitySet new.
        list := OrderedCollection new.

        checkBlock := [:cls |
            |methodArray selectorArray| 

            (checkedClasses includes:cls) ifFalse:[
                cls isObsolete ifTrue:[
                    Transcript showCR:'skipping obsolete class: ' , cls displayString
                ] ifFalse:[
                    methodArray := cls methodArray.
                    selectorArray := cls selectorArray.

                    1 to:methodArray size do:[:index |
                        |method sel|

                        method := methodArray at:index.
                        sel := selectorArray at:index.
                        (aBlock value:cls value:method value:sel) ifTrue:[
                            list add:(cls name , ' ' , sel)
                        ]
                    ].
                    checkedClasses add:cls.
                ]
            ]
        ].

        aCollectionOfClasses do:[:aClass |
            "
             output disabled - it slows down things too much (when searching for
             implementors or senders)
            "
            wantInst ifTrue:[
"/                Transcript show:'searching '; show:aClass name; showCR:' ...'; endEntry.
                checkBlock value:aClass
            ].
            wantClass ifTrue:[
"/                Transcript show:'searching '; show:aClass class name; showCR:' ...'; endEntry.
                checkBlock value:(aClass class)
            ].
            Processor yield
        ]
    ].
    ^ self browseMethods:list title:title

    "Created: 10.12.1995 / 15:34:57 / cg"
    "Modified: 18.5.1996 / 15:44:58 / cg"
!

browseMethodsIn:aCollectionOfClasses where:aBlock title:title
    "launch a browser for all instance- and classmethods from 
     all classes in aCollectionOfClasses where aBlock evaluates to true.
     The block is called with 3 arguments, class, method and seelctor."

    ^ self browseMethodsIn:aCollectionOfClasses inst:true class:true where:aBlock title:title

!

browseMethodsOf:aClass where:aBlock title:title
    "launch a browser for all instance- and classmethods in aClass 
     where aBlock evaluates to true.
     The block is called with 3 arguments, class, method and seelctor."

    ^ self browseMethodsIn:(Array with:aClass) where:aBlock title:title
!

browseMethodsWhere:aBlock title:title
    "launch a browser for all methods where aBlock returns true.
     The block is called with 3 arguments, class, method and seelctor."

    ^ self browseMethodsIn:(Smalltalk allClasses) where:aBlock title:title
! !

!SystemBrowser class methodsFor:'startup with query'!

askThenBrowseClass
    self getClassThenPerform:#browseClass:

    "
     SystemBrowser askThenBrowseClass
    "
!

askThenBrowseClassHierarchy
    self getClassThenPerform:#browseClassHierarchy:

    "
     SystemBrowser askThenBrowseClassHierarchy
    "
!

askThenBrowseFullClassProtocol
    self getClassThenPerform:#browseFullClassProtocol:

    "
     SystemBrowser askThenBrowseFullClassProtocol
    "
!

getClassThenPerform:aSelector
    |enterBox|

    enterBox := EnterBox title:(self classResources at:'Browse which class:') withCRs.
    enterBox okText:(ClassResources at:'browse').
    enterBox entryCompletionBlock:[:contents |
	|s what m|

	s := contents withoutSpaces.
	what := Smalltalk classnameCompletion:s.
	enterBox contents:what first.
    ].
    enterBox action:[:className |
	|cls|

	cls := Smalltalk classNamed:className.
	cls isNil ifTrue:[
	    self warn:(ClassResources at:'no such class').
	] ifFalse:[
	    self perform:aSelector with:cls  
	]
    ].
    enterBox showAtPointer

    "
     SystemBrowser getClassThenPerform:#browseClass:
    "
! !

!SystemBrowser class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/Attic/SBrowser.st,v 1.58 1996-05-18 15:47:03 cg Exp $'
! !
SystemBrowser initialize!