added ignoreCase option to string-search.
authorClaus Gittinger <cg@exept.de>
Thu, 18 Jun 1998 16:54:51 +0200
changeset 1704 83cb6f5b8a1d
parent 1703 ea66390f879b
child 1705 5acde5f91748
added ignoreCase option to string-search.
BrowserView.st
BrwsrView.st
--- a/BrowserView.st	Thu Jun 18 16:52:55 1998 +0200
+++ b/BrowserView.st	Thu Jun 18 16:54:51 1998 +0200
@@ -21,7 +21,7 @@
 		lastCategory lastModule lastPackage lastMethodMoveClass
 		namespaceList allNamespaces gotClassList classList selectorList
 		showAllNamespaces classInstVarsInVarList coloringProcess
-		codeModified'
+		codeModified autoSearchIgnoreCase'
 	classVariableNames:'CheckForInstancesWhenRemovingClasses RememberAspect DefaultIcon
 		StopIcon TraceIcon TimeIcon CanvasIcon MenuIcon ImageIcon
 		TabListIcon HierarchicalListIcon TableColumnsIcon HelpIcon
@@ -5739,7 +5739,22 @@
      search for the searchstring in the codeView"
 
     self setSearchPattern:aString.
+    autoSearchIgnoreCase := false.
     autoSearch := aString
+
+    "Modified: / 18.6.1998 / 16:49:50 / cg"
+!
+
+autoSearch:aString ignoreCase:ign
+    "used with class-method list browsing. If true,
+     selecting an entry from the list will automatically
+     search for the searchstring in the codeView"
+
+    self setSearchPattern:aString.
+    autoSearchIgnoreCase := ign.
+    autoSearch := aString
+
+    "Created: / 18.6.1998 / 16:49:59 / cg"
 !
 
 destroy
@@ -8219,12 +8234,13 @@
     "launch an enterBox for string to search for"
 
     self 
-	askForSearchTitle:'string to search for in sources:' 
-	openWith:#browseForString:in:
-	isSelector:true
-	searchArea:#class
-
-    "Modified: 11.11.1996 / 12:44:13 / cg"
+        askForSearchTitle:'string to search for in sources:' 
+        openWith:#browseForString:in:ignoreCase:
+        isSelector:true
+        searchArea:#class
+        withCaseIgnore:true
+
+    "Modified: / 18.6.1998 / 16:42:11 / cg"
 !
 
 methodTrace
@@ -8573,7 +8589,8 @@
         "
         autoSearch notNil ifTrue:[
             codeView 
-                searchFwd:autoSearch 
+                searchFwd:autoSearch
+                ignoreCase:autoSearchIgnoreCase 
                 startingAtLine:1 col:0 
                 ifAbsent:[]
         ].
@@ -8606,7 +8623,7 @@
 
     "Created: / 23.11.1995 / 14:17:44 / cg"
     "Modified: / 17.6.1996 / 16:47:50 / stefan"
-    "Modified: / 12.1.1998 / 19:07:36 / cg"
+    "Modified: / 18.6.1998 / 16:50:37 / cg"
 !
 
 methodTemplate
@@ -9427,94 +9444,112 @@
 !BrowserView methodsFor:'private'!
 
 askAndBrowseMethodCategory:title action:aBlock
-    "convenient method: setup enterBox with initial being current method category"
+    "convenient helper method: setup enterBox with initial being current method category"
 
     |sel box|
 
     box := self 
-		enterBoxTitle:title 
-		okText:'browse'
-		label:'browse category'.
+                enterBoxTitle:title 
+                okText:'browse'
+                label:'browse category'.
 
     sel := codeView selection.
     sel isNil ifTrue:[
-	currentMethodCategory notNil ifTrue:[
-	    sel := currentMethodCategory
-	]
+        currentMethodCategory notNil ifTrue:[
+            sel := currentMethodCategory
+        ]
     ].
     sel notNil ifTrue:[
-	box initialText:(sel asString withoutSpaces)
+        box initialText:(sel asString withoutSpaces)
     ].
     box action:[:aString | self withBusyCursorDo:[aBlock value:aString]].
     box showAtPointer
 
-    "Modified: 18.8.1997 / 15:42:07 / cg"
+    "Modified: / 18.6.1998 / 16:40:46 / cg"
 !
 
 askForMethodCategory
+    "convenient helper method: setup a box asking for a method category"
+
     |someCategories box txt retVal|
 
     someCategories := actualClass categories sort.
     box := self listBoxTitle:'accept in which method category ?' okText:'accept' list:someCategories.
 
     lastMethodCategory isNil ifTrue:[
-	txt := 'new methods'
+        txt := 'new methods'
     ] ifFalse:[
-	txt := lastMethodCategory
+        txt := lastMethodCategory
     ].
     box initialText:txt.
     box action:[:aString | aString notEmpty ifTrue:[retVal := aString] ].
     box showAtPointer.
     ^ retVal
 
-    "Modified: 27.3.1996 / 15:33:46 / cg"
+    "Modified: / 18.6.1998 / 16:41:03 / cg"
 !
 
 askForSearchSelectorTitle:title openWith:aSelector
