FileSelectionItem.st
author ca
Wed, 22 Oct 1997 15:26:06 +0200
changeset 569 2a1014d6697c
parent 535 9a237ca905d2
child 731 05ea1ee08afb
permissions -rw-r--r--
checkin from browser

"
 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:'modificationTime matchAction isDirectory imageType
		haveToReadChildren showIndicator'
	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:        imageType         : get type of icon assigned to file

                                drawableImageType : get the type of image to be drawn

    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 ).
        image notNil ifTrue:[
            image := image onDevice:aDevice.
            image clearMaskedPixels.
            icons at:(el first) put:image.
        ]
    ].
  ^ icons


! !

!FileSelectionItem methodsFor:'accessing'!

children
    "get's list of children
    "
    haveToReadChildren ifTrue:[
        children := self readInChildren
    ].
  ^ children
!

drawableImageType
    "returns type of image to be drawn
    "
    (children size ~~ 0 and:[hide == false]) ifTrue:[
        ^ #directoryOpened
    ].
    ^ self imageType
!

match:aOneArgBlock

    aOneArgBlock isNil ifTrue:[
        self discardFiles ifTrue:[
            matchAction := [:aFile :isDirectory| isDirectory ]
        ] ifFalse:[
            self discardDirectories ifTrue:[
                matchAction := [:aFile :isDirectory| isDirectory not ]
            ] ifFalse:[
                matchAction := [:aFile :isDir| true ]
            ]
        ]
    ] ifFalse:[
        self discardFiles ifTrue:[
            matchAction := [:aFile :isDirectory| (isDirectory and:[aOneArgBlock value:aFile]) ]
        ] ifFalse:[
            self discardDirectories ifTrue:[
                matchAction := [:aFile :isDirectory| (isDirectory not and:[aOneArgBlock value:aFile]) ]
            ] ifFalse:[
                matchAction := [:aFile :isDir| aOneArgBlock value:aFile ]
            ]
        ]
    ]    
!

pathName
    "returns full pathname of node
    "
    ^ contents asString


!

pathName:aPathname
    "initialze attributes associated with the full pathname, aPathname
    "
    |file|

    file := self class asFilename:aPathname.
    self fileName:file baseName:(file baseName) parent:nil isDirectory:(file isDirectory)
! !

!FileSelectionItem methodsFor:'accessing hierarchy'!

collapse
    "chech to release children
    "
    hide := true.

    children size ~~ 0 ifTrue:[
        children do:[:aChild|
            aChild releaseCollapsedChildren ifFalse:[
                ^ self
            ]
        ].
        parent notNil ifTrue:[                  "/ not for root
            haveToReadChildren := true.
            modificationTime   := nil.
            children := OrderedCollection new.
        ]
    ]
!

collapseAll
    "release my childrens
    "
    hide := true.

    children size ~~ 0 ifTrue:[
        parent isNil ifTrue:[
            self allChildrenDo:[:aChild| aChild collapseAll ]
        ] ifFalse:[
            haveToReadChildren := true.
            modificationTime   := nil.
            children := OrderedCollection new.
        ]
    ].
! !

!FileSelectionItem methodsFor:'private'!

fileName:aFilenname baseName:aBaseName parent:aParent isDirectory:aBool
    "initialze attributes associated with the full pathname, aPathname
    "
    contents    := aFilenname.
    name        := aBaseName.
    parent      := aParent.
    isDirectory := haveToReadChildren := aBool.

    isDirectory ifFalse:[
        showIndicator := false
    ] ifTrue:[
        showIndicator := nil
    ].

    parent notNil ifTrue:[
        matchAction := parent matchAction       "/ same as from parent
    ] ifFalse:[
        self match:nil                          "/ setup matchAction new
    ]

!

matchAction
    "returns my match action
    "
    ^ matchAction
! !

!FileSelectionItem methodsFor:'queries'!

discardDirectories
    "returns true if children are not type of directory; could be
     reimplemented for speed in any subclass
    "
    ^ false
!

discardFiles
    "returns true if children are not type of file; could be
     reimplemented for speed in any subclass
    "
    ^ false
