[squeak-dev] Re: Edgar from the Ostracism Re: Squeak 4.1 release candidate 2

Edgar J. De Cleene edgardec2005 at gmail.com
Thu Apr 8 11:30:09 UTC 2010




On 4/7/10 1:12 PM, "Andreas Raab" <andreas.raab at gmx.de> wrote:

> Really, I fail to see how anyone can reasonably claim superiority of
> change sets for what we're doing at this point.
> 
> Cheers,
>    - Andreas

Can't say any, your argument is  terrific.
Only one question.
Could we have some similar to
Utilities readNextUpdateFromServer retrieving only the next logic .mcz
coming from trunk?
This one ?
Utilities updateFromServerThroughUpdateNumber:

Suppose my wrong technique say the Closures changes is in 7200 and some
thinking like me but not telling in public wish have a 4.0.1 image.

No change sets for feed the image, but he/she wish have numbered in the
ChangeSorter ?

I attach yours with my modifications.

Is so bad and drive you mad this ? Hurt too much ?.

Edgar

-------------- next part --------------
'From Squeak4.0 of 10 March 2010 [latest update: #7195] on 7 April 2010 at 11:45:29 am'!
"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'!
Object subclass: #MCPackageLoader
	instanceVariableNames: 'requirements unloadableDefinitions obsoletions additions removals errorDefinitions provisions methodAdditions '
	classVariableNames: 'ChangeHIghUp '
	poolDictionaries: ''
	category: 'Monticello-Loading'!

!ChangeSet methodsFor: 'fileIn/Out' stamp: 'edc 4/7/2010 11:45'!
fileOut
	"File out the receiver, to a file whose name is a function of the 
	change-set name and either of the date & time or chosen to have a 
	unique numeric tag, depending on the preference 
	'changeSetVersionNumbers'"
	| slips nameToUse internalStream |
	self checkForConversionMethods.
	ChangeSet promptForDefaultChangeSetDirectoryIfNecessary.
	self name endsWithDigit ifTrue:[nameToUse := self name ,  FileDirectory dot , FileStream cs]
	ifFalse:[
	nameToUse := Preferences changeSetVersionNumbers
				ifTrue: [self defaultChangeSetDirectory nextNameFor: self name extension: FileStream cs]
				ifFalse: [self name , FileDirectory dot , Utilities dateTimeSuffix , FileDirectory dot , FileStream cs]].
	
	
	nameToUse := self defaultChangeSetDirectory fullNameFor: nameToUse.
	Cursor write
		showWhile: [internalStream := WriteStream
						on: (String new: 10000).
			internalStream header; timeStamp.
			self fileOutPreambleOn: internalStream.
			self fileOutOn: internalStream.
			self fileOutPostscriptOn: internalStream.
			internalStream trailer.
			FileStream
				writeSourceCodeFrom: internalStream
				baseName: (nameToUse copyFrom: 1 to: nameToUse size - 3)
				isSt: false
				useHtml: false].
	Preferences checkForSlips
		ifFalse: [^ self].
	slips := self checkForSlips.
	(slips size > 0
			and: [(PopUpMenu withCaption: 'Methods in this fileOut have halts
or references to the Transcript
or other ''slips'' in them.
Would you like to browse them?' chooseFrom: 'Ignore\Browse slips')
					= 2])
		ifTrue: [self systemNavigation browseMessageList: slips name: 'Possible slips in ' , name]! !


!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.
	].! !


!MCPackageLoader methodsFor: 'private' stamp: 'edc 2/13/2010 17:46'!
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].
	self class changeHighestUpdate
		ifTrue: [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]
		ifFalse: [newChanges := (ChangesOrganizer changeSetNamed: baseName)
						ifNil: [ChangeSet new name: baseName].
			changeHolder newChanges: newChanges.
			[aBlock value]
				ensure: [changeHolder newChanges: oldChanges]]! !


!MCPackageLoader class methodsFor: 'as yet unclassified' stamp: 'edc 9/29/2009 12:03'!
changeHighestUpdate
" MCPackageLoader changeHighestUpdate"
"Whether change highestUpdate by default.
	If true, logs to a file named after the configuration (config.nn.log).
	If false, logs to the transcript."
	<preference: 'Change SystemVersion current highestUpdate' 
		category: 'Monticello' 
		description: 'If true,  each monticello package loaded rises the highestUpdate)' 
		type: #Boolean>
	^ChangeHIghUp  ifNil:[ChangeHIghUp := false].! !

!MCPackageLoader class methodsFor: 'as yet unclassified' stamp: 'edc 10/1/2009 16:29'!
setHighestUpdate: aBoolean
" MCPackageLoader togleHighestUpdate"
self changeHighestUpdate.
	^ChangeHIghUp  := aBoolean! !


!Utilities class methodsFor: 'fetching updates' stamp: 'edc 2/14/2010 09:15'!
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"
	| config |
	MCPackageLoader setHighestUpdate: true.
	
	"Flush all caches. If a previous download failed this is often helpful"
	MCFileBasedRepository flushAllCaches.
	config := MCMcmUpdater updateFromRepositories: #(
		'http://source.squeak.org/trunk'
	).
	MCPackageLoader  setHighestUpdate: false..
	self inform: 'Update completed.
Current update number: ', SystemVersion current highestUpdate.! !

Object subclass: #MCPackageLoader
	instanceVariableNames: 'requirements unloadableDefinitions obsoletions additions removals errorDefinitions provisions methodAdditions'
	classVariableNames: 'ChangeHIghUp'
	poolDictionaries: ''
	category: 'Monticello-Loading'!
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