AbstractFileFinderApplicationComponent.st
author Claus Gittinger <cg@exept.de>
Tue, 21 Apr 2020 13:26:33 +0200
changeset 19578 088c98423554
parent 19532 887a854246f4
permissions -rw-r--r--
#FEATURE by cg class: DebugView class definition changed: #enter:select:

"
 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' }"

"{ NameSpace: Smalltalk }"

AbstractFileApplicationNoteBookComponent subclass:#AbstractFileFinderApplicationComponent
	instanceVariableNames:'findFileView searchResultTable resultList enableStop enableSearch
		stopSignal accessLock searchTask expanded searchRecursively
		selectionHolder hasListEntries targetApplication matchedFilesList
		shownListHolder autoSelectInBrowserHolder filesSearchedCount
		bytesSearchedCount'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Tools-File'
!

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

documentation
" 
    abstract superclass of file-search appliations which are embedded in the file browserV2
"
! !

!AbstractFileFinderApplicationComponent class methodsFor:'queries'!

isAbstract
    "Return if this class is an abstract class.
     True is returned here for myself only; false for subclasses.
     Abstract subclasses must redefine this again."

    ^ self == AbstractFileFinderApplicationComponent.
!

searchResultTable
    self subclassResponsibility
! !

!AbstractFileFinderApplicationComponent methodsFor:'accessing'!

accessLock
    ^ accessLock
!

stopSignal

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

targetApplication:anApplication
    targetApplication := anApplication.

    "Modified (format): / 11-01-2012 / 22:41:01 / cg"
! !

!AbstractFileFinderApplicationComponent 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
        ] ifFalse:[
            masterApplication notify:aString.
        ].
    ].

    "Modified: / 03-08-2011 / 17:56:21 / cg"
!

clearShownList
    self shownList removeAll.
!

copySelectedFileNamesToClipboard
    |sel list stream|

    sel := selectionHolder value.
    list := self shownList.
    (sel notEmptyOrNil) ifTrue:[
        stream := CharacterWriteStream new.
        sel do:[: key |
            stream nextPutAll:(list at:key).
            stream cr.
        ].
        self window setClipboardText:stream contents.
    ].
!

generateResultStringForTimeElapsed:timeDuration
    "at the end of a search, generate a nice informative summary string.
     This can be redefined by different search tabs"

    |timeMillis timeString nFound|

    timeMillis := timeDuration asMilliseconds.
"/ OLD:
"/    timeMillis > 100 ifTrue:[
"/        timeString := ((timeMillis / 1000) asFixedPoint:2) printString , ' s'
"/    ] ifFalse:[
"/        timeString := timeMillis printString , ' ms'
"/    ].
"/ NEW:
    timeString := timeDuration printStringForApproximation.

    nFound := resultList size.
    ^ resources 
        string:((nFound == filesSearchedCount) 
                ifTrue:['Found %1 file%2 in %3 (%6 files/s)'] 
                ifFalse:[
                    "/ 'Found %1 file%2 in %3 (%4 files visited)'
                    "/ 'Found %1 file%2 in %3 (%4 files visited; scanrate: %5/s)'
                    'Found %1 file%2 in %3 (%4 files visited; %6 files/s)'
                ]) 
        with:nFound 
        with:(nFound == 1 ifTrue:'' ifFalse:'s') 
        with:timeString
        with:filesSearchedCount
        with:(UnitConverter fileSizeSIStringFor:(bytesSearchedCount * 1000 / (timeMillis max:1)))
        with:((filesSearchedCount * 1000 / (timeMillis max:1)) asFixedPoint:1).
!

openInNewBrowser
    |sel|

    sel := selectionHolder value.
    (sel notEmptyOrNil) ifTrue:[
        FileBrowserV2 openOn:(self shownList at:sel first) asFilename
    ].
!

selectInBrowser
    |sel entry fn application|

    sel := selectionHolder value.
    (sel notEmptyOrNil) ifTrue:[
        entry := self shownList at:sel first.
        (fn := entry asFilename) exists ifFalse:[ ^ self].
        
        application := targetApplication ? self masterApplication.
        application notNil ifTrue:[
            application gotoFile:fn.
        ].
    ].

    "Modified (format): / 15-06-2019 / 08:44:29 / Claus Gittinger"
