FindFileApplication.st
author Claus Gittinger <cg@exept.de>
Mon, 15 Mar 2004 23:57:47 +0100
changeset 5723 dadcb827b659
parent 5677 4aea2e3fd1e3
child 5726 464df1753187
permissions -rw-r--r--
more search

"
 COPYRIGHT (c) 2002 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

"{ Package: 'stx:libtool' }"

AbstractFileApplicationNoteBookComponent subclass:#FindFileApplication
	instanceVariableNames:'searchDirectories searchDirectoryHolder notSearchForSameContents
		namePatternHolder ignoreCaseInName contentsPatternHolder
		ignoreCaseInContents notContentsPatternHolder
		ignoreCaseInNotContents sameContentsAsHolder findFileView
		searchResultTable resultList enableStop enableSearch stopSignal
		accessLock searchTask expanded searchRecursively selectionHolder
		hasListEntries targetApplication useLocate useGrep
		rememberInCache'
	classVariableNames:'ContentsInfoCache'
	poolDictionaries:''
	category:'Interface-Tools-File'
!

!FindFileApplication class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2002 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
! !

!FindFileApplication class methodsFor:'instance creation'!

open
    ^ self openInDirectory:(Filename currentDirectory)

    "
     self open
    "
!

openInDirectory:aFilename
    ^ self openOnFileName:(aFilename asFilename asAbsoluteFilename)

    "
     self openInDirectory:'/etc'
    "
!

openOnFileName:aFileName
    ^ self openOnFileName:aFileName for:nil
!

openOnFileName:aFileName for:aTargetApplicationOrNil

    | instance builder|

    builder := super open.
    instance := builder application.
    instance item:(DirectoryContentsBrowser itemClass fileName:aFileName).
    aTargetApplicationOrNil notNil ifTrue:[
        instance targetApplication:aTargetApplicationOrNil.
    ].
    ^ builder
! !

!FindFileApplication class methodsFor:'defaults'!

tabStringFor:aApplicationType

    ^ 'Find file in:'
! !

