FindFileApplication.st
author Claus Gittinger <cg@exept.de>
Sat, 12 Oct 2002 02:48:29 +0200
changeset 3980 3f8311a42ca7
parent 3937 80d958725879
child 3983 dd593a7482fa
permissions -rw-r--r--
menus reorganized

"{ Package: 'stx:libtool' }"

AbstractFileApplicationNoteBookComponent subclass:#FindFileApplication
	instanceVariableNames:'contentsPatternHolder ignoreCaseInName notSearchForSameContents
		namePatternHolder ignoreCaseInContents searchDirectoryHolder
		findFileView searchResultTable resultList enableStop enableSearch
		stopSignal accessLock searchTask expanded searchRecursively
		selectionHolder hasListEntries'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Tools-File'
!


!FindFileApplication class methodsFor:'instance creation'!

open

    ^ self openOnFileName:(Filename currentDirectory asAbsoluteFilename)
!

openOnFileName:aFileName

    | instance builder|

    builder := super open.
    instance := builder application.
    instance item:(DirectoryContentsBrowser itemClass with:aFileName).
    ^ builder
!

openOnFileName:aFileName for:aTargetApplication

    | instance builder|

    builder := super open.
    instance := builder application.
    instance item:(DirectoryContentsBrowser itemClass with:aFileName).
    ^ 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 16 42 681 374)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#MenuPanelSpec
              #name: 'ToolBar1'
              #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 32 0)
              #menu: #searchMenu
              #textDefault: true
            )
           #(#ViewSpec
              #name: 'Box1'
              #layout: #(#LayoutFrame 0 0.0 32 0 0 1.0 126 0)
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#LabelSpec
                    #label: 'Search files named:'
                    #name: 'Label1'
                    #layout: #(#LayoutFrame 3 0 7 0 148 0 24 0)
                    #translateLabel: true
                    #adjust: #left
                  )
                 #(#InputFieldSpec
                    #name: 'EntryField1'
                    #layout: #(#LayoutFrame 140 0 4 0 -115 1 24 0)
                    #tabable: true
                    #model: #namePatternHolder
                    #immediateAccept: true
                    #acceptOnLeave: false
                    #acceptOnPointerLeave: false
                  )
                 #(#CheckBoxSpec
                    #label: 'Ignore case'
                    #name: 'CheckBox1'
                    #layout: #(#LayoutFrame -97 1 5 0 1 1 28 0)
                    #tabable: true
                    #model: #ignoreCaseInName
                    #translateLabel: true
                  )
                 #(#LabelSpec
                    #label: 'Containing the string:'
                    #name: 'Label2'
                    #layout: #(#LayoutFrame 4 0 31 0 136 0 48 0)
                    #translateLabel: true
                    #adjust: #left
                  )
                 #(#InputFieldSpec
                    #name: 'EntryField2'
                    #layout: #(#LayoutFrame 140 0 29 0 -115 1 49 0)
                    #enableChannel: #notSearchForSameContents
                    #tabable: true
                    #model: #contentsPatternHolder
                    #immediateAccept: true
                    #acceptOnPointerLeave: false
                  )
                 #(#CheckBoxSpec
                    #label: 'Ignore case'
                    #name: 'CheckBox2'
                    #layout: #(#LayoutFrame -97 1 30 0 4 1 50 0)
                    #enableChannel: #notSearchForSameContents
                    #tabable: true
                    #model: #ignoreCaseInContents
                    #translateLabel: true
                  )
                 #(#LabelSpec
                    #label: 'Directory:'
                    #name: 'Directory'
                    #layout: #(#LayoutFrame 4 0 57 0 136 0 74 0)
                    #translateLabel: true
                    #adjust: #left
                  )
                 #(#FilenameInputFieldSpec
                    #name: 'FilenameEntryField1'
                    #layout: #(#LayoutFrame 140 0 54 0 -115 1 74 0)
                    #model: #searchDirectoryHolder
                    #immediateAccept: true
                    #acceptOnPointerLeave: false
                  )
                 #(#CheckBoxSpec
                    #label: 'Recursively'
                    #name: 'CheckBox3'
                    #layout: #(#LayoutFrame -97 1 54 0 1 1 77 0)
                    #tabable: true
                    #model: #searchRecursively
                    #translateLabel: true
                  )
                 )
               
              )
            )
           #(#SequenceViewSpec
              #name: 'List1'
              #layout: #(#LayoutFrame 0 0.0 117 0 0 1.0 0 1)
              #model: #selectionHolder
              #menu: #menu
              #hasHorizontalScrollBar: true
              #hasVerticalScrollBar: true
              #isMultiSelect: true
              #doubleClickSelector: #selectInBrowser
              #useIndex: true
              #sequenceList: #resultList
            )
           )
         
        )
      )
! !

!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
! !

!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 dir|

