DirectoryContents.st
author Claus Gittinger <cg@exept.de>
Tue, 22 Aug 2000 15:57:19 +0200
changeset 906 30c1ab2aee8d
parent 904 f4791de2295b
child 951 37870a37b930
permissions -rw-r--r--
category change

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



"{ Package: 'stx:libbasic2' }"

Object subclass:#DirectoryContents
	instanceVariableNames:'directory timeStamp names files types'
	classVariableNames:'List'
	poolDictionaries:''
	category:'System-Support'
!

!DirectoryContents 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
"
    DirectoryContents provides a cached view onto a fileDirectory.


    Notice:
        This class is not available in other ST-systems;
        Applications using it may not be portable.

    [author:]
        Claus Atzkern

    [see also:]
        Filename
        FileStream DirectoryStream OperatingSystem
"

! !

!DirectoryContents class methodsFor:'accessing'!

directoryNamed:aDirectoryName
    "returns the DirectoryContents for a directory named 
     aDirectoryName, aString or Filename
    "
    |directory dir max|

    directory := aDirectoryName asFilename.

    directory exists ifFalse:[
        ^ nil
    ].

    List isNil ifTrue:[
        List := OrderedCollection new
    ] ifFalse:[
        dir := self directoryAt:directory.

        dir notNil ifTrue:[
            ^ dir
        ].
        max := self maxCachedDirectories.

        List size > max ifTrue:[
            List := List select:[:aDir|
                (aDir size > 32 and:[aDir isObsolete not])
            ].
            List size > max ifTrue:[
                List removeFirst
            ]
        ]
    ].
    dir := (self new directory:directory).
    "/ only cache if the mod'Time is valid.
    dir modificationTime notNil ifTrue:[
        List add:dir.
    ].
    ^ dir.

    "Modified: / 24.9.1998 / 17:50:15 / cg"
! !

!DirectoryContents class methodsFor:'cache flushing'!

flushCache
    "flush list of rememebred directory contents"

    List := nil

    "
     self flushCache
    "

    "Created: / 11.2.2000 / 00:13:59 / cg"
!

lowSpaceCleanup
    "flush list of rememebred directory contents when low on memory"

    List := nil

    "
     self lowSpaceCleanup
    "

    "Created: / 18.2.1998 / 18:17:05 / cg"
    "Modified: / 24.9.1998 / 17:51:15 / cg"
!

preSnapshot
    "flush list of rememebred directory contents' before saving an image"

    List := nil

    "Created: / 18.2.1998 / 18:17:05 / cg"
! !

!DirectoryContents class methodsFor:'constants'!

maxCachedDirectories
    "returns number of maximum cached directories
    "
    ^ 20

    "Modified: / 25.2.1998 / 19:56:24 / cg"
! !

!DirectoryContents class methodsFor:'private'!

directoryAt:aFilename
    "checks whether directory already exists and is valid.
     If true the directory is returned otherwise nil
    "
    |index directory|

    List notNil ifTrue:[
        index := List findFirst:[:d| d directory = aFilename ].

        index ~~ 0 ifTrue:[
            directory := List at:index.

            directory isObsolete ifFalse:[
                ^ directory
            ].
            List removeAtIndex:index
        ]
    ].
    ^ nil
! !

!DirectoryContents class methodsFor:'queries'!

directoryNamed:aDirectoryName detect:aTwoArgBlock
    "evaluate the block, [:filename :isDirectory] on the directory
     contents of a directory named aDirectoryName, until the block
     returns true. If nothing detected false is returned
    "
    |directory name dir|

    directory := aDirectoryName asFilename.

    directory exists ifFalse:[
        ^ false
    ].

    (dir := self directoryAt:directory) notNil ifTrue:[
        dir contentsDo:[:aFile :isDir|
            (aTwoArgBlock value:aFile value:isDir) ifTrue:[^ true]
        ].
        ^ false
    ].    

    (directory directoryContents ? #()) do:[:fn |
        |file|

        file := directory construct:fn.
        (aTwoArgBlock value:file value:(file isDirectory)) ifTrue:[
            ^ true
        ]
    ].