!FindFileApplication class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:FindFileApplication andSelector:#windowSpec
     FindFileApplication new openInterface:#windowSpec
     FindFileApplication open
    "

    <resource: #canvas>

    ^ 
     #(FullSpec
        name: windowSpec
        window: 
       (WindowSpec
          label: 'File Search'
          name: 'File Search'
          min: (Point 377 131)
          max: (Point 1280 1024)
          bounds: (Rectangle 0 0 729 512)
        )
        component: 
       (SpecCollection
          collection: (
           (MenuPanelSpec
              name: 'ToolBar1'
              layout: (LayoutFrame 0 0.0 0 0 0 1.0 32 0)
              level: 0
              menu: searchMenu
              textDefault: true
            )
           (ViewSpec
              name: 'Box1'
              layout: (LayoutFrame 0 0.0 32 0 0 1.0 156 0)
              component: 
             (SpecCollection
                collection: (
                 (LabelSpec
                    label: 'Directory:'
                    name: 'DirectoryLabel'
                    layout: (LayoutFrame 2 0 7 0 154 0 24 0)
                    translateLabel: true
                    adjust: right
                  )
                 (FilenameInputFieldSpec
                    name: 'DirectoryEntryField'
                    layout: (LayoutFrame 156 0 4 0 -315 1 24 0)
                    model: searchDirectoryHolder
                    immediateAccept: true
                    acceptOnPointerLeave: false
                  )
                 (CheckBoxSpec
                    label: 'Use ''locate'' Cmd'
                    name: 'UseLocateCheckBox'
                    layout: (LayoutFrame -300 1 5 0 -158 1 28 0)
                    visibilityChannel: canUseLocate
                    tabable: true
                    model: useLocate
                    translateLabel: true
                  )
                 (CheckBoxSpec
                    label: 'Recursive'
                    name: 'RecursiveSearchCheckBox'
                    layout: (LayoutFrame -160 1 5 0 -4 1 28 0)
                    tabable: true
                    model: searchRecursively
                    translateLabel: true
                  )
                 (LabelSpec
                    label: 'Search Files Named:'
                    name: 'FileNameLabel'
                    layout: (LayoutFrame 2 0 31 0 154 0 48 0)
                    translateLabel: true
                    adjust: right
                  )
                 (InputFieldSpec
                    name: 'FileNameEntryField'
                    layout: (LayoutFrame 156 0 28 0 -315 1 48 0)
                    tabable: true
                    model: namePatternHolder
                    formatString: ''
                    immediateAccept: true
                    acceptOnLeave: false
                    acceptOnPointerLeave: false
                  )
                 (CheckBoxSpec
                    label: 'Directories'
                    name: 'SearchDirectoriesCheckBox'
                    layout: (LayoutFrame -300 1 29 0 -158 1 52 0)
                    tabable: true
                    model: searchDirectories
                    translateLabel: true
                  )
                 (CheckBoxSpec
                    label: 'Ignore Case'
                    name: 'IgnoreCaseInNameCheckBox'
                    layout: (LayoutFrame -160 1 29 0 -4 1 52 0)
                    tabable: true
                    model: ignoreCaseInName
                    translateLabel: true
                  )
                 (LabelSpec
                    label: 'Containing:'
                    name: 'ContentsLabel'
                    layout: (LayoutFrame 2 0 55 0 154 0 72 0)
                    translateLabel: true
                    adjust: right
                  )
                 (InputFieldSpec
                    name: 'ContentsEntryField'
                    layout: (LayoutFrame 156 0 52 0 -315 1 72 0)
                    enableChannel: notSearchForSameContents
                    tabable: true
                    model: contentsPatternHolder
                    immediateAccept: true
                    acceptOnPointerLeave: false
                  )
                 (CheckBoxSpec
                    label: 'Use ''grep'' Cmd'
                    name: 'UseGrepCheckBox'
                    layout: (LayoutFrame -300 1 53 0 -158 1 76 0)
                    visibilityChannel: canUseGrep
                    tabable: true
                    model: useGrep
                    translateLabel: true
                  )
                 (CheckBoxSpec
                    label: 'Ignore Case'
                    name: 'IgnoreCaseInContentsCheckBox'
                    layout: (LayoutFrame -160 1 53 0 -4 1 76 0)
                    enableChannel: notSearchForSameContents
                    tabable: true
                    model: ignoreCaseInContents
                    translateLabel: true
                  )
                 (LabelSpec
                    label: 'Not Containing:'
                    name: 'NotContentsLabel'
                    layout: (LayoutFrame 2 0 79 0 154 0 96 0)
                    translateLabel: true
                    adjust: right
                  )
                 (InputFieldSpec
                    name: 'NotContentsEntryField'
                    layout: (LayoutFrame 156 0 76 0 -315 1 96 0)
                    enableChannel: notSearchForSameContents
                    tabable: true
                    model: notContentsPatternHolder
                    immediateAccept: true
                    acceptOnPointerLeave: false
                  )
                 (CheckBoxSpec
                    label: 'Ignore Case'
                    name: 'IgnoreCaseInNotContentsCheckBox'
                    layout: (LayoutFrame -160 1 77 0 -4 1 100 0)
                    enableChannel: notSearchForSameContents
                    tabable: true
                    model: ignoreCaseInNotContents
                    translateLabel: true
                  )
                 (LabelSpec
                    label: 'Same Contents As:'
                    name: 'SameContentsAsLabel'
                    layout: (LayoutFrame 2 0 103 0 154 0 120 0)
                    translateLabel: true
                    adjust: right
                  )
                 (InputFieldSpec
                    name: 'SameContentsAsEntryField'
                    layout: (LayoutFrame 156 0 100 0 -315 1 120 0)
                    enableChannel: notSearchForSameContents
                    tabable: true
                    model: sameContentsAsHolder
                    formatString: ''
                    immediateAccept: true
                    acceptOnPointerLeave: false
                  )
                 (CheckBoxSpec
                    label: 'Cache Info'
                    name: 'RememberInCacheCheckBox'
                    layout: (LayoutFrame -300 1 101 0 -158 1 124 0)
                    visibilityChannel: canUseGrep
                    tabable: true
                    model: rememberInCache
                    translateLabel: true
                  )
                 )
               
              )
            )
           (SequenceViewSpec
              name: 'List1'
              layout: (LayoutFrame 0 0.0 156 0 0 1.0 0 1)
              model: selectionHolder
              menu: menu
              hasHorizontalScrollBar: true
              hasVerticalScrollBar: true
              isMultiSelect: true
              doubleClickSelector: fileDoubleClick:
              useIndex: true
              sequenceList: resultList
            )
           (ProgressIndicatorSpec
              name: 'ProgressIndicator1'
              layout: (LayoutFrame 125 0 11 0 231 0 21 0)
              visibilityChannel: enableStop
              backgroundColor: (Color 0.0 66.9993 66.9993)
              showPercentage: false
              isActivityIndicator: true
            )
           )
         
        )
      )
! !

!FindFileApplication class methodsFor:'menu specs'!