-    "convenient method: setup enterBox with text from codeView or selected
+    "convenient helper method: setup enterBox with text from codeView or selected
      method for browsing based on a selector. Set action and launch box"
 
     ^ self 
-	askForSearchTitle:title 
-	openWith:aSelector 
-	isSelector:true
-
-    "Modified: 11.11.1996 / 12:43:24 / cg"
+        askForSearchTitle:title 
+        openWith:aSelector 
+        isSelector:true
+
+    "Modified: / 18.6.1998 / 16:40:39 / cg"
 !
 
 askForSearchTitle:title openWith:aSelector isSelector:isSelector
-    "convenient method: setup enterBox with text from codeView or selected
+    "convenient helper method: setup enterBox with text from codeView or selected
      method for browsing based on a selector. Set action and launch box"
 
     ^ self
-	askForSearchTitle:title 
-	openWith:aSelector 
-	isSelector:isSelector 
-	searchArea:#everywhere
-
-    "Modified: 11.11.1996 / 12:42:46 / cg"
+        askForSearchTitle:title 
+        openWith:aSelector 
+        isSelector:isSelector 
+        searchArea:#everywhere
+
+    "Modified: / 18.6.1998 / 16:40:35 / cg"
 !
 
 askForSearchTitle:title openWith:aSelector isSelector:isSelector searchArea:whereDefault
-    "convenient method: setup enterBox with text from codeView or selected
+    "convenient helper method: setup enterBox with text from codeView or selected
      method for browsing based on a selector. Set action and launch box.
      SearchArea may be one of #everywhere, #classCategory, #class, #classWithPrivateClasses,
      #classHierarchy or #classHierarchyWithPrivateClasses"
 
-    |box grp panel selectorHolder where whereChannel 
+    ^ self
+        askForSearchTitle:title 
+        openWith:aSelector 
+        isSelector:isSelector 
+        searchArea:whereDefault 
+        withCaseIgnore:false
+
+    "Modified: / 18.6.1998 / 16:40:26 / cg"
+!
+
+askForSearchTitle:title openWith:aSelector isSelector:isSelector searchArea:whereDefault withCaseIgnore:withCaseIgnore
+    "convenient helper method: setup enterBox with text from codeView or selected
+     method for browsing based on a selector. Set action and launch box.
+     SearchArea may be one of #everywhere, #classCategory, #class, #classWithPrivateClasses,
+     #classHierarchy or #classHierarchyWithPrivateClasses"
+
+    |box grp panel selectorHolder where whereChannel caseHolder
      b sel classes areas toSearch cls privates inputField|
 
     areas := #(everywhere 
-	       classCategory 
-	       class 
-	       classHierarchy 
-	       classWithPrivateClasses 
-	       classHierarchyWithPrivateClasses).
+               classCategory 
+               class 
+               classHierarchy 
+               classWithPrivateClasses 
+               classHierarchyWithPrivateClasses).
 
     isSelector ifTrue:[
-	sel := self selectorToSearchFor.
+        sel := self selectorToSearchFor.
     ] ifFalse:[
-	sel := self stringToSearchFor.
+        sel := self stringToSearchFor.
     ].
     selectorHolder := sel asValue.
 
