[squeak-dev] Re: Squeak 4.1 release candidate 2

Andreas Raab andreas.raab at gmx.de
Tue Apr 6 03:21:25 UTC 2010


On 4/5/2010 1:08 PM, Juan Vuletich wrote:
> Is there some way to take a 4.0 image and update it to 4.1?

Absolutely. Download 4.0, file in the attached change set (which is what 
I'd be proposing as the "final" 4.0/3.10 update) and update.

Do note that there are a few places where you need to explicitly resolve 
merge conflicts, so it's not entirely automatic. Also, I've found that 
depending on one's luck you may run into an issue with 
Number>>readFrom:ifFail: - if that happens to you simply implement 
readFrom:ifFail: as "^self readFrom:" and proceed.

If you're updating a custom image you may have more merge conflicts but 
the process should work there too (it did for me in several images I 
used it on for testing).

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