menu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:FindFileApplication andSelector:#menu
     (Menu new fromLiteralArrayEncoding:(FindFileApplication menu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #label: 'Select in Browser'
            #translateLabel: true
            #isVisible: #isEmbeddedApplication
            #value: #selectInBrowser
            #enabled: #hasOneFileSelected
          )
         #(#MenuItem
            #label: 'Copy Selected Files'
            #translateLabel: true
            #value: #copySelectedFiles
            #enabled: #hasSelectionInResultList
          )
         #(#MenuItem
            #label: 'Open in New File Browser'
            #translateLabel: true
            #value: #openInNewBrowser
            #enabled: #hasOneFileSelected
          )
         #(#MenuItem
            #label: 'Remove selected Files'
            #translateLabel: true
            #value: #removeFromList
            #enabled: #hasSelection
          )
         #(#MenuItem
            #label: 'Remove all Files'
            #translateLabel: true
            #value: #removeAllFromList
            #enabled: #hasListEntries
          )
         )
        nil
        nil
      )
!

searchMenu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:FindFileApplication andSelector:#searchMenu
     (Menu new fromLiteralArrayEncoding:(FindFileApplication searchMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #label: 'Search'
            #translateLabel: true
            #isButton: true
            #value: #doSearch
            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #search20x20Icon)
          )
         #(#MenuItem
            #label: 'Stop'
            #translateLabel: true
            #isButton: true
            #value: #stop
            #enabled: #enableStop
            #labelImage: #(#ResourceRetriever #ToolbarIconLibrary #stop22x22Icon)
          )
         #(#MenuItem
            #label: 'Clean Up'
            #translateLabel: true
            #isButton: true
            #value: #removeAllFromList
            #enabled: #hasListEntries
            #labelImage: #(#ResourceRetriever #Icon #deleteIcon)
          )
         #(#MenuItem
            #label: 'Close'
            #translateLabel: true
            #isButton: true
            #startGroup: #right
            #value: #doClose
            #labelImage: #(#ResourceRetriever #AbstractFileBrowser #closeIcon)
          )
         )
        nil
        nil
      )
! !

!FindFileApplication class methodsFor:'tableColumns specs'!

searchResultTable
    "This resource specification was automatically generated
     by the DataSetBuilder of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the DataSetBuilder may not be able to read the specification."

    "
     DataSetBuilder new openOnClass:FindFileApplication andSelector:#searchResultTable
    "

    <resource: #tableColumns>

    ^#(
      #(#DataSetColumnSpec
         #label: 'Filename'
         #id: 'FileName'
         #labelButtonType: #Button
         #model: #fileName
         #showRowSeparator: false
         #showColSeparator: false
       )
      )
    
! !

!FindFileApplication methodsFor:'accessing'!

accessLock
    "return the value of the instance variable 'accessLock' (automatically generated)"

    accessLock isNil ifTrue:[
        accessLock := Semaphore forMutualExclusion name:'accessLock'.
    ].
    ^ accessLock
!

stopSignal

    stopSignal isNil ifTrue:[
        stopSignal := Signal new.
    ].
    ^ stopSignal
!

targetApplication:something
    "set the value of the instance variable 'targetApplication' (automatically generated)"

    targetApplication := something.
! !

!FindFileApplication methodsFor:'actions'!

changeInformationTo:aString

    self changeInformationTo:aString toTab:false
!

changeInformationTo:aString toTab:aBoolean
    masterApplication isNil ifTrue:[
        findFileView label:aString
    ] ifFalse:[
        aBoolean ifTrue:[
            masterApplication tabStringChangeTo:aString for:self
        ]
    ].
!

copySelectedFiles
    |sel list stream|

    sel := self selectionHolder value.
    list := self resultList.
    (sel notNil and:[sel notEmpty]) ifTrue:[
        stream := WriteStream on:''.
        sel do:[: key |
            stream nextPutAll:(list at:key).
            stream cr.
        ].
        self window setTextSelection:stream contents.
        stream close.
    ].
!

doSearch

    | namePattern namePatterns contentsPattern notContentsPattern dir fileToCompareAgainst|

