#DOCUMENTATION by cg
authorClaus Gittinger <cg@exept.de>
Thu, 28 Mar 2019 16:18:40 +0100
changeset 24017 8da6aa16509d
parent 24016 71594012e33c
child 24018 8db2b5564d4b
#DOCUMENTATION by cg class: Filename class category of: #possiblyQuotedPathname:
Filename.st
--- a/Filename.st	Thu Mar 28 16:12:18 2019 +0100
+++ b/Filename.st	Thu Mar 28 16:18:40 2019 +0100
@@ -2,7 +2,7 @@
 
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-	      All Rights Reserved
+              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
@@ -16,10 +16,10 @@
 "{ NameSpace: Smalltalk }"
 
 Object subclass:#Filename
-	instanceVariableNames:'nameString'
-	classVariableNames:'ConcreteClass DefaultTempDirectory TempDirectory'
-	poolDictionaries:''
-	category:'System-Support'
+        instanceVariableNames:'nameString'
+        classVariableNames:'ConcreteClass DefaultTempDirectory TempDirectory'
+        poolDictionaries:''
+        category:'System-Support'
 !
 
 !Filename class methodsFor:'documentation'!
@@ -27,7 +27,7 @@
 copyright
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
-	      All Rights Reserved
+              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
@@ -91,133 +91,133 @@
 examples
 "
     does a file/directory exist ?:
-									[exBegin]
-	|f|
-
-	f := 'foobar' asFilename.
-	^ f exists
-									[exEnd]
+                                                                        [exBegin]
+        |f|
+
+        f := 'foobar' asFilename.
+        ^ f exists
+                                                                        [exEnd]
 
 
     is it a directory ?:
-									[exBegin]
-	|f|
-
-	f := '/tmp' asFilename.
-	^ f isDirectory.
-									[exEnd]
+                                                                        [exBegin]
+        |f|
+
+        f := '/tmp' asFilename.
+        ^ f isDirectory.
+                                                                        [exEnd]
 
 
     get the working directory:
-									[exBegin]
-	^ Filename defaultDirectory
-									[exEnd]
+                                                                        [exBegin]
+        ^ Filename defaultDirectory
+                                                                        [exEnd]
 
 
     get a files full pathname
     (caring for relative names or symbolic links):
-									[exBegin]
-	|f|
-
-	f := '..' asFilename.
-	^ f pathName
-									[exEnd]
+                                                                        [exBegin]
+        |f|
+
+        f := '..' asFilename.
+        ^ f pathName
+                                                                        [exEnd]
 
 
     get a directories directory:
-									[exBegin]
-	|f|
-
-	f := Filename defaultDirectory.
-	^ f directory
-									[exEnd]
+                                                                        [exBegin]
+        |f|
+
+        f := Filename defaultDirectory.
+        ^ f directory
+                                                                        [exEnd]
 
 
     get a files directory:
-									[exBegin]
-	|f|
-
-	f := './smalltalk' asFilename.
-	^ f directory
-									[exEnd]
+                                                                        [exBegin]
+        |f|
+
+        f := './smalltalk' asFilename.
+        ^ f directory
+                                                                        [exEnd]
 
 
     getting access & modification times:
-									[exBegin]
-	|f|
-
-	f := '/tmp' asFilename.
-	^ f dates
-									[exEnd]
+                                                                        [exBegin]
+        |f|
+
+        f := '/tmp' asFilename.
+        ^ f dates
+                                                                        [exEnd]
 
     access time only:
-									[exBegin]
-	|f|
-
-	f := '/tmp' asFilename.
-	^ f dates at:#accessed
-									[exEnd]
+                                                                        [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]
+                                                                        [exBegin]
+        |f|
+
+        f := '/tmp' asFilename.
+        ^ f info
+                                                                        [exEnd]
 
 
     getting a temporary file (unique name):
-									[exBegin]
-	|f|
-
-	f := Filename newTemporary.
-	^ f
-									[exEnd]
+                                                                        [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]
+                                                                        [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]
+                                                                        [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]
+                                                                        [exBegin]
+        |f|
+
+        f := Filename newTemporary.
+        (f writeStream) nextPutAll:'hello world'; close.
+
+        f edit
+                                                                        [exEnd]
 "
 ! !
 
@@ -227,7 +227,7 @@
     "initialize for the OS we are running on"
 
     ConcreteClass isNil ifTrue:[
-	self initializeConcreteClass
+        self initializeConcreteClass
     ].
 
     "
@@ -241,17 +241,17 @@
     "initialize for the OS we are running on"
 
     OperatingSystem isUNIXlike ifTrue:[
-	ConcreteClass := UnixFilename
+        ConcreteClass := UnixFilename
     ] ifFalse:[OperatingSystem isMSDOSlike ifTrue:[
-	ConcreteClass := PCFilename
+        ConcreteClass := PCFilename
     ] ifFalse:[OperatingSystem isVMSlike ifTrue:[
-	ConcreteClass := OpenVMSFilename
+        ConcreteClass := OpenVMSFilename
     ] ifFalse:[
-	self error:'Filename: unknown OperatingSystem when initializing concrete Filename class'.
+        self error:'Filename: unknown OperatingSystem when initializing concrete Filename class'.
     ]]].
 
     ConcreteClass isNil ifTrue:[
-	self error:'Filename: Missing concrete Filename class'.
+        self error:'Filename: Missing concrete Filename class'.
     ].
 
     "
@@ -288,9 +288,9 @@
     |exeName|
 
     Smalltalk isStandAloneApp ifTrue:[
-	exeName := OperatingSystem nameOfSTXExecutable.
+        exeName := OperatingSystem nameOfSTXExecutable.
     ] ifFalse:[
-	exeName := 'smalltalk'
+        exeName := 'smalltalk'
     ].
     ^ self applicationDataDirectoryFor:exeName
 