!

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

!

isDirectory
    ^ isDirectory
!

releaseCollapsedChildren
    "release collapsed children
    "
    |canCollapse|

    children size == 0 ifTrue:[
        ^ true
    ].
    canCollapse := true.

    children do:[:aChild|
        aChild releaseCollapsedChildren ifFalse:[
            canCollapse := false
        ]
    ].
    (canCollapse and:[self isExpandable]) ifTrue:[
        parent notNil ifTrue:[                          "/ not the root directory
            haveToReadChildren := true.
            modificationTime   := nil.
            children := OrderedCollection new.
          ^ true.
        ]
    ].
    ^ false
!

showIndicator

    showIndicator isNil ifTrue:[
        (self imageType == #directoryLocked) ifTrue:[
            showIndicator := haveToReadChildren := false.
        ] ifFalse:[
            showIndicator := DirectoryContents directoryNamed:contents detect:matchAction
        ]
    ].
    ^ showIndicator

! !

!FileSelectionItem methodsFor:'repair mechanism'!

hasObsoleteNodes
    "check whether node or any child node is obsolete
    "
    modificationTime notNil ifTrue:[
        modificationTime < contents modificationTime ifTrue:[
            ^ true
        ].
        (self discardDirectories or:[children size == 0]) ifFalse:[
            children do:[:aChild| aChild hasObsoleteNodes ifTrue:[^ true]]
        ]
    ].
    ^ false
!

repairObsoleteNodes
    "repair nodes
    "
    |list chd hasChanged|

    modificationTime isNil ifTrue:[
        ^ false
    ].

    modificationTime < contents modificationTime ifTrue:[
        list := self readInChildren.                    
        hasChanged := list size ~~ children size.

        children do:[:aChild||i|
            i := list findFirst:[:f| f name = aChild name ].

            i ~~ 0 ifTrue:[
                list at:i put:aChild
            ] ifFalse:[
                hasChanged := true
            ].
        ].
        hasChanged ifTrue:[
            children := list
        ]
    ] ifFalse:[
        hasChanged := false
    ].
    children size ~~ 0 ifTrue:[
        children do:[:aChild|
            (aChild repairObsoleteNodes) ifTrue:[hasChanged := true]
        ]
    ].
    ^ self shown ifTrue:[hasChanged]
                ifFalse:[false]

! !

!FileSelectionItem methodsFor:'update'!

imageType

    |readable|

    imageType isNil ifTrue:[
        readable := contents isReadable.

        isDirectory ifTrue:[
            (readable and:[contents isExecutable]) ifTrue:[
                contents isSymbolicLink ifFalse:[imageType := #directory]
                                         ifTrue:[imageType := #directoryLink]
            ] ifFalse:[
                imageType := #directoryLocked
            ]
        ] ifFalse:[
            readable ifFalse:[
                imageType := #fileLocked
            ] ifTrue:[
                contents isSymbolicLink ifFalse:[
                    (Image isImageFileSuffix:(contents suffix)) ifFalse:[
                        imageType := #file
                    ] ifTrue:[
                        imageType := #imageFile
                    ]
                ] ifTrue:[
                    imageType := #fileLink
                ]
            ]
        ]
    ].
    ^ imageType

!

readInChildren
    "read children from directory
    "
    |list directory node|

    list := OrderedCollection new.

    self imageType == #directoryLocked ifFalse:[
        directory := DirectoryContents directoryNamed:contents.
        modificationTime := directory modificationTime.

        directory contentsAndBaseNamesDo:[:f :n :d|
            (matchAction value:f value:d) ifTrue:[
                list add:(self class new fileName:f baseName:n parent:self isDirectory:d)
            ]
        ]
    ].
    haveToReadChildren := false.
    showIndicator := list size ~~ 0.
  ^ list
! !

!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 methodsFor:'queries'!

discardFiles
    ^ true
! !

!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 methodsFor:'queries'!

discardDirectories
    ^ true


! !

!FileSelectionItem class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/FileSelectionItem.st,v 1.6 1997-10-22 13:25:03 ca Exp $'
! !