Archiver.st
author Claus Gittinger <cg@exept.de>
Wed, 29 Sep 2004 13:30:56 +0200
changeset 1479 7da16828bfab
parent 1392 e5290b66715f
child 1554 a92694a00c33
permissions -rw-r--r--
*** empty log message ***

"{ Package: 'stx:libbasic2' }"

Object subclass:#Archiver
	instanceVariableNames:'process temporaryDirectory fileName outStream errorStream
		synchron'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Support-FileFormats'
!

Archiver subclass:#MultiFileArchive
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Object subclass:#ArchiverOutputParser
	instanceVariableNames:'firstLineRead archiver'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Archiver subclass:#CompressedFile
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Archiver::CompressedFile subclass:#BZ2Compressed
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Archiver subclass:#CompressedTarArchive
	instanceVariableNames:'tarArchiver tarFile'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Archiver::CompressedFile subclass:#GZipCompressed
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Archiver::MultiFileArchive subclass:#ArArchive
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Archiver::MultiFileArchive subclass:#TarArchive
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Archiver::CompressedTarArchive subclass:#TarBZ2Archive
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Archiver::CompressedTarArchive subclass:#TarGZipArchive
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!

Archiver::MultiFileArchive subclass:#ZipArchive
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Archiver
!


!Archiver class methodsFor:'instance creation'!

classForMimeType:aMimeType
    ^ 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               
    "
!

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           )

"/                ('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
            ]
        ].
    ].
    ^ 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               
    "
!

newFor:aFilename
    |fn mimeType archiverClass|

    fn := aFilename asFilename.
    mimeType := fn mimeTypeFromName.
    archiverClass := self classForMimeType:mimeType fileName:fn.
    archiverClass isNil ifTrue:[^ nil].
    ^ archiverClass with:aFilename
!

with:aFilename

    | instance |

    instance := self new.
    instance fileName:aFilename.
    ^ instance
! !

!Archiver class methodsFor:'classAccess'!

arArchive

    ^ ArArchive
!

gzipArchive
    ^ GZipCompressed
!

tarArchive

    ^ TarArchive
!

tarGZipArchive

    ^ TarGZipArchive
!

zipArchive

    ^ ZipArchive
! !

!Archiver class methodsFor:'columns'!

columns
    self subclassResponsibility
! !

!Archiver class methodsFor:'command strings'!

stringWithQuotedFileBaseNames:aColOfFiles

    aColOfFiles isNil ifTrue:[^ ''].

    ^ String 
        streamContents:[:str |
            aColOfFiles do:[:fn | 
                str nextPutAll:' "'.
                str nextPutAll:(fn asFilename baseName).
                str nextPutAll:'"'.
            ].
        ]
! !

!Archiver class methodsFor:'commandOutputReader'!

commandOutputParser
    ^ self commandOutputParserClass new
!

commandOutputParserClass
    ^ ArchiverOutputParser
! !

!Archiver class methodsFor:'queries'!

canAddFiles

    ^ false
!

canDragnDrop

    ^ true.
!

canExtractFiles

    ^ false
!

canRemoveFiles

    ^ false
!

canViewFile

    ^ false
!

hasTitleLine

    ^ false
! !

!Archiver methodsFor:'accessing'!

errorStream
    "return the value of the instance variable 'errorStream' (automatically generated)"

    ^ errorStream
!

errorStream:something
    "set the value of the instance variable 'errorStream' (automatically generated)"

    errorStream := something.
!

fileName
    "return the value of the instance variable 'fileName' (automatically generated)"

    ^ fileName
!

fileName:something
    "set the value of the instance variable 'fileName' (automatically generated)"

    fileName := something.
!

outStream
    "return the value of the instance variable 'outStream' (automatically generated)"

    ^ outStream
!

outStream:something
    "set the value of the instance variable 'outStream' (automatically generated)"

    outStream := something.
!

process
    "return the value of the instance variable 'process' (automatically generated)"

    ^ process
!

process:something
    "set the value of the instance variable 'process' (automatically generated)"

    process := something.
!

synchron
    "return the value of the instance variable 'synchron' (automatically generated)"

    ^ synchron
!

synchron:something
    "set the value of the instance variable 'synchron' (automatically generated)"

    synchron := something.
!

temporaryDirectory
    "return the value of the instance variable 'temporaryDirectory' (automatically generated)"

    temporaryDirectory isNil ifTrue:[
        temporaryDirectory := Filename newTemporary.
        temporaryDirectory makeDirectory.
    ].
    ^ temporaryDirectory