@@ -9524,88 +9559,94 @@
     inputField := box addInputFieldOn:selectorHolder tabable:true.
     inputField selectAll.
     inputField entryCompletionBlock:[:contents |
-	|s what m|
-
-	s := contents withoutSpaces.
-	box topView withWaitCursorDo:[
-	    what := Smalltalk selectorCompletion:s.
-	    inputField contents:what first.
-	    (what at:2) size ~~ 1 ifTrue:[
-		self beep
-	    ]
-	]
+        |s what m|
+
+        s := contents withoutSpaces.
+        box topView withWaitCursorDo:[
+            what := Smalltalk selectorCompletion:s.
+            inputField contents:what first.
+            (what at:2) size ~~ 1 ifTrue:[
+                self beep
+            ]
+        ]
+    ].
+
+    withCaseIgnore ifTrue:[
+"/        box addVerticalSpace.
+        box addCheckBox:(resources string:'ignore case') on:(caseHolder := false asValue).
+"/        box addVerticalSpace.
     ].
 
     (currentClassCategory notNil or:[currentClass notNil]) ifTrue:[
-	box addHorizontalLine.
-	box addVerticalSpace.
-
-	(box addTextLabel:(resources string:'search in:')) adjust:#left.
-
-	panel := VerticalPanelView "HorizontalPanelView" new.
-	panel horizontalLayout:#fitSpace.
-
-	grp := RadioButtonGroup new.
-	b := CheckBox "RadioButton" label:(resources string:'everywhere').
-	panel add:b. grp add:b.
-	box makeTabable:b.
-
-	currentClassCategory notNil ifTrue:[
-	    b := CheckBox "RadioButton" label:(resources string:'class category').
-	    panel add:b. grp add:b.
-	    box makeTabable:b.
-	].
-
-	currentClass notNil ifTrue:[
-	    b := CheckBox "RadioButton" label:(resources string:'class').
-	    panel add:b.grp add:b.
-	    box makeTabable:b.
-
-	    b := CheckBox "RadioButton" label:(resources string:'class & subclasses').
-	    panel add:b. grp add:b.
-	    box makeTabable:b.
-
-	    currentClass subclasses size == 0 ifTrue:[
-		b disable.
-	    ].
-
-	    b := CheckBox "RadioButton" label:(resources string:'class & private classes').
-	    panel add:b.grp add:b.
-	    box makeTabable:b.
-
-	    currentClass privateClasses size == 0 ifTrue:[
-		b disable
-	    ].
-
-	    b := CheckBox "RadioButton" label:(resources string:'class & subclasses & all private classes').
-	    panel add:b. grp add:b.
-	    box makeTabable:b.
-
-	    currentClass subclasses size == 0 ifTrue:[
-		b disable.
-	    ] ifFalse:[
+        box addHorizontalLine.
+        box addVerticalSpace.
+
+        (box addTextLabel:(resources string:'search in:')) adjust:#left.
+
+        panel := VerticalPanelView "HorizontalPanelView" new.
+        panel horizontalLayout:#fitSpace.
+
+        grp := RadioButtonGroup new.
+        b := CheckBox "RadioButton" label:(resources string:'everywhere').
+        panel add:b. grp add:b.
+        box makeTabable:b.
+
+        currentClassCategory notNil ifTrue:[
+            b := CheckBox "RadioButton" label:(resources string:'class category').
+            panel add:b. grp add:b.
+            box makeTabable:b.
+        ].
+
+        currentClass notNil ifTrue:[
+            b := CheckBox "RadioButton" label:(resources string:'class').
+            panel add:b.grp add:b.
+            box makeTabable:b.
+
+            b := CheckBox "RadioButton" label:(resources string:'class & subclasses').
+            panel add:b. grp add:b.
+            box makeTabable:b.
+
+            currentClass subclasses size == 0 ifTrue:[
+                b disable.
+            ].
+
+            b := CheckBox "RadioButton" label:(resources string:'class & private classes').
+            panel add:b.grp add:b.
+            box makeTabable:b.
+
+            currentClass privateClasses size == 0 ifTrue:[
+                b disable
+            ].
+
+            b := CheckBox "RadioButton" label:(resources string:'class & subclasses & all private classes').
+            panel add:b. grp add:b.
+            box makeTabable:b.
+
+            currentClass subclasses size == 0 ifTrue:[
+                b disable.
+            ] ifFalse:[
 "/ this takes too long ...
 "/                toSearch := IdentitySet new.
 "/                currentClass withAllSubclasses do:[:cls | toSearch add:cls privateClasses].
 "/                toSearch size == 0 ifTrue:[
 "/                    b disable
 "/                ]
-	    ]
-	].
-	whereDefault notNil ifTrue:[
-	    where := areas indexOf:whereDefault.
-	    where == 0 ifTrue:[where := 1].
-	] ifFalse:[
-	    where := 1.
-	].
-	grp value:where.
-	whereChannel := grp.
-	box addComponent:panel indent:0.  "/ panel has its own idea of indenting
-
-	box addVerticalSpace.
-	box addHorizontalLine.
+            ]
+        ].
+        whereDefault notNil ifTrue:[
+            where := areas indexOf:whereDefault.
+            where == 0 ifTrue:[where := 1].
+        ] ifFalse:[
+            where := 1.
+        ].
+        grp value:where.
+        whereChannel := grp.
+        box addComponent:panel indent:0.  "/ panel has its own idea of indenting
+
+        box addVerticalSpace.
+        box addHorizontalLine.
     ] ifFalse:[
-	whereChannel := 1 asValue.
+        whereChannel := 1 asValue.
     ].
 
     box addAbortButton.
