Filename.st
author Claus Gittinger <cg@exept.de>
Tue, 31 Jul 2001 17:10:05 +0200
changeset 5897 793b0adad934
parent 5890 2c91b599a4dc
child 5928 77964582cb35
permissions -rw-r--r--
checkin from browser

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

"{ Package: 'stx:libbasic' }"

Object subclass:#Filename
	instanceVariableNames:'nameString'
	classVariableNames:'NextTempFilenameIndex ConcreteClass'
	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

    Beside lots of protocol to query for a files attributes, the class
    protocol offers methods for filename completion, to construct pathes
    (in an OS-independent way) and to create temporary files.
    Especially the path-construction methods (i.e. #construct:) are highly
    recommended in order to avoid having OS details (like directory separators
    being slash or backslash) spreaded in your application.

    [author:]
        Claus Gittinger

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

examples
"
    does a file/directory exist ?:
                                                                        [exBegin]
        |f|

        f := 'foobar' asFilename.
        ^ f exists  
                                                                        [exEnd]


    is it a directory ?:
                                                                        [exBegin]
        |f|

        f := '/tmp' asFilename.
        ^ f isDirectory.   
                                                                        [exEnd]

        
    get the working directory:
                                                                        [exBegin]
        ^ Filename defaultDirectory
                                                                        [exEnd]


    get a files full pathname 
    (caring for relative names or symbolic links):
                                                                        [exBegin]
        |f|

        f := '..' asFilename.
        ^ f pathName  
                                                                        [exEnd]


    get a directories directory:
                                                                        [exBegin]
        |f|

        f := Filename defaultDirectory.
        ^ f directory 
                                                                        [exEnd]


    get a files directory:
                                                                        [exBegin]
        |f|

        f := './smalltalk' asFilename.
        ^ f directory 
                                                                        [exEnd]


    getting access & modification times:
                                                                        [exBegin]
        |f|

        f := '/tmp' asFilename.
        ^ f dates
                                                                        [exEnd]

    access time only:
                                                                        [exBegin]
        |f|

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

    getting all information on a file/directory:
                                                                        [exBegin]
        |f|

        f := '/tmp' asFilename.
        ^ f info
                                                                        [exEnd]


    getting a temporary file (unique name):
                                                                        [exBegin]
        |f|

        f := Filename newTemporary.
        ^ f    
                                                                        [exEnd]

    creating, writing, reading and removing a temporary file:
                                                                        [exBegin]
        |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.
                                                                        [exEnd]
        

    getting a directories contents:
                                                                        [exBegin]
        |f files|

        f := Filename currentDirectory.
        files := f directoryContents.
        Transcript showCR:'the files are:'.
        Transcript showCR:(files printString).
                                                                        [exEnd]


    editing a file:
                                                                        [exBegin]
        |f|

        f := Filename newTemporary.
        (f writeStream) nextPutAll:'hello world'; close.

        f edit
                                                                        [exEnd]
"
! !

!Filename class methodsFor:'initialization'!

initialize
    "initialize for the OS we are running on"

    self initializeConcreteClass

    "
     self initialize
    "

    "Created: 7.9.1997 / 23:32:55 / cg"
!

initializeConcreteClass
    "initialize for the OS we are running on"

    OperatingSystem isMSDOSlike ifTrue:[
        ConcreteClass := PCFilename
    ] ifFalse:[
        OperatingSystem isVMSlike ifTrue:[
            ConcreteClass := OpenVMSFilename
        ] ifFalse:[
            OperatingSystem isUNIXlike ifTrue:[
                ConcreteClass := UnixFilename
            ] ifFalse:[
                ConcreteClass := nil
            ]
        ]
    ]

    "
     self initialize
    "

    "Modified: 7.9.1997 / 23:32:37 / cg"
!

reinitialize
    "initialize for the OS we are running on"

    self initializeConcreteClass

    "
     self initialize
    "

    "Created: 7.9.1997 / 23:33:02 / cg"
! !

!Filename class methodsFor:'instance creation'!

currentDirectory
    "return a filename for the current directory"

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass currentDirectory
    ].

    "/ fallBack - works on Unix & MSDOS (but not on VMS)

    ^ self named:'.'
    "/ ^ self named:('.' asFilename pathName)

    "
     Filename currentDirectory 
    "

    "Modified: 8.9.1997 / 00:24:15 / cg"
!

currentDirectoryName
    "return a filename for the current directory"

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass currentDirectoryName
    ].

    "/ fallBack - works on Unix & MSDOS (but not on VMS)

    ^ '.'

    "
     Filename currentDirectoryName    
    "

    "Modified: / 8.9.1997 / 00:24:15 / cg"
    "Created: / 21.10.1998 / 17:49:57 / cg"
!

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

defaultTempDirectoryName
    "return the default temp directory as a filename.
     This is used, if no special preferences were defined in
     any of the TEMP-environment variables (see tempDirectory)."

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass defaultTempDirectoryName
    ].

    ^ '/tmp'

    "
     Filename defaultTempDirectoryName           
    "

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

findDefaultDirectory
    "same as #defaultDirectory for ST80 compatibility"

    ^ self defaultDirectory

    "Created: 20.6.1997 / 17:00:29 / cg"
!

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|

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass fromComponents:aCollectionOfDirectoryNames
    ].

    "/ fallBack - works on Unix & MSDOS

    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 , sep , 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: 8.9.1997 / 00:23:16 / cg"
!

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

    |name|

    name := Dialog 
        requestFileName:'filename:' 
        default:nil
        fromDirectory:(FileSelectionBox lastFileSelectionDirectory).

    name size > 0 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
    ].
    ^ self named:s

    "
     Filename homeDirectory        
    "

    "Modified: 8.9.1997 / 00:25:23 / cg"
!

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

    |cls|

    cls := self.
    cls == Filename ifTrue:[
        cls := self concreteClass
    ].
    ^ (cls basicNew) setName:aString

    "
     Filename named:'/tmp/fooBar'
    "

    "Modified: 7.9.1997 / 23:30:06 / cg"
!

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.
     Notice, that no file is created by this - only a unique name
     is generated."

    ^ 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 unique 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 nameString fn|

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass newTemporaryIn:aDirectoryPrefix
    ].

    "/ care for existing leftOver tempFiles
    "/ from a previous boot of the OS
    "/ (i.e. my pid could be the same as when executed
    "/  the last time before system reboot ...)

    [fn isNil or:[fn exists]] whileTrue:[
        "/ although the above allows things to be redefined in concrete classes,
        "/ the following should work on all systems ...

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

        pid := OperatingSystem getProcessId printString.
        nameString := (self tempFileNameTemplate) bindWith:pid with:(NextTempFilenameIndex printString).
        NextTempFilenameIndex := NextTempFilenameIndex + 1.

        (aDirectoryPrefix isNil or:[aDirectoryPrefix asString isEmpty]) ifFalse:[
            fn := aDirectoryPrefix asFilename construct:nameString
        ] ifTrue:[
            fn := self named:nameString
        ]
    ].
    ^ fn

    "temp files in '/tmp':

     Filename newTemporary    
    "

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

     UnixFilename newTemporaryIn:'/tmp'    
     UnixFilename newTemporaryIn:'/tmp'  
     UnixFilename newTemporaryIn:'/usr/tmp'    
     UnixFilename 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: / 11.8.1998 / 22:51:43 / cg"
!

nullDevice
    "return the filename of the nullDevice (if available).
     returns nil, if the OperatingSystem does not support this."

    |s|

    s := OperatingSystem getNullDevice.
    s isNil ifTrue:[
        ^ nil
    ].
    ^ self named:s

    "
     Filename nullDevice        
    "

    "Created: / 19.5.1999 / 12:24:26 / cg"
!

rootDirectory
    "return a filename for the root directory"

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass rootDirectory
    ].

    "/ fallBack - works on Unix & MSDOS (but not on VMS)

    ^ self named:(self separator asString)

    "
     Filename rootDirectory
    "

    "Modified: 8.9.1997 / 00:24:15 / cg"
!

rootDirectoryOnVolume:aVolumeName
    "return a filename for the root directory on some volume"

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass rootDirectoryOnVolume:aVolumeName
    ].

    "/ fallBack - works on Unix (not on MSDOS or VMS)

    ^ self rootDirectory

    "
     Filename rootDirectoryOnVolume:'/phys/idefix'
     Filename rootDirectoryOnVolume:'d:'
    "

    "Modified: / 5.10.1998 / 12:45:39 / cg"
!

tempDirectory
    "return the temp directory as a filename.
     If any of the environment variables STX_TMPDIR, ST_TMPDIR,
     TMPDIR or TEMPDIR 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|

    #('STX_TMPDIR' 'ST_TMPDIR' 'TMPDIR' 'TEMPDIR' 'TEMP' 'TMP') do:[:envVar |
        tempDir isNil ifTrue:[
            tempDir := OperatingSystem getEnvironment:envVar.
        ].
    ].
    tempDir isNil ifTrue:[
        tempDir := self defaultTempDirectoryName
    ].
    ^ 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: 8.9.1997 / 00:08:11 / cg"
! !

