Tools__NewSystemBrowser.st
branchjv
changeset 16570 dc5e958a20dc
parent 16459 85d703589d34
parent 16484 7724f132ff07
child 16571 cf319f2e56d0
--- a/Tools__NewSystemBrowser.st	Fri May 06 06:55:08 2016 +0200
+++ b/Tools__NewSystemBrowser.st	Mon May 09 21:47:57 2016 +0200
@@ -49,7 +49,7 @@
 		LastClassSearchBoxShowedFullName CachedTagToRevisionMapping
 		CachedMethodsImplemented LastCypressDirectory
 		LastClassSearchBoxShowedJavaOnly LastRemoteRepository
-		LastClassDocDirectory DefaultShowCoverage'
+		LastClassDocDirectory DefaultShowCoverage LastLintedPackage'
 	poolDictionaries:''
 	category:'Interface-Browsers-New'
 !
@@ -7314,6 +7314,12 @@
             itemValue: debugMenuOpenCallGraphForClasses
             showBusyCursorWhilePerforming: true
           )
+         (MenuItem
+            enabled: hasRBLintRuleClassSelected
+            label: 'Run this Rule On...'
+            itemValue: debugMenuRunLintRuleOn
+            showBusyCursorWhilePerforming: true
+          )
          )
         nil
         nil
@@ -23930,7 +23936,7 @@
         or:[navigationState isMethodBrowser]]) ifFalse:[
             filteredVariables := self variableFilter value.
             filteredVariables size > 0 ifTrue:[
-                self searchVariables:filteredVariables readers:true writers:true asAutoSearch:false.
+                self setupToSearchVariables:filteredVariables readers:true writers:true asAutoSearch:false.
                 "/ codeView notNil ifTrue:[codeView searchFwd]
             ] ifFalse:[
                 self autoSearchPattern:nil
@@ -24012,12 +24018,14 @@
                 ] ifFalse:[
                     searchPattern := navigationState autoSearchPattern.
                     searchPattern notNil ifTrue:[
+                        "/ check if user did some other search in the meantime
                         searchPattern = codeView searchPattern ifTrue:[
                             codeView
                                 cursorHome;
                                 cursorRight; "/ to avoid finding the selector
                                 searchFwd:searchPattern
                                     ignoreCase:(navigationState autoSearchIgnoreCase)
+                                    match:(navigationState autoSearchIsMatch)
                                     ifAbsent:[codeView cursorHome].
                         ].
                     ].
@@ -26324,7 +26332,7 @@
         withTextEntry:true
         withMethodList:true
         setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+                            brwsr autoSearchPattern:string ignoreCase:ignoreCase match:doMatch.
                          ]
 
     "Modified: / 28-02-2012 / 16:40:11 / cg"
@@ -26349,7 +26357,7 @@
         searchArea:whereDefault
         withCaseIgnore:true
         setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+                            brwsr autoSearchPattern:string ignoreCase:ignoreCase match:doMatch.
                          ]
 
     "Modified: / 28-02-2012 / 16:40:37 / cg"
@@ -26374,7 +26382,7 @@
         searchArea:whereDefault
         withCaseIgnore:true
         setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+                            brwsr autoSearchPattern:string ignoreCase:ignoreCase match:doMatch.
                          ]
 
     "Modified: / 28-02-2012 / 16:40:54 / cg"
@@ -26404,7 +26412,7 @@
         withTextEntry:true
         withMethodList:true
         setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+                            brwsr autoSearchPattern:string ignoreCase:ignoreCase match:doMatch.
                          ]
 !
 
@@ -26828,7 +26836,7 @@
         searchArea:(self defaultSearchArea)
         withCaseIgnore:false
         setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+                            brwsr autoSearchPattern:string ignoreCase:ignoreCase match:doMatch.
                          ]
 
     "Modified: / 25-11-2010 / 11:41:10 / cg"
@@ -27122,7 +27130,7 @@
         withTextEntry:true
         withMethodList:true
         setSearchPattern:[:brwsr :selector :ignoreCase :doMatch|
-                            brwsr autoSearchSelector:selector ignoreCase:ignoreCase doMatch:doMatch.
+                            brwsr setSearchSelector:selector ignoreCase:ignoreCase doMatch:doMatch.
                          ]
 
     "Modified: / 20-08-2012 / 14:28:30 / cg"
