Tools__SearchDialog.st
branchjv
changeset 12123 4bde08cebd48
child 12125 0c49a3b13e43
equal deleted inserted replaced
11227:3d57003855a7 12123:4bde08cebd48
       
     1 "
       
     2  COPYRIGHT (c) 2000 by eXept Software AG
       
     3 	      All Rights Reserved
       
     4 
       
     5  This software is furnished under a license and may be used
       
     6  only in accordance with the terms of that license and with the
       
     7  inclusion of the above copyright notice.   This software may not
       
     8  be provided or otherwise made available to, or used by, any
       
     9  other person.  No title to or ownership of the software is
       
    10  hereby transferred.
       
    11 "
       
    12 "{ Package: 'stx:libtool' }"
       
    13 
       
    14 "{ NameSpace: Tools }"
       
    15 
       
    16 DialogBox subclass:#SearchDialog
       
    17 	instanceVariableNames:'openHow classes methods selectedClasses selectedCategories
       
    18 		selectedMethods selectedPackages currentClass currentNamespace
       
    19 		currentClassCategory currentPackage browser whereRadioGroup
       
    20 		currentPanel searchAreas caseHolder matchHolder isMethodHolder
       
    21 		codeField selectorHolder defaultOpenHow withTextEntry allowFind
       
    22 		allowBuffer allowBrowser searchWhat searchClassProtocolHolder
       
    23 		searchInstanceProtocolHolder selectorOrCode selectionList
       
    24 		listHolder matchProcess inputField'
       
    25 	classVariableNames:'LastCodeSearched LastCodeSearchWasMethod LastGlobalSearched
       
    26 		LastStringSearched LastSearchWasMatch LastSearchWasCaseSensitive
       
    27 		LastStringSearchArea LastCodeSearchArea AREA_LISTOFMETHODS
       
    28 		LastResourceSearched'
       
    29 	poolDictionaries:''
       
    30 	category:'Interface-Browsers-New'
       
    31 !
       
    32 
       
    33 !SearchDialog class methodsFor:'documentation'!
       
    34 
       
    35 copyright
       
    36 "
       
    37  COPYRIGHT (c) 2000 by eXept Software AG
       
    38 	      All Rights Reserved
       
    39 
       
    40  This software is furnished under a license and may be used
       
    41  only in accordance with the terms of that license and with the
       
    42  inclusion of the above copyright notice.   This software may not
       
    43  be provided or otherwise made available to, or used by, any
       
    44  other person.  No title to or ownership of the software is
       
    45  hereby transferred.
       
    46 "
       
    47 ! !
       
    48 
       
    49 !SearchDialog class methodsFor:'initialization'!
       
    50 
       
    51 initialize
       
    52     AREA_LISTOFMETHODS := #listOfMethods
       
    53 
       
    54     "Created: / 19-11-2010 / 12:00:18 / cg"
       
    55 ! !
       
    56 
       
    57 !SearchDialog class methodsFor:'constants'!
       
    58 
       
    59 constantForListOfMethodsArea
       
    60     ^ AREA_LISTOFMETHODS
       
    61 
       
    62     "Created: / 19-11-2010 / 12:11:50 / cg"
       
    63 ! !
       
    64 
       
    65 !SearchDialog class methodsFor:'queries'!
       
    66 
       
    67 lastCodeSearchArea
       
    68     ^ LastCodeSearchArea
       
    69 !
       
    70 
       
    71 lastStringSearchArea
       
    72     ^ LastStringSearchArea
       
    73 ! !
       
    74 
       
    75 !SearchDialog methodsFor:'accessing-entered values'!
       
    76 
       
    77 classesToSearch
       
    78     ^ classes.
       
    79 !
       
    80 
       
    81 codeToSearch
       
    82     ^ selectorOrCode.
       
    83 !
       
    84 
       
    85 matchMethods
       
    86     ^ isMethodHolder value ? false.
       
    87 !
       
    88 
       
    89 methodsToSearch
       
    90     ^ methods.
       
    91 !
       
    92 
       
    93 openHow
       
    94     ^ openHow.
       
    95 !
       
    96 
       
    97 searchIgnoringCase
       
    98     ^ self searchIsCaseSensitive not
       
    99 !
       
   100 
       
   101 searchIsCaseSensitive
       
   102     ^ (caseHolder value ? false)
       
   103 !
       
   104 
       
   105 searchWithMatch
       
   106     ^ matchHolder value ? false.
       
   107 !
       
   108 
       
   109 selectorToSearch
       
   110     ^ selectorOrCode.
       
   111 ! !
       
   112 
       
   113 !SearchDialog methodsFor:'private'!
       
   114 
       
   115 searchClassProtocolHolder
       
   116     searchClassProtocolHolder isNil ifTrue:[
       
   117         searchClassProtocolHolder := true asValue
       
   118     ].
       
   119     ^ searchClassProtocolHolder
       
   120 !
       
   121 
       
   122 searchInstanceProtocolHolder
       
   123     searchInstanceProtocolHolder isNil ifTrue:[
       
   124         searchInstanceProtocolHolder := true asValue
       
   125     ].
       
   126     ^ searchInstanceProtocolHolder
       
   127 !
       
   128 
       
   129 showHelpOnCodePatterns
       
   130     HTMLDocumentView openFullOnHelpFile:'Browser/RBSearchPatterns.html'
       
   131 !
       
   132 
       
   133 updateListOfMatchingSelectorsFor:s
       
   134     |p|
       
   135 
       
   136     (p := matchProcess) notNil ifTrue:[
       
   137         p terminate.
       
   138     ].
       
   139     listHolder isNil ifTrue:[^ self].
       
   140 
       
   141     matchProcess := 
       
   142         [
       
   143             |what matching|
       
   144 
       
   145             [
       
   146                 searchWhat == #globalName ifFalse:[ 
       
   147                     what := DoWhatIMeanSupport selectorCompletion:s inEnvironment:Smalltalk match:(matchHolder value) ignoreCase:(caseHolder value not)
       
   148                 ] ifTrue:[ 
       
   149                     what := DoWhatIMeanSupport globalNameCompletion:s inEnvironment:Smalltalk match:(matchHolder value).
       
   150                 ].
       
   151                 "/ best := what first.
       
   152                 matching := what second.
       
   153                 self sensor pushAction:[ listHolder contents:matching ].
       
   154             ] ensure:[
       
   155                 matchProcess := nil.
       
   156             ].
       
   157         ] fork.
       
   158 
       
   159     "Modified: / 26-10-2010 / 20:33:05 / cg"
       
   160 ! !
       
   161 
       
   162 !SearchDialog methodsFor:'public'!
       
   163 
       
   164 addTextEntryWithCaseIgnore:withCaseIgnore withMatch:withMatch 
       
   165     matchHolder := caseHolder := nil.
       
   166 
       
   167     searchWhat == #code ifTrue:[
       
   168         self addTextEntryFieldForCode.
       
   169         ^ self.
       
   170     ].
       
   171 
       
   172     self addInputFieldForSelectorOrNameOrString.
       
   173     withCaseIgnore ifTrue:[
       
   174         self 
       
   175             addCheckBox:(resources string:'Case Sensitive')
       
   176             on:(caseHolder := (LastSearchWasCaseSensitive ? false) asValue).
       
   177     ].
       
   178     withMatch ifTrue:[
       
   179         self 
       
   180             addCheckBox:(resources string:'Match')
       
   181             on:(matchHolder := (LastSearchWasMatch ? true) asValue).
       
   182 "/                (isSelector and:[ sel notNil. ]) ifTrue:[ 
       
   183 "/                    sel includesMatchCharacters ifTrue:[ 
       
   184 "/                        matchHolder value:false.
       
   185 "/                    ].
       
   186 "/                ].
       
   187     ]
       
   188 
       
   189     "Modified (format): / 06-07-2011 / 11:56:31 / cg"
       
   190 !
       
   191 
       
   192 askThenDo:aBlock 
       
   193     |where code sel matchHolderValue caseHolderValue|
       
   194 
       
   195     self open.
       
   196     self beScreenDialog.                "raise it above all windows"
       
   197     self accepted ifFalse:[ 
       
   198         ^ self.
       
   199     ].
       
   200 
       
   201     openHow isNil ifTrue:[ 
       
   202         openHow := defaultOpenHow.
       
   203     ].
       
   204     where := whereRadioGroup value.
       
   205     withTextEntry ifTrue:[ 
       
   206         searchWhat == #code ifTrue:[
       
   207             code := codeField contentsAsString.
       
   208             LastCodeSearched := code.
       
   209             LastCodeSearchArea := where.
       
   210         ] ifFalse:[
       
   211             (selectionList notNil and:[selectionList hasSelection]) ifTrue:[
       
   212                 sel := selectionList selectionValue.
       
   213             ] ifFalse:[
       
   214                 sel := selectorHolder value.
       
   215             ].
       
   216             sel isEmptyOrNil ifTrue:[ 
       
   217                 browser warn:((searchWhat == #selector) 
       
   218                             ifTrue:[ 'No selector entered for search'. ]
       
   219                             ifFalse:[ 'Nothing entered for search'. ]).
       
   220                 ^ self.
       
   221             ].
       
   222             sel := sel string.
       
   223 
       
   224             browser rememberSearchPattern:sel.
       
   225             searchWhat == #globalName ifTrue:[ 
       
   226                 LastGlobalSearched := sel.
       
   227             ] ifFalse:[
       
   228                 searchWhat == #string ifTrue:[
       
   229                     LastStringSearched := sel.
       
   230                     LastStringSearchArea := where.
       
   231                 ] ifFalse:[
       
   232                     (sel startsWith:'#''') ifTrue:[
       
   233                         sel := sel copyFrom:3.
       
   234                         (sel endsWith:$') ifTrue:[
       
   235                             sel := sel copyWithoutLast:1.
       
   236                         ].
       
   237                     ].
       
   238                 ]
       
   239             ]
       
   240         ].
       
   241     ].
       
   242     where isNil ifTrue:[ 
       
   243         browser warn:'No class(es) for search'.
       
   244         ^ self.
       
   245     ].
       
   246     self getClassesAndMethodsFor:where.
       
   247 
       
   248     (#(#classesWithPrivateClasses #classHierarchiesWithPrivateClasses #ownersWithPrivateClasses #ownersHierarchiesWithPrivateClasses) 
       
   249         includes:where) 
       
   250             ifTrue:[ 
       
   251                 |toSearch|
       
   252 
       
   253                 toSearch := IdentitySet withAll:classes.
       
   254                 classes := IdentitySet withAll:toSearch.
       
   255                 [ toSearch notEmpty ] whileTrue:[
       
   256                     |cls|
       
   257 
       
   258                     cls := toSearch removeFirst.
       
   259                     classes addAll:cls allPrivateClasses.
       
   260                 ].
       
   261             ].
       
   262 
       
   263     classes size == 0 ifTrue:[
       
   264         classes := nil.
       
   265         methods size == 0 ifTrue:[ 
       
   266             browser warn:'No class(es) given for search.'.
       
   267             ^ self.
       
   268         ].
       
   269     ] ifFalse:[
       
   270         classes := classes asOrderedCollection.
       
   271         methods size ~~ 0 ifTrue:[ 
       
   272             browser warn:'oops'.
       
   273             methods := nil.
       
   274         ].
       
   275     ].
       
   276 
       
   277     matchHolderValue := matchHolder value.
       
   278     matchHolderValue notNil ifTrue:[
       
   279         LastSearchWasMatch := matchHolderValue
       
   280     ].
       
   281     caseHolderValue := caseHolder value.
       
   282     caseHolderValue notNil ifTrue:[
       
   283         LastSearchWasCaseSensitive := caseHolderValue
       
   284     ].
       
   285 
       
   286     selectorOrCode := sel ? code.
       
   287 
       
   288     aBlock numArgs == 7 ifTrue:[
       
   289         "/ old style
       
   290         aBlock
       
   291             value:classes
       
   292             value:(sel ? code)
       
   293             value:(self searchIgnoringCase)
       
   294             value:openHow
       
   295             value:(matchHolderValue ? false)
       
   296             value:methods
       
   297             value:(isMethodHolder value ? false).
       
   298     ] ifFalse:[
       
   299         aBlock value.
       
   300     ]
       
   301 
       
   302     "Modified: / 04-08-2011 / 23:18:42 / cg"
       
   303 !
       
   304 
       
   305 setupToAskForMethodSearchTitle:title forBrowser:brwsrArg searchWhat:searchWhatArg 
       
   306   searchArea:whereDefault withCaseIgnore:withCaseIgnore withMatch:withMatch 
       
   307   withMethodList:withMethodList allowFind:allowFindArg allowBuffer:allowBufferArg 
       
   308   allowBrowser:allowBrowserArg withTextEntry:withTextEntryArg 
       
   309 
       
   310     |where ns methodNameSpaces methodPackages hPanel leftVerticalPanel rightVerticalPanel|
       
   311 
       
   312     allowFind := allowFindArg.
       
   313     allowBuffer := allowBufferArg.
       
   314     allowBrowser := allowBrowserArg.
       
   315     searchWhat := searchWhatArg.
       
   316 
       
   317     withTextEntry := withTextEntryArg.
       
   318     browser := brwsrArg.
       
   319     resources := browser resources.
       
   320 
       
   321     (self addTextLabel:(resources stringWithCRs:title)) adjust:#left.
       
   322 
       
   323     selectedClasses := browser selectedClasses value.
       
   324     selectedCategories := browser selectedCategoriesValue.
       
   325     selectedCategories := selectedCategories reject:[:cat | NavigatorModel isPseudoCategory:cat].
       
   326     selectedMethods := browser selectedMethods value.
       
   327     currentClass := browser theSingleSelectedClass.
       
   328     currentClassCategory := browser theSingleSelectedCategory.
       
   329     currentPackage := browser theSingleSelectedProject.
       
   330     currentClass isNil ifTrue:[
       
   331         browser hasMethodSelected ifTrue:[
       
   332             currentClass := selectedMethods first mclass.
       
   333             "/ selectedClasses := (selectedMethods collect:[:each | each mclass ]) asIdentitySet.
       
   334             "/ selectedClasses := selectedClasses select:[:each | each notNil ].
       
   335         ].
       
   336     ].
       
   337     currentClass notNil ifTrue:[
       
   338         currentClass := currentClass theNonMetaclass.
       
   339     ].
       
   340     withTextEntry ifTrue:[
       
   341         self addTextEntryWithCaseIgnore:withCaseIgnore withMatch:withMatch.
       
   342     ].
       
   343     searchAreas := OrderedCollection new.
       
   344 
       
   345     self addHorizontalLine.
       
   346     self addVerticalSpace.
       
   347 
       
   348     hPanel := HorizontalPanelView "SimpleView" new.
       
   349     hPanel verticalLayout:#top.
       
   350     hPanel horizontalLayout:#left.
       
   351 
       
   352     leftVerticalPanel := currentPanel := VerticalPanelView new.
       
   353     leftVerticalPanel verticalLayout:#topSpace.
       
   354     leftVerticalPanel horizontalLayout:#fitSpace.
       
   355 
       
   356     (self addTextLabel:(resources string:'Search in:')) adjust:#left.
       
   357     whereRadioGroup := RadioButtonGroup new.
       
   358 
       
   359     (selectedCategories size > 0 or:[ selectedClasses size > 0 ]) ifTrue:[
       
   360         self addCheckBoxForEverywhere.
       
   361         "/        classMethodListView notNil ifTrue:[
       
   362         "/            b := CheckBox label:(resources string:'Shown Methods').
       
   363         "/            panel add:b. whereChannel add:b value:#currentMethodList.
       
   364         "/            areas add:#currentMethodList.
       
   365         "/            self makeTabable:b.
       
   366         "/        ].
       
   367         browser isMethodListBrowser ifTrue:[
       
   368             methods := browser selectedMethods value ? #().
       
   369             methodNameSpaces := methods
       
   370                         select:[:eachMethod | eachMethod mclass notNil]
       
   371                         thenCollect:[:eachMethod | eachMethod mclass topNameSpace ].
       
   372             methodPackages := methods 
       
   373                         collect:[:eachMethod | eachMethod package ].
       
   374         ].
       
   375         methodNameSpaces size == 1 ifTrue:[
       
   376             currentNamespace := methodNameSpaces first.
       
   377         ] ifFalse:[
       
   378             currentNamespace := browser currentNamespace.
       
   379             selectedClasses size == 0 ifTrue:[
       
   380                 |classesInAllSelectedCategories nameSpacesOfAllClassesInAllSelectedCategories|
       
   381                 classesInAllSelectedCategories := Smalltalk allClasses select:[:cls | selectedCategories includes:cls category].
       
   382                 nameSpacesOfAllClassesInAllSelectedCategories := classesInAllSelectedCategories collect:[:eachClass | eachClass topNameSpace].
       
   383                 nameSpacesOfAllClassesInAllSelectedCategories size == 1 ifTrue:[
       
   384                     currentNamespace := nameSpacesOfAllClassesInAllSelectedCategories first.
       
   385                 ].
       
   386             ].
       
   387         ].
       
   388 
       
   389         (currentNamespace notNil 
       
   390             and:[ currentNamespace ~= (browser nameListEntryForALL) ]) 
       
   391                 ifTrue:[ self addCheckBoxForCurrentNamespace ]
       
   392                 ifFalse:[
       
   393                     (currentClass notNil 
       
   394                         and:[ (ns := currentClass nameSpace) notNil and:[ ns ~~ Smalltalk ] ]) 
       
   395                             ifTrue:[ self addCheckBoxForClassesNamespace:ns ].
       
   396                 ].
       
   397 
       
   398         methodPackages size == 1 ifTrue:[
       
   399             currentPackage := methodPackages first.
       
   400         ] ifFalse:[
       
   401             currentPackage := browser currentProject.
       
   402 "/            selectedClasses size == 0 ifTrue:[
       
   403 "/                |classesInAllSelectedCategories packagesOfAllClassesInAllSelectedCategories|
       
   404 "/                classesInAllSelectedCategories := Smalltalk allClasses select:[:cls | selectedCategories includes:cls category].
       
   405 "/                packagesOfAllClassesInAllSelectedCategories := classesInAllSelectedCategories collect:[:eachClass | eachClass package].
       
   406 "/                packagesOfAllClassesInAllSelectedCategories size == 1 ifTrue:[
       
   407 "/                    currentPackage := packagesOfAllClassesInAllSelectedCategories first.
       
   408 "/                ].
       
   409 "/            ].
       
   410         ].
       
   411 
       
   412         (currentPackage notNil 
       
   413             and:[ currentPackage ~= (browser nameListEntryForALL) ]) 
       
   414                 ifTrue:[ self addCheckBoxForCurrentPackage ]
       
   415                 ifFalse:[
       
   416                     (currentClass notNil) ifTrue:[ 
       
   417                         self addCheckBoxForClassesPackage:(currentClass package) 
       
   418                     ].
       
   419                 ].
       
   420 
       
   421         selectedCategories size > 0 ifTrue:[
       
   422             self addCheckBoxForSelectedClassCategory.
       
   423         ].
       
   424         (selectedClasses size > 0 or:[ selectedMethods size > 0 ]) ifTrue:[
       
   425             self addCheckBoxForSelectedClass.
       
   426             self addCheckBoxForSelectedClassAndSuperclasses.
       
   427             self addCheckBoxForSelectedClassAndSubclasses.
       
   428             self addCheckBoxForSelectedClassAndPrivateClasses.
       
   429             self addCheckBoxForSelectedClassAndSubclassesAndPrivateClasses.
       
   430             self addCheckBoxForOwnerAndItsPrivateClasses.
       
   431             self addCheckBoxForOwnerAndItsSubclassesAndItsPrivateClasses.
       
   432         ].
       
   433     ] ifFalse:[
       
   434         browser currentNamespace ~~ Smalltalk ifTrue:[
       
   435             self addCheckBoxForEverywhere.
       
   436             currentNamespace := browser currentNamespace.
       
   437             currentNamespace ~= (browser nameListEntryForALL) ifTrue:[
       
   438                 self addCheckBoxForCurrentNamespace.
       
   439             ] ifFalse:[
       
   440                 (currentClass notNil 
       
   441                 and:[ (ns := currentClass nameSpace) notNil 
       
   442                 and:[ ns ~~ Smalltalk ] ]) 
       
   443                 ifTrue:[ 
       
   444                     self addCheckBoxForClassesNamespace:ns 
       
   445                 ].
       
   446             ].
       
   447         ].
       
   448     ].
       
   449     searchAreas size == 0 ifTrue:[
       
   450         self addCheckBoxForEverywhere.
       
   451     ].
       
   452     self addCheckBoxForChangedClassesList.
       
   453 
       
   454     (withMethodList and:[ browser isMethodListBrowser ]) ifTrue:[
       
   455         searchAreas size == 0 ifTrue:[
       
   456             self addCheckBoxForEverywhere.
       
   457         ].
       
   458         self addCheckBoxForMethodList.
       
   459         browser selectedMethods value size > 1 ifTrue:[
       
   460             self addCheckBoxForSelectedMethods.
       
   461         ].
       
   462         self addCheckBoxForSelectedMethodClasses.
       
   463     ] ifFalse:[
       
   464         searchAreas size == 0 ifTrue:[
       
   465             self addCheckBoxForEverywhere.
       
   466         ].
       
   467         self addCheckBoxForChangedMethodList.
       
   468     ].
       
   469 
       
   470     searchAreas size == 0 ifTrue:[
       
   471         whereRadioGroup := #everywhere asValue.
       
   472         self addDummyCheckBoxForEverywhere.
       
   473     ] ifFalse:[
       
   474         whereDefault notNil ifTrue:[
       
   475             (searchAreas includes:whereDefault) ifTrue:[
       
   476                 where := whereDefault asSymbol.
       
   477             ] ifFalse:[
       
   478                 where := searchAreas first.
       
   479             ].
       
   480         ] ifFalse:[
       
   481             where := #everywhere.
       
   482         ].
       
   483         whereRadioGroup value:where.
       
   484     ].
       
   485 
       
   486     hPanel add:leftVerticalPanel.
       
   487 
       
   488     rightVerticalPanel := currentPanel := VerticalPanelView new.
       
   489     rightVerticalPanel verticalLayout:#topSpace.
       
   490     rightVerticalPanel horizontalLayout:#fitSpace.
       
   491 
       
   492 false ifTrue:[
       
   493     self addCheckBoxForClassMethodSearch.
       
   494     self addCheckBoxForInstanceMethodSearch.
       
   495 ].
       
   496 
       
   497 "/    rightVerticalPanel origin:0.75@0.0 corner:1.0@1.0.
       
   498     hPanel 
       
   499         preferredExtent:(leftVerticalPanel preferredHeight + rightVerticalPanel preferredHeight)
       
   500                         @
       
   501                         (leftVerticalPanel preferredHeight max:rightVerticalPanel preferredHeight).
       
   502     hPanel add:rightVerticalPanel.
       
   503     self addComponent:hPanel indent:0.
       
   504 
       
   505     "/ panel has its own idea of indenting
       
   506     self addVerticalSpace.
       
   507     searchWhat == #selector ifTrue:[
       
   508         selectionList := self addFilteredListOfMatchingSelectors.
       
   509         self stickAtBottomWithVariableHeight:selectionList.
       
   510         matchHolder notNil ifTrue:[
       
   511             matchHolder onChangeEvaluate:[ self updateListOfMatchingSelectorsFor:inputField contents ]
       
   512         ].
       
   513         inputField notNil ifTrue:[ self updateListOfMatchingSelectorsFor:inputField contents ].
       
   514     ] ifFalse:[
       
   515         self addHorizontalLine.
       
   516     ].
       
   517     self addButtons.
       
   518 
       
   519     self label:(resources string:'Search').
       
   520 
       
   521     "Modified: / 10-10-2006 / 15:30:52 / cg"
       
   522     "Modified (format): / 06-07-2011 / 11:53:23 / cg"
       
   523 ! !
       
   524 
       
   525 !SearchDialog methodsFor:'setup'!
       
   526 
       
   527 addCheckBox:b forSearchArea:area 
       
   528     currentPanel add:b.
       
   529     whereRadioGroup add:b value:area.
       
   530     searchAreas add:area.
       
   531     self makeTabable:b.
       
   532 !
       
   533 
       
   534 addCheckBoxForChangedClassesList
       
   535     |b|
       
   536 
       
   537     b := CheckBox label:(resources string:'Changed Classes').
       
   538     self addCheckBox:b forSearchArea:#listOfChangedClasses.
       
   539     ChangeSet current changedClasses isEmpty ifTrue:[
       
   540         b disable
       
   541     ].
       
   542     ^ b.
       
   543 !
       
   544 
       
   545 addCheckBoxForChangedMethodList
       
   546     |b|
       
   547 
       
   548     b := CheckBox label:(resources string:'Changed Methods').
       
   549     self addCheckBox:b forSearchArea:#listOfChangedMethods.
       
   550     ChangeSet current changeSelectors isEmpty ifTrue:[
       
   551         b disable
       
   552     ].
       
   553     ^ b.
       
   554 !
       
   555 
       
   556 addCheckBoxForClassMethodSearch
       
   557     |b|
       
   558 
       
   559     b := CheckBox label:(resources string:'Class Protocol').
       
   560     b model:(self searchClassProtocolHolder).
       
   561     currentPanel add:b.
       
   562     ^ b.
       
   563 !
       
   564 
       
   565 addCheckBoxForClassesNamespace:ns 
       
   566     |b|
       
   567 
       
   568     b := CheckBox 
       
   569                 label:(resources string:'Classes'' nameSpace ("%1")' with:ns name).
       
   570     self addCheckBox:b forSearchArea:#currentClassesNameSpace.
       
   571     ^ b.
       
   572 !
       
   573 
       
   574 addCheckBoxForClassesPackage:pkg 
       
   575     |b|
       
   576 
       
   577     b := CheckBox 
       
   578                 label:(resources string:'Classes'' package ("%1")' with:pkg).
       
   579     self addCheckBox:b forSearchArea:#currentClassesPackage.
       
   580     ^ b.
       
   581 
       
   582     "Created: / 21-09-2006 / 17:39:55 / cg"
       
   583 !
       
   584 
       
   585 addCheckBoxForCurrentNamespace
       
   586     |b|
       
   587 
       
   588     b := CheckBox 
       
   589             label:(resources string:'Current nameSpace ("%1")' with:currentNamespace name).
       
   590     self addCheckBox:b forSearchArea:#currentNameSpace.
       
   591     ^ b.
       
   592 
       
   593     "Modified: / 10-10-2006 / 15:28:47 / cg"
       
   594 !
       
   595 
       
   596 addCheckBoxForCurrentPackage
       
   597     |b|
       
   598 
       
   599     b := CheckBox 
       
   600             label:(resources string:'Current package ("%1")' with:currentPackage).
       
   601     self addCheckBox:b forSearchArea:#currentPackage.
       
   602     ^ b.
       
   603 
       
   604     "Modified: / 10-10-2006 / 15:28:51 / cg"
       
   605 !
       
   606 
       
   607 addCheckBoxForCurrentPackage:pkg 
       
   608     |b|
       
   609 
       
   610     b := CheckBox 
       
   611             label:(resources string:'Classes'' package ("%1")' with:pkg).
       
   612     self addCheckBox:b forSearchArea:#currentClassesPackage.
       
   613     ^ b.
       
   614 
       
   615     "Modified: / 10-10-2006 / 15:29:06 / cg"
       
   616 !
       
   617 
       
   618 addCheckBoxForEverywhere
       
   619     |b|
       
   620 
       
   621     b := CheckBox label:(resources string:'Everywhere').
       
   622     self addCheckBox:b forSearchArea:#everywhere.
       
   623     ^ b.
       
   624 !
       
   625 
       
   626 addCheckBoxForInstanceMethodSearch
       
   627     |b|
       
   628 
       
   629     b := CheckBox label:(resources string:'Instance Protocol').
       
   630     b model:(self searchInstanceProtocolHolder).
       
   631     currentPanel add:b.
       
   632     ^ b.
       
   633 !
       
   634 
       
   635 addCheckBoxForMethodList
       
   636     |b|
       
   637 
       
   638     b := CheckBox label:(resources string:'Methodlist').
       
   639     self addCheckBox:b forSearchArea:AREA_LISTOFMETHODS.
       
   640     ^ b.
       
   641 
       
   642     "Modified: / 19-11-2010 / 12:00:52 / cg"
       
   643 !
       
   644 
       
   645 addCheckBoxForOwnerAndItsPrivateClasses
       
   646     |b lbl arg|
       
   647 
       
   648     (currentClass notNil and:[ currentClass isPrivate. ]) ifTrue:[ 
       
   649         lbl := 'Owner (%1) & all its private classes'.
       
   650         arg := currentClass owningClass name.
       
   651     ] ifFalse:[ 
       
   652         lbl := 'Owners & all their private classes'.
       
   653     ].
       
   654     b := CheckBox label:(resources string:lbl with:arg).
       
   655     self addCheckBox:b forSearchArea:#ownersWithPrivateClasses.
       
   656     (selectedClasses contains:[ :cls | cls isPrivate. ]) ifFalse:[ 
       
   657         b disable.
       
   658     ].
       
   659     ^ b.
       
   660 !
       
   661 
       
   662 addCheckBoxForOwnerAndItsSubclassesAndItsPrivateClasses
       
   663     |b lbl arg|
       
   664 
       
   665     (currentClass notNil and:[ currentClass isPrivate. ]) ifTrue:[ 
       
   666         lbl := 'Owner (%1) & its subclasses & all its private classes'.
       
   667         arg := currentClass owningClass name.
       
   668     ] ifFalse:[ 
       
   669         lbl := 'Owners & their subclasses & all their private classes'.
       
   670     ].
       
   671     b := CheckBox label:(resources string:lbl with:arg).
       
   672     self addCheckBox:b forSearchArea:#ownersHierarchiesWithPrivateClasses.
       
   673     (selectedClasses contains:[ :cls | cls isPrivate. ]) ifFalse:[ 
       
   674         b disable.
       
   675     ].
       
   676     ^ b.
       
   677 !
       
   678 
       
   679 addCheckBoxForSelectedClass
       
   680     |b lbl arg|
       
   681 
       
   682     (browser isMethodListBrowser 
       
   683     or:[ currentClass isNil
       
   684     or:[ selectedClasses size > 1] ]) ifTrue:[ 
       
   685         selectedClasses size == 1 ifTrue:[ 
       
   686             lbl := 'Selected class ("%1")'.
       
   687             arg := selectedClasses first theNonMetaclass name.
       
   688         ] ifFalse:[ 
       
   689             lbl := 'Selected classes (%1)'.
       
   690             arg := selectedClasses size.
       
   691         ].
       
   692     ] ifFalse:[ 
       
   693         lbl := 'Class ("%1")'.
       
   694         arg := currentClass name.
       
   695     ].
       
   696     b := CheckBox label:(resources string:lbl with:arg).
       
   697     self addCheckBox:b forSearchArea:#classes.
       
   698     ^ b.
       
   699 !
       
   700 
       
   701 addCheckBoxForSelectedClassAndPrivateClasses
       
   702     |b lbl|
       
   703 
       
   704     (browser isMethodListBrowser 
       
   705     or:[ currentClass isNil 
       
   706     or:[ selectedClasses size > 1] ]) ifTrue:[ 
       
   707         lbl := 'Selected classes & all private classes'.
       
   708     ] ifFalse:[ 
       
   709         lbl := 'Class & private classes'.
       
   710     ].
       
   711     b := CheckBox label:(resources string:lbl).
       
   712     self addCheckBox:b forSearchArea:#classesWithPrivateClasses.
       
   713     (selectedClasses 
       
   714         contains:[ :cls | cls theNonMetaclass privateClasses size > 0. ]) 
       
   715             ifFalse:[ b disable. ].
       
   716     ^ b.
       
   717 !
       
   718 
       
   719 addCheckBoxForSelectedClassAndSubclasses
       
   720     |b lbl|
       
   721 
       
   722     (browser isMethodListBrowser 
       
   723     or:[ currentClass isNil
       
   724     or:[ selectedClasses size > 1] ]) ifTrue:[ 
       
   725         lbl := 'Selected classes & all subclasses'.
       
   726     ] ifFalse:[ 
       
   727         lbl := 'Class & subclasses'.
       
   728     ].
       
   729     b := CheckBox label:(resources string:lbl).
       
   730     self addCheckBox:b forSearchArea:#classHierarchies.
       
   731     (selectedClasses 
       
   732         contains:[ :cls | cls theNonMetaclass subclasses size > 0. ]) 
       
   733             ifFalse:[ b disable. ].
       
   734     ^ b.
       
   735 !
       
   736 
       
   737 addCheckBoxForSelectedClassAndSubclassesAndPrivateClasses
       
   738     |b lbl|
       
   739 
       
   740     (browser isMethodListBrowser 
       
   741     or:[ currentClass isNil
       
   742     or:[ selectedClasses size > 1] ]) ifTrue:[ 
       
   743         lbl := 'Selected classes & all subclasses & all private classes'.
       
   744     ] ifFalse:[ 
       
   745         lbl := 'Class & subclasses & all private classes'.
       
   746     ].
       
   747     b := CheckBox label:(resources string:lbl).
       
   748     self addCheckBox:b forSearchArea:#classHierarchiesWithPrivateClasses.
       
   749     (selectedClasses 
       
   750         contains:[ :cls | cls theNonMetaclass privateClasses size > 0. ]) 
       
   751             ifFalse:[ b disable. ].
       
   752     ^ b.
       
   753 !
       
   754 
       
   755 addCheckBoxForSelectedClassAndSuperclasses
       
   756     |b lbl|
       
   757 
       
   758     (browser isMethodListBrowser 
       
   759     or:[ currentClass isNil
       
   760     or:[ selectedClasses size > 1] ]) ifTrue:[ 
       
   761         lbl := 'Selected classes & all superclasses'.
       
   762     ] ifFalse:[ 
       
   763         lbl := 'Class & superclasses'.
       
   764     ].
       
   765     b := CheckBox label:(resources string:lbl).
       
   766     self addCheckBox:b forSearchArea:#classesAndSuperclasses.
       
   767     (selectedClasses 
       
   768         contains:[ :cls | cls theNonMetaclass superclass notNil. ]) 
       
   769             ifFalse:[ b disable. ].
       
   770     ^ b.
       
   771 !
       
   772 
       
   773 addCheckBoxForSelectedClassCategory
       
   774     |b lbl arg|
       
   775 
       
   776     currentClassCategory notNil ifTrue:[ 
       
   777         lbl := 'Class category ("%1")'.
       
   778         arg := currentClassCategory.
       
   779     ] ifFalse:[ 
       
   780         lbl := 'Selected classes categories (%1)'.
       
   781         arg := selectedCategories size.
       
   782     ].
       
   783     b := CheckBox label:(resources string:lbl with:arg).
       
   784     self addCheckBox:b forSearchArea:#classCategories.
       
   785     ^ b.
       
   786 !
       
   787 
       
   788 addCheckBoxForSelectedMethodClasses
       
   789     |b classes|
       
   790 
       
   791     classes := ((browser selectedMethods value ? #()) 
       
   792                     select:[:m | m mclass notNil]
       
   793                     thenCollect:[:m | m mclass theNonMetaclass]) asSet.
       
   794     classes size == 1 ifTrue:[
       
   795         b := CheckBox label:(resources string:'Selected method''s class (%1)'
       
   796                             with:classes first name).
       
   797     ] ifFalse:[
       
   798         b := CheckBox label:(resources string:'Selected methods'' classes (%1)'
       
   799                             with:classes size).
       
   800     ].
       
   801     self addCheckBox:b forSearchArea:#listOfSelectedMethodClasses.
       
   802     ^ b.
       
   803 
       
   804     "Modified: / 01-11-2010 / 21:35:46 / cg"
       
   805 !
       
   806 
       
   807 addCheckBoxForSelectedMethods
       
   808     |b|
       
   809 
       
   810     b := CheckBox label:(resources string:'Selected methods (%1)'
       
   811 			with:browser selectedMethods value size).
       
   812     self addCheckBox:b forSearchArea:#listOfSelectedMethods.
       
   813     ^ b.
       
   814 !
       
   815 
       
   816 addCheckBoxForSelectedPackage
       
   817     |b lbl arg|
       
   818 
       
   819     currentClassCategory notNil ifTrue:[ 
       
   820         lbl := 'Class category ("%1")'.
       
   821         arg := currentClassCategory.
       
   822     ] ifFalse:[ 
       
   823         lbl := 'Selected classes categories (%1)'.
       
   824         arg := selectedCategories size.
       
   825     ].
       
   826     b := CheckBox label:(resources string:lbl with:arg).
       
   827     self addCheckBox:b forSearchArea:#classCategories.
       
   828     ^ b.
       
   829 !
       
   830 
       
   831 addDummyCheckBoxForEverywhere
       
   832     |b|
       
   833 
       
   834     b := CheckBox label:(resources string:'Everywhere').
       
   835     b turnOn.
       
   836     b disable.
       
   837 
       
   838     currentPanel add:b.
       
   839 !
       
   840 
       
   841 addFilteredListOfMatchingSelectors
       
   842     |l|
       
   843 
       
   844     listHolder := List new.
       
   845 
       
   846     l := HVScrollableView for:SelectionInListView.
       
   847     l listHolder:listHolder.
       
   848     self addComponent:l.
       
   849     l doubleClickAction:[
       
   850             selectorHolder value:(l selectionValue).
       
   851             matchHolder value:false.
       
   852             caseHolder value:false.
       
   853             self doAccept.
       
   854             self okPressed.
       
   855     ].
       
   856     ^ l.
       
   857 !
       
   858 
       
   859 addInputFieldForSelectorOrNameOrString
       
   860     |sel lastSearchPatterns|
       
   861 
       
   862     searchWhat == #selector ifTrue:[ 
       
   863         sel := browser selectorToSearchFor.
       
   864     ] ifFalse:[ 
       
   865         searchWhat == #globalName ifTrue:[ 
       
   866             sel := browser globalNameToSearchFor ? LastGlobalSearched.
       
   867         ] ifFalse:[ 
       
   868             searchWhat == #string ifTrue:[
       
   869                 sel := browser stringToSearchFor ? LastStringSearched.
       
   870             ] ifFalse:[
       
   871                 searchWhat == #resource ifTrue:[
       
   872                     sel := browser stringToSearchFor ? LastResourceSearched.
       
   873                 ] ifFalse:[
       
   874                     sel := browser selectorToSearchFor.
       
   875                 ]
       
   876             ]
       
   877         ].
       
   878     ].
       
   879 
       
   880     lastSearchPatterns := browser lastSearchPatterns.
       
   881     sel isEmptyOrNil ifTrue:[ 
       
   882         "/ use last searchString
       
   883         lastSearchPatterns size > 0 ifTrue:[ 
       
   884             sel := lastSearchPatterns first.
       
   885         ].
       
   886     ].
       
   887     selectorHolder := (sel ? '') withoutSeparators asValue.
       
   888 
       
   889     inputField := self addComboBoxOn:selectorHolder tabable:true.
       
   890     inputField list:lastSearchPatterns.
       
   891     inputField selectAllInitially.
       
   892     inputField immediateAccept:true.
       
   893     inputField takeFocus.
       
   894     inputField 
       
   895         entryCompletionBlock:[ :contents | 
       
   896             |s what|
       
   897 
       
   898             s := contents withoutSpaces.
       
   899             self topView 
       
   900                 withWaitCursorDo:[
       
   901                     |best matching|
       
   902 
       
   903                     searchWhat == #resource ifTrue:[
       
   904                         what := DoWhatIMeanSupport resourceCompletion:s inEnvironment:Smalltalk match:true ignoreCase:false.
       
   905                     ] ifFalse:[
       
   906                         searchWhat == #globalName ifFalse:[ 
       
   907                             what := DoWhatIMeanSupport selectorCompletion:s inEnvironment:Smalltalk.
       
   908                         ] ifTrue:[ 
       
   909                             what := DoWhatIMeanSupport globalNameCompletion:s inEnvironment:Smalltalk match:true.
       
   910                         ].
       
   911                     ].
       
   912                     best := what first.
       
   913                     matching := what second.
       
   914                     inputField contents:best.
       
   915                     "/ listHolder contents:matching.
       
   916                     matching size ~~ 1 ifTrue:[ 
       
   917                         browser window beep.
       
   918                     ].
       
   919                 ].
       
   920         ].
       
   921 
       
   922     selectorHolder onChangeEvaluate:[ self updateListOfMatchingSelectorsFor:inputField contents ].
       
   923 
       
   924     "Modified: / 06-07-2011 / 12:07:12 / cg"
       
   925 !
       
   926 
       
   927 addTextEntryFieldForCode
       
   928     |initial box panel patternInfoBox infoLabel helpButton errMessageField checkCodeAction
       
   929      metaBox b|
       
   930 
       
   931     box := View new.
       
   932     box extent:(600 @ 200).
       
   933 
       
   934     panel := VariableHorizontalPanel in:box.
       
   935     panel origin:0.0@0.0 corner:(1.0@1.0).
       
   936 
       
   937     codeField := CodeView in:panel.        
       
   938     codeField canTab:true.
       
   939 "/    codeField origin:0.0@0.0 corner:(0.75@1.0).
       
   940 
       
   941     patternInfoBox := View in:panel.
       
   942 
       
   943     infoLabel := Label in:patternInfoBox.
       
   944     infoLabel geometryLayout:(LayoutFrame bottomInset:30).
       
   945 
       
   946     infoLabel font:(codeField font asSize:(codeField font size - 2)).
       
   947     infoLabel adjust:#left.
       
   948     infoLabel label:(self helpTextForMetaPatterns).
       
   949 
       
   950     panel relativeCorners:#(0.6 1.0).
       
   951     panel showHandle:true.
       
   952 
       
   953     helpButton := Button label:(resources string:'Pattern Help') in:patternInfoBox.
       
   954     helpButton layout:((AlignmentOrigin fractionalFromPoint:0.5@1.0) 
       
   955                             leftOffset:2
       
   956                             topOffset:helpButton preferredHeight negated;
       
   957                             leftAlignmentFraction:0.5 topAlignmentFraction:0).
       
   958     helpButton topInset:0.75@1.0.
       
   959     helpButton action:[self showHelpOnCodePatterns].
       
   960 
       
   961 
       
   962     self addComponent:box tabable:true.
       
   963 
       
   964     metaBox := HorizontalPanelView new.
       
   965     metaBox horizontalLayout:#leftMax.
       
   966     b := Button label:'+Lit' action:[ codeField pasteOrReplace:'`#n' ] in:metaBox.
       
   967     b helpKey:#matchAnyLiteral.
       
   968     b := Button label:'+Var' action:[ codeField pasteOrReplace:'`v' ] in:metaBox.
       
   969     b helpKey:#matchAnyVariable.
       
   970     b := Button label:'+Expr' action:[ codeField pasteOrReplace:'`@e' ] in:metaBox.
       
   971     b helpKey:#matchAnyExpression.
       
   972     b := Button label:'+Msg' action:[ codeField pasteOrReplace:'`@m:' ] in:metaBox.
       
   973     b helpKey:#matchAnyMessage.
       
   974     b := Button label:'+Node' action:[ codeField pasteOrReplace:'`{:node | node isLiteral and:[node value isSymbol] }' ] in:metaBox.
       
   975     b helpKey:#matchAnyNode.
       
   976     b := Button label:'+Stats' action:[ codeField pasteOrReplace:'`.@stats' ] in:metaBox.
       
   977     b helpKey:#matchAnyStats.                                      
       
   978     self addComponent:metaBox.
       
   979 
       
   980     errMessageField := (self addTextLabel:'') adjust:#left.
       
   981     errMessageField level:-1.    
       
   982     self addCheckBox:(resources string:'Method') on:self isMethodHolder.
       
   983 
       
   984     checkCodeAction := [ self checkCodeIn:codeField notifying:errMessageField. ].
       
   985 
       
   986     codeField modifiedChannel onChangeEvaluate:checkCodeAction.
       
   987     self isMethodHolder onChangeEvaluate:checkCodeAction.
       
   988 
       
   989     initial := browser selectionInCodeView.
       
   990     initial isEmptyOrNil ifTrue:[
       
   991         initial := LastCodeSearched ? ''
       
   992     ].
       
   993     codeField contents:initial.
       
   994     checkCodeAction value.
       
   995 
       
   996     "Modified: / 23-07-2011 / 10:35:14 / cg"
       
   997 !
       
   998 
       
   999 checkCodeIn:codeField notifying:errMessageField
       
  1000     |codeString tree errAction|
       
  1001 
       
  1002     codeString := codeField contents asString string.
       
  1003     errAction := [:str :pos |
       
  1004                     |line col badLine|
       
  1005 
       
  1006                     line := codeField lineOfCharacterPosition:pos.
       
  1007                     col := (codeField colOfCharacterPosition:pos) max:1.
       
  1008 
       
  1009                     badLine := (codeField listAt:line) ? ''.
       
  1010                     col <= badLine size size ifTrue:[
       
  1011                         codeField 
       
  1012                             listAt:line 
       
  1013                             put:(badLine asText 
       
  1014                                     emphasisAt:col 
       
  1015                                     put:(UserPreferences current unknownIdentifierEmphasis)).
       
  1016                         "/ codeField selectFromCharacterPosition:pos to:pos.
       
  1017                     ].
       
  1018                     errMessageField label:('line: ',line printString,' ',str).
       
  1019                     errMessageField backgroundColor:Color red.    
       
  1020                     codeField requestFocus.
       
  1021                     nil.
       
  1022                  ].
       
  1023 
       
  1024     isMethodHolder value ifTrue:[
       
  1025         tree := RBParser parseRewriteMethod:codeString onError: errAction.
       
  1026     ] ifFalse:[
       
  1027         tree := RBParser parseRewriteExpression:codeString onError: errAction.
       
  1028     ].
       
  1029     tree notNil ifTrue:[ 
       
  1030         errMessageField backgroundColor:View defaultViewBackgroundColor.    
       
  1031         errMessageField label:nil 
       
  1032     ].
       
  1033     codeField modifiedChannel setValue:false.
       
  1034 !
       
  1035 
       
  1036 getClassesAndMethodsFor:where 
       
  1037     where == #everywhere ifTrue:[ 
       
  1038         classes := Smalltalk allClasses.
       
  1039         methods := nil.
       
  1040         ^ self.
       
  1041     ].
       
  1042     where == #currentNameSpace ifTrue:[ 
       
  1043         classes := currentNamespace allClassesWithAllPrivateClasses.
       
  1044         methods := nil.
       
  1045         ^ self.
       
  1046     ].
       
  1047     where == #currentClassesNameSpace ifTrue:[ 
       
  1048         currentClass isPrivate ifTrue:[ 
       
  1049             classes := currentClass topOwningClass nameSpace 
       
  1050                         allClassesWithAllPrivateClasses.
       
  1051         ] ifFalse:[ 
       
  1052             classes := currentClass nameSpace allClassesWithAllPrivateClasses.
       
  1053         ].
       
  1054         methods := nil.
       
  1055         ^ self.
       
  1056     ].
       
  1057     where == #currentPackage ifTrue:[ 
       
  1058         classes := Smalltalk allClassesInPackage:currentPackage. 
       
  1059         methods := nil.
       
  1060         ^ self.
       
  1061     ].
       
  1062     where == #currentClassesPackage ifTrue:[ 
       
  1063         classes := Smalltalk allClassesInPackage:currentClass package. 
       
  1064         methods := nil.
       
  1065         ^ self.
       
  1066     ].
       
  1067     where == #classCategories ifTrue:[ 
       
  1068         classes := Smalltalk allClasses 
       
  1069                     select:[ :cls | selectedCategories includes:cls category. ].
       
  1070         classes := classes collect:[ :each | each theNonMetaclass. ].
       
  1071         methods := nil.
       
  1072         ^ self.
       
  1073     ].
       
  1074     (where == #classes or:[ where == #classesWithPrivateClasses. ]) ifTrue:[ 
       
  1075         classes := selectedClasses collect:[ :each | each theNonMetaclass. ].
       
  1076         methods := nil.
       
  1077         ^ self.
       
  1078     ].
       
  1079     (where == #classHierarchies or:[ where == #classHierarchiesWithPrivateClasses. ]) 
       
  1080     ifTrue:[ 
       
  1081         classes := IdentitySet new.
       
  1082         selectedClasses do:[ :cls | 
       
  1083             classes addAll:cls theNonMetaclass withAllSubclasses.
       
  1084         ].
       
  1085         methods := nil.
       
  1086         ^ self.
       
  1087     ].
       
  1088     where == #ownersWithPrivateClasses ifTrue:[ 
       
  1089         classes := IdentitySet new.
       
  1090         selectedClasses do:[ :cls | 
       
  1091             |c|
       
  1092 
       
  1093             c := cls theNonMetaclass.
       
  1094             classes add:(c owningClass ? c).
       
  1095         ].
       
  1096         methods := nil.
       
  1097         ^ self.
       
  1098     ].
       
  1099     where == #ownersHierarchiesWithPrivateClasses ifTrue:[ 
       
  1100         classes := IdentitySet new.
       
  1101         selectedClasses do:[ :cls | 
       
  1102             |c|
       
  1103 
       
  1104             c := cls theNonMetaclass.
       
  1105             classes addAll:(c owningClass ? c) withAllSubclasses.
       
  1106         ].
       
  1107         methods := nil.
       
  1108         ^ self.
       
  1109     ].
       
  1110     (where == #classesAndSuperclasses) ifTrue:[ 
       
  1111         classes := IdentitySet new.
       
  1112         selectedClasses do:[ :cls | 
       
  1113             classes addAll:cls theNonMetaclass withAllSuperclasses.
       
  1114         ].
       
  1115         methods := nil.
       
  1116         ^ self.
       
  1117     ].
       
  1118     (where == AREA_LISTOFMETHODS) ifTrue:[ 
       
  1119         classes := nil.
       
  1120         methods := browser methodListApp methodList value.
       
  1121         ^ self.
       
  1122     ].
       
  1123     (where == #listOfSelectedMethods) ifTrue:[ 
       
  1124         classes := nil.
       
  1125         methods := browser selectedMethods value.
       
  1126         ^ self.
       
  1127     ].
       
  1128     (where == #listOfSelectedMethodClasses) ifTrue:[ 
       
  1129         classes := (browser selectedMethods value collect:[:m | m mclass theNonMetaclass]) asSet asOrderedCollection.
       
  1130         methods := nil.
       
  1131         ^ self.
       
  1132     ].
       
  1133     (where == #listOfChangedClasses) ifTrue:[ 
       
  1134         classes := ChangeSet current changedClasses.
       
  1135         methods := nil.
       
  1136         ^ self.
       
  1137     ].
       
  1138     (where == #listOfChangedMethods) ifTrue:[ 
       
  1139         classes := nil.
       
  1140         methods := Set new.
       
  1141         ChangeSet current do:[:chg |
       
  1142             |mthd|
       
  1143 
       
  1144             chg notNil ifTrue:[
       
  1145                 chg isMethodChange ifTrue:[
       
  1146                     mthd := chg changeMethod.
       
  1147                     mthd notNil ifTrue:[
       
  1148                         methods add:mthd
       
  1149                     ]
       
  1150                 ]
       
  1151             ]
       
  1152         ].
       
  1153         methods := methods asOrderedCollection.
       
  1154         ^ self.
       
  1155     ].
       
  1156 
       
  1157     self halt:'inumplemented search'.
       
  1158 
       
  1159     "Modified: / 19-11-2010 / 12:01:15 / cg"
       
  1160 !
       
  1161 
       
  1162 helpTextForMetaPatterns
       
  1163     ^ 'MetaPatterns:
       
  1164     ' , '`' allBold , ' = meta 
       
  1165     ' , '@' allBold , ' = list/any
       
  1166     ' , '.' allBold , ' = statement
       
  1167     ' , '`' allBold , ' = recurse
       
  1168 
       
  1169     ' , '`#n' allBold , ' any lit
       
  1170     ' , '`v' allBold , '  any var (`V => global)
       
  1171     ' , '`@e' allBold , ' any expr
       
  1172     ' , '`@m:' allBold , ' any message (`m => unary)
       
  1173     ' , '`{:n|...}' allBold , ' node pattern
       
  1174     ' , '`''a.*''' allBold , ' regex on string const
       
  1175 '.
       
  1176 
       
  1177     "Modified: / 08-08-2011 / 20:33:03 / cg"
       
  1178 !
       
  1179 
       
  1180 isMethodHolder
       
  1181     isMethodHolder isNil ifTrue:[isMethodHolder := (LastCodeSearchWasMethod ? false) asValue].
       
  1182     ^ isMethodHolder
       
  1183 ! !
       
  1184 
       
  1185 !SearchDialog methodsFor:'setup-buttons'!
       
  1186 
       
  1187 addBrowseButton
       
  1188     |b|
       
  1189 
       
  1190     b := Button label:(resources string:'Browse').
       
  1191     (DialogBox defaultOKButtonAtLeft) ifTrue:[ 
       
  1192 	self addButton:b before:nil.
       
  1193     ] ifFalse:[ 
       
  1194 	self addButton:b after:nil.
       
  1195     ].
       
  1196     b 
       
  1197 	action:[ 
       
  1198 	    openHow := #newBrowser.
       
  1199 	    self doAccept.
       
  1200 	    self okPressed.
       
  1201 	].
       
  1202     ^ b.
       
  1203 !
       
  1204 
       
  1205 addBufferButton
       
  1206     |b|
       
  1207 
       
  1208     b := Button label:(resources string:'Add Buffer').
       
  1209     (DialogBox defaultOKButtonAtLeft) ifTrue:[ 
       
  1210 	self addButton:b before:nil.
       
  1211     ] ifFalse:[ 
       
  1212 	self addButton:b after:nil.
       
  1213     ].
       
  1214     b 
       
  1215 	action:[ 
       
  1216 	    openHow := #newBuffer.
       
  1217 	    self doAccept.
       
  1218 	    self okPressed.
       
  1219 	].
       
  1220     ^ b.
       
  1221 !
       
  1222 
       
  1223 addButtons
       
  1224     "add find/newBrowser/newBuffer buttons"
       
  1225 
       
  1226     |prevButton|
       
  1227 
       
  1228     allowFind ifTrue:[
       
  1229         defaultOpenHow := #showHere.
       
  1230         prevButton := self addFindButton.
       
  1231     ].
       
  1232     allowBrowser ifTrue:[
       
  1233         defaultOpenHow := #newBrowser.
       
  1234         prevButton := self addBrowseButton.
       
  1235     ].
       
  1236     allowBuffer ifTrue:[
       
  1237         defaultOpenHow := #newBuffer.
       
  1238         prevButton := self addBufferButton.
       
  1239     ].
       
  1240     prevButton notNil ifTrue:[
       
  1241         prevButton isReturnButton:true.
       
  1242     ].
       
  1243     self addAbortButton.
       
  1244 !
       
  1245 
       
  1246 addFindButton
       
  1247     |b|
       
  1248 
       
  1249     b := Button label:(resources string:'Find').
       
  1250     (DialogBox defaultOKButtonAtLeft) ifTrue:[ 
       
  1251 	self addButton:b before:nil.
       
  1252     ] ifFalse:[ 
       
  1253 	self addButton:b after:nil.
       
  1254     ].
       
  1255     b 
       
  1256 	action:[ 
       
  1257 	    openHow := #showHere.
       
  1258 	    self doAccept.
       
  1259 	    self okPressed.
       
  1260 	].
       
  1261     ^ b.
       
  1262 ! !
       
  1263 
       
  1264 !SearchDialog class methodsFor:'documentation'!
       
  1265 
       
  1266 version_CVS
       
  1267     ^ '§Header: /cvs/stx/stx/libtool/Tools_SearchDialog.st,v 1.65 2011/08/08 18:47:27 cg Exp §'
       
  1268 ! !
       
  1269 
       
  1270 SearchDialog initialize!