@@ -9615,65 +9656,69 @@
     box open.
 
     box accepted ifTrue:[
-	sel := selectorHolder value.
-	where := whereChannel value.
-
-	sel isEmpty ifTrue:[
-	    self warn:'nothing entered for search'.
-	    ^ self.
-	].
-	where isNil ifTrue:[
-	    self warn:'no class(es) for search'.
-	    ^ self.
-	].
-
-	where := areas at:where ifAbsent:#class.
-
-	where == #everywhere ifTrue:[
-	    classes := Smalltalk allClasses.
-	] ifFalse:[
-	    where == #classCategory ifTrue:[
-		classes := Smalltalk allClassesInCategory:currentClassCategory
-	    ] ifFalse:[
-		(where == #class or:[where == #classWithPrivateClasses]) ifTrue:[
-		    currentClass isNil ifTrue:[
-			classes := #()
-		    ] ifFalse:[
-			classes := Array with:currentClass
-		    ]
-		] ifFalse:[
-		    (where == #classHierarchy or:[where == #classHierarchyWithPrivateClasses]) ifTrue:[
-			classes := currentClass withAllSubclasses
-		    ]
-		]
-	    ]
-	].
-	(where == #classWithPrivateClasses or:[where == #classHierarchyWithPrivateClasses]) ifTrue:[
-	    toSearch := IdentitySet withAll:classes.
-	    classes := IdentitySet withAll:toSearch.
-
-	    [toSearch notEmpty] whileTrue:[
-		cls := toSearch removeFirst.
-		privates := cls privateClasses.
-		privates notNil ifTrue:[
-		    toSearch addAll:cls privateClasses.
-		    classes addAll:cls privateClasses.
-		]
-	    ].
-	    classes := classes asOrderedCollection.
-	].
-
-	classes isEmpty ifTrue:[
-	    self warn:'no class(es) given for search'.
-	] ifFalse:[
-	    self withSearchCursorDo:[
-		SystemBrowser perform:aSelector with:sel with:classes
-	    ]
-	]
-    ]
-
-    "Created: 11.11.1996 / 12:42:14 / cg"
-    "Modified: 28.7.1997 / 18:04:04 / cg"
+        sel := selectorHolder value.
+        where := whereChannel value.
+
+        sel isEmpty ifTrue:[
+            self warn:'nothing entered for search'.
+            ^ self.
+        ].
+        where isNil ifTrue:[
+            self warn:'no class(es) for search'.
+            ^ self.
+        ].
+
+        where := areas at:where ifAbsent:#class.
+
+        where == #everywhere ifTrue:[
+            classes := Smalltalk allClasses.
+        ] ifFalse:[
+            where == #classCategory ifTrue:[
+                classes := Smalltalk allClassesInCategory:currentClassCategory
+            ] ifFalse:[
+                (where == #class or:[where == #classWithPrivateClasses]) ifTrue:[
+                    currentClass isNil ifTrue:[
+                        classes := #()
+                    ] ifFalse:[
+                        classes := Array with:currentClass
+                    ]
+                ] ifFalse:[
+                    (where == #classHierarchy or:[where == #classHierarchyWithPrivateClasses]) ifTrue:[
+                        classes := currentClass withAllSubclasses
+                    ]
+                ]
+            ]
+        ].
+        (where == #classWithPrivateClasses or:[where == #classHierarchyWithPrivateClasses]) ifTrue:[
+            toSearch := IdentitySet withAll:classes.
+            classes := IdentitySet withAll:toSearch.
+
+            [toSearch notEmpty] whileTrue:[
+                cls := toSearch removeFirst.
+                privates := cls privateClasses.
+                privates notNil ifTrue:[
+                    toSearch addAll:cls privateClasses.
+                    classes addAll:cls privateClasses.
+                ]
+            ].
+            classes := classes asOrderedCollection.
+        ].
+
+        classes isEmpty ifTrue:[
+            self warn:'no class(es) given for search'.
+        ] ifFalse:[
+            self withSearchCursorDo:[
+                withCaseIgnore ifTrue:[
+                    SystemBrowser perform:aSelector with:sel with:classes with:caseHolder value
+                ] ifFalse:[
+                    SystemBrowser perform:aSelector with:sel with:classes
+                ]
+            ]
+        ]
+    ]
+
+    "Created: / 18.6.1998 / 16:39:44 / cg"
+    "Modified: / 18.6.1998 / 16:40:30 / cg"
 !
 
 busyLabel:what with:someArgument
