Filename.st
author claus
Mon, 10 Oct 1994 01:29:28 +0100
changeset 159 514c749165c3
parent 132 ab2cfccd218c
child 174 9e273c60e785
permissions -rw-r--r--
*** empty log message ***

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

Object subclass:#Filename
	 instanceVariableNames:'nameString'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'System-Support'!

Filename comment:'
COPYRIGHT (c) 1992 by Claus Gittinger
	     All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Filename.st,v 1.13 1994-10-10 00:26:07 claus Exp $
'!

!Filename class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1992 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/Filename.st,v 1.13 1994-10-10 00:26:07 claus Exp $
"
!

documentation
"
    Filenames; originally added for ST-80 compatibility, is
    taking over functionality from other classes (FileDirectory).

    Instances of Filename do not nescessarily represent valid or existing
    files - i.e. it is possible (and useful) to have instances for non-existing
    files around. In other words: the name-string is not checked automatically
    for being correct or existing.
    Thus, it is possible to do queries such as:

	'/fee/foo/foe' asFilename exists     
	'/not_existing' asFilename isDirectory 
	'/foo/bar' asFilename isReadable 
    (all of the above usually return false).


"
! !

!Filename class methodsFor:'instance creation'!

currentDirectory
    "return a filename for the current directory"

    ^ (self basicNew) setName:(FileDirectory currentDirectory pathName)

    "
     Filename currentDirectory 
    "
!

named:aString
    "return a filename for a directory named aString."

    ^ (self basicNew) setName:aString

    "
     Filename named:'/tmp/fooBar'
    "
! !

!Filename class methodsFor:'queries'!

separator
    "return the file/directory separator.
     Usually, this is $/ for unix-like systems 
     and $\ for dos-like ones (there may be more in the future)."

     ^ OperatingSystem fileSeparator

     "
      Filename separator  
     "
! !

!Filename methodsFor:'instance creation'!

construct:subname
    "taking the receiver as a directory name, construct a new
     filename for an entry within this directory (i.e. for a file
     or a subdirectory in that directory)."

    nameString = self class separator asString ifTrue:[
	"I am the root"
	^ (self class basicNew) setName:(nameString  , subname)
    ].
    ^ (self class basicNew) setName:(nameString , self class separator asString , subname)

    "
     ('/tmp' asFilename construct:'foo') asString    
     ('/' asFilename construct:'foo') asString         
     ('/usr/tmp' asFilename construct:'foo') asString
    "
! !

!Filename methodsFor:'converting'!

asString
    "return the receiver converted to a string"

    ^ nameString
!

asFilename
    "return the receiver converted to a filename."

    "Thats pretty easy here :-)"
    ^ self
! !

!Filename privateMethodsFor:'private accessing'!

setName:aString
    "set the filename"

    nameString := aString
! !

!Filename methodsFor:'queries'!

separator
    "return the directory-separator character (or string)"

    ^ self class separator
!

directoryName
    "return the directoryName of the file/directory.
     - thats the name of the directory where the file/dir represented by
       the receiver is contained in."

    ^ OperatingSystem directoryNameOf:(self pathName) "nameString"

    "
     '/foo/bar' asFilename directoryName
     '.' asFilename directoryName        
     '..' asFilename directoryName       
     '../..' asFilename directoryName     
    "
!

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

    ^ OperatingSystem baseNameOf:(self pathName) "nameString"

    "
     '/foo/bar' asFilename baseName  
     '.' asFilename baseName          
     '..' asFilename baseName         
     '../..' asFilename baseName       
    "
!

pathName
    "return the full pathname of the file represented by the receiver."

    (nameString startsWith:self class separator) ifTrue:[
	^ nameString
    ].
    ^ (FileDirectory directoryNamed:nameString) pathName

    "
     '/foo/bar' asFilename pathName
     '.' asFilename pathName 
     '../..' asFilename pathName 
    "
!

isAbsolute
    "return true, if the receiver represents an absolute pathname
     (in contrast to one relative to the current directory)."

    ^ (nameString startsWith:self class separator)

    "
     '/foo/bar' asFilename isAbsolute   
     '..' asFilename isAbsolute         
     'source/SBrowser.st' asFilename isAbsolute  
    "
!

isRelative
    "return true, if this name is interpreted relative to some
     directory (opposite of absolute)"

    ^ self isAbsolute not
!

isDirectory
    "return true, if the receiver represents an existing,
     readable directories pathname."

    ^ OperatingSystem isDirectory:nameString

    "
     '/foo/bar' asFilename isDirectory
     '/tmp' asFilename isDirectory
     'Makefile' asFilename isDirectory   
    "
!

exists
    "return true, if such a file exists."

    ^ OperatingSystem isValidPath:nameString

    "
     '/foo/bar' asFilename exists 
     '/tmp' asFilename exists  
     'Makefile' asFilename exists   
    "
!

isReadable
    "return true, if such a file exists and is readable."

    ^ OperatingSystem isReadable:nameString

    "
     '/foo/bar' asFilename isReadable   
     '/tmp' asFilename isReadable      
     'Makefile' asFilename isReadable   
    "
!

canBeWritten
    "same as isWritable - for ST-80 compatibility"

    ^ self isWritable
!

isWritable
    "return true, if such a file exists and is writable."

    ^ OperatingSystem isWritable:nameString

    "
     '/foo/bar' asFilename isWritable 
     '/tmp' asFilename isWritable   
     'Makefile' asFilename isWritable   
    "
!

