Tools__NewSystemBrowser.st
changeset 16533 84fe5d2d72f3
parent 16498 1101b39beeba
child 16560 b7fd79c0e807
child 16571 cf319f2e56d0
equal deleted inserted replaced
16532:2f9e7091b4b5 16533:84fe5d2d72f3
   446 'Hide toolbar. Show again via the "View"-Menu'
   446 'Hide toolbar. Show again via the "View"-Menu'
   447 
   447 
   448 #hideBookmarkBar
   448 #hideBookmarkBar
   449 'Hide the bookmark-bar. Show again via the "View"-menu'
   449 'Hide the bookmark-bar. Show again via the "View"-menu'
   450 
   450 
       
   451 #infoLabelHelp
       
   452 'Display info on the just selected method, the clicked on code-fragment or the current activity'
       
   453 
   451 #redoOperation
   454 #redoOperation
   452 'Redo undone operation'
   455 'Redo undone operation'
   453 
   456 
   454 #undoOperation
   457 #undoOperation
   455 'Undo operation'
   458 'Undo operation'
       
   459 
   456 
   460 
   457 ).
   461 ).
   458 
   462 
   459     (RefactoryChangeManager notNil and:[ RefactoryChangeManager isLoaded ]) ifTrue:[
   463     (RefactoryChangeManager notNil and:[ RefactoryChangeManager isLoaded ]) ifTrue:[
   460         manager := RefactoryChangeManager instance.
   464         manager := RefactoryChangeManager instance.
  1471                          name: 'InfoLabel'
  1475                          name: 'InfoLabel'
  1472                          level: -1
  1476                          level: -1
  1473                          translateLabel: true
  1477                          translateLabel: true
  1474                          labelChannel: infoLabelHolder
  1478                          labelChannel: infoLabelHolder
  1475                          adjust: left
  1479                          adjust: left
       
  1480                          activeHelpKey: infoLabelHelp
  1476                        )
  1481                        )
  1477                       (HorizontalPanelViewSpec
  1482                       (HorizontalPanelViewSpec
  1478                          name: 'PackageInfoPanel'
  1483                          name: 'PackageInfoPanel'
  1479                          level: -1
  1484                          level: -1
  1480                          horizontalLayout: rightSpaceFit
  1485                          horizontalLayout: rightSpaceFit
  1481                          verticalLayout: fitSpace
  1486                          verticalLayout: fitSpace
  1482                          horizontalSpace: 0
  1487                          horizontalSpace: 0
  1483                          verticalSpace: 0
  1488                          verticalSpace: 0
  1484                          elementsChangeSize: true
  1489                          elementsChangeSize: true
       
  1490                          activeHelpKey: packageInfoLabel
  1485                          component: 
  1491                          component: 
  1486                         (SpecCollection
  1492                         (SpecCollection
  1487                            collection: (
  1493                            collection: (
  1488                             (LabelSpec
  1494                             (LabelSpec
  1489                                label: 'Package'
  1495                                label: 'Package'
 12641             label: 'Sort by Name'
 12647             label: 'Sort by Name'
 12642             hideMenuOnActivated: false
 12648             hideMenuOnActivated: false
 12643             indication: sortVariablesByName
 12649             indication: sortVariablesByName
 12644           )
 12650           )
 12645          (MenuItem
 12651          (MenuItem
       
 12652             label: 'Group by Inheritance'
       
 12653             hideMenuOnActivated: false
       
 12654             indication: groupVariablesByInheritance
       
 12655           )
       
 12656          (MenuItem
 12646             label: '-'
 12657             label: '-'
 12647           )
 12658           )
 12648          (MenuItem
 12659          (MenuItem
 12649             enabled: hasClassSelectedHolder
 12660             enabled: hasClassSelectedHolder
 12650             label: 'Generate'
 12661             label: 'Generate'
 19663 selectedMethods4
 19674 selectedMethods4
 19664     ^ self navigationState selectedMethodsArrayAt:4
 19675     ^ self navigationState selectedMethodsArrayAt:4
 19665 !
 19676 !
 19666 
 19677 
 19667 selectedMethodsClasses
 19678 selectedMethodsClasses
 19668     ^ (self selectedMethodsValue collect:[:m | m mclass] as:Set)
 19679     ^ (self selectedMethodsValue 
       
 19680         collect:[:m | m mclass] as:Set)
 19669             select:[:each| each notNil]
 19681             select:[:each| each notNil]
 19670 
 19682 
 19671     "Created: / 07-08-2006 / 12:13:37 / cg"
 19683     "Created: / 07-08-2006 / 12:13:37 / cg"
 19672 !
 19684 !
 19673 
 19685 
 19711 selectorListGenerator
 19723 selectorListGenerator
 19712     ^ self navigationState selectorListGenerator
 19724     ^ self navigationState selectorListGenerator
 19713 !
 19725 !
 19714 
 19726 
 19715 selectorListGenerator1
 19727 selectorListGenerator1
       
 19728     "used for the sender-/implementor-chain's first methodlist"
       
 19729     
 19716     ^ self navigationState selectorListGeneratorArrayAt:1
 19730     ^ self navigationState selectorListGeneratorArrayAt:1
 19717 !
 19731 !
 19718 
 19732 
 19719 selectorListGenerator2
 19733 selectorListGenerator2
       
 19734     "used for the sender-/implementor-chain's second methodlist"
       
 19735 
 19720     ^ self navigationState selectorListGeneratorArrayAt:2
 19736     ^ self navigationState selectorListGeneratorArrayAt:2
 19721 !
 19737 !
 19722 
 19738 
 19723 selectorListGenerator3
 19739 selectorListGenerator3
       
 19740     "used for the sender-/implementor-chain's third methodlist"
       
 19741 
 19724     ^ self navigationState selectorListGeneratorArrayAt:3
 19742     ^ self navigationState selectorListGeneratorArrayAt:3
 19725 !
 19743 !
 19726 
 19744 
 19727 selectorListGenerator4
 19745 selectorListGenerator4
       
 19746     "used for the sender-/implementor-chain's fourth methodlist"
       
 19747 
 19728     ^ self navigationState selectorListGeneratorArrayAt:4
 19748     ^ self navigationState selectorListGeneratorArrayAt:4
 19729 !
 19749 !
 19730 
 19750 
 19731 selectorListGenerator5
 19751 selectorListGenerator5
 19732 
 19752     "Used for all method's generator of ClassList. "
 19733     "Used for all methods generator of ClassList. "
       
 19734 
 19753 
 19735     ^ self navigationState selectorListGeneratorArrayAt:5
 19754     ^ self navigationState selectorListGeneratorArrayAt:5
 19736 
 19755 
 19737     "Created: / 07-08-2011 / 19:06:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 19756     "Created: / 07-08-2011 / 19:06:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 19738 !
 19757 !
 20348     classListApp unloadedClassesColor:clr.
 20367     classListApp unloadedClassesColor:clr.
 20349     "/ classListApp updateList.
 20368     "/ classListApp updateList.
 20350     classListApp invalidateList.
 20369     classListApp invalidateList.
 20351 
 20370 
 20352     "Modified: / 31.10.2001 / 11:14:50 / cg"
 20371     "Modified: / 31.10.2001 / 11:14:50 / cg"
       
 20372 !
       
 20373 
       
 20374 groupVariablesByInheritance
       
 20375     ^ builder valueAspectFor:#groupVariablesByInheritance initialValue:true
 20353 !
 20376 !
 20354 
 20377 
 20355 hidePrivateClasses
 20378 hidePrivateClasses
 20356     ^ self navigationState hidePrivateClasses
 20379     ^ self navigationState hidePrivateClasses
 20357 
 20380 
 24889 
 24912 
 24890 flyByHelpSpec
 24913 flyByHelpSpec
 24891     |changeSet spec|
 24914     |changeSet spec|
 24892 
 24915 
 24893     spec := super flyByHelpSpec.
 24916     spec := super flyByHelpSpec.
       
 24917 
 24894     changeSet := ChangeSet current.
 24918     changeSet := ChangeSet current.
       
 24919     "/ (changeSet contains:[:chg | chg isMethodChange and:[chg changeClass notNil]]) ifTrue:[
 24895     (changeSet findLast:[:chg | chg isMethodChange and:[chg changeClass notNil]]) ~~ 0 ifTrue:[
 24920     (changeSet findLast:[:chg | chg isMethodChange and:[chg changeClass notNil]]) ~~ 0 ifTrue:[
 24896         spec at:#recentChanges put:(spec at:#recentlyChangedMethods).
 24921         spec at:#recentChanges put:(spec at:#recentlyChangedMethods).
 24897     ] ifFalse:[
 24922     ] ifFalse:[
 24898 "/        (changeSet contains:[:chg | chg isClassChange and:[chg changeClass notNil]]) ifTrue:[
 24923 "/        (changeSet contains:[:chg | chg isClassChange and:[chg changeClass notNil]]) ifTrue:[
 24899 "/            spec at:#recentChanges put:(spec at:#recentlyChangedClasses).
 24924 "/            spec at:#recentChanges put:(spec at:#recentlyChangedClasses).
 24904     ^ spec.
 24929     ^ spec.
 24905 
 24930 
 24906     "Modified: / 08-09-2011 / 05:05:06 / cg"
 24931     "Modified: / 08-09-2011 / 05:05:06 / cg"
 24907 !
 24932 !
 24908 
 24933 
 24909 flyByHelpTextFor:aComponent
 24934 flyByHelpTextFor:aWidget at:aPoint
 24910 "/    (aComponent == builder componentAt:) ifTrue:[
 24935     |action info label|
 24911 "/    ].
 24936     
 24912     ^ super flyByHelpTextFor:aComponent
 24937     aWidget = (navigationState canvas builder componentAt:'InfoLabel') ifTrue:[
       
 24938         action := aWidget actionAt:aPoint.
       
 24939         Transcript showCR:action.
       
 24940         info := action perform:#info ifNotUnderstood:nil.
       
 24941         info notNil ifTrue:[
       
 24942             ^ info value
       
 24943         ].
       
 24944         (label := aWidget label) notNil ifTrue:[
       
 24945             (label widthOn:aWidget) > aWidget width ifTrue:[
       
 24946                 ^ label
       
 24947             ]    
       
 24948         ]    
       
 24949     ].
       
 24950     ^ nil
 24913 ! !
 24951 ! !
 24914 
 24952 
 24915 !NewSystemBrowser methodsFor:'history'!
 24953 !NewSystemBrowser methodsFor:'history'!
 24916 
 24954 
 24917 addToFindHistory:class selector:selector
 24955 addToFindHistory:class selector:selector
 46527 
 46565 
 46528 selectorMenuBrowseRepositoryVersionsUsingManager: manager
 46566 selectorMenuBrowseRepositoryVersionsUsingManager: manager
 46529 
 46567 
 46530     |method mclass mselector className mgr revisions previousMethods browser
 46568     |method mclass mselector className mgr revisions previousMethods browser
 46531      lastSource currentSource lastRevision lastDate lastChange lastAuthor thisIsAnExtensionMethod
 46569      lastSource currentSource lastRevision lastDate lastChange lastAuthor thisIsAnExtensionMethod
 46532      packageId directory module|
 46570      packageId directory module currentVersion newestVersion|
 46533 
 46571 
 46534     method := self theSingleSelectedMethod.
 46572     method := self theSingleSelectedMethod.
 46535     method isNil ifTrue:[^ self].
 46573     method isNil ifTrue:[^ self].
 46536 
 46574 
 46537     mclass := method mclass.
 46575     mclass := method mclass.
 46542 
 46580 
 46543         set := ChangeSet forExistingMethods:(Array with:method).
 46581         set := ChangeSet forExistingMethods:(Array with:method).
 46544         set := set select:[:c | c isMethodChange].
 46582         set := set select:[:c | c isMethodChange].
 46545         lastChange := set first.
 46583         lastChange := set first.
 46546     ] value.
 46584     ] value.
 46547 
 46585     currentVersion := mclass revisionOfManager:manager.
       
 46586     
 46548     thisIsAnExtensionMethod := (method isExtension).
 46587     thisIsAnExtensionMethod := (method isExtension).
 46549     thisIsAnExtensionMethod ifTrue:[
 46588     thisIsAnExtensionMethod ifTrue:[
 46550         packageId := method package asPackageId.
 46589         packageId := method package asPackageId.
 46551         mgr := manager
 46590         mgr := manager
 46552     ] ifFalse:[
 46591     ] ifFalse:[
 46557     ].
 46596     ].
 46558     directory := packageId directory.
 46597     directory := packageId directory.
 46559     module := packageId module.
 46598     module := packageId module.
 46560 
 46599 
 46561     self withWaitCursorDo:[
 46600     self withWaitCursorDo:[
 46562         |revisionLog start stop answer t tS list msg first|
 46601         |revisionLog numRevisions stop answer t tS list msg first|
 46563 
 46602 
 46564         thisIsAnExtensionMethod ifTrue:[
 46603         thisIsAnExtensionMethod ifTrue:[
 46565             revisionLog := mgr
 46604             revisionLog := mgr
 46566                 revisionLogOf:nil
 46605                 revisionLogOf:nil
 46567                 fromRevision:nil
 46606                 fromRevision:nil
 46573         ] ifFalse:[
 46612         ] ifFalse:[
 46574             revisionLog := mgr revisionLogOf:mclass.
 46613             revisionLog := mgr revisionLogOf:mclass.
 46575         ].
 46614         ].
 46576         revisions := revisionLog at:#revisions.
 46615         revisions := revisionLog at:#revisions.
 46577 
 46616 
 46578         start := 1.
 46617         stop := numRevisions := revisions size.
 46579         stop := revisions size.
       
 46580         stop > 20 ifTrue:[
 46618         stop > 20 ifTrue:[
 46581             thisIsAnExtensionMethod ifTrue:[
 46619             thisIsAnExtensionMethod ifTrue:[
 46582                 t := 500.   "/ fake time
 46620                 t := 500.   "/ fake time
 46583             ] ifFalse:[
 46621             ] ifFalse:[
 46584                 "/ measure the time it takes to checkout a version...
 46622                 "/ measure the time it takes to checkout a version...
 46588                     revSourceStream := mgr getSourceStreamFor:mclass revision:((revisions at:10) at:#revision).
 46626                     revSourceStream := mgr getSourceStreamFor:mclass revision:((revisions at:10) at:#revision).
 46589                     ChangeSet fromStream:revSourceStream.
 46627                     ChangeSet fromStream:revSourceStream.
 46590                     revSourceStream close.
 46628                     revSourceStream close.
 46591                 ].
 46629                 ].
 46592             ].
 46630             ].
       
 46631             newestVersion := revisions first at:#revision.
 46593 
 46632 
 46594             list := revisions collect:[:entry |
 46633             list := revisions collect:[:entry |
 46595                                         |rev author dateString date msg|
 46634                                         |rev author dateString date msg|
 46596 
 46635 
 46597                                         rev := entry at:#revision.
 46636                                         rev := entry at:#revision.
 46602                                         entry at:#date put:dateString.
 46641                                         entry at:#date put:dateString.
 46603                                         msg := ((entry at:#logMessage) asStringCollection firstIfEmpty:'') asString.
 46642                                         msg := ((entry at:#logMessage) asStringCollection firstIfEmpty:'') asString.
 46604                                         rev,' ',author,' ',dateString,' ',msg
 46643                                         rev,' ',author,' ',dateString,' ',msg
 46605                                       ].
 46644                                       ].
 46606             msg := 'There are %1 revisions to extract from the repository'.
 46645             msg := 'There are %1 revisions to extract from the repository'.
 46607             t := (t * revisions size / 1000) rounded.
 46646             t := (t * numRevisions / 1000) rounded.
 46608             t < 10 ifTrue:[
 46647             t < 10 ifTrue:[
 46609                 msg := msg,'\(this will take a few seconds).'.
 46648                 msg := msg,'\(this will take a few seconds).'.
 46610                 tS := t.
 46649                 tS := t.
 46611             ] ifFalse:[
 46650             ] ifFalse:[
 46612                 t := t * revisions size // 1000 // 10 * 10.
 46651                 t := t * numRevisions // 1000 // 10 * 10.
 46613                 tS := (TimeDuration fromSeconds:t) printStringForApproximation.
 46652                 tS := (TimeDuration fromSeconds:t) printStringForApproximation.
 46614                 msg := msg,'\(this will take roughly %2).'
 46653                 msg := msg,'\(this will take roughly %2).'
 46615             ].
 46654             ].
 46616             msg := msg,'\\Do you want to see all or only some of the revisions ?'.
 46655             msg := msg,'\\Do you want to see all or only some of the revisions ?'.
 46617 
 46656 
 46618             answer := Dialog
 46657             answer := Dialog
 46619                 choose:(resources stringWithCRs:msg
 46658                 choose:(resources stringWithCRs:msg with:numRevisions with:tS)
 46620                                     with:revisions size
       
 46621                                     with:tS)
       
 46622                 fromList:list values:revisions initialSelection:nil
 46659                 fromList:list values:revisions initialSelection:nil
 46623                 buttons:nil
 46660                 buttons:nil
 46624                 values:nil
 46661                 values:nil
 46625                 default:nil
 46662                 default:nil
 46626                 lines:20
 46663                 lines:20
 46627                 cancel:[^ self]
 46664                 cancel:[^ self]
 46628                 multiple:false
 46665                 multiple:false
 46629                 title:(resources string:'Confirmation')
 46666                 title:(resources string:'Confirmation')
 46630                 postBuildBlock:[:dialog |
 46667                 postBuildBlock:
 46631                             |b|
 46668                     [:dialog |
 46632 
 46669                         |b|
 46633                             b := Button label:(resources string:'Browse Newer than Selected').
 46670 
 46634                             b action:[ stop := (dialog componentAt:#ListView) selection. dialog okPressed].
 46671                         b := Button label:(resources string:'Browse Newer than Selected').
 46635                             b := dialog addButton:b before:dialog okButton.
 46672                         b action:[ stop := (dialog componentAt:#ListView) selection. dialog okPressed].
 46636 
 46673                         b := dialog addButton:b before:dialog okButton.
 46637                             dialog okButton label:(resources string:'Browse All').
 46674 
 46638                             dialog okButton action:[ stop := revisions size. dialog okPressed].
 46675                         dialog okButton label:(resources string:'Browse All').
 46639                         ].
 46676                         dialog okButton action:[ stop := revisions size. dialog okPressed].
       
 46677                     ].
 46640 
 46678 
 46641             stop isNil ifTrue:[^ self ].
 46679             stop isNil ifTrue:[^ self ].
 46642         ].
 46680         ].
 46643 
 46681 
 46644 t := Time millisecondsToRun:[
 46682 t := Time millisecondsToRun:[
 46645 
 46683 
 46646         previousMethods := ChangeSet new.
 46684         previousMethods := ChangeSet new.
 46647         lastSource := currentSource := method source.
 46685         currentSource := method source.
       
 46686         currentVersion = newestVersion ifTrue:[
       
 46687             lastSource := currentSource.
       
 46688         ].    
 46648         lastRevision := lastDate := lastAuthor := nil.
 46689         lastRevision := lastDate := lastAuthor := nil.
 46649         first := true.
 46690         first := true.
 46650 
 46691 self halt.
 46651         revisions from:start to:stop do:[:eachLogEntry |
 46692         "/ revisions at:1 is now the newest (may be newer than current!!)         
       
 46693         revisions from:1 to:stop do:[:eachLogEntry |
 46652             |revision date author revSourceStream|
 46694             |revision date author revSourceStream|
 46653 
 46695 
 46654             revision := eachLogEntry at:#revision.
 46696             revision := eachLogEntry at:#revision.
 46655             date := eachLogEntry at:#date.
 46697             date := eachLogEntry at:#date.
 46656             author := eachLogEntry at:#author ifAbsent:'?'.      
 46698             author := eachLogEntry at:#author ifAbsent:'?'.      
 46657 
 46699 
 46658             [
 46700             [
 46659                 |chg nChg classChangeSet changeSource changeName|
 46701                 |chg nChg classChangeSet changeSource changeName|
 46660 
 46702 
 46661                 self activityNotification:('Fetching revision ',revision,'...').
 46703                 self activityNotification:(resources string:'Fetching revision %1...' with:revision).
 46662                 thisIsAnExtensionMethod ifTrue:[
 46704                 thisIsAnExtensionMethod ifTrue:[
 46663                     revSourceStream := mgr
 46705                     revSourceStream := mgr
 46664                                             streamForClass:nil
 46706                                             streamForClass:nil
 46665                                             fileName:'extensions.st'
 46707                                             fileName:'extensions.st'
 46666                                             revision:revision
 46708                                             revision:revision
 46669                                             cache:true.
 46711                                             cache:true.
 46670                 ] ifFalse:[
 46712                 ] ifFalse:[
 46671                     revSourceStream := mgr getSourceStreamFor:mclass revision:revision.
 46713                     revSourceStream := mgr getSourceStreamFor:mclass revision:revision.
 46672                 ].
 46714                 ].
 46673                 revSourceStream isNil ifTrue:[
 46715                 revSourceStream isNil ifTrue:[
 46674                     self warn:'could not load source for ' , mclass name , ' revision ', revision,  ' from repository'.
 46716                     self warn:(resources string:'Could not load source for %1 revision %2 from repository' with:mclass name with:revision).
 46675                     chg := nil.
 46717                     chg := nil.
 46676                 ] ifFalse:[
 46718                 ] ifFalse:[
 46677                     classChangeSet := ChangeSet fromStream:revSourceStream.
 46719                     classChangeSet := ChangeSet fromStream:revSourceStream.
 46678 
 46720 
 46679                     chg := classChangeSet
 46721                     chg := classChangeSet
 46680                                 detect:[:chg | chg isMethodChange
 46722                                 detect:[:chg | chg isMethodChange
 46681                                                and:[chg selector = mselector
 46723                                                and:[chg selector = mselector
 46682                                                and:[chg className = className]]]
 46724                                                and:[chg fullClassName = className]]]
 46683                                 ifNone:nil.
 46725                                 ifNone:nil.
       
 46726                     chg isNil ifTrue:[
       
 46727                         "/ maybe the class was renamed!!
       
 46728                         (classChangeSet contains:[:chg | chg isMethodChange and:[chg selector = mselector]]) ifTrue:[
       
 46729                             self halt:'check for renamed class'.
       
 46730                         ]     
       
 46731                     ].            
 46684                 ].
 46732                 ].
 46685 
 46733 
 46686                 chg isNil ifTrue:[
 46734                 chg isNil ifTrue:[
 46687                     "the method was created in the next version (previous one processed)"
 46735                     "the method was created in the next version (previous one processed)"
 46688                 ] ifFalse:[
 46736                 ] ifFalse:[
 46695                         "/ mhm - was not in the previous version
 46743                         "/ mhm - was not in the previous version
 46696                     ] ifFalse:[
 46744                     ] ifFalse:[
 46697                         nChg := lastChange asNamedMethodChange
 46745                         nChg := lastChange asNamedMethodChange
 46698                     ].
 46746                     ].
 46699                     lastRevision isNil ifTrue:[
 46747                     lastRevision isNil ifTrue:[
       
 46748                         
 46700                         (stop = revisions size) ifTrue:[
 46749                         (stop = revisions size) ifTrue:[
 46701                             changeName := 'current (not in the repository)'.
 46750                             changeName := 'current (not in the repository)'.
 46702                         ] ifFalse:[
 46751                         ] ifFalse:[
 46703                             "/ not showing all - dont really know
 46752                             "/ not showing all - don't really know
 46704                             changeName := 'current'.
 46753                             changeName := 'current'.
 46705                         ].
 46754                         ].
 46706                     ] ifFalse:[
 46755                     ] ifFalse:[
 46707                         changeName := lastRevision,' [',lastDate,' by ',lastAuthor,']'.
 46756                         changeName := lastRevision,' [',lastDate,' by ',lastAuthor,']'.
 46708                         first ifTrue:[
 46757                         first ifTrue:[
 46709                             changeName := changeName,' (= current)'.
 46758                             (newestVersion compareAsVersionNumberWith:lastRevision) >= 0 ifTrue:[
       
 46759                                 changeName := changeName,' (= current)'.
       
 46760                             ].    
 46710                         ]
 46761                         ]
 46711                     ].
 46762                     ].
 46712                     nChg notNil ifTrue:[
 46763                     nChg notNil ifTrue:[
 46713                         nChg changeName:changeName.
 46764                         nChg changeName:changeName.
 46714                         previousMethods add:nChg.
 46765                         previousMethods add:nChg.
 46728 ].
 46779 ].
 46729 "/ Transcript showCR:('it took %1 seconds' bindWith:(t /1000)printString).
 46780 "/ Transcript showCR:('it took %1 seconds' bindWith:(t /1000)printString).
 46730 
 46781 
 46731         self activityNotification:nil.
 46782         self activityNotification:nil.
 46732         browser := (UserPreferences current changeSetBrowserClass) openOn:previousMethods.
 46783         browser := (UserPreferences current changeSetBrowserClass) openOn:previousMethods.
 46733         browser window label:('Revisions of ' , mclass name , ' ' , mselector).
 46784         browser window label:(resources string:'Revisions of %1 » %2' with:mclass name with:mselector).
 46734         browser readOnly:true.
 46785         browser readOnly:true.
 46735     ].
 46786     ].
 46736 
 46787 
 46737     "Modified: / 01-07-2011 / 16:34:29 / cg"
 46788     "Modified: / 01-07-2011 / 16:34:29 / cg"
 46738     "Created: / 18-11-2011 / 18:19:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 46789     "Created: / 18-11-2011 / 18:19:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 55991                 newBrowser windowGroup notNil ifTrue:[
 56042                 newBrowser windowGroup notNil ifTrue:[
 55992                     t > 5 seconds ifTrue:[
 56043                     t > 5 seconds ifTrue:[
 55993                         newBrowser methodListApp autoUpdateOnChange: false.
 56044                         newBrowser methodListApp autoUpdateOnChange: false.
 55994                     ].
 56045                     ].
 55995                 ].
 56046                 ].
       
 56047                 Transcript show:'search time: '; showCR:t.
 55996                 ^ newBrowser.
 56048                 ^ newBrowser.
 55997             ].
 56049             ].
 55998         ].
 56050         ].
 55999     ] valueWithRestart.
 56051     ] valueWithRestart.
 56000 
 56052