3.10.2 Forever ? (was Re: [squeak-dev] How to get a Trunk image)

Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Mon Sep 7 20:16:23 UTC 2009




On 9/7/09 4:34 PM, "David T. Lewis" <lewis at mail.msen.com> wrote:

>> I have a complete flow from Squeak3.10-7159-basic in .cs for each .mcz.
>> Also change the SystemVersion current highestUpdate and the version , as we
>> have too much different to this image/
>> For me, I have a Squeak3.11-alpha.7335.image which could put in Ftp and also
>> produce all .cs , for people like me feeling more confortable with .cs.
> 
> Edgar,
> 
> That sounds like a very good thing. How did you produce the .cs for each .mcz?
> 
> Dave


I attach the first .cs , the rest is made automatic.
In this I do not change any and do not put any different to trunk.
The .cs with number > 7173 could be exported from the image and the change
to for have the SystemVersion current highestUpdate rising without changing
others MC loads could be made different, off course.
If Board agree , I put all, the .cs and the Squeak3.11-alpha.7335.image in
my folder for some could polish and put in a best place.

Edgar

-------------- next part --------------
'From SqueakLight|II of 31 May 2008 [latest update: #7237] on 12 August 2009 at 9:36:15 am'!

!ReleaseBuilderFor3dot10 methodsFor: 'managing updates' stamp: 'edc 8/12/2009 09:27'!
flushCaches
	MCFileBasedRepository flushAllCaches.
	MCDefinition clearInstances.
	Smalltalk garbageCollect.
	"Initialization required for tests: strange why this is not a teardwon
	method "
	"SendCaches initializeAllInstances"! !

-------------- next part --------------
'From Squeak3.10beta of 22 July 2007 [latest update: #7159] on 5 September 2009 at 8:19:02 am'!




!MCPackageLoader methodsFor: 'private' stamp: 'edc 9/1/2009 03:37'!
useChangeSetNamed: baseName during: aBlock
    "Use the named change set, or create one with the given name."
    | changeHolder oldChanges newChanges csName |

    changeHolder := (ChangeSet respondsTo: #newChanges:)
                        ifTrue: [ChangeSet]
                        ifFalse: [Smalltalk].
    oldChanges := (ChangeSet respondsTo: #current)
                        ifTrue: [ChangeSet current]
                        ifFalse: [Smalltalk changes].
csName := (SystemVersion current highestUpdate + 1) asString,baseName.
    newChanges := (ChangesOrganizer changeSetNamed: csName) ifNil: [ ChangeSet new name: csName ].
    changeHolder newChanges: newChanges.
    [aBlock value] ensure: [changeHolder newChanges: oldChanges].
SystemVersion current registerUpdate: SystemVersion current highestUpdate + 1
! !

-------------- next part --------------
'From Squeak3.11alpha of 5 September 2009 [latest update: #7172] on 5 September 2009 at 8:31 am'!
"Change Set:		7173Starting trunk
Date:			5 September 2009
Author:			Edgar J. De Cleene

Trying to have upadted image with numbered change sets of any coming fron trunk"
Trnascript open.
MethodContext instVarNames at: 2 put: 'closureOrNil'.
MCMcmUpdater updateFromRepositories: #(
     'http://source.squeak.org/trunk')!

-------------- next part --------------
'From Squeak3.11alpha of 1 September 2009 [latest update: #7163] on 1 September 2009 at 9:18:36 am'!
ReleaseBuilderFor3dot10 subclass: #ReleaseBuilderFor3dot11
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ReleaseBuilder'!

!ReleaseBuilderFor3dot11 methodsFor: 'cleaning' stamp: 'edc 7/16/2009 19:48'!
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: [PackageOrganizer default unregisterPackageNamed: 'FlexibleVocabularies'.Command zapObsolete.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 | [PointerFinder on: each]
                        on: Error
                        do: [:error | Transcript show: error; cr]]].
                        self cleanUnwantedCs


! !

!ReleaseBuilderFor3dot11 methodsFor: 'cleaning' stamp: 'edc 7/16/2009 17:37'!
cleanupPhasePrepare
self cleanUnwantedCs.
                "SMSqueakMap default clearCaches."