@@ -367,19 +367,19 @@
      Use this for files which MUST remain the same (stx_sourceCache)"
 
     DefaultTempDirectory isNil ifTrue:[
-	self tempDirectory.  "/ actually sets DefaultTempDirectory as side effect
-	DefaultTempDirectory isNil ifTrue:[
-	    DefaultTempDirectory := TempDirectory
-	].
+        self tempDirectory.  "/ actually sets DefaultTempDirectory as side effect
+        DefaultTempDirectory isNil ifTrue:[
+            DefaultTempDirectory := TempDirectory
+        ].
     ].
 
     DefaultTempDirectory exists ifFalse:[
-	DefaultTempDirectory
-	    makeDirectory;
-	    addAccessRights:#(readUser readGroup readOthers
-			      writeUser writeGroup writeOthers
-			      executeUser executeGroup executeOthers
-			      removeOnlyByOwner).
+        DefaultTempDirectory
+            makeDirectory;
+            addAccessRights:#(readUser readGroup readOthers
+                              writeUser writeGroup writeOthers
+                              executeUser executeGroup executeOthers
+                              removeOnlyByOwner).
     ].
     ^ DefaultTempDirectory
 
@@ -474,7 +474,7 @@
      root directory (i.e. '/') an absolute path-filename is returned."
 
     self isAbstract ifTrue:[
-	^ ConcreteClass fromComponents:aCollectionOfDirectoryNames
+        ^ ConcreteClass fromComponents:aCollectionOfDirectoryNames
     ].
 
     ^ self named:(self nameFromComponents:aCollectionOfDirectoryNames)
@@ -489,10 +489,10 @@
      Filename fromComponents:#('/')
 
      Filename fromComponents:
-	 (Filename components:('.' asFilename pathName))
+         (Filename components:('.' asFilename pathName))
 
      Filename fromComponents:
-	 (Filename components:('.' asFilename name))
+         (Filename components:('.' asFilename name))
     "
 
     "Modified: 8.9.1997 / 00:23:16 / cg"
@@ -505,12 +505,12 @@
     |name|
 
     name := Dialog
-	requestFileName:'filename:'
-	default:nil
-	fromDirectory:(FileSelectionBox lastFileSelectionDirectory).
+        requestFileName:'filename:'
+        default:nil
+        fromDirectory:(FileSelectionBox lastFileSelectionDirectory).
 
     name notEmptyOrNil ifTrue:[
-	^ self named:name
+        ^ self named:name
     ].
     ^ nil
 
@@ -531,7 +531,7 @@
 
     s := OperatingSystem getHomeDirectory.
     s isNil ifTrue:[
-	^ self defaultDirectory
+        ^ self defaultDirectory
     ].
     ^ self named:s
 
@@ -547,7 +547,7 @@
      This is the same as 'aString asFilename'."
 
     self isAbstract ifTrue:[
-	^ ConcreteClass named:aString
+        ^ ConcreteClass named:aString
     ].
     ^ self basicNew setName:aString
 
@@ -755,7 +755,7 @@
 
     s := self nullFilename.
     s isNil ifTrue:[
-	^ nil
+        ^ nil
     ].
     ^ self named:s
 
@@ -774,12 +774,12 @@
      An absolute network-filename is returned."
 
     self isAbstract ifTrue:[
-	^ ConcreteClass remoteHost:remoteHostString
-			rootComponents:aCollectionOfDirectoryNames
+        ^ ConcreteClass remoteHost:remoteHostString
+                        rootComponents:aCollectionOfDirectoryNames
     ].
 
     remoteHostString notEmptyOrNil ifTrue:[
-	self error:'remote hosts are not supported by OS'
+        self error:'remote hosts are not supported by OS'
     ].
 
     ^ self rootComponents:aCollectionOfDirectoryNames
@@ -797,7 +797,7 @@
     |sep s|
 
     self isAbstract ifTrue:[
-	^ ConcreteClass rootComponents:aCollectionOfDirectoryNames
+        ^ ConcreteClass rootComponents:aCollectionOfDirectoryNames
     ].
 
     "/ fallBack - works on Unix & MSDOS
@@ -805,9 +805,9 @@
     sep := self separatorString.
     s := CharacterWriteStream new.
     aCollectionOfDirectoryNames do:[:component |
-	component ~= sep ifTrue:[
-	    s nextPutAll:sep; nextPutAll:component
-	]
+        component ~= sep ifTrue:[
+            s nextPutAll:sep; nextPutAll:component
+        ]
     ].
     s := s contents.
     s size == 0 ifTrue:[s := sep].
@@ -823,10 +823,10 @@
      Filename rootComponents:#('/')
 
      Filename rootComponents:
-	 (Filename components:('.' asFilename pathName))
+         (Filename components:('.' asFilename pathName))
 
      Filename rootComponents:
-	 (Filename components:('.' asFilename name))
+         (Filename components:('.' asFilename name))
     "
 
     "Modified: 8.9.1997 / 00:23:16 / cg"
@@ -836,7 +836,7 @@
     "return a filename for the root directory"
 
     self isAbstract ifTrue:[
-	^ ConcreteClass rootDirectory
+        ^ ConcreteClass rootDirectory
     ].
 
     "/ fallBack - works on Unix & MSDOS (but not on VMS)
@@ -854,7 +854,7 @@
     "return a filename for the root directory on some volume"
 
     self isAbstract ifTrue:[
-	^ ConcreteClass rootDirectoryOnVolume:aVolumeName
+        ^ ConcreteClass rootDirectoryOnVolume:aVolumeName
     ].
 
     "/ fallBack - works on Unix (not on MSDOS or VMS)
