[squeak-dev] Re: The boundary between 3.10 and 3.11

Andreas Raab andreas.raab at gmx.de
Sat Dec 19 16:22:08 UTC 2009


Folks -

I spent some time looking at the update process from 3.10 to 3.11 and 
I'm not entirely happy with the process proposed so far. There are two 
independent issues here:

1) Are there fixes from 3.11 that should be backported to 3.10? If we 
have fixes that 3.10 users would like to see we should set up another 
maintenance release, i.e., 3.10.3 and push those out. This issue is 
unrelated to updating to 3.11.

2) How do we get people from 3.10 to 3.11? From my perspective offering 
an update that takes you from a known stable version (3.10) to an 
unstable version (3.11alpha) feels wrong. I think this should be a 
manual decision.

As a consequence, I would propose that we split the process a little: We 
define another update target in the updates.list for 3.11 alpha which 
contains the necessary preparations for updating to 3.11. I have 
attached a change set which can be filed into any 3.10.x image and will 
allow you to successfully receive trunk updates (it does take a while 
though). Anyone who now wants to transform their 3.10.x image forward to 
3.11 can do so by manually advancing their system version to 3.11alpha 
and simply hit update (which would load the attached update first, then 
continue with loading trunk updates).

This process leaves us with the options of both backporting a few more 
fixes in the middle as well as issuing an automatic update to allow 
advancing to 3.11 if we decide that's a useful step.