"/    self changeExtentToSeeSearchResult.

    dir := self searchDirectoryHolder value.
    dir isNil ifTrue:[
        Dialog warn:'Missing directory name'.
        ^ self.
    ].
    dir asFilename exists not ifTrue:[
        Dialog warn:('No such directory: %1' bindWith:dir asString allBold).
        ^ self.
    ].
    
    searchTask notNil ifTrue:[
        (Dialog 
            confirm:(resources string:'There is already another find-file task running !!') withCRs
            yesLabel:(resources at:'Stop other Task and Proceed')
            noLabel:(resources at:'Cancel'))
        ifFalse:[^ self].
        self stop.
    ].

    namePattern := self namePatternHolder value.
    namePattern size == 0 ifTrue:[
        namePatterns := nil
    ] ifFalse:[
        ignoreCaseInName value ifTrue:[
            namePattern := namePattern asLowercase
        ].
        namePatterns := namePattern asCollectionOfSubstringsSeparatedBy:$;
    ].
    contentsPattern := self contentsPatternHolder value.
    contentsPattern size == 0 ifTrue:[
        contentsPattern := nil
    ] ifFalse:[
        self ignoreCaseInContents value ifTrue:[
            contentsPattern := contentsPattern asLowercase
        ]
    ].
    notContentsPattern := self notContentsPatternHolder value.
    notContentsPattern size == 0 ifTrue:[
        notContentsPattern := nil
    ] ifFalse:[
        self ignoreCaseInNotContents value ifTrue:[
            notContentsPattern := notContentsPattern asLowercase
        ]
    ].
    fileToCompareAgainst := sameContentsAsHolder value withoutSeparators.
    fileToCompareAgainst isEmpty ifTrue:[
        fileToCompareAgainst := nil.
    ] ifFalse:[
        fileToCompareAgainst := fileToCompareAgainst asFilename
    ].

    searchTask := Process for:[
        |message t|

        [    
            (self stopSignal) catch:[
                self enableStop value:true.
                self resultList removeAll.
                self changeInformationTo:'Find File ' , '- searching ' toTab:true.
                self notify:'searching...'.
                t := Time millisecondsToRun:[
                    self 
                        doFindFileNamed:namePatterns
                        directories:(self searchDirectories value)
                        ignoreCase:(self ignoreCaseInName value)
                        containingString:contentsPattern
                        ignoreCaseInContents:(self ignoreCaseInContents value)
                        notContainingString:notContentsPattern
                        ignoreCaseInNotContents:(self ignoreCaseInNotContents value)
                        sameContentsAsFile:fileToCompareAgainst  
                        sameContentsAs:nil 
                        in:(self searchDirectoryHolder value).
                ].
                t > 100 ifTrue:[
                    t := ((t / 1000) asFixedPoint:2) printString , ' s'
                ] ifFalse:[
                    t := t printString , ' ms'
                ].
                message := 'Found %1 file%2 in %3' bindWith:(resultList size) with:(resultList size == 1 ifTrue:'' ifFalse:'s') with:t.
                self enableStop value:false.
                self enableSearch value:true.
                self changeInformationTo:'Find File ' , '- done.' toTab:true.
            ].
        ] valueNowOrOnUnwindDo:[
            searchTask := nil.
            self enableStop value:false.
            self notify:message.
        ]
    ] priority:(Processor systemBackgroundPriority).

    searchTask name:('FindFile[', self searchDirectoryHolder value asFilename baseName, ']').
    searchTask resume.
!

openInNewBrowser
    |sel|

    sel := self selectionHolder value.
    (sel notNil and:[sel notEmpty]) ifTrue:[
        FileBrowserV2 openOn:(self resultList at:sel first) asFilename
    ].
!

removeAllFromList

    self resultList removeAll.
!

removeFromList
    |sel list|

    sel := self selectionHolder value.
    list := self resultList.
    (sel notNil and:[sel notEmpty]) ifTrue:[
        sel reverseDo:[: key |
            list removeAtIndex:key
        ]
    ].
!

selectInBrowser
    |sel entry application|

    sel := self selectionHolder value.
    (sel notNil and:[sel notEmpty]) ifTrue:[
        entry := self resultList at:sel first.
        entry asFilename exists ifFalse:[ ^ self].
        application := targetApplication ? self masterApplication.
        application notNil ifTrue:[
            application gotoFile:(entry asFilename).
        ].
    ].
!

stop

    searchTask notNil ifTrue:[
        self accessLock critical:[
            searchTask interruptWith:[stopSignal raiseRequest].
        ]
    ].
    self enableStop value:false.
    self enableSearch value:true.
    self changeInformationTo:'Find File ' , '- search stopped' toTab:true.
!

stopSearchTask
    |task|

    (task := searchTask) notNil ifTrue:[
        searchTask := nil.

        Object errorSignal handle:[:ex|
            Dialog warn:ex description.
        ]do:[
            task isDead ifFalse:[
                task terminateWithAllSubprocessesInGroup.
                task waitUntilTerminated.
            ]
        ]
    ].
