FileSelectionBox.st
author claus
Fri, 12 Aug 1994 01:47:09 +0200
changeset 44 f5e3a267fe4e
parent 41 2f8d0f8e796b
child 59 450ce95a72a4
permissions -rw-r--r--
pass fullname to matchblock

"
 COPYRIGHT (c) 1990 by Claus Gittinger
              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.
"

ListSelectionBox subclass:#FileSelectionBox
       instanceVariableNames:'patternField'
       classVariableNames:''
       poolDictionaries:''
       category:'Views-DialogBoxes'
!

FileSelectionBox comment:'
COPYRIGHT (c) 1990 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libwidg/FileSelectionBox.st,v 1.9 1994-08-11 23:47:09 claus Exp $
'!

!FileSelectionBox class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1990 by Claus Gittinger
              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.
"
!

version
"
$Header: /cvs/stx/stx/libwidg/FileSelectionBox.st,v 1.9 1994-08-11 23:47:09 claus Exp $
"
!

documentation
"
    this class implements file selection boxes. Instances show a list of
    files, and perform an action block with the selected pathname as
    argument when ok is clicked.

    There is an optional PatternField, which shows itself when a pattern
    is defined (i.e. if there is no pattern, it is hidden). 
    If there is a pattern, only files matching the pattern will be shown in 
    the list (and directories).

    In addition, there is an optional matchBlock (actually this is defined 
    in the FileSelectionList). Only filenames for which this matchblock
    returns true will be presented.

    Example1:

        FileSelectionBox open

    Example2:

        FileSelectionBox new open

    Example3:

        |box|
        box := FileSelectionBox new.
        box title:'Which file ?'.
        box open

    Example4:

        |box|
        box := FileSelectionBox new.
        box title:'Which file ?'.
        box pattern:'*.doc'.
        box open

    Example5:

        |box|
        box := FileSelectionBox new.
        box title:'Which file ?'.
        box pattern:'*'.
        box matchBlock:[:name | name first isLowercase].
        box open

    Example5:

        |box|
        box := FileSelectionBox new.
        box title:'Which directory ?'.
        box pattern:'l*'.
        box matchBlock:[:name | OperatingSystem isDirectory:name].
        box open
"
! !

!FileSelectionBox class methodsFor:'defaults'!

listViewType
    "return the type of listView - using a FileSelectionList here"

    ^ FileSelectionList
! !

!FileSelectionBox methodsFor:'initialization'!

initialize
    super initialize.

    labelField extent:(0.7 @ labelField height).
    labelField label:(resources string:'select a file:').
    labelField adjust:#left.

    patternField := EditField in:self.
    patternField 
        origin:(0.7 @ labelField origin y)
        corner:(1.0 @ (labelField origin y+patternField heightIncludingBorder)).
    patternField initialText:'*'.
    patternField leaveAction:[:reason | 
        selectionList pattern:patternField contents. 
        self updateList
    ].
    patternField hidden:true. "delay showing, until a pattern is defined"

    selectionList action:[:line |
        |entry|

        entry := selectionList selectionValue.
        enterField contents:entry
    ].

    selectionList doubleClickAction:[:line |
        |entry|

        entry := selectionList selectionValue.
        entry notNil ifTrue:[
            ((selectionList directory typeOf:entry) == #directory) ifFalse:[
                enterField contents:entry.
                self okPressed
            ]
        ]
    ].
    enterField addDependent:self.

    "FileSelectionBox new show"
!

createEnterField
    "
     if the (optional) class FilenameEditField is present, use
     it, since it provides filename completion. Otherwise, we have
     to live with the dump field ...
    "
    FilenameEditField notNil ifTrue:[
        enterField := FilenameEditField in:self.
    ] ifFalse:[
        super createEnterField
    ]
! !

!FileSelectionBox methodsFor:'dependencies'!

update:something with:argument
    |commonName index|

    something == #directory ifTrue:[
        "
         sent by fileNameEnterField, if a filename
         completion was not possible due to multiple
         matches.
        "
        selectionList directory:argument.
        commonName := enterField contents asFilename baseName.
        commonName size > 0 ifTrue:[
            index := selectionList list findFirst:[:entry | entry startsWith:commonName].
            index ~~ 0 ifTrue:[
                selectionList makeLineVisible:index
            ]
        ]
    ]
! !

!FileSelectionBox methodsFor:'user actions'!

okPressed
    "called for both on ok-press and on return-key"

    |dir string fname|

    string := enterField contents.
    string notNil ifTrue:[
        string := string withoutSeparators.
        string asFilename isAbsolute ifTrue:[
            fname := string asFilename
        ] ifFalse:[
            dir := selectionList directory pathName asFilename.
            fname := dir construct:string
        ].
        fname isDirectory ifTrue:[
            selectionList directory:fname asString.
            self updateList.
            ^ self
        ]
    ].
    super okPressed
! !

!FileSelectionBox methodsFor:'private'!

updateList
    selectionList updateList
! !

!FileSelectionBox methodsFor:'accessing'!

openOn:aPath
    "open the box showing files in aPath.
     This is only a shortcut message - no new functionality."

    self directory:aPath.
    self showAtPointer
!

directory:nameOrDirectory
    "change the directory shown in the list."

    selectionList directory:nameOrDirectory
!

pattern:aPattern
    "set the pattern - this also enables the PatternField
     (if the pattern is non-nil) or hides it (if nil)."

    patternField initialText:aPattern.
    selectionList pattern:aPattern.
    aPattern isNil ifTrue:[
        patternField hidden:true.
        realized ifTrue:[
            patternField hide.
        ]
    ] ifFalse:[
        patternField hidden:false.
        realized ifTrue:[
            patternField realize.
        ].
    ].
!

matchBlock:aBlock
    "set the matchBlock (in the selectionList). Only files
     for which the block returns true are shown.
     The matching is actually done in the fileSelectionList,
     but we trick a bit to pass the full pathname instead of the
     selection-name to the block."

    selectionList matchBlock:[:name | 
        |dir fullPath|

        dir := selectionList directory pathName asFilename.
        fullPath := dir construct:name. 
        aBlock value:fullPath asString
    ]
!

contents
    "return the current entered value (i.e. the enterFields string).
     redefined to return the full pathname."

    |string sep|

    string := super contents.
    string isNil ifTrue:[
        ^ selectionList directory pathName
    ].
    sep := Filename separator.
    (string startsWith:sep) ifTrue:[
        ^ string
    ].
    ^ (selectionList directory pathName asFilename construct:string) asString
! !