@@ -10776,24 +10821,26 @@
         codeView modified ifFalse:[
             oldCodeList := codeView list copy.
             codeView modified ifFalse:[
-                oldCode := oldCodeList asStringWithoutEmphasis.
-                codeView modified ifFalse:[
-                    "/ oldCode := oldCodeList asStringWithoutEmphasis.
-                    cls := actualClass.
-
+                oldCodeList isNil ifFalse:[
+                    oldCode := oldCodeList asStringWithoutEmphasis.
                     codeView modified ifFalse:[
-                        newCode := highlighter formatMethod:oldCode in:cls.
-                        "/ must add this event - and not been interrupted
-                        "/ by any arriving key-event.
+                        "/ oldCode := oldCodeList asStringWithoutEmphasis.
+                        cls := actualClass.
+
                         codeView modified ifFalse:[
-                            newCode := newCode asStringCollection.
+                            newCode := highlighter formatMethod:oldCode in:cls.
+                            "/ must add this event - and not been interrupted
+                            "/ by any arriving key-event.
                             codeView modified ifFalse:[
-                                coloringProcess := nil.
-                                self sensor
-                                    pushUserEvent:#syntaxHighlightedCode: for:self
-                                    withArguments:(Array with:newCode).
+                                newCode := newCode asStringCollection.
+                                codeView modified ifFalse:[
+                                    coloringProcess := nil.
+                                    self sensor
+                                        pushUserEvent:#syntaxHighlightedCode: for:self
+                                        withArguments:(Array with:newCode).
+                                ]
                             ]
-                        ]
+                        ].
                     ].
                 ].
             ].
@@ -10805,7 +10852,7 @@
     codeView modifiedChannel onChangeSend:#codeChanged to:self.
 
     "Created: / 31.3.1998 / 14:25:29 / cg"
-    "Modified: / 18.6.1998 / 09:24:34 / cg"
+    "Modified: / 18.6.1998 / 16:39:14 / cg"
 !
 
 stopSyntaxHighlightProcess
@@ -11725,6 +11772,6 @@
 !BrowserView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.420 1998-06-18 13:11:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.421 1998-06-18 14:54:51 cg Exp $'
 ! !
 BrowserView initialize!
--- a/BrwsrView.st	Thu Jun 18 16:52:55 1998 +0200
+++ b/BrwsrView.st	Thu Jun 18 16:54:51 1998 +0200
@@ -21,7 +21,7 @@
 		lastCategory lastModule lastPackage lastMethodMoveClass
 		namespaceList allNamespaces gotClassList classList selectorList
 		showAllNamespaces classInstVarsInVarList coloringProcess
-		codeModified'
+		codeModified autoSearchIgnoreCase'
 	classVariableNames:'CheckForInstancesWhenRemovingClasses RememberAspect DefaultIcon
 		StopIcon TraceIcon TimeIcon CanvasIcon MenuIcon ImageIcon
 		TabListIcon HierarchicalListIcon TableColumnsIcon HelpIcon
@@ -5739,7 +5739,22 @@
      search for the searchstring in the codeView"
 
     self setSearchPattern:aString.
+    autoSearchIgnoreCase := false.
     autoSearch := aString
+
+    "Modified: / 18.6.1998 / 16:49:50 / cg"
+!
+
+autoSearch:aString ignoreCase:ign
+    "used with class-method list browsing. If true,
+     selecting an entry from the list will automatically
+     search for the searchstring in the codeView"
+
+    self setSearchPattern:aString.
+    autoSearchIgnoreCase := ign.
+    autoSearch := aString
+
+    "Created: / 18.6.1998 / 16:49:59 / cg"
 !
 
 destroy
@@ -8219,12 +8234,13 @@
     "launch an enterBox for string to search for"
 
     self 
-	askForSearchTitle:'string to search for in sources:' 
-	openWith:#browseForString:in:
-	isSelector:true
-	searchArea:#class
-
-    "Modified: 11.11.1996 / 12:44:13 / cg"
+        askForSearchTitle:'string to search for in sources:' 
+        openWith:#browseForString:in:ignoreCase:
+        isSelector:true
+        searchArea:#class
+        withCaseIgnore:true
+
+    "Modified: / 18.6.1998 / 16:42:11 / cg"
 !
 
 methodTrace
@@ -8573,7 +8589,8 @@
         "
         autoSearch notNil ifTrue:[
             codeView 
-                searchFwd:autoSearch 
+                searchFwd:autoSearch
+                ignoreCase:autoSearchIgnoreCase 
                 startingAtLine:1 col:0 
                 ifAbsent:[]
         ].
@@ -8606,7 +8623,7 @@
 
     "Created: / 23.11.1995 / 14:17:44 / cg"
     "Modified: / 17.6.1996 / 16:47:50 / stefan"
-    "Modified: / 12.1.1998 / 19:07:36 / cg"
+    "Modified: / 18.6.1998 / 16:50:37 / cg"
 !
 
 methodTemplate
@@ -9427,94 +9444,112 @@
 !BrowserView methodsFor:'private'!
 
 askAndBrowseMethodCategory:title action:aBlock
-    "convenient method: setup enterBox with initial being current method category"
+    "convenient helper method: setup enterBox with initial being current method category"
 
     |sel box|
 
     box := self 
-		enterBoxTitle:title 
-		okText:'browse'
-		label:'browse category'.
+                enterBoxTitle:title 
+                okText:'browse'
+                label:'browse category'.
 
     sel := codeView selection.
     sel isNil ifTrue:[
-	currentMethodCategory notNil ifTrue:[
-	    sel := currentMethodCategory
-	]
+        currentMethodCategory notNil ifTrue:[
+            sel := currentMethodCategory
+        ]
     ].
     sel notNil ifTrue:[
-	box initialText:(sel asString withoutSpaces)
+        box initialText:(sel asString withoutSpaces)
     ].
     box action:[:aString | self withBusyCursorDo:[aBlock value:aString]].
     box showAtPointer
 
-    "Modified: 18.8.1997 / 15:42:07 / cg"
+    "Modified: / 18.6.1998 / 16:40:46 / cg"
 !
 
 askForMethodCategory
+    "convenient helper method: setup a box asking for a method category"
+
     |someCategories box txt retVal|
 
     someCategories := actualClass categories sort.
     box := self listBoxTitle:'accept in which method category ?' okText:'accept' list:someCategories.
 
     lastMethodCategory isNil ifTrue:[
-	txt := 'new methods'
+        txt := 'new methods'
     ] ifFalse:[
-	txt := lastMethodCategory
+        txt := lastMethodCategory
     ].
     box initialText:txt.
     box action:[:aString | aString notEmpty ifTrue:[retVal := aString] ].
     box showAtPointer.
     ^ retVal
 
-    "Modified: 27.3.1996 / 15:33:46 / cg"
+    "Modified: / 18.6.1998 / 16:41:03 / cg"
 !
 
 askForSearchSelectorTitle:title openWith:aSelector
-    "convenient method: setup enterBox with text from codeView or selected
+    "convenient helper method: setup enterBox with text from codeView or selected
      method for browsing based on a selector. Set action and launch box"
 
     ^ self 
-	askForSearchTitle:title 
-	openWith:aSelector 
-	isSelector:true
-
-    "Modified: 11.11.1996 / 12:43:24 / cg"
+        askForSearchTitle:title 
+        openWith:aSelector 
+        isSelector:true
+
+    "Modified: / 18.6.1998 / 16:40:39 / cg"
 !
 
 askForSearchTitle:title openWith:aSelector isSelector:isSelector
-    "convenient method: setup enterBox with text from codeView or selected
+    "convenient helper method: setup enterBox with text from codeView or selected
      method for browsing based on a selector. Set action and launch box"
 
     ^ self
-	askForSearchTitle:title 
-	openWith:aSelector 
-	isSelector:isSelector 
-	searchArea:#everywhere
-
-    "Modified: 11.11.1996 / 12:42:46 / cg"
+        askForSearchTitle:title 
+        openWith:aSelector 
+        isSelector:isSelector 
+        searchArea:#everywhere
+
+    "Modified: / 18.6.1998 / 16:40:35 / cg"
 !
 
 askForSearchTitle:title openWith:aSelector isSelector:isSelector searchArea:whereDefault
-    "convenient method: setup enterBox with text from codeView or selected
+    "convenient helper method: setup enterBox with text from codeView or selected
      method for browsing based on a selector. Set action and launch box.
      SearchArea may be one of #everywhere, #classCategory, #class, #classWithPrivateClasses,
      #classHierarchy or #classHierarchyWithPrivateClasses"
 
-    |box grp panel selectorHolder where whereChannel 
+    ^ self
+        askForSearchTitle:title 
+        openWith:aSelector 
+        isSelector:isSelector 
+        searchArea:whereDefault 
+        withCaseIgnore:false
+
+    "Modified: / 18.6.1998 / 16:40:26 / cg"
+!
+
+askForSearchTitle:title openWith:aSelector isSelector:isSelector searchArea:whereDefault withCaseIgnore:withCaseIgnore
+    "convenient helper method: setup enterBox with text from codeView or selected
+     method for browsing based on a selector. Set action and launch box.
+     SearchArea may be one of #everywhere, #classCategory, #class, #classWithPrivateClasses,
+     #classHierarchy or #classHierarchyWithPrivateClasses"
+
+    |box grp panel selectorHolder where whereChannel caseHolder
      b sel classes areas toSearch cls privates inputField|
 
     areas := #(everywhere 
-	       classCategory 
-	       class 
-	       classHierarchy 
-	       classWithPrivateClasses 
-	       classHierarchyWithPrivateClasses).
+               classCategory 
+               class 
+               classHierarchy 
+               classWithPrivateClasses 
+               classHierarchyWithPrivateClasses).
 
     isSelector ifTrue:[
-	sel := self selectorToSearchFor.
+        sel := self selectorToSearchFor.
     ] ifFalse:[
-	sel := self stringToSearchFor.
+        sel := self stringToSearchFor.
     ].
     selectorHolder := sel asValue.
 