" Commented out for no Undeclared on image "
#(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: .
#(test1 test2) do:[:ea|
WorldWindow class removeSelector:   ea].
SystemOrganization removeCategoriesMatching: 'UserObjects'.
FileList2 class organization classify: #morphicViewOnDirectory: under: 'morphic ui'.
FileList2 class organization classify: #morphicView under: 'morphic ui'.
SystemOrganization classifyAll: #(AbstractMediaEventMorph ColorSwatch) under: 'MorphicExtras-AdditionalSupport'.
Morph class organization classify: #isTileScriptingElement under: '*Unload-scripting'
Morph class organization classify: #partName:categories:documentation:sampleImageForm: under: '*Unload-eToys-new-morph participation'! !


!ReleaseBuilderFor3dot11 methodsFor: 'sources managment' stamp: 'edc 2/12/2008 09:04'!
createCompressedSources
" ReleaseBuilderFor3dot11 new createCompressedSources"
| unzipped nameToUse zipped buffer dir |
ProtoObject allSubclassesWithLevelDo:[:cl :l| 
	dir := self createDirIfnotExists:cl category.
	
	
	Cursor write showWhile: [nameToUse :=  cl printString .
		(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, FileDirectory dot, ImageSegment compressedFileExtension).
	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: '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 9/1/2009 09:18'!
makeSqueakThreeTenEleven
	"ReleaseBuilderFor3dot11 new makeSqueakThreeTenEleven"
	Transcript open.
	self cleanupPhasePrepare
	"prepareforUnloadBookMorphandFriends;"
	;prepareforUnloadEtoys;
	prepareforUnloadNebraska
	;groupingTests;
	unloadSomeMore;unloadSomeMore3;cleanupPhaseFinal;createBackgroundColor.
	"World removeAllMorphs."
! !

!ReleaseBuilderFor3dot11 methodsFor: 'squeakThreeEleven' stamp: 'edc 6/5/2008 08:12'!
saveInLadrillos: packageName 
	| monti ances repo montiNames |
	monti := MCWorkingCopyBrowser new.
	repo := MCHttpRepository
				location: 'http://www.squeaksource.com/Ladrillos'
				user: ''
				password: ''.
	montiNames := repo readableFileNames.
	
	(SystemOrganization categoriesMatching: packageName , '*')
		do: [:cat | 
			| workingCopy | 
			PackageInfo registerPackageName: cat asString.
			workingCopy := MCWorkingCopy
						forPackage: (MCPackage new name: cat asString).
			workingCopy repositoryGroup addRepository: repo.
			repo user
				ifEmpty: [repo
						user: (UIManager default request: 'Ladrillos Repository username').
					repo
						password: (UIManager default request: 'Ladrillos Repository  password')].
			ances := montiNames
						detect: [:ea | ea beginsWith: cat asString]
						ifNone: [].
			ances
				ifNil: [repo
						storeVersion: (workingCopy newVersionWithName: workingCopy uniqueVersionName message: 'Starting Morphic partition')].
			monti workingCopyListChanged; changed: #workingCopySelection; changed: #repositoryList]! !


!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) match: '*Test*') not] thenDo: [:any|  SystemOrganization classify: any name under: 'Tests-Others'].

! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' stamp: 'edc 6/2/2008 09:33'!
prepareToUnloadTraits
"ReleaseBuilderFor3dot11 new  prepareToUnloadTraits"
SystemChangeNotifier uniqueInstance
noMoreNotificationsFor: ProvidedSelectors current;
noMoreNotificationsFor: RequiredSelectors current;
noMoreNotificationsFor: LocalSends current.
self unloadTraitsStubOutAcessors.

[ClassDescription subclass: #Metaclass
instanceVariableNames: 'thisClass'
classVariableNames: ' '
poolDictionaries: ' '
category: 'Kernel-Classes'.
ClassDescription subclass: #Class
instanceVariableNames: 'subclasses name classPool sharedPools environment category'
classVariableNames: ' '
poolDictionaries: ' '
category: 'Kernel-Classes'.
] on: Warning do: [:warning | warning resume].

Smalltalk allTraits do: [:trait | trait removeFromSystem. trait := nil].
"Recompile all methods that were part of a trait"
SystemNavigation default allBehaviorsDo: [:class | class selectorsAndMethodsDo: [:sel :method | class ~~ method methodClass ifTrue: [class recompile: sel]. method := nil]. class := nil].
"Remove references to traits from various places in the code"
self unloadTraits! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' 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: 'unloadPackages' stamp: 'edc 7/16/2009 19:48'!
prepareforUnloadEtoys
Smalltalk removeClassNamed: #FlexibleVocabulariesInfo.
Smalltalk removeClassNamed: #ColorSwatch.
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'.

