Unused method referenced undefined var and could not be stc-compiled
authorStefan Vogel <sv@exept.de>
Wed, 01 Feb 2006 12:05:09 +0100
changeset 1590 61d8f450a232
parent 1589 f0607bf986e0
child 1591 f655110a107f
Unused method referenced undefined var and could not be stc-compiled
Archiver.st
--- a/Archiver.st	Wed Jan 25 13:22:23 2006 +0100
+++ b/Archiver.st	Wed Feb 01 12:05:09 2006 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 2003 by eXept Software AG
-              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
@@ -102,7 +102,7 @@
 copyright
 "
  COPYRIGHT (c) 2003 by eXept Software AG
-              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
@@ -119,13 +119,13 @@
     ^ self classForMimeType:aMimeType fileName:nil
 
     "
-     self classForMimeType:'application/x-tar'    
-     self classForMimeType:'application/x-foo'    
-     self classForMimeType:'application/x-squeak-archive'   
-     self classForMimeType:'application/java-archive'   
-     'foo.sar' asFilename mimeTypeFromName               
-     'foo.jar' asFilename mimeTypeFromName               
-     'foo.a' asFilename mimeTypeFromName               
+     self classForMimeType:'application/x-tar'
+     self classForMimeType:'application/x-foo'
+     self classForMimeType:'application/x-squeak-archive'
+     self classForMimeType:'application/java-archive'
+     'foo.sar' asFilename mimeTypeFromName
+     'foo.jar' asFilename mimeTypeFromName
+     'foo.a' asFilename mimeTypeFromName
     "
 !
 
@@ -135,49 +135,49 @@
     aMimeType isNil ifTrue:[^ nil].
 
     className := (
-            #(
-                ('application/x-tar-compressed'         CompressedTarArchive    )  "/ abstract - see below
-                ('application/x-tar-gzip-compressed'    TarGZipArchive      ) 
-                ('application/x-tar-bzip2-compressed'   TarBZ2Archive       ) 
-                ('application/x-tar'                    TarArchive          )
-                ('application/x-gzip-compressed'        GZipCompressed      )
-                ('application/x-zip-compressed'         ZipArchive          )
-                ('application/x-bzip2-compressed'       BZ2Compressed       )
-                ('application/x-squeak-archive'         ZipArchive          )
-                ('application/java-archive'             ZipArchive          )
+	    #(
+		('application/x-tar-compressed'         CompressedTarArchive    )  "/ abstract - see below
+		('application/x-tar-gzip-compressed'    TarGZipArchive      )
+		('application/x-tar-bzip2-compressed'   TarBZ2Archive       )
+		('application/x-tar'                    TarArchive          )
+		('application/x-gzip-compressed'        GZipCompressed      )
+		('application/x-zip-compressed'         ZipArchive          )
+		('application/x-bzip2-compressed'       BZ2Compressed       )
+		('application/x-squeak-archive'         ZipArchive          )
+		('application/java-archive'             ZipArchive          )
 
-                ('application/x-ar-archive'             ArArchive           )
-                ('application/x-ar-library'             ArArchive           )
-                ('application/library'                  ArArchive           )
+		('application/x-ar-archive'             ArArchive           )
+		('application/x-ar-library'             ArArchive           )
+		('application/library'                  ArArchive           )
 
 "/                ('application/x-rpm'                    RPMArchive          )
 "/                ('application/x-rpm-archive'            RPMArchive          )
 "/                ('application/x-redhat packet manager'  RPMArchive          )
-            ) detect:[:entry | entry first = aMimeType] ifNone:#(nil nil)
-        ) last.
+	    ) detect:[:entry | entry first = aMimeType] ifNone:#(nil nil)
+	) last.
     className isNil ifTrue:[^ nil].
 
     className = CompressedTarArchive ifTrue:[
-        aFileNameOrNil isNil ifTrue:[
-            className := #TarGZipArchive
-        ] ifFalse:[
-            aFileNameOrNil suffix = 'bz2' ifTrue:[
-                className := #TarBZ2Archive
-            ] ifFalse:[
-                className := #TarGZipArchive
-            ]
-        ].
+	aFileNameOrNil isNil ifTrue:[
+	    className := #TarGZipArchive
+	] ifFalse:[
+	    aFileNameOrNil suffix = 'bz2' ifTrue:[
+		className := #TarBZ2Archive
+	    ] ifFalse:[
+		className := #TarGZipArchive
+	    ]
+	].
     ].
     ^ self privateClassesAt:className.
 
     "