@@ -27134,7 +27142,7 @@
     selectors := self selectedMethodsValue collect:[:each | each selector].
 
 false ifTrue:[
-self autoSearchSelector:selectors ignoreCase:false doMatch:true.
+self setSearchSelector:selectors ignoreCase:false doMatch:true.
 ].
     ^ self
         askForMethodAndSpawnSearchTitle:'Browse Senders of (any in selected):'
@@ -27151,7 +27159,7 @@
         withTextEntry:false
         withMethodList:false
         setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchSelector:selectors ignoreCase:ignoreCase doMatch:doMatch.
+                            brwsr setSearchSelector:selectors ignoreCase:ignoreCase doMatch:doMatch.
                          ]
 
     "Modified: / 28-02-2012 / 16:15:36 / cg"
@@ -28682,7 +28690,7 @@
      THis is called from a background worker - see smallLintRun:onEnvironment:
     "
 
-    | rules checker numOverAll count|
+    | rules checker numOverAll count lastPercentage|
 
     "/ avoid this reference (for project-dependencies). Should this method be an extension, maybe
     "/ checker := SmalllintChecker.
@@ -28692,7 +28700,8 @@
     aBrowserEnvironment cacheClasses.
     numOverAll := aBrowserEnvironment numberClasses * 2 "tests class AND metaclass" * rules size.
     count := 0.
-
+    lastPercentage := nil.
+    
     rules withIndexDo:[:rule :index|
         |t ruleName ruleClassName|
 
@@ -28709,14 +28718,24 @@
                 runRule: rule 
                 onEnvironment: aBrowserEnvironment 
                 progressFeedBackInto:[:classBeingChecked |
+                    |msg percentage|
+                    
                     count := count + 1.
-                    ProgressNotification new
-                        messageText: (('Checking: ' withColor:Color grey)
-                                      , ruleName 
-                                      , ((' (',ruleClassName,')')withColor:Color grey)
-                                      , ' in ',classBeingChecked name);
-                        parameter: ((count-1) / numOverAll * 100);
-                        raiseRequest.
+                    percentage := ((count-1) / numOverAll * 100).
+                    lastPercentage ~= percentage ifTrue:[
+                        msg := ('Checking: ' withColor:Color grey)
+                               , ruleName 
+                               , ((' (',ruleClassName,')')withColor:Color grey).
+                               
+                        rules size < 50 ifTrue:[
+                            msg := msg , ' in ',classBeingChecked name.
+                        ].    
+                        ProgressNotification new
+                            messageText: msg;
+                            parameter: percentage;
+                            raiseRequest.
+                        lastPercentage := percentage.    
+                    ].
                 ].
         ] value. "/ benchmark: rule name, ': '.
     ].
@@ -38769,7 +38788,7 @@
                 values:#(nil #browse #rewrite)
                 default:3.
 
-    answer == nil ifTrue:[
+    answer isNil ifTrue:[
         "/ cancel
         ^ false
     ].
@@ -38780,7 +38799,10 @@
                     label:'Senders of ' , selector
                     perMethodInfo:nil
                     sortBy:#class.
-        brwsr autoSearchPattern:selector.
+        "/ WRONG: must do a more intelligent autosearch here.
+        "/ brwsr autoSearchPattern:selector.
+        brwsr setSearchSelector:selector ignoreCase:false doMatch:false.
+
         ^ false
     ].
     ^ true
@@ -39521,6 +39543,50 @@
     self commonTraceHelperWith:#clearBreakPoint with:nil clear:false.
 !
 
+debugMenuRunLintRuleOn
+    "apply the selected rule(s) on a chosen set of classes"
+
+    |package packagesInChangeSet ruleset env packages|
+
+    packagesInChangeSet := 
+        (ChangeSet current 
+            collect:[:chg | |cls| (cls := chg changeClass) notNil ifTrue:[cls package] ]
+            thenSelect:[:pkg | pkg notNil]) 
+                asSet asOrderedCollection sort.
+            
+    package := Dialog 
+                requestProject:'Run rule on package:'
+                initialAnswer: (LastLintedPackage ? 'stx:libbasic')
+                suggestions: #( '* all *' ) , packagesInChangeSet.
+
+    package isNil ifTrue:[^ self].
+    
+    ruleset := RBLintRuleSet new.
+    self selectedClasses value do:[:each |
+        |cls|
+        
+        cls := each theNonMetaclass.
+        (cls isSubclassOf:RBLintRule) ifTrue:[
+            (cls isBroken
+            or:[ cls isVisible not ]) ifFalse:[
+                ruleset addRule:(cls new).
+            ].    
+        ].
+    ].
+    package = '* all *' ifTrue:[
+        packages := Smalltalk allPackageIDs
+    ] ifFalse:[    
+        packages := { package }
+    ].
+    
+    env := PackageEnvironment new
+                packageNames:packages;
+                label:('package ' , package);
+                yourself.
+                                                           
+    self smalllintRun:ruleset onEnvironment:env.
+!
+
 debugMenuStartCounting
     "set a countpoint on the current method"
 