@@ -931,8 +931,8 @@
     |temp|
 
     aFilename isNil ifTrue:[
-	TempDirectory := nil.
-	^ self.
+        TempDirectory := nil.
+        ^ self.
     ].
 
     temp := aFilename asFilename.
@@ -949,7 +949,7 @@
 
     s := OperatingSystem getTrashDirectory.
     s isNil ifTrue:[
-	^ nil
+        ^ nil
     ].
     ^ self named:s
 
@@ -995,7 +995,7 @@
      any of the TEMP-environment variables (see tempDirectory)."
 
     self isAbstract ifTrue:[
-	^ ConcreteClass defaultTempDirectoryName
+        ^ ConcreteClass defaultTempDirectoryName
     ].
 
     ^ '/tmp' asFilename
@@ -1101,26 +1101,6 @@
     "Modified: / 21-01-2019 / 16:26:56 / Stefan Vogel"
 !
 
-possiblyQuotedPathname:aPath
-    "return a filename path usable as command line argument,
-     by quoting in double quotes if there are any embedded special characters.
-     On Unix systems, special characters might also be prefixed by a backslash character."
-
-    (aPath startsWith:$") ifFalse:[
-        (aPath includes:Character space) ifTrue:[
-            ^ '"',aPath,'"'
-        ].
-    ].
-    ^ aPath
-
-
-    "
-     Filename possiblyQuotedPathname:'/tmp/bla'
-     Filename possiblyQuotedPathname:'/tmp directory/bla'
-     Filename possiblyQuotedPathname:'/tmp directory/bla file'
-    "
-!
-
 suggest:aFilenameString
     "return a fileNamestring based on the argument,
      which is legal on the current platform."
@@ -1136,7 +1116,7 @@
     "return a filename for the current directory"
 
     self isAbstract ifTrue:[
-	^ ConcreteClass currentDirectoryName
+        ^ ConcreteClass currentDirectoryName
     ].
 
     "/ fallBack - works on Unix & MSDOS (but not on VMS)
@@ -1166,7 +1146,7 @@
      The default is nil here, redefined for VMS"
 
     self isAbstract ifTrue:[
-	^ ConcreteClass directorySuffix
+        ^ ConcreteClass directorySuffix
     ].
 
     ^ nil
@@ -1233,8 +1213,8 @@
     |s f matchSet nMatch name dir isAbsolute sep|
 
     aString size == 0 ifTrue:[
-	aBlock value:(self named:'.').
-	^ ''
+        aBlock value:(self named:'.').
+        ^ ''
     ].
 
     sep := self separator.
@@ -1247,34 +1227,34 @@
     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:[
-	    filesOnly ifTrue:[
-		isDir not
-	    ] ifFalse:[
-		true
-	    ]
-	]
+        |f isDir|
+
+        isAbsolute ifTrue:[
+            f := aFilename asFilename
+        ] ifFalse:[
+            f := (dir construct:aFilename).
+        ].
+        isDir := f isDirectory.
+        directoriesOnly ifTrue:[
+            isDir
+        ] ifFalse:[
+            filesOnly ifTrue:[
+                isDir not
+            ] ifFalse:[
+                true
+            ]
+        ]
     ].
 
     f := f asCanonicalizedFilename.
-	(nMatch := matchSet size) ~~ 1 ifTrue:[
-	"
-	 more than one possible completion -
-	"
-	aMultipleBlock notNil ifTrue:[
-	    aMultipleBlock value:f value:matchSet.
-	].
-	aBlock value:f
+        (nMatch := matchSet size) ~~ 1 ifTrue:[
+        "
+         more than one possible completion -
+        "
+        aMultipleBlock notNil ifTrue:[
+            aMultipleBlock value:f value:matchSet.
+        ].
+        aBlock value:f
     ].
 
     "
@@ -1284,17 +1264,17 @@
     name := f asString.
 
     nMatch <= 1 ifTrue:[
-	"
-	 exactly one possible completion -
-	"
+        "
+         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
-		].
-	    ].
-	]
+        false "directoriesOnly" ifFalse:[
+            (f exists and:[f isDirectory]) ifTrue:[
+                (name endsWith:sep) ifFalse:[
+                    name := name , sep asString
+                ].
+            ].
+        ]
     ].
 
     s := name.
@@ -1302,11 +1282,11 @@
     "/ 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 endsWith:sep) ifFalse:[
+            (self named:s) isDirectory ifTrue:[
+                ^ s , sep asString
+            ]
+        ].
     ].
 
     ^ s
@@ -1326,7 +1306,7 @@
     |basePattern dir d files|
 
     self isAbstract ifTrue:[
-	^ ConcreteClass filesMatching:aPattern
+        ^ ConcreteClass filesMatching:aPattern
     ].
 
     "/ the following works on Unix & MSDOS (but not on openVMS)
@@ -1385,10 +1365,10 @@
     "ST-80 compatibility.
      what does this do ? (used in FileNavigator-goody).
      GUESS:
-	does it strip off any volume characters and make a path relative ?"
+        does it strip off any volume characters and make a path relative ?"
 
     self isAbstract ifTrue:[
-	^ ConcreteClass localNameStringFrom:aString
+        ^ ConcreteClass localNameStringFrom:aString
     ].
 
     ^ aString withoutPrefix:self separatorString
@@ -1402,7 +1382,7 @@
      be in size. This depends on the OperatingSystem."
 
     self isAbstract ifTrue:[
-	^ ConcreteClass maxComponentLength
+        ^ ConcreteClass maxComponentLength
     ].
     ^ OperatingSystem maxFileNameLength
 !
@@ -1412,7 +1392,7 @@
      This depends on the OperatingSystem."
 
     self isAbstract ifTrue:[
-	^ ConcreteClass maxLength
+        ^ ConcreteClass maxLength
     ].
     ^ OperatingSystem maxPathLength
 