-     self classForMimeType:'application/x-tar'    
-     self classForMimeType:'application/x-foo'    
-     self classForMimeType:'application/x-squeak-archive'   
-     self classForMimeType:'application/java-archive'   
-     'foo.sar' asFilename mimeTypeFromName               
-     'foo.jar' asFilename mimeTypeFromName               
-     'foo.a' asFilename mimeTypeFromName               
+     self classForMimeType:'application/x-tar'
+     self classForMimeType:'application/x-foo'
+     self classForMimeType:'application/x-squeak-archive'
+     self classForMimeType:'application/java-archive'
+     'foo.sar' asFilename mimeTypeFromName
+     'foo.jar' asFilename mimeTypeFromName
+     'foo.a' asFilename mimeTypeFromName
     "
 !
 
@@ -238,14 +238,14 @@
 
     aColOfFiles isNil ifTrue:[^ ''].
 
-    ^ String 
-        streamContents:[:str |
-            aColOfFiles do:[:fn | 
-                str nextPutAll:' "'.
-                str nextPutAll:(fn asFilename baseName).
-                str nextPutAll:'"'.
-            ].
-        ]
+    ^ String
+	streamContents:[:str |
+	    aColOfFiles do:[:fn |
+		str nextPutAll:' "'.
+		str nextPutAll:(fn asFilename baseName).
+		str nextPutAll:'"'.
+	    ].
+	]
 ! !
 
 !Archiver class methodsFor:'commandOutputReader'!
@@ -356,8 +356,8 @@
     "return the value of the instance variable 'temporaryDirectory' (automatically generated)"
 
     temporaryDirectory isNil ifTrue:[
-        temporaryDirectory := Filename newTemporary.
-        temporaryDirectory makeDirectory.
+	temporaryDirectory := Filename newTemporary.
+	temporaryDirectory makeDirectory.
     ].
     ^ temporaryDirectory
 ! !
@@ -374,7 +374,7 @@
     self fileName isNil ifTrue:[ ^ self].
     dir := self fileName directory.
     cmd := self getCommandToListFiles:aColOfFiles.
-    self executeCommand:cmd directory:dir 
+    self executeCommand:cmd directory:dir
 !
 
 removeFilesFromArchive:aColOfFiles
@@ -399,17 +399,17 @@
     | tmp |
 
     temporaryDirectory notNil ifTrue:[
-        tmp := self temporaryDirectory.
-        (FileDirectory directoryNamed:(tmp directory)) removeDirectory:tmp baseName.
-        temporaryDirectory := nil.
+	tmp := self temporaryDirectory.
+	(FileDirectory directoryNamed:(tmp directory)) removeDirectory:tmp baseName.
+	temporaryDirectory := nil.
     ].
 !
 
 stopProcess
 
     process notNil ifTrue:[
-        process terminateWithAllSubprocesses.
-        process waitUntilTerminated.
+	process terminateWithAllSubprocesses.
+	process waitUntilTerminated.
     ].
 ! !
 
@@ -420,32 +420,32 @@
 
     synchron isNil ifTrue:[synchron := true].
     synchron ifTrue:[
-         OperatingSystem 
-            executeCommand:cmd
-            inputFrom:nil
-            outputTo:outStream
-            errorTo:errorStream
-            inDirectory:aDirectory
-            lineWise:true
-            onError:[:status| false].
+	 OperatingSystem
+	    executeCommand:cmd
+	    inputFrom:nil
+	    outputTo:outStream
+	    errorTo:errorStream
+	    inDirectory:aDirectory
+	    lineWise:true
+	    onError:[:status| false].
     ] ifFalse:[
-        process := Process for:[
-                [ 
-                     OperatingSystem 
-                        executeCommand:cmd
-                        inputFrom:nil
-                        outputTo:outStream
-                        errorTo:errorStream
-                        inDirectory:aDirectory
-                        lineWise:true
-                        onError:[:status| false].
-                ] ensure:[
-                    process := nil.
-                ].
+	process := Process for:[
+		[
+		     OperatingSystem
+			executeCommand:cmd
+			inputFrom:nil
+			outputTo:outStream
+			errorTo:errorStream
+			inDirectory:aDirectory
+			lineWise:true
+			onError:[:status| false].
+		] ensure:[
+		    process := nil.
+		].
 
-        ] priority:(Processor systemBackgroundPriority).
-        process name:('Archiver command: ', cmd).
-        process resume.
+	] priority:(Processor systemBackgroundPriority).
+	process name:('Archiver command: ', cmd).
+	process resume.
     ]
 !
 