!

startSearchTask:aBlock name:taskName
    |thisSearchTask|

    searchTask := thisSearchTask :=
        [
            |message timeElapsed|

            [    
                (self stopSignal) catch:[
                    enableStop value:true.
                    resultList removeAll.
                    matchedFilesList removeAll.
                    self notify:'Searching...'.
                    filesSearchedCount := bytesSearchedCount := 0.

                    "/ self changeInformationTo:'Find File ' , '- searching ' toTab:true.
                    timeElapsed := TimeDuration toRun:aBlock.

                    enableStop value:false.
                    enableSearch value:true.
                    self changeInformationTo:'Find File ' , '- done.' toTab:true.

                    message := self generateResultStringForTimeElapsed:timeElapsed.
                ].
            ] ensure:[
                thisSearchTask == searchTask ifTrue:[
                    searchTask := nil.
                    enableStop value:false.
                    self notify:message.
                ].
            ]
        ] newProcess.

    searchTask priorityRange:(Processor userBackgroundPriority to:Processor userSchedulingPriority"-1").
    searchTask name:taskName.
    searchTask resume.
    ^ searchTask

    "Created: / 12-01-2012 / 01:52:17 / cg"
    "Modified: / 11-09-2018 / 15:21:15 / Claus Gittinger"
    "Modified: / 11-09-2019 / 16:02:44 / Stefan Vogel"
!

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

    "Modified: / 11-01-2012 / 22:42:07 / cg"
!

stopSearchTask
    |task|

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

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

!AbstractFileFinderApplicationComponent methodsFor:'aspects'!

autoSelectInBrowser
    ^ autoSelectInBrowserHolder value.
!

autoSelectInBrowserHolder
    ^ autoSelectInBrowserHolder.
!

contentsPatternHolder
    "to be redefined"
    
    ^ nil

    "Created: / 15-06-2019 / 08:43:11 / Claus Gittinger"
!

enableSearch
    ^ enableSearch.
!

enableStop
    ^ enableStop.
!

hasListEntries
    ^ hasListEntries.
!

ignoreCaseInContents
    "to be redefined"
    
    ^ false

    "Created: / 15-06-2019 / 08:43:47 / Claus Gittinger"
!

matchedFilesList
    ^ matchedFilesList.
!

resultList
    ^ resultList.
!

searchRecursively
    ^ searchRecursively.
!

searchResultTable
    ^ searchResultTable.
!

selectionHolder
    ^ selectionHolder
!

shownList
    ^ shownListHolder valueHolder.
!

shownListHolder
    ^ shownListHolder.
! !

!AbstractFileFinderApplicationComponent methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    changedObject == shownListHolder ifTrue:[
        hasListEntries value:(changedObject valueHolder notEmptyOrNil).
        ^ self
    ].
    changedObject == selectionHolder ifTrue:[
        self autoSelectInBrowser ifTrue:[
            self selectInBrowser.
        ].
        ^ self
    ].
    super update:something with:aParameter from:changedObject
! !

!AbstractFileFinderApplicationComponent methodsFor:'drag & drop'!

getDisplayObjects:anArgument
    "retrieve the objects displayed during a drag"

    | sel string size fnName stream|

    sel := selectionHolder value.
    size := sel size.
    size == 0  ifTrue:[^ ''].

    stream := CharacterWriteStream with:((resultList at:sel first) asFilename baseName asString).
    size == 1 ifTrue:[
        fnName := 'ui_menuitem.xpm'.
    ] ifFalse:[
        fnName := 'ui_submenu_open.xpm'.
        stream nextPutAll:' ... '.
        stream nextPutAll:((resultList at:sel last) asFilename baseName asString).
    ].
    string := stream contents.

    ^ Array with:(LabelAndIcon 
                    icon:(Image fromFile:fnName)
                    string:(string allBold))

    "Modified: / 20-06-2017 / 08:16:39 / cg"
!

getDropObjects:anArgument
    "common code, used in subclasses"

    |sel|

    sel := selectionHolder value.
    ^ sel 
        collect:[:idx|
            |el|

            el := resultList at:idx.
            DropObject newFile:(el asFilename) 
        ].
! !

!AbstractFileFinderApplicationComponent methodsFor:'event handling'!