! !

!Archiver methodsFor:'actions'!

extractFilesTo:aDirectory
    self extractFiles:nil to:aDirectory
!

listFiles:aColOfFiles
    |cmd dir|

    self fileName isNil ifTrue:[ ^ self].
    dir := self fileName directory.
    cmd := self getCommandToListFiles:aColOfFiles.
    self executeCommand:cmd directory:dir 
!

removeFilesFromArchive:aColOfFiles

    self subclassResponsibility.
! !

!Archiver methodsFor:'actions-basic'!

addFilesToArchive:colOfFiles
    self subclassResponsibility.
!

extractFiles:aColOfFilesOrNil to:aDirectory
    self subclassResponsibility.
! !

!Archiver methodsFor:'actions-private'!

removeTemporaryDirectory

    | tmp |

    temporaryDirectory notNil ifTrue:[
        tmp := self temporaryDirectory.
        (FileDirectory directoryNamed:(tmp directory)) removeDirectory:tmp baseName.
        temporaryDirectory := nil.
    ].
!

stopProcess

    process notNil ifTrue:[
        process terminateWithAllSubprocesses.
        process waitUntilTerminated.
    ].
! !

!Archiver methodsFor:'command execution'!

executeCommand:cmd directory:aDirectory


    synchron isNil ifTrue:[synchron := true].
    synchron ifTrue:[
         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.
                ].

        ] priority:(Processor systemBackgroundPriority).
        process name:('Archiver command: ', cmd).
        process resume.
    ]
!

isValidOutputLine:line
    "return true, if line contains a valid list-files output line"

    self subclassResponsibility
!

listFilesReader
    |reader|

    reader := ArchiverOutputParser new.
    reader archiver:self.
    ^ reader
!

outStream:aOutStream errorStream:aErrorStream

    outStream := aOutStream.
    errorStream := aErrorStream.
!

outStream:aOutStream errorStream:aErrorStream synchron:aBoolean

    outStream := aOutStream.
    errorStream := aErrorStream.
    synchron := aBoolean
! !

!Archiver methodsFor:'command strings'!

addDoubleQuotedFilenames:collectionOfFilenames toStream:aStream
    collectionOfFilenames notNil ifTrue:[
        collectionOfFilenames do:[:el | 
            aStream nextPutAll:' "'.
            aStream nextPutAll:(el asString).
            aStream nextPutAll:'"'
        ].
    ].
! !

!Archiver methodsFor:'initialization & release'!

release

    self stopProcess.
    self removeTemporaryDirectory.
! !

!Archiver::MultiFileArchive methodsFor:'actions'!

addFilesToArchive:colOfFiles
    |cmd tempDir archivFile archivInTemp|

    archivFile := self fileName.

    tempDir := self temporaryDirectory.
    archivInTemp := tempDir construct:(archivFile baseName).

    "/ copy archiv to tempDir
    archivFile copyTo:archivInTemp.
    "/ 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))
        ].

        "/ addFiles to the tar archive
        cmd := self getCommandToAdd:colOfFiles toArchive:archivInTemp.
        self executeCommand:cmd directory:tempDir.

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

extractFiles:aColOfFilesOrNil to:aDirectory
    |execDir cmd|

    execDir := self fileName directory.
    cmd := self getCommandToExtractFiles:aColOfFilesOrNil intoDirectory:aDirectory.
    self executeCommand:cmd directory:execDir.
!

extractFiles:aColOfFiles withoutDirectoryTo:aDirectory
    |execDir tempDir tempFile targetFile|

    execDir := self fileName directory.
    tempDir := self temporaryDirectory.
    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.
        ].
    ].
!

removeFilesFromArchive:aColOfFiles

    |cmd|

    cmd := self getCommandToRemoveFiles:aColOfFiles.
    self executeCommand:cmd directory:(self fileName directory). 
! !

!Archiver::MultiFileArchive methodsFor:'command strings'!

getCommandToAdd:colOfFiles toArchive:archivIn
    self subclassResponsibility
!

getCommandToExtractFiles:sel intoDirectory:dir
    self subclassResponsibility
!

getCommandToListFiles:aColOfFiles
    self subclassResponsibility
!

getCommandToRemoveFiles:aColOfFiles
    self subclassResponsibility
! !

!Archiver::ArchiverOutputParser class methodsFor:'instance creation'!

new
    ^ self basicNew initialize.