!Filename class methodsFor:'defaults'!

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

    ^ ConcreteClass ? self

    "Created: 14.2.1997 / 16:36:13 / cg"
    "Modified: 7.9.1997 / 23:29:20 / 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."

    ^ ConcreteClass

    "Modified: 8.9.1997 / 00:36:01 / cg"
! !

!Filename class methodsFor:'misc'!

canonicalize:aPathString
    "convert the argument, aPathString to a good format.
     This should eliminate useless directory components (i.e. '././')
     and useless tree walks (i.e. '../foo/..')."

    ^ aPathString

    "Created: / 13.9.1997 / 10:50:01 / cg"
    "Modified: / 1.11.1997 / 12:44:57 / cg"
!

filterSeps:aFilenameString
    "ST80 compatibility:
     filter out (invalid) separators in aFilenameString.
     We recommend using #makeLegalFilename"

    ^ aFilenameString copyReplaceAll:(Character space) with:$_.

    "Created: / 1.11.1997 / 12:39:50 / cg"
    "Modified: / 18.7.1998 / 22:53:24 / cg"
!

suggest:aFilenameString 
    "return a fileNamestring based on the argument, 
     which is legal on the current platform."

    ^ self canonicalize:aFilenameString

    "Created: / 1.11.1997 / 12:42:39 / 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. '/')."

    |sep f vol rest components|

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass components:aString
    ].

    "/ the following works on Unix & MSDOS (but not on openVMS)
    "/ However, MSDOS drive-letters and network drives are
    "/ not correctly handled here.

    sep := self separator.
    f := aString asFilename.
    vol := f volume.
    vol size ~~ 0 ifTrue:[
        rest := f localPathName.
    ] ifFalse:[
        rest := aString
    ].

    components := rest asCollectionOfSubstringsSeparatedBy:sep.
    components first isEmpty ifTrue:[
        components at:1 put:(sep asString)
    ].

    "/ prepend volume to first component (the root directory)
    vol size ~~ 0 ifTrue:[
        components at:1 put:(vol , (components at:1)).
    ].
    components last isEmpty ifTrue:[
        ^ components copyWithoutLast:1
    ].
    ^ components

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

     Filename components:'\'     
     Filename components:'\foo'     
     Filename components:'\foo\'     
     Filename components:'\foo\bar'     
     Filename components:'\foo\bar\'     
     Filename components:'c:'        
     Filename components:'c:\'       
     Filename components:'c:\foo'      
     Filename components:'c:\foo\'     
     Filename components:'c:\foo\bar'     
     Filename components:'c:\foo\bar\'  
     Filename components:'\\idefix'     
     Filename components:'\\idefix\home'     
     Filename components:'\\idefix\home\bar'    
    "

    "Modified: / 24.9.1998 / 19:10:52 / cg"
!

directorySuffix
    "Return the OS dependent directory suffix string, or nil if there is none.
     The default is nil here, redefined for VMS"

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass directorySuffix
    ].

    ^ nil
!

errorReporter
    "who knows the signals to report errors?"
        
    ^ FileStream

    "Created: 2.7.1996 / 12:30:25 / stefan"
!

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.
     The boolean directoriesOnly and filesOnly control respectively,
     if only directories or only regular files are to be considered for completion.
     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 dir isAbsolute sep|

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass 
            filenameCompletionFor:aString 
            directory:inDirectory       
            directoriesOnly:directoriesOnly 
            filesOnly:filesOnly 
            ifMultiple:aBlock
    ].

    aString size == 0 ifTrue:[
        aBlock value:(self named:'.').
        ^ ''
    ].

    sep := self separator.

    "/ the following works on Unix & MSDOS (but not on openVMS)

    f := self named:aString.
    isAbsolute := f isAbsolute.

    matchSet := f filenameCompletionIn:inDirectory.
    dir := f directory.

    matchSet := matchSet select:[:aFilename |
        |f isDir|

        isAbsolute ifTrue:[
            f := aFilename asFilename
        ] ifFalse:[
            f := (dir construct:aFilename). 
        ].
        isDir := f isDirectory.
        directoriesOnly ifTrue:[    
            isDir
        ] ifFalse:[
            isDir 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.
        false "directoriesOnly" ifFalse:[
            (f exists and:[f isDirectory]) ifTrue:[
                (name endsWith:sep) ifFalse:[
                    name := name , sep asString
                ].
            ].
        ]
    ].

    s := name.

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

    ^ s

    "Modified: / 30.4.1999 / 09:40:13 / cg"
!

filesMatching:aPattern
    "return a collection of strings, representing the names
     of files matching aPattern.
     If aPattern contains a directory path, files are tried there;
     otherwise, files from the currentDirectory are tried.
     The returned strings are the expanded names, in the same form
     as given in pattern.
     The pattern should be a simple pattern."

    |basePattern dir d files|

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass filesMatching:aPattern
    ].

    "/ the following works on Unix & MSDOS (but not on openVMS)

    dir := aPattern asFilename directoryName.
    basePattern := aPattern asFilename baseName.
    d := dir asFilename.
    files := dir asFilename filesMatchingWithoutDotDirs:basePattern.
    dir = '.' ifTrue:[^ files].
    ^ files collect:[:base | d constructString:base].

    "
     Filename filesMatching:'*'   
     Filename filesMatching:'/*'
     Filename filesMatching:'/usr/local/*'
    "

    "Modified: 8.9.1997 / 00:32:31 / cg"
!

isBadCharacter:aCharacter
    "return true, if aCharacter is unallowed in a filename."

    |ascii|

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass isBadCharacter:aCharacter
    ].

    ascii := aCharacter asciiValue.
    ascii < 32 ifTrue:[
        ^ true  "/ a control character
    ].
    ascii == 16rFF ifTrue:[
        ^ true  "/ delete character
    ].
    ^ false

    "Modified: 8.9.1997 / 00:32:59 / cg"
!

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

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass isCaseSensitive
    ].

    ^ OperatingSystem caseSensitiveFilenames

    "Modified: 8.9.1997 / 00:33:32 / cg"
!

localNameStringFrom:aString
    "ST-80 compatibility.
     what does this do ? (used in FileNavigator-goody).
     GUESS: 
	does it strip off any volume characters and make a path relative ?"

    |sep|

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass localNameStringFrom:aString
    ].

    sep := self separator asString.
    (aString startsWith:sep) ifTrue:[
	^ aString copyFrom:sep size + 1
    ].
    ^ aString

    "Modified: 7.9.1995 / 10:44:56 / claus"
    "Modified: 8.9.1997 / 00:33:51 / cg"
!

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

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass maxComponentLength
    ].
    ^ OperatingSystem maxFileNameLength
!

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

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass maxLength
    ].
    ^ OperatingSystem maxPathLength

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

nullFilename
    "Return the OS dependent filename for /dev/null, or nil if there is none.
     The default is nil here"

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass nullFilename
    ].

    ^ nil

    "Created: / 12.1.1998 / 12:15:30 / stefan"
!

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

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass parentDirectoryName
    ].

    ^ OperatingSystem parentDirectoryName

    "
     Filename parentDirectoryName  
    "

    "Modified: 8.9.1997 / 00:34:39 / cg"
!

separator
    "return the file/directory separator.
     This is to be redefined in concrete classes;
     the following default usually leads to a flat view of
     the fileSystem (huh - BS2000 ?)"

     (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass separator
     ].
     ^ $_

     "
      Filename separator  
     "

    "Modified: 8.9.1997 / 00:20:28 / cg"
!

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

     ^ $.

     "
      Filename suffixSeparator  
     "

    "Modified: 7.9.1995 / 11:10:43 / claus"
    "Modified: 30.4.1996 / 12:14:25 / cg"
!

tempFileNameTemplate
    "return a template for temporary files.
     This is expanded with the current processID and a sequenceNumber
     to generate a unique filename."

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass tempFileNameTemplate
    ].

    ^ 'stxtmp_%1_%2'

    "Created: 8.9.1997 / 00:01:46 / cg"
    "Modified: 8.9.1997 / 00:35:02 / cg"
!

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

    (self ~~ ConcreteClass) ifTrue:[
        ^ ConcreteClass volumes
    ].

    ^ OperatingSystem getDriveList

    "Modified: 7.9.1995 / 10:45:25 / claus"
    "Modified: 8.9.1997 / 00:35:19 / cg"
! !

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

contentsIsPrefixOf:aFilename
    "return true if the contents of the file represented by the receiver
     is the same as or a prefix of the contents of the file represented by the argument, aFilename.
     This compares the files actual contents; not the filenames."

    |f2 s1 s2 buffer1 buffer2 rslt n|

    f2 := aFilename asFilename.
    self fileSize > f2 fileSize ifTrue:[^ false].

    buffer1 := ByteArray new:8192.
    buffer2 := ByteArray new:8192.

    s1 := self readStream.
    s1 isNil ifTrue:[
        ^ self error:('cannot open %1 for reading' bindWith:nameString)
    ].
    s2 := f2 readStream.
    s2 isNil ifTrue:[
        ^ self error:('cannot open %1 for reading' bindWith:aFilename asFilename name)
    ].
    s1 binary.
    s2 binary.

    [s1 atEnd] whileFalse:[
        n := s1 nextBytes:8192 into:buffer1 startingAt:1.
        n == 0 ifTrue:[
            "/ receiver shorter.
            s1 close. s2 close.
            ^ true
        ].
        (s2 nextBytes:n into:buffer2 startingAt:1) ~~ n ifTrue:[
            "/ aFilename shorter
            s1 close. s2 close.
            ^ false
        ].
        buffer1 ~= buffer2 ifTrue:[
            s1 close. s2 close.
            ^ false
        ]
    ].
    "/ receiver shorter or same size.
    s1 close. s2 close.
    ^ true

    "
     |s|

     s := 'testFile1' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33333'.
     s close.

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33333'.
     s close.

     ('testFile1' asFilename contentsIsPrefixOf:'testFile2'  ) ifFalse:[self halt].

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33333'.
     s nextPutAll:'44444'.
     s close.

     ('testFile1' asFilename contentsIsPrefixOf:'testFile2'  ) ifFalse:[self halt].

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s close.

     ('testFile1' asFilename contentsIsPrefixOf:'testFile2'  ) ifTrue:[self halt].

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33334'.
     s close.

     ('testFile1' asFilename contentsIsPrefixOf:'testFile2'  ) ifTrue:[self halt].

    "