isExecutable
    "return true, if such a file exists and is executable (by Unix's definition).
     For directories, true is returned if the directory can be entered.
     See isExecutableProgram for a related check."

    ^ OperatingSystem isExecutable:nameString

    "
     '/foo/bar' asFilename isExecutable 
     '/tmp' asFilename isExecutable   
     'Makefile' asFilename isExecutable   
     '/bin/ls' asFilename isExecutable   
    "
!

isExecutableProgram
    "return true, if such a file exists and is an executable program.
     (i.e. for directories, false is returned.)"

    ^ (OperatingSystem isExecutable:nameString)
      and:[(OperatingSystem isDirectory:nameString) not]

    "
     '/tmp' asFilename isExecutable         
     '/bin/ls' asFilename isExecutable       
     '/tmp' asFilename isExecutableProgram   
     '/bin/ls' asFilename isExecutableProgram    
    "
!

filenameCompletion
    "try to complete the filename. This method has both a side effect,
     and a return value:
	 it returns a collection of matching filename strings,
	 and sets (as side effect) the receivers filename to the longest common
	 match. 
     (i.e. if the size of the returned collection is exactly 1,
      the completion has succeeded and the receivers name has been changed to
      that. 
      If the returned collection is empty, nothing matched.
      If the size of the returned collection is greater than one, the receivers
      filename-string has been set to the longest common filename-prefix)"

    |dir name matching matchLen try allMatching|

    dir := self directoryName.
    name := self baseName.
    matching := OrderedCollection new.
    (FileDirectory directoryNamed:dir) do:[:fileName |
	(fileName startsWith:name) ifTrue:[
	    matching add:fileName
	]
    ].
    "
     if there is only one, change my name ...
    "
    matching size == 1 ifTrue:[
	dir = '/' ifTrue:[
	   dir := ''
	].
	nameString := dir , self class separator asString , matching first.
	matching first = name ifTrue:[
	    self isDirectory ifTrue:[
		nameString := nameString , self class separator asString
	    ]
	]
    ] ifFalse:[
	matching size > 1 ifTrue:[
	    "
	     find the longest common prefix
	    "
	    matchLen := name size.
	    matchLen > matching first size ifTrue:[
		try := name.
		allMatching := false
	    ] ifFalse:[
		try := matching first copyTo:matchLen.
		allMatching := true.
	    ].

	    [allMatching] whileTrue:[
		matching do:[:aName |
		    (aName startsWith:try) ifFalse:[
			allMatching := false
		    ]
		].
		allMatching ifTrue:[
		    matchLen <  matching first size ifTrue:[
			matchLen := matchLen + 1.
			try := matching first copyTo:matchLen.
		    ] ifFalse:[
			allMatching := false
		    ]
		] ifFalse:[
		    try := matching first copyTo:matchLen - 1.
		]
	    ].
	    "
	     and set my name to the last full match
	    "
	    dir = '/' ifTrue:[
	       dir := ''
	    ].
	    nameString := dir , self class separator asString , try
	]
    ].
    "
     return the match-set, so caller can decide what to do
     (i.e. show the matches, output a warning etc ...)
    "
    ^ matching

    "
     'Make' asFilename filenameCompletion;yourself 
     'Makef' asFilename filenameCompletion;yourself 
     '/u' asFilename filenameCompletion 
    "
! !

!Filename methodsFor:'file access'!

delete
    "remove the file - same as remove, for ST-80 compatibility"

    ^ self remove
!

remove
    "remove the file - the argument must be convertable to a String"

    ^ OperatingSystem removeFile:nameString

    "
     (FileStream newFileNamed:'foo') close.
     'foo' asFilename remove
    "
!

renameTo:newName
    "rename the file - the argument must be convertable to a String"

    ^ OperatingSystem renameFile:nameString to:(newName asString)

    "
     '/tmp/foo' asFilename renameTo:'/tmp/bar'
    "
!

copyTo:newName
    "copy the file - the argument must be convertable to a filename"

    |inStream outStream buffer bufferSize count|

    bufferSize := 8 * 1024.
    buffer := ByteArray new:bufferSize.
    inStream := self readStream.
    outStream := newName asFilename writeStream.
    (inStream isNil or:[outStream isNil]) ifTrue:[
	^ self error:'file copy failed'
    ].

    [inStream atEnd] whileFalse:[
	count := inStream nextBytes:bufferSize into:buffer.
	outStream nextPutBytes:count from:buffer.
    ].
    outStream close.

    "
     'Makefile' asFilename copyTo:'Makefile.foo'
     'smalltalk' asFilename copyTo:'/dev/null'
    "
!

fileIn
    "load smalltalk code from the file"

    ^ self readStream fileIn
!

newReadWriteStream
    "return a stream for read/write"

    ^ FileStream newFileNamed:nameString
!

readWriteStream
    "return a stream for read/write"

    ^ FileStream oldFileNamed:nameString
!

readStream
    "return a stream for reading"

    ^ FileStream readonlyFileNamed:nameString
!

writeStream
    "return a stream for writing"

    ^ FileStream newFileForWritingNamed:nameString
!

appendingWriteStream
    "return a stream for appending"

    ^ FileStream appendingOldFileNamed:nameString 
! !

!Filename methodsFor:'printing & storing'!

storeOn:aStream
    aStream nextPut:$(.
    nameString storeOn:aStream.
    aStream nextPutAll:' asFilename)'
!

printOn:aStream
    aStream nextPutAll:'FileName('''.
    nameString printOn:aStream.
    aStream nextPutAll:''')'
! !