@@ -9524,88 +9559,94 @@
     inputField := box addInputFieldOn:selectorHolder tabable:true.
     inputField selectAll.
     inputField entryCompletionBlock:[:contents |
-	|s what m|
-
-	s := contents withoutSpaces.
-	box topView withWaitCursorDo:[
-	    what := Smalltalk selectorCompletion:s.
-	    inputField contents:what first.
-	    (what at:2) size ~~ 1 ifTrue:[
-		self beep
-	    ]
-	]
+        |s what m|
+
+        s := contents withoutSpaces.
+        box topView withWaitCursorDo:[
+            what := Smalltalk selectorCompletion:s.
+            inputField contents:what first.
+            (what at:2) size ~~ 1 ifTrue:[
+                self beep
+            ]
+        ]
+    ].
+
+    withCaseIgnore ifTrue:[
+"/        box addVerticalSpace.
+        box addCheckBox:(resources string:'ignore case') on:(caseHolder := false asValue).
+"/        box addVerticalSpace.
     ].
 
     (currentClassCategory notNil or:[currentClass notNil]) ifTrue:[
-	box addHorizontalLine.
-	box addVerticalSpace.
-
-	(box addTextLabel:(resources string:'search in:')) adjust:#left.
-
-	panel := VerticalPanelView "HorizontalPanelView" new.
-	panel horizontalLayout:#fitSpace.
-
-	grp := RadioButtonGroup new.
-	b := CheckBox "RadioButton" label:(resources string:'everywhere').
-	panel add:b. grp add:b.
-	box makeTabable:b.
-
-	currentClassCategory notNil ifTrue:[
-	    b := CheckBox "RadioButton" label:(resources string:'class category').
-	    panel add:b. grp add:b.
-	    box makeTabable:b.
-	].
-
-	currentClass notNil ifTrue:[
-	    b := CheckBox "RadioButton" label:(resources string:'class').
-	    panel add:b.grp add:b.
-	    box makeTabable:b.
-
-	    b := CheckBox "RadioButton" label:(resources string:'class & subclasses').
-	    panel add:b. grp add:b.
-	    box makeTabable:b.
-
-	    currentClass subclasses size == 0 ifTrue:[
-		b disable.
-	    ].
-
-	    b := CheckBox "RadioButton" label:(resources string:'class & private classes').
-	    panel add:b.grp add:b.
-	    box makeTabable:b.
-
-	    currentClass privateClasses size == 0 ifTrue:[
-		b disable
-	    ].
-
-	    b := CheckBox "RadioButton" label:(resources string:'class & subclasses & all private classes').
-	    panel add:b. grp add:b.
-	    box makeTabable:b.
-
-	    currentClass subclasses size == 0 ifTrue:[
-		b disable.
-	    ] ifFalse:[
+        box addHorizontalLine.
+        box addVerticalSpace.
+
+        (box addTextLabel:(resources string:'search in:')) adjust:#left.
+
+        panel := VerticalPanelView "HorizontalPanelView" new.
+        panel horizontalLayout:#fitSpace.
+
+        grp := RadioButtonGroup new.
+        b := CheckBox "RadioButton" label:(resources string:'everywhere').
+        panel add:b. grp add:b.
+        box makeTabable:b.
+
+        currentClassCategory notNil ifTrue:[
+            b := CheckBox "RadioButton" label:(resources string:'class category').
+            panel add:b. grp add:b.
+            box makeTabable:b.
+        ].
+
+        currentClass notNil ifTrue:[
+            b := CheckBox "RadioButton" label:(resources string:'class').
+            panel add:b.grp add:b.
+            box makeTabable:b.
+
+            b := CheckBox "RadioButton" label:(resources string:'class & subclasses').
+            panel add:b. grp add:b.
+            box makeTabable:b.
+
+            currentClass subclasses size == 0 ifTrue:[
+                b disable.
+            ].
+
+            b := CheckBox "RadioButton" label:(resources string:'class & private classes').
+            panel add:b.grp add:b.
+            box makeTabable:b.
+
+            currentClass privateClasses size == 0 ifTrue:[
+                b disable
+            ].
+
+            b := CheckBox "RadioButton" label:(resources string:'class & subclasses & all private classes').
+            panel add:b. grp add:b.
+            box makeTabable:b.
+
+            currentClass subclasses size == 0 ifTrue:[
+                b disable.
+            ] ifFalse:[
 "/ this takes too long ...
 "/                toSearch := IdentitySet new.
 "/                currentClass withAllSubclasses do:[:cls | toSearch add:cls privateClasses].
 "/                toSearch size == 0 ifTrue:[
 "/                    b disable
 "/                ]
-	    ]
-	].
-	whereDefault notNil ifTrue:[
-	    where := areas indexOf:whereDefault.
-	    where == 0 ifTrue:[where := 1].
-	] ifFalse:[
-	    where := 1.
-	].
-	grp value:where.
-	whereChannel := grp.
-	box addComponent:panel indent:0.  "/ panel has its own idea of indenting
-
-	box addVerticalSpace.
-	box addHorizontalLine.
+            ]
+        ].
+        whereDefault notNil ifTrue:[
+            where := areas indexOf:whereDefault.
+            where == 0 ifTrue:[where := 1].
+        ] ifFalse:[
+            where := 1.
+        ].
+        grp value:where.
+        whereChannel := grp.
+        box addComponent:panel indent:0.  "/ panel has its own idea of indenting
+
+        box addVerticalSpace.
+        box addHorizontalLine.
     ] ifFalse:[
-	whereChannel := 1 asValue.
+        whereChannel := 1 asValue.
     ].
 
     box addAbortButton.