! !

!FindFileApplication methodsFor:'aspects'!

canUseGrep
    "grep command is much faster, but:
        - not under MSDOS
    "

    ^ OperatingSystem isUNIXlike and:[ OperatingSystem canExecuteCommand:'egrep' ]
!

canUseLocate
    "locate command is much faster, but:
        - only if searching recursively,
        - no case ignore
        - no contents matching
    "

    ^ OperatingSystem isUNIXlike and:[ OperatingSystem canExecuteCommand:'locate' ]
!

contentsPatternHolder

    contentsPatternHolder isNil ifTrue:[
        contentsPatternHolder := nil asValue.
    ].
    ^ contentsPatternHolder.
!

enableSearch

    enableSearch isNil ifTrue:[
        enableSearch := true asValue.
    ].
    ^ enableSearch.
!

enableStop

    enableStop isNil ifTrue:[
        enableStop := true asValue.
    ].
    ^ enableStop.
!

hasListEntries

    hasListEntries isNil ifTrue:[
        hasListEntries := false asValue.
    ].
    ^ hasListEntries.
!

ignoreCaseInContents
    ignoreCaseInContents isNil ifTrue:[
        ignoreCaseInContents := false asValue.
    ].
    ^ ignoreCaseInContents.
!

ignoreCaseInName

    ignoreCaseInName isNil ifTrue:[
        ignoreCaseInName := false asValue.
    ].
    ^ ignoreCaseInName.
!

ignoreCaseInNotContents
    ignoreCaseInNotContents isNil ifTrue:[
        ignoreCaseInNotContents := false asValue.
    ].
    ^ ignoreCaseInNotContents.
!

namePatternHolder

    namePatternHolder isNil ifTrue:[
        namePatternHolder := '*' asValue.
    ].
    ^ namePatternHolder.
!

notContentsPatternHolder

    notContentsPatternHolder isNil ifTrue:[
        notContentsPatternHolder := nil asValue.
    ].
    ^ notContentsPatternHolder.
!

notSearchForSameContents

    notSearchForSameContents isNil ifTrue:[
        notSearchForSameContents := true asValue.
    ].
    ^ notSearchForSameContents.
!

rememberInCache
    rememberInCache isNil ifTrue:[
        rememberInCache := false asValue.
    ].
    ^ rememberInCache.
!

resultList

    resultList isNil ifTrue:[
        resultList := List new.
        resultList addDependent:self.
    ].
    ^ resultList.
!

sameContentsAsHolder
    |sel|

    sameContentsAsHolder isNil ifTrue:[
        sameContentsAsHolder := ValueHolder new.
        masterApplication notNil ifTrue:[
            sel := masterApplication currentSelectedFiles.
            sel size > 0 ifTrue:[
                sameContentsAsHolder value:(sel first asFilename pathName).
            ].
        ].
    ].
    ^ sameContentsAsHolder.
!

searchDirectories
    searchDirectories isNil ifTrue:[
        searchDirectories := false asValue.
    ].
    ^ searchDirectories.
!

searchDirectoryHolder

    searchDirectoryHolder isNil ifTrue:[
        searchDirectoryHolder := ValueHolder new.
    ].
    ^ searchDirectoryHolder.
!

searchRecursively

    searchRecursively isNil ifTrue:[
        searchRecursively := true asValue.
    ].
    ^ searchRecursively.
!

searchResultTable

    searchResultTable isNil ifTrue:[
        searchResultTable := self class searchResultTable asValue.
    ].
    ^ searchResultTable.
!

selectionHolder

    selectionHolder isNil ifTrue:[
        selectionHolder := ValueHolder new.
        selectionHolder addDependent:self.
    ].
    ^ selectionHolder
!

useGrep
    useGrep isNil ifTrue:[
        useGrep := false asValue.
    ].
    ^ useGrep.
!

useLocate
    useLocate isNil ifTrue:[
        useLocate := false asValue.
    ].
    ^ useLocate.
! !

!FindFileApplication methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    changedObject == self resultList ifTrue:[
        self hasListEntries value:(changedObject notEmpty).
        ^ self
    ].
    changedObject == self selectionHolder ifTrue:[
        self selectInBrowser.
        ^ self
    ].
    super update:something with:aParameter from:changedObject
! !

!FindFileApplication methodsFor:'event handling'!

