Filename.st
author Claus Gittinger <cg@exept.de>
Thu, 25 Apr 1996 18:20:46 +0200
changeset 1290 15ba3221b89b
parent 1286 4270a0b4917d
child 1317 cc737e0fdf48
permissions -rw-r--r--
documentation

"
 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:'NextTempFilenameIndex'
	poolDictionaries:''
	category:'System-Support'
!

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

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 examples will probably return false on your machine ;-).

    examples:

        'Makefile' asFilename readStream

        'newFile' asFilename writeStream

        Filename newTemporary writeStream

    [author:]
        Claus Gittinger

    [see also:]
        String
        FileStream DirectoryStream PipeStream Socket
        OperatingSystem
        Date Time
"
!

examples
"
    does a file/directory exist ?:

	|f|

	f := 'foobar' asFilename.
	^ f exists  


    is it a directory ?:

	|f|

	f := '/tmp' asFilename.
	^ f isDirectory.   

        
    get the working directory:

	^ Filename defaultDirectory


    get a files full pathname 
    (caring for relative names or symbolic links):

	|f|

	f := '..' asFilename.
	^ f pathName  


    get a directories directory:

	|f|

	f := Filename defaultDirectory.
	^ f directory 


    get a files directory:

	|f|

	f := './smalltalk' asFilename.
	^ f directory 


    getting access & modification times:


	|f|

	f := '/tmp' asFilename.
	^ f dates

    access time only:

	|f|

	f := '/tmp' asFilename.
	^ f dates at:#accessed  
        

    getting all information on a file/directory:


	|f|

	f := '/tmp' asFilename.
	^ f info


    getting a temporary file (unique name):

	|f|

	f := Filename newTemporary.
	^ f    


    creating, writing, reading and removing a temporary file:


	|f writeStream readStream|

	f := Filename newTemporary.
	writeStream := f writeStream.
	writeStream nextPutAll:'hello world'.
	writeStream cr.
	writeStream close.

	'contents (as seen by unix''s cat command:' printNL.
	OperatingSystem executeCommand:('cat ' , f pathName).

	readStream := f readStream.
	Transcript showCr:'contents as seen by smalltalk:'.
	Transcript showCr:(readStream upToEnd).
	readStream close.

	f delete.
        

    getting a directories contents:

	|f files|

	f := '.' asFilename.
	files := f directoryContents.
	Transcript showCr:'the files are:'.
	Transcript showCr:(files printString).


    editing a file:

	|f|

	f := '/tmp/fooBar' asFilename.
	(f writeStream) nextPutAll:'hello world'; close.

	f edit
"
! !

!Filename class methodsFor:'instance creation'!

currentDirectory
    "return a filename for the current directory"

    ^ self named:(FileDirectory currentDirectory pathName)

    "
     Filename currentDirectory 
    "
!

defaultDirectory
    "ST80 compatibility: same as currentDirectory"

    ^ self currentDirectory

    "
     Filename defaultDirectory 
    "
!

defaultDirectoryName
    "ST80 compatibility: return the defaultDirectories name (as a string)"

    ^ self defaultDirectory name

    "
     Filename defaultDirectoryName 
    "
!

fromComponents:aCollectionOfDirectoryNames
    "create & return a new filename from components given in
     aCollectionOfDirectoryNames. If the first component is the name of the
     root directory (i.e. '/') an absolute path-filename is returned."

    |sep s|

    sep := self separator asString.
    s := ''.
    aCollectionOfDirectoryNames keysAndValuesDo:[:index :component |
	index == 1 ifTrue:[
	    (component ~= sep 
	    or:[aCollectionOfDirectoryNames size == 1]) ifTrue:[
		s := s , component
	    ]
	] ifFalse:[
	    s := s , '/' , component
	].
    ].
    ^ self named:s

    "
     Filename fromComponents:#('/' 'foo' 'bar' 'baz')  
     Filename fromComponents:#('foo' 'bar' 'baz')  
     Filename fromComponents:#('/')  

     Filename fromComponents:
	 (Filename components:('.' asFilename pathName))

     Filename fromComponents:
	 (Filename components:('.' asFilename name)) 
    "

    "Modified: 29.2.1996 / 20:18:34 / cg"
!

fromUser
    "show a box to enter a filename. 
     Return a filename instance or nil (if cancel was pressed)."

    |name|

    name := Dialog requestFileName:'filename:' ifFail:nil.
    name notNil ifTrue:[^ self named:name].
    ^ nil

    "
     Filename fromUser
    "

    "Modified: 19.4.1996 / 13:57:44 / cg"
!

homeDirectory
    "return your homeDirectory.
     Some OperatingSystems do not support this - on those, the defaultDirectory
     (which is the currentDirectory) is returned."

    |s|

    s := OperatingSystem getHomeDirectory.
    s isNil ifTrue:[
	^ self defaultDirectory
    ].
    ^ s asFilename

    "
     Filename homeDirectory        
    "

    "Modified: 29.2.1996 / 21:00:31 / cg"
!

named:aString
    "return a filename for a directory named aString.
     This is the same as 'aString asFilename'."

    ^ (self basicNew) setName:aString

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