@@ -480,11 +480,11 @@
 
 addDoubleQuotedFilenames:collectionOfFilenames toStream:aStream
     collectionOfFilenames notNil ifTrue:[
-        collectionOfFilenames do:[:el | 
-            aStream nextPutAll:' "'.
-            aStream nextPutAll:(el asString).
-            aStream nextPutAll:'"'
-        ].
+	collectionOfFilenames do:[:el |
+	    aStream nextPutAll:' "'.
+	    aStream nextPutAll:(el asString).
+	    aStream nextPutAll:'"'
+	].
     ].
 ! !
 
@@ -511,24 +511,24 @@
     "/ keep a save copy
     archivFile renameTo:(archivFile withSuffix:'sav').
     [
-        "/ copy files to be added to tempDir
-        colOfFiles do:[:file |
-            file recursiveCopyTo:(tempDir construct:(file asFilename baseName))
-        ].
+	"/ copy files to be added to tempDir
+	colOfFiles do:[:file |
+	    file recursiveCopyTo:(tempDir construct:(file asFilename baseName))
+	].
 
-        "/ addFiles to the tar archive
-        cmd := self getCommandToAdd:colOfFiles toArchive:archivInTemp.
-        self executeCommand:cmd directory:tempDir.
+	"/ addFiles to the tar archive
+	cmd := self getCommandToAdd:colOfFiles toArchive:archivInTemp.
+	self executeCommand:cmd directory:tempDir.
 
-        "/ copy tar archiv back
-        archivInTemp copyTo:archivFile.
+	"/ copy tar archiv back
+	archivInTemp copyTo:archivFile.
     ] ensure:[
-        "/ cg: remove the tempFile
-        archivInTemp remove.
-        "/ cg: remove copied files
-        colOfFiles do:[:file |
-            (tempDir construct:(file asFilename baseName)) remove.
-        ].
+	"/ cg: remove the tempFile
+	archivInTemp remove.
+	"/ cg: remove copied files
+	colOfFiles do:[:file |
+	    (tempDir construct:(file asFilename baseName)) remove.
+	].
     ].
 !
 
@@ -548,14 +548,14 @@
     self extractFiles:aColOfFiles to:tempDir.
 
     aColOfFiles do:[ : aFileString |
-        tempFile := self temporaryDirectory construct:aFileString.
-        targetFile := aDirectory construct:(aFileString asFilename baseName).
-        targetFile exists ifTrue:[
-            targetFile recursiveRemove.
-        ].
-        tempFile exists ifTrue:[
-            tempFile recursiveCopyTo:targetFile.
-        ].
+	tempFile := self temporaryDirectory construct:aFileString.
+	targetFile := aDirectory construct:(aFileString asFilename baseName).
+	targetFile exists ifTrue:[
+	    targetFile recursiveRemove.
+	].
+	tempFile exists ifTrue:[
+	    tempFile recursiveCopyTo:targetFile.
+	].
     ].
 !
 
@@ -564,7 +564,7 @@
     |cmd|
 
     cmd := self getCommandToRemoveFiles:aColOfFiles.
-    self executeCommand:cmd directory:(self fileName directory). 
+    self executeCommand:cmd directory:(self fileName directory).
 ! !
 
 !Archiver::MultiFileArchive methodsFor:'command strings'!
@@ -611,12 +611,12 @@
     |words archiverColumns item index key|
 
     (firstLineRead not and:[archiver class hasTitleLine]) ifTrue:[
-        firstLineRead := true.
-        ^ nil.
+	firstLineRead := true.
+	^ nil.
     ].
 
     (archiver isValidOutputLine:line) ifFalse:[
-        ^ nil.
+	^ nil.
     ].
 
     words := line asCollectionOfWords.