@@ -1425,7 +1405,7 @@
      The default is nil here"
 
     self isAbstract ifTrue:[
-	^ ConcreteClass nullFilename
+        ^ ConcreteClass nullFilename
     ].
 
     ^ OperatingSystem getNullDevice
@@ -1439,7 +1419,7 @@
      (there may be more in the future."
 
     self isAbstract ifTrue:[
-	^ ConcreteClass parentDirectoryName
+        ^ ConcreteClass parentDirectoryName
     ].
 
     ^ OperatingSystem parentDirectoryName
@@ -1496,7 +1476,7 @@
      to generate a unique filename."
 
     self isAbstract ifTrue:[
-	^ ConcreteClass tempFileNameTemplate
+        ^ ConcreteClass tempFileNameTemplate
     ].
 
     ^ 'stxtmp_%1_%2'
@@ -1511,7 +1491,7 @@
      Q: what does this do on Unix systems ? (used in FileNavigator-goody)."
 
     self isAbstract ifTrue:[
-	^ ConcreteClass volumes
+        ^ ConcreteClass volumes
     ].
 
     ^ OperatingSystem getDriveList
@@ -1564,23 +1544,23 @@
     comps := self components:aPathString.
     newComps := OrderedCollection new:comps size.
     comps do:[:eachComponent |
-	eachComponent ~= dot ifTrue:[
-	    eachComponent = dotDot ifTrue:[
-	       (newComps isEmpty
-		or:[(newComps size == 1 and:[newComps first startsWith:rootName])
-		or:[newComps last = dotDot]]) ifTrue:[
-		   newComps add:eachComponent
-	       ] ifFalse:[
-		   newComps removeLast
-	       ].
-	    ] ifFalse:[
-		newComps add:eachComponent
-	    ].
-	]
+        eachComponent ~= dot ifTrue:[
+            eachComponent = dotDot ifTrue:[
+               (newComps isEmpty
+                or:[(newComps size == 1 and:[newComps first startsWith:rootName])
+                or:[newComps last = dotDot]]) ifTrue:[
+                   newComps add:eachComponent
+               ] ifFalse:[
+                   newComps removeLast
+               ].
+            ] ifFalse:[
+                newComps add:eachComponent
+            ].
+        ]
     ].
     "/ add current Directory if empty
     newComps isEmpty ifTrue:[
-	newComps add:dot.
+        newComps add:dot.
     ].
     ^ newComps
 
@@ -1710,7 +1690,7 @@
     |sep s|
 
     self isAbstract ifTrue:[
-	^ ConcreteClass nameFromComponents:aCollectionOfDirectoryNames
+        ^ ConcreteClass nameFromComponents:aCollectionOfDirectoryNames
     ].
 
     "/ fallBack - works on Unix & MSDOS
@@ -1718,15 +1698,15 @@
     sep := self separatorString.
     s := ''.
     aCollectionOfDirectoryNames keysAndValuesDo:[:index :component |
-	index == 1 ifTrue:[
-	    s := component.
-	] ifFalse:[
-	    (index == 2 and:[ (s endsWith:sep) ]) ifTrue:[
-		s := s , component
-	    ] ifFalse:[
-		s := s , sep , component
-	    ]
-	].
+        index == 1 ifTrue:[
+            s := component.
+        ] ifFalse:[
+            (index == 2 and:[ (s endsWith:sep) ]) ifTrue:[
+                s := s , component
+            ] ifFalse:[
+                s := s , sep , component
+            ]
+        ].
     ].
     ^ s
 
@@ -1767,17 +1747,24 @@
     "Modified: 8.9.1997 / 00:23:16 / cg"
 !
 
-possiblyQuotedPath:aPath
-    "if aPath requires any quoting, do so"
-    
-    (aPath includes:Character space) ifTrue:[
-        (aPath startsWith:$") ifFalse:[
+possiblyQuotedPathname:aPath
+    "return a filename path usable as command line argument,
+     by quoting in double quotes if there are any embedded special characters.
+     On Unix systems, special characters might also be prefixed by a backslash character."
+
+    (aPath startsWith:$") ifFalse:[
+        (aPath includes:Character space) ifTrue:[
             ^ '"',aPath,'"'
-        ]
+        ].
     ].
     ^ aPath
 
-    "Created: / 28-03-2019 / 16:11:50 / Claus Gittinger"
+
+    "
+     Filename possiblyQuotedPathname:'/tmp/bla'
+     Filename possiblyQuotedPathname:'/tmp directory/bla'
+     Filename possiblyQuotedPathname:'/tmp directory/bla file'
+    "
 !
 
 readingFile:aPathName do:aBlock
@@ -1869,7 +1856,7 @@
     string := self asString.
     idx := string lastIndexOf:$..
     idx > 1 ifTrue:[
-	^ string copyFrom:idx
+        ^ string copyFrom:idx
     ].
     ^ nil
 
@@ -1918,11 +1905,11 @@
     |str|
 
     self species == aFilename species ifTrue:[
-	str := aFilename asString.
-	self species isCaseSensitive ifTrue:[
-	    ^ nameString = str
-	].
-	^ nameString sameAs:str
+        str := aFilename asString.
+        self species isCaseSensitive ifTrue:[
+            ^ nameString = str
+        ].
+        ^ nameString sameAs:str
     ].
     ^ false
 !
@@ -2068,10 +2055,10 @@
     "return an integer useful as a hash-key"
 
     self species isCaseSensitive ifFalse:[
-	"/ asLowercase is slightly better:
-	"/ it never converts single-byte strings to double one's,
-	"/ whereas asUppercase might (for umlaut-y)
-	^ nameString asUppercase hash
+        "/ asLowercase is slightly better:
+        "/ it never converts single-byte strings to double one's,
+        "/ whereas asUppercase might (for umlaut-y)
+        ^ nameString asUppercase hash
     ].
     ^ nameString hash
 !
@@ -2379,12 +2366,12 @@
      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
-	]
+        |eachFileOrDirectory|
+
+        eachFileOrDirectory := self construct:eachFileOrDirectoryName.
+        eachFileOrDirectory isDirectory ifTrue:[
+            aBlock value:eachFileOrDirectory
+        ]
     ].
 
     "