!

contentsStartsWithContentsOf:aFilename
    "return true if the contents of the file represented by aFilename
     is the same as or a prefix of the contents of the file represented by the receiver.
     This compares the files actual contents; not the filenames."

    ^ aFilename asFilename contentsIsPrefixOf:self

    "
     |s|

     s := 'testFile1' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33333'.
     s close.

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33333'.
     s close.

     ('testFile2' asFilename contentsStartsWithContentsOf:'testFile1'  ) ifFalse:[self halt].

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33333'.
     s nextPutAll:'44444'.
     s close.

     ('testFile2' asFilename contentsStartsWithContentsOf:'testFile1'  ) ifFalse:[self halt].

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s close.

     ('testFile2' asFilename contentsStartsWithContentsOf:'testFile1'  ) ifTrue:[self halt].

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33334'.
     s close.

     ('testFile2' asFilename contentsStartsWithContentsOf:'testFile1'  ) ifTrue:[self halt].

    "
!

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

    ^ nameString hash
!

sameContentsAs:aFilename
    "return true if the file represented by the receiver has the
     same contents as the file represented by the argument, aFilename.
     This compares the files actual contents; not the filenames."

    |f2|

    f2 := aFilename asFilename.
    f2 fileSize = self fileSize ifFalse:[^ false].
    ^ self contentsIsPrefixOf:f2.

    "
     'Make.proto' asFilename sameContentsAs:'Makefile'  
    "

    "
     |s|

     s := 'testFile1' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33333'.
     s close.

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33333'.
     s close.

     ('testFile1' asFilename sameContentsAs:'testFile2'  ) ifFalse:[self halt].

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33333'.
     s nextPutAll:'44444'.
     s close.

     ('testFile1' asFilename sameContentsAs:'testFile2'  ) ifTrue:[self halt].

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s close.

     ('testFile1' asFilename sameContentsAs:'testFile2'  ) ifTrue:[self halt].

     s := 'testFile2' asFilename writeStream.
     s nextPutAll:'11111'.
     s nextPutAll:'22222'.
     s nextPutAll:'33334'.
     s close.

     ('testFile1' asFilename sameContentsAs:'testFile2'  ) ifTrue:[self halt].

    "
! !

!Filename methodsFor:'converting'!

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

    ^ self class named:self pathName
!

asFilename
    "return the receiver converted to a filename; here, thats the receiver itself."

    "Thats pretty easy here :-)"
    ^ self

    "Modified: 12.11.1996 / 12:40:03 / cg"
!

asString
    "return the receiver converted to a string"

    ^ nameString
!

components
    "return the receivers filename components - that is the name of each directory
     along the pathName (that DOES include the root directory)"

    ^ self class components:self name

    "
     '.' asFilename asAbsoluteFilename components 
     'Makefile' asFilename asAbsoluteFilename components     
    "
!

makeLegalFilename 
    "convert the receivers name to be a legal filename.
     This removes/replaces invalid characters and/or compresses
     the name as required by the OS.
     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 includes:Character space) ifTrue:[
        nameString := nameString copyReplaceAll:(Character space) with:$_.
    ].
    "
     need more - especially on SYS5.3 type systems, 
     we may want to contract the fileName to 14 characters.
    "
    ^ self

    "
     'hello world' asFilename makeLegalFilename 
    "

    "Modified: / 20.7.1998 / 13:16:51 / cg"
!

withEncoding:encodingSymbol
    "dummy for now - for ST80 compatibility"

    ^ self

    "Created: 20.6.1997 / 17:01:28 / cg"
! !

!Filename methodsFor:'enumerating-contents'!

allDirectoriesDo:aBlock
    "evaluate aBlock for all (recursive) directories contained in the directory represented by the receiver.
     The block is invoked with a filename-arguments.
     The enumerations order within a directory is undefined - i.e. usually NOT sorted by
     filenames (but by creation time - on some systems).
     This excludes entries for '.' or '..'.
     NoOp for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before."

    self recursiveDirectoryContentsDo:[:eachFileOrDirectoryName | 
        |eachFileOrDirectory|

        eachFileOrDirectory := self construct:eachFileOrDirectoryName.
        eachFileOrDirectory isDirectory ifTrue:[
            aBlock value:eachFileOrDirectory
        ]
    ].

    "
     '.' asFilename allDirectoriesDo:[:fn | Transcript showCR:fn name].
     '.' asFilename directoriesDo:[:fn | Transcript showCR:fn name].
    "
!

directoriesDo:aBlock
    "evaluate aBlock for directories contained in the directory represented by the receiver.
     The block is invoked with a filename-arguments.
     The enumerations order is undefined - i.e. usually NOT sorted by
     filenames (but by creation time - on some systems).
     This excludes entries for '.' or '..'.
     NoOp for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before."

    self directoryContentsAsFilenamesDo:[:eachFileOrDirectory |
        eachFileOrDirectory isDirectory ifTrue:[
            aBlock value:eachFileOrDirectory
        ]
    ].

    "
     '.' asFilename directoriesDo:[:fn | Transcript showCR:fn baseName].
    "
!

directoryContentsAsFilenamesDo:aBlock
    "evaluate aBlock for each file in the directory represented by the receiver.
     The block is invoked with a filename-argument.
     The enumerations order is undefined - i.e. usually NOT sorted by
     filenames (but by creation time - on some systems).
     This excludes entries for '.' or '..'.
     NoOp for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before.
     Notice: this enumerates fileName objects; see also
     #directoryContentsDo:, which enumerates strings."

    self directoryContentsAsFilenames do:aBlock.

    "
     '.' asFilename directoryContentsAsFilenamesDo:[:fn | Transcript showCR:fn pathName].
    "

    "Modified: / 18.9.1997 / 18:42:23 / stefan"
    "Modified: / 23.12.1999 / 20:56:35 / cg"
!

directoryContentsDo:aBlock
    "evaluate aBlock for each file in the directory represented by the receiver.
     The block is invoked with a string-argument.
     The enumerations order is undefined - i.e. usually NOT sorted by
     filenames (but by creation time - on some systems).
     This excludes entries for '.' or '..'.
     NoOp for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before.
     Notice: this enumerates strings; see also
     #directoryContentsDo:, which enumerates fileName objects."

    |s fn|

    s := DirectoryStream directoryNamed:(self osNameForDirectoryContents).
    s isNil ifTrue:[^ nil].

    [
        [s atEnd] whileFalse:[
            fn := s nextLine.
            aBlock value:fn
        ]
    ] valueNowOrOnUnwindDo:[
        s close
    ].

    "
     '.' asFilename directoryContentsDo:[:fn | Transcript showCR:fn].
    "

    "Modified: / 18.9.1997 / 18:42:23 / stefan"
    "Modified: / 23.12.1999 / 20:56:35 / cg"
!

recursiveDirectoryContentsDo:aBlock 
    "evaluate aBlock for all files and directories found under the receiver.
     The block is invoked with a string-argument.
     The walk is bread-first.
     This excludes any entries for '.' or '..'.
     Subdirectory files are included with a relative pathname.
     Warning: this may take a long time to execute (especially with deep and/or remote fileSystems)."

    self recursiveDirectoryContentsDo:aBlock directoryPrefix:''

    "
     '.' asFilename recursiveDirectoryContentsDo:[:f | Transcript showCR:f] 
    "
!

recursiveDirectoryContentsDo:aBlock directoryPrefix:aPrefix
    "evaluate aBlock for all files and directories found under the receiver.
     The block is invoked with a string-argument.
     The walk is bread-first.
     This excludes any entries for '.' or '..'.
     Subdirectory files are included with a relative pathname.
     Warning: this may take a long time to execute (especially with deep and/or remote fileSystems)."

    |fileNames dirNames p|

    fileNames := OrderedCollection new.
    dirNames := OrderedCollection new.
    self directoryContentsDo:[:f | |t|
        t := self construct:f.
        t isDirectory ifTrue:[
            t isSymbolicLink ifFalse:[
                dirNames add:f
            ]
        ] ifFalse:[
            fileNames add:f
        ]
    ].

    aPrefix size > 0 ifTrue:[
        p := aPrefix , self separator asString
    ] ifFalse:[
        p := ''
    ].

    fileNames do:[:aFile | aBlock value:(p , aFile)].
    dirNames do:[:dN |
        aBlock value:(p , dN).
        (self construct:dN)
            recursiveDirectoryContentsDo:aBlock directoryPrefix:(p , dN)
    ].

    "
     '.' asFilename recursiveDirectoryContentsDo:[:f | Transcript showCR:f] 
     '/etc' asFilename recursiveDirectoryContentsDo:[:f | Transcript showCR:f] 
    "
