comment/format in:11 methods
authorClaus Gittinger <cg@exept.de>
Thu, 01 Mar 2012 16:46:35 +0100
changeset 11307 f5a4988c23ec
parent 11306 64efae786a2c
child 11308 f028f0cc8667
comment/format in:11 methods changed: #smallLintByRuleResultBrowserSpec #smalllintCheck:against: #smalllintRunRule:onEnvironment: category of:18 methods always show the rationale.
Tools__NewSystemBrowser.st
--- a/Tools__NewSystemBrowser.st	Thu Mar 01 16:44:18 2012 +0100
+++ b/Tools__NewSystemBrowser.st	Thu Mar 01 16:46:35 2012 +0100
@@ -5137,29 +5137,27 @@
                           )
                           handles: (Any 0.33 0.67 1.0)
                         )
-                       (SubCanvasSpec
-                          name: 'RuleDetails'
-                          layout: (LayoutFrame 0 0 -30 1 0 1 0 1)
-                          initiallyInvisible: true
-                          hasHorizontalScrollBar: false
-                          hasVerticalScrollBar: false
-                          majorKey: #'Tools::LintRuleDetail'
-                          subAspectHolders: 
-                         (Array
-                            
-                           (SubChannelInfoSpec
-                              subAspect: ruleHolder
-                              aspect: theSingleSelectedLintRuleHolder
-                            )
-                          )
-                          createNewApplication: true
-                          createNewBuilder: true
-                        )
                        )
                      
                     )
                   )
                  (SubCanvasSpec
+                    name: 'RuleDesc'
+                    hasHorizontalScrollBar: false
+                    hasVerticalScrollBar: false
+                    majorKey: #'Tools::LintRuleDetail'
+                    subAspectHolders: 
+                   (Array
+                      
+                     (SubChannelInfoSpec
+                        subAspect: ruleHolder
+                        aspect: theSingleSelectedLintRuleHolder
+                      )
+                    )
+                    createNewApplication: true
+                    createNewBuilder: true
+                  )
+                 (SubCanvasSpec
                     name: 'CodePane'
                     autoHideScrollBars: false
                     majorKey: NewSystemBrowser
@@ -5169,15 +5167,13 @@
                  )
                
               )
-              handles: (Any 0.5 1.0)
+              handles: (Any 0.333333333333333 0.455958549222798 1.0)
               postBuildCallback: postBuildTabContentView:
             )
            )
          
         )
       )
-
-    "Modified: / 31-12-2011 / 13:12:37 / cg"
 !
 
 visualProfilerSpec
@@ -25287,30 +25283,362 @@
     self spawnCategoryBrowserFor:(self selectedCategoriesValue) in:where
 ! !
 
