Archiver.st
changeset 1591 f655110a107f
parent 1590 61d8f450a232
child 1783 c7c8d7faccc0
--- a/Archiver.st	Wed Feb 01 12:05:09 2006 +0100
+++ b/Archiver.st	Wed Feb 01 13:27:39 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
@@ -15,7 +15,7 @@
 Object subclass:#Archiver
 	instanceVariableNames:'process temporaryDirectory fileName outStream errorStream
 		synchron'
-	classVariableNames:''
+	classVariableNames:'MimeTypeMapping'
 	poolDictionaries:''
 	category:'System-Support-FileFormats'
 !
@@ -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
@@ -113,91 +113,72 @@
 "
 ! !
 
-!Archiver class methodsFor:'instance creation'!
-
-classForMimeType:aMimeType
-    ^ self classForMimeType:aMimeType fileName:nil
+!Archiver class methodsFor:'initialization'!
 
-    "
-     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
-    "
-!
+initialize
+    MimeTypeMapping := Dictionary withKeysAndValues:
+    #(
+        'application/x-tar-compressed'         CompressedTarArchive     "abstract - special handling"
+        '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-rpm'                    RPMArchive          
+"/       'application/x-rpm-archive'            RPMArchive          
+"/       'application/x-redhat packet manager'  RPMArchive          
+    ).
+! !
+
+!Archiver class methodsFor:'instance creation'!
 
 classForMimeType:aMimeType fileName:aFileNameOrNil
     |className|
 
-    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-ar-archive'             ArArchive           )
-		('application/x-ar-library'             ArArchive           )
-		('application/library'                  ArArchive           )
+    className := MimeTypeMapping at:aMimeType ifAbsent:[^ nil].
 
-"/                ('application/x-rpm'                    RPMArchive          )
-"/                ('application/x-rpm-archive'            RPMArchive          )
-"/                ('application/x-redhat packet manager'  RPMArchive          )
-	    ) 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
-	    ]
-	].
+    className = #CompressedTarArchive ifTrue:[
+        (aFileNameOrNil notNil and:[aFileNameOrNil suffix = 'bz2']) ifTrue:[
+            className := #TarBZ2Archive
+        ] ifFalse:[
+            "this is the default"
+            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:nil fileName:nil   
+     self classForMimeType:'application/x-tar-compressed' fileName:nil   
+     self classForMimeType:'application/x-tar' fileName:nil   
+     self classForMimeType:'application/x-foo' fileName:nil   
+     self classForMimeType:'application/x-squeak-archive' fileName:nil  
+     self classForMimeType:'application/java-archive' fileName:nil 
+     'foo.sar' asFilename mimeTypeFromName               
+     'foo.jar' asFilename mimeTypeFromName               
+     'foo.a' asFilename mimeTypeFromName               
     "
 !
 
 newFor:aFilename
-    |fn mimeType archiverClass|
+    |fn archiverClass|
 
     fn := aFilename asFilename.
-    mimeType := fn mimeTypeFromName.
-    archiverClass := self classForMimeType:mimeType fileName:fn.
+    archiverClass := self classForMimeType:fn mimeTypeFromName fileName:fn.
     archiverClass isNil ifTrue:[^ nil].
-    ^ archiverClass with:aFilename
+    ^ archiverClass with:fn
 !
 
 with:aFilename
-
-    | instance |
-
-    instance := self new.
-    instance fileName:aFilename.
-    ^ instance
+    ^ self new fileName:aFilename.
 ! !
 
 !Archiver class methodsFor:'classAccess'!
@@ -238,14 +219,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 +337,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 +355,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 +380,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 +401,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 +461,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 +492,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 +529,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 +545,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 +592,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 +606,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 +670,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,20 +691,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.
+    self executeCommand:cmd directory:aDirectory. 
 ! !
 
 !Archiver::CompressedFile methodsFor:'columns'!
@@ -739,20 +720,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'!
@@ -768,9 +749,9 @@
 !Archiver::BZ2Compressed methodsFor:'columns'!
 
 columns
-    ^ #(
-	 #(#fileName        1)
-    )
+    ^ #(      
+         #(#fileName        1)
+    ) 
 !
 
 isValidOutputLine:line
@@ -816,7 +797,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.
@@ -903,14 +884,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
@@ -933,16 +914,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
@@ -952,38 +933,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.
@@ -1017,12 +998,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
@@ -1041,15 +1022,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:''.
@@ -1057,22 +1038,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:''.
@@ -1080,15 +1061,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.
@@ -1097,9 +1078,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
@@ -1205,15 +1186,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
@@ -1229,14 +1210,14 @@
     archiveFile exists ifFalse:[^ nil].
 
     stream := WriteStream on:''.
+    
+    stream nextPutAll:('%1 -r "%2"' 
+                    bindWith:self class zipCommand
+                    with:archiveFile asString string).
 
-    stream nextPutAll:('%1 -r "%2"'
-		    bindWith:self class zipCommand
-		    with:archiveFile asString string).
-
-    self
-	addDoubleQuotedFilenames:(aColOfFiles collect:[:each | each asFilename baseName])
-	toStream:stream.
+    self 
+        addDoubleQuotedFilenames:(aColOfFiles collect:[:each | each asFilename baseName])
+        toStream:stream.
 
     ^ stream contents
 !
@@ -1249,16 +1230,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:''.
@@ -1266,26 +1247,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.
@@ -1294,5 +1275,7 @@
 !Archiver class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/Archiver.st,v 1.26 2006-02-01 11:05:09 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/Archiver.st,v 1.27 2006-02-01 12:27:39 stefan Exp $'
 ! !
+
+Archiver initialize!