"/    dir := DirectoryStream directoryNamed:(directory pathName).
"/
"/    dir isNil ifFalse:[
"/        [
"/            [dir atEnd] whileFalse:[
"/                (name := dir nextLine) notNil ifTrue:[
"/                    name := directory construct:name.
"/
"/                    (aTwoArgBlock value:name value:(name isDirectory)) ifTrue:[
"/                        ^ true
"/                    ]
"/                ]
"/            ].
"/        ] valueNowOrOnUnwindDo:[
"/            dir close.
"/        ]
"/    ].

    ^ false

    "Modified: / 24.9.1998 / 21:14:58 / cg"
! !

!DirectoryContents methodsFor:'accessing'!

directory
    "returns the directoy name as Filename
    "
    ^ directory
!

modificationTime
    "get the last modification time of the directory
    "
    ^ timeStamp
! !

!DirectoryContents methodsFor:'enumerating'!

contentsAndBaseNamesDo:aThreeArgBlock
    "evaluate the block on each file; the argument to the block is the
     filename, the baseName and true in case of a directory
     block arguments: [:fileName :aBaseName :isDirectory|
    "
    self indiciesDo:[:i|
        aThreeArgBlock value:(files at:i) value:(names at:i) value:(types at:i)
    ].
!

contentsDo:aTwoArgBlock
    "evaluate the block on each file; the argument to the block is the
     filename and true in case of a directory
     block arguments: [:fileName :isDirectory|
    "
    self indiciesDo:[:i|
        aTwoArgBlock value:(files at:i) value:(types at:i)
    ].
!

directoriesAndBasenamesDo:aTwoArgBlock
    "evaluate block on each directory; a Filename and Basename.
     The directories are sorted
    "
    self indiciesDo:[:i|
        (types at:i) ifTrue:[
            aTwoArgBlock value:(files at:i) value:(names at:i)
        ]
    ]
!

directoriesDo:aOneArgBlock
    "evaluate block on each directory; a Filename. The directories are sorted
    "
    self indiciesDo:[:i|
        (types at:i) ifTrue:[
            aOneArgBlock value:(files at:i)
        ]
    ]
!

filesAndBasenamesDo:aTwoArgBlock
    "evaluate block on each file; a Filename and a Basename.
     The files are sorted.
    "
    self indiciesDo:[:i|
        (types at:i) ifFalse:[
            aTwoArgBlock value:(files at:i) value:(names at:i)
        ]
    ]
!

filesDo:aOneArgBlock
    "evaluate block on each file; a Filename. The files are sorted.
    "
    self indiciesDo:[:i|
        (types at:i) ifFalse:[
            aOneArgBlock value:(files at:i)
        ]
    ]
! !

!DirectoryContents methodsFor:'instance creation'!

directory:aFilename
    "instance creation; setup attributes
    "
    |contents|

    directory := aFilename asFilename.
    timeStamp := directory modificationTime.
    contents  := directory directoryContents.
    names     := contents notNil ifTrue:[contents sort] ifFalse:[#()].

! !

!DirectoryContents methodsFor:'private'!

indiciesDo:aOneArgBlock
    "check whether files and types are set; than run from
     1 to size evaluating the block with the index
    "
    |file t f
     size "{ Class:SmallInteger }"|

    size := names size.

    types isNil ifTrue:[
        t := Array new:size.
        f := Array new:size.

        1 to:size do:[:i|
            file := directory construct:(names at:i).
            t at:i put:(file isDirectory).
            f at:i put:file
        ].
        types := t.
        files := f.
    ].
    1 to:size do:[:i| aOneArgBlock value:i]
! !

!DirectoryContents methodsFor:'queries'!

isObsolete
    "returns true if directory contents is obsolete
    "
    ^ (     directory exists not
        or:[timeStamp notNil and:[timeStamp < directory modificationTime]]
      )

    "Modified: / 17.8.1998 / 10:05:23 / cg"
!

size
    "get number of files including directories in the directory
    "
    ^ names size
! !

!DirectoryContents methodsFor:'testing'!

isEmpty
    "retuirns true if directory is empty
    "
    ^ names size == 0
!

notEmpty
    "returns true if directory is not empty
    "
    ^ names size ~~ 0
! !

!DirectoryContents class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/DirectoryContents.st,v 1.11 2000-08-22 13:56:28 cg Exp $'
! !