FileDir.st
author claus
Mon, 10 Oct 1994 01:29:28 +0100
changeset 159 514c749165c3
parent 92 0c73b48551ac
child 172 52750f9c44de
permissions -rw-r--r--
*** empty log message ***

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

Collection subclass:#FileDirectory
       instanceVariableNames:'pathName lazy'
       classVariableNames:'PathOfCurrentDirectory'
       poolDictionaries:''
       category:'Collections-Files'
!

FileDirectory comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
             All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Attic/FileDir.st,v 1.12 1994-10-10 00:26:00 claus Exp $
'!

!FileDirectory class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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/libbasic/Attic/FileDir.st,v 1.12 1994-10-10 00:26:00 claus Exp $
"
!

documentation
"
    FileDirectories represent directories in the underlying host system.
    They provide various methods to create/delete and query for files and/or
    directories.
"
! !

!FileDirectory class methodsFor:'initialization'!

initialize
    super initialize.
    ObjectMemory addDependent:self
!

update:something
    something == #restarted ifTrue:[
        PathOfCurrentDirectory := nil
    ]
! !

!FileDirectory class methodsFor:'instance creation'!

rootDirectory
    "create and return a new FileDirectory for the root directory"

    ^ (self basicNew) pathName:(OperatingSystem fileSeparator asString)

    "
     FileDirectory rootDirectory contents
     FileDirectory rootDirectory files
     FileDirectory rootDirectory isReadable
    "
!

currentDirectory
    "create and return a new FileDirectory for the current directory"

    ^ (self basicNew) pathName:'.'

    "
     FileDirectory currentDirectory contents
     FileDirectory currentDirectory files
     FileDirectory currentDirectory isReadable
     FileDirectory currentDirectory pathName
    "
!

directoryNamed:name
    "create and return a new FileDirectory for the directory
     with given pathname"

    ^ (self basicNew) pathName:name

    "
     (FileDirectory directoryNamed:'..') pathName
     (FileDirectory directoryNamed:'../..') files
    "
!

directoryNamed:name in:aFileDirectory
    "create and return a new FileDirectory for the directory with given name
     in another FileDirectory"

    |baseName sep|

    sep := OperatingSystem fileSeparator.
    ((name at:1) == sep) ifTrue:[
        ^ self directoryNamed:name
    ].
    (aFileDirectory isKindOf:FileDirectory) ifTrue:[
        baseName := aFileDirectory pathName
    ] ifFalse:[
        baseName := aFileDirectory
    ].
"
    (name = '..') ifTrue:[
        ^ (self basicNew) pathName:(OperatingSystem directoryNameOf:baseName)
    ].
"
    (name = '.') ifTrue:[^ aFileDirectory].

    (baseName = sep asString) ifFalse:[
        (baseName endsWith:sep) ifFalse:[
            baseName := baseName copyWith:sep
        ]
    ].
    ^ (self basicNew) pathName:(baseName , name)
! !

!FileDirectory methodsFor:'accessing'!

baseName
    "return my baseName
     - thats the directory name without leading parent-dirs"

    lazy ifTrue:[self getFullPathName].
    ^ OperatingSystem baseNameOf:pathName
!

directoryName
    "return my directoryName
     - thats the directory name where I'm in"

    lazy ifTrue:[self getFullPathName].
    ^ OperatingSystem directoryNameOf:pathName
!

pathName
    "return my full pathname"

    lazy ifTrue:[self getFullPathName].
    ^ pathName
!

pathName:dirName
    "set my pathname; return nil if not a valid path; self otherwise"

    pathName := dirName.
    (dirName startsWith:OperatingSystem fileSeparator) ifFalse:[
        lazy := true
    ] ifTrue:[
        (dirName includes:$.) ifTrue:[
            lazy := true
        ]
    ].
    ^ self
"
    (OperatingSystem isDirectory:pathName) ifFalse:[^ nil]
"
!

contents 
    "return a collection with all files and subdirectories in the receiver"

    |coll|

    coll := OrderedCollection new.
    self do:[:name |
        coll add:name
    ].
    (coll size ~~ 0) ifTrue:[
        coll sort
    ].
    ^ coll
!

directories
    "return a collection with all subdirectories in the receiver directory"

    |coll|

    coll := OrderedCollection new.
    self directoriesDo:[:name |
        coll add:name
    ].
    (coll size ~~ 0) ifTrue:[
        coll sort
    ].
    ^ coll
!

files
    "return a collection with all plain files in the receiver directory"

    |coll|

    coll := OrderedCollection new.
    self filesDo:[:name |
        coll add:name
    ].
    ^ coll sort
! !

!FileDirectory methodsFor:'private'!