"/    self changeExtentToSeeSearchResult.

    dir := self searchDirectoryHolder value.
    dir isNil ifTrue:[
        Dialog warn:'please type in a Directory first'.
        ^ self.
    ].
    dir asFilename exists not ifTrue:[
        Dialog warn:dir, 'not exists'.
        ^ self.
    ].
    
    searchTask notNil ifTrue:[
        (Dialog 
            confirm:(resources string:'there is already a find file running !!') withCRs
            yesLabel:(resources at:'Stop and continue')
            noLabel:(resources at:'Cancel'))
        ifFalse:[^ self].
        self stop.
    ].
    self enableStop value:true.

    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
        ]
    ].
    searchTask := Process for:[
        [            
            (self stopSignal) catch:[
                self resultList removeAll.
                self changeInformationTo:'Find File ' , '- search started ' toTab:true.
                self 
                    doFindFileNamed:namePatterns
                    ignoreCase:self ignoreCaseInName value
                    containingString:contentsPattern
                    ignoreCaseInContents:self ignoreCaseInContents value
                    sameContentsAsFile:nil 
                    sameContentsAs:nil 
                    in:self searchDirectoryHolder value.
                self enableStop value:false.
                self enableSearch value:true.
                self changeInformationTo:'Find File ' , '- search finished' toTab:true.
            ].
        ] valueNowOrOnUnwindDo:[
            searchTask := nil.
            self enableStop value:false.
        ]
    ] 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.
    ].
    application := 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'!

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.
!

namePatternHolder

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

notSearchForSameContents

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

resultList

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

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
! !

!FindFileApplication methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    "Invoked when an object that I depend upon sends a change notification."

    "stub code automatically generated - please change as required"

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

!FindFileApplication methodsFor:'event handling'!

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 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 - file stuff'!

doFindFileNamed:namePatterns ignoreCase:ignCaseInName containingString:contentsString ignoreCaseInContents:ignCaseInString sameContentsAsFile:filenameToCompareContentsOrNil sameContentsAs:bytesToCompareContentsOrNil in:aDirectory

    |dir subDirs nameMatches contentsMatches lines contentsToCompare list|

    list := self resultList.
    bytesToCompareContentsOrNil notNil ifTrue:[
        contentsToCompare := bytesToCompareContentsOrNil
    ].

    subDirs := OrderedCollection new.

    dir := aDirectory asFilename.
    self changeInformationTo:'Find File ' , '- searching .' , ((dir name) copyFrom:(self searchDirectoryHolder value asString size + 1)) toTab:false.
    (dir directoryContents ? #()) sort do:[:fn |
        |f|

        f := dir construct:fn.
        f isDirectory ifTrue:[
            f isSymbolicLink ifFalse:[
                subDirs add:f
            ]
        ] ifFalse:[
            (nameMatches := namePatterns isNil) ifFalse:[
                ignCaseInName ifTrue:[
                    nameMatches := namePatterns contains:[:aPattern | aPattern match:(fn asLowercase)]
                ] ifFalse:[
                    nameMatches := namePatterns contains:[:aPattern | aPattern  match:fn]
                ]
            ].
            nameMatches ifTrue:[
                filenameToCompareContentsOrNil notNil ifTrue:[
                    "/ contents compare ...
                    contentsMatches := false.
                    f pathName ~= filenameToCompareContentsOrNil pathName ifTrue:[
                        f fileSize == filenameToCompareContentsOrNil fileSize ifTrue:[
                            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).
                        ]
                    ]
                ] ifFalse:[
                    "/ string search ...
                    (contentsMatches := contentsString isNil) ifFalse:[
                        (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.
                                    ignCaseInString ifTrue:[
                                        contentsMatches := cont asLowercase includesString:contentsString asLowercase
                                    ] ifFalse:[
                                        contentsMatches := cont includesString:contentsString
                                    ].
                                ] do:[    
                                    lines := f contents ? #().
                                    ignCaseInString ifTrue:[
                                        contentsMatches := (lines findFirst:[:l | l asLowercase includesString:contentsString asLowercase]) ~~ 0
                                    ] ifFalse:[
                                        contentsMatches := (lines findFirst:[:l | l includesString:contentsString]) ~~ 0
                                    ].
                                ].
                            ].
                        ].
                    ].
                ].
                contentsMatches ifTrue:[
                    list add: f asString.
                ]
            ]
        ]
    ].

    self searchRecursively value ifTrue:[
        subDirs do:[:dir |
            self
                doFindFileNamed:namePatterns 
                ignoreCase:ignCaseInName 
                containingString:contentsString 
                ignoreCaseInContents:ignCaseInString 
                sameContentsAsFile:filenameToCompareContentsOrNil 
                sameContentsAs:contentsToCompare
                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'!

initialize:aFile

    self searchDirectoryHolder value:(self getDirWithoutFileName:aFile).
    aFile isDirectory ifTrue:[
        self namePatternHolder value:'*'.
    ] ifFalse:[
        self namePatternHolder value:aFile baseName.
    ].
    self enableStop value:false.
    self enableSearch value:true.
!

item:aItem

    |file|

    super item:aItem.
    file := self fileName.
    self searchDirectoryHolder value:(self getDirWithoutFileName:file).
    file isDirectory ifTrue:[
        self namePatternHolder value:'*'.
    ] ifFalse:[
        self namePatternHolder value:file baseName.
    ].
    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.
    ^ super release
! !

!FindFileApplication class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/FindFileApplication.st,v 1.2 2002-10-01 15:17:30 cg Exp $'
! !