Skip to content

Commit

Permalink
Remove dependencies from Compression to old Streams
Browse files Browse the repository at this point in the history
 - use regular streams on strings and bytearrays
 - clean users
 - remove unused and obscure "test" methods that log into files
  • Loading branch information
guillep committed Jan 8, 2019
1 parent ff30ad8 commit 7a25ac7
Show file tree
Hide file tree
Showing 6 changed files with 14 additions and 152 deletions.
27 changes: 0 additions & 27 deletions src/Compression/ReadWriteStream.extension.st
@@ -1,32 +1,5 @@
Extension { #name : #ReadWriteStream }

{ #category : #'*Compression' }
ReadWriteStream >> asUnZippedStream [
| isGZip outputStream first strm archive |
"Decompress this file if needed, and return a stream. No file is written. File extension may be .gz or anything else. Also works on archives (.zip, .gZip)."
strm := self binary.
strm isZipArchive
ifTrue: [
archive := ZipArchive new readFrom: strm.
archive members
detect: [ :any | any fileName asLowercase endsWith: '.ttf' ]
ifFound: [ :which |
strm := which contentStream.
archive close ]
ifNone: [
archive close.
^ self error: 'Can''t find .ttf file in archive' ] ].
first := strm next.
isGZip := strm next * 256 + first = GZipConstants gzipMagic.
strm skip: -2.
isGZip
ifTrue: [
outputStream := (MultiByteBinaryOrTextStream with: (GZipReadStream on: strm) upToEnd) reset.
strm close ]
ifFalse: [ outputStream := strm ].
^ outputStream
]

{ #category : #'*Compression' }
ReadWriteStream >> isZipArchive [
"Determine if this appears to be a valid Zip archive"
Expand Down
16 changes: 6 additions & 10 deletions src/Compression/String.extension.st
Expand Up @@ -35,15 +35,11 @@ String >> unzipped [

{ #category : #'*Compression' }
String >> zipped [
| stream gzstream |

stream := RWBinaryOrTextStream on: String new.

gzstream := GZipWriteStream on: stream.
gzstream nextPutAll: self.
gzstream close.
stream reset.

^ stream contents
| gzstream |

^ String streamContents: [ :stream |
gzstream := GZipWriteStream on: stream.
gzstream nextPutAll: self.
gzstream close.
]
]
14 changes: 4 additions & 10 deletions src/Compression/ZipArchiveMember.class.st
Expand Up @@ -205,20 +205,15 @@ ZipArchiveMember >> contentStreamFromEncoding: encodingName [
"Answer my contents as a text stream.
Interpret the raw bytes with given encodingName"

| s |
s := MultiByteBinaryOrTextStream on: (String new: self uncompressedSize).
s converter: (TextConverter newForEncoding: encodingName).
self extractTo: s.
s reset.
^ s

^ (ByteArray new: self uncompressedSize streamContents: [ :stream |
self extractTo: stream ]) decodeWith: encodingName
]

{ #category : #reading }
ZipArchiveMember >> contents [
"Answer my contents as a string."
| s |
s := RWBinaryOrTextStream on: (String new: self uncompressedSize).
s := (String new: self uncompressedSize) writeStream.
self extractTo: s.
s text.
^s contents
Expand All @@ -228,9 +223,8 @@ ZipArchiveMember >> contents [
ZipArchiveMember >> contentsFrom: start to: finish [
"Answer my contents as a string."
| s |
s := RWBinaryOrTextStream on: (String new: finish - start + 1).
s := (String new: finish - start + 1) writeStream.
self extractTo: s from: start to: finish.
s text.
^s contents
]

Expand Down
101 changes: 0 additions & 101 deletions src/Compression/ZipWriteStream.class.st
Expand Up @@ -35,28 +35,6 @@ ZipWriteStream class >> baseLength [
^BaseLength
]

{ #category : #'regression test' }
ZipWriteStream class >> compressAndDecompress: aFile using: tempFile stats: stats [

| fileSize tempStream result |
aFile ifNil: [^nil].
fileSize := aFile size.
(fileSize < 1"00000" "or:[fileSize > 1000000]") ifTrue:[aFile close. ^nil].
Transcript cr; show:'Testing ', aFile name,' ... '.
tempStream := File openForWriteFileNamed: tempFile fullName.
'Compressing ', aFile name,'...' displayProgressFrom: 1 to: aFile size during: [ :bar |
result := self regressionCompress: aFile into: tempStream notifiying: bar stats: stats].
result ifTrue: [
'Validating ', aFile name,'...' displayProgressFrom: 0 to: aFile size during: [ :bar |
result := self regressionDecompress: aFile from: tempStream notifying: bar stats: stats]].
aFile close.
tempStream close.
tempFile delete.
result ~~ false ifTrue: [
Transcript show:' ok (', (result * 100 truncateTo: 0.01) printString,')'].
^result
]

{ #category : #accessing }
ZipWriteStream class >> distanceCodes [
^DistanceCodes
Expand All @@ -78,19 +56,6 @@ ZipWriteStream class >> initialize [
VerboseLevel := 0
]

{ #category : #'regression test' }
ZipWriteStream class >> logProblem: reason for: aFile [
| errFile |
errFile := FileStream fileNamed:'problems.log'.
errFile position: errFile size.
errFile cr; nextPutAll: aFile name;
cr; nextPutAll: reason.
errFile close.
self trace:' failed (', reason,')'.
aFile close.
^false
]

{ #category : #accessing }
ZipWriteStream class >> matchLengthCodes [
^MatchLengthCodes
Expand Down Expand Up @@ -142,72 +107,6 @@ ZipWriteStream class >> regressionCompress: aFile into: tempFile notifiying: pro
^true
]

{ #category : #'regression test' }
ZipWriteStream class >> regressionDecompress: aFile from: tempFile notifying: progressBar stats: stats [
"Validate aFile as decompressed from tempFile"

| unzip rawSize compressedSize buffer1 buffer2 |
rawSize := aFile size.
compressedSize := tempFile size.
aFile ascii.
aFile position: 0.
tempFile ascii.
tempFile position: 0.
buffer1 := ByteArray new: 4096.
buffer2 := buffer1 copy.
unzip := FastInflateStream on: tempFile.
[ aFile atEnd ]
whileFalse: [
progressBar current: aFile position.
buffer1 := aFile nextInto: buffer1.
buffer2 := unzip nextInto: buffer2.
buffer1 = buffer2
ifFalse: [ ^ self logProblem: 'contents ' for: aFile ] ].
unzip next ifNotNil: [ ^ self logProblem: 'EOF' for: aFile ].
stats at: #rawSize put: (stats at: #rawSize ifAbsent: [ 0 ]) + rawSize.
stats at: #compressedSize put: (stats at: #compressedSize ifAbsent: [ 0 ]) + compressedSize.
^ compressedSize asFloat / rawSize asFloat
]

{ #category : #'regression test' }
ZipWriteStream class >> regressionTest [ "ZipWriteStream regressionTest"
"Compress and decompress everything we can
find to validate that compression works as expected."
self regressionTestFrom: FileSystem workingDirectory.
]

{ #category : #'regression test' }
ZipWriteStream class >> regressionTestFrom: fd [
"ZipWriteStream regressionTestFrom: FileSystem disk workingDirectory"
"ZipWriteStream regressionTestFrom: (FileSystem disk root)"
| tempFile stats |
Transcript clear.
stats := Dictionary new.
tempFile := FileSystem disk workingDirectory / '$$sqcompress$$'.
tempFile delete.
self regressionTestFrom: fd using: tempFile stats: stats.
]

{ #category : #'regression test' }
ZipWriteStream class >> regressionTestFrom: fd using: tempFile stats: stats [
| files |
files := fd files asSortedCollection.
files do: [ :file |
file = tempFile ifFalse: [
self
compressAndDecompress: (File openForReadFileNamed: file fullName)
using: tempFile
stats: stats]].

stats at: #numFiles put: (stats at: #numFiles ifAbsent:[0]) + files size.
files := nil.

self printRegressionStats: stats from: fd.
fd directories asSortedCollection do:[:directory|
self regressionTestFrom: directory using: tempFile stats: stats.
].
]

{ #category : #crc }
ZipWriteStream class >> updateCrc: oldCrc from: start to: stop in: aCollection [
^ CRC update: oldCrc from: start to: stop in: aCollection
Expand Down
4 changes: 2 additions & 2 deletions src/Monticello/MCMczReader.class.st
Expand Up @@ -62,12 +62,12 @@ MCMczReader >> contentStreamForMember: member [

{ #category : #parsing }
MCMczReader >> contentsForMember: member [
^[(member contentStreamFromEncoding: 'utf8') text contents] on: ZnInvalidUTF8, UTF8InvalidText
^[(member contentStreamFromEncoding: 'utf8') contents] on: ZnInvalidUTF8, UTF8InvalidText
do: [:exc |
"Case of legacy encoding, presumably it is latin-1.
But if contents starts with a null character, it might be a case of WideString encoded in UTF-32BE"
| str |
str := (member contentStreamFromEncoding: 'latin1') text.
str := (member contentStreamFromEncoding: 'latin1').
exc return: ((str peek = Character null and: [ str size \\ 4 = 0 ])
ifTrue: [WideString fromByteArray: str contents asByteArray]
ifFalse: [str contents])]
Expand Down
4 changes: 2 additions & 2 deletions src/System-Installers/MczInstaller.class.st
Expand Up @@ -129,12 +129,12 @@ MczInstaller >> contentStreamForMember: member [

{ #category : #parsing }
MczInstaller >> contentsForMember: member [
^[(member contentStreamFromEncoding: 'utf8') text contents] on: ZnInvalidUTF8
^[(member contentStreamFromEncoding: 'utf8') contents] on: ZnInvalidUTF8
do: [:exc |
"Case of legacy encoding, presumably it is latin-1.
But if contents starts with a null character, it might be a case of WideString encoded in UTF-32BE"
| str |
str := (member contentStreamFromEncoding: 'latin1') text.
str := (member contentStreamFromEncoding: 'latin1').
exc return: ((str peek = Character null and: [ str size \\ 4 = 0 ])
ifTrue: [WideString fromByteArray: str contents asByteArray]
ifFalse: [str contents])]
Expand Down

0 comments on commit 7a25ac7

Please sign in to comment.