@@ -2402,9 +2389,9 @@
     here := self.
     parent := here directory.
     [here notNil and:[parent ~= here]] whileTrue:[
-	aBlock value:parent.
-	here := parent.
-	parent := here directory.
+        aBlock value:parent.
+        here := parent.
+        parent := here directory.
     ].
 
     "
@@ -2446,7 +2433,7 @@
      #directoryContentsDo:, which enumerates strings."
 
     self directoryContentsDo:[:entry |
-	aBlock value:(self construct:entry).
+        aBlock value:(self construct:entry).
     ]
 
     "
@@ -2527,9 +2514,9 @@
      contained in the directory represented by the receiver."
 
     ^ self directoryContentsAsFilenamesDo:[:eachFileOrDirectory |
-	eachFileOrDirectory isRegularFile ifTrue:[
-	    aBlock value: eachFileOrDirectory
-	].
+        eachFileOrDirectory isRegularFile ifTrue:[
+            aBlock value: eachFileOrDirectory
+        ].
     ].
 
     "
@@ -2675,11 +2662,11 @@
      (i.e. subdirs are ignored)"
 
     ^ self directoryContentsAsFilenamesDo:[:eachFileOrDirectory |
-	(eachFileOrDirectory hasSuffix:suffix) ifTrue:[
-	    eachFileOrDirectory isRegularFile ifTrue:[
-		aBlock value: eachFileOrDirectory
-	    ].
-	].
+        (eachFileOrDirectory hasSuffix:suffix) ifTrue:[
+            eachFileOrDirectory isRegularFile ifTrue:[
+                aBlock value: eachFileOrDirectory
+            ].
+        ].
     ].
 
     "
@@ -2898,7 +2885,7 @@
      So users of this method better test for existing directory before."
 
     self isDirectory ifTrue:[
-	aBlock value:self.
+        aBlock value:self.
     ].
     self allDirectoriesDo:aBlock.
 
@@ -2917,8 +2904,8 @@
     "report an error that some file could not be created"
 
     ^ OperatingSystem accessDeniedErrorSignal
-	raiseRequestWith:filename?self
-	errorString:(' - cannot create/write file: "%1"' bindWith:(filename ? self) asString)
+        raiseRequestWith:filename?self
+        errorString:(' - cannot create/write file: "%1"' bindWith:(filename ? self) asString)
 !
 
 reportError:string with:filename
@@ -2927,8 +2914,8 @@
     "report an error"
 
     ^ OsError
-	raiseRequestWith:filename?self
-	errorString:string
+        raiseRequestWith:filename?self
+        errorString:string
 ! !
 
 !Filename methodsFor:'file access'!
@@ -3098,7 +3085,7 @@
      instead of an exception when an error occurs."
 
     ^ [
-	FileStream appendingOldFileNamed:(self osNameForAccess)
+        FileStream appendingOldFileNamed:(self osNameForAccess)
       ] on:FileStream openErrorSignal do:[:ex| nil].
 !
 
@@ -3112,7 +3099,7 @@
      instead of an exception when an error occurs."
 
     ^ [
-	 FileStream newFileNamed:(self osNameForAccess)
+         FileStream newFileNamed:(self osNameForAccess)
     ] on:FileStream openErrorSignal do:[:ex|nil].
 !
 
@@ -3125,7 +3112,7 @@
      instead of an exception when an error occurs."
 
     ^ [
-	FileStream readonlyFileNamed:(self osNameForAccess)
+        FileStream readonlyFileNamed:(self osNameForAccess)
     ] on:FileStream openErrorSignal do:[:ex|nil].
 
     "
@@ -3144,7 +3131,7 @@
      instead of an exception when an error occurs."
 
     ^ [
-	FileStream fileNamed:(self osNameForAccess)
+        FileStream fileNamed:(self osNameForAccess)
     ] on:FileStream openErrorSignal do:[:ex|^ nil].
 !
 
@@ -3158,7 +3145,7 @@
      instead of an exception when an error occurs."
 
     ^ [
-	FileStream newFileForWritingNamed:(self osNameForAccess)
+        FileStream newFileForWritingNamed:(self osNameForAccess)
     ] on:FileStream openErrorSignal do:[:ex|^ nil].
 
 
@@ -3574,17 +3561,17 @@
     |writeStream|
 
     self exists ifTrue:[
-	OperatingSystem accessDeniedErrorSignal
-	    raiseRequestWith:self
-	    errorString:(' - file exists: ' , self asString).
-	^ self
+        OperatingSystem accessDeniedErrorSignal
+            raiseRequestWith:self
+            errorString:(' - file exists: ' , self asString).
+        ^ self
     ].
 
     FileStream openErrorSignal handle:[:ex|
-	self fileCreationError:self.
-	^ self
+        self fileCreationError:self.
+        ^ self
     ] do:[
-	writeStream := self newReadWriteStream.
+        writeStream := self newReadWriteStream.
     ].
     writeStream close.
 !
@@ -3650,14 +3637,14 @@
      (Notice, that a rename is tried first, in case of non-cross device move)"
 
     [self renameTo:newName]