! !

!Archiver::ArchiverOutputParser methodsFor:'accessing'!

archiver:something
    "set the value of the instance variable 'archiver' (automatically generated)"

    archiver := something.
! !

!Archiver::ArchiverOutputParser methodsFor:'initialization'!

initialize
    firstLineRead := false.
! !

!Archiver::ArchiverOutputParser methodsFor:'parsing'!

parseLine:line forItemClass:itemClass
    |words archiverColumns item index key|

    (firstLineRead not and:[archiver class hasTitleLine]) ifTrue:[
        firstLineRead := true.
        ^ nil.
    ].

    (archiver isValidOutputLine:line) ifFalse:[
        ^ nil.
    ].

    words := line asCollectionOfWords.
    archiverColumns := archiver columns.
    item := itemClass new.
    index := 1.

    archiverColumns do:[:colDescr |
        | 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.
    ].
    ((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.
        ].
    ] ifFalse:[
        key := MIMETypes mimeTypeForFilename:(item fileName asFilename baseName).
    ].
    item icon:(FileBrowser iconForKeyMatching:key).
    ^ item
! !

!Archiver::CompressedFile class methodsFor:'command strings'!

compressCommand
    self subclassResponsibility
!

uncompressCommand
    self subclassResponsibility
! !

!Archiver::CompressedFile class methodsFor:'queries'!

canViewFile

    ^ true
! !

!Archiver::CompressedFile methodsFor:'actions'!

compressFile:aFile to:newFile
    | cmd directory|

    directory := newFile directory.
    (directory exists) ifFalse:[
        DialogBox warn:'cannot compress to non-existing directory ', directory asString.
    ].
    (directory isDirectory) ifFalse:[
        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.
    ].
!

extractFiles:aColOfFilesOrNil to:aDirectory
    self uncompressTo:aDirectory
!

uncompressTo:aDirectory
    | cmd file newFile|

    (aDirectory exists) ifFalse:[
        DialogBox warn:'cannot uncompress to non-existing directory ', aDirectory asString.
        ^ self
    ].
    (aDirectory isDirectory) ifFalse:[
        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.
    ].
    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).
! !

!Archiver::CompressedFile methodsFor:'columns'!

columns
    self subclassResponsibility
!

isValidOutputLine:line
    ^ line endsWith:self fileName withoutSuffix baseName.
! !

!Archiver::CompressedFile methodsFor:'command strings'!

getCommandToCompress:aFile asNew:newFile
    ^ '%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
! !

!Archiver::BZ2Compressed class methodsFor:'command strings'!

compressCommand
    ^ 'bzip2'
!

uncompressCommand
    ^ 'bunzip2'
! !

!Archiver::BZ2Compressed methodsFor:'columns'!

columns
    ^ #(      
         #(#fileName        1)
    ) 
!

isValidOutputLine:line
    ^ true
! !

!Archiver::BZ2Compressed methodsFor:'command strings'!

getCommandToListFiles:dummyArg
    ^ 'echo ' , self fileName withoutSuffix baseName
"/    ^ 'bzip2 -t -v "' , self fileName baseName , '"'
! !

!Archiver::CompressedTarArchive class methodsFor:'queries'!

canAddFiles
    ^ Archiver tarArchive canAddFiles
!

canRemoveFiles
    ^ Archiver tarArchive canRemoveFiles
!

canViewFile
    ^ Archiver tarArchive canViewFile
!

compressorClass
    self subclassResponsibility
! !

!Archiver::CompressedTarArchive methodsFor:'accessing'!

fileName:aFile
    |tempDir file compressor suffix tarFilename|

    super fileName:aFile.
    " unzip file in tempDirectory and do all the things with tar file "
    tempDir := self temporaryDirectory.
    compressor := (self class compressorClass) with:(self fileName).
    compressor uncompressTo:tempDir.
    suffix := self fileName suffix.
    file := self fileName withoutSuffix.
    tarFilename := file baseName.
    file suffix ~= 'tar' ifTrue:[
        tarFilename := tarFilename , '.tar'
    ].
    tarFile := self temporaryDirectory construct:tarFilename.
    tarArchiver := Archiver::TarArchive with:tarFile.
! !

!Archiver::CompressedTarArchive methodsFor:'actions'!

addFilesToArchive:colOfFiles
    self setCommandOptions.
    tarArchiver addFilesToArchive:colOfFiles.
    "/ synchronize the tar archive under temporary file with archiv file position
    self synchronize.