newTemporary
    "return a new unique filename - use this for temporary files.
     The filenames returned are '/tmp/stxtmp_xx_nn' where xx is our
     unix process id, and nn is a unique number, incremented with every
     call to this method.
     If any of the environment variables ST_TMPDIR or TMPDIR is set, 
     its value defines the temp directory."

    ^ self newTemporaryIn:self tempDirectory pathName

    "
     Filename newTemporary    
     Filename newTemporary     
    "

    "Modified: 7.9.1995 / 10:48:31 / claus"
    "Modified: 7.3.1996 / 14:51:33 / cg"
!

newTemporaryIn:aDirectoryPrefix
    "return a new unique filename - use this for temporary files.
     The filenames returned are in aDirectoryPrefix and named 'stxtmp_xx_nn',
     where xx is our unix process id, and nn is a unique number, incremented 
     with every call to this method.
     Notice: only a filename object is created and returned - no physical
     file is created by this method (i.e. you have to send #writeStream or
     whatever to it in order to really create something).
     See also: #newTemporary which looks for a good temp directory."

    |pid nm|

    NextTempFilenameIndex isNil ifTrue:[
	NextTempFilenameIndex := 1.
    ].

    "
     the following has to be made OS independent ...
    "
    pid := OperatingSystem getProcessId printString.
    nm := 'stxtmp_' , pid , '_' , NextTempFilenameIndex printString.
    NextTempFilenameIndex := NextTempFilenameIndex + 1.

    (aDirectoryPrefix isNil or:[aDirectoryPrefix asString isEmpty]) ifFalse:[
	nm := aDirectoryPrefix asFilename construct:nm
    ] ifTrue:[
	nm := nm asFilename
    ].
    ^ nm

    "temp files in '/tmp':

     Filename newTemporary    
    "

    "temp files somewhere 
     (not recommended - use above since it can be controlled via shell variables):

     Filename newTemporaryIn:'/tmp'    
     Filename newTemporaryIn:'/tmp'  
     Filename newTemporaryIn:'/usr/tmp'    
     Filename newTemporaryIn:'/'  
    "

    "a local temp file:

     Filename newTemporaryIn:''         
     Filename newTemporaryIn:nil         
     Filename newTemporaryIn:'.'         
     Filename newTemporaryIn:('source' asFilename) 
    "

    "Modified: 7.9.1995 / 10:48:31 / claus"
    "Modified: 7.3.1996 / 14:49:56 / cg"
!