-	on:OsError
-	do:[:ex |
-	    ex creator == OperatingSystem fileNotFoundErrorSignal ifTrue:[
-		ex reject
-	    ].
-	    self safeCopyTo:newName.
-	    self remove
-	].
+        on:OsError
+        do:[:ex |
+            ex creator == OperatingSystem fileNotFoundErrorSignal ifTrue:[
+                ex reject
+            ].
+            self safeCopyTo:newName.
+            self remove
+        ].
 
     "
      |f s|
@@ -3690,16 +3677,16 @@
 
     newName := newNameArg asFilename.
     [self renameTo:newName]
-	on:(OSErrorHolder inappropriateReferentSignal)
-	do:[:ex |
-	    "handle renames accross device boundaries (Unix. cross device link)"
-	    self isDirectory ifTrue:[
-		self recursiveMoveDirectoryTo:newName.
-	    ] ifFalse:[
-		self safeCopyTo:newName.
-		self remove.
-	    ].
-	].
+        on:(OSErrorHolder inappropriateReferentSignal)
+        do:[:ex |
+            "handle renames accross device boundaries (Unix. cross device link)"
+            self isDirectory ifTrue:[
+                self recursiveMoveDirectoryTo:newName.
+            ] ifFalse:[
+                self safeCopyTo:newName.
+                self remove.
+            ].
+        ].
 
     "
      |f s|
@@ -3883,11 +3870,11 @@
      (Notice, that a rename is tried first, in case of non-cross device move)"
 
     [self renameTo:newName]
-	on:OsError
-	do:[
-	    self recursiveCopyTo:newName.
-	    self recursiveRemove
-	].
+        on:OsError
+        do:[
+            self recursiveCopyTo:newName.
+            self recursiveRemove
+        ].
 !
 
 recursiveRemove
@@ -3903,7 +3890,7 @@
 
     ok := OperatingSystem recursiveRemoveDirectory:(self osNameForDirectory).
     ok ifFalse:[
-	self recursiveRemoveWithoutOSCommand
+        self recursiveRemoveWithoutOSCommand
     ].
 
     "
@@ -3970,8 +3957,8 @@
      command to do the remove."
 
     self
-	recursiveRemoveAll;
-	remove.
+        recursiveRemoveAll;
+        remove.
 
     "
      'foo' asFilename makeDirectory.
@@ -4184,7 +4171,7 @@
      (raises an exception, if not)"
 
     (OperatingSystem truncateFile:self osNameForFile to:newSize) ifFalse:[
-	^ self reportError:'unsupported operation' with:self
+        ^ self reportError:'unsupported operation' with:self
     ]
 
     "
@@ -4249,12 +4236,12 @@
     osName := self osNameForAccess.
     info := OperatingSystem infoOf:osName.
     info isNil ifTrue:[
-	"maybe this is a symbolic link with a broken link target.
-	 Answer the dates of the link itself"
-	info := OperatingSystem linkInfoOf:osName.
-	info isNil ifTrue:[
-	    ^ nil
-	]
+        "maybe this is a symbolic link with a broken link target.
+         Answer the dates of the link itself"
+        info := OperatingSystem linkInfoOf:osName.
+        info isNil ifTrue:[
+            ^ nil
+        ]
     ].
     dates := IdentityDictionary new.
     dates at:#created put:(info creationTime).
@@ -4432,7 +4419,7 @@
       which is accessed via the symbolic link).
 
      In addition to the normal entries, Unix returns an additional entry:
-	 path -> the target files pathname
+         path -> the target files pathname
 
      See the comment in #info for more details."
 
@@ -4745,12 +4732,12 @@
     nameString := self species canonicalize:nameString.
 
     "
-	'/tmp/bla' asFilename canonicalize.
-	'/tmp/bla/../fasel' asFilename canonicalize.
-	'/tmp/bla/.././/fasel' asFilename canonicalize.
-	'..' asFilename canonicalize.
-	'bla/../fasel' asFilename canonicalize.
-	'//bla/../fasel' asFilename canonicalize.
+        '/tmp/bla' asFilename canonicalize.
+        '/tmp/bla/../fasel' asFilename canonicalize.
+        '/tmp/bla/.././/fasel' asFilename canonicalize.
+        '..' asFilename canonicalize.
+        'bla/../fasel' asFilename canonicalize.
+        '//bla/../fasel' asFilename canonicalize.
     "
 ! !
 
@@ -4778,7 +4765,7 @@
      On non-osx systems, an error is raised"
 
     OperatingSystem isOSXlike ifFalse:[
-	self warn:'sorry - this operation is only available under osx'.
+        self warn:'sorry - this operation is only available under osx'.
     ].
 
     OperatingSystem executeCommand:'open "',self pathName,'"'
@@ -4927,7 +4914,7 @@
     "VW compatibility"
 
     ^ (self filesMatching:aPattern)
-	    collect:[:eachName | self construct:eachName].
+            collect:[:eachName | self construct:eachName].
 
     "
      '/etc' asFilename filenamesMatching:'a*;c*'
@@ -5162,13 +5149,13 @@
 isMountPoint:aPathName
     "return true, if I represent a mount-point.
      Warning:
-	the receiver must be an absolute pathname,
-	because a realPath is not used/generated for the query (to avoid automounting).
-	Aka: do not ask: '../../' asFilename isMountPoint;
+        the receiver must be an absolute pathname,
+        because a realPath is not used/generated for the query (to avoid automounting).
+        Aka: do not ask: '../../' asFilename isMountPoint;
     "
 
     self isAbsolute ifFalse:[
-	self error:'this query must be done on an absolute pathname'.
+        self error:'this query must be done on an absolute pathname'.
     ].
     ^ OperatingSystem isMountPoint:(self name)
 !