fileDoubleClick:file
    |fn app openedAppl contentsPattern|

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

    app := targetApplication ? self masterApplication.
    fn isDirectory ifTrue:[
        app gotoFile:fn.
        ^ self.
    ].
    app notNil ifTrue:[
        openedAppl := app openApplForFile:file.
        (openedAppl notNil and:[openedAppl isTextEditor]) ifTrue:[
            openedAppl window assignKeyboardFocusToFirstKeyboardConsumer.    "/ should this be done in openApplForFile?
            contentsPattern := self contentsPatternHolder value.
            (contentsPattern notNil and:[ contentsPattern notEmpty and:[contentsPattern ~= '*']]) ifTrue:[
                openedAppl searchForPattern:contentsPattern ignoreCase:(self ignoreCaseInContents value).
            ]        
        ].
    ] ifFalse:[
        self openInNewBrowser.
    ]

    "Modified: / 10-07-2019 / 18:19:24 / Claus Gittinger"
!

fileListDoubleClick:indexOrIndexCollection
    |idx file|

    idx := indexOrIndexCollection isInteger 
                ifTrue:[indexOrIndexCollection] 
                ifFalse:[indexOrIndexCollection first].
    file := self shownList at:idx.
    self fileDoubleClick:file
!

fileSelected:entries
    |file fn|

    entries isEmptyOrNil ifTrue:[^ self].

    file := self shownList at:entries first.
    file isText ifTrue:[^ self].

    fn := file asFilename.
    fn exists ifFalse:[
        self notify:('%1 does not (no longer ?) exist or is not accessible.' bindWith:file allBold).
        ^ self
    ].
    fn isDirectory ifTrue:[
        self notify:nil.
        ^ self.
    ].

    self notify:('%1: %2.' bindWith:fn baseName allBold with:(UnitConverter fileSizeStringFor:fn fileSize)).

    "Created: / 04-07-2006 / 11:35:38 / cg"
!

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

    <resource: #keyboard (#Return )>

    |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 fileListDoubleClick:(selectionHolder value)
"/                        self isEmbeddedApplication ifTrue:[
"/                            self selectInBrowser.
"/                        ] ifFalse:[
"/                            self openInNewBrowser.
"/                        ]
                    ]
                ].
                ^ true
            ].
        ]
    ].
    ^ false
! !

!AbstractFileFinderApplicationComponent methodsFor:'initialization'!

initialize
    <modifier: #super> "must be called if redefined"

    super initialize.

    autoSelectInBrowserHolder := false asValue.
    enableSearch := true asValue.
    enableStop := true asValue.
    hasListEntries := false asValue.
    (matchedFilesList := List new) addDependent:self.
    (resultList := List new) addDependent:self.
    searchRecursively := true asValue.
    searchResultTable := self class searchResultTable asValue.
    (selectionHolder := ValueHolder new) addDependent:self.
    shownListHolder := IndirectValue for:resultList.
    shownListHolder addDependent:self.

    accessLock := Semaphore forMutualExclusion name:'accessLock'.

    self enableStop value:false.
    self enableSearch value:true.

    "Modified: / 08-02-2017 / 00:27:46 / cg"
! !

!AbstractFileFinderApplicationComponent methodsFor:'queries'!

hasOneFileSelected
    ^ selectionHolder value size == 1
!

hasSelectionInResultList
    ^ selectionHolder value notEmptyOrNil
!

hasTwoFilesSelected
    ^ selectionHolder value size == 2
!

hasTwoImageFilesSelected
    |sel|

    sel := selectionHolder value.
    ^ (sel size == 2) and:[ sel conform:[:fn | fn asFilename mimeTypeFromName isImageType] ]

    "Created: / 10-09-2017 / 16:54:55 / cg"
! !

!AbstractFileFinderApplicationComponent methodsFor:'tasks'!

stopSearchTaskOrAbort
    searchTask isNil ifTrue:[ ^ self ].

    (Dialog 
            confirm:(resources stringWithCRs:'There is already another find-file task running !!')
            yesLabel:(resources string:'Stop other Task and Proceed')
            noLabel:(resources string:'Cancel'))
        ifFalse:[AbortSignal raise].
    self stop.

    "Created: / 12-01-2012 / 01:48:42 / cg"
! !

!AbstractFileFinderApplicationComponent class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !