FileSelectionItem.st
author Claus Gittinger <cg@exept.de>
Thu, 07 Aug 1997 15:29:28 +0200
changeset 489 45b03c9e0277
parent 486 d981d312947d
child 493 babd683808e3
permissions -rw-r--r--
*** empty log message ***

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



TreeItem subclass:#FileSelectionItem
	instanceVariableNames:'isDirectory imageType invalidate'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Support'
!

FileSelectionItem subclass:#Directory
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:FileSelectionItem
!

FileSelectionItem subclass:#File
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:FileSelectionItem
!

!FileSelectionItem class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 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
"
    class to build up file trees like structures. You can define your own
    icons and filter. Redefinging the icons you have to look especially for
    this methods:

        class method:           iconsOn:        : returns a list of icons used

        instance method:        updateImageType : set default key into icon list
                                                  for the image associated with node

                                imageUnselected : image or key into icon list
                                                  used for unselected mode

                                imageSelected   : image or key into icon directory
                                                  used for selected mode

    Especially suited for use with FileSelectionTree.

    [Author:]
        Claus Atzkern

    [See also:]
        TreeItem
        FileSelectionTree
"
! !

!FileSelectionItem class methodsFor:'instance creation'!

pathName:aPath
    "create a new node entry associated with the full pathname, aPath
    "
    |node|

    node := self new.
    node pathName:aPath.
  ^ node


! !

!FileSelectionItem class methodsFor:'accessing class'!

directoriesOnly
    ^ Directory
!

filesOnly
    ^ File
! !

!FileSelectionItem class methodsFor:'converting'!

asFilename:aPathname
    "convert pathname to an absolute path
    "
    |path|

    path := aPathname asString.

    (path size > 1 and:[path endsWith:(Filename separator)]) ifTrue:[
        ^ (path copyWithout:1) asFilename.
    ].
  ^ aPathname asFilename
! !

!FileSelectionItem class methodsFor:'defaults'!

iconsOn:aDevice
    "returns an IdentityDictionary containing a list of images and keys used
     by any file entry.
    "
    |icons image|

    icons := IdentityDictionary new.

    #(
        (#directory       'tiny_yellow_dir.xpm')
        (#directoryOpened 'tiny_yellow_dir_open.xpm')
        (#directoryLocked 'tiny_yellow_dir_locked.xpm')
        (#directoryLink   'tiny_yellow_dir_link.xpm'  )

        (#file            'tiny_file_plain.xpm'       )
        (#fileLink        'tiny_file_link.xpm'        )
        (#fileLocked      'tiny_file_lock.xpm'        )
        (#imageFile       'tiny_file_pix.xpm'         )

     ) do:[:el |
        image := Image fromFile:('xpmBitmaps/document_images/', el last ).
        icons at:(el first) put:(image onDevice:aDevice).
    ].
  ^ icons


! !

!FileSelectionItem class methodsFor:'queries'!

isSelectableFile:aFilename
    "checks whether file can be selected through filter
    "
    aFilename notNil ifTrue:[
        ^ aFilename asFilename exists
    ].
  ^ false
! !

!FileSelectionItem methodsFor:'accessing'!

children
    "get's list of children
    "
    invalidate ifTrue:[
        isDirectory ifTrue:[self updateChildren].
        invalidate := false
    ].
  ^ children
!

pathName
    "returns full pathname of node
    "
  ^ contents asString


!

pathName:aPathname
    "initialze attributes associated with the full pathname, aPathname
    "
    contents := self class asFilename:aPathname.
    name     := contents baseName.
    isDirectory := contents isDirectory.
    self updateImageType.

    isDirectory ifTrue:[
        invalidate := imageType ~~ #directoryLocked
    ] ifFalse:[
        invalidate := false
    ].
! !

!FileSelectionItem methodsFor:'images'!

imageSelected
    "returns type or an image set for node in selected mode
    "
    "returns type or an image set for node in selected mode
    "
    (isDirectory and:[imageType ~~ #directoryLocked]) ifTrue:[
        ^ #directoryOpened
     ].
   ^ imageType


!

imageUnselected
    "returns type or an image set for node in selected mode
    "
   ^ imageType


! !

!FileSelectionItem methodsFor:'initialization'!

initialize
    "set default values
    "
    super initialize.
    invalidate := false.
! !

!FileSelectionItem methodsFor:'queries'!

hasChildren
    "returns true if the pathname assigned to this node is a directory
     otherwise false
    "
  ^ isDirectory

!

isDirectory
    ^ isDirectory
!

match:aFilename
    "returns true if file matched otherwise false
    "
  ^ true

! !

!FileSelectionItem methodsFor:'update'!

updateChildren
    "read children from directory
    "
    |pathName directory item aFilename|

    children  := OrderedCollection new.
    pathName  := self pathName.
    directory := FileDirectory new.
    directory pathName:pathName.

    directory do:[:aName|
        ((aName first == $.) and:[aName last == $.]) ifFalse:[
            aFilename := contents construct:aName.
            (self match:aFilename) ifTrue:[
                item := self class pathName:aFilename.
                item parent:self.
                children add:item
            ]
        ]
    ].
    children sort:[:a :b | a name < b name].
    invalidate := false.

!

updateImageType
    "update image type
    "
    isDirectory ifTrue:[
        contents isSymbolicLink ifTrue:[
            imageType := #directoryLink
        ] ifFalse:[
            (contents isExecutable and:[contents isReadable]) ifTrue:[
                imageType := #directory
            ] ifFalse:[
                imageType := #directoryLocked
            ]
        ].
      ^ self
    ].

    contents isSymbolicLink ifTrue:[  
        imageType := #fileLink
    ] ifFalse:[
        contents isReadable ifTrue:[
            (Image isImageFileSuffix:(contents suffix)) ifFalse:[
                imageType := #file
            ] ifTrue:[
                imageType := #imageFile
            ]
        ] ifFalse:[
            imageType := #fileLocked
        ]
    ]
! !

!FileSelectionItem::Directory class methodsFor:'documentation'!

documentation
"
    subtype of FileSelectionItem only showing directories; more an example to show
    how to implement filters

    [Author:]
        Claus Atzkern

    [See also:]
        FileSelectionItem
"

! !

!FileSelectionItem::Directory class methodsFor:'queries'!

isSelectableFile:aFilename
    "checks whether file can be selected through filter
    "
    (super isSelectableFile:aFilename) ifTrue:[
        ^ aFilename asFilename isDirectory
    ].
  ^ false


! !

!FileSelectionItem::Directory methodsFor:'queries'!

match:aFilename
    ^ aFilename isDirectory
! !

!FileSelectionItem::File class methodsFor:'documentation'!

documentation
"
    subtype of FileSelectionItem only showing files; more an example to show
    how to implement filters

    [Author:]
        Claus Atzkern

    [See also:]
        FileSelectionItem
"


! !

!FileSelectionItem::File class methodsFor:'queries'!

isSelectableFile:aFilename
    "checks whether file can be selected through filter
    "
    (super isSelectableFile:aFilename) ifTrue:[
        ^ aFilename asFilename isDirectory not
    ].
  ^ false


! !

!FileSelectionItem::File methodsFor:'queries'!

match:aFilename
    ^ aFilename isDirectory not


! !

!FileSelectionItem class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/FileSelectionItem.st,v 1.2 1997-08-07 13:29:28 cg Exp $'
! !