[squeak-dev] The Trunk: Installer-Core-nice.336.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Feb 11 20:04:32 UTC 2010


Nicolas Cellier uploaded a new version of Installer-Core to project The Trunk:
http://source.squeak.org/trunk/Installer-Core-nice.336.mcz

==================== Summary ====================

Name: Installer-Core-nice.336
Author: nice
Time: 11 February 2010, 9:04:24.712 pm
UUID: d15618c9-d46a-4ddb-8240-7964aed0bdc2
Ancestors: Installer-Core-mtf.335

1) push some temp declarations inside blocks
2) use sort:
3) remove use of doWhileTrue:

The only value added by #doWhileTrue: vs #whileTrue is to return the value of receiver block.
The senders did not even use this return value, so this usage is absolutely void...
Well, not exactly void, it also deoptimize the method (I presume we don't care).

1) Given these are the two sole senders of doWhileTrue:
2) Given that I personnally misunderstand doWhileTrue: (at first read, I thought it would be equivalent to whileTrue:)
I militate for deprecation of doWhileTrue:
Opinions ?

=============== Diff against Installer-Core-mtf.335 ===============

Item was changed:
  ----- Method: InstallerUpdateStream>>writeList:toStream: (in category 'updates') -----
  writeList: listContents toStream: strm
  	"Write a parsed updates.list out as text.
  	This is the inverse of parseUpdateListContents:"
- 
- 	| fileNames releaseTag |
  	strm reset.
  	listContents do:
+ 		[:pair |
+ 		| releaseTag fileNames | 
- 		[:pair | 
  		releaseTag := pair first.  
  		fileNames := pair last.
  		strm nextPut: $#; nextPutAll: releaseTag; cr.
  		fileNames do: [:fileName | strm nextPutAll: fileName; cr]].
  	strm close!

Item was changed:
  ----- Method: InstallerUniverse>>basicInstall (in category 'basic interface') -----
  basicInstall
- 
- 	| pkgAndVersion pkg version potentials |
  	self packages do: [ :packageName |
+ 		| potentials pkg pkgAndVersion version |
  	
  		pkgAndVersion := self packageAndVersionFrom: packageName.
  		pkg := pkgAndVersion first.
  		version := pkgAndVersion last.
  	
  		potentials := universe packageVersionsForPackage: pkg.
  	
  		pkg := version isEmpty 
  			ifTrue: [ potentials last ]
  			ifFalse: [ 
  				version := self classUVersion readFrom: version readStream.  
  				potentials detect:[ :p | p version = version] ifNone: [ ^ self error: 'version not found']
  			].		
+ 		universe planToInstallPackage: pkg.
- 	universe planToInstallPackage: pkg.
  	].
  	self uniDoInstall!

Item was changed:
  ----- Method: Installer>>install:from: (in category 'mantis') -----
  install: aFileName from: stream
- 
- | ext installSelector mcThing |
- 	 
  	self log: ' installing...'.
+ 
+ 	self withAnswersDo: [
+ 		| ext installSelector mcThing |
-  
- 	self withAnswersDo:	[
- 		
  		mcThing := self classMCReader ifNotNil: [ self mcThing: aFileName from: stream ].
- 		
  		mcThing 
  			ifNotNil: [ (mcThing respondsTo: #install) 
  						ifTrue: [ mcThing install ]
  				        	ifFalse: [ (mcThing respondsTo: #load) ifTrue: [ mcThing load ] ]
  			]
  			ifNil: [ 
- 		
  				ext := (aFileName copyAfterLast: $/) in: [ :path | path isEmpty ifTrue: [ aFileName ] ifFalse: [ path ] ].
  				ext :=  ext copyAfterLast: $..
  				ext = '' ifTrue: [ ext := 'st' ].
  				installSelector := ('install', ext asUppercase, ':from:') asSymbol.
  	
  				useFileIn ifTrue: [ 
  				[
  					SystemChangeNotifier uniqueInstance doSilently: [self install: aFileName from: stream using: installSelector ]] 
  						on: Warning do: [ :ex | ex resume: true ].
  				] ifFalse: [
  					self install: aFileName from: stream using: installSelector. 
  				]
  			]
  	]. 
  
  	self log: ' done.'
  !

Item was changed:
  ----- Method: InstallerMonticello>>mcThing (in category 'monticello') -----
  mcThing
+ 	| loader files count |
  
- 	| loader files fileToLoad  version  count |
- 
  	loader := self classMCVersionLoader new.
  	
  	count := 0. files := nil.
  	self logCR: 'reading ', mc description, '...'.
  		"several attempts to read files - repository readableFileNames sometimes fails"
  	[ count := count + 1.
  	 (files = nil) and:[ count < 5 ] ] 
+ 		whileTrue: [files := mc readableFileNames sort: self mcSortFileBlock ].
- 		whileTrue: [files := mc readableFileNames asSortedCollection: self mcSortFileBlock ].
  	files ifNil: [  Warning signal: 'Repository not readable: ', mc description. ^ nil  ].
  		
  	self packages do: [ :pkg |
+ 		| fileToLoad version |
  
  		self log: 'finding ', pkg asString, '...'.
  		
  		fileToLoad := files detect: (self mcDetectFileBlock: pkg) ifNone: [ nil ].
  		
  		version := mc versionFromFileNamed: fileToLoad.
  		(version isKindOf: MCConfiguration) 
  			ifTrue: [ ^ version ]
  			ifFalse:[
  				MCRepositoryGroup default addRepository: self normalizedRepository.
  				version workingCopy repositoryGroup addRepository: self normalizedRepository.
  				loader addVersion: version ].
  			
  		self logCR: ' found ', version fileName, '...'.
  	].
  
  	^ loader!

Item was changed:
  ----- Method: InstallerSqueakMap>>update (in category 'squeakmap') -----
  update
  "Updates the local map for SqueakMap, upgrading SqueakMap to the latest version if necessary.
  
  When SqueakMap is old and needs to be upgraded, it does four things that mostly make sense in the interactive world SM was built for, but are totally evil here in the world of automatic scripting:
  1. It asks the user if she wants to upgrade, in the form of a pop-up (see SMSqueakMap >> #checkVersion:).
  2. It terminates its own process.
  3. It creates a new UI process.
  (see the last line of the SqueakMap upgrade file-in: ''Project spawnNewProcessAndTerminateOld: true'', from 
  http://map.squeak.org/accountbyid/9bdedc18-1525-44a6-9b79-db5d4a87f6f8/files/SqueakMap8.st
  4. It opens a SqueakMap window
  
  We work around these three problems seperately:
  1. We use #answer:with: and #withAnswersDo: to automatically answer ''Yes'' when asked if we want to upgrade
  2. We don't want this process to be terminated, so we run the update in a forked process and wait for it to finish, using #fork, #ensure:, and a Semaphore
  3. We keep track of the UI process before updating, and if it changes, we terminate the new UI process and reinstall the old one using Project >> #resumeProcess:
  4. We don't bother with the newly opened window. The other three problems are much worse.
  
  We do all this in a new process, since it is not unlikely that this method is executing in the UI process"
  
+ 	| oldUIProcess doneSema |
- 	| oldUIProcess newUIProcess doneSema |
  	self answer: 'You need to upgrade the SqueakMap package' with: true.
  	oldUIProcess := Project uiProcess.
  	doneSema := Semaphore new.
  	[[self withAnswersDo: [self classSMSqueakMap default loadUpdates]] 
+ 		ensure: [
+ 			| newUIProcess |
+ 			newUIProcess := Project uiProcess.
+ 			(oldUIProcess ~~ newUIProcess
- 		ensure: [newUIProcess := Project uiProcess.
- 		(oldUIProcess ~~ newUIProcess
  				and: [oldUIProcess notNil]
  					and: [oldUIProcess isTerminated not])
  					 ifTrue: [
  							newUIProcess ifNotNil: [newUIProcess terminate].
  							oldUIProcess suspend.
  							Project resumeProcess: oldUIProcess.].
+ 			doneSema signal]] fork.
- 	doneSema signal]] fork.
  	doneSema wait!

Item was changed:
  ----- Method: InstallerWeb>>urlToDownload (in category 'web install') -----
  urlToDownload
+ 	"while we look for a url which returns what we are looking for, we get the data anyway"
- 
- 	"while we look for a url which returns what we are looking for, we  get the data anyway"
  	
+ 	| delay |
- 	| delay retry |
  	delay := 0.
+ 	self class webSearchPath do: [ :pathSpec |
+ 		| potentialUrl readPathSpec retry |
- 	self class webSearchPath do: [ :pathSpec | | potentialUrl readPathSpec  |
  		readPathSpec := pathSpec value readStream.
  		potentialUrl := (readPathSpec upTo: $*), self package, (readPathSpec upToEnd ifNil: [ '' ]).
+ 		[retry := false.
+ 		pageDataStream := self urlGet: potentialUrl.
+ 		self wasPbwikiSpeedWarning
+ 			ifTrue: [
+ 				retry := true.
+ 				delay := delay + 5. 
+ 				self logCR: 'PBWiki speed warning. Retrying in ', delay printString, ' seconds'.
+ 				(Delay forSeconds: delay) wait]
+ 			ifFalse: [ self hasPage ifTrue: [ pageDataStream reset. ^ potentialUrl ] ].
+ 		retry ] whileTrue
+ 	].
- 		[ retry := false. pageDataStream := self urlGet: potentialUrl ] doWhileTrue: [ 	
- 			self wasPbwikiSpeedWarning
- 				ifTrue: [ retry := true. delay := delay + 5. 
- 					self logCR: 'PBWiki speed warning. Retrying in ', delay printString, ' seconds'.
- 					(Delay forSeconds: delay) wait]
- 				ifFalse: [ self hasPage ifTrue: [ pageDataStream reset. ^ potentialUrl ] ].
- 			retry ]].
  	^nil
  !

Item was changed:
  ----- Method: InstallerUrl>>urlThing (in category 'url') -----
  urlThing
+  	| retry delay |
-  
- 	| retry delay |
  	
  	self logCR: 'retrieving ', self urlToDownload , ' ...'.
  	
  	delay := 0.
+ 	[retry := false.
+ 	pageDataStream := self urlGet: self urlToDownload.
+ 	self wasPbwikiSpeedWarning ifTrue: [
+ 		retry := true. delay := delay + 5.
+ 		self logCR: 'PBWiki speed warning. Retrying in ', delay printString, ' seconds'.
+ 		(Delay forSeconds: delay) wait ].
+ 	retry ] whileTrue.
- 	[ retry := false. pageDataStream := self urlGet: self urlToDownload ] 
- 		doWhileTrue: [  	
- 			self wasPbwikiSpeedWarning ifTrue: [retry := true. delay := delay + 5.
- 				self logCR: 'PBWiki speed warning. Retrying in ', delay printString, ' seconds'.
- 				(Delay forSeconds: delay) wait ].
- 											
- 			retry ].
  		
  	pageDataStream ifNil: [ self error: 'unable to contact host' ].
  	 
  	^ pageDataStream
  	!




More information about the Squeak-dev mailing list