!

extractFiles:aColOfFiles to:aDirectory
    self setCommandOptions.
    tarArchiver extractFiles:aColOfFiles to:aDirectory.
!

extractFiles:aColOfFiles withoutDirectoryTo:aDirectory
    self setCommandOptions.
    tarArchiver extractFiles:aColOfFiles withoutDirectoryTo:aDirectory.
!

listFiles:aColOfFiles
    self setCommandOptions.
    tarArchiver listFiles:aColOfFiles.
!

removeFilesFromArchive:aColOfFiles
    self setCommandOptions.
    tarArchiver removeFilesFromArchive:aColOfFiles.
    self synchronize.
! !

!Archiver::CompressedTarArchive methodsFor:'actions private'!

setCommandOptions
    tarArchiver outStream:(self outStream).
    tarArchiver errorStream:(self errorStream).
    tarArchiver synchron:(self synchron).
!

synchronize
    self subclassResponsibility
! !

!Archiver::CompressedTarArchive methodsFor:'columns'!

columns
    ^ tarArchiver columns
!

isValidOutputLine:line
    ^ tarArchiver isValidOutputLine:line
! !

!Archiver::CompressedTarArchive methodsFor:'initialization & release'!

release
    super release.
    tarArchiver release.
! !

!Archiver::GZipCompressed class methodsFor:'command strings'!

compressCommand
    ^ 'gzip'
!

uncompressCommand
    ^ 'gunzip'
! !

!Archiver::GZipCompressed class methodsFor:'queries'!

hasTitleLine
    ^ true
! !

!Archiver::GZipCompressed methodsFor:'columns'!

columns

    "/ columns in stream order
    "/  colums id/readSelector          words to read
    ^ #( "/ #(#method          1)      
         "/ #(#crc             1)    
         "/ #(#dateAndTime     3)   
         #(#compressSize    1)  
         #(#size            1) 
         #(#ratio           1) 
         #(#fileName        #rest)
    ) 
!

isValidOutputLine:line
    ^ line endsWith:self fileName withoutSuffix baseName.
! !

!Archiver::GZipCompressed methodsFor:'command strings'!

getCommandToListFiles:dummyArg
    ^ 'gzip -l "' , self fileName baseName , '"'
! !

!Archiver::ArArchive class methodsFor:'command strings'!

arCommand
    ^ 'ar'
! !

!Archiver::ArArchive methodsFor:'columns'!

columns
    "/  colums id/readSelector words to read
    ^ #( 
         #(#permissions     1)      
         #(#ownerGroup      1)    
         #(#size            1)   
         #(#monthName       1)  
         #(#dayString       1)  
         #(#timeString      1)  
         #(#yearString      1)  
         #(#fileName        #rest)
    ) 
!

isValidOutputLine:line
    ('[-r][-w][-x]' match:(line copyTo:3)) ifTrue:[^ true].
    ^ false.
! !

!Archiver::ArArchive methodsFor:'command strings'!

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

    sel notNil ifTrue:[
        sel do:[:el | 
            stream nextPutAll:' "'.
            stream nextPutAll:(el asString).
            stream nextPutAll:'"'
        ].
    ].
    stream nextPutAll:')'.
    ^ stream contents.
!

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:(self class stringWithQuotedFileBaseNames:aColOfFiles).
    ^ stream contents.
! !

!Archiver::TarArchive class methodsFor:'command strings'!

tarCommand
    ^ 'tar'
! !

!Archiver::TarArchive class methodsFor:'queries'!

canAddFiles

    ^ true
!

canRemoveFiles

    ^ true
!

canViewFile

    ^ true
! !

!Archiver::TarArchive methodsFor:'columns'!

columns

    "/  colums id/readSelector words to read
    ^ #( #(#permissions     1)      
         #(#ownerGroup      1)    
         #(#size            1)   
         #(#dateAndTime     2)  
         #(#fileName        #rest)
    ) 
!

isValidOutputLine:line
    ('[-d][-r][-w][-x]' match:(line copyTo:4)) ifTrue:[^ true].
    ^ false.
! !

!Archiver::TarArchive methodsFor:'command strings'!

getCommandToAdd:aColOfFiles toArchive:archiveFile
    |stream|

    archiveFile exists ifFalse:[^ nil].

    stream := WriteStream on:''.

    "/ 'r'  TarArchivAddOption
    "/ 'f'  TarArchivFileOption
    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 
    |stream|

    stream := WriteStream on:''.

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

    sel notNil ifTrue:[
        sel do:[:el | 
            stream nextPutAll:' "'.
            stream nextPutAll:(el asString).
            stream nextPutAll:'"'
        ].
    ].
    ^ stream contents.
