2.8 Update candidates

Bob Arning arning at charm.net
Sun Nov 12 22:29:29 UTC 2000


On Sun, 12 Nov 2000 13:04:26 -0800 Ned Konz <ned at bike-nomad.com> wrote:
>Well, basic QA would take a current 2.8 image and try to file in each of
>these change sets in order. I filed out each of these change sets from
>my 2.9 image, and tried this. I found:

Ned,

Filing out a change set from a 2.9 image will file out the current state of those methods, not necessarily what that change set originally specified (if they were later modified by another). For thos who might like to try getting the originals, here is a hack to do so.

Cheers,
Bob

=====code follows=====
'From Squeak2.8 of 13 June 2000 [latest update: #2360] on 12 November 2000 at 5:25:04 pm'!
"Change Set:		getSomeUpdates
Date:			12 November 2000
Author:			Bob Arning

- a hack to get 2.9 updates into 2.8 system. Evaluate 'Utilities bob1' to read the specified change sets to disk. You can then experiment with loading them one at a time from the updates folder.

Some of the updates in the list Dan emailed do not work in 2.8. Others are already in 2.8 under another number. Some of these are noted in #bob1 "!


!Utilities class methodsFor: 'fetching updates' stamp: 'RAA 11/12/2000 17:22'!
bob1
"
Utilities bob1
"

	self flag: #bob.		" a hack to get some 2.9 updates into 2.8"

"broken - 2406 2410 "
"not needed - 2422 2521 2522 "

	self 
		readServerUpdatesFrom: #(
					2406 2410 2412 2413 2414 2415 2416 2422 2424 
					2439 2502 2521 2522 2627 2630 2633 2644 2653 2656 ) 
		saveLocally: true 
		updateImage: false.

! !

!Utilities class methodsFor: 'fetching updates' stamp: 'RAA 11/12/2000 17:11'!
extract2point9: list
	"Pull out the part of the list that applies to this version."

	| delims lines ii out |

	self flag: #bob.		" a hack to get some 2.9 updates into 2.9"



	delims _ String with: Character cr with: Character linefeed.
	lines _ list findTokens: delims.
	ii _ lines indexOf: '#Squeak2.9alpha'.
	ii = 0 ifTrue: [^ #()].
	out _ OrderedCollection new.
	[(ii _ ii + 1) <= lines size] whileTrue:
		[(lines at: ii) first == $# ifTrue: [^ out "next version"].
		(lines at: ii) first == $* ifFalse: [out addLast: (lines at: ii)]].	"keep, except comments"
	^ out! !

!Utilities class methodsFor: 'fetching updates' stamp: 'RAA 11/12/2000 17:11'!
newUpdatesOn: serverList fromList: numbersToGet
	"Return a list of fully formed URLs of update files we do not yet have.  Go to the listed servers and look at the file 'updates.list' for the names of the last N update files.  We look backwards for the first one we have, and make the list from there.  tk 9/10/97
	No updates numbered higher than aNumber (if it is not nil) are returned " 

	| existing doc list out ff raw char itsNumber |

	self flag: #bob.		" a hack to get some 2.9 updates into 2.9"



	out _ OrderedCollection new.
	existing _ ChangeSorter allChangeSetNames.
	existing _ existing collect: [:cngSet | cngSet copyReplaceAll: '/' with: '_'].
			"Replace slashes with underbars"
	serverList do: [:server |
		doc _ HTTPSocket httpGet: server,'updates.list' accept: 'application/octet-stream'.
		"test here for server being up"
		doc class == RWBinaryOrTextStream ifTrue:
			[raw _ doc reset; contents.	"one file name per line"
			list _ self extract2point9: raw.
			list reverseDo: [:fileName |
				ff _ (fileName findTokens: '/') last.	"allow subdirectories"

				(existing includes: ff sansPeriodSuffix)
					ifFalse:
						[itsNumber _ ff initialIntegerOrNil. 
						(itsNumber == nil or: [numbersToGet includes: itsNumber])
							ifTrue:
								[out addFirst: server, fileName]]
					ifTrue: [^ out]].
			((out size > 0) or: [char _ doc reset; skipSeparators; next.
				(char == $*) | (char == $#)]) ifTrue:
					[^ out "we have our list"]].	"else got error msg instead of file"
		"Server was down, try next one"].
	PopUpMenu notify: 'All code update servers seem to be unavailable'.
	^ out! !

!Utilities class methodsFor: 'fetching updates' stamp: 'RAA 11/12/2000 17:11'!
readServerUpdatesFrom: aList saveLocally: saveLocally updateImage: updateImage

"Utilities readServerUpdatesThrough: 828 saveLocally: true updateImage: true"

	| urls failed loaded str docQueue this nextDoc docQueueSema |

	self flag: #bob.		" a hack to get some 2.9 updates into 2.9"



	Utilities chooseUpdateList ifFalse: [^ self].	"ask the user which kind of updates"
	Cursor wait showWhile: [(Smalltalk includesKey: #EToySystem)
		ifTrue: [ScriptingSystem guessDOLProxy].

	urls _ self newUpdatesOn: (Utilities serverUrls collect: [:url | url, 'updates/']) 
				fromList: aList.
	loaded _ 0.
	failed _ nil.

	"send downloaded documents throuh this queue"
	docQueue := SharedQueue new.

	"this semaphore keeps too many documents from beeing queueed up at a time"
	docQueueSema := Semaphore new.
	5 timesRepeat: [ docQueueSema signal ].

	"fork a process to download the updates"
	self retrieveUrls: urls ontoQueue: docQueue withWaitSema: docQueueSema.

	"process downloaded updates in the foreground"
	[ this _ docQueue next.
	  nextDoc _ docQueue next.  
	  nextDoc = #failed ifTrue: [ failed _ this ].
	  (failed isNil and: [ nextDoc ~= #finished ])
	] whileTrue: [
		failed ifNil: [
			nextDoc reset; text.
			nextDoc size = 0 ifTrue: [ failed _ this ]. ].
		failed ifNil: [
			nextDoc peek asciiValue = 4	"pure object file"
				ifTrue: [failed _ this]].	"Must be fileIn, not pure object file"
		failed ifNil: [
			"(this endsWith: '.html') ifTrue: [doc _ doc asHtml]."
				"HTML source code not supported here yet"
			updateImage ifTrue:	
				[ChangeSorter newChangesFromStream: nextDoc
					named: (this findTokens: '/') last].
			saveLocally ifTrue:
				[self saveUpdate: nextDoc onFile: (this findTokens: '/') last].	"if wanted"
			loaded _ loaded + 1].

		docQueueSema signal].
	].

	"report to user"
	str _ loaded printString ,' new update file(s) processed.'.
	failed ifNotNil: [str _ str, '\Could not load ' withCRs, 
		(urls size - loaded) printString ,' update file(s).',
		'\Starting with "' withCRs, failed, '".'].
	failed ifNil: [
		"DocLibrary external ifNotNil: [
			DocLibrary external updateMethodVersions] are not using this yet"].
	self inform: str.

! !





More information about the Squeak-dev mailing list