!

withAllDirectoriesDo:aBlock
    "evaluate aBlock for myself and all (recursive) directories contained in the directory represented by the receiver.
     The block is invoked with a filename-arguments.
     The enumerations order within a directory is undefined - i.e. usually NOT sorted by
     filenames (but by creation time - on some systems).
     This excludes entries for '.' or '..'.
     NoOp for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before."

    self isDirectory ifTrue:[
        aBlock value:self.
        self allDirectoriesDo:aBlock
    ].

    "
     '.' asFilename withAllDirectoriesDo:[:fn | Transcript showCR:fn name].
    "
! !

!Filename methodsFor:'error handling'!

accessDeniedError:filename
    "{ Pragma: +optSpace }"

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

    |errNo errString|

    errNo := OperatingSystem lastErrorNumber.
    errString := OperatingSystem lastErrorString.
    errString size == 0 ifTrue:[
        errString := ''.
    ] ifFalse:[
        errString := ' (' , errString , ')'
    ].

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

    "Modified: / 26.9.1999 / 16:11:44 / cg"
!

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

appendStream
    "return a stream for appending to the file represented by the receiver.
     If the file does not already exist, it is created.
     Same as #appendingWriteStream for ST-80 compatibility."

    ^ self appendingWriteStream
!

appendingWriteStream
    "return a stream for appending to the file represented by the receiver.
     If the file does not already exist, it is created;
     if it does exist, writes are appended at the end."

    ^ FileStream appendingOldFileNamed:(self osNameForAccess)

    "
     |s|

     s := '/tmp/foo' asFilename writeStream.
     s nextPutAll:'1234567890'.
     s close.

     s := '/tmp/foo' asFilename appendingWriteStream.
     s nextPutAll:'abcdef'.
     s close.

     '/tmp/foo' asFilename contents   
    "
!

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

    ^ FileStream newFileNamed:(self osNameForAccess)

    "
     |s|

     s := '/tmp/foo' asFilename writeStream.
     s nextPutAll:'1234567890'.
     s close.

     s := '/tmp/foo' asFilename newReadWriteStream.
     s nextPutAll:'12345'.
     s close.

     '/tmp/foo' asFilename contents   
    "
!

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:(self osNameForAccess)

    "
     '/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.
     If the file does exist, it is NOT truncated."

    self exists ifTrue:[
        ^ FileStream oldFileNamed:(self osNameForAccess)
    ].
    ^ FileStream newFileNamed:(self osNameForAccess)

    "
     |s|

     s := '/tmp/foo' asFilename writeStream.
     s nextPutAll:'1234567890'.
     s close.

     s := '/tmp/foo' asFilename readWriteStream.
     s nextPutAll:'abcdef'.
     s close.

     '/tmp/foo' asFilename contents      
    "
!

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

    ^ FileStream newFileForWritingNamed:(self osNameForAccess)

    "
     '/tmp/foo' asFilename writeStream 
    "

    "
     |s|

     s := '/tmp/foo' asFilename writeStream.
     s nextPutAll:'1234567890'.
     s close.

     s := '/tmp/foo' asFilename writeStream.
     s nextPutAll:'12345'.
     s close.

     '/tmp/foo' asFilename contents  
    "
! !

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

    osName := self osNameForFile.
    access := OperatingSystem accessModeOf:osName.
    aCollection do:[:accessSymbol |
	access := access bitOr:(OperatingSystem accessMaskFor:accessSymbol).
    ].
    (OperatingSystem changeAccessModeOf:osName 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).
    "
!

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

    ^ OperatingSystem createDirectory:(self osNameForDirectory)
!

copyTo:newName
    "copy the file - the argument must be convertable to a filename.
     Raises an exception, if an error occurs."

    |inStream outStream buffer bufferSize count newFile|

    OperatingSystem isMSDOSlike ifTrue:[
        "/ mhmh - NT hangs, when copying bigger blocks to a network drive - why ?
        bufferSize := 1 * 1024.
    ] ifFalse:[
        bufferSize := 8 * 1024.
    ].

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

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

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

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

    "Modified: / 23.12.1999 / 21:52:36 / cg"
!

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

    self remove
!

makeDirectory
    "create a directory with the receivers name.
     Raises an exception if not successful"

    (self basicMakeDirectory) ifFalse:[
        "/
        "/ could have existed before ...
        "/
        (self exists and:[self isDirectory]) ifFalse:[
            self fileCreationError:self.
            ^ false
        ]
    ].
    ^ true

    "Modified: / 5.5.1999 / 13:36:33 / cg"
!

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

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

    ^ self addAccessRights:#(executeGroup)

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

makeReadableForGroup
    "make the file readable for the group - you must have permission to do so."

    ^ self addAccessRights:#(readGroup)
!

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

makeWritableForGroup
    "make the file writable for the group - you must have permission to do so."

    ^ self addAccessRights:#(writeGroup)
!

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 exception if not successful.
     (Notice, that a rename is tried first, in case of non-cross device move)"

    OperatingSystem errorSignal handle:[:ex |
        self copyTo:newName.
        self remove
    ] do:[
        self renameTo:newName.
    ]

    "
     |f s|

     f := '/tmp/foo' asFilename.
     s := f writeStream.
     s nextPutLine:'hello'.
     s close.
     f renameTo:'./foo'
    "

    "
     |f s|

     f := '/tmp/foo' asFilename.
     s := f writeStream.
     s nextPutLine:'hello'.
     s close.
     f moveTo:'./foo'
    "
!

recursiveCopyTo:destination
    "if I represent a regular file, copy it.
     Otherwise, copy the directory and recursively
     and recursively all of its subfiles/subdirectories.
     Raises an exception if not successful."

    |ok d|

    self isDirectory ifFalse:[
        d := destination asFilename.
        (d exists and:[d isDirectory]) ifTrue:[
            d := d construct:self baseName.
        ].
        ^ self copyTo:d
    ].

    "/ typically, an 'cp -r' is faster;
    "/ however, if the command fails (or the OS does not support it),
    "/ fallBack doing a manual directory walk.

    ok := OperatingSystem 
            recursiveCopyDirectory:(self osNameForDirectory)
            to:(destination asFilename osNameForDirectory).

    ok ifFalse:[
        self recursiveCopyWithoutOSCommandTo:destination
    ].

    "Created: / 5.5.1999 / 13:35:01 / cg"
    "Modified: / 31.5.1999 / 13:11:34 / cg"
!

recursiveCopyWithoutOSCommandTo:destination
    "if I represent a regular file, copy it.
     Otherwise, copy the directory and all of its subfiles/subdirectories.
     This one walks down the directory hierarchy, not using any OS
     command to do the copy.
     Raises an exception if not successful."

    |destinationFilename d|

    d := destination asFilename.
"/    (d exists and:[d isDirectory]) ifTrue:[
"/        d := d construct:self baseName.
"/    ].

    self isDirectory ifTrue:[
        destinationFilename := d asFilename construct:self baseName.
        destinationFilename makeDirectory.
        self directoryContents do:[:aFilenameString |
            |src dst|

            src := self construct:aFilenameString.
            src isDirectory ifTrue:[
                src recursiveCopyWithoutOSCommandTo:destinationFilename
            ] ifFalse:[
                src copyTo:(destinationFilename construct:aFilenameString)
            ].
        ]
    ] ifFalse:[
        self copyTo:d
    ]

    "
     '.' asFilename recursiveCopyWithoutOSCommandTo:'/tmp/xxx'.
     'smalltalk.rc' asFilename recursiveCopyWithoutOSCommandTo:'/tmp/xxx'.
    "

    "Modified: / 31.5.1999 / 18:12:31 / cg"
!

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

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

    "Created: / 27.11.1995 / 23:36:40 / cg"
    "Modified: / 5.5.1999 / 13:38:42 / cg"
!

recursiveRemove
    "if I represent a regular file, remove it.
     Otherwise, remove the directory and all of its subfiles/subdirectories.
     Raise an exception if not successful."

    |ok|

    "/ typically, an 'rm -rf' is faster and removes better;
    "/ however, if the command fails (or the OS does not support it), 
    "/ fallBack doing a manual directory walk.

    ok := OperatingSystem recursiveRemoveDirectory:(self osNameForDirectory).
    ok ifFalse:[
        self recursiveRemoveWithoutOSCommand
    ].

    "
     '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"
    "Modified: / 5.5.1999 / 13:43:35 / cg"
!