-!NewSystemBrowser methodsFor:'menu actions-checks'!
+!NewSystemBrowser methodsFor:'menu actions-checks-lint'!
+
+loadSmalllint
+    |pkg dlg|
+
+    pkg := Smalltalk at:#'stx_goodies_refactoryBrowser_lint'.
+    (pkg isNil or:[ pkg isFullyLoaded not ]) ifTrue:[
+        Smalltalk loadPackage:#'stx:goodies/refactoryBrowser/lint'
+            asAutoloaded:false
+    ].
+
+    "
+        Tools::NewSystemBrowser basicNew loadSmallLint"
+    "Created: / 17-04-2010 / 09:40:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+runLint
+    "run the new smallLint checker tool"
+
+    self 
+        smalllintCheck: self selectedCodeComponentsAsEnvironment 
+        against: #smalllintRules
+
+    "Modified: / 17-04-2010 / 10:44:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 01-03-2012 / 14:10:47 / cg"
+!
+
+smalllintCheck:anEnvironment against:ruleSetSymbol
+    "this is exected by an async task!!"
+
+    |rule|
+
+    self 
+        assert:(#( #smalllintRulesAll #smalllintRulesFromUser #smalllintRules ) includes:ruleSetSymbol).
+
+    rule := self perform:ruleSetSymbol asSymbol.
+    rule isNil ifTrue:[ ^ self ].
+"/ cg: that is wrong implemented in RBxxxRule: isEmpty has two meanings:
+"/     for composite: has sub-rules
+"/     for non-composite: has a result
+"/ therefore, isEmpty returns true here, so we will be always asked twice!!
+
+    rule isEmpty ifTrue:[
+        ruleSetSymbol ~~ #smalllintRulesFromUser ifTrue:[
+            rule := self smalllintRulesFromUser.
+            rule isNil ifTrue:[ ^ self ].
+        ]
+    ].
+
+    self showMessage:'Checking code...'
+        while:[
+            self smalllintRunRule:rule onEnvironment:anEnvironment.
+            (rule isEmpty not or:[ (Dialog confirm:'Nothing found.\\Press OK to add result viewer anyway.' withCRs) ]) 
+            ifTrue:[
+                self 
+                    spawnSmalllintBrowserByRuleFor:rule
+                    in:#newBuffer
+                    label:'SmallLint results for ' , anEnvironment label
+            ]
+        ].
+
+    "Modified: / 15-12-2008 / 18:51:43 / Josef Grega <gregaj1@fel.cvut.cz>"
+    "Modified: / 28-12-2008 / 14:40:01 / bazantj <enter your email here>"
+    "Created: / 24-02-2009 / 11:02:57 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 22-07-2009 / 14:38:30 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 28-08-2010 / 20:45:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-03-2012 / 15:20:11 / cg"
+!
+
+smalllintRules
+
+   ^LastLintRules 
+        ifNil:[self smalllintRulesFromUser]
+        ifNotNil:[LastLintRules]
+
+
+    "
+        Tools::NewSystemBrowser basicNew smalllintRules
+    "
+
+    "Modified: / 17-04-2010 / 09:42:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+smalllintRulesAll
+
+    | all checks |
+    all := RBCompositeLintRule allRules.
+    checks := all rules detect:[ :each | each name = 'Lint checks' ].
+    checks rules: (checks rules reject: [ :each | each name = 'Squeak bugs' ]).
+    ^all
+
+    "Created: / 17-04-2010 / 10:07:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 25-08-2010 / 14:38:21 / Jan Vrany <enter your email here>"
+!
+
+smalllintRulesFromUser
+    |dlg|
+
+    self loadSmalllint.
+    dlg := Tools::LintRuleSelectionDialog new.
+    dlg selection: (LastLintRules ifNil:[nil"self smalllintRulesAll flattened"] ifNotNil:[LastLintRules flattened]).
+    ^(dlg open; accepted) 
+            ifTrue:[ LastLintRules := dlg selectionAsRule ] 
+            ifFalse:[ nil ].
+
+    "
+        LastLintRules := nil.
+        Tools::NewSystemBrowser basicNew smalllintRulesFromUser
+    "
+
+    "Created: / 17-04-2010 / 09:41:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 25-08-2010 / 15:35:16 / Jan Vrany <enter your email here>"
+!
+
+smalllintRulesOrAll
+
+    "Returns a set of user-selected SmallLint rules or all rules,
+     if no user selection is done"    
+
+   ^LastLintRules notNil ifTrue:[
+        LastLintRules
+    ] ifFalse:[
+        self smalllintRulesAll
+    ]
+
+    "Created: / 23-01-2012 / 10:59:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+smalllintRulesOrAllHolder
+    "Returns a holder on user-selected SmallLint rules
+     (or all rules if user made no selection"
+
+    ^[ self smalllintRulesOrAll ]
+
+    "Modified: / 17-04-2010 / 09:42:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 23-01-2012 / 11:05:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+smalllintRunRule: aLintRule onEnvironment: anEnvironment
+    "run a checker in the background"
+
+    | rules |
+
+    rules := aLintRule flattened.
+    rules withIndexDo:[:rule :index|
+        ProgressNotification new
+            messageText: ('Checking: ', rule name);
+            parameter: (rules size / 100) * index;
+            raiseRequest.
+       (SmalllintChecker runRule: rule onEnvironment: anEnvironment)
+    ].
+    ProgressNotification new
+        messageText: ('Done');
+        parameter: 100;
+        raiseRequest.
+
+    "Modified: / 15-12-2008 / 18:51:43 / Josef Grega <gregaj1@fel.cvut.cz>"
+    "Modified: / 28-12-2008 / 14:40:01 / bazantj <enter your email here>"
+    "Modified: / 22-07-2009 / 14:38:30 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Created: / 28-08-2010 / 12:12:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-03-2012 / 15:22:20 / cg"
+!
+
+spawnSmalllintBrowserByRuleFor: result in:where label:labelOrNil
+    ^ self
+        newBrowserOrBufferDependingOn:where
+        label:labelOrNil
+        forSpec: #smallLintByRuleResultBrowserSpec
+        setupWith:[:browser | 
+            |methodGenerator classGenerator ruleGenerator ruleHolder|
+
+"/            ruleHolder := BlockValue
+"/                            with:[:listEntries | listEntries size ~~ 1 ifTrue:[nil] ifFalse:[ listEntries first rule ] ]
+"/                            argument: (browser builder findComponentAt:'RuleList') application listSelection.
+"/            (browser builder findComponentAt:'RuleDetails') application ruleHolder:ruleHolder.
+
+            ruleGenerator :=
+                Iterator on:[:whatToDo|
+                    result failedRules do:whatToDo].
+
+            methodGenerator :=
+                Iterator on: [:whatToDo|
+                    | selectedRules selectedClasses failedMethods |
+
+                    selectedClasses := browser selectedClasses value.
+                    selectedRules := browser selectedLintRules value.
+                    failedMethods := OrderedCollection new.
+                    selectedClasses isEmptyOrNil ifFalse:
+                        [selectedRules ? #() do:
+                            [:rule|
+                            failedMethods addAll:
+                                (rule failedMethodsInAnyOf: selectedClasses meta: self hasMetaSelected)].
+                    failedMethods do:
+                        [:mth|
+                        whatToDo
+                            value:mth containingClass
+                            value:mth category
+                            value:mth selector
+                            value:mth]]].
+
+            browser lintRuleListGenerator value:ruleGenerator.
+            browser selectorListGenerator value:methodGenerator.
+
+            browser selectedClasses
+                onChangeSend: #changed to: browser selectorListGenerator.
+            browser selectedLintRules
+                onChangeSend: #changed to: browser selectorListGenerator.
+            browser meta
+                onChangeSend: #changed to: browser selectorListGenerator.
+
+            "/self halt.
+            "
+            theMethodList isNil ifTrue:[
+                methodsOrMethodGeneratorBlock isBlock ifTrue:[
+                    theMethodList := methodsOrMethodGeneratorBlock value.
+                ] ifFalse:[
+                    theMethodList := methodsOrMethodGeneratorBlock copy.
+                ].
+            ].
+            perClassInfo := perClassInfoHolder value.
+            perMethodInfo := perMethodInfoHolder value.
+
+            methodGenerator := Iterator on:[:whatToDo |
+                                            theMethodList isNil ifTrue:[
+                                                methodsOrMethodGeneratorBlock isBlock ifTrue:[
+                                                    theMethodList := methodsOrMethodGeneratorBlock value.
+                                                ] ifFalse:[
+                                                    theMethodList := methodsOrMethodGeneratorBlock copy.
+                                                ].
+                                            ].
+                                            perClassInfo := perClassInfoHolder value.
+                                            perMethodInfo := perMethodInfoHolder value.
+
+                                            theMethodNameList := theMethodList collect:[:eachMethod | eachMethod mclass -> eachMethod selector].
+                                            theMethodNameList do:[:mAssoc |
+                                                |methodClass methodSelector method|
+
+                                                methodClass := mAssoc key.
+                                                methodSelector := mAssoc value.
+                                                methodClass notNil ifTrue:[
+                                                    method := methodClass compiledMethodAt:methodSelector.
+                                                    method notNil ifTrue:[
+                                                        whatToDo
+                                                            value:methodClass
+                                                            value:method category
+                                                            value:methodSelector
+                                                            value:method.
+                                                    ].
+                                                ].
+                                            ].
+                                            methodsOrMethodGeneratorBlock isBlock ifTrue:[
+                                                theMethodList := nil.
+                                            ].
+                                            whatToDo
+                                                value:nil
+                                                value:nil
+                                                value:nil
+                                                value:nil.
+                                      ].
+
+            sortHow notNil ifTrue:[brwsr sortBy value:sortHow].
+
+            brwsr selectorListGenerator value:methodGenerator.
+            perClassInfo notNil ifTrue:[
+                classGenerator := perClassInfo keys.
+                brwsr classListGenerator value:classGenerator.
+                brwsr meta value:false.
+            ].
+
+            perClassInfo notNil ifTrue:[
+                brwsr selectedClasses
+                    onChangeEvaluate:[
+                        |class infoText|
+
+                        brwsr selectedMethods value:nil.
+                        class := brwsr theSingleSelectedClass.
+                        class notNil ifTrue:[
+                            brwsr meta value:false.
+                            infoText := perClassInfoHolder value at:class theNonMetaclass ifAbsent:nil.
+                            infoText isNil ifTrue:[
+                                infoText := perClassInfo at:class theMetaclass ifAbsent:nil
+                            ]
+                        ].
+                        brwsr methodInfo value:infoText.
+                    ]
+            ].
+
+            perMethodInfo notNil ifTrue:[
+                brwsr selectedMethods
+                    onChangeEvaluate:[
+                        |mthd infoText|
+
+                        brwsr selectedClasses value:nil.
+                        mthd := brwsr theSingleSelectedMethod.
+                        mthd notNil ifTrue:[
+                            infoText := perMethodInfo at:mthd ifAbsent:nil
+                        ].
+                        brwsr methodInfo value:infoText.
+                    ]
+            ] ifFalse:[
+                (doSelect and:[theMethodList size == 1]) ifTrue:[
+                    brwsr selectMethods:(Array with:theMethodList first).
+                    brwsr methodsSelectionChanged.
+                ]
+            ].
+
+            methodsOrMethodGeneratorBlock isBlock ifTrue:[
+                theMethodList := nil 
+            ]
+            "
+        ]
+
+    "Modified: / 22-07-2009 / 15:51:56 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Created: / 02-02-2010 / 20:05:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 02-02-2010 / 21:46:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 25-08-2010 / 10:30:33 / Jan Vrany <enter your email here>"
+    "Modified: / 01-03-2012 / 15:00:59 / cg"
+! !
+
+!NewSystemBrowser methodsFor:'menu actions-checks-old'!
 
 classMenuCheck
-    "perform all checks on the selected class(es)."
+    "perform a bunch of checks on the selected class(es).
+     This uses the old (more or less to be obsoleted) classChecker,
+     not the new SmallLint tool."
 
     self classMenuCheck:#allChecks
+
+    "Modified (comment): / 01-03-2012 / 14:10:06 / cg"
 !
 
 classMenuCheck:whichCheck
-    "perform an individual check on the selected class(es)."
+    "perform an individual check on the selected class(es).
+     This uses the old (more or less to be obsoleted) classChecker,
+     not the new SmallLint tool."
 
     self classMenuCheckEach:(Array with:whichCheck)
 
-    "Modified: / 18.8.2000 / 22:44:19 / cg"
+    "Modified: / 18-08-2000 / 22:44:19 / cg"
+    "Modified (comment): / 01-03-2012 / 14:10:14 / cg"
 !
 
 classMenuCheckAll
-    "perform all checks on the selected class(es)."
+    "perform all checks on the selected class(es).
+     This uses the old (more or less to be obsoleted) classChecker,
+     not the new SmallLint tool."
 
     self classMenuCheck:#allChecks
+
+    "Modified (comment): / 01-03-2012 / 14:10:19 / cg"
 !
 
 classMenuCheckEach:aCollectionOfCheckSymbols
-    "perform a bunch of checks on the selected class(es)."
+    "perform a bunch of checks on the selected class(es).
+     This uses the old (more or less to be obsoleted) classChecker,
+     not the new SmallLint tool."
 
     |classes theSingleClass lbl badMethodsGenerator badMethodInfoHolder badClassInfoHolder|
 
@@ -25376,16 +25704,23 @@
 
     "Created: / 18-08-2000 / 22:43:56 / cg"
     "Modified: / 28-02-2012 / 16:45:37 / cg"
+    "Modified (comment): / 01-03-2012 / 14:09:59 / cg"
 !
 
 classMenuCheckErrors
-    "perform error-checks on the selected class(es)."
+    "perform error-checks on the selected class(es).
+     This uses the old (more or less to be obsoleted) classChecker,
+     not the new SmallLint tool."
 
     self classMenuCheck:#errorChecks
+
+    "Modified (comment): / 01-03-2012 / 14:10:26 / cg"
 !
 
 classMenuCheckIndividual
-    "allow individual checks to be selected and perform those on the selected class(es)."
+    "allow individual checks to be selected and perform those on the selected class(es).
+     This uses the old (more or less to be obsoleted) classChecker,
+     not the new SmallLint tool."
 
     |allChecks selectedChecks|
 
@@ -25404,19 +25739,28 @@
     LastIndividualChecks := selectedChecks.
     self classMenuCheckEach:selectedChecks.
 
-    "Modified: / 18.8.2000 / 22:44:36 / cg"
+    "Modified: / 18-08-2000 / 22:44:36 / cg"
+    "Modified (comment): / 01-03-2012 / 14:10:31 / cg"
 !
 
 classMenuCheckStyle
-    "perform style-checks on the selected class(es)."
+    "perform style-checks on the selected class(es).
+     This uses the old (more or less to be obsoleted) classChecker,
+     not the new SmallLint tool."
 
     self classMenuCheck:#styleChecks
+
+    "Modified (comment): / 01-03-2012 / 14:10:36 / cg"
 !
 
 classMenuCheckWarnings
-    "perform warning-checks on the selected class(es)."
+    "perform warning-checks on the selected class(es).
+     This uses the old (more or less to be obsoleted) classChecker,
+     not the new SmallLint tool."
 
     self classMenuCheck:#warningChecks
+
+    "Modified (comment): / 01-03-2012 / 14:10:43 / cg"
 ! !
 
 !NewSystemBrowser methodsFor:'menu actions-class'!
@@ -34866,17 +35210,6 @@
     self updateSpecialCodeEditorVisibility
 ! !
 
-!NewSystemBrowser methodsFor:'menu actions-lint'!
-
-runLint
-
-    self 
-        smalllintCheck: self selectedCodeComponentsAsEnvironment 
-        against: #smalllintRules
-
-    "Modified: / 17-04-2010 / 10:44:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
 !NewSystemBrowser methodsFor:'menu actions-methodList'!
 
 methodListMenuCheckInClass
@@ -50598,8 +50931,9 @@
 theSingleSelectedLintRuleHolder
 
     ^BlockValue
-        with:
-            [:generator| | rule size |
+        with:[:generator| 
+            | rule size |
+
             rule := nil.
             size := 0.
             (generator value ? #()) do:[:each|rule := each.size := size + 1].
@@ -50607,6 +50941,7 @@
         argument: self selectedLintRules
 
     "Created: / 05-02-2010 / 12:56:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-03-2012 / 15:31:23 / cg"
 !
 
 theSingleSelectedLoadedNonMetaclassOrNil
@@ -51952,299 +52287,6 @@
     ^ nil.
 ! !
 
-!NewSystemBrowser methodsFor:'private-smalllint'!
-
-loadSmalllint
-    |pkg dlg|
-
-    pkg := Smalltalk at:#'stx_goodies_refactoryBrowser_lint'.
-    (pkg isNil or:[ pkg isFullyLoaded not ]) ifTrue:[
-        Smalltalk loadPackage:#'stx:goodies/refactoryBrowser/lint'
-            asAutoloaded:false
-    ].
-
-    "
-        Tools::NewSystemBrowser basicNew loadSmallLint"
-    "Created: / 17-04-2010 / 09:40:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-smalllintCheck:anEnvironment against:ruleSetSymbol 
-    |rule|
-
-    self 
-        assert:(#( #smalllintRulesAll #smalllintRulesFromUser #smalllintRules ) 
-                includes:ruleSetSymbol).
-    rule := self perform:ruleSetSymbol asSymbol.
-    rule isNil ifTrue:[ ^ self ].
-"/ cg: that is wrong implemented in RBxxxRule: isEmpty has two meanings:
-"/     for composite: has sub-rules
-"/     for non-composite: has a result
-"/ therefore, isEmpty returns true here, so we will be always asked twice!!
-
-    rule isEmpty ifTrue:[
-        ruleSetSymbol ~~ #smalllintRulesFromUser ifTrue:[
-            rule := self smalllintRulesFromUser.
-            rule isNil ifTrue:[ ^ self ].
-        ]
-    ].
-
-    self showMessage:'Checking code...'
-        while:[
-            self smalllintRunRule:rule onEnvironment:anEnvironment.
-            self 
-                spawnSmalllintBrowserByRuleFor:rule
-                in:#newBuffer
-                label:'SmallLint results for ' , anEnvironment label
-        ].
-
-    "Modified: / 15-12-2008 / 18:51:43 / Josef Grega <gregaj1@fel.cvut.cz>"
-    "Modified: / 28-12-2008 / 14:40:01 / bazantj <enter your email here>"
-    "Created: / 24-02-2009 / 11:02:57 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 22-07-2009 / 14:38:30 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 28-08-2010 / 20:45:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 01-03-2012 / 08:41:43 / cg"
-!
-
-smalllintRules
-
-   ^LastLintRules 
-        ifNil:[self smalllintRulesFromUser]
-        ifNotNil:[LastLintRules]
-
-
-    "
-        Tools::NewSystemBrowser basicNew smalllintRules
-    "
-
-    "Modified: / 17-04-2010 / 09:42:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-smalllintRulesAll
-
-    | all checks |
-    all := RBCompositeLintRule allRules.
-    checks := all rules detect:[ :each | each name = 'Lint checks' ].
-    checks rules: (checks rules reject: [ :each | each name = 'Squeak bugs' ]).
-    ^all
-
-    "Created: / 17-04-2010 / 10:07:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 25-08-2010 / 14:38:21 / Jan Vrany <enter your email here>"
-!
-
-smalllintRulesFromUser
-    |dlg|
-
-    self loadSmalllint.
-    dlg := Tools::LintRuleSelectionDialog new.
-    dlg selection: (LastLintRules ifNil:[nil"self smalllintRulesAll flattened"] ifNotNil:[LastLintRules flattened]).
-    ^(dlg open; accepted) 
-            ifTrue:[ LastLintRules := dlg selectionAsRule ] 
-            ifFalse:[ nil ].
-
-    "
-        LastLintRules := nil.
-        Tools::NewSystemBrowser basicNew smalllintRulesFromUser
-    "
-
-    "Created: / 17-04-2010 / 09:41:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 25-08-2010 / 15:35:16 / Jan Vrany <enter your email here>"
-!
-
-smalllintRulesOrAll
-
-    "Returns a set of user-selected SmallLint rules or all rules,
-     if no user selection is done"    
-
-   ^LastLintRules notNil ifTrue:[
-        LastLintRules
-    ] ifFalse:[
-        self smalllintRulesAll
-    ]
-
-    "Created: / 23-01-2012 / 10:59:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-smalllintRulesOrAllHolder
-    "Returns a holder on user-selected SmallLint rules
-     (or all rules if user made no selection"
-
-    ^[ self smalllintRulesOrAll ]
-
-    "Modified: / 17-04-2010 / 09:42:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Created: / 23-01-2012 / 11:05:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-smalllintRunRule: aLintRule onEnvironment: anEnvironment
-
-    | rules |
-    rules := aLintRule flattened.
-    rules withIndexDo:
-        [:rule :index|
-        ProgressNotification new
-            messageText: ('Checking: ', rule name);
-            parameter: (rules size / 100) * index;
-            raiseRequest.
-       (SmalllintChecker runRule: rule onEnvironment: anEnvironment)]
-
-    "Modified: / 15-12-2008 / 18:51:43 / Josef Grega <gregaj1@fel.cvut.cz>"
-    "Modified: / 28-12-2008 / 14:40:01 / bazantj <enter your email here>"
-    "Modified: / 22-07-2009 / 14:38:30 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Created: / 28-08-2010 / 12:12:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-spawnSmalllintBrowserByRuleFor: result in:where label:labelOrNil
-
-    ^ self
-        newBrowserOrBufferDependingOn:where
-        label:labelOrNil
-        forSpec: #smallLintByRuleResultBrowserSpec
-        setupWith:[:browser | |methodGenerator classGenerator ruleGenerator |
-            ruleGenerator :=
-                Iterator on:
-                    [:whatToDo|
-                    result failedRules do:whatToDo].
-
-            methodGenerator :=
-                Iterator on:
-                    [:whatToDo|
-                    | selectedRules selectedClasses failedMethods |
-                    selectedClasses := browser selectedClasses value.
-                    selectedRules := browser selectedLintRules value.
-                    failedMethods := OrderedCollection new.
-                    selectedClasses isEmptyOrNil ifFalse:
-                        [selectedRules ? #() do:
-                            [:rule|
-                            failedMethods addAll:
-                                (rule failedMethodsInAnyOf: selectedClasses meta: self hasMetaSelected)].
-                    failedMethods do:
-                        [:mth|
-                        whatToDo
-                            value:mth containingClass
-                            value:mth category
-                            value:mth selector
-                            value:mth]]].
-
-            browser lintRuleListGenerator value:ruleGenerator.
-            browser selectorListGenerator value:methodGenerator.
-
-            browser selectedClasses
-                onChangeSend: #changed to: browser selectorListGenerator.
-            browser selectedLintRules
-                onChangeSend: #changed to: browser selectorListGenerator.
-            browser meta
-                onChangeSend: #changed to: browser selectorListGenerator.
-
-
-
-            "/self halt.
-            "
-            theMethodList isNil ifTrue:[
-                methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                    theMethodList := methodsOrMethodGeneratorBlock value.
-                ] ifFalse:[
-                    theMethodList := methodsOrMethodGeneratorBlock copy.
-                ].
-            ].
-            perClassInfo := perClassInfoHolder value.
-            perMethodInfo := perMethodInfoHolder value.
-
-            methodGenerator := Iterator on:[:whatToDo |
-                                            theMethodList isNil ifTrue:[
-                                                methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                                                    theMethodList := methodsOrMethodGeneratorBlock value.
-                                                ] ifFalse:[
-                                                    theMethodList := methodsOrMethodGeneratorBlock copy.
-                                                ].
-                                            ].
-                                            perClassInfo := perClassInfoHolder value.
-                                            perMethodInfo := perMethodInfoHolder value.
-
-                                            theMethodNameList := theMethodList collect:[:eachMethod | eachMethod mclass -> eachMethod selector].
-                                            theMethodNameList do:[:mAssoc |
-                                                |methodClass methodSelector method|
-
-                                                methodClass := mAssoc key.
-                                                methodSelector := mAssoc value.
-                                                methodClass notNil ifTrue:[
-                                                    method := methodClass compiledMethodAt:methodSelector.
-                                                    method notNil ifTrue:[
-                                                        whatToDo
-                                                            value:methodClass
-                                                            value:method category
-                                                            value:methodSelector
-                                                            value:method.
-                                                    ].
-                                                ].
-                                            ].
-                                            methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                                                theMethodList := nil.
-                                            ].
-                                            whatToDo
-                                                value:nil
-                                                value:nil
-                                                value:nil
-                                                value:nil.
-                                      ].
-
-            sortHow notNil ifTrue:[brwsr sortBy value:sortHow].
-
-            brwsr selectorListGenerator value:methodGenerator.
-            perClassInfo notNil ifTrue:[
-                classGenerator := perClassInfo keys.
-                brwsr classListGenerator value:classGenerator.
-                brwsr meta value:false.
-            ].
-
-            perClassInfo notNil ifTrue:[
-                brwsr selectedClasses
-                    onChangeEvaluate:[
-                        |class infoText|
-
-                        brwsr selectedMethods value:nil.
-                        class := brwsr theSingleSelectedClass.
-                        class notNil ifTrue:[
-                            brwsr meta value:false.
-                            infoText := perClassInfoHolder value at:class theNonMetaclass ifAbsent:nil.
-                            infoText isNil ifTrue:[
-                                infoText := perClassInfo at:class theMetaclass ifAbsent:nil
-                            ]
-                        ].
-                        brwsr methodInfo value:infoText.
-                    ]
-            ].
-
-            perMethodInfo notNil ifTrue:[
-                brwsr selectedMethods
-                    onChangeEvaluate:[
-                        |mthd infoText|
-
-                        brwsr selectedClasses value:nil.
-                        mthd := brwsr theSingleSelectedMethod.
-                        mthd notNil ifTrue:[
-                            infoText := perMethodInfo at:mthd ifAbsent:nil
-                        ].
-                        brwsr methodInfo value:infoText.
-                    ]
-            ] ifFalse:[
-                (doSelect and:[theMethodList size == 1]) ifTrue:[
-                    brwsr selectMethods:(Array with:theMethodList first).
-                    brwsr methodsSelectionChanged.
-                ]
-            ].
-
-            methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                theMethodList := nil 
-            ]
-            "
-        ]
-
-    "Modified: / 22-07-2009 / 15:51:56 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Created: / 02-02-2010 / 20:05:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 02-02-2010 / 21:46:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 25-08-2010 / 10:30:33 / Jan Vrany <enter your email here>"
-    "Modified: / 04-08-2011 / 19:05:35 / cg"
-! !
-
 !NewSystemBrowser methodsFor:'private-syntax coloring'!
 
 startSyntaxHighlightProcess
@@ -56054,11 +56096,11 @@
 !NewSystemBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1718 2012-03-01 13:02:33 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1719 2012-03-01 15:46:35 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1718 2012-03-01 13:02:33 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1719 2012-03-01 15:46:35 cg Exp $'
 !
 
 version_SVN