@@ -5189,11 +5176,11 @@
     "return true, if such a file exists and is a shared library."
 
     ObjectFileLoader isNil ifTrue:[
-	"we cannot handle shared libraries, so there are no shared libraries"
-	^ false.
+        "we cannot handle shared libraries, so there are no shared libraries"
+        ^ false.
     ].
     ^ (ObjectFileLoader validBinaryExtensions includes:self suffix)
-	and:[self isRegularFile].
+        and:[self isRegularFile].
 
     "
      'libstx_libbasic.so' asFilename isSharedLibrary
@@ -5242,23 +5229,23 @@
      with UID mapping and attribute cache enabled, there may be false negatives."
 
     self isDirectory ifFalse:[
-	^ false.
+        ^ false.
     ].
 
     self isWritable ifFalse:[
-	"/ on an NFS mounted filesystem with UID mapping and
-	"/ attribute cache enabled,
-	"/ this query may fail, but creation may work actually.
-	"/ check again...
-	[
-	    |tempFile|
-
-	    tempFile := FileStream newTemporaryIn:self.
-	    tempFile close.
-	    tempFile fileName remove.
-	] on:OpenError do:[:ex|
-	    ^ false.
-	].
+        "/ on an NFS mounted filesystem with UID mapping and
+        "/ attribute cache enabled,
+        "/ this query may fail, but creation may work actually.
+        "/ check again...
+        [
+            |tempFile|
+
+            tempFile := FileStream newTemporaryIn:self.
+            tempFile close.
+            tempFile fileName remove.
+        ] on:OpenError do:[:ex|
+            ^ false.
+        ].
     ].
     ^ true.
 
@@ -5291,9 +5278,9 @@
      per default (from directories etc.)"
 
     self == Filename ifTrue:[
-	^ ConcreteClass.
+        ^ ConcreteClass.
     ] ifFalse:[
-	^ self class.
+        ^ self class.
     ].
 !
 
@@ -5305,7 +5292,7 @@
 
     newName := self species nameWithSpecialExpansions:nameString.
     newName = nameString ifTrue:[
-	^ self.
+        ^ self.
     ].
     ^ self species named:newName.
 
@@ -5644,127 +5631,127 @@
 
     sepString := mySpecies separatorString.
     (nm endsWith:sepString) ifTrue:[
-	"/ two exceptions here:
-	"/   if there is only one file in the directory, that one must be it.
-	"/   otherwise, return the longest common prefix of all files.
-	self isDirectory ifTrue:[
-	    |first longest|
-
-	    first := nil.
-	    OpenError catch:[
-		self directoryContentsDo:[:fileName |
-		    ((fileName ~= '.') and:[fileName ~= parentString]) ifTrue:[
-			matching add:fileName.
-			first isNil ifTrue:[
-			    first := longest := fileName.
-			] ifFalse:[
-			    "/ more than one file
-			    longest := longest commonPrefixWith:fileName ignoreCase:caseless.
-			    longest isEmpty ifTrue:[
-				^ #()
-			    ].
-			]
-		    ]
-		].
-	    ].
-	    longest notNil ifTrue:[
-		nameString := (self constructString:longest).
-		 ^ matching
-	    ].
-	].
-	^ #()
+        "/ two exceptions here:
+        "/   if there is only one file in the directory, that one must be it.
+        "/   otherwise, return the longest common prefix of all files.
+        self isDirectory ifTrue:[
+            |first longest|
+
+            first := nil.
+            OpenError catch:[
+                self directoryContentsDo:[:fileName |
+                    ((fileName ~= '.') and:[fileName ~= parentString]) ifTrue:[
+                        matching add:fileName.
+                        first isNil ifTrue:[
+                            first := longest := fileName.
+                        ] ifFalse:[
+                            "/ more than one file
+                            longest := longest commonPrefixWith:fileName ignoreCase:caseless.
+                            longest isEmpty ifTrue:[
+                                ^ #()
+                            ].
+                        ]
+                    ]
+                ].
+            ].
+            longest notNil ifTrue:[
+                nameString := (self constructString:longest).
+                 ^ matching
+            ].
+        ].
+        ^ #()
     ].
 
     parentString := mySpecies parentDirectoryName.
     baseName := self baseName.
     baseName ~= nm ifTrue:[
-	prefix := self directoryName.
+        prefix := self directoryName.
     ].
 
     self isAbsolute ifTrue:[
-	dir := self directory
+        dir := self directory
     ] ifFalse:[
-	aDirectory isNil ifTrue:[
-	    dir := self directory
-	] ifFalse:[
-	    dir := (aDirectory asFilename construct:nm) directory
-	]
+        aDirectory isNil ifTrue:[
+            dir := self directory
+        ] ifFalse:[
+            dir := (aDirectory asFilename construct:nm) directory
+        ]
     ].
 
     caseless ifTrue:[
-	lcBaseName := baseName asLowercase
+        lcBaseName := baseName asLowercase
     ].
 
     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
-		]
-	    ]
-	].
+        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
+        "
+         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 endsWith:sepString) ifTrue:[
-	    "/ avoid introducing double slashes
-	    prefix := prefix copyButLast:(sepString size).
-	].
-	matching := matching collect:[:n | prefix , sepString , n].
-	nMatch == 1 ifTrue:[
-	    nameString := nm := matching first
-	] ifFalse:[
-	    nMatch > 1 ifTrue:[
-		nameString := nm := prefix , sepString , nm
-	    ]
-	]
+        (prefix endsWith:sepString) ifTrue:[
+            "/ avoid introducing double slashes
+            prefix := prefix copyButLast:(sepString size).
+        ].
+        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
-	]
+        nMatch == 1 ifTrue:[
+            nameString := nm := matching first
+        ]
     ].
 
     "