fileDoubleClick:entries
    |file fn app openedAppl contentsPattern|

    file := self resultList at:entries first.
    fn := file asFilename.
    fn exists ifFalse:[
        Dialog warn:('File %1 does not (no longer ?) exist.' bindWith:file allBold).
        ^ self
    ].

    app := targetApplication ? self masterApplication.
    file asFilename isDirectory ifTrue:[
        app gotoFile:(file asFilename).
        ^ self.
    ].
    app notNil ifTrue:[
        openedAppl := app openApplForFile:file.
        (openedAppl notNil and:[openedAppl isTextEditor]) ifTrue:[
            contentsPattern := self contentsPatternHolder value.
            (contentsPattern notNil and:[ contentsPattern notEmpty and:[contentsPattern ~= '*']]) ifTrue:[
                openedAppl searchForPattern:contentsPattern ignoreCase:(self ignoreCaseInContents value).
            ]        
        ].
    ] ifFalse:[
        self openInNewBrowser.
    ]
!

processEvent:anEvent
    "filter keyboard events.
     Return true, if I have eaten the event"

    |focusView key rawKey|

    anEvent isKeyPressEvent ifTrue:[
        focusView := anEvent targetView.
        key := anEvent key.
        rawKey := anEvent rawKey.

        (focusView isSameOrComponentOf:self window) ifTrue:[
            (key == #Return) ifTrue:[
                (focusView name ~= 'selectionInListView') ifTrue:[
                    self doSearch.
                ] ifFalse:[
                    self hasOneFileSelected ifTrue:[
                        self fileDoubleClick:(self selectionHolder value)
"/                        self isEmbeddedApplication ifTrue:[
"/                            self selectInBrowser.
"/                        ] ifFalse:[
"/                            self openInNewBrowser.
"/                        ]
                    ]
                ].
                ^ true
            ].
        ]
    ].
    ^ false
! !

!FindFileApplication methodsFor:'private'!

changeExtentToSeeSearchResult
    
    | extent window|

    expanded isNil ifTrue:[
        window := self builder window.
        window ifNotNil:[
            window := window topView.
            extent := window extent.
            window extent:((extent x) @ (extent y + 300)).
            expanded := true.
            window containerChangedSize.
        ].
    ].
! !

!FindFileApplication methodsFor:'private - searching'!