@@ -49317,7 +49383,7 @@
                         label:label.
 
         theSingleSelector notNil ifTrue:[
-            newBrowser autoSearchSelector:theSingleSelector ignoreCase:false doMatch:false.
+            newBrowser setSearchSelector:theSingleSelector ignoreCase:false doMatch:false.
         ].
     ]
 
@@ -49385,7 +49451,7 @@
                         in:openHow
                         label:label.
         
-        newBrowser autoSearchPattern:(aStringCollection asStringWith:'|') ignoreCase:false.
+        newBrowser autoSearchPattern:(aStringCollection asStringWith:'|') ignoreCase:false match:doMatch.
         newBrowser sortBy value:#classes.
         newBrowser
     ]
@@ -49736,7 +49802,7 @@
 
     brwsr variableFilter value:varNameList.
 
-    self autoSearchVariables:varNameList readers:(accessType ~~ #write) writers:(accessType ~~ #read).
+    brwsr autoSearchVariables:varNameList readers:(accessType ~~ #write) writers:(accessType ~~ #read).
 !
 
 findClassesOfVariable:aVariableName accessWith:aSelector in:collectionOfClasses
@@ -51336,7 +51402,7 @@
             label:[:chg | 
                 |lbl|
                 "/ lbl := chg printString
-                lbl := (chg className ? '???') , ' » ' , (chg selector  ? '???') allBold.
+                lbl := (chg className ? '???') , '  ' , (chg selector  ? '???') allBold.
                 (chg isMethodChange and:[chg changeMethod isNil]) ifTrue:[
                     lbl := lbl asText allStrikedOut,' ','(removed)' allItalic.
                 ].    
@@ -54344,34 +54410,18 @@
     ]
 !
 
+autoSearchPattern:aString ignoreCase:doIgnoreCaseBoolean match:doMatchBoolean
+    aString notNil ifTrue:[
+        self navigationState 
+            autoSearchPattern:aString ignoreCase:doIgnoreCaseBoolean match:doMatchBoolean. 
+        self codeView 
+            setSearchPattern:aString ignoreCase:doIgnoreCaseBoolean match:doMatchBoolean.
+    ]
+!
+
 autoSearchSelector:aSelectorOrCollectionOfSelectors ignoreCase:doIgnoreCase doMatch:doMatch
-    |searchAction|
-
-    aSelectorOrCollectionOfSelectors notNil ifTrue:[
-
-        searchAction :=
-            [:direction :startLine :startCol :foundBlock :notFoundBlock|
-                |codeView|
-
-                codeView := self codeView.
-                self
-                    searchForSelector:aSelectorOrCollectionOfSelectors direction:direction
-                    startLine:(startLine ? codeView cursorLine) startCol:(startCol ? codeView cursorCol)
-                    ignoreCase:doIgnoreCase doMatch:doMatch
-                    ifFound:
-                        [:charPos1 :charPos2 |
-                            codeView
-                                cursorToCharacterPosition:charPos1;
-                                selectFromCharacterPosition:charPos1 to:charPos2
-                        ]
-                    ifNotFound:notFoundBlock
-            ].
-
-        self navigationState autoSearchAction:searchAction.
-        self codeView
-            clearSearchAction; "/ searchAction
-            setSearchPattern:nil.
-    ]
+    <resource: #obsolete>
+    self setSearchSelector:aSelectorOrCollectionOfSelectors ignoreCase:doIgnoreCase doMatch:doMatch
 !
 
 autoSearchVariable:aVariable
@@ -54383,7 +54433,7 @@
 !
 
 autoSearchVariables:aCollectionOfVariables readers:doReaders writers:doWriters
-    self searchVariables:aCollectionOfVariables readers:doReaders writers:doWriters asAutoSearch:true.
+    self setupToSearchVariables:aCollectionOfVariables readers:doReaders writers:doWriters asAutoSearch:true.
 !
 
 classDefinitionStringFor:aClass
@@ -54477,6 +54527,9 @@
 
 searchForCodePattern:codePattern direction:direction startLine:startLine startCol:startCol
                             ifFound:foundBlock ifNotFound:notFoundBlock
+    "used as autosearchAction, if showing the result of a code-pattern search.
+     Does a language-aware search."
+
     ^ self
         searchForCodePatterns:(Array with:codePattern)
         direction:direction startLine:startLine startCol:startCol
@@ -54486,6 +54539,9 @@
 searchForCodePatterns:codePatterns direction:direction
                 startLine:startLine startCol:startCol
                 ifFound:foundBlock ifNotFound:notFoundBlock
+    "used as autosearchAction, if showing the result of a code-pattern search.
+     Does a language-aware search."
+
     |searcher|
 
     self parseTreeSearcherAvailable ifFalse:[ ^ self ].
@@ -54506,6 +54562,9 @@
                             startLine:startLine startCol:startCol
                             ignoreCase:ignoreCase doMatch:doMatch
                             ifFound:foundBlock ifNotFound:notFoundBlock
+    "used as autosearchAction, if showing the result of a senders-search.
+     Does a language-aware search."
+
     |searcher|
 
     self parseTreeSearcherAvailable ifFalse:[ ^ self ].
@@ -54534,6 +54593,9 @@
                             startLine:startLine startCol:startCol
                             readers:searchReaders writers:searchWriters
                             ifFound:foundBlock ifNotFound:notFoundBlock
+    "used as autosearchAction, if showing the result of a variable-search.
+     Does a language-aware search."
+    
     |searcher namesWithAndWithoutNameSpace|
 
     self parseTreeSearcherAvailable ifFalse:[ ^ self ].
@@ -54558,14 +54620,18 @@
             self error:'missing search criteria'
         ].
     ].