@@ -625,41 +625,41 @@
     index := 1.
 
     archiverColumns do:[:colDescr |
-        | itemWordCount itemStream itemFieldSelector itemWriter |
+	| itemWordCount itemStream itemFieldSelector itemWriter |
 
-        itemWordCount := colDescr second.
-        itemFieldSelector := colDescr first.
-        itemFieldSelector notNil ifTrue:[
-            itemWriter := (itemFieldSelector , ':') asSymbol.
-        ].
-        itemStream := WriteStream on:''.
-        itemWordCount == #rest ifTrue:[
-            words from:index do:[:w|
-                itemStream nextPutAll:w.
-                itemStream space.
-            ].
-        ] ifFalse:[
-            words from:index to:(index + itemWordCount - 1) do:[:w|
-                itemStream nextPutAll:w.
-                itemStream space.
-            ].
-            index := index + itemWordCount.
-        ].
-        itemWriter notNil ifTrue:[
-            item perform:itemWriter with:(itemStream contents withoutSeparators).
-        ].
-        itemStream close.
+	itemWordCount := colDescr second.
+	itemFieldSelector := colDescr first.
+	itemFieldSelector notNil ifTrue:[
+	    itemWriter := (itemFieldSelector , ':') asSymbol.
+	].
+	itemStream := WriteStream on:''.
+	itemWordCount == #rest ifTrue:[
+	    words from:index do:[:w|
+		itemStream nextPutAll:w.
+		itemStream space.
+	    ].
+	] ifFalse:[
+	    words from:index to:(index + itemWordCount - 1) do:[:w|
+		itemStream nextPutAll:w.
+		itemStream space.
+	    ].
+	    index := index + itemWordCount.
+	].
+	itemWriter notNil ifTrue:[
+	    item perform:itemWriter with:(itemStream contents withoutSeparators).
+	].
+	itemStream close.
     ].
     ((archiverColumns collect:[:el| el first]) includes:#permissions) ifTrue:[
-        (item permissions startsWith:$d) ifTrue:[
-            key := #directory.
-            item isDirectory:true.
-        ] ifFalse:[
-            key := MIMETypes mimeTypeForFilename:(item fileName asFilename baseName).
-            item isDirectory:false.
-        ].
+	(item permissions startsWith:$d) ifTrue:[
+	    key := #directory.
+	    item isDirectory:true.
+	] ifFalse:[
+	    key := MIMETypes mimeTypeForFilename:(item fileName asFilename baseName).
+	    item isDirectory:false.
+	].
     ] ifFalse:[
-        key := MIMETypes mimeTypeForFilename:(item fileName asFilename baseName).
+	key := MIMETypes mimeTypeForFilename:(item fileName asFilename baseName).
     ].
     item icon:(FileBrowser iconForKeyMatching:key).
     ^ item
@@ -689,16 +689,16 @@
 
     directory := newFile directory.
     (directory exists) ifFalse:[
-        DialogBox warn:'cannot compress to non-existing directory ', directory asString.
+	DialogBox warn:'cannot compress to non-existing directory ', directory asString.
     ].
     (directory isDirectory) ifFalse:[
-        DialogBox warn:'cannot compress to non-directory ', directory asString.
+	DialogBox warn:'cannot compress to non-directory ', directory asString.
     ].
 
     cmd := self getCommandToCompress:aFile asNew:newFile.
     self executeCommand:cmd directory:directory.
     newFile exists ifTrue:[
-        self fileName:newFile.
+	self fileName:newFile.
     ].
 !
 
@@ -710,29 +710,20 @@
     | cmd file newFile|
 
     (aDirectory exists) ifFalse:[
-        DialogBox warn:'cannot uncompress to non-existing directory ', aDirectory asString.
-        ^ self
+	DialogBox warn:'cannot uncompress to non-existing directory ', aDirectory asString.
+	^ self
     ].
     (aDirectory isDirectory) ifFalse:[
-        DialogBox warn:'cannot uncompress to file ', aDirectory asString.
-        ^ self
+	DialogBox warn:'cannot uncompress to file ', aDirectory asString.
+	^ self
     ].
     file := newFile := self fileName.
     (file directory pathName = aDirectory pathName) ifFalse:[
-        newFile := aDirectory construct:(file baseName).
-        file copyTo:newFile.
+	newFile := aDirectory construct:(file baseName).
+	file copyTo:newFile.
     ].
     cmd := self getCommandToUncompress:newFile.