recursiveRemoveWithoutOSCommand
    "if I represent a regular file, remove it.
     Otherwise, remove the directory and all of its subfiles/subdirectories.
     Raise an error if not successful.
     This one walks down the directory hierarchy, not using any OS
     command to do the remove."

    |files|

    self isDirectory ifTrue:[
        (files := self directoryContents) size > 0 ifTrue:[
            files do:[:aFilenameString |
                |f|

                f := self construct:aFilenameString.
                f isDirectory ifTrue:[
                    f recursiveRemoveWithoutOSCommand
                ] ifFalse:[
                    f remove
                ].
            ].
        ]
    ].
    self remove

    "
     'foo' asFilename makeDirectory.
     'foo/bar' asFilename writeStream close.
     'foo' asFilename remove
    "
    "
     'foo' asFilename makeDirectory.
     'foo/bar' asFilename writeStream close.
     'foo' asFilename recursiveRemove
    "

    "Created: / 25.2.1998 / 19:50:40 / cg"
    "Modified: / 25.2.1998 / 19:52:08 / cg"
!

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

    |ok|

    self exists ifFalse:[ ^ self].
    (self isSymbolicLink not and:[self isDirectory]) ifTrue:[
        ok := OperatingSystem removeDirectory:(self osNameForFile)
    ] ifFalse:[
        ok := OperatingSystem removeFile:(self osNameForFile)
    ].
    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: / 20.11.1997 / 17:40:22 / stefan"
    "Modified: / 5.5.1999 / 13:41:12 / 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.
     Raises an exception if not successful."

    |access osName|

    osName := self osNameForFile.
    access := OperatingSystem accessModeOf:osName.
    aCollection do:[:accessSymbol |
        access := access bitAnd:(OperatingSystem accessMaskFor:accessSymbol) bitInvert.
    ].
    (OperatingSystem changeAccessModeOf:osName 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).
    "

    "Modified: / 5.5.1999 / 13:41:21 / cg"
!

removeDirectory
    "remove the directory.
     Raises an exception if not successful (or if its not a directory).
     Use #remove if it is not known if the receiver is a directory or file.
     Use #recursiveRemove in order to (recursively) remove non empty directories."

    |ok|

    ok := OperatingSystem removeDirectory:(self osNameForFile).
    ok ifFalse:[
        self exists ifFalse:[ ^ self].
        self removeError:self
    ].

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

    "
     'foo' asFilename writeStream close.
     'foo' asFilename removeDirectory   
    "

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

    "Modified: / 20.11.1997 / 17:40:22 / stefan"
    "Modified: / 5.5.1999 / 13:41:12 / cg"
!

removeFile
    "remove the file.
     Raises an exception if not successful (or if its not a file).
     Use #remove if it is not known if the receiver is a directory or file.
     Use #recursiveRemove in order to (recursively) remove non empty directories."

    |ok|

    ok := OperatingSystem removeFile:(self osNameForFile).
    ok ifFalse:[
        self exists ifFalse:[ ^ self].
        self removeError:self
    ].

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

    "
     'foo' asFilename makeDirectory.
     'foo' asFilename removeFile   
    "
!

renameOrCopyTo:newName
    "rename or copy the file - the argument must be convertable to a String.
     Raises an exception if not successful.
     This does basically the same as #renameTo:, with one exception:
     if, under unix, the new fileName is on another device, a rename operation
     fails, and #renameTo: raises an exception;
     in contrast, this method falls back to copying the file."

    |newFilename|

    newFilename := newName asFilename.

    (OperatingSystem 
        renameFile:(self osNameForFile) 
        to:(newFilename osNameForFile)
    ) ifFalse:[
        self exists ifFalse:[
            ^ self fileNotFoundError:self
        ].

        OperatingSystem isUNIXlike ifTrue:[
            OperatingSystem lastErrorSymbol == #EXDEV ifTrue:[
                "/ try to copy - and remove the original
                "/ this helps with cross-device renames.

              self copyTo:newName.
              ^ self
          ].
        ].
        ^ self accessDeniedError:newName asFilename.
    ].

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

    "Modified: / 5.5.1999 / 13:41:27 / cg"
!

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

    (OperatingSystem 
        renameFile:(self osNameForFile) 
        to:(newName asFilename osNameForFile)
    ) ifFalse:[
        self exists ifFalse:[
            ^ self fileNotFoundError:self
        ].
        ^ self accessDeniedError:newName asFilename.
    ].

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

    "Modified: / 5.5.1999 / 13:41:27 / cg"
!

