The Trunk: Compression-fbs.37.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
4 messages Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Compression-fbs.37.mcz

commits-2
Frank Shearar uploaded a new version of Compression to project The Trunk:
http://source.squeak.org/trunk/Compression-fbs.37.mcz

==================== Summary ====================

Name: Compression-fbs.37
Author: fbs
Time: 17 July 2013, 8:50:07.538 am
UUID: 77da886a-a70a-d242-8442-826c9cd67dad
Ancestors: Compression-fbs.36

Recategorise extension methods into either -Archives or -Streams subcategories.

=============== Diff against Compression-fbs.36 ===============

Item was changed:
+ ----- Method: CompiledMethodTrailer>>decodeEmbeddedSourceZip (in category '*Compression-Streams') -----
- ----- Method: CompiledMethodTrailer>>decodeEmbeddedSourceZip (in category '*Compression-KernelExtensions') -----
  decodeEmbeddedSourceZip
 
  "data is string with method's source code, compressed using zip compression"
  self decodeZip.!

Item was changed:
+ ----- Method: CompiledMethodTrailer>>decodeTempsNamesZip (in category '*Compression-Streams') -----
- ----- Method: CompiledMethodTrailer>>decodeTempsNamesZip (in category '*Compression-KernelExtensions') -----
  decodeTempsNamesZip
 
  "data is string with method's temporary names, compressed using zip compression"
  self decodeZip.!

Item was changed:
+ ----- Method: CompiledMethodTrailer>>decodeZip (in category '*Compression-Streams') -----
- ----- Method: CompiledMethodTrailer>>decodeZip (in category '*Compression-KernelExtensions') -----
  decodeZip
 
  "data := <trailer> unzip utf8ToSqueak"
  | len bytes |
  len := self decodeLengthField.
  bytes := ByteArray new: len.
  1 to: len do: [ :i |
  bytes at: i put: (method at: method size - size + i) ].
 
  data := (ZipReadStream on: bytes) contents asString convertFromEncoding: 'utf8'!

Item was changed:
+ ----- Method: CompiledMethodTrailer>>encodeEmbeddedSourceZip (in category '*Compression-Streams') -----
- ----- Method: CompiledMethodTrailer>>encodeEmbeddedSourceZip (in category '*Compression-KernelExtensions') -----
  encodeEmbeddedSourceZip
 
  "data is string with method's source code, encode it using Zip compression method"
  self encodeUsingZip
  !

Item was changed:
+ ----- Method: CompiledMethodTrailer>>encodeTempsNamesZip (in category '*Compression-Streams') -----
- ----- Method: CompiledMethodTrailer>>encodeTempsNamesZip (in category '*Compression-KernelExtensions') -----
  encodeTempsNamesZip
 
  "data is string with method's temporary names, encode it using zip compression"
  self encodeUsingZip
 
  "data is string with method's source code, encoded using qCompress method"
 
 
  !

Item was changed:
+ ----- Method: CompiledMethodTrailer>>encodeUsingZip (in category '*Compression-Streams') -----
- ----- Method: CompiledMethodTrailer>>encodeUsingZip (in category '*Compression-KernelExtensions') -----
  encodeUsingZip
 
  "data is string, encode it using gzip compression"
  | utf8str stream length encodedLength |
 
  self assert: (data isString).
  utf8str := data convertToEncoding: 'utf8'.
 
  stream := ((ZipWriteStream on: (ByteArray new: utf8str size))
  nextPutAll: utf8str asByteArray;
  close;
  encodedStream).
 
  length := stream position.
  encodedLength := self encodeLengthField: length.
 
  stream nextPutAll: encodedLength.
  "trailing byte"
  stream nextPut: (self kindAsByte + encodedLength size - 1).
 
  encodedData := stream contents
  !

Item was changed:
+ ----- Method: FileStream>>viewGZipContents (in category '*Compression-Streams') -----
- ----- Method: FileStream>>viewGZipContents (in category '*Compression') -----
  viewGZipContents
  "View the contents of a gzipped file"
 
  | stringContents |
  self binary.
  stringContents := self contentsOfEntireFile.
  stringContents := (GZipReadStream on: stringContents) upToEnd.
  ^ stringContents asString withSqueakLineEndings.!

Item was changed:
+ ----- Method: PositionableStream>>asZLibReadStream (in category '*Compression-Archives') -----
- ----- Method: PositionableStream>>asZLibReadStream (in category '*Compression') -----
  asZLibReadStream
  ^ZLibReadStream on: collection from: position+1 to: readLimit!