-    self executeCommand:cmd directory:aDirectory. 
-! !
-
-!Archiver::CompressedFile methodsFor:'actions private'!
-
-synchronize
-    |gzipArchiver|
-
-    gzipArchiver := Archiver::BZ2Compressed with:nil.
-    gzipArchiver compressFile:(tarArchiver fileName) to:(self fileName).
+    self executeCommand:cmd directory:aDirectory.
 ! !
 
 !Archiver::CompressedFile methodsFor:'columns'!
@@ -748,20 +739,20 @@
 !Archiver::CompressedFile methodsFor:'command strings'!
 
 getCommandToCompress:aFile asNew:newFile
-    ^ '%1 -c %2 > %3' 
-        bindWith:self class compressCommand
-        with:aFile asString 
-        with:newFile asString
+    ^ '%1 -c %2 > %3'
+	bindWith:self class compressCommand
+	with:aFile asString
+	with:newFile asString
 !
 
 getCommandToListFiles:dummyArg
     ^ 'gzip -l "' , self fileName baseName , '"'
 !
 
-getCommandToUncompress:aFileName 
-    ^ '%1 %2' 
-        bindWith:self class uncompressCommand
-        with:aFileName baseName
+getCommandToUncompress:aFileName
+    ^ '%1 %2'
+	bindWith:self class uncompressCommand
+	with:aFileName baseName
 ! !
 
 !Archiver::BZ2Compressed class methodsFor:'command strings'!
@@ -777,9 +768,9 @@
 !Archiver::BZ2Compressed methodsFor:'columns'!
 
 columns
-    ^ #(      
-         #(#fileName        1)
-    ) 
+    ^ #(
+	 #(#fileName        1)
+    )
 !
 
 isValidOutputLine:line
@@ -825,7 +816,7 @@
     file := self fileName withoutSuffix.
     tarFilename := file baseName.
     file suffix ~= 'tar' ifTrue:[
-        tarFilename := tarFilename , '.tar'
+	tarFilename := tarFilename , '.tar'
     ].
     tarFile := self temporaryDirectory construct:tarFilename.
     tarArchiver := Archiver::TarArchive with:tarFile.
@@ -912,14 +903,14 @@
 
     "/ columns in stream order
     "/  colums id/readSelector          words to read
-    ^ #( "/ #(#method          1)      
-         "/ #(#crc             1)    
-         "/ #(#dateAndTime     3)   
-         #(#compressSize    1)  
-         #(#size            1) 
-         #(#ratio           1) 
-         #(#fileName        #rest)
-    ) 
+    ^ #( "/ #(#method          1)
+	 "/ #(#crc             1)
+	 "/ #(#dateAndTime     3)
+	 #(#compressSize    1)
+	 #(#size            1)
+	 #(#ratio           1)
+	 #(#fileName        #rest)
+    )
 !
 
 isValidOutputLine:line
@@ -942,16 +933,16 @@
 
 columns
     "/  colums id/readSelector words to read
-    ^ #( 
-         #(#permissions     1)      
-         #(#ownerGroup      1)    
-         #(#size            1)   
-         #(#monthName       1)  
-         #(#dayString       1)  
-         #(#timeString      1)  
-         #(#yearString      1)  
-         #(#fileName        #rest)
-    ) 
+    ^ #(
+	 #(#permissions     1)
+	 #(#ownerGroup      1)
+	 #(#size            1)
+	 #(#monthName       1)
+	 #(#dayString       1)
+	 #(#timeString      1)
+	 #(#yearString      1)
+	 #(#fileName        #rest)
+    )
 !
 
 isValidOutputLine:line
@@ -961,38 +952,38 @@
 
 !Archiver::ArArchive methodsFor:'command strings'!
 
-getCommandToExtractFiles:sel intoDirectory:dir 
+getCommandToExtractFiles:sel intoDirectory:dir
     |stream|
 
     stream := WriteStream on:''.
 
     "/ 'x'  arArchivUnpackOption