getFullPathName
    "make my pathname be a full pathname - i.e. starting at root"

    |aStream command shortPathName fullPathName|

    (pathName = OperatingSystem fileSeparator asString) ifTrue:[
        lazy := false.
        ^ self
    ].

    "since currentDirectory is used very often, cache its path here"

    (pathName = '.') ifTrue:[
        PathOfCurrentDirectory notNil ifTrue:[
            pathName := PathOfCurrentDirectory.
            lazy := false.
            ^ self
        ]
    ].

    shortPathName := pathName.

    "some have a convenient function for this ..."
%{  /* STACK: 16000 */
#ifdef HAS_REALPATH
#   include <stdlib.h>
#   include <sys/param.h>

    char nameBuffer[MAXPATHLEN + 1];

    if (realpath(_stringVal(_INST(pathName)), nameBuffer)) {
        fullPathName = _MKSTRING(nameBuffer COMMA_CON);
    }
#endif
%}
.
    fullPathName notNil ifTrue:[
        pathName := fullPathName.
        lazy := false
    ] ifFalse:[
        "since there might be symbolic links and other stuff involved,
         better trust pwd than removing '..' by ourself
         - although this is very slow"

        command := 'cd ' , pathName , '; pwd'.
        aStream := PipeStream readingFrom:command.
        aStream isNil ifFalse:[
            (aStream atEnd) ifFalse:[
                fullPathName := aStream nextLine
            ].
            aStream close.
            fullPathName notNil ifTrue:[
                pathName := fullPathName.
                lazy := false
            ]
        ] ifTrue:[
            self error:('PipeStream for <' , command , '> failed').
            "by clearing lazy, we avoid triggering the error again"
            lazy := false
        ]
    ].

    "if it was the current dir, keep name for next query"
    (shortPathName = '.') ifTrue:[
        PathOfCurrentDirectory := fullPathName
    ]
! !

!FileDirectory methodsFor:'basic'!

createDirectory:newName
    "create a new filedirectory as a subdirectory of myself;
     return true if successful"

    |realName|

    (newName = '.') ifFalse:[
        (newName = '..') ifFalse:[
            ((newName at:1) == OperatingSystem fileSeparator) ifTrue:[
                realName := newName copyFrom:2
            ] ifFalse:[
                realName := newName
            ].
	    ^ OperatingSystem createDirectory:(self class fullPathNameOf:realName in:pathName)
        ]
    ].
    ^ false
!

removeFile:fileName
    "remove the file 'fileName' from myself; return true if successful"

    ^ OperatingSystem removeFile:(self class fullPathNameOf:fileName in:pathName).
!

removeDirectory:dirName
    "remove the directory 'dirName' from myself; return true if successful.
     If the directory is not empty, the containing files/directories are also
     removed."

    |path|

    path := self class fullPathNameOf:dirName in:pathName.
    (OperatingSystem removeDirectory:path) ifTrue:[^ true].
    ^ OperatingSystem recursiveRemoveDirectory:path
!
    
remove:aFileOrDirectoryName
    "remove the file or directory from myself; return true if successful"

    |path|

    path := self class fullPathNameOf:aFileOrDirectoryName in:pathName.
    (OperatingSystem isDirectory:path) ifTrue:[
        ^ OperatingSystem removeDirectory:path
    ].
    ^ OperatingSystem removeFile:path
!

link:oldFileName to:newFileName
    "link oldFileName to newFileName in myself, return true if successful"

    |path1 path2|

    path1 := self class fullPathNameOf:oldFileName in:pathName.
    path2 := self class fullPathNameOf:newFileName in:pathName.
    ^ OperatingSystem linkFile:path1 to:path2
!

renameFile:oldFileName newName:newFileName
    "rename the file; return true if successful"

    |path1 path2|

    path1 := self class fullPathNameOf:oldFileName in:pathName.
    path2 := self class fullPathNameOf:newFileName in:pathName.
    ^ OperatingSystem renameFile:path1 to:path2
! !

!FileDirectory class methodsFor:'private'!

fullPathNameOf:name in:path
    (name startsWith:OperatingSystem fileSeparator) ifTrue:[
        ^ name
    ].
    ^ path , OperatingSystem fileSeparator asString , name
! !

!FileDirectory methodsFor:'queries'!

id
    "return the directories file-id (inode number)"

    ^ OperatingSystem idOf:pathName
!

exists
    "return true if this directory exists"

    ^ OperatingSystem isDirectory:pathName

    "
     (FileDirectory directoryNamed:'fooBar') exists
     (FileDirectory directoryNamed:'/tmp') exists
    "
!

isEmpty
    "return true, if the directory is empty;
     redefined since '.' and '..' do not count as entries here."

    self do:[:fName |
        ((fName ~= '.') and:[fName ~= '..']) ifTrue:[^ false].
    ].
    ^ true
!

infoOf:name
    "return an array filled with file info for the file 'aFileName';
     return nil if such a file does not exist"

    ^ OperatingSystem infoOf:(self class fullPathNameOf:name in:pathName)