#('*eToys-queries' '*eToys-eToy vocabularies' '*eToys-color' '*eToys-customevents-custom events' '*eToys-type vocabularies') do:[:ea| 
Vocabulary class removeCategory: ea].

#('*flexibleVocabularies-flexiblevocabularies-scripting' '*flexibleVocabularies-flexibleVocabularies' '*eToys-scripting' '*eToys-new-morph participation' '*eToys-customevents-user events') do:[:ea|
Morph class removeCategory:  ea].
#(nascentUserScriptInstance userScriptForPlayer: selector:  ) do:[:ea|
Player class removeSelector:  ea].
Smalltalk removeClassNamed: #FlexibleVocabulariesInfo.
Preferences removePreference: #allowEtoyUserCustomEvents. 
Morph organization classify: #partName:categories:documentation:sampleImageForm: under: '*MorphicExtras-new-morph participation'.
#(possiblyReplaceEToyFlaps twiddleSuppliesButtonsIn:) do: [:ea| 
Flaps class removeSelector:   ea].
Flaps clobberFlapTabList.
Flaps addStandardFlaps.
SystemOrganization classifyAll: #(ComponentLikeModel) under: 'MorphicExtras-Components'
! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' 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: '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 7/16/2009 19:49'!
unloadSomeMore3
"ReleaseBuilderFor3dot11 new unloadSomeMore3;cleanupPhaseFinal;cleanUnwantedCs "
#('MorphicExtras-Demo'  'Morphic-CandidatesForGo' 'Nebraska' 'UserObjects')
		do: [:ea | (MCPackage named: ea) unload].
		SystemOrganization removeCategoriesMatching: 'EToys*'.
		self fixObsoleteReferences! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' stamp: 'edc 6/2/2008 10:14'!
unloadTraits
	"ReleaseBuilderFor3dot11 new unloadTraits"
	self saveInLadrillos: 'Traits'.
	self unloadTraitsClearRefs.
	(MCPackage named: 'Traits') unload.
	self unloadTraitsTraitsStubs.
	self fixObsoleteReferences! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' stamp: 'edc 6/2/2008 09:44'!
unloadTraitsClearRefs

| loader |
	loader _ CodeLoader new.
	loader baseURL:'http://installer.pbwiki.org/f/'.
	
	"Sources and segments can be loaded in parallel"
	loader loadSourceFiles: #('UnloadTraits-ClearRefs.cs' ).
	! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' stamp: 'edc 6/2/2008 09:34'!
unloadTraitsStubOutAcessors

| loader |
	loader _ CodeLoader new.
	loader baseURL:'http://installer.pbwiki.org/f/'.
	
	"Sources and segments can be loaded in parallel"
	loader loadSourceFiles: #('UnloadTraits-StubOutAcessors.cs' ).
	! !

!ReleaseBuilderFor3dot11 methodsFor: 'unloadPackages' stamp: 'edc 6/2/2008 09:45'!
unloadTraitsTraitsStubs

| loader |
	loader _ CodeLoader new.
	loader baseURL:'http://installer.pbwiki.org/f/'.
	
	"Sources and segments can be loaded in parallel"
	loader loadSourceFiles: #('UnloadTraits-TraitsStubs.cs' ).
	! !


!ReleaseBuilderFor3dot11 methodsFor: 'updates' stamp: 'edc 7/16/2009 17:38'!
installtrunk

" ReleaseBuilderFor3dot11 new installtrunk"

	MCWorkingCopy allManagers
		do: [:each | each repositoryGroup addRepository: (MCHttpRepository new location: 'http://source.squeak.org/trunk/';
					 user: 'squeak';
					 password: 'squeak')]! !

!ReleaseBuilderFor3dot11 methodsFor: 'updates' stamp: 'edc 7/15/2009 16:45'!
loadLastVersion: aListOfPackageNames 
	| mcw montiNames package version |
	mcw := MCWorkingCopyBrowser new
				repository: (MCHttpRepository
						location:  'http://source.squeak.org/trunk/'
						user: ''
						password: '').
	mcw repository
		ifNotNilDo: [:repos | montiNames := repos readableFileNames].
	aListOfPackageNames
		do: [:mo | 
			package := montiNames
						detect: [:ea | (ea findTokens: '-' ) first = mo]
						ifNone: [].
			package
				ifNotNil: [version := mcw repository loadVersionFromFileNamed: package.
					version load]].
	^ version! !