-    stream nextPutAll:('(cd %3 ; %1 x "%2" ' 
-                    bindWith:self class arCommand
-                    with:self fileName asString string
-                    with:dir asString string).
+    stream nextPutAll:('(cd %3 ; %1 x "%2" '
+		    bindWith:self class arCommand
+		    with:self fileName asString string
+		    with:dir asString string).
 
     sel notNil ifTrue:[
-        sel do:[:el | 
-            stream nextPutAll:' "'.
-            stream nextPutAll:(el asString).
-            stream nextPutAll:'"'
-        ].
+	sel do:[:el |
+	    stream nextPutAll:' "'.
+	    stream nextPutAll:(el asString).
+	    stream nextPutAll:'"'
+	].
     ].
     stream nextPutAll:')'.
     ^ stream contents.
 !
 
-getCommandToListFiles:aColOfFiles 
+getCommandToListFiles:aColOfFiles
     |stream|
 
     stream := WriteStream on:''.
 
     "/ 't'  arArchivListContentsOption
     "/ 'v'  arArchivVerboseOption
-    stream nextPutAll:('%1 tv "%2"' 
-                    bindWith:self class arCommand
-                    with:self fileName baseName).
+    stream nextPutAll:('%1 tv "%2"'
+		    bindWith:self class arCommand
+		    with:self fileName baseName).
 
     stream nextPutAll:(self class stringWithQuotedFileBaseNames:aColOfFiles).
     ^ stream contents.
@@ -1026,12 +1017,12 @@
 columns
 
     "/  colums id/readSelector words to read
-    ^ #( #(#permissions     1)      
-         #(#ownerGroup      1)    
-         #(#size            1)   
-         #(#dateAndTime     2)  
-         #(#fileName        #rest)
-    ) 
+    ^ #( #(#permissions     1)
+	 #(#ownerGroup      1)
+	 #(#size            1)
+	 #(#dateAndTime     2)
+	 #(#fileName        #rest)
+    )
 !
 
 isValidOutputLine:line
@@ -1050,15 +1041,15 @@
 
     "/ 'r'  TarArchivAddOption
     "/ 'f'  TarArchivFileOption
-    stream nextPutAll:('%1 rf "%2"' 
-                    bindWith:self class tarCommand
-                    with:archiveFile asString string).
+    stream nextPutAll:('%1 rf "%2"'
+		    bindWith:self class tarCommand
+		    with:archiveFile asString string).
 
     stream nextPutAll:(self class stringWithQuotedFileBaseNames:aColOfFiles).
     ^ stream contents
 !
 
-getCommandToExtractFiles:sel intoDirectory:dir 
+getCommandToExtractFiles:sel intoDirectory:dir
     |stream|
 
     stream := WriteStream on:''.
@@ -1066,22 +1057,22 @@
     "/ 'x'  TarArchivUnpackOption
     "/ 'f'  TarArchivFileOption
     "/ 'C'  TarArchivUnpackInDirectoryOption
-    stream nextPutAll:('%1 -xf "%2" -C %3' 
-                    bindWith:self class tarCommand
-                    with:self fileName asString string
-                    with:dir asString).
+    stream nextPutAll:('%1 -xf "%2" -C %3'
+		    bindWith:self class tarCommand
+		    with:self fileName asString string
+		    with:dir asString).
 
     sel notNil ifTrue:[
-        sel do:[:el | 
-            stream nextPutAll:' "'.
-            stream nextPutAll:(el asString).
-            stream nextPutAll:'"'
-        ].
+	sel do:[:el |
+	    stream nextPutAll:' "'.
+	    stream nextPutAll:(el asString).
+	    stream nextPutAll:'"'
+	].
     ].
     ^ stream contents.
 !
 
-getCommandToListFiles:aColOfFiles 
+getCommandToListFiles:aColOfFiles
     |stream|
 
     stream := WriteStream on:''.
@@ -1089,15 +1080,15 @@
     "/ 't'  TarArchivListContentsOption
     "/ 'v'  TarArchivVerboseOption
     "/ 'f'  TarArchivFileOption
-    stream nextPutAll:('%1 -tvf "%2"' 
-                    bindWith:self class tarCommand
-                    with:self fileName baseName).
+    stream nextPutAll:('%1 -tvf "%2"'
+		    bindWith:self class tarCommand
+		    with:self fileName baseName).
 
     stream nextPutAll:(self class stringWithQuotedFileBaseNames:aColOfFiles).
     ^ stream contents.
 !
 
-getCommandToRemoveFiles:sel 
+getCommandToRemoveFiles:sel
     |stream filename|
 
     filename := self fileName.
