VMS changes
authorClaus Gittinger <cg@exept.de>
Mon, 08 Sep 1997 20:05:39 +0200
changeset 2906 4cb3c10499a7
parent 2905 8307765e787a
child 2907 1666bf27f351
VMS changes
Class.st
Filename.st
--- a/Class.st	Sun Sep 07 01:52:48 1997 +0200
+++ b/Class.st	Mon Sep 08 20:05:39 1997 +0200
@@ -10,6 +10,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:3.1.9 on 8-sep-1997 at 12:47:46 am'                  !
+
 ClassDescription subclass:#Class
 	instanceVariableNames:'name category classvars comment subclasses classFilename package
 		revision primitiveSpec environment signature hook'
@@ -3252,7 +3254,7 @@
         "/ If the component includes slashes, its the directory
         "/ otherwise the library
         "/ 
-        dirComponents := Filename components:(components at:1).     
+        dirComponents := Filename concreteClass components:(components at:1).     
 
         (dirComponents size > 1
         and:[(mgr := self sourceCodeManager) notNil
@@ -3320,7 +3322,7 @@
     "
 
     "Created: 4.11.1995 / 20:36:53 / cg"
-    "Modified: 17.3.1997 / 18:13:03 / cg"
+    "Modified: 8.9.1997 / 00:21:45 / cg"
 !
 
 revision
@@ -3818,5 +3820,5 @@
 !Class class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Class.st,v 1.289 1997-08-08 09:00:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Class.st,v 1.290 1997-09-08 18:05:32 cg Exp $'
 ! !
--- a/Filename.st	Sun Sep 07 01:52:48 1997 +0200
+++ b/Filename.st	Mon Sep 08 20:05:39 1997 +0200
@@ -10,11 +10,11 @@
  hereby transferred.
 "
 
-'From Smalltalk/X, Version:3.1.9 on 7-sep-1997 at 2:56:23 pm'                   !
+'From Smalltalk/X, Version:3.1.9 on 8-sep-1997 at 12:38:49 am'                  !
 
 Object subclass:#Filename
 	instanceVariableNames:'nameString'
-	classVariableNames:'NextTempFilenameIndex'
+	classVariableNames:'NextTempFilenameIndex ConcreteClass'
 	poolDictionaries:''
 	category:'System-Support'
 !
@@ -204,18 +204,74 @@
 "
 ! !
 
+!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:('.' asFilename pathName)
 
     "
      Filename currentDirectory 
     "
 
-    "Modified: 15.4.1997 / 13:22:46 / cg"
+    "Modified: 8.9.1997 / 00:24:15 / cg"
 !
 
 defaultDirectory
@@ -238,6 +294,26 @@
     "
 !
 
+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"
 
@@ -253,17 +329,23 @@
 
     |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 , '/' , component
-	].
+        index == 1 ifTrue:[
+            (component ~= sep 
+            or:[aCollectionOfDirectoryNames size == 1]) ifTrue:[
+                s := s , component
+            ]
+        ] ifFalse:[
+            s := s , sep , component
+        ].
     ].
     ^ self named:s
 
@@ -273,13 +355,13 @@
      Filename fromComponents:#('/')  
 
      Filename fromComponents:
-	 (Filename components:('.' asFilename pathName))
+         (Filename components:('.' asFilename pathName))
 
      Filename fromComponents:
-	 (Filename components:('.' asFilename name)) 
+         (Filename components:('.' asFilename name)) 
     "
 
-    "Modified: 29.2.1996 / 20:18:34 / cg"
+    "Modified: 8.9.1997 / 00:23:16 / cg"
 !
 
 fromUser
@@ -308,26 +390,28 @@
 
     s := OperatingSystem getHomeDirectory.
     s isNil ifTrue:[
-	^ self defaultDirectory
+        ^ self defaultDirectory
     ].
-    ^ s asFilename
+    ^ self named:s
 
     "
      Filename homeDirectory        
     "
 
-    "Modified: 29.2.1996 / 21:00:31 / cg"
+    "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'."
 
-    ^ (self basicNew) setName:aString
+    ^ (self concreteClass basicNew) setName:aString
 
     "
      Filename named:'/tmp/fooBar'
     "
+
+    "Modified: 7.9.1997 / 23:30:06 / cg"
 !
 
 newTemporary