tempDirectory
    "return the temp directory as a filename.
     If any of the environment variables ST_TMPDIR or TMPDIR is set, 
     its value defines the name, otherwise, '/tmp' is used.
     (at least on unix ...).

     Notice: do not hardcode '/tmp' into your programs - things may be
	     different on other OS's. Also, the user may want to set the
	     TMPDIR environment variable to have her temp files somewhere else.
	     (especially on SUNOS, the root partition is ALWAYS too small ..."

    |tempDir|

    tempDir := OperatingSystem getEnvironment:'ST_TMPDIR'.
    tempDir isNil ifTrue:[
	tempDir := OperatingSystem getEnvironment:'TMPDIR'.
	tempDir isNil ifTrue:[
	    tempDir := '/tmp'
	].
    ].
    ^ self named:tempDir

    "
     Filename tempDirectory           
     Filename tempDirectory pathName   
    "

    "Modified: 7.9.1995 / 10:48:31 / claus"
    "Created: 7.3.1996 / 14:51:18 / cg"
    "Modified: 7.3.1996 / 14:53:10 / cg"
! !

!Filename class methodsFor:'queries'!

components:aString
    "separate the pathName given by aString into 
     a collection containing the directory components and the files name as
     the final component.
     If the argument names an absolute path, the first component will be the
     name of the root directory (i.e. '/')."

    |components|

    components := aString asCollectionOfSubstringsSeparatedBy:(self separator).
    components first isEmpty ifTrue:[
	components at:1 put:(self separator asString)
    ].
    ^ components


    "
     Filename components:'/foo/bar/baz' 
     Filename components:'foo/bar/baz'  
    "

    "Modified: 29.2.1996 / 20:06:38 / cg"
!

defaultClass
    "ST-80 compatibility:
     in ST-80, different subclasses of Filename are used for different
     OperatingSystems; defaultClass is supposed to return an appropriate class.
     Since in ST/X, there is (currently) only one Filename class, return it here."

    ^ self
!

filenameCompletionFor:aString directory:inDirectory directoriesOnly:directoriesOnly filesOnly:filesOnly ifMultiple:aBlock
    "perform filename completion on aString in some directory;
     return the longest matching filename prefix as a string.
     If directoriesOnly and filesOnly are true, only directories and files
     are considered respectively. If multiple files match, the exception
     block aBlock is evaluated with a filename representing the directory
     (where the match was done) as argument.
     (this may be different from the inDirectory argument, if aString is absolute
      or starts with ../)"

    |s f matchSet nMatch name words dir|

    s := aString.
    "
     find the last word ...
    "
    words := s asCollectionOfWords.
    words size == 0 ifTrue:[
	aBlock value:'.' asFilename.
	^ ''
    ].

    f := words last asFilename.

    matchSet := f filenameCompletionIn:inDirectory.

    dir := f directory.

    directoriesOnly ifTrue:[
	matchSet := matchSet select:[:aFilename |
	    (dir construct:aFilename) isDirectory
	].
    ] ifFalse:[
	filesOnly ifTrue:[
	    matchSet := matchSet select:[:aFilename |
		(dir construct:aFilename) isDirectory not
	    ].
	]
    ].

    (nMatch := matchSet size) ~~ 1 ifTrue:[
	"
	 more than one possible completion -
	"
	aBlock value:f
    ].
    "
     even with more than one possible completion,
     f's name is now the common prefix
    "
    name := f asString.
    nMatch == 1 ifTrue:[
	"
	 exactly one possible completion -
	"
	f := dir construct:matchSet first.

	directoriesOnly ifFalse:[
	    f isDirectory ifTrue:[
		(name endsWith:(Filename separator)) ifFalse:[
		    name := name , '/'
		].
	    ].
	]
    ].

    "
     construct new contents, by taking
     last words completion
    "
    s := ''.
    1 to:(words size - 1) do:[:idx |
	s := s , (words at:idx) , ' '
    ].
    s := s , name.

    "/ special: if there was no change, and the string represented
    "/ is a directories name, add a directory separator
    s = aString ifTrue:[
	(s endsWith:Filename separator) ifFalse:[
	    s asFilename isDirectory ifTrue:[
		^ s , Filename separator asString
	    ]
	]
    ].

    ^ s
!

isCaseSensitive
    "return true, if filenames are case sensitive.
     We ask the OS about this, to be independent here."

    ^ OperatingSystem caseSensitiveFilenames
!

localNameStringFrom:aString
    "ST-80 compatibility.
     what does this do ? (used in FileNavigator-goody).
     GUESS: does it strip off the voulume-character on MSDOS systems ?"

    (aString startsWith:'/') ifTrue:[
	^ aString copyFrom:2
    ].
    ^ aString

    "Modified: 7.9.1995 / 10:44:56 / claus"
!

maxLength
    "return the maximum number of characters a filename may be in size.
     This depends on the OperatingSystem."

    ^ OperatingSystem maxFileNameLength

    "Created: 29.2.1996 / 20:57:11 / cg"
    "Modified: 29.2.1996 / 20:57:46 / cg"
!

parentDirectoryName 
    "return the name used for the parent directory.
     This is '..' for unix and dos-like systems. 
     (there may be more in the future."

     ^ OperatingSystem parentDirectoryName

     "
      Filename parentDirectoryName  
     "
!

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

suffixSeparator
    "return the filename suffix separator.
     Usually, this is $. for unix-like and msdos systems 
     (there is currently no knowns system, where this differs)"

     ^ $.

     "
      Filename suffixSeparator  
     "

    "Modified: 7.9.1995 / 11:10:43 / claus"
!

volumes
    "ST-80 compatibility.
     what does this do ? (used in FileNavigator-goody).
     GUESS: does it return the available drives on MSDOS systems ?"

    ^ #('/')

    "Modified: 7.9.1995 / 10:45:25 / claus"
! !

!Filename methodsFor:'comparing'!

= aFilename
    "return true, if the argument represents the same filename"

    |str|

    self species == aFilename species ifTrue:[
	str := aFilename asString.
	self class isCaseSensitive ifTrue:[
	    ^ nameString = str
	].
	^ nameString sameAs:str
    ].
    ^ false
!

hash
    "return an integer useful as a hash-key"

    ^ nameString hash
! !

!Filename methodsFor:'converting'!

asAbsoluteFilename
    "return the receiver converted to a filename with
     an absolute pathname."

    ^ self pathName asFilename
!

asFilename
    "return the receiver converted to a filename."

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

asString
    "return the receiver converted to a string"

    ^ nameString
!

makeLegalFilename 
    "convert the receveivers name to be a legal filename.
     The implementation may change in the future to be more
     OS specific."

    "
     actually, in Unix spaces are allowed - but it makes life
     so hard; therefore, replace them by underscores ...
    "
    nameString replaceAll:(Character space) by:$_.
    "
     need more - especially on SYS5.3 type systems, 
     we may want to contract the fileName to 14 characters.
    "
    ^ self

    "
     'hello world' asFilename makeLegalFilename 
    "
! !

!Filename methodsFor:'error handling'!

accessDeniedError:filename
    "{ Pragma: +optSpace }"

    "report an error that access to some file was denied"

    ^ OperatingSystem accessDeniedErrorSignal
	raiseRequestWith:filename
	errorString:('access denied: ' , filename asString)
!

fileCreationError:filename
    "{ Pragma: +optSpace }"

    "report an error that some file could not be created"

    ^ OperatingSystem accessDeniedErrorSignal
	raiseRequestWith:filename
	errorString:('cannot create/write file: ' , filename asString)
!

fileNotFoundError:filename 
    "{ Pragma: +optSpace }"

    "report an error that some file was not found"

    ^ OperatingSystem fileNotFoundErrorSignal
	raiseRequestWith:filename
	errorString:('file not found: ' , filename asString)
!

removeError:filename
    "{ Pragma: +optSpace }"

    "report an error that some file could not be removed"

    ^ OperatingSystem accessDeniedErrorSignal
	raiseRequestWith:filename
	errorString:('cannot remove: ' , filename asString)
!

reportError:string with:filename
    "{ Pragma: +optSpace }"

    "report an error"

    ^ OperatingSystem errorSignal
	raiseRequestWith:filename
	errorString:string
! !

!Filename methodsFor:'file access'!

appendingWriteStream
    "return a stream for appending to the file represented by the receiver.
     If the file does not already exist, it is created."

    ^ FileStream appendingOldFileNamed:nameString 
!

newReadWriteStream
    "return a stream for read/write the file represented by the receiver.
     If the file does not already exist, it is created."

    ^ FileStream newFileNamed:nameString
!

readStream
    "return a stream for reading from the file represented by the receiver.
     If the file does not already exist, nil is returned."

    ^ FileStream readonlyFileNamed:nameString

    "
     '/tmp/foo' asFilename readStream 
    "
!

readWriteStream
    "return a stream for read/write the file represented by the receiver.
     If the file does not already exist, nil is returned."

    ^ FileStream oldFileNamed:nameString
!

writeStream
    "return a stream for writing to the file represented by the receiver.
     If the file does not already exist, it is created."

    ^ FileStream newFileForWritingNamed:nameString

    "
     '/tmp/foo' asFilename writeStream 
    "
! !

!Filename methodsFor:'file operations'!

addAccessRights:aCollection
    "add the access rights as specified in aCollection for the file represented
     by the receiver. The argument must be a collection of symbols,
     such as #readUser, #writeGroup etc."

    |access|

    access := OperatingSystem accessModeOf:nameString.
    aCollection do:[:accessSymbol |
	access := access bitOr:(OperatingSystem accessMaskFor:accessSymbol).
    ].
    (OperatingSystem changeAccessModeOf:nameString to:access) ifFalse:[
	^ self accessDeniedError:self
    ]

    "
     'foo' asFilename writeStream close.
     'foo' asFilename addAccessRights:#(readUser readGroup readOthers).
     'foo' asFilename addAccessRights:#(writeUser writeGroup writeOthers).
     'foo' asFilename addAccessRights:#(executeUser executeGroup executeOthers).
    "
!

copyTo:newName
    "copy the file - the argument must be convertable to a filename.
     Return true if successful, false if not."

    |inStream outStream buffer bufferSize count newFile|

    bufferSize := 8 * 1024.
    buffer := ByteArray new:bufferSize.
    inStream := self readStream.
    inStream isNil ifTrue:[
	^ self fileNotFoundError:self 
    ].

    outStream := (newFile := newName asFilename) writeStream.
    outStream isNil ifTrue:[
	^ self fileCreationError:newFile
    ].

    [inStream atEnd] whileFalse:[
	count := inStream nextBytes:bufferSize into:buffer.
	(outStream nextPutBytes:count from:buffer) ~= count ifTrue:[
	    ^ self fileCreationError:newFile
	]
    ].
    outStream close.
    inStream close.

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

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

    self remove
!

makeDirectory
    "create a directory with the receivers name.
     Return true if successful, false if not."

    (OperatingSystem createDirectory:nameString) ifFalse:[
	^ self fileCreationError:self
    ]
!

makeExecutable
    "make the file executable - you must have permission to do so.
     For directories, execution means: 'allow changing into it'"

    ^ self addAccessRights:#(executeUser)

    "Created: 9.1.1996 / 15:32:47 / cg"
!

makeExecutableForAll
    "make the file executable for all - you must have permission to do so.
     For directories, execution means: 'allow changing into it'"

    ^ self addAccessRights:#(executeUser executeGroup executeOthers)

    "Created: 9.1.1996 / 15:32:28 / cg"
!

makeReadable
    "make the file readable for  the owner - you must have permission to do so."

    ^ self addAccessRights:#(readUser)
!

makeReadableForAll
    "make the file readable for all - you must have permission to do so."

    ^ self addAccessRights:#(readUser readGroup readOthers)
!

makeUnwritable
    "make the file unwritable for all - you must have permission to do so."

    ^ self removeAccessRights:#(writeUser writeGroup writeOthers)
!

makeWritable
    "make the file writableable for all - you must have permission to do so."

    ^ self addAccessRights:#(writeUser)
!

makeWritableForAll
    "make the file writable for all - you must have permission to do so."

    ^ self addAccessRights:#(writeUser writeGroup writeOthers)
!

moveTo:newName
    "copy the file represented by the receiver, then delete it.
     This is different to renaming in case of cross device moves.
     Raise an error if not successful."

    self copyTo:newName.
    self remove
!

recursiveMakeDirectory
    "create a directory with the receivers name and all required intermediate
     directories.
     Raise an error if not successful."

    (OperatingSystem recursiveCreateDirectory:nameString) ifFalse:[
	^ self fileCreationError:self
    ]

    "Created: 27.11.1995 / 23:36:40 / cg"
!

recursiveRemove
    "remove the directory and all of its subfiles/subdirectories.
     Raise an error if not successful."

    |ok|

    ok := OperatingSystem recursiveRemoveDirectory:nameString.
    ok ifFalse:[
	self removeError:self
    ].

    "
     'foo' asFilename makeDirectory.
     'foo/bar' asFilename writeStream close.
     ('foo' asFilename remove) ifFalse:[
	Transcript showCr:'could not remove foo'
     ]
    "
    "
     'foo' asFilename makeDirectory.
     'foo/bar' asFilename writeStream close.
     ('foo' asFilename recursiveRemove) ifFalse:[
	Transcript showCr:'could not remove foo'
     ]
    "

    "Created: 14.11.1995 / 11:19:29 / cg"
!

remove
    "remove the file/directory.
     Raise an error if not successful.
     Use #recursiveRemove in order to (recursively) remove non empty directories."

    |ok|

    self exists ifFalse:[ ^ self].
    self isDirectory ifTrue:[
	ok := OperatingSystem removeDirectory:nameString
    ] ifFalse:[
	ok := OperatingSystem removeFile:nameString
    ].
    ok ifFalse:[
	self removeError:self
    ].

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

    "
     'foo' asFilename makeDirectory.
     'foo/bar' asFilename writeStream close.
     ('foo' asFilename remove) ifFalse:[
	Transcript showCr:'could not remove foo'
     ]
    "

    "Modified: 10.1.1996 / 18:44:50 / cg"
!

removeAccessRights:aCollection
    "remove the access rights as specified in aCollection for the file represented
     by the receiver. The argument must be a collection of symbols,
     such as #readUser, #writeGroup etc.
     Raise an error if not successful."

    |access|

    access := OperatingSystem accessModeOf:nameString.
    aCollection do:[:accessSymbol |
	access := access bitAnd:(OperatingSystem accessMaskFor:accessSymbol) bitInvert.
    ].
    (OperatingSystem changeAccessModeOf:nameString to:access) ifFalse:[
	^ self accessDeniedError:self
    ].

    "
     'foo' asFilename writeStream close.
     'foo' asFilename removeAccessRights:#(readUser readGroup readOthers).
     'foo' asFilename removeAccessRights:#(writeUser writeGroup writeOthers).
     'foo' asFilename removeAccessRights:#(executeUser executeGroup executeOthers).
    "
!

renameTo:newName
    "rename the file - the argument must be convertable to a String.
     Raise an error if not successful."

    |ok|

    ok := OperatingSystem renameFile:nameString to:(newName asString).
    ok ifFalse:[
	self exists ifFalse:[
	    ^ self fileNotFoundError:self
	].
	^ self accessDeniedError:newName asFilename.
    ].

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

truncateTo:newSize
    "change the files size.
     This may not be supported on all operating systems"

    (OperatingSystem truncateFile:nameString to:newSize) ifFalse:[
	^ self reportError:'unsupported operation' with:self
    ]

    "
     |s|

     s := 'test' asFilename writeStream.
     s next:1000 put:$1.
     s close.
     ('test' asFilename fileSize) printNL.
     'test' asFilename truncateTo:100.
     ('test' asFilename fileSize) printNL.
    "
! !

!Filename methodsFor:'file queries'!

dates
    "return the files modification and access times as an object (currently a dictionary)
     that responds to the at: message with arguments 
     #modified, #accessed or #statusChanged."

    |info dates|

    info := OperatingSystem infoOf:nameString.
    info isNil ifTrue:[
	info := OperatingSystem linkInfoOf:nameString.
	info isNil ifTrue:[
	    ^ nil
	]
    ].
    dates := IdentityDictionary new.
    dates at:#modified put:(info at:#modified).
    dates at:#accessed put:(info at:#accessed).
    dates at:#statusChanged put:(info at:#statusChanged).
    ^ dates

    "
     Filename currentDirectory dates
     '../regression' asFilename dates
    "
!

fileSize
    "return the size of the file in bytes"

    |info|

    info := self info.
    info isNil ifTrue:[^ nil].
    ^ info at:#size
!

fileType
    "this returns a string describing the type of contents of
     the file. This is done using the unix 'file' command,
     (which usually is configurable by /etc/magic).
     On non-unix systems, this may return an empty string, not knowning
     about the contents."

    |stream typeString|

    typeString := ''.
    stream := PipeStream readingFrom:('file ' , self pathName).
    stream notNil ifTrue:[
	typeString := stream contents asString.
	stream close.
	typeString := typeString copyFrom:(typeString indexOf:$:) + 1.
	typeString := typeString withoutSeparators
    ] ifFalse:[
	"
	 could add some fallback code here, for systems, where no
	 file command is avaliable ...
	 ... or at least analyze directory info.
	"
    ].
    ^ typeString

    "
     'Makefile' asFilename fileType 
     '.' asFilename fileType     
     '/dev/null' asFilename fileType        
     'smalltalk.rc' asFilename fileType    
     'bitmaps/SBrowser.xbm' asFilename fileType    
    "
!

info
    "return the files info; that is a collection of file attributes,
     (actually a dictionary) where the keys are #type, #uid, #gid, #size etc.
     The actual amount and detail returned may depend on the OS used.
     On unix, if you ask for the info of a symbolic link, the target
     files info is returned. (see also: #linkInfo)

     On unix, the contents is:
	id            -> the inode number (integer)
	uid           -> the numeric user id of the files owner
	gid           -> the numeric group id of the files owner
	statusChanged -> the absoluteTime when the files status changed last
			 (i.e. protection change, owner change etc.)
	accessed      -> the absoluteTime when the file was last accessed
	modified      -> the absoluteTime when the file was last modified
	size          -> the size (in bytes) of the file
	type          -> the files type (#regular, #directory, #characterSpecial)
	mode          -> the files access protection bits (rwxrwxrwx mask).

     The minimum returned info (i.e. on all OS's) will consist of at least:
	modified
	size
	type

     Some OS's (VMS) may return more info.

     Dont expect things like uid/gid/mode to be there; write your application
     to either handle the cases where info-entries are not present,
     or (better) use one of isXXXX query methods. (Be prepared for DOS ...)
    "

    ^ OperatingSystem infoOf:nameString

    "
     Filename currentDirectory info
     '/dev/null' asFilename info 
     'Make.proto' asFilename info
     'source/Point.st' asFilename info 
     'source/Point.st' asFilename linkInfo 
     '../../libbasic/Point.st' asFilename info 
    "
!

linkInfo
    "return the files info if its a symbolic link; nil otherwise.
     On OS's which do not support symbolic links, nil is always returned.
     The information is the same as returned by #info, except that if the
     receiver represents a symbolic link, the links information 
     is returned 
     (while in this case, #info returns the info of the target file, 
      which is accessed via the symbolic link).

     In addition to the normal entries, Unix returns an additional entry:
	 path -> the target files pathname

     See the comment in #info for more details."

    ^ OperatingSystem linkInfoOf:nameString

    "
     Filename currentDirectory linkInfo 
     '/dev/null' asFilename linkInfo    
     'Make.proto' asFilename linkInfo   
     'Make.proto' asFilename linkInfo at:#path  
     'source/Point.st' asFilename linkInfo 
     '../../libbasic/Point.st' asFilename linkInfo 
    "
! !

!Filename methodsFor:'file utilities'!

edit
    "start an editView on the file represented by the receiver"

    EditTextView openOn:self asString

    "
     'smalltalk.rc' asFilename edit
    "
!

fileIn
    "load smalltalk code from the file"

    ^ self readStream fileIn
! !

!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).
     See also: #withSuffix: (which is different, but often needed)"

    ^ (self constructString:subname) asFilename

    "
     '/tmp' asFilename construct:'foo'    
     '/' asFilename construct:'foo'         
     '/usr/tmp' asFilename construct:'foo'
     '/foo/bar' asFilename construct:'baz' 
    "

    "Modified: 29.2.1996 / 20:55:06 / cg"
!

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

    |sepString|

    sepString := self class separator asString.
    nameString = sepString ifTrue:[
	"I am the root"
	^ sepString  , subname
    ].
    ^ nameString , sepString , subname asString

    "
     '/tmp' asFilename constructString:'foo'   
     '/' asFilename constructString:'foo'         
     '/usr/tmp' asFilename constructString:'foo'
     '/foo/bar' asFilename constructString:'baz' 
    "

    "Modified: 7.9.1995 / 10:15:22 / claus"
    "Modified: 29.2.1996 / 20:55:18 / cg"
! !

!Filename methodsFor:'misc'!

, aString
    "this allows filenames to understand how names are concatenated.
     Returns a string consisting of the receivers name, concatenated
     by aString. Notice this is NOT the same as construct:, which inserts
     a directory delimiter and returns a new fileName instance.
     See also: #withSuffix: which is new and better."

    ^ (nameString , aString asString)

    "
     'Makefile' asFilename , '.bak'        
     ('Makefile' asFilename , '.bak') asFilename  
     'Makefile' asFilename withSuffix:'bak' 
     'Makefile' asFilename construct:'.bak'     
    "

    "Modified: 29.2.1996 / 20:54:12 / cg"
! !

!Filename methodsFor:'printing & storing'!

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

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

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

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

!Filename methodsFor:'private accessing'!

setName:aString
    "set the filename"

    nameString := aString
! !

!Filename methodsFor:'queries'!

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

    ^ self isWritable

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

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

    ^ OperatingSystem isValidPath:nameString

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

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         
     '..' asAbsoluteFilename isAbsolute         
     'source/SBrowser.st' asFilename isAbsolute  
    "
!

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

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

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

    ^ OperatingSystem isReadable:nameString

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

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

    ^ self isAbsolute not
!

isSymbolicLink
    "return true, if the file represented by the receiver is a symbolic
     link. Notice that not all OS's support symbolic links; those that do
     not will always return false."

    ^ OperatingSystem isSymbolicLink:nameString

    "
     'Make.proto' asFilename isSymbolicLink  
     'Makefile' asFilename isSymbolicLink   
    "
!

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

    ^ OperatingSystem isWritable:nameString

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

separator
    "return the directory-separator character"

    ^ self class separator

    "Modified: 29.2.1996 / 20:52:01 / cg"
! !

!Filename methodsFor:'queries-contents'!

contentsOfEntireFile
    "return the contents of the file as a string"

    |s contents|

    s := self readStream.
    [
	contents := s contents
    ] valueNowOrOnUnwindDo:[s close].
    ^ contents
!

directoryContents
    "return the contents of the directory as a collection of strings"

    ^ (FileDirectory directoryNamed:self asString) contents

    "
     '.' asFilename directoryContents
    "
!

filesMatching:aPattern
    "given the receiver, representing a directory;
     return a collection of files matching a pattern."

    ^ self directoryContents select:[:name | aPattern match:name]

    "
     Filename currentDirectory filesMatching:'M*' 
     '/etc' asFilename filesMatching:'[a-z]*' 
     '../../libbasic' asFilename filesMatching:'[A-D]*.st'  
    "

    "Modified: 29.2.1996 / 20:30:31 / cg"
! !

!Filename methodsFor:'queries-path & name'!

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

    ^ OperatingSystem baseNameOf:nameString "/ (self pathName) 

    "
     '/foo/bar' asFilename baseName  
     '.' asFilename baseName          
     '..' asFilename baseName         
     '../..' asFilename baseName        
     '../../libbasic' asFilename baseName        
     '../../libpr' asFilename baseName        
     '../../libbasic/Object.st' asFilename baseName        
    "
!

directory
    "return the directory name part of the file/directory as a new filename.
     - thats a filename for the directory where the file/dir represented by
       the receiver is contained in.
     (this is almost equivalent to #directoryName or #head, but returns
      a Filename instance instead of a string )."

    ^ self directoryName asFilename

    "
     '/foo/bar' asFilename directory      
     '/foo/bar' asFilename directoryName  
     '/foo/bar' asFilename head  

     '.' asFilename directory        
     '..' asFilename directory       
     '../..' asFilename directory     
    "

    "Modified: 29.2.1996 / 20:50:14 / cg"
!

directoryName
    "return the directory name part of the file/directory as a string.
     - thats the name of the directory where the file/dir represented by
       the receiver is contained in.
     (this is almost equivalent to #directory, but returns
      a string instead of a Filename instance).
     See also: #directoryPathName.
     Compatibility note: use #head for ST-80 compatibility."

    ^ OperatingSystem directoryNameOf:nameString "/ (self pathName)

    "
     '/foo/bar/' asFilename directoryName    
     '/foo/bar/' asFilename directory     

     '/foo/bar' asFilename directoryName    
     'bitmaps' asFilename directoryName        
     'bitmaps' asFilename directoryPathName        
     '.' asFilename directoryName        
     '..' asFilename directoryName       
     '../..' asFilename directoryName     
     '../..' asFilename directoryPathName     
    "

    "Modified: 7.9.1995 / 10:42:03 / claus"
    "Modified: 29.2.1996 / 20:23:49 / cg"
!

directoryPathName
    "return the full directory pathname part of the file/directory as a string.
     - thats the full pathname of the directory where the file/dir represented by
       the receiver is contained in.
     See also: #directoryName, #directory"

    ^ OperatingSystem directoryNameOf:(self pathName)

    "
     '/foo/bar/' asFilename directoryPathName    
     '/foo/bar' asFilename directoryPathName    

     '.' asFilename directoryPathName      
     '.' asFilename directoryName     
     '.' asFilename directory          

     '..' asFilename directoryPathName       
     '..' asFilename directoryName       
     '..' asFilename directory

     '../..' asFilename directoryPathName     
    "

    "Modified: 7.9.1995 / 10:42:13 / claus"
    "Modified: 29.2.1996 / 20:24:44 / cg"
!

filenameCompletion
    "try to complete the receiver filename.
     This method has both a return value and a side effect on the receiver:
       it returns a collection of matching filename objects,
       and leaves changes the receivers filename-string to the longest common
       match.
     If none matches, the returned collection is empty and the recevier is unchanged.
     If there is only one match, the size of the returned collection is exactly 1,
     containing the fully expanded filename and the receivers name is changed to it."

    ^ self filenameCompletionIn:nil

    " 
     'mak' asFilename filenameCompletion  
     'Make' asFilename filenameCompletion 
     'Makef' asFilename filenameCompletion;yourself  
     '/u' asFilename filenameCompletion             
     '../../libpr' asFilename inspect filenameCompletion    
    "

    "Modified: 29.2.1996 / 20:28:36 / cg"
!

filenameCompletionIn:aDirectory
    "try to complete the receiver filename.
     This method has both a return value and a side effect on the receiver:
       it returns a collection of matching filename objects,
       and leaves changes the receivers filename-string to the longest common
       match.
     If none matches, the returned collection is empty and the recevier is unchanged.
     If there is only one match, the size of the returned collection is exactly 1,
     containing the fully expanded filename and the receivers name is changed to it."

    |dir baseName matching matchLen try allMatching 
     sepString parentString prefix nMatch|

    sepString := self class separator asString.
    (nameString endsWith:sepString) ifTrue:[
	^ #()
    ].

    parentString := self class parentDirectoryName.
    baseName := self baseName.
    baseName ~= nameString ifTrue:[
	prefix := self directoryName.
    ].

    self isAbsolute ifTrue:[
	dir := self directory
    ] ifFalse:[
	aDirectory isNil ifTrue:[
	    dir := self directory
	] ifFalse:[
	    dir := (aDirectory construct:nameString) directory
	]
    ].

    matching := OrderedCollection new.
    dir directoryContents do:[:fileName |
	((fileName ~= '.') and:[fileName ~= parentString]) ifTrue:[
	    (fileName startsWith:baseName) ifTrue:[
		matching add:fileName
	    ]
	]
    ].
    (nMatch := matching size) > 1 ifTrue:[
	"
	 find the longest common prefix
	"
	matchLen := baseName size.
	matchLen > matching first size ifTrue:[
	    try := baseName.
	    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
	"
	nameString := try
    ].

    "
     if I had a directory-prefix, change names in collection ...
    "
    prefix notNil ifTrue:[
	prefix = '/' ifTrue:[
	    "/ avoid introducing double slashes
	    prefix := ''
	].
	matching := matching collect:[:n | prefix , '/' , n].
	nMatch == 1 ifTrue:[
	    nameString := matching first
	] ifFalse:[
	    nMatch > 1 ifTrue:[
		nameString := prefix , '/' , nameString
	    ]
	]
    ] ifFalse:[
	nMatch == 1 ifTrue:[
	    nameString := matching first
	]
    ].

    "
     return the match-set, so caller can decide what to do
     (i.e. show the matches, output a warning etc ...)
    "
    ^ matching

    " trivial cases:

     '../' asFilename filenameCompletion    
     '/' asFilename filenameCompletion      
     '/usr/' asFilename filenameCompletion   

     'mak' asFilename filenameCompletion   
     'Make' asFilename filenameCompletion    
     'Makef' asFilename filenameCompletion
     '/u' asFilename filenameCompletion             
     '../../libpr' asFilename filenameCompletion    
    "

    "Modified: 29.2.1996 / 20:28:45 / cg"
!

head 
    "return the directory name as a string. 
     An alias for directoryName, for ST-80 compatiblity.
     (this is almost equivalent to #directory, but returns
      a string instead of a Filename instance)"

    ^ self directoryName

    "
     Filename currentDirectory head  
     'Makefile' asFilename head    
     '/foo/bar/baz.st' asFilename head  
    "

    "Modified: 29.2.1996 / 20:21:25 / cg"
!

name
    "return the name of the file represented by the receiver as a string.
     This may or may not be a relative name (i.e. include ..'s).
     See also: pathName"

    self isAbsolute ifTrue:[^ self pathName].
    ^ nameString

    "
     '/foo/bar' asFilename name        
     '/foo/bar' asFilename pathName    
     '.' asFilename name                
     '.' asFilename pathName             
     '../..' asFilename name             
     '../..' asFilename pathName 
     'bitmaps' asFilename name                
     'bitmaps' asFilename pathName             
     '/tmp/../usr' asFilename name       
     '/tmp/../usr' asFilename pathName    
     'source/..' asFilename name    
     'source/..' asFilename pathName    
     '/tmp/..' asFilename name    
     '/tmp/..' asFilename pathName    
    "

    "Modified: 18.1.1996 / 21:36:27 / cg"
!

pathName
    "return the full pathname of the file represented by the receiver,
     as a string. This will not include ..'s. See also: name"

    |parentName sep|

    sep := self class separator.
    (nameString startsWith:sep) ifTrue:[
	parentName := self class parentDirectoryName.
	(nameString findString:parentName) == 0 ifTrue:[
	    ^ nameString
	]
    ].
    ^ (FileDirectory directoryNamed:nameString) pathName

    "
     '/foo/bar' asFilename pathName
     '.' asFilename pathName 
     '../..' asFilename pathName 
     '../..' asFilename name 
     '/tmp/../usr' asFilename pathName  
    "

    "Modified: 18.1.1996 / 21:36:46 / cg"
!

suffix
    "return my suffix.
     The suffix is the namepart after the final period character,
     or the empty string, if the name does not contain a period."

    ^ self prefixAndSuffix at:2

    "
     'abc.st' asFilename suffix   
     'abc' asFilename suffix      
     'a.b.c' asFilename suffix    
    "

    "Modified: 7.9.1995 / 11:09:03 / claus"
!

tail
    "the files name without directory prefix as a string. 
     An alias for baseName, for ST-80 compatiblity."

    ^ self baseName

    "
     Filename currentDirectory tail 
     'Makefile' asFilename tail    
     '/foo/bar/baz.st' asFilename tail  
    "

    "Modified: 29.2.1996 / 20:19:50 / cg"
! !

!Filename methodsFor:'suffixes'!

prefixAndSuffix
    "return an array consisting of my prefix and suffix.
     The suffix is the namepart after the final period character,
     the prefix everything before, except for the period.
     (on some systems, the suffix-character may be different from a period).
     For example, foo.bar.baz has a prefix of 'foo.bar' and a suffix of '.baz'.

     Notice: there is currently no known system which uses other than
     the period character as suffixCharacter."

    |nm idx|

    nm := self baseName.
    idx := nm lastIndexOf:(self class suffixSeparator).
    idx == 0 ifTrue:[
	^ Array with:nm with:''
    ].
    ^ Array 
	with:(nm copyTo:idx-1)
	with:(nm copyFrom:idx+1)

    "
     'abc.st' asFilename prefixAndSuffix  
     'abc' asFilename prefixAndSuffix  
     'a.b.c' asFilename prefixAndSuffix 

     |parts| 
     parts := 'Object.st' asFilename prefixAndSuffix.
     ((parts at:1) , '.o') asFilename
    "

    "Modified: 7.9.1995 / 11:15:42 / claus"
!

withSuffix:aSuffix
    "return a new filename for the receivers name with a suffix.
     If the name already has a sufix, the new suffix replacaes it;
     otherwise, the new suffix simply appended to the name."

    ^ self class named:
	(self withoutSuffix name 
	 , self class suffixSeparator asString 
	 , aSuffix asString)

    "
     'abc.st' asFilename withSuffix:'o'         
     'abc' asFilename withSuffix:'o'             
     'a.b.c' asFilename withSuffix:'o'            
     '/foo/bar/baz.st' asFilename withSuffix:'c'   
     '/foo/bar/baz.c' asFilename withSuffix:'st'   
    "

    "Modified: 7.9.1995 / 11:15:42 / claus"
    "Modified: 29.2.1996 / 20:50:03 / cg"
!

withoutSuffix
    "return a new filename for the receivers name without the suffix.
     If the name has no suffix, the receiver is returned."

    |idx|

    idx := nameString lastIndexOf:(self class suffixSeparator).
    idx == 0 ifTrue:[^ self].

    ^ self class named:(nameString copyTo:(idx - 1))

    "
     'abc.st' asFilename withoutSuffix         
     'abc' asFilename withoutSuffix            
     'a.b.c' asFilename withoutSuffix           
     '/foo/bar/baz.c' asFilename withoutSuffix   
    "

    "Modified: 7.9.1995 / 11:15:42 / claus"
    "Modified: 29.2.1996 / 20:49:59 / cg"
! !

!Filename class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Filename.st,v 1.56 1996-04-25 16:01:07 cg Exp $'
! !