!

getCommandToListFiles:aColOfFiles 
    |stream|

    stream := WriteStream on:''.

    "/ 't'  TarArchivListContentsOption
    "/ 'v'  TarArchivVerboseOption
    "/ 'f'  TarArchivFileOption
    stream nextPutAll:('%1 -tvf "%2"' 
                    bindWith:self class tarCommand
                    with:self fileName baseName).

    stream nextPutAll:(self class stringWithQuotedFileBaseNames:aColOfFiles).
    ^ stream contents.
!

getCommandToRemoveFiles:sel 
    |stream filename|

    filename := self fileName.
    filename exists ifFalse:[^ nil].

    stream := WriteStream on:''.

    "/ 'f'  TarArchivFileOption
    stream nextPutAll:('%1 --delete -f "%2"' 
                    bindWith:self class tarCommand
                    with:self fileName baseName).

    stream nextPutAll:(self class stringWithQuotedFileBaseNames:sel).
    ^ stream contents
! !

!Archiver::TarBZ2Archive class methodsFor:'queries'!

canAddFiles

    ^ Archiver tarArchive canAddFiles
!

canRemoveFiles

    ^ Archiver tarArchive canRemoveFiles
!

canViewFile

    ^ Archiver tarArchive canViewFile
!

compressorClass
    ^ Archiver::BZ2Compressed
! !

!Archiver::TarBZ2Archive methodsFor:'actions private'!

synchronize
    |gzipArchiver|

    gzipArchiver := Archiver::BZ2Compressed with:nil.
    gzipArchiver compressFile:(tarArchiver fileName) to:(self fileName).
! !

!Archiver::TarGZipArchive class methodsFor:'queries'!

canAddFiles

    ^ Archiver tarArchive canAddFiles
!

canRemoveFiles

    ^ Archiver tarArchive canRemoveFiles
!

canViewFile

    ^ Archiver tarArchive canViewFile
!

compressorClass
    ^ Archiver::GZipCompressed
! !

!Archiver::TarGZipArchive methodsFor:'actions private'!

synchronize
    |gzipArchiver|

    gzipArchiver := Archiver::GZipCompressed with:nil.
    gzipArchiver compressFile:(tarArchiver fileName) to:(self fileName).
! !

!Archiver::ZipArchive class methodsFor:'command strings'!

unzipCommand
    ^ 'unzip'
!

zipCommand
    ^ 'zip'
! !

!Archiver::ZipArchive class methodsFor:'queries'!

canAddFiles

    ^ true
!

canRemoveFiles

    ^ true
!

canViewFile

    ^ true
!

hasLastLine
    ^ true
!

hasTitleLine
    ^ true
! !

!Archiver::ZipArchive methodsFor:'columns'!

columns

    "/  colums id/readSelector    words to read
    ^ #( (#permissions     1)      
         (#version         2)    
         (#size            1)     
         (#type            1)    
         (#ratio           1)    
         (nil              1)  
         (#dateAndTime     2)  
         (#fileName        #rest)
    ) 
!

isValidOutputLine:line
    ('[-d][-r][-w][-x]' match:(line copyTo:4)) ifTrue:[^ true].
    ^ false.
! !

!Archiver::ZipArchive methodsFor:'command strings'!

getCommandToAdd:aColOfFiles toArchive:archiveFile
    |stream|

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

getCommandToExtractFiles:aColOfFiles intoDirectory:dir
    |stream|

    stream := WriteStream on:''.

    "/ -o   UnzipOverwriteExistingFilesOption
    "/ -d   UnzipExtDirectoryOption

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

    stream := WriteStream on:''.

    "/  -Z      ZipInfoOption
    "/  -h     ZipHeaderOption
    "/  -t      ZipTotalOption
    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.
    ].
    ^ stream contents.
!

getCommandToRemoveFiles:aColOfFiles 
    |stream|

    stream := WriteStream on:''.

    stream nextPutAll:('%1 -d "%2"' 
                        bindWith:self class zipCommand
                        with:self fileName asString string).

    self addDoubleQuotedFilenames:aColOfFiles toStream:stream.
    ^ stream contents.
! !

!Archiver class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Archiver.st,v 1.24 2004-09-29 11:30:56 cg Exp $'
! !