@@ -354,30 +438,32 @@
      The filenames returned are in aDirectoryPrefix and named 'stxtmp_xx_nn',
      where xx is our unix process id, and nn is a unique number, incremented 
      with every call to this method.
-     Notice: only a filename object is created and returned - no physical
+     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 nm|
+    |pid nameString|
+
+    (self ~~ ConcreteClass) ifTrue:[
+        ^ ConcreteClass newTemporaryIn:aDirectoryPrefix
+    ].
+
+    "/ although the above allows things to be redefined in concrete classes,
+    "/ the following should work on all systems ...
 
     NextTempFilenameIndex isNil ifTrue:[
-	NextTempFilenameIndex := 1.
+        NextTempFilenameIndex := 1.
     ].
 
-    "
-     the following has to be made OS independent ...
-    "
     pid := OperatingSystem getProcessId printString.
-    nm := 'stxtmp_' , pid , '_' , NextTempFilenameIndex printString.
+    nameString := (self tempFileNameTemplate) bindWith:pid with:(NextTempFilenameIndex printString).
     NextTempFilenameIndex := NextTempFilenameIndex + 1.
 
     (aDirectoryPrefix isNil or:[aDirectoryPrefix asString isEmpty]) ifFalse:[
-	nm := aDirectoryPrefix asFilename construct:nm
-    ] ifTrue:[
-	nm := nm asFilename
+        ^ aDirectoryPrefix asFilename construct:nameString
     ].
-    ^ nm
+    ^ self named:nameString
 
     "temp files in '/tmp':
 
@@ -402,7 +488,7 @@
     "
 
     "Modified: 7.9.1995 / 10:48:31 / claus"
-    "Modified: 7.3.1996 / 14:49:56 / cg"
+    "Modified: 8.9.1997 / 00:28:33 / cg"
 !
 
 tempDirectory
@@ -412,19 +498,19 @@
      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 ..."
+             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 := OperatingSystem getEnvironment:envVar.
+        ].
     ].
     tempDir isNil ifTrue:[
-	tempDir := '/tmp'
+        tempDir := self defaultTempDirectoryName
     ].
     ^ self named:tempDir
 
@@ -435,7 +521,7 @@
 
     "Modified: 7.9.1995 / 10:48:31 / claus"
     "Created: 7.3.1996 / 14:51:18 / cg"
-    "Modified: 12.11.1996 / 12:23:19 / cg"
+    "Modified: 8.9.1997 / 00:08:11 / cg"
 ! !
 
 !Filename class methodsFor:'defaults'!
@@ -446,9 +532,10 @@
      OperatingSystems; concreteClass is supposed to return an appropriate class.
      Since in ST/X, there is (currently) only one Filename class, return it here."
 
-    ^ self
+    ^ ConcreteClass ? self
 
     "Created: 14.2.1997 / 16:36:13 / cg"
+    "Modified: 7.9.1997 / 23:29:20 / cg"
 !
 
 defaultClass
@@ -457,7 +544,9 @@
      OperatingSystems; defaultClass is supposed to return an appropriate class.
      Since in ST/X, there is (currently) only one Filename class, return it here."
 
-    ^ self
+    ^ ConcreteClass
+
+    "Modified: 8.9.1997 / 00:36:01 / cg"
 ! !
 
 !Filename class methodsFor:'queries'!
@@ -471,10 +560,16 @@
 
     |sep components|
 
+    (self ~~ ConcreteClass) ifTrue:[
+        ^ ConcreteClass components:aString
+    ].
+
+    "/ the following works on Unix & MSDOS (but not on openVMS)
+
     sep := self separator.
     components := aString asCollectionOfSubstringsSeparatedBy:sep.
     components first isEmpty ifTrue:[
-	components at:1 put:(sep asString)
+        components at:1 put:(sep asString)
     ].
     ^ components
 
@@ -485,7 +580,7 @@
      Filename components:'foo'     
     "
 
-    "Modified: 26.3.1997 / 18:27:04 / cg"
+    "Modified: 8.9.1997 / 00:30:57 / cg"
 !
 
 errorReporter
@@ -508,14 +603,25 @@
 
     |s f matchSet nMatch name words dir|
 