truncateTo:newSize
    "change the files size.
     This may not be supported on all operating systems
     (raises an exception, if not)"

    (OperatingSystem truncateFile:(self osNameForFile) 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.
    "

    "Modified: / 5.5.1999 / 13:41:59 / cg"
! !

!Filename methodsFor:'file queries'!

accessTime
    "return a timeStamp containing the files last access time."

    | i |

    (i := self info) isNil ifTrue:[^ nil].
    ^ i accessed

    "
     Filename currentDirectory accessTime 
    "

    "Created: / 9.7.1996 / 10:19:15 / cg"
    "Modified: / 26.9.1997 / 13:05:51 / stefan"
    "Modified: / 17.8.1998 / 10:23:44 / cg"
!

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

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

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

    "Modified: 1.11.1996 / 20:19:24 / cg"
!

fileSize
    "return the size of the file in bytes"

    |i|

    (i := self info) isNil ifTrue:[^ nil].
    ^ i size

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

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 simply return 'file', 
     not knowning about the contents.
     Warning:
         Since the returned string differs among systems (and language settings),
         it is only useful for user-information; 
         NOT as a tag to be used by a program."

    |type buffer s n suffix idx baseNm|

    "/ since we cannot depend on a 'file' command being available,
    "/ do the most obvious ones here. 
    "/ (also useful since the 'file' command takes some time, and the code
    "/  below is faster for common things like directories)

    self isSymbolicLink ifTrue:[
        ^ 'symbolic link to ' , (self linkInfo path)
    ].
    self isDirectory ifTrue:[
        self isReadable ifFalse:[^ 'directory, unreadable'].
        self isExecutable ifFalse:[^ 'directory, locked'].
        ^ 'directory'
    ].
    (type := self type) == #characterSpecial ifTrue:[
        ^ 'character device special file'
    ].
    type == #blockSpecial ifTrue:[
        ^ 'block device special file'
    ].
    type == #socket ifTrue:[
        ^ 'socket'
    ].

    self isReadable ifFalse:[^ 'unreadable'].
    self fileSize == 0 ifTrue:[^ 'empty'].

    suffix := self suffix asLowercase.
    baseNm := self withoutSuffix baseName asLowercase.

    ((#('st' 'rc' 'chg' 'htm' 'html' 'ps') includes:suffix)
    or:[#('makefile') includes:baseNm]) ifTrue:[

        buffer := String new:2024.
        s := self readStream.
        s notNil ifTrue:[
            n := s nextBytes:buffer size into:buffer.
            s close.

            (suffix = 'st') ifTrue:[
                (buffer findString:'subclass:') ~~ 0 ifTrue:[
                    ^ 'smalltalk source'
                ].
                (buffer findString:'methodsFor:') ~~ 0 ifTrue:[
                    ^ 'smalltalk source'
                ].
            ].

            (buffer findString:'methodsFor:') ~~ 0 ifTrue:[
                ^ 'smalltalk changes / method source'
            ].

            (suffix = 'rc') ifTrue:[
                (buffer findString:'ST/X startup') ~~ 0 ifTrue:[
                    ^ 'smalltalk startup script'
                ].
            ].

            (suffix = 'htm' or:[suffix = 'html']) ifTrue:[
                (idx := buffer findString:'<H') ~~ 0 ifTrue:[
                    ((buffer continuesWith:'<HEAD' startingAt:idx)
                    or:[(buffer continuesWith:'<HTML' startingAt:idx)
                    or:[(buffer continuesWith:'<H1' startingAt:idx)
                    or:[(buffer continuesWith:'<H2' startingAt:idx)
                    or:[(buffer continuesWith:'<H3' startingAt:idx)
                    or:[(buffer continuesWith:'<H4' startingAt:idx)
                    or:[(buffer continuesWith:'<H5' startingAt:idx)
                    or:[(buffer continuesWith:'<H6' startingAt:idx)]]]]]]])
                    ifTrue:[
                        ^ 'HTML document text'
                    ]
                ].
            ].
        
            (suffix = 'ps') ifTrue:[
                (buffer findString:'%!!PS-Adobe') ~~ 0 ifTrue:[
                    ^ 'PostScript document'
                ].
            ].

            (baseNm = 'makefile') ifTrue:[
                (buffer startsWith:'#') ifTrue:[
                    ^ 'make rules'
                ]
            ]
        ]
    ].

    ^ 'file'

    "
     'Makefile' asFilename fileType 
     '.' asFilename fileType     
     '/dev/null' asFilename fileType 
     '/tmp/.X11-unix/X0' asFilename fileType 
     'smalltalk.rc' asFilename fileType    
     'bitmaps/SBrowser.xbm' asFilename fileType    
    "

    "Modified: / 21.7.1998 / 11:25:56 / cg"
!

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

    ^ OperatingSystem idOf:(self osNameForAccess)

    "
     Filename currentDirectory id 
    "

    "Modified: 9.7.1996 / 10:19:27 / cg"
    "Created: 5.8.1997 / 19:26:01 / cg"
!

info
    "return some object filled with the files info;
     the info (for which corresponding access methods are understood by
     the returned object) is:

         type  - a symbol giving the files fileType
         mode  - numeric access mode 
         uid   - owners user id
         gid   - owners group id
         size  - files size
         id    - files number (i.e. inode number)
         accessed      - last access time (as osTime-stamp)
         modified      - last modification time (as osTime-stamp)
         statusChanged - last staus change (as osTime-stamp)

     Some of the fields may be returned as nil on systems which do not provide
     all of the information.
     The minimum returned info (i.e. on all OS's) will consist of at least:
        modified
        size
        type

     Dont expect things like uid/gid/mode to be non-nil; write your application
     to either handle nil values,
     or (better) use one of isXXXX query methods. (Be prepared for DOS ...)
     (i.e. instead of:
        someFilename type == #directory
      use
        someFilename isDirectory
    "

    ^ OperatingSystem infoOf:(self osNameForAccess)

    "
     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
     '.' asFilename info
     '..' asFilename info
     '..\..' asFilename info
     '..\..\..' asFilename info
     '..\..\..\..' asFilename info
     'c:\' asFilename info
    "

    "Modified: / 17.8.1998 / 10:24:10 / cg"
!

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:(self osNameForAccess)

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

    "Modified: 1.11.1996 / 20:49:09 / cg"
!

modificationTime
    "return a timeStamp containing the files modification time."

    |i|

    (i := self info) isNil ifTrue:[^ nil].      "/ non-existing
    ^ i modified

    "
     Filename currentDirectory modificationTime
    "

    "Created: / 9.7.1996 / 10:18:59 / cg"
    "Modified: / 26.9.1997 / 13:05:39 / stefan"
    "Modified: / 14.8.1998 / 17:42:50 / cg"
!

type
    "return the symbolic type of the file"

    ^ OperatingSystem typeOf:(self osNameForAccess)

    "
     Filename currentDirectory type 
    "

    "Modified: 9.7.1996 / 10:19:27 / cg"
    "Created: 5.8.1997 / 19:31:26 / cg"
! !

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

    |s rslt|

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

!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).
     The argument may not specify an absolute path name.
     Please do not use this to create filenames with suffixes,
     since some systems require special naming conventions.
     See also: #withSuffix: (which is different, but often needed)."

    ^ self class named:(self constructString:subname)

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

     Bad example; works on UNIX, but may not on others:
       'foo/bar.baz' construct:'.suff'
    "

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

constructDirectory:subname
    "same as #construct: on most systems.
     (may allow different/relaxed name syntax of the argument on some systems)"
     
    ^ self class named:(self constructDirectoryString:subname)
!

constructDirectoryString:subName
    "same as #constructString: on most systems.
     (may allow different/relaxed name syntax of the argument on some systems)"

    ^ self constructString:subName
!

constructString:subName
    "taking the receiver as a directory name, construct a new
     filename-string for an entry within this directory 
     (i.e. for a file or a subdirectory in that directory).
     The argument may not specify an absolute path name.
     The code below works for UNIX & MSDOS; 
     other filename classes (i.e. VMS) may want to redefine this method."

    |sepString sub|

    sub := subName asString.
    sepString := self class separator asString.
    nameString = sepString ifTrue:[
	"I am the root"
	^ sepString  , sub
    ].
    (nameString endsWith:sepString) ifTrue:[
	^ nameString , sub
    ].
    ^ nameString , sepString , sub

    "
     '/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"
    "Created: / 9.9.1997 / 08:57:08 / cg"
    "Modified: / 20.1.1998 / 15:58:23 / md"
    "Modified: / 27.7.1998 / 19:47:51 / cg"
!

filenameFor:fileName
    "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).
     If the argument specifies an absolute path name, the argument is returned."

    |f|

    f := fileName asFilename.
    f isAbsolute ifTrue:[^ f].
    ^ (self construct:fileName)

    "
     '/tmp' asFilename filenameFor:'foo'    
     '/tmp' asFilename filenameFor:'/foo'    
    "

    "Created: 18.9.1997 / 14:34:14 / stefan"
! !

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

    <resource:#obsolete>

    self obsoleteMethodWarning:'use #construct:'.
    ^ (nameString , aString asString)

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

    "Modified: 7.9.1997 / 23:45:36 / cg"
! !

!Filename methodsFor:'printing & storing'!

printOn:aStream
    "append a user printed representation of the receiver to aStream.
     The format is suitable for a human - not meant to be read back."

    aStream nextPutAll:(self class name).
    aStream nextPutAll:'('''.
    nameString printOn:aStream.
    aStream nextPutAll:''')'

    "Modified: 7.9.1997 / 23:46:20 / cg"
!

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 := self nameWithSpecialExpansions:aString.

    "Modified: / 21.7.1998 / 10:44:18 / cg"
! !

!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:(self osNameForAccess)

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

filesMatching:aPattern
    "given the receiver, representing a directory;
     return a collection of files matching a pattern.
     The pattern may be a simple matchPattern, or a set of
     multiple patterns separated by semicolons."

    |matchers notCaseSensitive|

    matchers := aPattern asCollectionOfSubstringsSeparatedBy:$;.
    notCaseSensitive := self class isCaseSensitive not.
    ^ self directoryContents
        select:[:name | 
                (matchers detect:[:p | p match:name ignoreCase:notCaseSensitive] ifNone:0) ~~ 0
               ]

    "
     '/etc' asFilename filesMatching:'a*;c*' 
    "

    "Created: / 15.4.1997 / 15:40:02 / cg"
    "Modified: / 3.8.1998 / 21:22:15 / cg"
!

filesMatchingWithoutDotDirs:aPattern
    "given the receiver, representing a directory;
     return a collection of files matching a pattern.
     Exclude '.' and '..' from the returned list.
     The pattern may be a simple matchPattern, or a set of
     multiple patterns separated by semicolons."

    |matchers notCaseSensitive|

    matchers := aPattern asCollectionOfSubstringsSeparatedBy:$;.
    notCaseSensitive := self class isCaseSensitive not.

    ^ self directoryContents 
        select:[:name | 
                name ~= '.'
                and:[name ~= '..'
                and:[(matchers detect:[:p | p match:name ignoreCase:notCaseSensitive] ifNone:0) ~~ 0]]
      ]

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

    "Created: / 15.4.1997 / 12:52:10 / cg"
    "Modified: / 3.8.1998 / 21:22:30 / cg"
!

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

    (nameString startsWith:self class separator) ifTrue:[^ true].
    ^ self isVolumeAbsolute

    "
     '/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:(self osNameForAccess)

    "
     '/foo/bar' asFilename isDirectory
     '/tmp' asFilename isDirectory
     'Makefile' asFilename isDirectory   
     'c:\' asFilename isDirectory   
     'd:\' asFilename isDirectory   
    "

    "Modified: / 21.9.1998 / 15:53:10 / cg"
!

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:(self osNameForAccess)

    "
     '/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.)"

    |osName|

    osName := self osNameForAccess.
    ^ (OperatingSystem isExecutable:osName)
      and:[(OperatingSystem isDirectory:osName) not]

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

isExplicitRelative
    "return true, if this name is an explicit relative name
     (i.e. starts with './' or '../', to avoid path-prepending)"

    ^ false
!

isHidden
    "return true, if the receiver represents a hidden file.
     The definitions of hidden files depends on the OS used;
     on UNIX, a name starting with a period is considered hidden;
     on MSDOS, the files hidden attribute is used.
     VMS has no concept of hidden files."

    ^ false
!

isImplicit
    "return true, if the receiver represents a builtin file.
     The definitions of builtin files depends on the OS used;
     on UNIX, '.' and '..' are builtin names."

    ^ false

    "Created: 18.9.1997 / 18:04:51 / stefan"
!

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

    ^ OperatingSystem isReadable:(self osNameForFile)

    "
     '/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

    "
     './foo/bar' asFilename isRelative
     '../../foo/bar' asFilename isRelative
     '/foo/bar' asFilename isRelative     
     'bar' asFilename isRelative          
    "

    "Modified: 16.1.1997 / 01:19:14 / cg"
!

isRootDirectory
    "return true, if I represent the root directory 
     (i.e. I have no parentDir)"

    "/ mhmh - should we use:
    "/
    "/ parentDir := self construct:'..'.
    "/ (parentDir exists
    "/ and:[parentDir isDirectory
    "/ and:[parentDir id ~= self id]]) ifTrue:[
    "/    ^ false
    "/ ].
    "/ ^ true
    "/

    ^ self pathName = Filename rootDirectory pathName

    "Modified: 23.10.1997 / 00:38:35 / cg"
!

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:(self osNameForFile)

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

isVolumeAbsolute
    "return true, if the receiver represents an absolute pathname
     on some disk volume (MSDOS only)"

    ^ false

    "Modified: 7.9.1997 / 23:54:33 / cg"
!

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

    ^ OperatingSystem isWritable:(self osNameForFile)

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

binaryContentsOfEntireFile
    "return the binary contents of the file as a byteArray;
     or nil, if the file is unreadable/non-existing."

    |s contents|

    s := self readStream.
    s isNil ifTrue:[^ nil].
    s binary.
    [
        contents := s contentsOfEntireFile
    ] valueNowOrOnUnwindDo:[s close].
    ^ contents

    "Created: / 3.10.1998 / 17:56:39 / cg"
!

contents
    "return the contents of the file as a collection of lines;
     or nil, if the file is unreadable/non-existing.
     See also #contentsOfEntireFile, which returns a string for textFiles."

    |s contents|

    s := self readStream.
    s isNil ifTrue:[^ nil].

    [
        contents := s contents
    ] valueNowOrOnUnwindDo:[s close].
    ^ contents

    "
     'Makefile' asFilename contents
    "

    "Modified: / 2.7.1996 / 12:49:45 / stefan"
    "Created: / 11.7.1996 / 14:09:11 / cg"
    "Modified: / 15.10.1998 / 11:41:45 / cg"
!

contentsOfEntireFile
    "return the contents of the file as a string;
     or nil, if the file is unreadable/non-existing.
     See also #contents, which returns the lines as stringCollection for textFiles."

    |s contents|

    s := self readStream.
    s isNil ifTrue:[^ nil].

    [
        contents := s contentsOfEntireFile
    ] valueNowOrOnUnwindDo:[s close].
    ^ contents

    "
     'Makefile' asFilename contentsOfEntireFile
    "

    "Modified: / 2.7.1996 / 12:49:45 / stefan"
    "Modified: / 15.10.1998 / 11:42:05 / cg"
!

directoryContents
    "return the contents of the directory as a collection of strings.
     This excludes any entries for '.' or '..'.
     Returns nil for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before.
     Notice: this returns the file-names as strings; see also
     #directoryContentsAsFilenames, which returns fileName objects."

    |s contents|
    s := DirectoryStream directoryNamed:(self osNameForDirectoryContents).
    s isNil ifTrue:[^nil].

    [ contents := s contents.
    ] valueNowOrOnUnwindDo:[s close].

    contents remove:'.' ifAbsent:nil.
    contents remove:'..' ifAbsent:nil.
    ^ contents.

    "
     '.' asFilename directoryContents
     '/XXXdoesNotExist' asFilename directoryContents
    "

    "Modified: / 18.9.1997 / 18:42:23 / stefan"
    "Modified: / 3.8.1998 / 21:36:21 / cg"
!

directoryContentsAsFilenames
    "return the contents of the directory as a collection of filenames.
     This excludes any entries for '.' or '..'.
     Returns nil for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before.
     Notice: this returns the file-names as fileName objects; see also
     #directoryContents, which returns strings."

    |names|

    names := self directoryContents.
    names isNil ifTrue:[^ nil].
    ^ names asOrderedCollection collect:[:entry | self construct:entry].

    "
     '.' asFilename directoryContentsAsFilenames   
     '/XXXdoesNotExist' asFilename directoryContentsAsFilenames
    "

!

fullDirectoryContents
    "return the full contents of the directory as a collection of strings.
     This is much like #directoryContents, but includes an entry for the
     parent directory, if there is one.
     Returns nil for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before."

    |files|

    files := self directoryContents.
    files isNil ifTrue:[
        "/ mhmh - that one does not exist
        ^ files
    ].

    "/ add/remove parentDirectory if there is one/none

    files remove:'.' ifAbsent:nil.
    self isRootDirectory ifTrue:[
        files remove:'..' ifAbsent:nil.
    ] ifFalse:[
        (files includes:'..') ifFalse:[
            files addFirst:'..'.
        ]
    ].
    ^ files

    "
     '.' asFilename fullDirectoryContents
     '/XXXdoesNotExist' asFilename fullDirectoryContents
     'd:\FET' asFilename fullDirectoryContents
    "

    "Modified: / 21.9.1998 / 15:33:07 / cg"
!

mimeTypeOfContents
    "this tries to guess the mime type of contents of
     the file. Returns nil, if the file is unreadable, not a plain file
     or the contents is unknown.
     This is done using some heuristics, and may need some improvement"

    |type buffer s n suffix idx idx2 baseNm|

    self isDirectory ifTrue:[
        ^ 'nil'
    ].
    (type := self type) == #characterSpecial ifTrue:[
        ^ nil
    ].
    type == #blockSpecial ifTrue:[
        ^ nil
    ].
    type == #socket ifTrue:[
        ^ nil
    ].

    self isReadable ifFalse:[^ nil].
    self fileSize == 0 ifTrue:[^ nil].

    suffix := self suffix asLowercase.
    baseNm := self withoutSuffix baseName asLowercase.

    "/ read some data from the file ...
    buffer := String new:2024.
    s := self readStream.
    s isNil ifTrue:[^ nil].

    n := s nextBytes:buffer size into:buffer.
    s close.

    (idx := buffer findString:'MIMEType:') ~~ 0 ifTrue:[
        idx := idx + 'MIMEType:' size.
        idx := buffer indexOfNonSeparatorStartingAt:idx.
        idx2 := buffer indexOfSeparatorStartingAt:idx.
        idx2 > idx ifTrue:[
            ^ buffer copyFrom:idx to:idx2-1
        ].
    ].

    (buffer findString:'interchangeVersion:') ~~ 0 ifTrue:[
        ^ 'application/x-smalltalk-source-sif'
    ].
    (buffer findString:'subclass:') ~~ 0 ifTrue:[
        ^ 'application/x-smalltalk-source'
    ].
    (buffer findString:'methodsFor:') ~~ 0 ifTrue:[
        ^ 'application/x-smalltalk-source'
    ].

    (buffer findString:'<BODY:') ~~ 0 ifTrue:[
        ^ 'text/html'
    ].
    (idx := buffer findString:'<H') ~~ 0 ifTrue:[
        ((buffer continuesWith:'<HEAD' startingAt:idx)
        or:[(buffer continuesWith:'<HTML' startingAt:idx)
        or:[(buffer continuesWith:'<H1' startingAt:idx)
        or:[(buffer continuesWith:'<H2' startingAt:idx)
        or:[(buffer continuesWith:'<H3' startingAt:idx)
        or:[(buffer continuesWith:'<H4' startingAt:idx)
        or:[(buffer continuesWith:'<H5' startingAt:idx)
        or:[(buffer continuesWith:'<H6' startingAt:idx)]]]]]]])
        ifTrue:[
            ^ 'text/html'
        ]
    ].
        
    (buffer findString:'%!!PS-Adobe') ~~ 0 ifTrue:[
        ^ 'application/postscript'
    ].

    (buffer findString:'#!! /bin/sh') ~~ 0 ifTrue:[
        ^ 'application/x-sh'
    ].
    (buffer findString:'#!!/bin/sh') ~~ 0 ifTrue:[
        ^ 'application/x-sh'
    ].
"/    (buffer findString:'#!! /bin/bash') ~~ 0 ifTrue:[
"/        ^ 'application/x-bash'
"/    ].
"/    (buffer findString:'#!!/bin/bash') ~~ 0 ifTrue:[
"/        ^ 'application/x-bash'
"/    ].

    (buffer findString:'<?xml version=') ~~ 0 ifTrue:[
        ^ 'text/xml'
    ].

    ^ nil

    "
     'Makefile' asFilename mimeTypeOfContents 
     '.' asFilename mimeTypeOfContents     
     '/dev/null' asFilename mimeTypeOfContents 
     '/tmp/.X11-unix/X0' asFilename mimeTypeOfContents 
     'smalltalk.rc' asFilename mimeTypeOfContents    
     'bitmaps/SBrowser.xbm' asFilename mimeTypeOfContents    
     '../../rules/stmkmf' asFilename mimeTypeOfContents    
    "

    "Modified: / 19.11.1999 / 15:58:29 / cg"
!

recursiveDirectoryContents
    "return the contents of the directory and all subdirectories
     as a collection of strings.
     This excludes any entries for '.' or '..'.
     Subdirectory files are included with a relative pathname.
     Warning: this may take a long time to execute."

    |fileNames dirNames|

    fileNames := OrderedCollection new.
    dirNames := OrderedCollection new.
    self directoryContents do:[:f |
        (self construct:f) isDirectory ifTrue:[
            dirNames add:f
        ] ifFalse:[
            fileNames add:f
        ]
    ].

    dirNames do:[:dN |
        |dd subFiles|

        dd := dN asFilename.
        subFiles := (self construct:dN) recursiveDirectoryContents.
        fileNames addAll:(subFiles collect:[:f | dd constructString:f])
    ].
    ^ fileNames.

    "
     '.' asFilename recursiveDirectoryContents 
     '../../clients' asFilename recursiveDirectoryContents 
    "

! !

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

baseName
    "return my baseName as a string.
     - thats the file/directory name without leading parent-dirs.
     (i.e. '/usr/lib/st/file' asFilename baseName -> 'file'
       and '/usr/lib'         asFilename baseName -> lib).
     This method does not check if the path is valid

     See also: #pathName, #directoryName and #directoryPathName.
     Compatibility note: use #tail for ST-80 compatibility."

    |len index sep endIdx|

    sep := self separator.
    len := nameString size.
    ((len == 1) and:[(nameString at:1) == sep]) ifTrue:[
        ^ nameString
    ].

    endIdx := len.
    len > 1 ifTrue:[
        (nameString at:len) == sep ifTrue:[endIdx := endIdx - 1].
    ].
    index := nameString lastIndexOf:sep startingAt:len-1.
    index == 0 ifTrue:[
        ^ nameString copyTo:endIdx
    ].
    ^ nameString copyFrom:(index+1) to:endIdx

    "
     '/foo/bar' asFilename baseName  
     '/foo/bar.cc' asFilename baseName  
     '.' asFilename baseName          
     '..' asFilename baseName         
     '../..' asFilename baseName        
     '../../libbasic' asFilename baseName        
     '../../libpr' asFilename baseName        
     '../../libbasic/Object.st' asFilename baseName        
     '/' asFilename baseName        
     '\' asFilename baseName        
     'c:\' asFilename baseName        
     '\\idefix' asFilename baseName        
    "

    "Modified: / 24.9.1998 / 13:06:23 / cg"
!

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 class named:(self directoryName)

    "
     '/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 method does not check if the path is valid.

     (i.e. '/usr/lib/st/file' asFilename directoryName -> '/usr/lib/st'
       and '/usr/lib' asFilename directoryName         -> /usr').

     (this is almost equivalent to #directory, but returns
      a string instead of a Filename instance).

     See also: #pathName, #directoryPathName and #baseName.
     Compatibility note: use #head for ST-80 compatibility."

    |index sep sepString p rest|

    sep := self separator.
    sepString := sep asString.
    (nameString = sepString) ifTrue:[
        "/
        "/ the trivial '/' case
        "/
        ^ nameString
    ].

    "/
    "/ strip off multiple trailing slashes
    "/
    p := nameString.
    [p endsWith:sepString] whileTrue:[
        (p = sepString) ifTrue:[
            ^ p
        ].
        p := p copyWithoutLast:1
    ].

    "/ strip off trailing components

    index := p lastIndexOf:sep startingAt:p size.
    index == 0 ifTrue:[
        "/ no separator found
        p = '.' ifTrue:[
            ^ '..'
        ].
        p = '..' ifTrue:[
            ^ '../..'
        ].
        ^ '.'
    ].
    rest := p copyFrom:(index+1).
    rest = '.' ifTrue:[
        ^ p , '.'
    ].
    rest = '..' ifTrue:[
        ^ p , '/..'
    ].
    index == 1 ifTrue:[
        ^ '/'
    ].
    ^ p copyTo:(index - 1)

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

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

    "Modified: / 7.9.1995 / 10:42:03 / claus"
    "Modified: / 21.10.1998 / 22:52:25 / cg"
    "Modified: / 27.10.1998 / 13:19:26 / ps"
!

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: #pathName, #directoryName, #directory and #baseName"

    ^ (self class named:self pathName) directoryName

    "
     '/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: 21.12.1996 / 15:21:57 / 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: 3.7.1996 / 10:53:51 / 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 nm caseless lcBaseName|

    nm := self nameWithSpecialExpansions:nameString.

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

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

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

    caseless := self class isCaseSensitive not.
    caseless ifTrue:[
        lcBaseName := baseName asLowercase
    ].

    matching := OrderedCollection new.
    dir class errorReporter openErrorSignal handle:[:ex|
        ^ #().
    ] do:[
        dir directoryContents do:[:fileName |
            ((fileName ~= '.') and:[fileName ~= parentString]) ifTrue:[
                ((caseless and:[fileName asLowercase startsWith:lcBaseName])
                or:[caseless not and:[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 |
                ((caseless and:[aName asLowercase startsWith:try asLowercase])
                or:[caseless not and:[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 := nm := try
    ].

    "
     if I had a directory-prefix, change names in collection ...
    "
    prefix notNil ifTrue:[
        prefix = sepString ifTrue:[
            "/ avoid introducing double slashes
            prefix := ''
        ].
        matching := matching collect:[:n | prefix , sepString , n].
        nMatch == 1 ifTrue:[
            nameString := nm := matching first
        ] ifFalse:[
            nMatch > 1 ifTrue:[
                nameString := nm := prefix , sepString , nm
            ]
        ]
    ] ifFalse:[
        nMatch == 1 ifTrue:[
            nameString := nm := 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: / 22.9.1997 / 18:03:33 / stefan"
    "Modified: / 30.4.1999 / 09:39:52 / 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"
!

localPathName
    "return the full pathname of the file represented by the receiver,
     but without any volume information.
     Only makes a difference on MSDOS & VMS systems."

    ^ self pathName
!

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. 
     If the path represented by the receiver does NOT represent a valid path,
     no compression will be done (for now; this may change).
     See also: name"

    |p|

"/    sep := self class separator.
"/    (nameString startsWith:sep) ifTrue:[
"/        parentName := self class parentDirectoryName.
"/        (nameString findString:parentName) == 0 ifTrue:[
"/            ^ nameString
"/        ]
"/    ].
    p := OperatingSystem pathNameOf:nameString.
    ^ p

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

    "Modified: 27.4.1996 / 18:19:52 / cg"
!

physicalPathName
    "return the full pathname of the physical file represented by the receiver,
     If the receiver represents a symbolic link, thats the fileName of the
     final target. Otherwise, its the receivers pathName itself.
     If any file along the symbolic path does not exist (i.e. is a broken link),
     nil is returned."

    |t target path|

    self isSymbolicLink ifFalse:[
        self exists ifFalse:[^ nil].
        ^ self pathName
    ].
    t := self.
    [t isSymbolicLink] whileTrue:[
        path := t linkInfo path.
        path isNil ifTrue:[
            "/ cannot happen
            ^ nil
        ].
        target := (self class named:t directoryName) construct:path.
        target exists ifFalse:[^ nil].
        t := target asFilename
    ].
    t exists ifFalse:[^ nil].
    ^ t pathName

    "
     '/foo/bar' asFilename physicalPathName  
     '.' asFilename physicalPathName         
     '../..' asFilename physicalPathName     
     'include/abbrev.stc' asFilename physicalPathName           
    "

    "Modified: 21.12.1996 / 15:29:50 / cg"
!

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

volume
    "return the disc volume part of the name or an empty string.
     This is only used with MSDOS and VMS filenames 
     - by default (and on unix), an empty string is returned"

    ^ ''

    "Modified: 8.9.1997 / 00:37:33 / cg"
! !

!Filename methodsFor:'special accessing'!

nameWithSpecialExpansions:aString
    "return the nameString, expanding any OS specific
     macros. This should be redefined for OS's where such macros
     are common.
     On unix, a ~/ prefix is expanded to the users home dir (as in csh)"

    ^ aString

    "Modified: / 21.7.1998 / 10:43:20 / cg"
    "Created: / 21.7.1998 / 10:45:58 / cg"
!

osName
    "special - return the OS's name for the receiver."

    self isDirectory ifTrue:[
	^ self osNameForDirectory
    ].
    ^ self osNameForFile
!

osNameForAccess
    "internal - return the OS's name for the receiver to
     access its fileInfo.
     This may be redefined for systems, where a special suffix must be
     added in order to access directories (or others) as a file.
     (i.e. under VMS, a '.dir' suffix is added to access directories)"

    ^ nameString

    "Modified: / 21.7.1998 / 10:40:40 / cg"
!

osNameForDirectory
    "internal - return the OS's name for the receiver to
     access it as a directory."

    ^ nameString

    "Modified: / 12.8.1998 / 14:44:32 / cg"
!

osNameForDirectoryContents
    "internal - return the OS's name for the receiver to
     access it as a directory when reading its contents."

    ^ self osNameForDirectory

    "Created: / 3.8.1998 / 21:36:06 / cg"
    "Modified: / 12.8.1998 / 14:44:34 / cg"
!

osNameForFile
    "internal - return the OS's name for the receiver to
     access it as a file."

    ^ nameString
! !

!Filename methodsFor:'suffixes'!

hasSuffix:aSuffixString
    "return true if my suffix is the same as aString.
     This cares for systems, where case is ignored in filenames"

    |mySuffix|

    mySuffix := self suffix.
    self class isCaseSensitive ifTrue:[
        ^ mySuffix = aSuffixString
    ].
    ^ mySuffix asLowercase = aSuffixString asLowercase

    "
     'abc.st' asFilename hasSuffix:'st'   
     'abc.ST' asFilename hasSuffix:'st'   
    "

    "Modified: 7.9.1997 / 02:55:25 / cg"
!

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.
     The directory name part is stripped off (i.e. the returned prefix
     will consist of the files basename only.)
     (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'.
     See also: #withoutSuffix and #withSuffix
     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 
     '/foo/bar.c/baz.c' asFilename prefixAndSuffix 

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

    "Modified: 7.9.1995 / 11:15:42 / claus"
    "Modified: 3.7.1996 / 10:53:10 / 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"
!

withSuffix:aSuffix
    "return a new filename for the receivers name with a different suffix.
     If the name already has a suffix, the new suffix replacaes it;
     otherwise, the new suffix is 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'   
     '/foo/bar.c/baz.c' asFilename withSuffix:'st'   
     '/foo/bar.c/baz' asFilename withSuffix:'st'   
    "

    "Modified: 7.9.1995 / 11:15:42 / claus"
    "Modified: 11.12.1996 / 16:01:02 / cg"
!

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

    |nm idx idxFromEnd|

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

    idxFromEnd := nm size - idx.
    idx := nameString size - idxFromEnd.

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

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

    "Modified: 7.9.1995 / 11:15:42 / claus"
    "Modified: 3.7.1996 / 10:49:58 / cg"
! !

!Filename methodsFor:'testing'!

isFilename
    "return true, if the receiver is some kind of filename;
     false is returned here - the method is redefined from Object."

    ^true


! !

!Filename class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Filename.st,v 1.198 2001-07-13 14:28:48 cg Exp $'
! !
Filename initialize!