Proposal for SqueakCore 4.5 (was Re: [squeak-dev] Re: New release candidate: 4.4-12324)

Edgar J. De Cleene edgardec2005 at gmail.com
Fri Dec 28 10:21:05 UTC 2012




On 12/27/12 8:34 AM, "Frank Shearar" <frank.shearar at gmail.com> wrote:

> I also think that the ReleaseBuilder stuff doesn't belong in the Trunk
> image and should be maintained externally. (MAYBE it could be loaded
> into an image just as part of the release process, but really I'd like
> scaffolding - ConfigurationOf packages, ReleaseBuilder stuff, etc. -
> to not be in the image at all.)

For years I beg we MUST have a SqueakCore .

I made 3.10 and proud of it, the first step in modular Squeak.
Can't made 3.11...
I attach the last script for it, see unloadSomeMore.
I hope you success taking the code and improving.
Made a SqueakCore and any Squeaker could decide which packages load later.
Also is time to have new .sources and if we have a cleaner and small system
....

If you have time see the .cs.
I apply it to Squeak , Cuis and Pharo and you could see the results in
http://squeakros.org/3dot11
http://squeakros.org/Cuis3dot2
http://squeakros.org/Pharo1dot4

If we have a SqueakKernel , as Pavel made for Pharo and sure could build for
us if we send a nice mail to he, could load the classes we need

Edgar

-------------- next part --------------
'From Squeak3.10beta of 22 July 2007 [latest update: #7159] on 22 April 2008 at 7:40:50 am'!
ReleaseBuilderFor3dot10 subclass: #ReleaseBuilderFor3dot11
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ReleaseBuilder'!

!ReleaseBuilderFor3dot11 methodsFor: 'cleaning' stamp: 'edc 4/22/2008 07:40'!
cleanupPhaseFinal
" ReleaseBuilderFor3dot11 new cleanupPhaseFinal "
| tasks |
    tasks := OrderedCollection new
        
                add: [Smalltalk removeEmptyMessageCategories];
                add: [Workspace
                        allSubInstancesDo: [:each | each setBindings: Dictionary new]];
                add: [Undeclared removeUnreferencedKeys];
                add: [Categorizer sortAllCategories];
                add: [Symbol compactSymbolTable];
	add: [#(#TheWorldMenu #FileServices #AppRegistry #Preferences #FileList )
		do: [:cl | (Smalltalk at: cl) removeObsolete]]; add:[Flaps freshFlapsStart]; add:[MCFileBasedRepository flushAllCaches];
                 add: [HandMorph releaseCachedState;
	initForEvents.self fixObsoleteReferences];
                add: [Smalltalk forgetDoIts.

	DataStream initialize.
	Behavior flushObsoleteSubclasses.

	"The pointer to currentMethod is not realy needed (anybody care to fix this) and often holds on to obsolete bindings"
	MethodChangeRecord allInstancesDo: [:each | each noteNewMethod: nil].Smalltalk garbageCollectMost];
                 yourself.
Utilities
        informUserDuring: [:bar | tasks
                do: [:block |
                    bar value: block printString.
                    [block value]
                        on: Error
                        do: [:error | Transcript show: error;
                                 cr]]].
 SystemNavigation default obsoleteClasses isEmpty
        ifTrue: [SmalltalkImage current saveSession]
        ifFalse: [SystemNavigation default obsoleteClasses
                do: [:each | .self halt.[PointerFinder on: each]
                        on: Error
                        do: [:error | Transcript show: error; cr]]]


! !

!ReleaseBuilderFor3dot11 methodsFor: 'cleaning' stamp: 'edc 4/10/2008 09:24'!
cleanupPhasePrepare
self cleanUnwantedCs.
                SMSqueakMap default clearCaches.
#(zapMVCprojects zapAllOtherProjects discardFlash discardFFI
computeImageSegmentation discardSpeech ) do:[:ea| 
SystemDictionary removeSelector:ea].
#( reserveUrl: saveAsResource saveDocPane saveOnURL saveOnURL:
saveOnURLbasic isTurtleRow objectViewed inATwoWayScrollPane) do:[:ea| 
Morph removeSelector: ea].