@@ -9615,65 +9656,69 @@
     box open.
 
     box accepted ifTrue:[
-	sel := selectorHolder value.
-	where := whereChannel value.
-
-	sel isEmpty ifTrue:[
-	    self warn:'nothing entered for search'.
-	    ^ self.
-	].
-	where isNil ifTrue:[
-	    self warn:'no class(es) for search'.
-	    ^ self.
-	].
-
-	where := areas at:where ifAbsent:#class.
-
-	where == #everywhere ifTrue:[
-	    classes := Smalltalk allClasses.
-	] ifFalse:[
-	    where == #classCategory ifTrue:[
-		classes := Smalltalk allClassesInCategory:currentClassCategory
-	    ] ifFalse:[
-		(where == #class or:[where == #classWithPrivateClasses]) ifTrue:[
-		    currentClass isNil ifTrue:[
-			classes := #()
-		    ] ifFalse:[
-			classes := Array with:currentClass
-		    ]
-		] ifFalse:[
-		    (where == #classHierarchy or:[where == #classHierarchyWithPrivateClasses]) ifTrue:[
-			classes := currentClass withAllSubclasses
-		    ]
-		]
-	    ]
-	].
-	(where == #classWithPrivateClasses or:[where == #classHierarchyWithPrivateClasses]) ifTrue:[
-	    toSearch := IdentitySet withAll:classes.
-	    classes := IdentitySet withAll:toSearch.
-
-	    [toSearch notEmpty] whileTrue:[
-		cls := toSearch removeFirst.
-		privates := cls privateClasses.
-		privates notNil ifTrue:[
-		    toSearch addAll:cls privateClasses.
-		    classes addAll:cls privateClasses.
-		]
-	    ].
-	    classes := classes asOrderedCollection.
-	].
-
-	classes isEmpty ifTrue:[
-	    self warn:'no class(es) given for search'.
-	] ifFalse:[
-	    self withSearchCursorDo:[
-		SystemBrowser perform:aSelector with:sel with:classes
-	    ]
-	]
-    ]
-
-    "Created: 11.11.1996 / 12:42:14 / cg"
-    "Modified: 28.7.1997 / 18:04:04 / cg"
+        sel := selectorHolder value.
+        where := whereChannel value.
+
+        sel isEmpty ifTrue:[
+            self warn:'nothing entered for search'.
+            ^ self.
+        ].
+        where isNil ifTrue:[
+            self warn:'no class(es) for search'.
+            ^ self.
+        ].
+
+        where := areas at:where ifAbsent:#class.
+
+        where == #everywhere ifTrue:[
+            classes := Smalltalk allClasses.
+        ] ifFalse:[
+            where == #classCategory ifTrue:[
+                classes := Smalltalk allClassesInCategory:currentClassCategory
+            ] ifFalse:[
+                (where == #class or:[where == #classWithPrivateClasses]) ifTrue:[
+                    currentClass isNil ifTrue:[
+                        classes := #()
+                    ] ifFalse:[
+                        classes := Array with:currentClass
+                    ]
+                ] ifFalse:[
+                    (where == #classHierarchy or:[where == #classHierarchyWithPrivateClasses]) ifTrue:[
+                        classes := currentClass withAllSubclasses
+                    ]
+                ]
+            ]
+        ].
+        (where == #classWithPrivateClasses or:[where == #classHierarchyWithPrivateClasses]) ifTrue:[
+            toSearch := IdentitySet withAll:classes.
+            classes := IdentitySet withAll:toSearch.
+
+            [toSearch notEmpty] whileTrue:[
+                cls := toSearch removeFirst.
+                privates := cls privateClasses.
+                privates notNil ifTrue:[
+                    toSearch addAll:cls privateClasses.
+                    classes addAll:cls privateClasses.
+                ]
+            ].
+            classes := classes asOrderedCollection.
+        ].
+
+        classes isEmpty ifTrue:[
+            self warn:'no class(es) given for search'.
+        ] ifFalse:[
+            self withSearchCursorDo:[
+                withCaseIgnore ifTrue:[
+                    SystemBrowser perform:aSelector with:sel with:classes with:caseHolder value
+                ] ifFalse:[
+                    SystemBrowser perform:aSelector with:sel with:classes
+                ]
+            ]
+        ]
+    ]
+
+    "Created: / 18.6.1998 / 16:39:44 / cg"
+    "Modified: / 18.6.1998 / 16:40:30 / cg"
 !
 
 busyLabel:what with:someArgument