Item was changed:
+ ----- Method: ReadWriteStream>>asUnZippedStream (in category '*Compression-Streams') -----
- ----- Method: ReadWriteStream>>asUnZippedStream (in category '*Compression') -----
  asUnZippedStream
  | isGZip outputStream first strm archive which |
  "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.
  which := archive members detect: [:any | any fileName asLowercase endsWith: '.ttf']
  ifNone: [nil].
  which ifNil: [archive close.
  ^ self error: 'Can''t find .ttf file in archive'].
  strm := which contentStream.
  archive close].
 
  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!

Item was changed:
+ ----- Method: ReadWriteStream>>isZipArchive (in category '*Compression-Archives') -----
- ----- Method: ReadWriteStream>>isZipArchive (in category '*Compression') -----
  isZipArchive
  "Determine if this appears to be a valid Zip archive"
  | sig |
  self binary.
  sig := self next: 4.
  self position: self position - 4. "rewind"
  ^ZipArchive validSignatures includes: sig!

Item was changed:
+ ----- Method: StandardFileStream>>compressFile (in category '*Compression-Streams') -----
- ----- Method: StandardFileStream>>compressFile (in category '*Compression') -----
  compressFile
  "Write a new file that has the data in me compressed in GZip format."
  | zipped buffer |
 
  self readOnly; binary.
  zipped := self directory newFileNamed: (self name, FileDirectory dot, 'gz').
  zipped binary; setFileTypeToObject.
  "Type and Creator not to be text, so can be enclosed in an email"
  zipped := GZipWriteStream on: zipped.
  buffer := ByteArray new: 50000.
  'Compressing ', self fullName
  displayProgressFrom: 0 to: self size
  during: [:bar |
  [self atEnd] whileFalse: [
  bar value: self position.
  zipped nextPutAll: (self nextInto: buffer)].
  zipped close.
  self close].
  ^zipped!

Item was changed:
+ ----- Method: String>>unzipped (in category '*Compression-Streams') -----
- ----- Method: String>>unzipped (in category '*Compression') -----
  unzipped
  | magic1 magic2 |
  magic1 := (self at: 1) asInteger.
  magic2 := (self at: 2) asInteger.
  (magic1 = 16r1F and:[magic2 = 16r8B]) ifFalse:[^self].
  ^(GZipReadStream on: self) upToEnd!

Item was changed:
+ ----- Method: String>>zipped (in category '*Compression-Streams') -----
- ----- Method: String>>zipped (in category '*Compression') -----
  zipped
  | stream gzstream |
 
  stream := RWBinaryOrTextStream on: String new.
 
  gzstream := GZipWriteStream on: stream.
  gzstream nextPutAll: self.
  gzstream close.
  stream reset.
 
  ^ stream contents.
  !


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compression-fbs.37.mcz

Chris Muller-3
So you want to have a bunch of 3-method micro-packages like Pharo, so
that when you open Monticello and see 257 packages and also it's a
pain in the ass to define configuration scripts because of this?

On Wed, Jul 17, 2013 at 3:53 AM,  <[hidden email]> wrote:

> Frank Shearar uploaded a new version of Compression to project The Trunk:
> http://source.squeak.org/trunk/Compression-fbs.37.mcz
>
> ==================== Summary ====================
>
> Name: Compression-fbs.37
> Author: fbs
> Time: 17 July 2013, 8:50:07.538 am
> UUID: 77da886a-a70a-d242-8442-826c9cd67dad
> Ancestors: Compression-fbs.36
>
> Recategorise extension methods into either -Archives or -Streams subcategories.
>
> =============== Diff against Compression-fbs.36 ===============
>
> Item was changed:
> + ----- Method: CompiledMethodTrailer>>decodeEmbeddedSourceZip (in category '*Compression-Streams') -----
> - ----- Method: CompiledMethodTrailer>>decodeEmbeddedSourceZip (in category '*Compression-KernelExtensions') -----
>   decodeEmbeddedSourceZip
>
>         "data is string with method's source code, compressed using zip compression"
>         self decodeZip.!
>
> Item was changed:
> + ----- Method: CompiledMethodTrailer>>decodeTempsNamesZip (in category '*Compression-Streams') -----
> - ----- Method: CompiledMethodTrailer>>decodeTempsNamesZip (in category '*Compression-KernelExtensions') -----
>   decodeTempsNamesZip
>
>         "data is string with method's temporary names, compressed using zip compression"
>         self decodeZip.!
>
> Item was changed:
> + ----- Method: CompiledMethodTrailer>>decodeZip (in category '*Compression-Streams') -----
> - ----- Method: CompiledMethodTrailer>>decodeZip (in category '*Compression-KernelExtensions') -----
>   decodeZip
>
>         "data := <trailer> unzip utf8ToSqueak"
>         | len bytes |
>         len := self decodeLengthField.
>         bytes := ByteArray new: len.
>         1 to: len do: [ :i |
>                 bytes at: i put: (method at: method size - size + i) ].
>
>         data := (ZipReadStream on: bytes) contents asString convertFromEncoding: 'utf8'!
>
> Item was changed:
> + ----- Method: CompiledMethodTrailer>>encodeEmbeddedSourceZip (in category '*Compression-Streams') -----
> - ----- Method: CompiledMethodTrailer>>encodeEmbeddedSourceZip (in category '*Compression-KernelExtensions') -----
>   encodeEmbeddedSourceZip
>
>         "data is string with method's source code, encode it using Zip compression method"
>         self encodeUsingZip
>   !
>
> Item was changed:
> + ----- Method: CompiledMethodTrailer>>encodeTempsNamesZip (in category '*Compression-Streams') -----
> - ----- Method: CompiledMethodTrailer>>encodeTempsNamesZip (in category '*Compression-KernelExtensions') -----
>   encodeTempsNamesZip
>
>         "data is string with method's temporary names, encode it using zip compression"
>         self encodeUsingZip
>
>         "data is string with method's source code, encoded using qCompress method"
>
>
>   !
>
> Item was changed:
> + ----- Method: CompiledMethodTrailer>>encodeUsingZip (in category '*Compression-Streams') -----
> - ----- Method: CompiledMethodTrailer>>encodeUsingZip (in category '*Compression-KernelExtensions') -----
>   encodeUsingZip
>
>         "data is string, encode it using gzip compression"
>         | utf8str stream length encodedLength |
>
>         self assert: (data isString).
>         utf8str := data convertToEncoding: 'utf8'.
>
>         stream := ((ZipWriteStream on: (ByteArray new: utf8str size))
>                 nextPutAll: utf8str asByteArray;
>                 close;
>                 encodedStream).
>
>         length := stream position.
>         encodedLength := self encodeLengthField: length.
>
>         stream nextPutAll: encodedLength.
>         "trailing byte"
>         stream nextPut: (self kindAsByte + encodedLength size - 1).
>
>         encodedData := stream contents
>         !
>
> Item was changed:
> + ----- Method: FileStream>>viewGZipContents (in category '*Compression-Streams') -----
> - ----- Method: FileStream>>viewGZipContents (in category '*Compression') -----
>   viewGZipContents
>         "View the contents of a gzipped file"
>
>         | stringContents |
>         self binary.
>         stringContents := self contentsOfEntireFile.
>         stringContents := (GZipReadStream on: stringContents) upToEnd.
>         ^ stringContents asString withSqueakLineEndings.!
>
> Item was changed:
> + ----- Method: PositionableStream>>asZLibReadStream (in category '*Compression-Archives') -----
> - ----- Method: PositionableStream>>asZLibReadStream (in category '*Compression') -----
>   asZLibReadStream
>         ^ZLibReadStream on: collection from: position+1 to: readLimit!
>
> Item was changed:
> + ----- Method: ReadWriteStream>>asUnZippedStream (in category '*Compression-Streams') -----
> - ----- Method: ReadWriteStream>>asUnZippedStream (in category '*Compression') -----
>   asUnZippedStream
>         | isGZip outputStream first strm archive which |
>         "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.
>                 which := archive members detect: [:any | any fileName asLowercase endsWith: '.ttf']
>                                                                 ifNone: [nil].
>                 which ifNil: [archive close.
>                                         ^ self error: 'Can''t find .ttf file in archive'].
>                 strm := which contentStream.
>                 archive close].
>
>         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!
>
> Item was changed:
> + ----- Method: ReadWriteStream>>isZipArchive (in category '*Compression-Archives') -----
> - ----- Method: ReadWriteStream>>isZipArchive (in category '*Compression') -----
>   isZipArchive
>         "Determine if this appears to be a valid Zip archive"
>         | sig |
>         self binary.
>         sig := self next: 4.
>         self position: self position - 4. "rewind"
>         ^ZipArchive validSignatures includes: sig!
>
> Item was changed:
> + ----- Method: StandardFileStream>>compressFile (in category '*Compression-Streams') -----
> - ----- Method: StandardFileStream>>compressFile (in category '*Compression') -----
>   compressFile
>         "Write a new file that has the data in me compressed in GZip format."
>         | zipped buffer |
>
>         self readOnly; binary.
>         zipped := self directory newFileNamed: (self name, FileDirectory dot, 'gz').
>         zipped binary; setFileTypeToObject.
>                 "Type and Creator not to be text, so can be enclosed in an email"
>         zipped := GZipWriteStream on: zipped.
>         buffer := ByteArray new: 50000.
>         'Compressing ', self fullName
>                 displayProgressFrom: 0 to: self size
>                 during: [:bar |
>                         [self atEnd] whileFalse: [
>                                 bar value: self position.
>                                 zipped nextPutAll: (self nextInto: buffer)].
>                         zipped close.
>                         self close].
>         ^zipped!
>
> Item was changed:
> + ----- Method: String>>unzipped (in category '*Compression-Streams') -----
> - ----- Method: String>>unzipped (in category '*Compression') -----
>   unzipped
>         | magic1 magic2 |
>         magic1 := (self at: 1) asInteger.
>         magic2 := (self at: 2) asInteger.
>         (magic1 = 16r1F and:[magic2 = 16r8B]) ifFalse:[^self].
>         ^(GZipReadStream on: self) upToEnd!
>
> Item was changed:
> + ----- Method: String>>zipped (in category '*Compression-Streams') -----
> - ----- Method: String>>zipped (in category '*Compression') -----
>   zipped
>         | stream gzstream |
>
>         stream := RWBinaryOrTextStream on: String new.
>
>         gzstream := GZipWriteStream on: stream.
>         gzstream nextPutAll: self.
>         gzstream close.
>         stream reset.
>
>         ^ stream contents.
>   !
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compression-fbs.37.mcz