doFindFileNamed:namePatterns directories:searchDirectories ignoreCase:ignCaseInName 
    containingString:contentsStringArg ignoreCaseInContents:ignCaseInContents 
    notContainingString:notContentsStringArg ignoreCaseInNotContents:ignCaseInNotContents 
    sameContentsAsFile:filenameToCompareContentsOrNil sameContentsAs:bytesToCompareContentsOrNil in:aDirectory

    |dir nameMatches lines contentsToCompare list inStream
     doesFileMatch contentsString notContentsString check checkNot 
     grepCommand nameMatch fileSizeSearchFor fileSearchedFor fileMD5SearchedFor remember
     cache|

    contentsString := contentsStringArg.
    ignCaseInContents ifTrue:[ contentsString := contentsString asLowercase ].
    notContentsString := notContentsStringArg.
    ignCaseInNotContents ifTrue:[ notContentsString := notContentsString asLowercase ].    

    filenameToCompareContentsOrNil notNil ifTrue:[
        fileSizeSearchFor := filenameToCompareContentsOrNil fileSize.
        fileSearchedFor := filenameToCompareContentsOrNil pathName.
        fileMD5SearchedFor := MD5Stream hashValueOfFile:filenameToCompareContentsOrNil.
        remember := self rememberInCache value.
        remember ifTrue:[
            ContentsInfoCache isNil ifTrue:[
                ContentsInfoCache := Dictionary new.
            ]
        ].
    ].
    cache := ContentsInfoCache.

    dir := aDirectory asFilename.
    self changeInformationTo:'Find File ' , '- searching .' , ((dir name) copyFrom:(self searchDirectoryHolder value asString size + 1)) toTab:false.

    list := self resultList.

    filenameToCompareContentsOrNil notNil ifTrue:[
        doesFileMatch := 
            [:f |
                |contentsMatches fileMD5 fileName fileSize cacheLine|

                "/ contents compare ...
                contentsMatches := false.
                fileName := f pathName.
                fileName ~= fileSearchedFor ifTrue:[
                    cacheLine := cache at:fileName ifAbsent:nil.
                    cacheLine notNil ifTrue:[
                        fileSize := cacheLine at:1.    
                        fileMD5 := cacheLine at:2.    
                    ].
                    fileSize isNil ifTrue:[
                        fileSize := f fileSize.
                    ].
                    remember ifTrue:[
                        cacheLine := cache at:fileName ifAbsentPut:[Array new:2].
                        cacheLine at:1 put:fileSize.
                    ].
                    fileSize == fileSizeSearchFor ifTrue:[
                        fileMD5 isNil ifTrue:[
                            fileMD5 := MD5Stream hashValueOfFile:f.
                            remember ifTrue:[
                                cacheLine at:2 put:fileMD5
                            ].
                        ].
                        contentsMatches := (fileMD5 = fileMD5SearchedFor).
"/                        contentsToCompare isNil ifTrue:[
"/                            filenameToCompareContentsOrNil fileSize < (512*1024) ifTrue:[
"/                                contentsToCompare := filenameToCompareContentsOrNil binaryContentsOfEntireFile
"/                            ]
"/                        ].
"/                        contentsToCompare isNil ifTrue:[
"/                            "/ too large - compare block-wise ...
"/                            contentsMatches := (filenameToCompareContentsOrNil sameContentsAs:f).
"/                        ] ifFalse:[
"/                            contentsMatches := contentsToCompare = (f binaryContentsOfEntireFile).
"/                        ]
                    ].
                ] ifFalse:[
                    f isSymbolicLink ifTrue:[
                        list add: (f name , ' is a symbolic link to ' , f pathName).
                    ]
                ].
                contentsMatches
            ].
    ] ifFalse:[
        (contentsString isNil and:[notContentsString isNil]) ifTrue:[
            doesFileMatch := [:f | true].
        ] ifFalse:[
            (self canUseGrep 
            and:[self useGrep value]) ifTrue:[
                (ignCaseInContents not and:[ignCaseInNotContents not]) ifTrue:[
                    contentsString notNil ifTrue:[
                        notContentsString notNil ifTrue:[
                            grepCommand := '(grep "',contentsString,'" %1) && (grep -v "',notContentsString,'" %1)'.
                        ] ifFalse:[
                            grepCommand := 'grep "' , contentsString , '" %1'.
                        ].
                    ] ifFalse:[
                        grepCommand := 'grep -v "' , notContentsString , '" %1'.
                    ].
                    doesFileMatch := [:f | |cmd ret|
                                            cmd := grepCommand bindWith:f pathName.
                                            ret := OperatingSystem executeCommand:cmd.
                                            ret
                                     ].
                ]
            ].

            doesFileMatch isNil ifTrue:[
                contentsString notNil ifTrue:[
                    ignCaseInContents ifTrue:[
                        check := [:l | l asLowercase includesString:contentsString]
                    ] ifFalse:[
                        check := [:l | l includesString:contentsString]
                    ].
                ].
                notContentsString notNil ifTrue:[
                    ignCaseInNotContents ifTrue:[
                        checkNot := [:l | l asLowercase includesString:notContentsString]
                    ] ifFalse:[
                        checkNot := [:l | l includesString:notContentsString]
                    ].
                ].

                doesFileMatch := 
                    [:f |
                        |contentsMatches|

                        "/ string search ...
                        contentsMatches := true.
                        (f exists and:[f isReadable]) ifFalse:[
                            list add: (('*** ' , f pathName , ' skipped - unreadable or bad symbolic link ***') asText colorizeAllWith:(Color red darkened)).
                        ] ifTrue:[
                            f fileSize > (4024*1024) ifTrue:[
                                list add: (('*** ' , f pathName , ' skipped - too large ***') asText colorizeAllWith:(Color red darkened)).
                            ] ifFalse:[
                                Stream lineTooLongErrorSignal handle:[:ex |
                                    |cont|

                                    "/ this typically happens, when a binary file is read linewise ...
                                    cont := f readStream binary contentsOfEntireFile asString.
                                    check notNil ifTrue:[
                                        checkNot isNil ifTrue:[
                                            contentsMatches := check value:cont
                                        ] ifFalse:[
                                            contentsMatches := (check value:cont) and:[(checkNot value:cont) not].
                                        ]
                                    ] ifFalse:[
                                        contentsMatches := (checkNot value:cont) not.
                                    ].
                                ] do:[    
                                    lines := f contents ? #().
                                    check notNil ifTrue:[
                                        checkNot isNil ifTrue:[
                                            contentsMatches := (lines contains:check).
                                        ] ifFalse:[
                                            contentsMatches := (lines contains:check) and:[(lines contains:checkNot) not]
                                        ]
                                    ] ifFalse:[
                                        contentsMatches := (lines contains:checkNot) not.
                                    ].
                                ].
                            ].
                        ].
                        contentsMatches
                    ].
            ].
        ].
    ].


    (self canUseLocate 
    and:[self useLocate value
    and:[searchDirectories not]])
    ifTrue:[
        [
            |cmd line f|

            cmd := 'locate '.
            ignCaseInName ifTrue:[
                cmd := cmd , '--ignore-case '
            ].

            cmd := cmd , ((namePatterns collect:[:nm | dir asFilename asAbsoluteFilename constructString:nm])
                            asStringCollection asStringWith:Character space).
            inStream := PipeStream readingFrom:cmd inDirectory:dir.
            [inStream atEnd] whileFalse:[
                line := inStream nextLine.

                f := line asFilename.
                (doesFileMatch value:f) ifTrue:[
                    list add:line.
                ]
            ].
        ] ensure:[
            inStream notNil ifTrue:[inStream close].
        ].
        ^ self.
    ].
    
    bytesToCompareContentsOrNil notNil ifTrue:[
        contentsToCompare := bytesToCompareContentsOrNil
    ].

    namePatterns isNil ifTrue:[
        nameMatch := [:fn | true]
    ] ifFalse:[
        ignCaseInName ifTrue:[
            nameMatch := [:fn |
                nameMatches := namePatterns contains:[:aPattern | aPattern match:(fn asLowercase)]
            ].
        ] ifFalse:[
            nameMatch := [:fn |
                nameMatches := namePatterns contains:[:aPattern | aPattern match:fn]
            ].
        ].
    ].

    self 
        doFindFileNamed:namePatterns 
        directories:searchDirectories 
        nameMatch:nameMatch 
        contentsMatch:doesFileMatch 
        in:dir.