@@ -5876,19 +5863,19 @@
     otherNames := self class canonicalizedNameComponents:filenameArg name.
     myNames := self class canonicalizedNameComponents:self name.
     ((otherNames startsWith:myNames) and:[myNames first ~= self class parentDirectoryName]) ifTrue:[
-	^ otherNames ~= myNames
+        ^ otherNames ~= myNames
     ].
 
     "fall back - try it again with ~ substitution and symbolic links resolved"
     otherNames := self class canonicalizedNameComponents:filenameArg pathName.
     myNames := self class canonicalizedNameComponents:self pathName.
     (otherNames startsWith:myNames) ifTrue:[
-	^ otherNames ~= myNames
+        ^ otherNames ~= myNames
     ].
 
     myName := self class nameFromComponents:myNames.
     filenameArg allParentDirectoriesDo:[:parent |
-	parent pathName = myName ifTrue:[^ true].
+        parent pathName = myName ifTrue:[^ true].
     ].
     ^ false.
 
@@ -6244,10 +6231,10 @@
      readable directories pathname, and the directory is not empty."
 
     FileStream openErrorSignal
-	handle:[:ex| ]
-	do:[
-	    self directoryContentsDo:[:pathString|^ true].
-	].
+        handle:[:ex| ]
+        do:[
+            self directoryContentsDo:[:pathString|^ true].
+        ].
     ^ false.
 
     "
@@ -6371,8 +6358,8 @@
     "here we get the files without '.' and '..'"
     files := self directoryContents.
     files isNil ifTrue:[
-	"/ mhmh - that one does not exist
-	^ files
+        "/ mhmh - that one does not exist
+        ^ files
     ].
 
     files addFirst:'..'.
@@ -6409,8 +6396,8 @@
      This excludes any entries for '.' or '..'.
      Subdirectory files are included with a relative pathname.
      Notice:
-	this returns the file-names as strings;
-	see also #recursiveDirectoryContentsAsFilenames, which returns fileName instances.
+        this returns the file-names as strings;
+        see also #recursiveDirectoryContentsAsFilenames, which returns fileName instances.
 
      Warning: this may take a long time to execute."
 
@@ -6419,19 +6406,19 @@
     fileNames := OrderedCollection new.
     dirNames := OrderedCollection new.
     self directoryContents do:[:f |
-	(self construct:f) isDirectory ifTrue:[
-	    dirNames add:f
-	] ifFalse:[
-	    fileNames add: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])
+        |dd subFiles|
+
+        dd := dN asFilename.
+        subFiles := (self construct:dN) recursiveDirectoryContents.
+        fileNames addAll:(subFiles collect:[:f | dd constructString:f])
     ].
     ^ fileNames.
 
@@ -6449,8 +6436,8 @@
      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 instances;
-	see also #recursiveDirectoryContents, which returns strings.
+        this returns the file-names as fileName instances;
+        see also #recursiveDirectoryContents, which returns strings.
 
      Warning: this may take a long time to execute."
 
@@ -6481,24 +6468,24 @@
      Raises an error, if the file is unreadable/non-existing."
 
     ^ self
-	readingFileDo:[:s |
-	    |nBytes bytes n result|
-
-	    s binary.
-	    nBytes := self fileSize.
-	    (nBytes notNil and:[ nBytes ~~ 0 ]) ifTrue:[
-		bytes := ByteArray uninitializedNew:nBytes.
-		n := s nextBytes:nBytes into:bytes startingAt:1.
-		n == nBytes ifTrue:[
-		    result := bytes
-		] ifFalse:[
-		    result := bytes copyTo:n
-		]
-	    ] ifFalse:[
-		result := s contentsOfEntireFile
-	    ].
-	    result
-	]
+        readingFileDo:[:s |
+            |nBytes bytes n result|
+
+            s binary.
+            nBytes := self fileSize.
+            (nBytes notNil and:[ nBytes ~~ 0 ]) ifTrue:[
+                bytes := ByteArray uninitializedNew:nBytes.
+                n := s nextBytes:nBytes into:bytes startingAt:1.
+                n == nBytes ifTrue:[
+                    result := bytes
+                ] ifFalse:[
+                    result := bytes copyTo:n
+                ]
+            ] ifFalse:[
+                result := s contentsOfEntireFile
+            ].
+            result
+        ]
 
     "
      'Makefile' asFilename binaryContentsOfEntireFile
@@ -6646,7 +6633,7 @@
     "special - return the OS's name for the receiver."
 
     self isDirectory ifTrue:[
-	^ self osNameForDirectory
+        ^ self osNameForDirectory
     ].
     ^ self osNameForFile
 !
@@ -6744,7 +6731,7 @@
 
     mySuffix := self suffix.
     self species isCaseSensitive ifTrue:[
-	^ mySuffix = aSuffixString
+        ^ mySuffix = aSuffixString
     ].
     ^ mySuffix asLowercase = aSuffixString asLowercase
 
@@ -6834,8 +6821,8 @@
      '.foorc'.
      See also: #withoutSuffix and #withSuffix
      Notice:
-	there is currently no known system which uses other than
-	the period character as suffixCharacter."
+        there is currently no known system which uses other than
+        the period character as suffixCharacter."
 
     |nm idx|
 
@@ -6844,11 +6831,11 @@
     "/ be careful: if the name consists only of suffix (i.e '.foo'),
     "/ the suffix is considered empty.
     ((idx == 1) or:[ idx == 0 ]) ifTrue:[
-	^ Array with:nm with:''
+        ^ Array with:nm with:''
     ].
     ^ Array
-	with:(nm copyTo:idx-1)
-	with:(nm copyFrom:idx+1)
+        with:(nm copyTo:idx-1)
+        with:(nm copyFrom:idx+1)
 
     "
      'abc.st' asFilename prefixAndSuffix