!ReleaseBuilderFor3dot11 methodsFor: 'updates' stamp: 'edc 7/16/2009 17:38'!
repository
	repository isNil
		ifTrue: [repository := MCHttpRepository
						location: 'http://source.squeak.org/trunk'
						user: ''
						password: ''].
	^ repository! !
-------------- next part --------------
'From Squeak3.10beta of 22 July 2007 [latest update: #7159] on 17 July 2009 at 7:33:48 pm'!
"Change Set:		7160Utilities-initializeCommonRequestStrings
Date:			17 July 2009
Author:			Edgar J.De Cleene

Some convenince Utilities for test updates in developer computer and from remote ftp"!


!Utilities class methodsFor: 'common requests' stamp: 'edc 7/17/2009 19:27'!
initializeCommonRequestStrings
	"Initialize the common request strings, a directly-editable list of expressions that can be evaluated from the 'do...' menu."

	CommonRequestStrings _ StringHolder new contents: 
'Utilities emergencyCollapse.
Utilities closeAllDebuggers.
Utilities applyUpdatesFromDisk.
Utilities ftpUpdates.
Utilities browseRecentSubmissions.
SmalltalkImage current aboutThisSystem.
-
Sensor keyboard.
ParagraphEditor abandonChangeText.
Cursor normal show.
-
CommandHistory resetAllHistory.
Project allInstancesDo: [:p | p displayDepth: 16].
ScriptingSystem inspectFormDictionary.
Form fromUser bitEdit.
Display border: (0 at 0 extent: 640 at 480) width: 2.
-
Undeclared inspect.
Undeclared removeUnreferencedKeys; inspect.
Transcript clear.
Utilities grabScreenAndSaveOnDisk.
FrameRateMorph new openInHand.
-
Utilities reconstructTextWindowsFromFileNamed: ''TW''.
Utilities storeTextWindowContentsToFileNamed: ''TW''.
ChangeSorter removeEmptyUnnamedChangeSets.
ChangeSorter reorderChangeSets.
-
ActiveWorld installVectorVocabulary.
ActiveWorld abandonVocabularyPreference.
Smalltalk saveAsNewVersion'

"Utilities initializeCommonRequestStrings"! !

Utilities initializeCommonRequestStrings!

-------------- next part --------------
'From Squeak3.9 of 17 July 2009 [latest update: #7159] on 17 July 2009 at 7:17:57 pm'!
"Change Set:		7068AdvanceToThreeDotTenAlpha
Date:			17 July 2009
Author:			Edgar J. De Cleene

"



"Offer the chance to advance the version number."
(self confirm: 'There are no further updates for Squeak 3.10.
Do you wish to advance to version 3.11alpha?
[Yes] Your system will be marked as 3.11alpha, and you will
subsequently receive ''test pilot'' updates for 3.11.
[No] Your system will be marked as 3.10, allowing you
to receive only final fixes for the 3.10 stable release.
[Neither] You may choose No, and immediately quit without saving,
allowing you to make a backup copy before adopting this change.
DO YOU WANT TO ADVANCE to Version 3.11alpha now?')
	ifTrue: [SystemVersion newVersion: 'Squeak3.11alpha'.
			SystemVersion current date: Time now asDate.
			self inform: 'You may now save this Version 3.11alpha image
and retrieve updates again for 3.11alpha and beyond.']
	ifFalse: [self inform: 'You may now save this Version 3.10 final image.
- - - - -
(If you quit without saving now, your image will revert to
3.10 without any of the updates you just loaded)']!

-------------- next part --------------
'From Squeak3.11alpha of 1 September 2009 [latest update: #7168] on 1 September 2009 at 9:07:16 am'!
"Change Set:		7234
Date:			11 August 2009
Author:			Edgar J. De Cleene

First step to synch with trunk"
ReleaseBuilderFor3dot11 new installtrunk.
ReleaseBuilderFor3dot11 new updatePackages: 'MonticelloConfigurations-ar.58.mcz'.!



More information about the Squeak-dev mailing list