-    ^ self searchUsingSearcher:searcher direction:direction
-                    startLine:startLine startCol:startCol
-                    ifFound:foundBlock ifNotFound:notFoundBlock.
+    ^ self 
+        searchUsingSearcher:searcher direction:direction
+        startLine:startLine startCol:startCol
+        ifFound:foundBlock ifNotFound:notFoundBlock.
 !
 
 searchUsingSearcher:searcher direction:direction
                             startLine:startLine startCol:startCol
                             ifFound:foundBlock ifNotFound:notFoundBlock
+    "common helper, used by autosearchAction.
+     Does a language-aware search."
+     
     |codeTree nodes searchStartPos prevNode|
 
     RBParser isNil ifTrue:[^ self].
@@ -54608,10 +54674,44 @@
     notFoundBlock value
 !
 
-searchVariables:aCollectionOfVariables readers:doReaders writers:doWriters asAutoSearch:asAutoSearch
+setSearchSelector:aSelectorOrCollectionOfSelectors ignoreCase:doIgnoreCase doMatch:doMatch
+    "setup the codeView so it auto-searches for a message send"
+    
     |searchAction|
 
-    aCollectionOfVariables size > 0 ifTrue:[
+    aSelectorOrCollectionOfSelectors notNil ifTrue:[
+
+        searchAction :=
+            [:direction :startLine :startCol :foundBlock :notFoundBlock|
+                |codeView|
+
+                codeView := self codeView.
+                self
+                    searchForSelector:aSelectorOrCollectionOfSelectors direction:direction
+                    startLine:(startLine ? codeView cursorLine) startCol:(startCol ? codeView cursorCol)
+                    ignoreCase:doIgnoreCase doMatch:doMatch
+                    ifFound:
+                        [:charPos1 :charPos2 |
+                            codeView
+                                cursorToCharacterPosition:charPos1;
+                                selectFromCharacterPosition:charPos1 to:charPos2
+                        ]
+                    ifNotFound:notFoundBlock
+            ].
+
+        self navigationState autoSearchAction:searchAction.
+        self codeView
+            clearSearchAction; "/ searchAction
+            setSearchPattern:nil.
+    ]
+!
+
+setupToSearchVariables:aCollectionOfVariables readers:doReaders writers:doWriters asAutoSearch:asAutoSearch
+    "setup the search action to search for a variable or setof variables"
+    
+    |searchAction|
+
+    aCollectionOfVariables notEmptyOrNil ifTrue:[
         searchAction :=
             [:direction :startLine :startCol :foundBlock :notFoundBlock|
                 |codeView|