[squeak-dev] Re: Package unload status

Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Wed Jan 6 07:03:09 UTC 2010




On 1/5/10 8:36 PM, "Igor Stasenko" <siguctua at gmail.com> wrote:

> And what to do with all changes to Kernel being added recently to trunk?
> Or you want to deal with them later, in same fashion as Juan
> backported closure compiler?

Well, seems you don't know I working in reduced images for long time and for
two years lack understanding how 3.11 should be.

My last work this days is on MinimalMorphic which is only  7.3 Mb , could
load all 3.6 to 3.10 (no closures)

I develop several hacks for dealing with trunk, so only need polish as
Andreas polish my old ideas of unload in the ReleaseBuilderFor3dot11 class.

I attach some 3.11 still do not have and SqueakLight and Minimal use for a
while.

Having  "repository" of classes and reduced image could load from here with
some code.

The complete for 3.7 to 3.10 was around for a while and could be loaded with
some like:

lookForClassIn3dot9: aClass
    | inputStream cat path |
    Missing3dot9
        ifNil: [inputStream := HTTPLoader default retrieveContentsFor:
'ftp.squeak.org/various_images/SqueakLight//SLupdates/Organizer3dot9.obj'.
            inputStream := (MultiByteBinaryOrTextStream with: inputStream
contents) reset.
            inputStream setConverterForCode.
            Smalltalk at: #Missing3dot9 put: inputStream
fileInObjectAndCode].
    cat := Missing3dot9
                at: aClass
                ifAbsent: [^ self error: aClass , ' is not on  server '].
    ^ path := 'http://squeakros.atspace.com/3dot9/' , cat , '/' , aClass
asString , '.sqz'

And MinimalMorphic is not a toy.
We use in SqueakRos sites
http://sn.im/srpier
http://sn.im/miaida

Keep in mind computer is not 7/24, so could be on or not

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