!

doFindFileNamed:namePatterns directories:searchDirectories nameMatch:nameMatch contentsMatch:doesFileMatch in:aDirectory
    |dir subDirs list directoryContents|

    dir := aDirectory asFilename.
    self changeInformationTo:'Find File ' , '- searching .' , ((dir name) copyFrom:(self searchDirectoryHolder value asString size + 1)) toTab:false.

    list := self resultList.

    subDirs := OrderedCollection new.

    [
        directoryContents := dir directoryContents.
    ] on:FileStream openErrorSignal do:[:ex|
        list add:((ex parameter pathName , ' -> ' , ex description) asText colorizeAllWith:Color red darkened).
        "/        self warn:('Cannot access %1\(%2)'
        "/                        bindWith:ex parameter printString
        "/                        with:ex description) withCRs.
        ^ self
    ].

    directoryContents sort do:[:fn |
        |f isDirectory|

        f := dir construct:fn.

        isDirectory := f isDirectory.
        isDirectory ifTrue:[
            f isSymbolicLink ifFalse:[
                subDirs add:f
            ]
        ].
        (searchDirectories or:[isDirectory not]) ifTrue:[
            (nameMatch value:fn) ifTrue:[
                (isDirectory or:[ doesFileMatch value:f ])
                ifTrue:[
                    list add:(f asString).
                ]
            ]
        ]
    ].

    self searchRecursively value ifTrue:[
        subDirs do:[:dir |
            self
                doFindFileNamed:namePatterns 
                directories:searchDirectories 
                nameMatch:nameMatch 
                contentsMatch:doesFileMatch 
                in:dir
        ].
    ]
! !

!FindFileApplication methodsFor:'queries'!

getTabStringEnd

" get the tab string from the application list on the class side "

    ^ self fileName directory asString
!

hasOneFileSelected
    | sel |
    sel := self selectionHolder value.
    ^  (sel notNil and:[sel notEmpty and:[sel size = 1]])
!

hasSelectionInResultList
    | sel |
    sel := self selectionHolder value.
    ^  (sel notNil and:[sel notEmpty])
! !

!FindFileApplication methodsFor:'startup & release'!

item:anItem

    |file newPattern|

    super item:anItem.

    file := self fileName.
    self searchDirectoryHolder value:(self getDirWithoutFileName:file).

    file isDirectory ifTrue:[
        newPattern := '*'.
    ] ifFalse:[
        newPattern := '*.', anItem suffix.
    ].
    self namePatternHolder value:newPattern.
    self enableStop value:false.
    self enableSearch value:true.
    ^ true.
!

postOpenWith:aBuilder

    self masterApplication isNil ifTrue:[
        self masterApplication:nil.
    ].
    findFileView := aBuilder window.
    self windowGroup addPreEventHook:self.
    ^ super postOpenWith:aBuilder.
!

release

    self stopSearchTask.
    ContentsInfoCache := nil.
    ^ super release
! !

!FindFileApplication class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/FindFileApplication.st,v 1.26 2004-03-15 22:57:47 cg Exp $'
! !