+    (self ~~ ConcreteClass) ifTrue:[
+        ^ ConcreteClass 
+            filenameCompletionFor:aString 
+            directory:inDirectory       
+            directoriesOnly:directoriesOnly 
+            filesOnly:filesOnly 
+            ifMultiple:aBlock
+    ].
+
+    "/ the following works on Unix & MSDOS (but not on openVMS)
+
     s := aString.
     "
      find the last word ...
     "
     words := s asCollectionOfWords.
     words size == 0 ifTrue:[
-	aBlock value:'.' asFilename.
-	^ ''
+        aBlock value:'.' asFilename.
+        ^ ''
     ].
 
     f := words last asFilename.
@@ -525,22 +631,22 @@
     dir := f directory.
 
     directoriesOnly ifTrue:[
-	matchSet := matchSet select:[:aFilename |
-	    (dir construct:aFilename) isDirectory
-	].
+        matchSet := matchSet select:[:aFilename |
+            (dir construct:aFilename) isDirectory
+        ].
     ] ifFalse:[
-	filesOnly ifTrue:[
-	    matchSet := matchSet select:[:aFilename |
-		(dir construct:aFilename) isDirectory not
-	    ].
-	]
+        filesOnly ifTrue:[
+            matchSet := matchSet select:[:aFilename |
+                (dir construct:aFilename) isDirectory not
+            ].
+        ]
     ].
 
     (nMatch := matchSet size) ~~ 1 ifTrue:[
-	"
-	 more than one possible completion -
-	"
-	aBlock value:f
+        "
+         more than one possible completion -
+        "
+        aBlock value:f
     ].
     "
      even with more than one possible completion,
@@ -548,18 +654,18 @@
     "
     name := f asString.
     nMatch == 1 ifTrue:[
-	"
-	 exactly one possible completion -
-	"
-	f := dir construct:matchSet first.
-
-	directoriesOnly ifFalse:[
-	    f isDirectory ifTrue:[
-		(name endsWith:(Filename separator)) ifFalse:[
-		    name := name , '/'
-		].
-	    ].
-	]
+        "
+         exactly one possible completion -
+        "
+        f := dir construct:matchSet first.
+
+        directoriesOnly ifFalse:[
+            f isDirectory ifTrue:[
+                (name endsWith:(Filename separator)) ifFalse:[
+                    name := name , '/'
+                ].
+            ].
+        ]
     ].
 
     "
@@ -568,23 +674,23 @@
     "
     s := ''.
     1 to:(words size - 1) do:[:idx |
-	s := s , (words at:idx) , ' '
+        s := s , (words at:idx) , ' '
     ].
     s := s , name.
 
     "/ special: if there was no change, and the string represented
     "/ is a directories name, add a directory separator
     s = aString ifTrue:[
-	(s endsWith:Filename separator) ifFalse:[
-	    s asFilename isDirectory ifTrue:[
-		^ s , Filename separator asString
-	    ]
-	]
+        (s endsWith:Filename separator) ifFalse:[
+            s asFilename isDirectory ifTrue:[
+                ^ s , Filename separator asString
+            ]
+        ]
     ].
 
     ^ s
 
-    "Modified: 30.4.1996 / 12:13:20 / cg"
+    "Modified: 8.9.1997 / 00:31:51 / cg"
 !
 
 filesMatching:aPattern
@@ -598,6 +704,12 @@
 
     |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.
@@ -611,7 +723,7 @@
      Filename filesMatching:'/usr/local/*'
     "
 
-    "Modified: 15.4.1997 / 15:42:37 / cg"
+    "Modified: 8.9.1997 / 00:32:31 / cg"
 !
 
 isBadCharacter:aCharacter
@@ -619,32 +731,33 @@
 
     |ascii|
 