Summary:
1. Let's define a Squeak 3.11 alpha target in updates.list
2. Put in something like the attached CS as the only 3.11 update
    (this still has my timeout fix in it; might want to change this to
     Bert's solution)
3. Decide whether we have high priority fixes to backport as 3.10.3
4. Decide whether or not to offer an automatic update from 3.10 to 3.11

Cheers,
   - Andreas

Andreas Raab wrote:
> Hi Edgar -
> 
> Edgar J. De Cleene wrote:
>> Here I attach the .cs as we discuss earlier.
>> I do not thing any do the all way from the 7213 until we have now , 
>> because
>> is take hours and many hand labor.
> 
> I think we need to make sure that this works. I'll spend some time on it 
> today.
> 
>> I preparing the Christmas version of Fun3.11, it's your chance to ask for
>> packages your wish have into.
> 
> Sounds great. Do you want to check out Mason to see how it fits building 
> a larger image automatically? It would be good if we could start 
> automating these processes.
> 
> Cheers,
>   - Andreas
> 
> 
> 

-------------- next part --------------
'From Squeak3.10.2 of ''5 June 2008'' [latest update: #7179] on 19 December 2009 at 5:10:16 pm'!
"Change Set:		PrepareFor311Updates
Date:			19 December 2009
Author:			Andreas Raab

Necessary preparations for 3.11 updates from trunk."!

MCVersionReader subclass: #MCMcmReader
	instanceVariableNames: 'fileName configuration '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'MonticelloConfigurations'!
Object subclass: #MCMcmUpdater
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'MonticelloConfigurations'!

!MCConfiguration methodsFor: 'private' stamp: 'ar 12/19/2009 15:32'!
logUpdate: aPackage with: aVersion
	self log
		cr; nextPutAll: '========== ', aVersion info name, ' =========='; cr;
		cr; nextPutAll: aVersion info message asString; cr;
		flush.

	aPackage hasWorkingCopy ifFalse: [^self].

	aPackage workingCopy ancestors do: [:each |
		(aVersion info hasAncestor: each)
			ifTrue: [([aVersion info allAncestorsOnPathTo: each]
						valueWithin: 5 seconds onTimeout:[#()])
				do: [:ver | self log cr; nextPutAll: '>>> ', ver name, ' <<<'; cr;
							nextPutAll: ver message; cr; flush]]]! !


!MCMcmReader methodsFor: 'accessing' stamp: 'ar 6/30/2009 17:05'!
configuration
	configuration ifNil: [self loadConfiguration].
	"browser modifies configuration, but the reader might get cached"
	^configuration copy! !

!MCMcmReader methodsFor: 'accessing' stamp: 'ar 6/30/2009 17:05'!
loadConfiguration
	stream reset.
	configuration := MCConfiguration fromArray: (MCScanner scan: stream).
	configuration name: self configurationName.
! !

!MCMcmReader methodsFor: 'accessing' stamp: 'ar 6/30/2009 17:06'!
loadVersionInfo
	info := self configuration! !

!MCMcmReader methodsFor: 'accessing' stamp: 'ar 6/30/2009 17:06'!
version
	^self configuration! !


!MCMcmUpdater class methodsFor: 'updating' stamp: 'ar 6/30/2009 17:19'!
updateFromRepositories: repositoryUrls
	"MCMcmUpdater updateFromRepositories: #(
		'http://squeaksource.com/MCUpdateTest'
	)"

	| repos updateList parts base author version type config |
	Preferences enable: #upgradeIsMerge.

	"The list of repositories to consult in order"
	repos := repositoryUrls collect:[:url| 
		MCRepositoryGroup default repositories 
			detect:[:r| r description = url]
			ifNone:[ | r |
				r := MCHttpRepository location: url user: '' password: ''.
				MCRepositoryGroup default addRepository: r.
				r]].

	"The list of updates-author.version.mcm sorted by version"
	updateList := SortedCollection new.
	repos do:[:r|
		"Find all the updates-author.version.mcm files"
		r allFileNames do:[:versionedName|
			parts := versionedName findTokens: '.-'.
			parts size = 4 ifTrue:[
				base := parts at: 1.
				author := parts at: 2.
				version := [(parts at: 3) asNumber] on: Error do:[:ex| ex return: 0].
				type := parts at: 4.
			].
			(base = 'update' and:[version > 0 and:[type = 'mcm']]) 
				ifTrue:[updateList add: version -> versionedName]].
		"Now process each update file. Check if we have all dependencies and if not,
		load the entire configuration (this is mostly to skip older updates quickly)"
		updateList do:[:assoc|
			config := r versionFromFileNamed: assoc value.
			(config dependencies allSatisfy:[:dep| dep isFulfilled]) 
				ifFalse:[config upgrade]].
		"We've loaded all the provided update configurations.
		Use the latest configuration to update all the remaining packages."
		config updateFromRepositories.
		config upgrade.
	].! !


!Utilities class methodsFor: 'fetching updates' stamp: 'ar 7/2/2009 19:19'!
updateFromServer
	"Update the image by loading all pending updates from the server.  Also save local copies of the update files if the #updateSavesFile preference is set to true"
	MCMcmUpdater updateFromRepositories: #(
		'http://source.squeak.org/trunk'
	)
	"self readServerUpdatesSaveLocally: Preferences updateSavesFile updateImage: true"! !

MCVersionReader subclass: #MCMcmReader
	instanceVariableNames: 'fileName configuration'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'MonticelloConfigurations'!
"Postscript:
Give notice about update changes."
MethodContext instVarNames at: 2 put: 'closureOrNil'.
(StringHolder new contents: 
'PLEASE READ the following notes before you attempt to update further:

* Your system is now ready to receive trunk updates for 3.11. In order to process the following updates you MUST use an updated virtual machine available from:
- http://squeakvm.org/win32 (for Windows - use 3.11 or later)
- http://squeakvm.org/unix (for Unix - use 3.11 or later)
- ftp://ftp.smalltalkconsulting.com/ (for Mac - use Squeak4.2.1beta1U.app or later)

* At one point during the update process you will receive a Monticello conflict warning about class PreferenceExample. To get past this point, select the (bold) class definition of PreferenceExample, click on the "keep" button, then click on the "merge" button.

* If during updating you encounter network errors, just try updating again. Due to the number of updates outstanding you might have to try a few times, in particular when using wireless connections.

* If during updating you encounter an error that says "Cannot find EOCD position" (a variant on the network problem above) you will have to do the following: 1) Open a Monticello browser, 2) select any repository in the (right hand) repository list, 3) choose "flush cached versions" from the context menu and 4) update again.
')
		openLabel: 'Before continuing...'!



More information about the Squeak-dev mailing list