Skip to content

Commit

Permalink
Add Package as a possible scope for 'find with scope'. Thanks Hilaire.
Browse files Browse the repository at this point in the history
  • Loading branch information
jvuletich committed Dec 30, 2024
1 parent 2f703c5 commit 47311b9
Show file tree
Hide file tree
Showing 2 changed files with 82 additions and 0 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
'From Cuis7.3 [latest update: #6957] on 30 December 2024 at 1:04:30 pm'!

!MethodSet methodsFor: 'testing' stamp: 'jmv 12/30/2024 13:04:04'!
isEditingMethod

^selectedMessage notNil and: [ selectedMessage selector ~~ #Comment ]! !

Original file line number Diff line number Diff line change
@@ -0,0 +1,75 @@
'From Cuis7.3 [latest update: #6957] on 30 December 2024 at 1:06:16 pm'!

!SystemDictionary methodsFor: 'browsing' stamp: 'hlsf 12/30/2024 12:55:18'!
browseMethodsWithSourceString: aString in: aPackage
" Browse all methods in aPackage whose source code contains aString as a substring."

| matchingMethods |
matchingMethods := Set new.
aPackage classesDo: [ :aPackageClass |
(aPackageClass organization classComment
findString: aString
startingAt: 1
caseSensitive: false) > 0 ifTrue: [
matchingMethods add: (MethodReference class: aPackageClass selector: #Comment) ]].
aPackage methods do: [ :methodReference |
(methodReference sourceCode
findString: aString
startingAt: 1
caseSensitive: false) > 0 ifTrue: [
matchingMethods add: methodReference ]].

^ self
browseMessageList: matchingMethods asArray sort
name: 'Methods containing ' , aString printString, ' in package: ', aPackage packageName
autoHighlight: aString
allOccurrences: true.! !


!SmalltalkEditor methodsFor: 'menu & kbd shortcuts' stamp: 'hlsf 12/30/2024 12:57:55'!
findMethodSourceContainingIt
"Open a browser on methods which contain the current selection in their source (case-sensitive full-text search of source). Slow!!"
| searchString selection scopeClass scopeClassName includeSubclasses includeSuperclasses labelList package |

searchString := StringRequestMorph
request: 'Enter search text:'
initialAnswer: self selectedString
orCancel: [^self].

scopeClass := self codeProvider selectedClass.
scopeClassName := scopeClass name asString.
includeSubclasses := false.
includeSuperclasses := false.

labelList := {
'This method'.
'All methods in image'. } asOrderedCollection.
(scopeClass notNil)
ifTrue: [
labelList addAll: {
'Class ', scopeClassName printString.
'Class ', scopeClassName printString, ' and subclasses'.
'Class ', scopeClassName printString, ', subclasses, and superclasses'.}.
package := self codeProvider isEditingMethod
ifTrue: [CodePackage packageOfMethod: self codeProvider currentCompiledMethod asMethodReference ifNone: []]
ifFalse: [CodePackage packageOfClass: scopeClass ifNone: []].
package ifNotNil: [labelList add: 'In my package: ', package packageName]].

selection := (SelectionMenu labelList: labelList selections: nil) startUpWithCaption: 'Search Scope'.

(selection = 0) ifTrue:[^self].
(selection = 1) "This method"
ifTrue:[^self find: searchString].
(selection = 2) "All methods in image"
ifTrue:[scopeClass := nil].
"(selection = 3) ifTrue:[]. ""Class only - nothing to do"
(selection = 4) "Class and subclasses"
ifTrue:[includeSubclasses := true].
(selection = 5) "Class, subclasses, and superclasses"
ifTrue:[
includeSubclasses := true.
includeSuperclasses := true].
(selection = 6) "In my package if any "
ifTrue: [^ Smalltalk browseMethodsWithSourceString: searchString in: package].
Smalltalk browseMethodsWithSourceString: searchString scopeClass: scopeClass includeSubclasses: includeSubclasses includeSuperclasses: includeSuperclasses! !

0 comments on commit 47311b9

Please sign in to comment.