show privacy in senders/implementors list;
authorClaus Gittinger <cg@exept.de>
Mon, 15 Jul 1996 11:53:46 +0200
changeset 674 fa41cdb5faa5
parent 673 c227d07d31bf
child 675 57cc7dc74d67
show privacy in senders/implementors list; handle it when double clicking.
BrowserView.st
BrwsrView.st
--- a/BrowserView.st	Mon Jul 15 09:09:45 1996 +0200
+++ b/BrowserView.st	Mon Jul 15 11:53:46 1996 +0200
@@ -3300,12 +3300,19 @@
 classFromClassMethodString:aString
     "helper for classMethod-list - extract class name from the string"
 
-    |pos|
-
-    pos := aString lastIndexOf:(Character space).
-    ^ aString copyTo:(pos - 1)
+    |pos words s|
+
+    (aString endsWith:')') ifTrue:[
+        s := aString copyTo:(aString lastIndexOf:$()-1.
+        s := s withoutSpaces.
+    ] ifFalse:[
+        s := aString
+    ].
+    pos := s lastIndexOf:(Character space).
+    ^ s copyTo:(pos - 1)
 
     "Modified: 17.6.1996 / 17:06:59 / stefan"
+    "Modified: 15.7.1996 / 11:33:37 / cg"
 !
 
 classMethodSelection:lineNr
@@ -3313,9 +3320,10 @@
 
     |cls string classString selectorString meta|
 
-    string := classMethodListView selectionValue.
+    string := classMethodListView selectionValue string.
     classString := self classFromClassMethodString:string.
     selectorString := self selectorFromClassMethodString:string.
+
     ((classString ~= 'Metaclass') and:[classString endsWith:' class']) ifTrue:[
         classString := classString copyWithoutLast:6 "copyTo:(classString size - 5)".
         meta := true.
@@ -3345,17 +3353,25 @@
 
     "Modified: 31.8.1995 / 11:56:02 / claus"
     "Modified: 17.6.1996 / 16:51:28 / stefan"
+    "Modified: 15.7.1996 / 11:44:38 / cg"
 !
 
 selectorFromClassMethodString:aString
     "helper for classMethod-list - extract selector from the string"
 
-    |pos|
-
-    pos := aString lastIndexOf:(Character space).
-    ^ aString copyFrom:(pos + 1)
+    |pos s|
+
+    (aString endsWith:')') ifTrue:[
+        s := aString copyTo:(aString lastIndexOf:$()-1.
+        s := s withoutSpaces.
+    ] ifFalse:[
+        s := aString
+    ].
+    pos := s lastIndexOf:(Character space).
+    ^ s copyFrom:(pos + 1)
 
     "Modified: 17.6.1996 / 17:04:38 / stefan"
+    "Modified: 15.7.1996 / 11:33:41 / cg"
 ! !
 
 !BrowserView methodsFor:'event handling'!
@@ -4910,46 +4926,7 @@
 "/    (actualClass compiledMethodAt:currentSelector) inspect.
 
     "Modified: 4.6.1996 / 22:47:27 / cg"
-! !
-
-!BrowserView ignoredMethodsFor:'method list menu'!
-
-methodLocalAproposSearch
-    "launch an enterBox for a local keyword search"
-
-    self askForSelectorTitle:'keyword to search for:' 
-		    openWith:#aproposSearch:in:
-			 and:(currentClass withAllSubclasses)
-!
-
-methodLocalImplementors
-    "launch an enterBox for selector to search for"
-
-    self checkClassSelected ifFalse:[^ self].
-    self askForSelectorTitle:'selector to browse local implementors of:' 
-		    openWith:#browseImplementorsOf:under:
-			 and:currentClass
-!
-
-methodLocalSenders
-    "launch an enterBox for selector to search for in current class & subclasses"
-
-    self checkClassSelected ifFalse:[^ self].
-    self askForSelectorTitle:'selector to browse local senders of:' 
-		    openWith:#browseCallsOn:under:
-			 and:currentClass
-!
-
-methodLocalStringSearch
-    "launch an enterBox for string to search for"
-
-    self checkClassSelected ifFalse:[^ self].
-    self askForSelectorTitle:'string to search for in local methods:' 
-		    openWith:#browseForString:in:
-			 and:(currentClass withAllSubclasses)
-! !
-
-!BrowserView methodsFor:'method list menu'!
+!
 
 methodLocalSuperSends
     "launch a browser showing super sends in current class & subclasses"
@@ -5890,7 +5867,7 @@
     "switch (in the current class) to a method named matchString.
      If there are more than one matches, switch to the first."
 
-    |aSelector method cat classToSearch dict|
+    |aSelector method cat classToSearch dict m idx|
 
     currentClass notNil ifTrue:[
         classToSearch := actualClass.
@@ -5916,15 +5893,21 @@
 
             currentMethod := method.
             currentSelector := aSelector.
-            methodListView setSelectElement:aSelector.
+
+            m := aSelector , '*(*)'.
+            idx := methodListView list findFirst:[:line |
+                                                line = aSelector
+                                                or:[m match:line]].
+
+            methodListView setSelection:idx. "/ setSelectElement:aSelector.
             self methodSelectionChanged.
             ^ self
         ]
     ].
     self beep.
 
-    "Modified: 28.5.1996 / 16:54:49 / cg"
     "Modified: 28.6.1996 / 20:28:56 / stefan"
+    "Modified: 15.7.1996 / 11:44:11 / cg"
 !
 
 updateMethodList
@@ -6243,97 +6226,7 @@
 
     "Created: 10.7.1996 / 10:31:29 / cg"
     "Modified: 10.7.1996 / 12:50:25 / cg"
-! !
-
-!BrowserView ignoredMethodsFor:'private'!
-
-askForSelectorTitle:title
-    "convenient method: setup enterBox with text from codeView or selected
-     method for browsing based on a selector. Set action and launch box"
-
-    |box grp panel retVal selectorHolder where b|
-
-    selectorHolder := (self selectorToSearchFor) asValue.
-
-    box := Dialog new.
-    (box addTextLabel:title) adjust:#left.
-
-    box addInputFieldOn:(selectorHolder) tabable:true.
-
-    (box addTextLabel:'search in:') adjust:#left.
-
-    panel := HorizontalPanelView new.
-    panel horizontalLayout:#fitSpace.
-
-    grp := RadioButtonGroup new.
-    b := RadioButton label:'everywhere' action:[where := #everywhere].
-    panel add:b. grp add:b.
-    box makeTabable:b.
-
-    b := RadioButton label:'class category' action:[where := #classcategory.].
-    panel add:b. grp add:b.
-    box makeTabable:b.
-
-    b := RadioButton label:'class' action:[where := #class.].
-    panel add:b.grp add:b.
-    box makeTabable:b.
-
-    b := RadioButton label:'class & subclasses' action:[where := #classhierarchy.].
-    panel add:b. grp add:b.
-    box makeTabable:b.
-
-    grp value:1.
-
-    box addComponent:panel indent:0.  "/ panel has its own idea of indenting
-
-    box addAbortButton.
-    box addOkButton.
-
-    box open.
-
-
-    box := self enterBoxTitle:title okText:'browse'.
-    box initialText:(self selectorToSearchFor).
-    box action:[:aString | aString notEmpty ifTrue:[retVal := aString]].
-    box showAtPointer.
-    ^ retVal
-
-    "Modified: 10.7.1996 / 10:13:28 / cg"
-!
-
-askForSelectorTitle:title openWith:selector
-    "convenient method: setup enterBox with text from codeView or selected
-     method for browsing based on a selector. Set action and launch box"
-
-    |string|
-
-    string := self askForSelectorTitle:title.
-    string notNil ifTrue:[
-	self withSearchCursorDo:[
-	    SystemBrowser perform:selector with:string
-	]
-    ].
-
-    "Created: 23.11.1995 / 14:11:34 / cg"
-!
-
-askForSelectorTitle:title openWith:selector and:arg
-    "convenient method: setup enterBox with text from codeView or selected
-     method for browsing based on a selector. Set action and launch box"
-
-    |string|
-
-    string := self askForSelectorTitle:title.
-    string notNil ifTrue:[
-	self withSearchCursorDo:[
-	    SystemBrowser perform:selector with:string with:arg
-	]
-    ].
-
-    "Created: 23.11.1995 / 14:11:38 / cg"
-! !
-
-!BrowserView methodsFor:'private'!
+!
 
 busyLabel:what with:someArgument
     "set the title for some warning"
@@ -7473,6 +7366,6 @@
 !BrowserView  class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.158 1996-07-10 10:53:28 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.159 1996-07-15 09:53:46 cg Exp $'
 ! !
 BrowserView initialize!
--- a/BrwsrView.st	Mon Jul 15 09:09:45 1996 +0200
+++ b/BrwsrView.st	Mon Jul 15 11:53:46 1996 +0200
@@ -3300,12 +3300,19 @@
 classFromClassMethodString:aString
     "helper for classMethod-list - extract class name from the string"
 
-    |pos|
-
-    pos := aString lastIndexOf:(Character space).
-    ^ aString copyTo:(pos - 1)
+    |pos words s|
+
+    (aString endsWith:')') ifTrue:[
+        s := aString copyTo:(aString lastIndexOf:$()-1.
+        s := s withoutSpaces.
+    ] ifFalse:[
+        s := aString
+    ].
+    pos := s lastIndexOf:(Character space).
+    ^ s copyTo:(pos - 1)
 
     "Modified: 17.6.1996 / 17:06:59 / stefan"
+    "Modified: 15.7.1996 / 11:33:37 / cg"
 !
 
 classMethodSelection:lineNr
@@ -3313,9 +3320,10 @@
 
     |cls string classString selectorString meta|
 
-    string := classMethodListView selectionValue.
+    string := classMethodListView selectionValue string.
     classString := self classFromClassMethodString:string.
     selectorString := self selectorFromClassMethodString:string.
+
     ((classString ~= 'Metaclass') and:[classString endsWith:' class']) ifTrue:[
         classString := classString copyWithoutLast:6 "copyTo:(classString size - 5)".
         meta := true.
@@ -3345,17 +3353,25 @@
 
     "Modified: 31.8.1995 / 11:56:02 / claus"
     "Modified: 17.6.1996 / 16:51:28 / stefan"
+    "Modified: 15.7.1996 / 11:44:38 / cg"
 !
 
 selectorFromClassMethodString:aString
     "helper for classMethod-list - extract selector from the string"
 
-    |pos|
-
-    pos := aString lastIndexOf:(Character space).
-    ^ aString copyFrom:(pos + 1)
+    |pos s|
+
+    (aString endsWith:')') ifTrue:[
+        s := aString copyTo:(aString lastIndexOf:$()-1.
+        s := s withoutSpaces.
+    ] ifFalse:[
+        s := aString
+    ].
+    pos := s lastIndexOf:(Character space).
+    ^ s copyFrom:(pos + 1)
 
     "Modified: 17.6.1996 / 17:04:38 / stefan"
+    "Modified: 15.7.1996 / 11:33:41 / cg"
 ! !
 
 !BrowserView methodsFor:'event handling'!
@@ -4910,46 +4926,7 @@
 "/    (actualClass compiledMethodAt:currentSelector) inspect.
 
     "Modified: 4.6.1996 / 22:47:27 / cg"
-! !
-
-!BrowserView ignoredMethodsFor:'method list menu'!
-
-methodLocalAproposSearch
-    "launch an enterBox for a local keyword search"
-
-    self askForSelectorTitle:'keyword to search for:' 
-		    openWith:#aproposSearch:in:
-			 and:(currentClass withAllSubclasses)
-!
-
-methodLocalImplementors
-    "launch an enterBox for selector to search for"
-
-    self checkClassSelected ifFalse:[^ self].
-    self askForSelectorTitle:'selector to browse local implementors of:' 
-		    openWith:#browseImplementorsOf:under:
-			 and:currentClass
-!
-
-methodLocalSenders
-    "launch an enterBox for selector to search for in current class & subclasses"
-
-    self checkClassSelected ifFalse:[^ self].
-    self askForSelectorTitle:'selector to browse local senders of:' 
-		    openWith:#browseCallsOn:under:
-			 and:currentClass
-!
-
-methodLocalStringSearch
-    "launch an enterBox for string to search for"
-
-    self checkClassSelected ifFalse:[^ self].
-    self askForSelectorTitle:'string to search for in local methods:' 
-		    openWith:#browseForString:in:
-			 and:(currentClass withAllSubclasses)
-! !
-
-!BrowserView methodsFor:'method list menu'!
+!
 
 methodLocalSuperSends
     "launch a browser showing super sends in current class & subclasses"
@@ -5890,7 +5867,7 @@
     "switch (in the current class) to a method named matchString.
      If there are more than one matches, switch to the first."
 
-    |aSelector method cat classToSearch dict|
+    |aSelector method cat classToSearch dict m idx|
 
     currentClass notNil ifTrue:[
         classToSearch := actualClass.
@@ -5916,15 +5893,21 @@
 
             currentMethod := method.
             currentSelector := aSelector.
-            methodListView setSelectElement:aSelector.
+
+            m := aSelector , '*(*)'.
+            idx := methodListView list findFirst:[:line |
+                                                line = aSelector
+                                                or:[m match:line]].
+
+            methodListView setSelection:idx. "/ setSelectElement:aSelector.
             self methodSelectionChanged.
             ^ self
         ]
     ].
     self beep.
 
-    "Modified: 28.5.1996 / 16:54:49 / cg"
     "Modified: 28.6.1996 / 20:28:56 / stefan"
+    "Modified: 15.7.1996 / 11:44:11 / cg"
 !
 
 updateMethodList
@@ -6243,97 +6226,7 @@
 
     "Created: 10.7.1996 / 10:31:29 / cg"
     "Modified: 10.7.1996 / 12:50:25 / cg"
-! !
-
-!BrowserView ignoredMethodsFor:'private'!
-
-askForSelectorTitle:title
-    "convenient method: setup enterBox with text from codeView or selected
-     method for browsing based on a selector. Set action and launch box"
-
-    |box grp panel retVal selectorHolder where b|
-
-    selectorHolder := (self selectorToSearchFor) asValue.
-
-    box := Dialog new.
-    (box addTextLabel:title) adjust:#left.
-
-    box addInputFieldOn:(selectorHolder) tabable:true.
-
-    (box addTextLabel:'search in:') adjust:#left.
-
-    panel := HorizontalPanelView new.
-    panel horizontalLayout:#fitSpace.
-
-    grp := RadioButtonGroup new.
-    b := RadioButton label:'everywhere' action:[where := #everywhere].
-    panel add:b. grp add:b.
-    box makeTabable:b.
-
-    b := RadioButton label:'class category' action:[where := #classcategory.].
-    panel add:b. grp add:b.
-    box makeTabable:b.
-
-    b := RadioButton label:'class' action:[where := #class.].
-    panel add:b.grp add:b.
-    box makeTabable:b.
-
-    b := RadioButton label:'class & subclasses' action:[where := #classhierarchy.].
-    panel add:b. grp add:b.
-    box makeTabable:b.
-
-    grp value:1.
-
-    box addComponent:panel indent:0.  "/ panel has its own idea of indenting
-
-    box addAbortButton.
-    box addOkButton.
-
-    box open.
-
-
-    box := self enterBoxTitle:title okText:'browse'.
-    box initialText:(self selectorToSearchFor).
-    box action:[:aString | aString notEmpty ifTrue:[retVal := aString]].
-    box showAtPointer.
-    ^ retVal
-
-    "Modified: 10.7.1996 / 10:13:28 / cg"
-!
-
-askForSelectorTitle:title openWith:selector
-    "convenient method: setup enterBox with text from codeView or selected
-     method for browsing based on a selector. Set action and launch box"
-
-    |string|
-
-    string := self askForSelectorTitle:title.
-    string notNil ifTrue:[
-	self withSearchCursorDo:[
-	    SystemBrowser perform:selector with:string
-	]
-    ].
-
-    "Created: 23.11.1995 / 14:11:34 / cg"
-!
-
-askForSelectorTitle:title openWith:selector and:arg
-    "convenient method: setup enterBox with text from codeView or selected
-     method for browsing based on a selector. Set action and launch box"
-
-    |string|
-
-    string := self askForSelectorTitle:title.
-    string notNil ifTrue:[
-	self withSearchCursorDo:[
-	    SystemBrowser perform:selector with:string with:arg
-	]
-    ].
-
-    "Created: 23.11.1995 / 14:11:38 / cg"
-! !
-
-!BrowserView methodsFor:'private'!
+!
 
 busyLabel:what with:someArgument
     "set the title for some warning"
@@ -7473,6 +7366,6 @@
 !BrowserView  class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Attic/BrwsrView.st,v 1.158 1996-07-10 10:53:28 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Attic/BrwsrView.st,v 1.159 1996-07-15 09:53:46 cg Exp $'
 ! !
 BrowserView initialize!