Frank Shearar-3
On 17 July 2013 16:01, Chris Muller <[hidden email]> wrote:
> So you want to have a bunch of 3-method micro-packages like Pharo, so
> that when you open Monticello and see 257 packages and also it's a
> pain in the ass to define configuration scripts because of this?

I didn't know that a simple recategorisation would get such a hot response!

Even if I did rip Compression apart - which it seems now that I don't
need to do - you would neither know nor care about it in your
configuration scripts unless you were doing something highly
specialised like making a near-minimal image.

And if you _were_ making such a special image, I suspect you'd _want_
such precise control.

But when you've read my other mail you'll see it's a fool's errand to
try split Compression into Compression-Archives and
Compression-Streams because you'd just have a cyclic dependency
between the two. I'm trying to remove _all_ cyclic dependencies.

frank

> On Wed, Jul 17, 2013 at 3:53 AM,  <[hidden email]> wrote:
>> Frank Shearar uploaded a new version of Compression to project The Trunk:
>> http://source.squeak.org/trunk/Compression-fbs.37.mcz
>>
>> ==================== Summary ====================

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compression-fbs.37.mcz

Chris Muller-4
>> So you want to have a bunch of 3-method micro-packages like Pharo, so
>> that when you open Monticello and see 257 packages and also it's a
>> pain in the ass to define configuration scripts because of this?
>
> I didn't know that a simple recategorisation would get such a hot response!

I didn't mean to sound hot as much as just, "hold on a sec here, let's
talk about this."

> Even if I did rip Compression apart - which it seems now that I don't
> need to do - you would neither know nor care about it in your
> configuration scripts unless you were doing something highly
> specialised like making a near-minimal image.

Mmm, well, even if I wasn't making a highly specialised like making a
near-minimal image, I'd still have to know which one to load _first_
-- either Compression-Archives or Compression-Streams.

> And if you _were_ making such a special image, I suspect you'd _want_
> such precise control.

Either that or the ability to _unload_ what I don't want.

There is _no way_ to make a truly minimal-for-a-vertical-purpose image
by only adding packages to a micro-kernel.  This is why I think the
"hundreds of tiny hyphenated packages approach" taken by Pharo is
wrong.  You will always end up with extranneous methods you don't need
unless you unload them.

*Except* in the case of imprinting via Spoon, of course.   :)

> But when you've read my other mail you'll see it's a fool's errand to
> try split Compression into Compression-Archives and
> Compression-Streams because you'd just have a cyclic dependency
> between the two. I'm trying to remove _all_ cyclic dependencies.

Good, we do need to eliminate the cycles between packages.  I hope it
can be done without needing to introduce new framework and/or package
layers.

Thanks..

>
> frank
>
>> On Wed, Jul 17, 2013 at 3:53 AM,  <[hidden email]> wrote:
>>> Frank Shearar uploaded a new version of Compression to project The Trunk:
>>> http://source.squeak.org/trunk/Compression-fbs.37.mcz
>>>
>>> ==================== Summary ====================