!

timeOfLastChange:name
    "return the timeStamp of a file in myself"

    ^ OperatingSystem timeOfLastChange:(self class fullPathNameOf:name in:pathName)
!

timeOfLastChange
    "return the timeStamp of myself"

    ^ OperatingSystem timeOfLastChange:pathName
!

accessModeOf:name
    "return the access-mode bits (rwxrwxrwx) of a file in myself"

    ^ OperatingSystem accessModeOf:(self class fullPathNameOf:name in:pathName)
!

changeAccessModeOf:name to:modeBits
    "set the access-mode bits (rwxrwxrwx) of a file in myself"

    ^ OperatingSystem changeAccessModeOf:(self class fullPathNameOf:name in:pathName)
                                      to:modeBits
!

typeOf:name
    "return the symbolic type of a file in myself"

    ^ OperatingSystem typeOf:(self class fullPathNameOf:name in:pathName)
!

exists:name
    "return true, if the given name exists in myself"

    ^ OperatingSystem isValidPath:(self class fullPathNameOf:name in:pathName)
!

isDirectory:name
    "return true, if the given name is that of a directory in myself"

    ^ OperatingSystem isDirectory:(self class fullPathNameOf:name in:pathName)
!

isReadable:name
    "return true, if the given file is readable"

    ^ OperatingSystem isReadable:(self class fullPathNameOf:name in:pathName)
!

isWritable:name
    "return true, if the given file is readable"

    ^ OperatingSystem isWritable:(self class fullPathNameOf:name in:pathName)
!

isExecutable:name
    "return true, if the given file is executable"

    ^ OperatingSystem isExecutable:(self class fullPathNameOf:name in:pathName)
! !

!FileDirectory methodsFor:'printing & storing'!

printString
    lazy ifTrue:[self getFullPathName].
    ^ '(a FileDirectory pathName:' , pathName, ')'
!

storeOn:aStream
    lazy ifTrue:[self getFullPathName].
    aStream nextPutAll:'(FileDirectory directoryNamed:'.
    aStream nextPutAll:pathName.
    aStream nextPut:$)
! !

!FileDirectory methodsFor:'more instance creation'!

directoryNamed:aName
    ^ self class directoryNamed:aName in:self pathName
! !

!FileDirectory methodsFor:'enumerating'!

where:testBlock do:aBlock
    "evaluate the argument, aBlock for every object in the directory
     for which testBlock evaluates to true."

    |aStream name|

    aStream := DirectoryStream directoryNamed:pathName.
    aStream isNil ifTrue:[^ nil].
    [aStream atEnd] whileFalse:[
        name := aStream nextLine.
        name notNil ifTrue:[
            (testBlock value:name) ifTrue:[
                aBlock value:name
            ]
        ]
    ].
    aStream close
!

do:aBlock
    "evaluate the argument, aBlock for every name in the directory"

    self where:[:name | true] do:aBlock
!

namesDo:aBlock
    "evaluate the argument, aBlock for every name in the directory.
     for ST-80 compatibility"

    self do:aBlock
!

filesDo:aBlock
    "evaluate the argument, aBlock for every plain file name in the directory"

    self where:[:name | (self isDirectory:name) not] do:aBlock
!

directoriesDo:aBlock
    "evaluate the argument, aBlock for every subdirectory name in the directory"

    self where:[:name | (self isDirectory:name) ifTrue:[
                            ((name ~= '.') and:[name ~= '..'])
                        ] ifFalse:[
                            false
                        ]
               ] do:aBlock
!

allFilesDo:aBlock
    "evaluate the argument, aBlock for every file name in the directory and in all
     subdirectories"

    |aStream command line|

    lazy ifTrue:[self getFullPathName].
    command := 'cd ' , pathName , '; find . -print'.
    aStream := PipeStream readingFrom:command.
    aStream isNil ifTrue:[^ nil].
    [aStream atEnd] whileFalse:[
        line := aStream nextLine.
        line notNil ifTrue:[
            (line = '.') ifFalse:[
                "cut off initial ./"
                line := line copyFrom:3
            ].
            aBlock value:line
        ]
    ].
    aStream close
!

allDirectoriesDo:aBlock
    "evaluate the argument, aBlock for every directory name
     in the directory and in all subdirectories"

    |aStream command line|

    lazy ifTrue:[self getFullPathName].
    command := 'cd ' , pathName , '; find . -type d -print'.
    aStream := PipeStream readingFrom:command.
    aStream isNil ifTrue:[^ nil].
    [aStream atEnd] whileFalse:[
        line := aStream nextLine.
        line notNil ifTrue:[
            (line = '.') ifFalse:[
                "cut off initial ./"
                line := line copyFrom:3
            ].
            aBlock value:line
        ]
    ].
    aStream close
! !