@@ -1106,9 +1097,9 @@
     stream := WriteStream on:''.
 
     "/ 'f'  TarArchivFileOption
-    stream nextPutAll:('%1 --delete -f "%2"' 
-                    bindWith:self class tarCommand
-                    with:self fileName baseName).
+    stream nextPutAll:('%1 --delete -f "%2"'
+		    bindWith:self class tarCommand
+		    with:self fileName baseName).
 
     stream nextPutAll:(self class stringWithQuotedFileBaseNames:sel).
     ^ stream contents
@@ -1214,15 +1205,15 @@
 columns
 
     "/  colums id/readSelector    words to read
-    ^ #( (#permissions     1)      
-         (#version         2)    
-         (#size            1)     
-         (#type            1)    
-         (#ratio           1)    
-         (nil              1)  
-         (#dateAndTime     2)  
-         (#fileName        #rest)
-    ) 
+    ^ #( (#permissions     1)
+	 (#version         2)
+	 (#size            1)
+	 (#type            1)
+	 (#ratio           1)
+	 (nil              1)
+	 (#dateAndTime     2)
+	 (#fileName        #rest)
+    )
 !
 
 isValidOutputLine:line
@@ -1238,14 +1229,14 @@
     archiveFile exists ifFalse:[^ nil].
 
     stream := WriteStream on:''.
-    
-    stream nextPutAll:('%1 -r "%2"' 
-                    bindWith:self class zipCommand
-                    with:archiveFile asString string).
 
-    self 
-        addDoubleQuotedFilenames:(aColOfFiles collect:[:each | each asFilename baseName])
-        toStream:stream.
+    stream nextPutAll:('%1 -r "%2"'
+		    bindWith:self class zipCommand
+		    with:archiveFile asString string).
+
+    self
+	addDoubleQuotedFilenames:(aColOfFiles collect:[:each | each asFilename baseName])
+	toStream:stream.
 
     ^ stream contents
 !
@@ -1258,16 +1249,16 @@
     "/ -o   UnzipOverwriteExistingFilesOption
     "/ -d   UnzipExtDirectoryOption
 
-    stream nextPutAll:('%1 -o -d "%2" "%3"' 
-                    bindWith:self class unzipCommand
-                    with:dir asString string
-                    with:self fileName asString).
+    stream nextPutAll:('%1 -o -d "%2" "%3"'
+		    bindWith:self class unzipCommand
+		    with:dir asString string
+		    with:self fileName asString).
 
     self addDoubleQuotedFilenames:aColOfFiles toStream:stream.
     ^ stream contents.
 !
 
-getCommandToListFiles:aColOfFiles 
+getCommandToListFiles:aColOfFiles
     |stream|
 
     stream := WriteStream on:''.
@@ -1275,26 +1266,26 @@
     "/  -Z      ZipInfoOption
     "/  -h     ZipHeaderOption
     "/  -t      ZipTotalOption
-    stream nextPutAll:('%1 -Z -m -h "%2"' 
-                        bindWith:self class unzipCommand
-                        with:self fileName asString string).
+    stream nextPutAll:('%1 -Z -m -h "%2"'
+			bindWith:self class unzipCommand
+			with:self fileName asString string).
 
     aColOfFiles notNil ifTrue:[       self halt.
-        self 
-            addDoubleQuotedFilenames:(aColOfFiles collect:[:each | each asFilename baseName])
-            toStream:stream.
+	self
+	    addDoubleQuotedFilenames:(aColOfFiles collect:[:each | each asFilename baseName])
+	    toStream:stream.
     ].
     ^ stream contents.
 !
 
-getCommandToRemoveFiles:aColOfFiles 
+getCommandToRemoveFiles:aColOfFiles
     |stream|
 
     stream := WriteStream on:''.
 
-    stream nextPutAll:('%1 -d "%2"' 
-                        bindWith:self class zipCommand
-                        with:self fileName asString string).
+    stream nextPutAll:('%1 -d "%2"'
+			bindWith:self class zipCommand
+			with:self fileName asString string).
 
     self addDoubleQuotedFilenames:aColOfFiles toStream:stream.
     ^ stream contents.
@@ -1303,5 +1294,5 @@
 !Archiver class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/Archiver.st,v 1.25 2005-05-06 17:10:22 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/Archiver.st,v 1.26 2006-02-01 11:05:09 stefan Exp $'
 ! !