#(playfieldOptionsMenu presentPlayfieldMenu allScriptEditors
attemptCleanupReporting: modernizeBJProject
scriptorForTextualScript:ofPlayer:) do:[:ea| 
PasteUpMorph removeSelector:   ea].
#(isUniversalTiles noteDeletionOf:fromWorld: scriptorsForSelector:inWorld: tilesToCall: handMeTilesToFire) do:[:ea| 
Player removeSelector:   ea].
Player class removeCategory: 'turtles'.
Player removeCategory: 'slots-user'.
Morph removeCategory: 'scripting'.
ColorType removeCategory: 'tiles'.
TheWorldMainDockingBar removeSelector: #hideAllViewersIn: .
SystemOrganization removeCategoriesMatching: 'UserObjects'.
FileList2 class organization classify: #morphicViewOnDirectory: under: 'morphic ui'.
FileList2 class organization classify: #morphicView under: 'morphic ui'.! !

!ReleaseBuilderFor3dot11 methodsFor: 'cleaning' stamp: 'edc 2/5/2008 07:33'!
getRidOfUnwantedMorphs
| objFl aButton  partBin unwantedMorph |
aButton _ SimpleButtonMorph new label: 'Tools'.
			aButton actWhen: #buttonDown.
objFl := Flaps globalFlapTabWithID: 'Objects'.
objFl referent showCategory: 'Tools' fromButton: aButton.
partBin := objFl referent submorphs at: 1.
unwantedMorph := partBin submorphThat: [:any| (any arguments at: 2) = 'SUnit Runner'] ifNone: [].
unwantedMorph delete.
2 timesRepeat: [unwantedMorph := partBin submorphThat: [:any| (any arguments at: 2) = 'Package Loader'] ifNone: []. "we have two of this "
unwantedMorph delete].
objFl := Flaps globalFlapTabWithID: 'Tools'.
partBin := objFl referent.
unwantedMorph := partBin submorphThat: [:any| (any arguments at: 2) = 'Package Loader'] ifNone: [].
unwantedMorph delete.
unwantedMorph := partBin submorphThat: [:any| (any arguments at: 2) = 'SUnit Runner'] ifNone: [].
unwantedMorph delete.! !

!ReleaseBuilderFor3dot11 methodsFor: 'cleaning' stamp: 'edc 4/11/2008 04:41'!
prepareforUnloadBookMorphandFriends
SystemOrganization addCategory: #BookMorphandFriends.

SystemOrganization classifyAll: #( BookMorph BookPageSorterMorph BookPageThumbnailMorph BooklikeMorph FlexMorph FloatingBookControlsMorph KedamaMorph MethodMorph  MorphThumbnail   StoryboardBookMorph ) under: 'BookMorphandFriends'.
! !

!ReleaseBuilderFor3dot11 methodsFor: 'cleaning' stamp: 'edc 4/11/2008 05:26'!
prepareforUnloadEtoys
SystemOrganization classifyAll: #(ActorState MethodMorph Player Presenter StickySketchMorph UnscriptedPlayer SlotInformation UnscriptedCardPlayer) under: 'MorphicExtras-EToys-Scripting'.
#( actorState actorState: isPartsDonor isPartsDonor: player player:) do: [:method|
MorphExtension organization classify: method under: '*MorphicExtras-accessing' suppressIfDefault: false].
HaloMorph organization classify: #doMakeSiblingOrDup:with: under: 'Old Etoys-handles'.
HaloMorph organization classify: #doDupOrMakeSibling:with: under: 'Old Etoys-handles'.
self loadTogether: #('Morphic-CandidatesForGo-edc.3.mcz' ) merge: false.
SystemOrganization classifyAll: #(ScriptEditorMorph TwoWayScrollPane TabSorterMorph) under:
'Morphic-CandidatesForGo'.

Preferences removePreference: #allowEtoyUserCustomEvents. 
Morph organization classify: #partName:categories:documentation:sampleImageForm: under: '*MorphicExtras-new-morph participation'.
Flaps clobberFlapTabList.
Flaps addStandardFlaps.
SystemOrganization classifyAll: #(ComponentLikeModel) under: 'MorphicExtras-Components'
! !