+    (self ~~ ConcreteClass) ifTrue:[
+        ^ ConcreteClass isBadCharacter:aCharacter
+    ].
+
     ascii := aCharacter asciiValue.
     ascii < 32 ifTrue:[
-	^ true	"/ a control character
+        ^ true  "/ a control character
     ].
     ascii == 16rFF ifTrue:[
-	^ true	"/ delete character
-    ].
-
-    "/ OS specifics ...
-    OperatingSystem isUNIXlike ifTrue:[
-	^ aCharacter ~~ $/
-    ].
-    OperatingSystem isMSDOSlike ifTrue:[
-	^ '<>:"/\|' includes:aCharacter
-    ].
-    OperatingSystem isVMSlike ifTrue:[
-	^ '/\' includes:aCharacter
+        ^ 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
@@ -652,12 +765,17 @@
      what does this do ? (used in FileNavigator-goody).
      GUESS: does it strip off the voulume-character on MSDOS systems ?"
 
+    (self ~~ ConcreteClass) ifTrue:[
+        ^ ConcreteClass localNameStringFrom:aString
+    ].
+
     (aString startsWith:'/') ifTrue:[
-	^ aString copyFrom:2
+        ^ aString copyFrom:2
     ].
     ^ aString
 
     "Modified: 7.9.1995 / 10:44:56 / claus"
+    "Modified: 8.9.1997 / 00:33:51 / cg"
 !
 
 maxLength
@@ -675,23 +793,35 @@
      This is '..' for unix and dos-like systems. 
      (there may be more in the future."
 
-     ^ OperatingSystem parentDirectoryName
-
-     "
-      Filename parentDirectoryName  
-     "
+    (self ~~ ConcreteClass) ifTrue:[
+        ^ ConcreteClass parentDirectoryName
+    ].
+
+    ^ OperatingSystem parentDirectoryName
+
+    "
+     Filename parentDirectoryName  
+    "
+
+    "Modified: 8.9.1997 / 00:34:39 / cg"
 !
 
 separator
     "return the file/directory separator.
-     Usually, this is $/ for unix-like systems 
-     and $\ for dos-like ones (there may be more in the future)."
-
-     ^ OperatingSystem fileSeparator
+     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
@@ -709,15 +839,34 @@
     "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: 15.4.1997 / 13:25:21 / cg"
+    "Modified: 8.9.1997 / 00:35:19 / cg"
 ! !
 
 !Filename methodsFor:'comparing'!
@@ -1232,19 +1381,19 @@
      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."
 
-    |stream buffer s n typeString suffix idx baseNm|
+    |buffer s n typeString suffix idx baseNm|
 
     "/ since executing 'file' takes some time, do the most obvious
     "/ ones here. 
     "/ (also useful for systems, which have no file command, such as NT)
 
     self isSymbolicLink ifTrue:[
-	^ 'symbolic link to ' , (self linkInfo path)
+        ^ 'symbolic link to ' , (self linkInfo path)
     ].
     self isDirectory ifTrue:[
-	self isReadable ifFalse:[^ 'directory, unreadable'].
-	self isExecutable ifFalse:[^ 'directory, locked'].
-	^ 'directory'
+        self isReadable ifFalse:[^ 'directory, unreadable'].
+        self isExecutable ifFalse:[^ 'directory, locked'].
+        ^ 'directory'
     ].
     self isReadable ifFalse:[^ 'unreadable'].
     self fileSize == 0 ifTrue:[^ 'empty'].
@@ -1252,76 +1401,60 @@
     buffer := String new:2024.
     s := self readStream.
     s notNil ifTrue:[
-	n := s nextBytes:buffer size into:buffer.
-	s close.
-
-	true "n == buffer size" ifTrue:[
-	    ((suffix := self suffix asLowercase) = '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'
-		    ]
-		].
-	    ].
+        n := s nextBytes:buffer size into:buffer.
+        s close.
+
+        true "n == buffer size" ifTrue:[
+            ((suffix := self suffix asLowercase) = '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 := self withoutSuffix baseName asLowercase.
-	    (baseNm = 'makefile') ifTrue:[
-		(buffer startsWith:'#') ifTrue:[
-		    ^ 'make rules'
-		]
-	    ]
-	]
+            (suffix = 'ps') ifTrue:[
+                (buffer findString:'%!!PS-Adobe') ~~ 0 ifTrue:[
+                    ^ 'PostScript document'
+                ].
+            ].
+
+            baseNm := self withoutSuffix baseName asLowercase.
+            (baseNm = 'makefile') ifTrue:[
+                (buffer startsWith:'#') ifTrue:[
+                    ^ 'make rules'
+                ]
+            ]
+        ]
     ].
 
-    typeString := 'file'.
-    OperatingSystem isUNIXlike ifTrue:[
-	stream := PipeStream readingFrom:('file ' , self pathName).
-    ].
-    stream notNil ifTrue:[
-	typeString := stream contents asString.
-	stream close.
-	typeString := typeString copyFrom:(typeString indexOf:$:) + 1.
-	typeString := typeString withoutSeparators
-    ] ifFalse:[
-	"
-	 could add some fallback code here, for systems, where no
-	 file command is avaliable ...
-	 ... or at least analyze directory info.
-	"
-    ].
-    ^ typeString
+    ^ 'file'
 
     "
      'Makefile' asFilename fileType 
@@ -1331,7 +1464,7 @@
      'bitmaps/SBrowser.xbm' asFilename fileType    
     "
 
-    "Modified: 30.4.1997 / 12:40:43 / cg"
+    "Modified: 7.9.1997 / 23:43:48 / cg"
 !
 
 id
@@ -1481,31 +1614,6 @@
     "
 
     "Modified: 29.2.1996 / 20:55:06 / cg"
-!
-
-constructString:subname
-    "taking the receiver as a directory name, construct a new
-     filenames string for an entry within this directory 
-     (i.e. for a file or a subdirectory in that directory)."
-
-    |sepString|
-
-    sepString := self class separator asString.
-    nameString = sepString ifTrue:[
-	"I am the root"
-	^ sepString  , subname
-    ].
-    ^ nameString , sepString , subname asString
-
-    "
-     '/tmp' asFilename constructString:'foo'   
-     '/' asFilename constructString:'foo'         
-     '/usr/tmp' asFilename constructString:'foo'
-     '/foo/bar' asFilename constructString:'baz' 
-    "
-
-    "Modified: 7.9.1995 / 10:15:22 / claus"
-    "Modified: 29.2.1996 / 20:55:18 / cg"
 ! !
 
 !Filename methodsFor:'misc'!
@@ -1517,6 +1625,7 @@
      a directory delimiter and returns a new fileName instance.
      See also: #withSuffix: which is new and better."
 
+    self obsoleteMethodWarning:'use #construct:'.
     ^ (nameString , aString asString)
 
     "
@@ -1526,7 +1635,7 @@
      'Makefile' asFilename construct:'.bak'     
     "
 
-    "Modified: 29.2.1996 / 20:54:12 / cg"
+    "Modified: 7.9.1997 / 23:45:36 / cg"
 ! !
 
 !Filename methodsFor:'printing & storing'!
@@ -1534,9 +1643,12 @@
 printOn:aStream
     "append a printed representation of the receiver to aStream."
 
-    aStream nextPutAll:'FileName('''.
+    aStream nextPutAll:(self class name).
+    aStream nextPutAll:'('''.
     nameString printOn:aStream.
     aStream nextPutAll:''')'
+
+    "Modified: 7.9.1997 / 23:46:20 / cg"
 !
 
 storeOn:aStream
@@ -1734,10 +1846,9 @@
     "return true, if the receiver represents an absolute pathname
      on some disk volume (MSDOS only)"
 
-    OperatingSystem isMSDOSlike ifTrue:[
-	^ (nameString at:2) == $:
-    ].
     ^ false
+
+    "Modified: 7.9.1997 / 23:54:33 / cg"
 !
 
 isWritable
@@ -1946,89 +2057,89 @@
 
     sepString := self class separator asString.
     (nameString endsWith:sepString) ifTrue:[
-	^ #()
+        ^ #()
     ].
 
     parentString := self class parentDirectoryName.
     baseName := self baseName.
     baseName ~= nameString 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 construct:nameString) directory
-	]
+        aDirectory isNil ifTrue:[
+            dir := self directory
+        ] ifFalse:[
+            dir := (aDirectory construct:nameString) directory
+        ]
     ].
 
     matching := OrderedCollection new.
     dir directoryContents do:[:fileName |
-	((fileName ~= '.') and:[fileName ~= parentString]) ifTrue:[
-	    (fileName startsWith:baseName) ifTrue:[
-		matching add:fileName
-	    ]
-	]
+        ((fileName ~= '.') and:[fileName ~= parentString]) ifTrue:[
+            (fileName startsWith:baseName) ifTrue:[
+                matching add:fileName
+            ]
+        ]
     ].
     (nMatch := matching size) > 1 ifTrue:[
-	"
-	 find the longest common prefix
-	"
-	matchLen := baseName size.
-	matchLen > matching first size ifTrue:[
-	    try := baseName.
-	    allMatching := false
-	] ifFalse:[
-	    try := matching first copyTo:matchLen.
-	    allMatching := true.
-	].
-
-	[allMatching] whileTrue:[
-	    matching do:[:aName |
-		(aName startsWith:try) ifFalse:[
-		    allMatching := false
-		]
-	    ].
-	    allMatching ifTrue:[
-		matchLen <  matching first size ifTrue:[
-		    matchLen := matchLen + 1.
-		    try := matching first copyTo:matchLen.
-		] ifFalse:[
-		    allMatching := false
-		]
-	    ] ifFalse:[
-		try := matching first copyTo:matchLen - 1.
-	    ]
-	].
-	"
-	 and set my name to the last full match
-	"
-	nameString := try
+        "
+         find the longest common prefix
+        "
+        matchLen := baseName size.
+        matchLen > matching first size ifTrue:[
+            try := baseName.
+            allMatching := false
+        ] ifFalse:[
+            try := matching first copyTo:matchLen.
+            allMatching := true.
+        ].
+
+        [allMatching] whileTrue:[
+            matching do:[:aName |
+                (aName startsWith:try) ifFalse:[
+                    allMatching := false
+                ]
+            ].
+            allMatching ifTrue:[
+                matchLen <  matching first size ifTrue:[
+                    matchLen := matchLen + 1.
+                    try := matching first copyTo:matchLen.
+                ] ifFalse:[
+                    allMatching := false
+                ]
+            ] ifFalse:[
+                try := matching first copyTo:matchLen - 1.
+            ]
+        ].
+        "
+         and set my name to the last full match
+        "
+        nameString := try
     ].
 
     "
      if I had a directory-prefix, change names in collection ...
     "
     prefix notNil ifTrue:[
-	prefix = '/' ifTrue:[
-	    "/ avoid introducing double slashes
-	    prefix := ''
-	].
-	matching := matching collect:[:n | prefix , '/' , n].
-	nMatch == 1 ifTrue:[
-	    nameString := matching first
-	] ifFalse:[
-	    nMatch > 1 ifTrue:[
-		nameString := prefix , '/' , nameString
-	    ]
-	]
+        prefix = sepString ifTrue:[
+            "/ avoid introducing double slashes
+            prefix := ''
+        ].
+        matching := matching collect:[:n | prefix , sepString , n].
+        nMatch == 1 ifTrue:[
+            nameString := matching first
+        ] ifFalse:[
+            nMatch > 1 ifTrue:[
+                nameString := prefix , sepString , nameString
+            ]
+        ]
     ] ifFalse:[
-	nMatch == 1 ifTrue:[
-	    nameString := matching first
-	]
+        nMatch == 1 ifTrue:[
+            nameString := matching first
+        ]
     ].
 
     "
@@ -2050,27 +2161,7 @@
      '../../libpr' asFilename filenameCompletion    
     "
 
-    "Modified: 29.2.1996 / 20:28:45 / cg"
-!
-
-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"
+    "Modified: 7.9.1997 / 23:56:53 / cg"
 !
 
 head 
@@ -2186,22 +2277,6 @@
     "Modified: 21.12.1996 / 15:29:50 / cg"
 !
 
-suffix
-    "return my suffix.
-     The suffix is the namepart after the final period character,
-     or the empty string, if the name does not contain a period."
-
-    ^ self prefixAndSuffix at:2
-
-    "
-     'abc.st' asFilename suffix   
-     'abc' asFilename suffix      
-     'a.b.c' asFilename suffix    
-    "
-
-    "Modified: 7.9.1995 / 11:09:03 / claus"
-!
-
 tail
     "the files name without directory prefix as a string. 
      An alias for baseName, for ST-80 compatiblity."
@@ -2219,18 +2294,36 @@
 
 volume
     "return the disc volume part of the name or an empty string.
-     This is only used with DOS filenames - on unix, an empty string is returned"
-
-    OperatingSystem isMSDOSlike ifTrue:[
-	(nameString at:2) == $: ifTrue:[
-	    ^ nameString copyTo:1
-	]
-    ].
+     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:'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,
@@ -2270,6 +2363,22 @@
     "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 suffix.
      If the name already has a suffix, the new suffix replacaes it;
@@ -2323,5 +2432,6 @@
 !Filename class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Filename.st,v 1.94 1997-09-06 23:47:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Filename.st,v 1.95 1997-09-08 18:05:39 cg Exp $'
 ! !
+Filename initialize!