FNmEdtFld.st
author claus
Thu, 07 Sep 1995 14:48:20 +0200
changeset 72 f17df5ea35ed
parent 71 9f9243f5813b
child 75 903e595b4cec
permissions -rw-r--r--
.

"
 COPYRIGHT (c) 1994 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.
"

EditField subclass:#FilenameEditField 
       instanceVariableNames:'directoriesOnly filesOnly directory'
       classVariableNames:   ''
       poolDictionaries:''
       category:'Views-Text'
!

!FilenameEditField class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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/libwidg2/Attic/FNmEdtFld.st,v 1.14 1995-09-07 12:47:59 claus Exp $
"
!

documentation
"
    like a normal editField, but does filename-completion on the last word of
    the contents, when TAB is pressed.
    Filename completion ignores regular files if directoriesOnly is true,
    and ignores directories, if filesOnly is true. Both default to false.
"
! !

!FilenameEditField class methodsFor:'defaults'!

filenameCompletionBlock 
    "return a block which can be used for fileName completion.
     This has been extracted into a separate method, to allow reuse of
     this code (for example, for use with regular editFields ..)"

    ^ [:field :inDirectory :directoriesOnly :filesOnly |
	|s f matchSet nMatch name words dir|

	s := field contents.
	"
	 find the last word ...
	"
	words := s asCollectionOfWords.
	f := words last asFilename.
	f isAbsolute ifFalse:[
	     inDirectory asString ~= '.' ifTrue:[
		 f := (inDirectory name asFilename construct:f) name asFilename
	     ].
	].
	f isAbsolute ifTrue:[
	    f := f pathName asFilename.
	].

	matchSet := f filenameCompletion.
	dir := f directory.

	directoriesOnly ifTrue:[
	    matchSet := matchSet select:[:aFilename |
		(dir construct:aFilename) isDirectory
	    ].
	] ifFalse:[
	    filesOnly ifTrue:[
		matchSet := matchSet select:[:aFilename |
		    (dir construct:aFilename) isDirectory not
		].
	    ]
	].

	(nMatch := matchSet size) ~~ 1 ifTrue:[
	    "
	     more than one possible completion -
	    "
	    field changed:#directory with:f directoryName.
	    field flash.
	    field device beep.
	].
	"
	 even with more than one possible completion,
	 f's name is now common prefix
	"
	name := f asString.
	nMatch == 1 ifTrue:[
	    "
	     exactly one possible completion -
	    "
"/            f := dir construct:matchSet first.
	    f := matchSet first asFilename.

	    directoriesOnly ifTrue:[
		name := f asString
	    ] ifFalse:[
		f isDirectory ifTrue:[
		    (name endsWith:(Filename separator)) ifFalse:[
			name := f asString , '/'
		    ].
		].
	    ]
	].
	"
	 construct new contents, by taking
	 last words completion
	"
	s := ''.
	1 to:(words size - 1) do:[:idx |
	    s := s , (words at:idx) , ' '
	].
	s := s , name.
	field contents:s.
	field cursorToEndOfLine.
    ].
! !

!FilenameEditField methodsFor:'initialization'!

initialize
    super initialize.
    directoriesOnly := filesOnly := false.
    directory := '.' asFilename.

    entryCompletionBlock := [
	self class 
	    filenameCompletionBlock 
		value:self 
		value:directory
		value:directoriesOnly
		value:filesOnly
    ].

    "Modified: 7.9.1995 / 10:20:46 / claus"
!

realize
    "move the cursor to the end - thats the most interresting part of
     a filename
    "
    super realize.
    self cursorToEndOfLine.
! !

!FilenameEditField methodsFor:'accessing'!

directory
    ^ directory

    "Modified: 7.9.1995 / 10:12:40 / claus"
!

directory:aFilename
    directory := aFilename asFilename

    "Modified: 7.9.1995 / 10:12:55 / claus"
!

showsDirectoriesOnly
    "return if expanding names for directories only"

    ^ directoriesOnly

    "Modified: 6.9.1995 / 20:35:30 / claus"
!

showsFilesOnly
    "return if expanding names for files only"

    ^ filesOnly

    "Modified: 6.9.1995 / 20:34:57 / claus"
!

directoriesOnly
    "set to expand names for directories only"

    directoriesOnly := true.
!

filesOnly
    "set to expand names for files only"

    filesOnly := true.
!

initialText:aString selected:aBoolean
    "move the cursor to the end - thats the most interresting part of
     a filename
    "

    super initialText:aString selected:aBoolean.
    self cursorToEndOfLine.
! !

!FilenameEditField methodsFor:'event handling'!

keyPress:key x:x y:y
    "handle tab for filename completion.
     Bug: it completes the last word; it should complete the
	  word before the cursor."

    <resource: #keyboard ( #FilenameCompletion ) >

    enabled ifTrue:[
	((key == #Tab)
	or:[key == #FilenameCompletion]) ifTrue:[
	    entryCompletionBlock value.
	    ^ self
	]
    ].
    ^ super keyPress:key x:x y:y.
! !