!ReleaseBuilderFor3dot11 methodsFor: 'cleaning' stamp: 'edc 2/15/2008 10:19'!
prepareforUnloadNebraska
SystemOrganization addCategory: #'Nebraska-Refactoring'.

SystemOrganization classifyAll: #(EToyGenericDialogMorph EToyProjectDetailsMorph EToyProjectHistoryMorph EToyProjectQueryMorph EToyProjectRenamerMorph EtoyUpdatingThreePhaseButtonMorph) under: 'Nebraska-Refactoring'.
WorldState organization classify: #remoteCanvasesDo: under: '*MorphicExtras-nebraska compatible'.
! !


!ReleaseBuilderFor3dot11 methodsFor: 'squeakThreeEleven' stamp: 'edc 2/5/2008 07:21'!
createBackgroundColor
| gf |
gf := GradientFillStyle  ramp: {0.0->(Color r: 0.97 g: 0.98 b: 1.0) .
1.0->(Color r: 0.0 g: 0.658 b: 0.474)}.
	gf	origin: 0 @ 0;
		direction: 0 at 400;
		normal: 640 at 0;
		radial: false.
World fillStyle: gf! !

!ReleaseBuilderFor3dot11 methodsFor: 'squeakThreeEleven' stamp: 'edc 4/10/2008 09:34'!
makeSqueakThreeTenEleven
	"ReleaseBuilderFor3dot11 new makeSqueakThreeTenEleven"
	"World removeAllMorphs."
	Transcript open.
	self cleanupPhasePrepare;getRidOfUnwantedMorphs;groupingTests;
	prepareforUnloadBookMorphandFriends;
	prepareforUnloadEtoys;
	prepareforUnloadNebraska;
	unloadSomeMore;unloadSomeMore2;unloadSomeMore3;cleanupPhaseFinal;createBackgroundColor! !


!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' stamp: 'edc 2/5/2008 07:56'!
groupingTests
" this is how I build Tests-edc.35 for unload "
| classList |

classList := OrderedCollection new.
	#(TestCase TestResource) do: [:cl|  (Smalltalk at:  cl)
		allSubclassesWithLevelDo: [:c :i | classList addFirst: c]
		startingLevel: 0].		
				 
	Smalltalk organization addCategory: 'Tests-Others'.
	 classList select: [:ea| ((ea basicCategory asString) beginsWith: 'Tests') not] thenDo: [:any|  SystemOrganization classify: any name under: 'Tests-Others']
	
! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' stamp: 'edc 3/13/2008 10:29'!
unloadSomeMore
#('Tests' 'SMLoader' 'SMBase' 'SUnit' 'SUnitGUI' 'ScriptLoader' 'Universes' 'Installer' 'XML-Parser' )
		do: [:ea | (MCPackage named: ea) unload].
		self fixObsoleteReferences ! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' stamp: 'edc 3/13/2008 10:29'!
unloadSomeMore2
"ReleaseBuilderFor3dot11 new unloadSomeMore2;cleanupPhaseFinal "
#('BookMorphandFriends'   )
		do: [:ea | (MCPackage named: ea) unload].self fixObsoleteReferences! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' stamp: 'edc 3/25/2008 08:35'!
unloadSomeMore3
"ReleaseBuilderFor3dot11 new unloadSomeMore3;cleanupPhaseFinal;cleanUnwantedCs "
#('MorphicExtras-Demo'  'Morphic-CandidatesForGo' )
		do: [:ea | (MCPackage named: ea) unload].
		SystemOrganization removeCategoriesMatching: 'EToys*'.
		self fixObsoleteReferences! !
-------------- next part --------------
A non-text attachment was scrubbed...
Name: ReleaseBuilderFor3dot11.cs
Type: application/octet-stream
Size: 1593 bytes
Desc: not available
Url : http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20121228/d5bf538e/ReleaseBuilderFor3dot11.obj


More information about the Squeak-dev mailing list