@@ -10776,24 +10821,26 @@
         codeView modified ifFalse:[
             oldCodeList := codeView list copy.
             codeView modified ifFalse:[
-                oldCode := oldCodeList asStringWithoutEmphasis.
-                codeView modified ifFalse:[
-                    "/ oldCode := oldCodeList asStringWithoutEmphasis.
-                    cls := actualClass.
-
+                oldCodeList isNil ifFalse:[
+                    oldCode := oldCodeList asStringWithoutEmphasis.
                     codeView modified ifFalse:[
-                        newCode := highlighter formatMethod:oldCode in:cls.
-                        "/ must add this event - and not been interrupted
-                        "/ by any arriving key-event.
+                        "/ oldCode := oldCodeList asStringWithoutEmphasis.
+                        cls := actualClass.
+
                         codeView modified ifFalse:[
-                            newCode := newCode asStringCollection.
+                            newCode := highlighter formatMethod:oldCode in:cls.
+                            "/ must add this event - and not been interrupted
+                            "/ by any arriving key-event.
                             codeView modified ifFalse:[
-                                coloringProcess := nil.
-                                self sensor
-                                    pushUserEvent:#syntaxHighlightedCode: for:self
-                                    withArguments:(Array with:newCode).
+                                newCode := newCode asStringCollection.
+                                codeView modified ifFalse:[
+                                    coloringProcess := nil.
+                                    self sensor
+                                        pushUserEvent:#syntaxHighlightedCode: for:self
+                                        withArguments:(Array with:newCode).
+                                ]
                             ]
-                        ]
+                        ].
                     ].
                 ].
             ].
@@ -10805,7 +10852,7 @@
     codeView modifiedChannel onChangeSend:#codeChanged to:self.
 
     "Created: / 31.3.1998 / 14:25:29 / cg"
-    "Modified: / 18.6.1998 / 09:24:34 / cg"
+    "Modified: / 18.6.1998 / 16:39:14 / cg"
 !
 
 stopSyntaxHighlightProcess
@@ -11725,6 +11772,6 @@
 !BrowserView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Attic/BrwsrView.st,v 1.420 1998-06-18 13:11:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Attic/BrwsrView.st,v 1.421 1998-06-18 14:54:51 cg Exp $'
 ! !
 BrowserView initialize!