FileDirectory.st
author Claus Gittinger <cg@exept.de>
Thu, 25 Apr 1996 18:20:46 +0200
changeset 1290 15ba3221b89b
parent 629 2ceefe9b5a19
child 1469 570ef7f8667b
permissions -rw-r--r--
documentation

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

documentation
"
    FileDirectories represent directories in the underlying host system.
    They provide various methods to create/delete and query for files and/or
    directories. Also, since FileDirectory inherits from Collection, it
    provides all enumeration and testing protocol. For example, you can
    loop over the filenames in a directory using 'aFileDirectory do:[:nm | ...]'.

    Notice:
        This class is not available in other ST-systems, while for example,
        ST-80 provides a Filename class.
        Therefore, Filename will take over much of the functionality in the near 
        future.

        Use instances of Filename if possible.

    [author:]
        Claus Gittinger

    [see also:]
        Filename
        FileStream DirectoryStream OperatingSystem
"
! !

!FileDirectory class methodsFor:'initialization'!

initialize
    "/
    "/ want to know about image restart
    "/
    ObjectMemory addDependent:self
!

update:something
    "/
    "/ currentDirectory may be different when restarted
    "/
    something == #restarted ifTrue:[
	PathOfCurrentDirectory := nil
    ]
! !

!FileDirectory class methodsFor:'instance creation'!

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

    ^ self directoryNamed:'.'

    "
     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 directoryNamed:(baseName , name)
!

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

    ^ self directoryNamed:(OperatingSystem fileSeparator asString)

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

!FileDirectory class methodsFor:'private'!

fullPathNameOf:name in:path
    |sep|

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

!FileDirectory methodsFor:'accessing'!

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

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

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

    |coll|

    coll := OrderedCollection new.
    self do:[:name |
	coll add:name
    ].
    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 sort.
    ^ coll
!

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

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

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

    |coll|

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

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 startsWith:'./') ifFalse:[
"/        (dirName includes:$.) ifTrue:[
	    lazy := true
	]
    ].
    ^ self
"
    (OperatingSystem isDirectory:pathName) ifFalse:[^ nil]
"
! !

!FileDirectory methodsFor:'basic'!

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

    |realName|

    (newName notNil and:[newName notEmpty]) ifTrue:[
	(newName ~= '.' and:[newName ~= '..']) ifTrue:[
	    ((newName at:1) == OperatingSystem fileSeparator) ifTrue:[
		realName := newName copyFrom:2
	    ] ifFalse:[
		realName := newName
	    ].
	    ^ OperatingSystem createDirectory:(self pathNameOf:realName)
	]
    ].
    ^ false
!

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

    |path1 path2|

    path1 := self pathNameOf:oldFileName.
    path2 := self pathNameOf:newFileName.
    ^ OperatingSystem linkFile:path1 to:path2
!

remove:aFileOrDirectoryName
    "remove the file or directory from myself; return true if successful"

    |path|

    path := self pathNameOf:aFileOrDirectoryName.
    (OperatingSystem isDirectory:path) ifTrue:[
	^ OperatingSystem removeDirectory:path
    ].
    ^ OperatingSystem removeFile:path
!

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 pathNameOf:dirName.
    (OperatingSystem removeDirectory:path) ifTrue:[^ true].
    ^ OperatingSystem recursiveRemoveDirectory:path
!

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

    ^ OperatingSystem removeFile:(self pathNameOf:fileName).
!

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

    |path1 path2|

    path1 := self pathNameOf:oldFileName.
    path2 := self pathNameOf:newFileName.
    ^ OperatingSystem renameFile:path1 to:path2
! !

!FileDirectory methodsFor:'converting'!

asFilename
    "return myself as a filename"

    ^ self pathName asFilename
!

asFilename:someFile
    "return a filename for a file named someFile in myself"

    ^ self asFilename construct:someFile
! !

!FileDirectory methodsFor:'enumerating'!

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
!

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
!

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
!

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

    self where:[:name | true] 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
!

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

    self do:aBlock
!

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
! !

!FileDirectory methodsFor:'more instance creation'!

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

!FileDirectory methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation of the receiver to aStream."

    lazy ifTrue:[self getFullPathName].
    aStream nextPutAll:'(a FileDirectory pathName:';
	    nextPutAll:pathName;
	    nextPutAll:')'
!

storeOn:aStream
    "append a printed representation of the receiver to aStream,
     which allows reconstructing it via readFrom:"

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

!FileDirectory methodsFor:'private'!

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

    |shortPathName|

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

    pathName := OperatingSystem pathNameOf:pathName.
    lazy := false.

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

pathNameOf:fileName
    ^ self class fullPathNameOf:fileName in:pathName
! !

!FileDirectory methodsFor:'queries'!

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

    ^ OperatingSystem accessModeOf:(self pathNameOf:name)
!

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

    ^ OperatingSystem changeAccessModeOf:(self pathNameOf:name) to:modeBits
!

exists
    "return true if this directory exists"

    ^ OperatingSystem isDirectory:pathName

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

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

    ^ OperatingSystem isValidPath:(self pathNameOf:name)
!

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

    ^ OperatingSystem idOf:pathName
!

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 pathNameOf:name)
!

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

    ^ OperatingSystem isDirectory:(self pathNameOf:name)
!

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
!

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

    ^ OperatingSystem isExecutable:(self pathNameOf:name)
!

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

    ^ OperatingSystem isReadable:(self pathNameOf:name)
!

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

    ^ OperatingSystem isWritable:(self pathNameOf:name)
!

species
    ^ OrderedCollection
!

timeOfLastChange
    "return the timeStamp of myself"

    ^ OperatingSystem timeOfLastChange:pathName
!

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

    ^ OperatingSystem timeOfLastChange:(self pathNameOf:name)
!

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

    ^ OperatingSystem typeOf:(self pathNameOf:name)
! !

!FileDirectory class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/FileDirectory.st,v 1.27 1996-04-25 16:15:05 cg Exp $'
! !
FileDirectory initialize!