[squeak-dev] Compressed sources

Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Thu Jan 14 08:07:06 UTC 2010




On 1/13/10 8:35 PM, "Bert Freudenberg" <bert at freudenbergs.de> wrote:

> I seem to remember a hack that allowed the sources file to be compressed on
> disk. It would be uncompressed on-the-fly. Does someone remember that hack? I
> couldn't find it.
> 
> Background: The new OLPC XO does not use a compressing filesystem anymore. So
> the Etoys sources file size hurts more than before.
> 
> - Bert -
Yes, was a Dan proposal many moons ago and I test and have some old images
with it.
I could look in old backups if nobody have it at hand.

And I several times proposal the attached and have a "class repository"

Edgar

-------------- next part --------------
'From SqueakLight|II of 31 May 2008 [latest update: #7228] on 28 December 2009 at 11:26:08 am'!


!ReleaseBuilderFor3dot11 methodsFor: 'sources managment' stamp: 'edc 12/28/2009 10:00'!
createCompressedSources
	"ReleaseBuilderFor3dot11 new createCompressedSources"
	| unzipped nameToUse zipped buffer dir |
	ProtoObject
		allSubclassesWithLevelDo: [:cl :l | 
			dir := self createDirIfnotExists: cl category.
			Cursor write
				showWhile: [nameToUse := cl printString, FileDirectory dot , ImageSegment compressedFileExtension.
					(dir fileExists: nameToUse)
						ifFalse: [unzipped := RWBinaryOrTextStream on: ''.
							unzipped header; timeStamp.
							cl
								fileOutOn: unzipped
								moveSource: false
								toFile: 0.
							unzipped trailer.
							unzipped reset.
							zipped := dir newFileNamed: nameToUse .
							zipped binary.
							zipped := GZipWriteStream on: zipped.
							buffer := ByteArray new: 50000.
							'Compressing ' , nameToUse
								displayProgressAt: Sensor cursorPoint
								from: 0
								to: unzipped size
								during: [:bar | 
									[unzipped atEnd]
										whileFalse: [bar value: unzipped position.
											zipped
												nextPutAll: (unzipped nextInto: buffer)].
									zipped close.
									unzipped close]]]]
		startingLevel: 0! !

!ReleaseBuilderFor3dot11 methodsFor: 'sources managment' stamp: 'edc 2/12/2008 07:43'!
createDirIfnotExists: aDirName
(FileDirectory default directoryExists:aDirName)
		ifFalse: [FileDirectory default createDirectory: aDirName].
	^FileDirectory default directoryNamed: aDirName! !

!ReleaseBuilderFor3dot11 methodsFor: 'sources managment' stamp: 'edc 12/28/2009 11:21'!
decompress: aStandardFileStream class: aClass 
	| ff stringContents rw fcb pseudo |
	ff := FileStream oldFileOrNoneNamed: aStandardFileStream.
	ff binary.
	stringContents := ff contentsOfEntireFile.
	Cursor wait
		showWhile: [stringContents := (GZipReadStream on: stringContents) upToEnd].
	stringContents := stringContents asString withSqueakLineEndings.
	rw := RWBinaryOrTextStream with: stringContents.
	rw reset.
	fcb := FilePackage new fullName: aClass;
				 fileInFrom: rw.
	pseudo := fcb getClass: aClass.
	pseudo removeAllUnmodified.

	^ pseudo! !

!ReleaseBuilderFor3dot11 methodsFor: 'sources managment' stamp: 'edc 12/28/2009 11:26'!
readCompressedSources
	"ReleaseBuilderFor3dot11 new readCompressedSources"
	| nameToUse dir pseudo |
	dir := FileDirectory default.
	ProtoObject
		allSubclassesWithLevelDo: [:cl :l | 
			(ChangeSet current containsClass: cl) ifFalse:[
			
			Cursor write
				showWhile: [nameToUse := cl printString , FileDirectory dot , ImageSegment compressedFileExtension.
					(dir fileExists: nameToUse)
						ifTrue: [pseudo := self decompress: dir pathName , FileDirectory slash , nameToUse class: cl name.
							pseudo fileIn.
							pseudo fileOut.
							Transcript show: cl name;
								 cr]]]]
		startingLevel: 0! !


More information about the Squeak-dev mailing list