[Pkg] Installer: Installer-Core-mtf.233.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Thu Oct 9 20:21:28 UTC 2008


A new version of Installer-Core was added to project Installer:
http://www.squeaksource.com/Installer/Installer-Core-mtf.233.mcz

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

Name: Installer-Core-mtf.233
Author: mtf
Time: 9 October 2008, 1:21:18 pm
UUID: 24206889-2ba2-41bb-8e4b-c87ea316df23
Ancestors: Installer-Core-kph.232

Split up Installer into 14 classes

Monticello's move-unaware diffing makes reviewing this change virtually impossible. Here are the side-by-side comparable file-outs I used to manage this change:
http://lists.squeakfoundation.org/pipermail/release/2008-October/000035.html

=============== Diff against Installer-Core-kph.232 ===============

Item was changed:
+ ----- Method: Installer class>>sophie (in category 'monticello') -----
- ----- Method: Installer class>>sophie (in category 'instanciation-abbreviated') -----
  sophie
  
  	^ self monticello http: 'source.sophieproject.org'
  	
  !

Item was added:
+ ----- Method: InstallerWeb class>>install: (in category 'compatability') -----
+ install: webPageName
+ "This keeps the syntax Installer web install: working"
+ 	^ self new install: webPageName!

Item was added:
+ ----- Method: InstallerCruft>>reportFor:page:on: (in category 'action report') -----
+ reportFor: theLine page: thePage on: report 
+  	
+ 	[ thePage atEnd ] whileFalse: [ 
+ 		| line |
+ 		line := thePage nextLine.
+ 		self actionMatch: line reportOn: report ifNoMatch: [ report nextPutAll: line; cr. ]].!

Item was changed:
+ ----- Method: Installer>>withAnswersDo: (in category 'auto answering') -----
- ----- Method: Installer>>withAnswersDo: (in category 'monticello') -----
  withAnswersDo: aBlock
  
  	(aBlock respondsTo: #valueSuppressingMessages:supplyingAnswers: )
  		ifTrue: [aBlock valueSuppressingMessages: self messagesToSuppress supplyingAnswers: self answers.]
  		ifFalse: [ aBlock value ]
  !

Item was added:
+ ----- Method: Installer>>basicInstall (in category 'basic interface') -----
+ basicInstall!

Item was changed:
+ ----- Method: Installer class>>squeakmap (in category 'squeakmap') -----
- ----- Method: Installer class>>squeakmap (in category 'instanciation') -----
  squeakmap
  
+ 	^ InstallerSqueakMap new sm: true; yourself!
- 	^self new sm: true; yourself!

Item was added:
+ ----- Method: InstallerUniverse>>classUVersion (in category 'class references') -----
+ classUVersion
+ 
+ 	^Smalltalk at: #UVersion  ifAbsent: [ self error: 'Universes code not present' ]!

Item was added:
+ InstallerWebBased subclass: #InstallerMantis
+ 	instanceVariableNames: 'ma bug desc date'
+ 	classVariableNames: 'Fixes'
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was added:
+ ----- Method: InstallerMantis>>setBug: (in category 'mantis') -----
+ setBug: stringOrNumber
+ 
+ 	| str |
+ 	self logCR: stringOrNumber.
+  	stringOrNumber isInteger ifTrue: [ bug := stringOrNumber. desc := ''. ^self ].
+  	bug := stringOrNumber asInteger.
+ 	str := str printString. 
+ 	desc := stringOrNumber copyFrom: (str size + 1) to: (stringOrNumber size) 
+ 
+ !

Item was added:
+ ----- Method: InstallerUpdateStream>>loadUpdatesFromDiskToUpdateNumber:stopIfGap: (in category 'updates') -----
+ loadUpdatesFromDiskToUpdateNumber: lastUpdateNumber stopIfGap: stopIfGapFlag 
+ 	"To use this mechanism, be sure all updates you want to have considered 
+ 	are in a folder named 'updates' which resides in the same directory as  
+ 	your image. Having done that, simply evaluate:  
+ 	 
+ 	Installer new loadUpdatesFromDiskToUpdateNumber: 100020 stopIfGap: false  
+ 	 
+ 	and all numbered updates <= lastUpdateNumber not yet in the image will 
+ 	be loaded in numerical order."
+ 	
+ 	"apparently does not use the updatelist too bad!! and to rewrite - sd 7 March 2008"
+ 	| previousHighest currentUpdateNumber done fileNames aMessage updateDirectory loaded |
+ 	updateDirectory := self updateDirectoryOrNil.
+ 	updateDirectory ifNil: [^ self].
+ 	previousHighest := SystemVersion current highestUpdate.
+ 	currentUpdateNumber := previousHighest.
+ 	done := false.
+ 	loaded := 0.
+ 	[done]
+ 		whileFalse: [currentUpdateNumber := currentUpdateNumber + 1.
+ 			currentUpdateNumber > lastUpdateNumber
+ 				ifTrue: [done := true]
+ 				ifFalse: [fileNames := updateDirectory fileNamesMatching: currentUpdateNumber printString , '*'.
+ 					fileNames size > 1
+ 						ifTrue: [^ self inform: 'ambiguity -- two files both start with ' , currentUpdateNumber printString , '
+ (at this point it is probably best to remedy
+ the situation on disk, then try again.)'].
+ 					fileNames size == 0
+ 						ifTrue: [Transcript cr; show: 'gap in updates from disk for update number '; print: currentUpdateNumber; show: ' found...'.
+ 							done := stopIfGapFlag]
+ 						ifFalse: [ChangeSet
+ 								newChangesFromStream: (updateDirectory readOnlyFileNamed: fileNames first)
+ 								named: fileNames first.
+ 							SystemVersion current registerUpdate: currentUpdateNumber.
+ 							loaded := loaded + 1]]].
+ 	aMessage := loaded = 0
+ 				ifTrue: ['No new updates found.']
+ 				ifFalse: [loaded printString , ' update(s) loaded.'].
+ 	self inform: aMessage , '
+ Highest numbered update is now ' , (currentUpdateNumber - 1) printString , '.'!

Item was added:
+ ----- Method: InstallerSake class>>sake (in category 'accessing') -----
+ sake
+ 
+ 	^ Sake ifNil: [ self classPackages current ]!

Item was added:
+ ----- Method: InstallerMantis>>justFixBug: (in category 'public interface') -----
+ justFixBug: aBugNo
+ 
+ 	^self class skipLoadingTests: true during: [ self fixBug: aBugNo date: nil ]!

Item was changed:
  ----- Method: Installer>>packagesMatching: (in category 'searching') -----
  packagesMatching: aMatch
- 
- 	self sm ifTrue: [ ^ (self availablePackages select: [ :p | aMatch match: p name ]) 
- 								collect: [ :p | self copy package: p name; yourself ] ].
- 	self mc ifNotNil: [ ^ (self availablePackages select: [ :p | ( aMatch , '.mcz' ) match: p ]) 								collect: [ :p | self copy package: p ; yourself ] ].
- 	self wsm ifNotNil: [ ^ (self availablePackages select: [ :p | ( aMatch) match: p ]) 
- 								collect: [ :p | self copy package: p ; yourself ] ].
  	^'search type not supported'!

Item was added:
+ ----- Method: InstallerCruft class>>classes (in category 'accessing system') -----
+ classes
+ 
+ 	^ Smalltalk!

Item was added:
+ InstallerInternetBased subclass: #InstallerWebBased
+ 	instanceVariableNames: 'markers'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was added:
+ ----- Method: InstallerInternetBased>>httpGet: (in category 'utils') -----
+ httpGet: aUrl
+ 
+ 	| page |
+ 	page := self classHTTPSocket httpGet: aUrl accept: 'application/octet-stream'.  
+  
+ 	(page respondsTo: #reset)  ifFalse: [ self error: 'unable to contact web site' ].
+ 	^ page
+ 	!

Item was changed:
+ ----- Method: Installer class>>websqueakmap (in category 'websqueakmap') -----
- ----- Method: Installer class>>websqueakmap (in category 'instanciation') -----
  websqueakmap
  
+ 	^ InstallerWebSqueakMap new wsm: 'http://map.squeak.org'; yourself!
- 	^self new wsm: 'http://map.squeak.org'; yourself!

Item was changed:
+ ----- Method: Installer class>>saltypickle (in category 'monticello') -----
- ----- Method: Installer class>>saltypickle (in category 'instanciation-abbreviated') -----
  saltypickle
  
  	^ self monticello http: 'squeak.saltypickle.com'!

Item was added:
+ ----- Method: InstallerMantis>>fixBug:date: (in category 'public interface') -----
+ fixBug: aBugNo date: aDate
+ 
+ 	self setBug: aBugNo.
+  	self install: self maUrl from: self maScript.
+ 	self maCheckDateAgainst: aDate.
+ 	
+ 	
+ 	
+ !

Item was added:
+ ----- Method: Installer>>basicBrowse (in category 'basic interface') -----
+ basicBrowse!

Item was added:
+ ----- Method: InstallerCruft>>classMCMczReader (in category 'class references') -----
+ classMCMczReader
+ 
+ 	^Smalltalk at: #MCMczReader ifAbsent: [ nil ]
+ 	!

Item was changed:
+ ----- Method: Installer>>view: (in category 'public interface') -----
- ----- Method: Installer>>view: (in category 'accessing') -----
  view: packageNameCollectionOrDetectBlock
  
  	self package: packageNameCollectionOrDetectBlock.
  	self view!

Item was added:
+ ----- Method: InstallerWeb>>basicBrowse (in category 'basic interface') -----
+ basicBrowse
+  
+  	 self webThing size > 0 
+ 		ifTrue: [ self browse: url from: pageDataStream ]
+ 		ifFalse: [ self logCR: 'NO DATA ',url,' was empty' ].
+ 	 !

Item was added:
+ ----- Method: InstallerMantis>>ensureFix: (in category 'public interface') -----
+ ensureFix: aBugNo
+ 
+ 	| fixesAppliedNumbers |
+ 	self setBug: aBugNo.
+ 	fixesAppliedNumbers := self class fixesApplied collect: [ :fixDesc | fixDesc asInteger ].
+ 	(fixesAppliedNumbers includes: bug) ifFalse: [ self fixBug: aBugNo ]!

Item was added:
+ ----- Method: InstallerMantis>>date: (in category 'accessing') -----
+ date: anObject
+ 
+ 	date := anObject asDate!

Item was added:
+ ----- Method: InstallerSqueakMap>>basicAvailablePackages (in category 'basic interface') -----
+ basicAvailablePackages
+ 	
+ 	^self classSMSqueakMap default packagesByName!

Item was added:
+ ----- Method: InstallerFile>>file (in category 'accessing') -----
+ file
+ 
+ 	^ afile!

Item was added:
+ ----- Method: InstallerInternetBased>>urlGet: (in category 'url') -----
+ urlGet: aUrl
+ 
+ 	| page |
+ 	page := HTTPSocket httpGet: aUrl accept: 'application/octet-stream'.  
+ 	(page respondsTo: #reset)  ifFalse: [ ^ nil ].
+ 	(self isHtmlStream: page) ifTrue: [ page := self extractFromHtml: page option: nil ].
+ 	^ page reset
+ 	!

Item was added:
+ ----- Method: InstallerWebSqueakMap>>wsm: (in category 'websqueakmap') -----
+ wsm: aUrl
+  
+ 	wsm := aUrl last = $/ ifTrue: [ aUrl ] ifFalse: [ aUrl, '/' ]!

Item was added:
+ ----- Method: InstallerMonticello>>mc: (in category 'accessing') -----
+ mc: aUrl
+ 
+ 	mc := aUrl last = $/ ifTrue: [ aUrl ] ifFalse: [ aUrl, '/' ]!

Item was changed:
+ ----- Method: Installer class>>squeakfoundation (in category 'monticello') -----
- ----- Method: Installer class>>squeakfoundation (in category 'instanciation-abbreviated') -----
  squeakfoundation
  
  	^ self monticello http: 'source.squeakfoundation.org'!

Item was added:
+ ----- Method: InstallerInternetBased class>>entities (in category 'accessing') -----
+ entities
+ 
+ 	^ Entities ifNil: [ Entities := 
+ 				"enough entities to be going on with"
+   				Dictionary new.
+ 				Entities at: 'lt' put: '<';
+ 				at: 'gt' put: '>';
+ 				at: 'amp' put: '&';
+ 				at: 'star' put: '*';
+ 				at: 'quot' put: '"';
+ 				at: 'nbsp' put: ' ';
+  			yourself
+ ]
+ 
+  !

Item was added:
+ ----- Method: InstallerMonticello class>>classMCCacheRepository (in category 'class references') -----
+ classMCCacheRepository
+ 
+ 	^Smalltalk at: #MCCacheRepository ifAbsent: [ self error: 'Monticello not present' ]
+ 	!

Item was changed:
+ ----- Method: Installer class>>validationBlock (in category 'accessing') -----
- ----- Method: Installer class>>validationBlock (in category 'instanciation-abbreviated') -----
  validationBlock
  
  	^ ValidationBlock!

Item was added:
+ ----- Method: InstallerMonticello class>>classMCDirectoryRepository (in category 'class references') -----
+ classMCDirectoryRepository
+ 
+ 	^Smalltalk at: #MCDirectoryRepository ifAbsent: [ self error: 'Monticello not present' ]
+ 	!

Item was added:
+ ----- Method: InstallerSqueakMap>>basicVersions (in category 'basic interface') -----
+ basicVersions
+  
+ 	^ (self smReleasesForPackage: self package) 
+ 			collect: [ :v | self copy package: (v package name,'(',v version,')'); yourself. ] 
+ 
+  !

Item was added:
+ ----- Method: InstallerSqueakMap>>basicView (in category 'basic interface') -----
+ basicView
+ 
+ 	self smThing explore!

Item was added:
+ ----- Method: InstallerWeb class>>initialize (in category 'instanciation') -----
+ initialize
+ 	
+ 	WebSearchPath := OrderedCollection 
+ 		with:  [ 'http://installer.pbwiki.com/*-', (Smalltalk version copy replaceAll: $. with: $:)  ,'-', Utilities authorInitialsPerSe  ,'?raw=bare' ]
+ 		with:  [ 'http://installer.pbwiki.com/*-', (Smalltalk version copy replaceAll: $. with: $:), '?raw=bare' ]
+ 		with:  [ 'http://installer.pbwiki.com/*-', (SystemVersion current majorMinorVersion replaceAll: $. with: $:)  ,'?raw=bare' ]
+ 		with:  'http://installer.pbwiki.com/*?raw=bare'
+ 	 
+  !

Item was added:
+ ----- Method: InstallerMonticello class>>classMCSmtpRepository (in category 'class references') -----
+ classMCSmtpRepository
+ 
+ 	^Smalltalk at: #MCSmtpRepository ifAbsent: [ self error: 'Monticello not present' ]
+ 	!

Item was changed:
  ----- Method: Installer>>browse (in category 'public interface') -----
  browse
+ 	self logErrorDuring: [self basicBrowse]!
- 
- 	self logErrorDuring: [
- 		self file ifNotNil: [ ^ self fileBrowse ].
- 		self mc ifNotNil: [ ^self mcBrowse ].
- 		self wsm ifNotNil: [ ^self wsmBrowse ].
- 		self sm ifTrue: [ ^self smBrowse ].
- 		self url ifNotNil: [ ^self urlBrowse ].
- 		self package ifNotNil: [ ^self webBrowse ].
- 	] !

Item was added:
+ ----- Method: InstallerWeb>>webThing (in category 'web install') -----
+ webThing
+  
+  	url := self webFindUrlToDownload.
+ 	url ifNil: [ self logCR: 'page ', self package, ' not found on path' ]
+ 		ifNotNil: [ self logCR: 'found ',  url, ' ...'.   ].
+ 	^ pageDataStream!

Item was added:
+ ----- Method: InstallerMantis>>maCheckDateAgainst: (in category 'utils') -----
+ maCheckDateAgainst: okDate
+ 
+ 	(okDate notNil and: [date < okDate asDate ]) 
+ 		ifTrue: [ self notify: 'bug ', self bug asString, ' updated on ', date printString ].
+  !

Item was changed:
+ ----- Method: Installer>>availablePackages (in category 'public interface') -----
- ----- Method: Installer>>availablePackages (in category 'accessing') -----
  availablePackages
  	
+ 	^ self basicAvailablePackages!
- 	self sm ifTrue: [ ^self smPackages ].
- 	self mc ifNotNil: [ ^self mc allFileNames ].
- 	self wsm ifNotNil: [ ^self wsmPackagesByName keys ].!

Item was changed:
+ ----- Method: Installer class>>installUrl: (in category 'url') -----
- ----- Method: Installer class>>installUrl: (in category 'instanciation') -----
  installUrl: urlString
  
+ 	^ self url url: urlString; install.
- 	^ self web url: urlString; install.
  !

Item was added:
+ ----- Method: InstallerInternetBased>>isHtmlStream: (in category 'url') -----
+ isHtmlStream: page
+ 	"matches  '<!!DOCTYPE HTML', and <html>' "
+ 	
+ 	| first |	
+ 	first := (page next: 14) asUppercase.
+ 	^ (first = '<!!DOCTYPE HTML') | (first beginsWith: '<HTML>')
+ 	
+ !

Item was added:
+ ----- Method: InstallerMantis>>maReadNotes: (in category 'mantis') -----
+ maReadNotes: page 
+ 
+ 	 |  notes note  |
+  
+ 	notes := OrderedCollection new.
+ 
+ 	[ page upToAll: 'tr class="bugnote"'; upTo: $>.
+ 	  page atEnd ]
+ 		
+ 	whileFalse: [ 
+ 		note := (self removeHtmlMarkupFrom: (page upToAll: '</tr>') readStream) contents.
+ 		note := note withBlanksCondensed.
+ 		"note replaceAll: Character cr with: $ ."
+ 		note replaceAll: Character lf with: Character cr.
+ 		notes add: note  
+ 	].
+ 	
+ 	^notes!

Item was added:
+ ----- Method: InstallerSake class>>classPackages (in category 'accessing system') -----
+ classPackages
+ 
+ 	^Smalltalk at: #Packages  ifAbsent: [ self error: 'Sake Packages code not present' ]!

Item was added:
+ ----- Method: Installer>>basicAvailablePackages (in category 'basic interface') -----
+ basicAvailablePackages!

Item was added:
+ ----- Method: InstallerMonticello class>>unloadCleanUp (in category 'unload') -----
+ unloadCleanUp
+  
+ 	SystemOrganization removeEmptyCategories.
+ 
+ 	"Until Mantis 5718 is addressed"
+  	Smalltalk at: #PackagePaneBrowser ifPresent: [ :ppbClass | ppbClass allInstancesDo: [ :ppb | ppb updatePackages ]  ].
+  	Smalltalk at: #Browser ifPresent: [ :bClass | bClass allInstancesDo: [ :b | b updateSystemCategories ] ].
+ 	MCFileBasedRepository freeSomeSpace.
+ 	SmalltalkImage current fixObsoleteReferences.!

Item was added:
+ ----- Method: InstallerSake class>>sake: (in category 'accessing') -----
+ sake: aClass
+ 
+ 	Sake := aClass!

Item was added:
+ ----- Method: InstallerSqueakMap>>basicInstall (in category 'basic interface') -----
+ basicInstall 
+ 
+ 	self log: ' installing '. 
+ 	self withAnswersDo: [ self smThing install ].
+ 	self log: ' done'.
+ !

Item was added:
+ Installer subclass: #InstallerSake
+ 	instanceVariableNames: 'sake'
+ 	classVariableNames: 'Sake'
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was added:
+ ----- 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 := pair first.  
+ 		fileNames := pair last.
+ 		strm nextPut: $#; nextPutAll: releaseTag; cr.
+ 		fileNames do: [:fileName | strm nextPutAll: fileName; cr]].
+ 	strm close!

Item was added:
+ ----- Method: InstallerWebSqueakMap>>wsm (in category 'websqueakmap') -----
+ wsm
+ 	
+ 	^ wsm!

Item was added:
+ ----- Method: InstallerInternetBased>>replaceEntitiesIn: (in category 'url') -----
+ replaceEntitiesIn: in
+ 
+ 	| out |
+ 	out := ReadWriteStream on: (String new: 100).
+ 	[ in atEnd ] whileFalse: [ 
+ 		out nextPutAll: ((in upTo: $&) replaceAll: Character lf with: Character cr).
+ 		in atEnd ifFalse: [ out nextPutAll: (self class entities at: (in upTo: $;) ifAbsent: '?') ].	
+ 	].
+ 
+ 	^out reset!

Item was added:
+ ----- Method: InstallerCruft>>viewUrl (in category 'utils') -----
+ viewUrl
+ 
+ 	^Workspace new contents: (self urlGet contents); openLabel: self urlToDownload.
+ !

Item was added:
+ ----- Method: InstallerMantis>>maUrlFor: (in category 'mantis') -----
+ maUrlFor: maBugNo
+  
+ 	^ url := self ma, 'view.php?id=', maBugNo asString 
+  !

Item was changed:
+ ----- Method: Installer>>rememberAs: (in category 'custom names') -----
- ----- Method: Installer>>rememberAs: (in category 'accessing') -----
  rememberAs: symbol
  
  	self class remembered at: symbol asSymbol put: self!

Item was added:
+ ----- Method: InstallerCruft class>>mczInstall: (in category 'documentation') -----
+ mczInstall: urlOrFile
+ 
+ 	^ self new mczInstall: urlOrFile
+ !

Item was changed:
+ ----- Method: Installer class>>installSilentlyUrl: (in category 'url') -----
- ----- Method: Installer class>>installSilentlyUrl: (in category 'instanciation') -----
  installSilentlyUrl: urlString
  
+ 	^ SystemChangeNotifier uniqueInstance doSilently: [ self url url: urlString; install ].
- 	^ SystemChangeNotifier uniqueInstance doSilently: [ self web url: urlString; install ].
  !

Item was added:
+ ----- Method: InstallerMonticello class>>classMCFtpRepository (in category 'class references') -----
+ classMCFtpRepository
+ 
+ 	^Smalltalk at: #MCFtpRepository ifAbsent: [ self error: 'Monticello not present' ]
+ 	!

Item was added:
+ ----- Method: InstallerMonticello class>>cache (in category 'instance creation') -----
+ cache
+     | mc |
+ 	^ self new	
+ 		mc: (mc := self classMCCacheRepository default)
+ 		root: mc directory localName
+  !

Item was added:
+ ----- Method: InstallerSqueakMap>>packagesMatching: (in category 'searching') -----
+ packagesMatching: aMatch
+ 	^ (self availablePackages
+ 		select: [ :p | aMatch match: p name ]) 
+ 		collect: [ :p | self copy package: p name; yourself ]!

Item was added:
+ ----- Method: InstallerUrl>>basicView (in category 'basic interface') -----
+ basicView
+  	 "(Installer debug url: 'http://installer.pbwiki.com/f/Installer.st') view.".
+ 	
+ 	self view: self urlToDownload from: self urlThing.
+ 	
+ 	
+ !

Item was changed:
+ ----- Method: Installer class>>path: (in category 'web') -----
- ----- Method: Installer class>>path: (in category 'instanciation') -----
  path: aString
  	"convenience abbreviation"
  	
  	self webSearchPathFrom: aString!

Item was added:
+ ----- Method: InstallerMonticello>>project (in category 'accessing') -----
+ project
+ 
+ 	^ project!

Item was added:
+ ----- Method: InstallerMonticello class>>goods:port: (in category 'instance creation') -----
+ goods: host port: aport
+ 	
+ 	^ self new mc: ((self classMCGOODSRepository new) host: host port: aport; yourself)
+  !

Item was added:
+ ----- Method: InstallerMantis>>bugFiles: (in category 'public interface') -----
+ bugFiles: aBugNo
+  	"provide a list of files associated with the bug in id order"
+ 	"
+ 	Installer mantis bugFiles: 6660.
+ 	"
+ 	self setBug: aBugNo.
+ 	^ (self maFiles associations asSortedCollection: [ :a :b | a value asInteger < b value asInteger ]) 
+ 				collect: [ :a | a key ]!

Item was changed:
+ ----- Method: Installer>>installQuietly (in category 'public interface') -----
- ----- Method: Installer>>installQuietly (in category 'accessing') -----
  installQuietly 
  
    	[ self install ] on: Warning do: [ :ex | ex resume: true ].!

Item was added:
+ ----- Method: InstallerUniverse>>universe (in category 'universes') -----
+ universe
+ 
+ 	^ universe!

Item was changed:
+ ----- Method: Installer class>>sm (in category 'squeakmap') -----
- ----- Method: Installer class>>sm (in category 'instanciation-abbreviated') -----
  sm
  
  	^ self squeakmap!

Item was changed:
+ ----- Method: Installer class>>universe (in category 'universe') -----
- ----- Method: Installer class>>universe (in category 'instanciation') -----
  universe
  
+ 	^ InstallerUniverse new universe: (self classUGlobalInstaller universe: self classUUniverse systemUniverse)!
- 	^ self new universe: (self classUGlobalInstaller universe: self classUUniverse systemUniverse)!

Item was added:
+ ----- Method: InstallerUpdateStream>>loadUpdatesFromDisk (in category 'updates') -----
+ loadUpdatesFromDisk
+ 	
+ 	| updateDirectory updateNumbers |
+ 	updateDirectory := self updateDirectoryOrNil.
+ 	updateDirectory ifNil: [^ self].
+ 	updateNumbers := updateDirectory fileNames
+ 						collect: [:fn | fn initialIntegerOrNil]
+ 						thenSelect: [:fn | fn notNil].
+ 	
+ 	self loadUpdatesFromDiskToUpdateNumber: updateNumbers max
+ 		stopIfGap: false
+ 		
+ 	!

Item was added:
+ ----- Method: InstallerSake>>sake: (in category 'websqueakmap') -----
+ sake: aSakePackagesClass
+ 
+ 	sake := aSakePackagesClass!

Item was added:
+ ----- Method: InstallerMonticello>>basicAvailablePackages (in category 'basic interface') -----
+ basicAvailablePackages
+ 	^ self mc allFileNames!

Item was changed:
+ ----- Method: Installer>>versions (in category 'public interface') -----
- ----- Method: Installer>>versions (in category 'accessing') -----
  versions
  	
+ 	^ self basicVersions!
- 	self sm ifTrue: [ ^self smVersions ].
- 	self mc ifNotNil: [ ^self mcVersions ].
- 	self wsm ifNotNil: [ ^self wsmVersions ].!

Item was added:
+ ----- Method: InstallerMantis class>>host: (in category 'instance creation') -----
+ host: host
+ 
+ 	^self new	ma: host; 
+ 			markers: '&quot;fix begin&quot;...&quot;fix test&quot;...&quot;fix end&quot;'; 
+ 			yourself.
+ !

Item was added:
+ ----- Method: InstallerFile>>file: (in category 'accessing') -----
+ file: f
+ 
+   afile := f!

Item was added:
+ ----- Method: InstallerWebSqueakMap>>basicVersions (in category 'basic interface') -----
+ basicVersions
+ 
+ 	| pkgAndVersion packageId packageName packageVersion versions |
+ 	pkgAndVersion := self packageAndVersionFrom: self package .
+ 	packageName := pkgAndVersion first.
+ 	packageVersion := pkgAndVersion last.
+ 	packageVersion isEmpty ifTrue: [ packageVersion := #latest ].
+ 	packageId := self availablePackages at: packageName.
+ 	versions := (self wsmReleasesFor: packageId) keys.
+ 	versions remove: #latest.
+ 	^ versions collect: [ :version | self copy package: (packageName,'(', version ,')'); yourself ]. !

Item was added:
+ ----- Method: InstallerSqueakMap>>basicBrowse (in category 'basic interface') -----
+ basicBrowse
+ 
+ 	self smThing explore!

Item was added:
+ ----- Method: InstallerMantis>>bug:fix: (in category 'public interface') -----
+ bug: aBugNo fix: aFileName
+ 
+ 	^ self bug: aBugNo fix: aFileName date: nil!

Item was added:
+ ----- Method: InstallerUrl>>basicInstall (in category 'basic interface') -----
+ basicInstall 
+  	 
+ 	self install: self urlToDownload from: self urlThing.
+ 	^ pageDataStream 
+ !

Item was added:
+ ----- Method: InstallerUrl>>urlToDownload (in category 'url') -----
+ urlToDownload
+ 
+ 	^ (self url, (self package ifNil: [ '' ])) asUrl asString.
+ 	
+  !

Item was changed:
+ ----- Method: Installer>>printOn: (in category 'printing') -----
- ----- Method: Installer>>printOn: (in category 'accessing') -----
  printOn: s
+ 
+ 	"I don't feel like fixing this yet"
+ 	true ifTrue: [^ super printOn: s].
   
  	s nextPutAll: '(Installer'.
  
  	self sm ifTrue: [ s nextPutAll: ' squeakmap' ].
  	self ma ifNotNil: [ s nextPutAll: ' mantis' ].
  	self wsm ifNotNil: [ s nextPutAll: ' websqueakmap' ].
  	self url ifNotNil: [ s nextPutAll: ' url:''', self url,'''' ].
  	self mc ifNotNil: [ s nextPutAll: ' repository:''', mc description,'''' ].
  
  	s nextPut: $).
  
  	self project ifNotNil: [ s nextPutAll: ' project:'; nextPutAll: '''', self project, ''''.
  						self package ifNotNil: [ s nextPutAll: '; '] ].
  					
  	self package ifNotNil: [ s nextPutAll: ' package:'; nextPutAll: '''', self package asString, '''' ].
  					
  	s nextPut: $..!

Item was added:
+ ----- Method: InstallerUrl>>urlThing (in category 'url') -----
+ urlThing
+  
+ 	self logCR: 'retrieving ', self urlToDownload , ' ...'.
+ 	(pageDataStream := self urlGet: self urlToDownload) 
+ 		ifNil: [ self error: 'unable to contact host' ].
+ 	 
+ 	^ pageDataStream
+ 	!

Item was added:
+ ----- Method: InstallerCruft>>user: (in category 'accessing') -----
+ user: anObject
+ 
+ 	user := anObject!

Item was added:
+ ----- Method: InstallerMonticello>>basicVersions (in category 'basic interface') -----
+ basicVersions
+ 
+ 	^ (self availablePackages select: [ :p | ( self package,'-*.mcz' ) match: p ]) collect: [ :p | self copy package: p  ; yourself ].
+  !

Item was added:
+ Installer subclass: #InstallerFile
+ 	instanceVariableNames: 'afile'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was changed:
+ ----- Method: Installer>>open (in category 'public interface') -----
+ open!
- ----- Method: Installer>>open (in category 'actions') -----
- open
- 	
- 	self sm ifTrue: [ self classSMLoader open ].
- 	self mc ifNotNil: [ self mc morphicOpen: nil ].!

Item was added:
+ ----- Method: InstallerMantis>>viewBug: (in category 'public interface') -----
+ viewBug: aBugNo
+ 
+ 	^Workspace new contents: (self bug: aBugNo); openLabel: ('Mantis ', aBugNo printString).
+ !

Item was changed:
+ ----- Method: Installer class>>impara (in category 'monticello') -----
- ----- Method: Installer class>>impara (in category 'instanciation-abbreviated') -----
  impara
  
  	^ self monticello http: 'source.impara.de'!

Item was added:
+ ----- Method: InstallerMantis>>bug:fix:date: (in category 'public interface') -----
+ bug: aBugNo fix: aFileName date: aDate
+  
+ 	| fixed |
+ 	self setBug: aBugNo.
+ 	self ditchOldChangeSetFor: aFileName.
+ 	self install: aFileName from: (self maThing: aFileName date: aDate).
+ 
+ 	fixed := self class fixesApplied.
+ 	(fixed isEmpty or: [ fixed last ~= aBugNo]) ifTrue: [ fixed add: aBugNo ].
+ 		
+ 	^ date!

Item was changed:
+ ----- Method: Installer class>>websqueakmap: (in category 'websqueakmap') -----
- ----- Method: Installer class>>websqueakmap: (in category 'instanciation') -----
  websqueakmap: host
  
+ 	^ InstallerWebSqueakMap new wsm: host; yourself!
- 	^self new wsm: host; yourself!

Item was added:
+ ----- Method: InstallerMonticello>>basicView (in category 'basic interface') -----
+ basicView
+ 	 "Installer ss project: 'Installer'; view: 'Installer-Core'. "
+ 	| it |
+ 	it := self mcThing. 
+ 	(it respondsTo: #open) ifTrue: [ ^ it open ].
+ 
+ 	(MCSnapshotBrowser forSnapshot: it)
+ 		showLabelled: 'Snapshot of ', self package!

Item was added:
+ ----- Method: InstallerMantis>>maUrl (in category 'mantis') -----
+ maUrl
+  
+ 	^ url := self ma, 'view.php?id=', bug asString
+  !

Item was added:
+ ----- Method: InstallerMonticello>>mcUrl (in category 'monticello') -----
+ mcUrl
+ 
+ 	^ self mc, (self project ifNil: [''])!

Item was added:
+ ----- Method: InstallerWebSqueakMap>>basicInstall (in category 'basic interface') -----
+ basicInstall
+ 	
+ 	| it |
+ 	it := self wsmThing.
+ 	self install: it from: it asUrl retrieveContents contentStream.
+ 
+ 	!

Item was changed:
+ ----- Method: Installer class>>webSearchPathFrom: (in category 'web') -----
- ----- Method: Installer class>>webSearchPathFrom: (in category 'accessing') -----
  webSearchPathFrom: string
  
  	| reader wsp path |
  	reader := string readStream.
  	wsp := self webSearchPath.
  	[ reader atEnd ] whileFalse: [ 
  		path := reader upTo: $;.
  		(wsp includes: wsp) ifFalse: [ wsp addFirst: path ]].
  
  	 !

Item was added:
+ ----- Method: InstallerMonticello>>mc (in category 'accessing') -----
+ mc
+ 
+ 	^ mc!

Item was added:
+ ----- Method: InstallerCruft class>>do: (in category 'launcher support') -----
+ do: webPageName
+ 
+ 	| rs |
+ 	self webSearchPath isEmpty ifTrue: [ ^self error: 'search path not set' ].
+ 	rs := webPageName readStream.
+ 	[ rs atEnd ] whileFalse: [ self install: (rs upTo: $;) ].
+ !

Item was added:
+ ----- Method: InstallerWeb class>>searchPath (in category 'accessing') -----
+ searchPath
+ 	"a search path item, has the following format. prefix*suffix"
+ 
+ 	^ WebSearchPath ifNil: [ WebSearchPath := OrderedCollection new ].!

Item was added:
+ ----- Method: InstallerCruft>>urlAction:reportOn: (in category 'action report') -----
+ urlAction: line reportOn: report 
+  
+ 	url :=  line readStream upTo: $' ; upTo: $'.
+   	
+ 	self reportSection: line on: report.
+ 
+ 	(pageDataStream := self urlGet: self urlToDownload) 
+ 		ifNil: [ self error: 'unable to contact host' ].
+ 	 	
+ 	self reportFor: line page: pageDataStream on: report !

Item was added:
+ ----- Method: InstallerInternetBased>>classHTTPSocket (in category 'class references') -----
+ classHTTPSocket
+ 
+ 	^Smalltalk at: #HTTPSocket ifAbsent: [ self error: 'Network package not present' ]!

Item was added:
+ ----- Method: InstallerMonticello>>basicInstall (in category 'basic interface') -----
+ basicInstall
+ 	 
+ 	self withAnswersDo: [ self mcThing load ].
+ 	self log: 'loaded'.
+ !

Item was added:
+ ----- Method: InstallerMonticello class>>unload: (in category 'unload') -----
+ unload: match 
+ 
+ 	(MCWorkingCopy allManagers select: [ :wc | match match: (wc package name) ])
+ 		 do: [ :wc | 
+  			 	self logCR: 'Unloading ', wc package asString.
+  				wc unload.].
+ 	self unloadCleanUp!

Item was added:
+ ----- Method: InstallerSqueakMap>>classSMSqueakMap (in category 'class references') -----
+ classSMSqueakMap
+ 
+ 	^Smalltalk at: #SMSqueakMap  ifAbsent: [ self error: 'SqueakMap not present' ]!

Item was added:
+ ----- Method: InstallerWebBased>>markersTest (in category 'url') -----
+ markersTest
+ 		 	 
+ 	^ self markers readStream upToAll: '...'; upToAll: '...'!

Item was added:
+ ----- Method: InstallerInternetBased>>urlGet (in category 'url') -----
+ urlGet
+ 
+ 	^ self urlGet: self urlToDownload!

Item was changed:
+ ----- Method: Installer class>>wsm (in category 'websqueakmap') -----
- ----- Method: Installer class>>wsm (in category 'instanciation-abbreviated') -----
  wsm
  
  	^ self websqueakmap!

Item was added:
+ ----- Method: InstallerUrl>>basicBrowse (in category 'basic interface') -----
+ basicBrowse
+  	"(Installer debug url: 'http://installer.pbwiki.com/f/Installer.st') browse.".
+ 	
+ 	self browse: self urlToDownload from: self urlThing.
+ 	
+ 	
+ !

Item was added:
+ ----- Method: InstallerCruft>>reportSection:on: (in category 'action report') -----
+ reportSection: line on: report
+ 	
+ 	report isEmpty ifFalse: [ report cr ].
+ 	report nextPutAll: '">>>> ' ; nextPutAll: (line copyWithout: $"); nextPut: $"; cr.
+ 
+ 	!

Item was added:
+ ----- Method: InstallerSake>>sake (in category 'websqueakmap') -----
+ sake 
+ 
+ 	^ sake  !

Item was added:
+ ----- Method: InstallerWebBased>>markers (in category 'accessing') -----
+ markers
+ 
+ 	^ markers ifNil: [ '<code st>..."test ...</code st>' ]!

Item was changed:
+ ----- Method: Installer class>>ss (in category 'monticello') -----
- ----- Method: Installer class>>ss (in category 'instanciation-abbreviated') -----
  ss
  
  	^ self squeaksource
   !

Item was added:
+ ----- Method: InstallerCruft class>>history (in category 'documentation') -----
+ history
+ 
+ "
+ 7 Jan 2007  
+ !!Installer fixBug: <aBugNo>
+ 
+ aBugNo can now be a number or a string, beginning with a number. 
+ This allows the mantis bug report summary to be used verbatim.
+ It also provides more infomarion for Installer to support self documentation.
+ 
+ !!Install fix if not already installed
+  Installer ensureFix: <aBugNoOrString>
+  Installer ensureFixes: #(1 2 3 4)
+ 
+ Installer now keeps a list of fix <aBugNoOrString> that have been installed up to this point.
+ #ensureFix: will only install the fix if it has not already been loaded.
+ note that only the bugNumber not the description is significant in the check.
+ 
+ 8 Jan 2007
+ !!Installer view: <webPageNameOrUrl>
+ 
+ Provided that web page based scripts follow some simple rules, installer can collate the scripts from 
+ web pages into a single workspace where you can manually 'doit' portions as you wish.
+ 
+ The report generation is not very clever, it only matches on:
+  'Installer install:' ,  'Installer installUrl:', and 'Installer mantis fixBug:'
+  note these lines must be properly completed with an ending $. (period).
+ 
+ also invoked by commandline option VIEW=<webPageNameOrUrl>
+ 
+ 10 Jan 2007
+ !!Now matches simpler html
+ 
+ Check for an html page, now matches
+ '<!!DOCTYPE HTML' and <html> 
+ the allows use of pbwiki's raw=bare option which returns iframe 
+ embeddable html without the usual headers.
+ 
+ 8 May 2007
+ Modified bug:fix:date: so that the fixesApplied history does not contain unnecessary duplicate entries.
+ Fixed changeset naming for mantis bugs.
+ 
+ 25 July 2007
+ Added Universes  Support
+ "!

Item was added:
+ ----- Method: InstallerMonticello>>packagesMatching: (in category 'searching') -----
+ packagesMatching: aMatch
+ 	^ (self availablePackages
+ 		select: [:p | ( aMatch , '.mcz' ) match: p])
+ 		collect: [:p | self copy package: p ; yourself]!

Item was added:
+ ----- Method: InstallerSqueakMap>>packageAndVersionFrom: (in category 'squeakmap') -----
+ packageAndVersionFrom: pkg
+ 
+ 	| p |
+ 	p := ReadStream on: pkg .
+ 	^Array with: (p upTo: $() with: (p upTo: $)).!

Item was added:
+ ----- Method: InstallerUniverse>>uniDoInstall (in category 'universes') -----
+ uniDoInstall
+ 
+ 	self withAnswersDo: [ self universe doInstall ] !

Item was changed:
+ ----- Method: Installer class>>doesNotUnderstand: (in category 'custom names') -----
- ----- Method: Installer class>>doesNotUnderstand: (in category 'accessing system') -----
  doesNotUnderstand: aMessage
  
  	^ self remembered at: aMessage selector ifAbsent: [ super doesNotUnderstand: aMessage ]!

Item was added:
+ ----- Method: InstallerCruft>>webAction:reportOn: (in category 'action report') -----
+ webAction: line reportOn: report
+ 	
+ 	self package: (line readStream upTo: $' ; upTo: $').
+ 
+ 	self reportSection: line on: report.
+ 	
+  	url := self webFindUrlToDownload.
+ 	
+ 	self reportFor: line page: pageDataStream on: report !

Item was added:
+ ----- Method: InstallerMonticello>>basicBrowse (in category 'basic interface') -----
+ basicBrowse
+ 	 "Installer ss project: 'Installer'; browse: 'Installer-Core'."
+ 
+ 	| it |
+ 	it := self mcThing.
+ 	
+ 	(it respondsTo: #browse) ifTrue: [ ^ it browse ].
+ 	
+ 	(MCSnapshotBrowser forSnapshot: it)
+ 		showLabelled: 'Snapshot of ', self package!

Item was added:
+ ----- Method: InstallerMantis>>bug:view: (in category 'public interface') -----
+ bug: aBugNo view: aFileName
+ 	"Installer mantis bug: 6089 browse: 'TTFSpeedUp-dgd.1.cs'"
+ 	
+ 	 self setBug: aBugNo.
+ 	^ self view: aFileName from: (self maThing: aFileName date: nil)!

Item was added:
+ ----- Method: InstallerMantis>>maRead:field: (in category 'mantis') -----
+ maRead: page field: fieldKey
+ 
+ 	 | value |
+  
+ 	value := page upToAll: ('!!-- ', fieldKey, ' -->'); upToAll: '<td'; upTo: $>; upToAll: '</td>'.
+ 	
+ 	page upTo: $<.
+ 	
+ 	page peek = $t ifTrue: [ value := page upToAll: 'td'; upTo: $>; upToAll: '</td>' ].
+ 	  
+ 	^Association key: fieldKey value: value withBlanksTrimmed!

Item was added:
+ ----- Method: InstallerUpdateStream>>parseUpdateListContents: (in category 'updates') -----
+ parseUpdateListContents: listContentString
+ 	"Parse the contents of an updates.list into {{releaseTag. {fileNames*}}*}, and return it."
+ 
+ 	| sections releaseTag strm line fileNames |
+ 	sections := OrderedCollection new.
+ 	fileNames := OrderedCollection new: 1000.
+ 	releaseTag := nil.
+ 	strm := ReadStream on: listContentString.
+ 	[strm atEnd] whileFalse:
+ 		[line := strm upTo: Character cr.
+ 		line size > 0 ifTrue:
+ 			[line first = $#
+ 				ifTrue: [releaseTag ifNotNil: [sections addLast: {releaseTag. fileNames asArray}].
+ 						releaseTag := line allButFirst.
+ 						fileNames resetTo: 1]
+ 				ifFalse: [line first = $* ifFalse: [fileNames addLast: line]]]].
+ 	releaseTag ifNotNil: [sections addLast: {releaseTag. fileNames asArray}].
+ 	^ sections asArray
+ !

Item was added:
+ ----- Method: InstallerMantis>>bug:retrieve: (in category 'public interface') -----
+ bug: aBugNo retrieve: aFileName
+ 
+ 	 self setBug: aBugNo.
+ 	^ (self maStreamForFile: aFileName) contents!

Item was added:
+ ----- Method: InstallerWebBased>>removeHtmlMarkupFrom: (in category 'url') -----
+ removeHtmlMarkupFrom: in 
+ 
+ 	| out |
+ 	out := ReadWriteStream on: (String new: 100).
+ 	[ in atEnd ] whileFalse: [ 
+ 		out nextPutAll: (in upTo: $<).
+ 		(((in upTo: $>) asLowercase beginsWith: 'br') and: [ (in peek = Character cr) ]) ifTrue: [ in next ].	
+ 	].
+ 	
+ 	^self replaceEntitiesIn: out reset.
+ !

Item was added:
+ ----- Method: InstallerSake>>basicInstall (in category 'basic interface') -----
+ basicInstall
+  
+ 	self withAnswersDo: [ (self packages collect: [ :packageName | sake named: packageName ]) asTask run ].
+ 	!

Item was changed:
+ ----- Method: Installer class>>url: (in category 'url') -----
- ----- Method: Installer class>>url: (in category 'instanciation') -----
  url: urlString
  
+ 	^self url url: urlString; yourself!
- 	^self web url: urlString; yourself!

Item was added:
+ ----- Method: InstallerMantis>>maScript (in category 'mantis') -----
+ maScript 
+ 
+ 	^self extractFromHtml: self maPage option: #last
+ !

Item was added:
+ ----- Method: InstallerUniverse>>update (in category 'public interface') -----
+ update
+ 
+ 	(LastUniUpdate isNil or:[ (DateAndTime now - LastUniUpdate) > 600 seconds  ])
+ 		ifTrue: [universe requestPackageList.
+ 				LastUniUpdate := DateAndTime now]!

Item was added:
+ ----- Method: InstallerCruft>>createRBforBug: (in category 'mantis') -----
+ createRBforBug: aBugNo 
+ 	| aStream  fileList selFile aFileName |
+ 
+ 	self setBug: aBugNo.
+ fileList := self maFiles keys asOrderedCollection.
+ fileList  addLast: 'none'.
+ ReleaseBuilderFor3dot10 clear.
+ [selFile := UIManager default chooseFrom: fileList title: 'Choose what files load '.
+ selFile = fileList size ifFalse:[
+ aFileName := fileList at: selFile.
+ 	self logCR: 'obtaining ', aFileName, '...'.
+ 
+ 	aStream := self maStreamForFile: aFileName .
+ 	ReleaseBuilderFor3dot10 current packagesInfluenced: aStream named: aFileName.
+ 	
+ 	self installCS: aFileName from: aStream].selFile = fileList size]whileFalse.
+ 	
+ 	ReleaseBuilderFor3dot10 current newUpdateFor: aBugNo
+ 	
+ 	
+ 	!

Item was changed:
+ ----- Method: Installer class>>squeaksource (in category 'monticello') -----
- ----- Method: Installer class>>squeaksource (in category 'instanciation-abbreviated') -----
  squeaksource
  
  	^ self monticello http: 'www.squeaksource.com'!

Item was added:
+ ----- Method: InstallerSqueakMap>>smThing (in category 'squeakmap') -----
+ smThing 
+ 
+ 	| pkgAndVersion releases release |
+ 	pkgAndVersion := self packageAndVersionFrom: self package.
+ 	self logCR: 'retrieving ', self package, ' from SqueakMap...'.
+ 	releases := self smReleasesForPackage: pkgAndVersion first.
+ 	release := pkgAndVersion last isEmpty 
+ 				ifTrue: [ releases last ]
+ 				ifFalse:[ releases detect: [ :rel | rel version = pkgAndVersion last ] ]. 
+ 	^ release
+ 		
+ 	
+ !

Item was added:
+ ----- Method: InstallerSqueakMap>>sm: (in category 'accessing') -----
+ sm: anObject
+ 
+ 	sm := anObject!

Item was changed:
+ ----- Method: Installer class>>mantis: (in category 'mantis') -----
- ----- Method: Installer class>>mantis: (in category 'instanciation') -----
  mantis: host
  
+ 	^ InstallerMantis host: host!
- 	^self new	ma: host; 
- 			markers: '&quot;fix begin&quot;...&quot;fix test&quot;...&quot;fix end&quot;'; 
- 			yourself.
- !

Item was added:
+ ----- Method: InstallerMonticello>>mcDetectFileBlock (in category 'monticello') -----
+ mcDetectFileBlock
+ 
+ 	self package isString ifTrue: [  ^ [ :aFile | aFile beginsWith: self package ] ].
+ 
+ 	(self package isKindOf: Array) 
+ 			ifTrue: [  ^  [ :aFile | (self package detect: [ :item | aFile beginsWith: item ] ifNone: [ false ]) ~= false ] ].
+ 
+ 	self package isBlock ifTrue: [ ^ self package ].
+   
+  !

Item was added:
+ ----- Method: InstallerMonticello class>>classMCVersionLoader (in category 'class references') -----
+ classMCVersionLoader
+ 
+ 	^Smalltalk at: #MCVersionLoader  ifAbsent: [ self error: 'Monticello not present' ]!

Item was added:
+ ----- Method: InstallerMantis>>ma: (in category 'accessing') -----
+ ma: aUrl
+ 
+ 	ma := aUrl last = $/ ifTrue: [ aUrl ] ifFalse: [ aUrl, '/' ]!

Item was changed:
+ ----- Method: Installer class>>webSearchPath (in category 'web') -----
- ----- Method: Installer class>>webSearchPath (in category 'accessing') -----
  webSearchPath
  	"a search path item, has the following format. prefix*suffix"
  
+ 	^ self web searchPath!
- 	^ WebSearchPath ifNil: [ WebSearchPath := OrderedCollection new ].!

Item was added:
+ ----- Method: InstallerMantis>>desc: (in category 'accessing') -----
+ desc: anObject
+ 
+ 	desc := anObject!

Item was added:
+ ----- Method: InstallerSqueakMap>>classSMLoader (in category 'class references') -----
+ classSMLoader
+ 
+ 	^Smalltalk at: #SMLoader  ifAbsent: [ self error: 'SqueakMap Loader not present' ]!

Item was added:
+ ----- Method: InstallerCruft class>>view: (in category 'instanciation') -----
+ view: webPageNameOrUrl
+ 
+ 	| theReport |
+ 
+ 	theReport := String streamContents: [ :report | 
+ 	(webPageNameOrUrl beginsWith: 'http://') ifTrue: [ 
+ 		self new urlAction: ('Installer installUrl: ', (webPageNameOrUrl printString),'.')  	
+ 						 reportOn: report.
+ 	]
+ 	ifFalse: [
+ 		self new webAction: ('Installer install: ', (webPageNameOrUrl printString),'.')  	
+ 						 reportOn: report.
+ 	]].
+ 
+ 	Workspace new contents: (theReport contents); openLabel: webPageNameOrUrl.
+ 
+ 	^theReport contents
+ !

Item was added:
+ ----- Method: InstallerSqueakMap>>open (in category 'public interface') -----
+ open
+ 	self classSMLoader open!

Item was changed:
+ ----- Method: Installer class>>sf (in category 'monticello') -----
- ----- Method: Installer class>>sf (in category 'instanciation-abbreviated') -----
  sf
  
  	^ self squeakfoundation
   !

Item was added:
+ ----- Method: InstallerUniverse class>>classUGlobalInstaller (in category 'accessing system') -----
+ classUGlobalInstaller
+ 
+ 	^Smalltalk at: #UGlobalInstaller  ifAbsent: [ self error: 'Universes code not present' ]!

Item was added:
+ ----- Method: InstallerMantis>>justFixBug:date: (in category 'public interface') -----
+ justFixBug: aBugNo date: d
+ 
+ 	^self class skipLoadingTests: true during: [ self fixBug: aBugNo date: d ]!

Item was added:
+ ----- Method: InstallerCruft>>skipTests (in category 'mantis') -----
+ skipTests
+ 
+ !

Item was added:
+ ----- Method: InstallerSqueakMap>>sm (in category 'accessing') -----
+ sm
+ 
+ 	^ sm ifNil: [ false ]!

Item was added:
+ ----- Method: InstallerWebSqueakMap>>basicAvailablePackages (in category 'websqueakmap') -----
+ basicAvailablePackages
+ 
+ 	| html id name pkgs | 
+ 	pkgs := Dictionary new.
+ 	html := self httpGet: (self wsm, 'packagesbyname').
+ 	
+ 	[ id := html upToAll: '/package/'; upToAll: '">'.
+ 	name := html upTo: $<.
+ 	(id notEmpty and: [ name notEmpty ])] 
+ 		whileTrue: [ pkgs at: name put: id ].
+ 
+ 	^ pkgs	
+ 	!

Item was added:
+ ----- Method: InstallerWebSqueakMap>>wsmDownloadUrl (in category 'websqueakmap') -----
+ wsmDownloadUrl 
+ 	| pkgAndVersion packageId packageName packageVersion releaseAutoVersion
+  	downloadPage |
+ 
+ 	pkgAndVersion := self packageAndVersionFrom: self package.
+ 	packageName := pkgAndVersion first.
+ 	packageVersion := pkgAndVersion last.
+ 	packageVersion isEmpty ifTrue: [ packageVersion := #latest ].
+ 
+ 	packageId := self availablePackages at: packageName.
+ 	releaseAutoVersion := (self wsmReleasesFor: packageId) at: packageVersion.
+ 					 
+ 	downloadPage := self httpGet: (self wsm,'packagebyname/', packageName,'/autoversion/', releaseAutoVersion,'/downloadurl') asUrl asString.
+ 				 		 
+ 	^ downloadPage contents
+ 	
+ !

Item was added:
+ InstallerInternetBased subclass: #InstallerUrl
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was changed:
  ----- Method: Installer>>update (in category 'public interface') -----
+ update!
- update
- 
- 	universe ifNotNil: [ self uniUpdate ].
- 	sm ifNotNil: [ self smUpdate ].!

Item was added:
+ ----- Method: InstallerInternetBased>>url: (in category 'accessing') -----
+ url: aUrl
+  
+ 	url := aUrl!

Item was added:
+ ----- Method: InstallerMantis>>bugFilesView: (in category 'public interface') -----
+ bugFilesView: aBugNo
+  	
+ 				
+ 	(self bugFiles: aBugNo) do: [ :ea | self bug: aBugNo view: ea ].!

Item was added:
+ Installer subclass: #InstallerMonticello
+ 	instanceVariableNames: 'mc root project'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was added:
+ ----- Method: InstallerMonticello>>mcThing (in category 'monticello') -----
+ mcThing
+ 
+ 	| loader files fileToLoad  version  count |
+ 
+ 	loader := self class classMCVersionLoader new.
+ 	
+ 	1 to: self packages size do: [ :n |
+ 
+ 		self logCR: 'finding ', self package asString, '...'.
+ 		"several attempts to read files - repository readableFileNames sometimes fails"
+ 		count := 0. fileToLoad := nil.
+ 	
+ 		[count := count + 1.
+ 		 (fileToLoad = nil) and:[ count < 5 ] ] 
+ 			whileTrue: [
+ 							files := mc readableFileNames asSortedCollection: self mcSortFileBlock.
+ 							fileToLoad := files detect: self mcDetectFileBlock ifNone: [ nil ].
+ 		].
+ 
+ 		version := mc versionFromFileNamed: fileToLoad.
+ 		(version isKindOf: MCConfiguration) 
+ 			ifTrue: [ ^ version ]
+ 			ifFalse:[version workingCopy repositoryGroup addRepository: mc.
+ 				loader addVersion: version].
+ 		self log: ' found ', version fileName, '...'.
+ 
+ 		packages removeFirst.
+ 	].
+ 
+ 	^ loader!

Item was added:
+ ----- Method: InstallerUniverse class>>classUUniverse (in category 'accessing system') -----
+ classUUniverse
+ 
+ 	^Smalltalk at: #UUniverse  ifAbsent: [ self error: 'Universes code not present' ]!

Item was changed:
+ ----- Method: Installer class>>web (in category 'web') -----
- ----- Method: Installer class>>web (in category 'instanciation') -----
  web 
+ 	^ InstallerWeb!
- 	^self new !

Item was added:
+ ----- Method: Installer class>>http: (in category 'instance creation') -----
+ http: aUrl  
+ 	
+ 	^ self http: aUrl user: 'squeak' password: 'squeak'
+ 		
+  !

Item was changed:
+ ----- Method: Installer class>>goran (in category 'monticello') -----
- ----- Method: Installer class>>goran (in category 'instanciation-abbreviated') -----
  goran
  
  	^ self monticello http: 'squeak.krampe.se'; project: ''!

Item was added:
+ ----- Method: InstallerWeb>>webFindUrlToDownload (in category 'web install') -----
+ webFindUrlToDownload
+ 
+ 	| delay retry |
+ 	delay := 0.
+ 	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 ] 
+ 						doWhileTrue: [ 	
+ 								(pageDataStream notNil and: [ pageDataStream size > 0 ]) 
+ 									ifTrue: [ (pageDataStream contents includesSubString: 'Please slow down a bit') 
+ 													ifTrue: [ retry := true ]
+ 													ifFalse: [ pageDataStream reset. 
+ 																^ potentialUrl ] ].
+ 								(Delay forSeconds: (delay := delay + 5)) wait.
+ 								retry ]].
+ 	^nil
+ !

Item was added:
+ ----- Method: InstallerWebBased>>markers: (in category 'accessing') -----
+ markers: anObject
+ 
+ 	markers := anObject!

Item was added:
+ ----- Method: InstallerCruft class>>launchHelp (in category 'launcher support') -----
+ launchHelp
+ 
+ ^'path=/dir/*.txt          Specify a search path for the item to install
+ p=/dir1/*.txt;<url2>/    Multiple items delimited by ;
+                          The page name is typically appended to the path string, or
+                          if a "*" is present, it will be replaced by the page name.
+ 					
+ in,i,install=<page>      Page appended to the path to begin the install process
+ url,u=<url>              Install using an explicit url from which to obtain a script or file
+ file=<url>                Install using a local file
+ +debug                   Do not trap errors
+ view=<page>              Print the script that would have been installed.
+ 
+ For more options use Script eval="Installer ... " 
+ '
+ !

Item was added:
+ ----- Method: InstallerCruft>>actionMatch:reportOn:ifNoMatch: (in category 'action report') -----
+ actionMatch: theLine reportOn: report ifNoMatch: aBlock
+ 
+ 	| line |	
+ 	line := theLine withBlanksCondensed.
+ 	((line beginsWith: 'Installer install:') | (line beginsWith: 'Installer do:')) 
+ 		ifTrue: [ ^self webAction: theLine reportOn: report ].
+ 		
+ 	((line beginsWith: 'Installer installUrl:') and: 
+ 		[ | ext |
+ 		 ext :=  (line readStream upToAll: '''.') copyAfterLast: $..
+ 		 (#( 'cs' 'st' 'mcz' 'sar') includes: ext) not ]) ifTrue: [ ^self urlAction: theLine reportOn: report ].
+ 
+ 	(line beginsWith: 'Installer mantis fixBug:') ifTrue: [ ^self mantisAction: theLine reportOn: report ].
+ 	aBlock value.
+ !

Item was added:
+ ----- Method: InstallerWebSqueakMap>>basicView (in category 'basic interface') -----
+ basicView
+ 	
+ 	| it |
+ 	it := self wsmThing.
+ 	self view: it from: (self httpGet: it).
+ 
+ 	!

Item was added:
+ Installer subclass: #InstallerUniverse
+ 	instanceVariableNames: 'universe'
+ 	classVariableNames: 'LastUniUpdate'
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was added:
+ Installer subclass: #InstallerSqueakMap
+ 	instanceVariableNames: 'sm'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was added:
+ ----- Method: InstallerCruft>>mczInstall: (in category 'monticello') -----
+ mczInstall: urlOrFile
+ 
+ 	self log: ('Loading ', urlOrFile, ' ...').
+ 
+ 	(urlOrFile beginsWith: 'http:')
+ 		ifTrue: [  MczInstaller installStream: (HTTPSocket httpGet: urlOrFile) ]
+ 		ifFalse: [ MczInstaller installFileNamed: urlOrFile ].
+ 		
+ 	self logCR: ' Loaded'.
+ 
+ 	
+ 
+ !

Item was added:
+ ----- Method: InstallerWeb>>basicInstall (in category 'basic interface') -----
+ basicInstall
+  
+  	 self webThing size > 0 
+ 		ifTrue: [ self install: url from: pageDataStream ]
+ 		ifFalse: [ url ifNil: [ ^ self logCR: self package, ' not found on webSearchPath' ].
+ 				  self logCR: '...',url,' was empty' ].
+ 	 !

Item was changed:
+ ----- Method: Installer class>>sake: (in category 'sake') -----
- ----- Method: Installer class>>sake: (in category 'instanciation') -----
  sake: aSakePackagesClass
  
+ 	^ InstallerSake new sake: aSakePackagesClass!
- 	^ self new sake: aSakePackagesClass!

Item was added:
+ ----- Method: InstallerCruft class>>smalltalkImage (in category 'accessing system') -----
+ smalltalkImage
+ 
+ 	^ SmalltalkImage current!

Item was added:
+ ----- Method: InstallerMantis>>bug: (in category 'accessing') -----
+ bug: aBugNo
+ 	"Installer mantis viewBug: 5639."
+ 	| page text | 
+ 
+ 	self setBug: aBugNo.
+ 	
+ 	page := self maPage.
+  
+ 	text := String streamContents: [ :str |	
+ 			
+ 		#('Bug ID' 'Category' 'Severity' 'Reproducibility' 'Date Submitted' 
+ 			'Date Updated' 'Reporter' 'View Status' 'Handler' 
+ 			'Priority' 'Resolution' 'Status' 'Product Version' 'Summary' 'Description' 'Additional Information' ) 
+ 				do: [ :field |
+ 						| f |
+ 						f := self maRead: page field: field.
+ 			str nextPutAll: f key; nextPutAll: ': '; nextPutAll: f value; cr.
+ 		].
+ 	
+ 	str nextPutAll: 'Notes: '; cr.
+ 		(self maReadNotes: page) do: [ :note | str nextPutAll: note; cr; cr ].
+ 		
+ 		str nextPutAll: 'Files: '; nextPutAll: self maFiles keys asArray printString.
+ 	].
+  	^ text	
+ !

Item was added:
+ ----- Method: InstallerMantis>>bugScript: (in category 'public interface') -----
+ bugScript: aBugNo
+ 
+ 	self setBug: aBugNo.
+  	^ self maScript contents.
+ 	 
+ 	
+ 	
+ !

Item was added:
+ ----- Method: InstallerMantis class>>fixesApplied (in category 'accessing') -----
+ fixesApplied
+ 
+ 	^ Fixes ifNil: [ Fixes := OrderedCollection new ].!

Item was added:
+ ----- Method: InstallerUpdateStream>>updateDirectoryOrNil (in category 'updates') -----
+ updateDirectoryOrNil
+ 
+ 	^ (FileDirectory default directoryNames includes: 'updates')
+ 		ifTrue: [FileDirectory default directoryNamed: 'updates']
+ 		ifFalse: [self inform: 'Error: cannot find "updates" folder'.
+ 				nil]!

Item was added:
+ ----- Method: InstallerWebBased>>extractFromHtml:option: (in category 'action report') -----
+ extractFromHtml: html option: allOrLast
+ 
+ 	|  start stop test in |
+ 
+ 	start := self markersBegin.
+ 	stop :=  self markersEnd.
+ 	test := self markersTest.
+ 			 
+ 	in := ReadWriteStream with: String new.
+ 		
+ 	[ html upToAll: start; atEnd ] 
+ 		whileFalse: [
+ 			| chunk |
+ 			(allOrLast == #last) ifTrue: [ in resetToStart ]. 
+ 			chunk := html upToAll: stop.
+ 			self isSkipLoadingTestsSet ifTrue: [ chunk := chunk readStream upToAll: test ].
+ 			in nextPutAll: chunk. 
+ 		 ].
+ 
+ 	^self removeHtmlMarkupFrom: in reset
+ 	 
+ !

Item was changed:
+ ----- Method: Installer class>>monticello (in category 'monticello') -----
- ----- Method: Installer class>>monticello (in category 'instanciation') -----
  monticello
  
+ 	^ InstallerMonticello!
- 	^ self new!

Item was added:
+ ----- Method: InstallerMantis>>bug:browse: (in category 'public interface') -----
+ bug: aBugNo browse: aFileName
+ 
+ 	 self setBug: aBugNo.
+ 	^ self browse: aFileName from: (self maThing: aFileName date: nil)!

Item was changed:
  ----- Method: Installer>>install (in category 'public interface') -----
  install
+ 	self logErrorDuring: [self basicInstall]!
- 
- 	self logErrorDuring: [
- 		self sake ifNotNil: [ ^ self sakeInstall ].
- 		self universe ifNotNil: [ ^ self uniInstall ].
- 		self file ifNotNil: [ ^ self fileInstall ].
- 		self mc ifNotNil: [ ^self mcInstall ].
- 		self wsm ifNotNil: [ ^self wsmInstall ].
- 		self sm ifTrue: [ ^self smInstall ].
- 		self url ifNotNil: [ ^self urlInstall ].
- 		self package ifNotNil: [ ^self webInstall ].
- 	] !

Item was changed:
+ ----- Method: Installer class>>validationBlock: (in category 'accessing') -----
- ----- Method: Installer class>>validationBlock: (in category 'instanciation-abbreviated') -----
  validationBlock: aBlock
  
  	ValidationBlock := aBlock!

Item was added:
+ Installer subclass: #InstallerCruft
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!
+ 
+ !InstallerCruft commentStamp: 'mtf 10/1/2008 22:24' prior: 0!
+ I am a copy of Installer as of Installer-Core-kph.232. I am being split up.
+ I  am called InstallerCruft because I stand-in for Sake{MC,SM,Mantis,Web,etc}Installer!

Item was added:
+ Installer subclass: #InstallerInternetBased
+ 	instanceVariableNames: 'url pageDataStream'
+ 	classVariableNames: 'Entities'
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was added:
+ ----- Method: InstallerMantis>>bug (in category 'accessing') -----
+ bug
+ 	
+ 	^ bug!

Item was added:
+ ----- Method: InstallerMantis>>maFiles (in category 'mantis') -----
+ maFiles
+  	| file files bugPage id  | 
+  	files := Dictionary new.
+  	bugPage := self maPage.
+ 	 [ 
+ 		id := bugPage upToAll: 'href="file_download.php?file_id='; upTo: $&. 
+  		file := bugPage upToAll: 'amp;type=bug"' ; upTo: $<.
+  		((file size > 1) and: [file first = $>]) ifTrue: [ files at: file copyWithoutFirst put: id ].
+  		id notEmpty ] whileTrue.
+ 
+ 	^files !

Item was added:
+ ----- Method: InstallerWebSqueakMap>>packagesMatching: (in category 'searching') -----
+ packagesMatching: aMatch
+ 	^ (self availablePackages
+ 		select: [ :p | ( aMatch) match: p ]) 
+ 		collect: [ :p | self copy package: p ; yourself ]!

Item was added:
+ ----- Method: InstallerMonticello>>project: (in category 'accessing') -----
+ project: name
+ 
+ 	project := name.
+ 	packages := nil.
+ 	
+ 	(mc respondsTo: #location:) ifTrue:[ mc := mc copy location: root , name ].
+ 	(mc respondsTo: #directory:) ifTrue: [ mc := mc copy directory: root ,'/', name ].
+ 		
+ 	^self copy.!

Item was changed:
+ ----- Method: Installer class>>webInstall: (in category 'web') -----
- ----- Method: Installer class>>webInstall: (in category 'instanciation') -----
  webInstall: webPageName
  
  	self webSearchPath isEmpty ifTrue: [ ^self error: 'search path not set' ].
  	^ self web install: webPageName
  !

Item was changed:
+ ----- Method: Installer class>>keith (in category 'monticello') -----
- ----- Method: Installer class>>keith (in category 'instanciation-abbreviated') -----
  keith
  
  	^ self monticello ftp: 'squeak.warwick.st' directory: 'mc' user: 'squeak' password: 'viewpoints'!

Item was added:
+ Installer subclass: #InstallerUpdateStream
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was added:
+ ----- Method: InstallerMantis>>fixBug: (in category 'public interface') -----
+ fixBug: aBugNo
+ 
+ 	^ self fixBug: aBugNo date: nil!

Item was added:
+ ----- Method: InstallerMonticello>>open (in category 'public interface') -----
+ open
+ 	self mc morphicOpen: nil!

Item was added:
+ ----- Method: InstallerMonticello class>>magma:port: (in category 'instance creation') -----
+ magma: host port: aport
+ 	
+ 	^ self new mc: (self classMCMagmaRepository new) host: host port: aport; yourself!

Item was added:
+ ----- Method: InstallerCruft class>>launchFrom: (in category 'launcher support') -----
+ launchFrom: launcher
+ 
+ 	^self launchWith: launcher getParameters!

Item was added:
+ ----- Method: InstallerMantis>>ensureFixes: (in category 'public interface') -----
+ ensureFixes: aBugNos
+ 
+ 	aBugNos do: [ :bugNo | self ensureFixes: bugNo ].!

Item was added:
+ ----- Method: InstallerMonticello class>>classMCGOODSRepository (in category 'class references') -----
+ classMCGOODSRepository
+ 
+ 	^Smalltalk at: #MCGOODSRepository ifAbsent: [ self error: 'Monticello not present' ]
+ 	!

Item was added:
+ ----- Method: InstallerMantis>>desc (in category 'accessing') -----
+ desc
+ 	 
+ 	^ desc!

Item was changed:
+ ----- Method: Installer class>>setSakeToUse: (in category 'sake') -----
- ----- Method: Installer class>>setSakeToUse: (in category 'instanciation') -----
  setSakeToUse: aClass
  
+ 	InstallerSake sake: aClass!
- 	Sake := aClass!

Item was added:
+ ----- Method: Installer class>>url (in category 'url') -----
+ url
+ 
+ 	^ InstallerUrl new!

Item was changed:
+ ----- Method: Installer class>>sake (in category 'sake') -----
- ----- Method: Installer class>>sake (in category 'instanciation') -----
  sake
  
+ 	^ self sake: InstallerSake sake!
- 	^ self sake: (Sake ifNil: [ self classPackages current ])!

Item was added:
+ ----- Method: InstallerMantis>>ma (in category 'accessing') -----
+ ma
+ 
+ 	^ ma!

Item was changed:
  Object subclass: #Installer
+ 	instanceVariableNames: 'answers packages messagesToSuppress'
+ 	classVariableNames: 'IsSetToTrapErrors Remembered SkipLoadingTests InstallerBindings ValidationBlock'
- 	instanceVariableNames: 'sm wsm mc ma url root command markers project package bug desc answers packages messagesToSuppress pageDataStream date universe afile sake'
- 	classVariableNames: 'WebSearchPath SkipLoadingTests Fixes Sake Entities ValidationBlock InstallerBindings Remembered LastUniUpdate IsSetToTrapErrors'
  	poolDictionaries: ''
  	category: 'Installer-Core'!
  
  !Installer commentStamp: 'kph 12/19/2007 14:42' prior: 0!
  Documentation now available at http://installer.pbwiki.com/Installer
   !

Item was added:
+ ----- Method: InstallerFile class>>installFile: (in category 'instanciation') -----
+ installFile: fileName
+  
+ 	^ (self file: fileName) install.
+ !

Item was added:
+ ----- Method: InstallerCruft>>evaluate: (in category 'mantis') -----
+ evaluate: stream
+ 
+ 	stream fileIn.!

Item was added:
+ ----- Method: InstallerFile>>basicView (in category 'basic interface') -----
+ basicView
+ 	
+ 	self view: self file from:  (FileDirectory readOnlyFileNamed: self file).
+ 
+ 	!

Item was added:
+ ----- Method: InstallerMantis>>maThing:date: (in category 'mantis') -----
+ maThing: aFileName date: aDate
+  
+ 	self logCR: 'obtaining ', aFileName, '...'.
+ 
+ 	pageDataStream := self maStreamForFile: aFileName.
+ 
+ 	self maCheckDateAgainst: aDate.
+ 
+ 	^ pageDataStream
+ 	!

Item was added:
+ ----- Method: InstallerSqueakMap>>smPackageAndVersion (in category 'squeakmap') -----
+ smPackageAndVersion
+ 
+ 	| p |
+ 	p := ReadStream on: self package .
+ 	^Array with: (p upTo: $() with: (p upTo: $)).!

Item was changed:
+ ----- Method: Installer class>>remembered (in category 'custom names') -----
- ----- Method: Installer class>>remembered (in category 'accessing system') -----
  remembered
  
  	^	Remembered ifNil: [ Remembered := IdentityDictionary new ]!

Item was added:
+ ----- Method: InstallerMantis>>maStreamForFile: (in category 'mantis') -----
+ maStreamForFile: aFileName
+ 
+ 	| fileId  |
+ 
+  	fileId :=  self maFiles at: aFileName ifAbsent: [ self error: aFileName, ' not found' ].
+ 
+  	^ self httpGet: (self ma, 'file_download.php?file_id=' , fileId , '&type=bug').
+ 	 !

Item was changed:
+ ----- Method: Installer>>installQuietly: (in category 'public interface') -----
- ----- Method: Installer>>installQuietly: (in category 'accessing') -----
  installQuietly: packageNameCollectionOrDetectBlock
  
  	self package: packageNameCollectionOrDetectBlock.
   	self installQuietly.!

Item was added:
+ ----- Method: InstallerCruft class>>launchWith: (in category 'launcher support') -----
+ launchWith: params
+ 
+  	params at: 'P' ifPresent: [ :v | params at: 'PATH' put: v ].
+  	params at: 'I' ifPresent: [ :v | params at: 'INSTALL' put: v ].
+  	params at: 'IN' ifPresent: [ :v | params at: 'INSTALL' put: v ].
+  	params at: 'U' ifPresent: [ :v | params at: 'URL' put: v ].
+ 
+ 	params at: 'PATH' ifPresent: [ :v | 
+ 		self webSearchPathFrom: v.
+ 	].
+ 
+ 	params at: 'USER' ifPresent: [ :v | 
+ 		Utilities setAuthorInitials: v
+ 	].
+ 	params at: 'VERSION' ifPresent: [ :v | 
+ 		SystemVersion current version: v
+ 	].
+ 	params at: 'VIEW' ifPresent: [ :v |
+ 		self view: v
+ 	].
+ 
+ 	IsSetToTrapErrors := true.
+ 	params at: 'DEBUG' ifPresent: [ :v | IsSetToTrapErrors := (v == true) not ].
+ 
+  	params at: 'URL' ifPresent: [ :v | 
+ 		 self installUrl: v
+ 	].
+ 
+ 	params at: 'FILE' ifPresent: [ :v | 
+ 		 self installFile: v
+ 	].
+  
+  	params at: 'INSTALL' ifPresent: [ :v | 
+ 		  self do: v
+ 	].
+ 	params at: 'DO' ifPresent: [ :v | 
+ 		  self do: v
+ 	].
+  
+ 	 ^true
+ 
+ 	!

Item was added:
+ ----- Method: InstallerMonticello class>>http:user:password: (in category 'instance creation') -----
+ http: aUrl user: name password: secret
+ 	
+ 	| mc |
+ 	^ self new
+ 		mc: (mc := self classMCHttpRepository location: aUrl user: name password: secret)
+ 		root: mc locationWithTrailingSlash!

Item was added:
+ InstallerWebBased subclass: #InstallerWebSqueakMap
+ 	instanceVariableNames: 'wsm'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was changed:
+ ----- Method: Installer class>>cache (in category 'monticello') -----
- ----- Method: Installer class>>cache (in category 'instanciation-abbreviated') -----
  cache
  	^ self monticello cache!

Item was added:
+ ----- Method: InstallerMonticello class>>ftp:directory:user:password: (in category 'instance creation') -----
+ ftp: host directory: dir user: name password: secret
+ 	"Installer mc ftp: 'mc.gjallar.se' directory: '' user: 'gjallar' password: secret."
+ 	
+ 	^ self new
+ 		mc: (self classMCFtpRepository host: host directory: dir user: name password: '')
+ 		root: dir!

Item was added:
+ ----- Method: InstallerWebBased>>markersBegin (in category 'url') -----
+ markersBegin
+ 		 	 
+ 	 ^ self markers copyUpTo: $.!

Item was added:
+ ----- 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 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 := 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 wait!

Item was added:
+ ----- Method: InstallerWebSqueakMap>>wsmThing (in category 'websqueakmap') -----
+ wsmThing
+ 
+ 	| downloadUrl |
+ 	self logCR: 'finding ', self package, ' from websqueakmap(', self wsm, ') ...'.
+ 	downloadUrl := self wsmDownloadUrl.
+ 	self logCR: 'found at ', downloadUrl asString, ' ...'.
+ 	^ downloadUrl
+ 	!

Item was added:
+ ----- Method: InstallerCruft>>user (in category 'accessing') -----
+ user
+ 
+ 	^ user ifNil: [ '' ]!

Item was added:
+ ----- Method: InstallerFile>>basicInstall (in category 'basic interface') -----
+ basicInstall
+ 	
+ 	self install: self file from: (FileDirectory default readOnlyFileNamed: self file)
+ 
+ 	!

Item was added:
+ ----- Method: InstallerMonticello>>mcSortFileBlock (in category 'monticello') -----
+ mcSortFileBlock
+ 
+ 	^ [:a :b | 
+         	[(a findBetweenSubStrs: #($.)) allButLast last asInteger > (b findBetweenSubStrs: #($.)) allButLast last asInteger] 
+ 				on: Error do: [:ex | false]].!

Item was changed:
+ ----- Method: Installer class>>lukas (in category 'monticello') -----
- ----- Method: Installer class>>lukas (in category 'instanciation-abbreviated') -----
  lukas
  
  	^ self monticello http: 'source.lukas-renggli.ch'!

Item was changed:
+ ----- Method: Installer class>>mc (in category 'monticello') -----
- ----- Method: Installer class>>mc (in category 'instanciation') -----
  mc
  
+ 	^ self monticello!
- 	^ self new!

Item was added:
+ ----- Method: InstallerCruft class>>classProjectLauncher (in category 'accessing system') -----
+ classProjectLauncher
+ 
+ 	^Smalltalk at: #ProjectLauncher ifAbsent: [ self error: 'ProjectLauncher not present' ]!

Item was added:
+ ----- Method: InstallerInternetBased>>url (in category 'accessing') -----
+ url
+ 
+ 	^url!

Item was added:
+ ----- Method: InstallerFile class>>file: (in category 'instanciation') -----
+ file: fileName
+  
+ 	^ InstallerFile new file: fileName; yourself
+ !

Item was added:
+ ----- Method: InstallerUniverse>>basicInstall (in category 'basic interface') -----
+ basicInstall
+ 
+ 	| pkgAndVersion pkg version potentials |
+ 	self packages do: [ :packageName |
+ 	
+ 		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.
+ 	].
+ 	self uniDoInstall!

Item was changed:
+ ----- Method: Installer class>>mantis (in category 'mantis') -----
- ----- Method: Installer class>>mantis (in category 'instanciation') -----
  mantis
  
  	^ self mantis: 'http://bugs.squeak.org/'!

Item was added:
+ ----- Method: InstallerMonticello>>mc:root: (in category 'initialize-release') -----
+ mc: aRepo root: aPath
+ 	mc := aRepo.
+ 	root := aPath.!

Item was added:
+ ----- Method: InstallerCruft class>>unload: (in category 'unload') -----
+ unload: categoryMatchesString 
+ 
+ 	^ self error: 'deprecated, use Installer mc unload: ''pkgname''.'!

Item was added:
+ ----- Method: InstallerWebBased>>markersEnd (in category 'url') -----
+ markersEnd
+ 	"return the third marker or the second if there are only two"
+ 	
+ 	| str  a | 
+ 	str := self markers readStream.
+ 	a := str upToAll: '...'; upToAll: '...'.
+ 	str atEnd  ifTrue: [ ^a ] ifFalse: [ ^str upToEnd ]
+ 	!

Item was added:
+ ----- Method: InstallerCruft class>>sourceFiles (in category 'accessing system') -----
+ sourceFiles
+ 
+ 	^ SourceFiles!

Item was added:
+ ----- Method: InstallerMonticello class>>directory: (in category 'instance creation') -----
+ directory: dir
+ 
+ 	| directory |
+ 	directory := dir isString 
+ 		ifTrue: [  FileDirectory on: (FileDirectory default fullNameFor: dir) ]
+ 		ifFalse: [ dir ].
+ 		
+ 	^ self new
+ 		mc: (self classMCDirectoryRepository new directory: directory; yourself)
+ 		root: dir!

Item was added:
+ ----- Method: InstallerUniverse>>universe: (in category 'universes') -----
+ universe: u
+ 
+ 	universe := u.
+ 	self update.!

Item was added:
+ ----- Method: InstallerCruft>>mantisAction:reportOn: (in category 'action report') -----
+ mantisAction: line reportOn: report
+ 	
+ 	| param mantis |
+ 	mantis := Installer mantis.
+ 	param :=  line readStream upTo: $: ; upTo: $..
+ 	
+ 	mantis setBug: ((param readStream upTo: $'; atEnd)
+ 		 ifTrue: [  param ]
+ 		 ifFalse: [ param readStream upTo: $'; upTo: $' ]).
+ 	
+ 	self reportSection: line on: report.
+ 	report nextPutAll: (mantis replaceEntitiesIn: mantis markersBegin readStream).
+ 	self reportFor: line page: mantis maScript on: report.
+ 	report nextPutAll: (mantis replaceEntitiesIn: mantis markersEnd readStream); cr.
+ 	!

Item was added:
+ ----- Method: Installer>>basicVersions (in category 'basic interface') -----
+ basicVersions!

Item was added:
+ ----- Method: InstallerSqueakMap>>smSearch: (in category 'searching') -----
+ smSearch: aMatch  
+ 
+ 	| results |
+ 	results := Set new.
+ 	self availablePackages do: [ :pkg |
+ 		({ 'name:',pkg name.
+ 		   'summary:', pkg summary.
+ 		   'description:', pkg description.
+ 		   'author:', pkg author. } anySatisfy: [ :field | aMatch match: field ])
+ 		 ifTrue: [ results add: (self copy package: pkg name) ]. 
+ 	].
+ 	^results
+ 
+ !

Item was added:
+ ----- Method: InstallerMonticello class>>classMCMagmaRepository (in category 'class references') -----
+ classMCMagmaRepository
+ 
+ 	^Smalltalk at: #MCMagmaRepository ifAbsent: [ self error: 'Magma not present' ]
+ 	!

Item was added:
+ ----- Method: InstallerSqueakMap>>smReleasesForPackage: (in category 'squeakmap') -----
+ smReleasesForPackage: name 
+ 
+ 	^(self classSMSqueakMap default packageWithName: name) releases!

Item was added:
+ ----- Method: InstallerMantis>>maPage (in category 'mantis') -----
+ maPage
+   	"  self mantis bug: 5251."
+ 
+ 	| page |
+ 	page :=  self httpGet: self maUrl.
+  	date := ((self maRead: page field: 'Date Updated') value copyUpTo: $ ).
+ 	date isEmpty ifTrue: [ ^self error: bug, ' not found' ].
+ 	date := date asDate.
+  	^page reset!

Item was added:
+ InstallerWebBased subclass: #InstallerWeb
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'WebSearchPath'
+ 	poolDictionaries: ''
+ 	category: 'Installer-Core'!

Item was added:
+ ----- Method: InstallerCruft class>>classSakePackages (in category 'accessing system') -----
+ classSakePackages
+ 
+ 	^Smalltalk at: #SakePackages  ifAbsent: [ self error: 'Sake Packages code not present' ]!

Item was added:
+ ----- Method: Installer>>basicView (in category 'basic interface') -----
+ basicView!

Item was changed:
+ ----- Method: Installer>>view (in category 'public interface') -----
- ----- Method: Installer>>view (in category 'accessing') -----
  view
+ 	self logErrorDuring: [self basicView]!
- 
- 	self logErrorDuring: [
- 		self file ifNotNil: [ ^ self fileView ].
- 		self mc ifNotNil: [ ^self mcView ].
- 		self wsm ifNotNil: [ ^self wsmView ].
- 		self sm ifTrue: [ ^self smView ].
- 		self url ifNotNil: [ ^self urlView ].
- 		self package ifNotNil: [ ^self webView ].
- 	] !

Item was added:
+ ----- Method: InstallerWebSqueakMap>>wsmReleasesFor: (in category 'websqueakmap') -----
+ wsmReleasesFor: packageId
+ 
+ 	| html autoVersion version releases |
+ 	releases := Dictionary new.
+ 	html := self httpGet: (self wsm, '/package/', packageId ).
+ 	[releases at: #latest put: autoVersion.
+ 	autoVersion := html upToAll: '/autoversion/'; upTo: $".
+ 	version := html upTo: $-; upTo: $<.
+ 	(autoVersion notEmpty and: [version notEmpty ])] 
+ 		whileTrue: [ releases at: version put: autoVersion ].
+ 	^ releases
+ 	!

Item was changed:
+ ----- Method: Installer class>>repository: (in category 'monticello') -----
- ----- Method: Installer class>>repository: (in category 'instanciation') -----
  repository: host  
  
  	^self monticello http: host !

Item was changed:
+ ----- Method: Installer class>>wiresong (in category 'monticello') -----
- ----- Method: Installer class>>wiresong (in category 'instanciation-abbreviated') -----
  wiresong
  
  	^ self monticello http: 'source.wiresong.ca'!

Item was changed:
+ ----- Method: Installer class>>install: (in category 'web') -----
- ----- Method: Installer class>>install: (in category 'instanciation') -----
  install: webPageName
  
  	self webSearchPath isEmpty ifTrue: [ ^self error: 'search path not set' ].
  
  	^ self web install: webPageName
  !

Item was added:
+ ----- Method: InstallerFile>>basicBrowse (in category 'basic interface') -----
+ basicBrowse
+ 	
+ 	self browse: self file from:  (FileDirectory readOnlyFileNamed: self file).
+ 
+ 	!

Item was added:
+ ----- Method: InstallerWeb>>basicView (in category 'basic interface') -----
+ basicView
+  
+  	 self webThing size > 0 
+ 		ifTrue: [ self view: url from: pageDataStream ]
+ 		ifFalse: [ self logCR: 'NO DATA ',url,' was empty' ].
+ 	 !

Item was added:
+ ----- Method: InstallerUpdateStream>>changesetNamesFromUpdates:through: (in category 'updates') -----
+ changesetNamesFromUpdates: startNumber through: stopNumber
+ 	"Answer the concatenation of summary strings for updates numbered in the given range"
+ 	"self new changesetNamesFromUpdates: 7059 through: 7061"
+ 	
+ 	^ String streamContents: [:aStream |
+ 		((ChangeSet changeSetsNamedSuchThat:
+ 			[:aName | aName first isDigit and:
+ 						[aName initialIntegerOrNil >= startNumber] and:
+ 						[aName initialIntegerOrNil <= stopNumber]]) asSortedCollection:
+ 				[:a :b | a name < b name]) do:
+ 					[:aChangeSet | aStream cr; nextPutAll: aChangeSet summaryString]]
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: InstallerMonticello class>>classMCHttpRepository (in category 'class references') -----
+ classMCHttpRepository
+ 
+ 	^Smalltalk at: #MCHttpRepository ifAbsent: [ self error: 'Monticello not present' ]
+ 	!

Item was added:
+ ----- Method: InstallerCruft>>info (in category 'accessing') -----
+ info
+ 
+ 	self sm ifTrue: [ ^ self smInfo  ].
+ 	self wsm ifNotNil: [ ^ self wsmInfo  ].!

Item was removed:
- ----- Method: Installer>>urlInstall (in category 'url') -----
- urlInstall 
-  	 
- 	self install: self urlToDownload from: self urlThing.
- 	^ pageDataStream 
- !

Item was removed:
- ----- Method: Installer>>mcDetectFileBlock (in category 'monticello') -----
- mcDetectFileBlock
- 
- 	self package isString ifTrue: [  ^ [ :aFile | aFile beginsWith: self package ] ].
- 
- 	(self package isKindOf: Array) 
- 			ifTrue: [  ^  [ :aFile | (self package detect: [ :item | aFile beginsWith: item ] ifNone: [ false ]) ~= false ] ].
- 
- 	self package isBlock ifTrue: [ ^ self package ].
-   
-  !

Item was removed:
- ----- Method: Installer>>extractFromHtml:option: (in category 'action report') -----
- extractFromHtml: html option: allOrLast
- 
- 	|  start stop test in |
- 
- 	start := self markersBegin.
- 	stop :=  self markersEnd.
- 	test := self markersTest.
- 			 
- 	in := ReadWriteStream with: String new.
- 		
- 	[ html upToAll: start; atEnd ] 
- 		whileFalse: [
- 			| chunk |
- 			(allOrLast == #last) ifTrue: [ in resetToStart ]. 
- 			chunk := html upToAll: stop.
- 			self isSkipLoadingTestsSet ifTrue: [ chunk := chunk readStream upToAll: test ].
- 			in nextPutAll: chunk. 
- 		 ].
- 
- 	^self removeHtmlMarkupFrom: in reset
- 	 
- !

Item was removed:
- ----- Method: Installer>>urlAction:reportOn: (in category 'action report') -----
- urlAction: line reportOn: report 
-  
- 	url :=  line readStream upTo: $' ; upTo: $'.
-   	
- 	self reportSection: line on: report.
- 
- 	(pageDataStream := self urlGet: self urlToDownload) 
- 		ifNil: [ self error: 'unable to contact host' ].
- 	 	
- 	self reportFor: line page: pageDataStream on: report !

Item was removed:
- ----- Method: Installer>>viewUrl (in category 'utils') -----
- viewUrl
- 
- 	^Workspace new contents: (self urlGet contents); openLabel: self urlToDownload.
- !

Item was removed:
- ----- Method: Installer class>>unload: (in category 'unload') -----
- unload: categoryMatchesString 
- 
- 	^ self error: 'deprecated, use Installer mc unload: ''pkgname''.'!

Item was removed:
- ----- Method: Installer>>uniUpdate (in category 'universes') -----
- uniUpdate
- 
- 	(LastUniUpdate isNil or:[ (DateAndTime now - LastUniUpdate) > 600 seconds  ])
- 		ifTrue: [universe requestPackageList.
- 				LastUniUpdate := DateAndTime now]!

Item was removed:
- ----- Method: Installer>>sakeInstall (in category 'actions') -----
- sakeInstall
-  
- 	self withAnswersDo: [ (self packages collect: [ :packageName | sake named: packageName ]) asTask run ].
- 	!

Item was removed:
- ----- Method: Installer class>>sourceFiles (in category 'accessing system') -----
- sourceFiles
- 
- 	^ SourceFiles!

Item was removed:
- ----- Method: Installer class>>initialize (in category 'instanciation') -----
- initialize
- 	
- 	WebSearchPath := OrderedCollection 
- 		with:  [ 'http://installer.pbwiki.com/*-', (Smalltalk version copy replaceAll: $. with: $:)  ,'-', Utilities authorInitialsPerSe  ,'?raw=bare' ]
- 		with:  [ 'http://installer.pbwiki.com/*-', (Smalltalk version copy replaceAll: $. with: $:), '?raw=bare' ]
- 		with:  [ 'http://installer.pbwiki.com/*-', (SystemVersion current majorMinorVersion replaceAll: $. with: $:)  ,'?raw=bare' ]
- 		with:  'http://installer.pbwiki.com/*?raw=bare'
- 	 
-  !

Item was removed:
- ----- Method: Installer>>ma: (in category 'accessing') -----
- ma: aUrl
- 
- 	ma := aUrl last = $/ ifTrue: [ aUrl ] ifFalse: [ aUrl, '/' ]!

Item was removed:
- ----- Method: Installer>>loadUpdatesFromDisk (in category 'updates') -----
- loadUpdatesFromDisk
- 	
- 	| updateDirectory updateNumbers |
- 	updateDirectory := self updateDirectoryOrNil.
- 	updateDirectory ifNil: [^ self].
- 	updateNumbers := updateDirectory fileNames
- 						collect: [:fn | fn initialIntegerOrNil]
- 						thenSelect: [:fn | fn notNil].
- 	
- 	self loadUpdatesFromDiskToUpdateNumber: updateNumbers max
- 		stopIfGap: false
- 		
- 	!

Item was removed:
- ----- Method: Installer>>mantisAction:reportOn: (in category 'action report') -----
- mantisAction: line reportOn: report
- 	
- 	| param mantis |
- 	mantis := Installer mantis.
- 	param :=  line readStream upTo: $: ; upTo: $..
- 	
- 	mantis setBug: ((param readStream upTo: $'; atEnd)
- 		 ifTrue: [  param ]
- 		 ifFalse: [ param readStream upTo: $'; upTo: $' ]).
- 	
- 	self reportSection: line on: report.
- 	report nextPutAll: (mantis replaceEntitiesIn: mantis markersBegin readStream).
- 	self reportFor: line page: mantis maScript on: report.
- 	report nextPutAll: (mantis replaceEntitiesIn: mantis markersEnd readStream); cr.
- 	!

Item was removed:
- ----- Method: Installer>>wsm (in category 'websqueakmap') -----
- wsm
- 	
- 	^ wsm!

Item was removed:
- ----- Method: Installer>>smVersions (in category 'squeakmap') -----
- smVersions
-  
- 	^ (self smReleasesForPackage: self package) 
- 			collect: [ :v | self copy package: (v package name,'(',v version,')'); yourself. ] 
- 
-  !

Item was removed:
- ----- Method: Installer>>universe: (in category 'universes') -----
- universe: u
- 
- 	universe := u.
- 	self uniUpdate.!

Item was removed:
- ----- Method: Installer>>fixBug:date: (in category 'mantis') -----
- fixBug: aBugNo date: aDate
- 
- 	self setBug: aBugNo.
-  	self install: self maUrl from: self maScript.
- 	self maCheckDateAgainst: aDate.
- 	
- 	
- 	
- !

Item was removed:
- ----- Method: Installer>>desc: (in category 'accessing') -----
- desc: anObject
- 
- 	desc := anObject!

Item was removed:
- ----- Method: Installer>>wsmPackagesByName (in category 'websqueakmap') -----
- wsmPackagesByName
- 
- 	| html id name pkgs | 
- 	pkgs := Dictionary new.
- 	html := self httpGet: (self wsm, 'packagesbyname').
- 	
- 	[ id := html upToAll: '/package/'; upToAll: '">'.
- 	name := html upTo: $<.
- 	(id notEmpty and: [ name notEmpty ])] 
- 		whileTrue: [ pkgs at: name put: id ].
- 
- 	^ pkgs	
- 	!

Item was removed:
- ----- Method: Installer class>>file: (in category 'instanciation') -----
- file: fileName
-  
- 	^ self new file: fileName; yourself
- !

Item was removed:
- ----- Method: Installer>>classMCSmtpRepository (in category 'class references') -----
- classMCSmtpRepository
- 
- 	^Smalltalk at: #MCSmtpRepository ifAbsent: [ self error: 'Monticello not present' ]
- 	!

Item was removed:
- ----- Method: Installer class>>classSakePackages (in category 'accessing system') -----
- classSakePackages
- 
- 	^Smalltalk at: #SakePackages  ifAbsent: [ self error: 'Sake Packages code not present' ]!

Item was removed:
- ----- Method: Installer>>fileView (in category 'file') -----
- fileView
- 	
- 	self view: self file from:  (FileDirectory readOnlyFileNamed: self file).
- 
- 	!

Item was removed:
- ----- Method: Installer>>smUpdate (in category 'squeakmap') -----
- smUpdate
- "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 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 := 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 wait!

Item was removed:
- ----- Method: Installer>>justFixBug:date: (in category 'mantis') -----
- justFixBug: aBugNo date: d
- 
- 	^self class skipLoadingTests: true during: [ self fixBug: aBugNo date: d ]!

Item was removed:
- ----- Method: Installer>>ensureFix: (in category 'mantis') -----
- ensureFix: aBugNo
- 
- 	| fixesAppliedNumbers |
- 	self setBug: aBugNo.
- 	fixesAppliedNumbers := self class fixesApplied collect: [ :fixDesc | fixDesc asInteger ].
- 	(fixesAppliedNumbers includes: bug) ifFalse: [ self fixBug: aBugNo ]!

Item was removed:
- ----- Method: Installer>>date: (in category 'accessing') -----
- date: anObject
- 
- 	date := anObject asDate!

Item was removed:
- ----- Method: Installer>>httpGet: (in category 'utils') -----
- httpGet: aUrl
- 
- 	| page |
- 	page := self classHTTPSocket httpGet: aUrl accept: 'application/octet-stream'.  
-  
- 	(page respondsTo: #reset)  ifFalse: [ self error: 'unable to contact web site' ].
- 	^ page
- 	!

Item was removed:
- ----- Method: Installer>>info (in category 'accessing') -----
- info
- 
- 	self sm ifTrue: [ ^ self smInfo  ].
- 	self wsm ifNotNil: [ ^ self wsmInfo  ].!

Item was removed:
- ----- Method: Installer>>parseUpdateListContents: (in category 'updates') -----
- parseUpdateListContents: listContentString
- 	"Parse the contents of an updates.list into {{releaseTag. {fileNames*}}*}, and return it."
- 
- 	| sections releaseTag strm line fileNames |
- 	sections := OrderedCollection new.
- 	fileNames := OrderedCollection new: 1000.
- 	releaseTag := nil.
- 	strm := ReadStream on: listContentString.
- 	[strm atEnd] whileFalse:
- 		[line := strm upTo: Character cr.
- 		line size > 0 ifTrue:
- 			[line first = $#
- 				ifTrue: [releaseTag ifNotNil: [sections addLast: {releaseTag. fileNames asArray}].
- 						releaseTag := line allButFirst.
- 						fileNames resetTo: 1]
- 				ifFalse: [line first = $* ifFalse: [fileNames addLast: line]]]].
- 	releaseTag ifNotNil: [sections addLast: {releaseTag. fileNames asArray}].
- 	^ sections asArray
- !

Item was removed:
- ----- Method: Installer>>bugFilesView: (in category 'mantis') -----
- bugFilesView: aBugNo
-  	
- 				
- 	(self bugFiles: aBugNo) do: [ :ea | self bug: aBugNo view: ea ].!

Item was removed:
- ----- Method: Installer>>wsmReleasesFor: (in category 'websqueakmap') -----
- wsmReleasesFor: packageId
- 
- 	| html autoVersion version releases |
- 	releases := Dictionary new.
- 	html := self httpGet: (self wsm, '/package/', packageId ).
- 	[releases at: #latest put: autoVersion.
- 	autoVersion := html upToAll: '/autoversion/'; upTo: $".
- 	version := html upTo: $-; upTo: $<.
- 	(autoVersion notEmpty and: [version notEmpty ])] 
- 		whileTrue: [ releases at: version put: autoVersion ].
- 	^ releases
- 	!

Item was removed:
- ----- Method: Installer>>http: (in category 'monticello') -----
- http: aUrl  
- 	
- 	self http: aUrl user: 'squeak' password: 'squeak'
- 		
-  !

Item was removed:
- ----- Method: Installer>>smView (in category 'squeakmap') -----
- smView
- 
- 	self smThing explore!

Item was removed:
- ----- Method: Installer>>classMCVersionLoader (in category 'class references') -----
- classMCVersionLoader
- 
- 	^Smalltalk at: #MCVersionLoader  ifAbsent: [ self error: 'Monticello not present' ]!

Item was removed:
- ----- Method: Installer>>reportFor:page:on: (in category 'action report') -----
- reportFor: theLine page: thePage on: report 
-  	
- 	[ thePage atEnd ] whileFalse: [ 
- 		| line |
- 		line := thePage nextLine.
- 		self actionMatch: line reportOn: report ifNoMatch: [ report nextPutAll: line; cr. ]].!

Item was removed:
- ----- Method: Installer>>webAction:reportOn: (in category 'action report') -----
- webAction: line reportOn: report
- 	
- 	self package: (line readStream upTo: $' ; upTo: $').
- 
- 	self reportSection: line on: report.
- 	
-  	url := self webFindUrlToDownload.
- 	
- 	self reportFor: line page: pageDataStream on: report !

Item was removed:
- ----- Method: Installer>>webInstall (in category 'web install') -----
- webInstall
-  
-  	 self webThing size > 0 
- 		ifTrue: [ self install: url from: pageDataStream ]
- 		ifFalse: [ url ifNil: [ ^ self logCR: self package, ' not found on webSearchPath' ].
- 				  self logCR: '...',url,' was empty' ].
- 	 !

Item was removed:
- ----- Method: Installer>>smPackageAndVersion (in category 'squeakmap') -----
- smPackageAndVersion
- 
- 	| p |
- 	p := ReadStream on: self package .
- 	^Array with: (p upTo: $() with: (p upTo: $)).!

Item was removed:
- ----- Method: Installer>>sake: (in category 'websqueakmap') -----
- sake: aSakePackagesClass
- 
- 	sake := aSakePackagesClass!

Item was removed:
- ----- Method: Installer>>mcVersions (in category 'monticello') -----
- mcVersions
- 
- 	^ (self availablePackages select: [ :p | ( self package,'-*.mcz' ) match: p ]) collect: [ :p | self copy package: p  ; yourself ].
-  !

Item was removed:
- ----- Method: Installer>>smBrowse (in category 'squeakmap') -----
- smBrowse
- 
- 	self smThing explore!

Item was removed:
- ----- Method: Installer>>bug: (in category 'mantis') -----
- bug: aBugNo
- 	"Installer mantis viewBug: 5639."
- 	| page text | 
- 
- 	self setBug: aBugNo.
- 	
- 	page := self maPage.
-  
- 	text := String streamContents: [ :str |	
- 			
- 		#('Bug ID' 'Category' 'Severity' 'Reproducibility' 'Date Submitted' 
- 			'Date Updated' 'Reporter' 'View Status' 'Handler' 
- 			'Priority' 'Resolution' 'Status' 'Product Version' 'Summary' 'Description' 'Additional Information' ) 
- 				do: [ :field |
- 						| f |
- 						f := self maRead: page field: field.
- 			str nextPutAll: f key; nextPutAll: ': '; nextPutAll: f value; cr.
- 		].
- 	
- 	str nextPutAll: 'Notes: '; cr.
- 		(self maReadNotes: page) do: [ :note | str nextPutAll: note; cr; cr ].
- 		
- 		str nextPutAll: 'Files: '; nextPutAll: self maFiles keys asArray printString.
- 	].
-  	^ text	
- !

Item was removed:
- ----- Method: Installer>>bugScript: (in category 'mantis') -----
- bugScript: aBugNo
- 
- 	self setBug: aBugNo.
-  	^ self maScript contents.
- 	 
- 	
- 	
- !

Item was removed:
- ----- Method: Installer class>>fixesApplied (in category 'accessing') -----
- fixesApplied
- 
- 	^ Fixes ifNil: [ Fixes := OrderedCollection new ].!

Item was removed:
- ----- Method: Installer class>>classes (in category 'accessing system') -----
- classes
- 
- 	^ Smalltalk!

Item was removed:
- ----- Method: Installer>>webView (in category 'web install') -----
- webView
-  
-  	 self webThing size > 0 
- 		ifTrue: [ self view: url from: pageDataStream ]
- 		ifFalse: [ self logCR: 'NO DATA ',url,' was empty' ].
- 	 !

Item was removed:
- ----- Method: Installer>>bug:browse: (in category 'mantis') -----
- bug: aBugNo browse: aFileName
- 
- 	 self setBug: aBugNo.
- 	^ self browse: aFileName from: (self maThing: aFileName date: nil)!

Item was removed:
- ----- Method: Installer class>>classProjectLauncher (in category 'accessing system') -----
- classProjectLauncher
- 
- 	^Smalltalk at: #ProjectLauncher ifAbsent: [ self error: 'ProjectLauncher not present' ]!

Item was removed:
- ----- Method: Installer class>>do: (in category 'launcher support') -----
- do: webPageName
- 
- 	| rs |
- 	self webSearchPath isEmpty ifTrue: [ ^self error: 'search path not set' ].
- 	rs := webPageName readStream.
- 	[ rs atEnd ] whileFalse: [ self install: (rs upTo: $;) ].
- !

Item was removed:
- ----- Method: Installer>>webFindUrlToDownload (in category 'web install') -----
- webFindUrlToDownload
- 
- 	| delay retry |
- 	delay := 0.
- 	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 ] 
- 						doWhileTrue: [ 	
- 								(pageDataStream notNil and: [ pageDataStream size > 0 ]) 
- 									ifTrue: [ (pageDataStream contents includesSubString: 'Please slow down a bit') 
- 													ifTrue: [ retry := true ]
- 													ifFalse: [ pageDataStream reset. 
- 																^ potentialUrl ] ].
- 								(Delay forSeconds: (delay := delay + 5)) wait.
- 								retry ]].
- 	^nil
- !

Item was removed:
- ----- Method: Installer>>classMCCacheRepository (in category 'class references') -----
- classMCCacheRepository
- 
- 	^Smalltalk at: #MCCacheRepository ifAbsent: [ self error: 'Monticello not present' ]
- 	!

Item was removed:
- ----- Method: Installer>>maCheckDateAgainst: (in category 'utils') -----
- maCheckDateAgainst: okDate
- 
- 	(okDate notNil and: [date < okDate asDate ]) 
- 		ifTrue: [ self notify: 'bug ', self bug asString, ' updated on ', date printString ].
-  !

Item was removed:
- ----- Method: Installer>>maReadNotes: (in category 'mantis') -----
- maReadNotes: page 
- 
- 	 |  notes note  |
-  
- 	notes := OrderedCollection new.
- 
- 	[ page upToAll: 'tr class="bugnote"'; upTo: $>.
- 	  page atEnd ]
- 		
- 	whileFalse: [ 
- 		note := (self removeHtmlMarkupFrom: (page upToAll: '</tr>') readStream) contents.
- 		note := note withBlanksCondensed.
- 		"note replaceAll: Character cr with: $ ."
- 		note replaceAll: Character lf with: Character cr.
- 		notes add: note  
- 	].
- 	
- 	^notes!

Item was removed:
- ----- Method: Installer>>mcView (in category 'monticello') -----
- mcView
- 	 "Installer ss project: 'Installer'; view: 'Installer-Core'. "
- 	| it |
- 	it := self mcThing. 
- 	(it respondsTo: #open) ifTrue: [ ^ it open ].
- 
- 	(MCSnapshotBrowser forSnapshot: it)
- 		showLabelled: 'Snapshot of ', self package!

Item was removed:
- ----- Method: Installer>>smThing (in category 'squeakmap') -----
- smThing 
- 
- 	| pkgAndVersion releases release |
- 	pkgAndVersion := self packageAndVersionFrom: self package.
- 	self logCR: 'retrieving ', self package, ' from SqueakMap...'.
- 	releases := self smReleasesForPackage: pkgAndVersion first.
- 	release := pkgAndVersion last isEmpty 
- 				ifTrue: [ releases last ]
- 				ifFalse:[ releases detect: [ :rel | rel version = pkgAndVersion last ] ]. 
- 	^ release
- 		
- 	
- !

Item was removed:
- ----- Method: Installer>>classMCDirectoryRepository (in category 'class references') -----
- classMCDirectoryRepository
- 
- 	^Smalltalk at: #MCDirectoryRepository ifAbsent: [ self error: 'Monticello not present' ]
- 	!

Item was removed:
- ----- Method: Installer>>maUrlFor: (in category 'mantis') -----
- maUrlFor: maBugNo
-  
- 	^ url := self ma, 'view.php?id=', maBugNo asString 
-  !

Item was removed:
- ----- Method: Installer class>>classPackages (in category 'accessing system') -----
- classPackages
- 
- 	^Smalltalk at: #Packages  ifAbsent: [ self error: 'Sake Packages code not present' ]!

Item was removed:
- ----- Method: Installer>>webThing (in category 'web install') -----
- webThing
-  
-  	url := self webFindUrlToDownload.
- 	url ifNil: [ self logCR: 'page ', self package, ' not found on path' ]
- 		ifNotNil: [ self logCR: 'found ',  url, ' ...'.   ].
- 	^ pageDataStream!

Item was removed:
- ----- Method: Installer class>>view: (in category 'instanciation') -----
- view: webPageNameOrUrl
- 
- 	| theReport |
- 
- 	theReport := String streamContents: [ :report | 
- 	(webPageNameOrUrl beginsWith: 'http://') ifTrue: [ 
- 		self new urlAction: ('Installer installUrl: ', (webPageNameOrUrl printString),'.')  	
- 						 reportOn: report.
- 	]
- 	ifFalse: [
- 		self new webAction: ('Installer install: ', (webPageNameOrUrl printString),'.')  	
- 						 reportOn: report.
- 	]].
- 
- 	Workspace new contents: (theReport contents); openLabel: webPageNameOrUrl.
- 
- 	^theReport contents
- !

Item was removed:
- ----- Method: Installer>>wsmView (in category 'websqueakmap') -----
- wsmView
- 	
- 	| it |
- 	it := self wsmThing.
- 	self view: it from: (self httpGet: it).
- 
- 	!

Item was removed:
- ----- Method: Installer>>reportSection:on: (in category 'action report') -----
- reportSection: line on: report
- 	
- 	report isEmpty ifFalse: [ report cr ].
- 	report nextPutAll: '">>>> ' ; nextPutAll: (line copyWithout: $"); nextPut: $"; cr.
- 
- 	!

Item was removed:
- ----- Method: Installer>>classSMSqueakMap (in category 'class references') -----
- classSMSqueakMap
- 
- 	^Smalltalk at: #SMSqueakMap  ifAbsent: [ self error: 'SqueakMap not present' ]!

Item was removed:
- ----- Method: Installer>>bug (in category 'accessing') -----
- bug
- 	
- 	^ bug!

Item was removed:
- ----- Method: Installer>>maFiles (in category 'mantis') -----
- maFiles
-  	| file files bugPage id  | 
-  	files := Dictionary new.
-  	bugPage := self maPage.
- 	 [ 
- 		id := bugPage upToAll: 'href="file_download.php?file_id='; upTo: $&. 
-  		file := bugPage upToAll: 'amp;type=bug"' ; upTo: $<.
-  		((file size > 1) and: [file first = $>]) ifTrue: [ files at: file copyWithoutFirst put: id ].
-  		id notEmpty ] whileTrue.
- 
- 	^files !

Item was removed:
- ----- Method: Installer>>classSMLoader (in category 'class references') -----
- classSMLoader
- 
- 	^Smalltalk at: #SMLoader  ifAbsent: [ self error: 'SqueakMap Loader not present' ]!

Item was removed:
- ----- Method: Installer>>skipTests (in category 'mantis') -----
- skipTests
- 
- !

Item was removed:
- ----- Method: Installer>>project (in category 'accessing') -----
- project
- 
- 	^ project!

Item was removed:
- ----- Method: Installer>>smSearch: (in category 'searching') -----
- smSearch: aMatch  
- 
- 	| results |
- 	results := Set new.
- 	self availablePackages do: [ :pkg |
- 		({ 'name:',pkg name.
- 		   'summary:', pkg summary.
- 		   'description:', pkg description.
- 		   'author:', pkg author. } anySatisfy: [ :field | aMatch match: field ])
- 		 ifTrue: [ results add: (self copy package: pkg name) ]. 
- 	].
- 	^results
- 
- !

Item was removed:
- ----- Method: Installer>>smReleasesForPackage: (in category 'squeakmap') -----
- smReleasesForPackage: name 
- 
- 	^(self classSMSqueakMap default packageWithName: name) releases!

Item was removed:
- ----- Method: Installer>>changesetNamesFromUpdates:through: (in category 'updates') -----
- changesetNamesFromUpdates: startNumber through: stopNumber
- 	"Answer the concatenation of summary strings for updates numbered in the given range"
- 	"self new changesetNamesFromUpdates: 7059 through: 7061"
- 	
- 	^ String streamContents: [:aStream |
- 		((ChangeSet changeSetsNamedSuchThat:
- 			[:aName | aName first isDigit and:
- 						[aName initialIntegerOrNil >= startNumber] and:
- 						[aName initialIntegerOrNil <= stopNumber]]) asSortedCollection:
- 				[:a :b | a name < b name]) do:
- 					[:aChangeSet | aStream cr; nextPutAll: aChangeSet summaryString]]
- 
- 
- 
- !

Item was removed:
- ----- Method: Installer>>markersEnd (in category 'url') -----
- markersEnd
- 	"return the third marker or the second if there are only two"
- 	
- 	| str  a | 
- 	str := self markers readStream.
- 	a := str upToAll: '...'; upToAll: '...'.
- 	str atEnd  ifTrue: [ ^a ] ifFalse: [ ^str upToEnd ]
- 	!

Item was removed:
- ----- Method: Installer>>markersTest (in category 'url') -----
- markersTest
- 		 	 
- 	^ self markers readStream upToAll: '...'; upToAll: '...'!

Item was removed:
- ----- Method: Installer>>isHtmlStream: (in category 'url') -----
- isHtmlStream: page
- 	"matches  '<!!DOCTYPE HTML', and <html>' "
- 	
- 	| first |	
- 	first := (page next: 14) asUppercase.
- 	^ (first = '<!!DOCTYPE HTML') | (first beginsWith: '<HTML>')
- 	
- !

Item was removed:
- ----- Method: Installer>>sm (in category 'accessing') -----
- sm
- 
- 	^ sm ifNil: [ false ]!

Item was removed:
- ----- Method: Installer>>universe (in category 'universes') -----
- universe
- 
- 	^ universe!

Item was removed:
- ----- Method: Installer>>fixBug: (in category 'mantis') -----
- fixBug: aBugNo
- 
- 	^ self fixBug: aBugNo date: nil!

Item was removed:
- ----- Method: Installer>>ensureFixes: (in category 'mantis') -----
- ensureFixes: aBugNos
- 
- 	aBugNos do: [ :bugNo | self ensureFixes: bugNo ].!

Item was removed:
- ----- Method: Installer>>mcThing (in category 'monticello') -----
- mcThing
- 
- 	| loader files fileToLoad  version  count |
- 
- 	loader := self classMCVersionLoader new.
- 	
- 	1 to: self packages size do: [ :n |
- 
- 		self logCR: 'finding ', self package asString, '...'.
- 		"several attempts to read files - repository readableFileNames sometimes fails"
- 		count := 0. fileToLoad := nil.
- 	
- 		[count := count + 1.
- 		 (fileToLoad = nil) and:[ count < 5 ] ] 
- 			whileTrue: [
- 							files := mc readableFileNames asSortedCollection: self mcSortFileBlock.
- 							fileToLoad := files detect: self mcDetectFileBlock ifNone: [ nil ].
- 		].
- 
- 		version := mc versionFromFileNamed: fileToLoad.
- 		(version isKindOf: MCConfiguration) 
- 			ifTrue: [ ^ version ]
- 			ifFalse:[version workingCopy repositoryGroup addRepository: mc.
- 				loader addVersion: version].
- 		self log: ' found ', version fileName, '...'.
- 
- 		packages removeFirst.
- 	].
- 
- 	^ loader!

Item was removed:
- ----- Method: Installer>>bugFiles: (in category 'mantis') -----
- bugFiles: aBugNo
-  	"provide a list of files associated with the bug in id order"
- 	"
- 	Installer mantis bugFiles: 6660.
- 	"
- 	self setBug: aBugNo.
- 	^ (self maFiles associations asSortedCollection: [ :a :b | a value asInteger < b value asInteger ]) 
- 				collect: [ :a | a key ]!

Item was removed:
- ----- Method: Installer>>replaceEntitiesIn: (in category 'url') -----
- replaceEntitiesIn: in
- 
- 	| out |
- 	out := ReadWriteStream on: (String new: 100).
- 	[ in atEnd ] whileFalse: [ 
- 		out nextPutAll: ((in upTo: $&) replaceAll: Character lf with: Character cr).
- 		in atEnd ifFalse: [ out nextPutAll: (self class entities at: (in upTo: $;) ifAbsent: '?') ].	
- 	].
- 
- 	^out reset!

Item was removed:
- ----- Method: Installer>>unloadCleanUp (in category 'actions') -----
- unloadCleanUp
-  
- 	SystemOrganization removeEmptyCategories.
- 
- 	"Until Mantis 5718 is addressed"
-  	Smalltalk at: #PackagePaneBrowser ifPresent: [ :ppbClass | ppbClass allInstancesDo: [ :ppb | ppb updatePackages ]  ].
-  	Smalltalk at: #Browser ifPresent: [ :bClass | bClass allInstancesDo: [ :b | b updateSystemCategories ] ].
- 	MCFileBasedRepository freeSomeSpace.
- 	SmalltalkImage current fixObsoleteReferences.!

Item was removed:
- ----- Method: Installer>>loadUpdatesFromDiskToUpdateNumber:stopIfGap: (in category 'updates') -----
- loadUpdatesFromDiskToUpdateNumber: lastUpdateNumber stopIfGap: stopIfGapFlag 
- 	"To use this mechanism, be sure all updates you want to have considered 
- 	are in a folder named 'updates' which resides in the same directory as  
- 	your image. Having done that, simply evaluate:  
- 	 
- 	Installer new loadUpdatesFromDiskToUpdateNumber: 100020 stopIfGap: false  
- 	 
- 	and all numbered updates <= lastUpdateNumber not yet in the image will 
- 	be loaded in numerical order."
- 	
- 	"apparently does not use the updatelist too bad!! and to rewrite - sd 7 March 2008"
- 	| previousHighest currentUpdateNumber done fileNames aMessage updateDirectory loaded |
- 	updateDirectory := self updateDirectoryOrNil.
- 	updateDirectory ifNil: [^ self].
- 	previousHighest := SystemVersion current highestUpdate.
- 	currentUpdateNumber := previousHighest.
- 	done := false.
- 	loaded := 0.
- 	[done]
- 		whileFalse: [currentUpdateNumber := currentUpdateNumber + 1.
- 			currentUpdateNumber > lastUpdateNumber
- 				ifTrue: [done := true]
- 				ifFalse: [fileNames := updateDirectory fileNamesMatching: currentUpdateNumber printString , '*'.
- 					fileNames size > 1
- 						ifTrue: [^ self inform: 'ambiguity -- two files both start with ' , currentUpdateNumber printString , '
- (at this point it is probably best to remedy
- the situation on disk, then try again.)'].
- 					fileNames size == 0
- 						ifTrue: [Transcript cr; show: 'gap in updates from disk for update number '; print: currentUpdateNumber; show: ' found...'.
- 							done := stopIfGapFlag]
- 						ifFalse: [ChangeSet
- 								newChangesFromStream: (updateDirectory readOnlyFileNamed: fileNames first)
- 								named: fileNames first.
- 							SystemVersion current registerUpdate: currentUpdateNumber.
- 							loaded := loaded + 1]]].
- 	aMessage := loaded = 0
- 				ifTrue: ['No new updates found.']
- 				ifFalse: [loaded printString , ' update(s) loaded.'].
- 	self inform: aMessage , '
- Highest numbered update is now ' , (currentUpdateNumber - 1) printString , '.'!

Item was removed:
- ----- Method: Installer>>mc: (in category 'accessing') -----
- mc: aUrl
- 
- 	mc := aUrl last = $/ ifTrue: [ aUrl ] ifFalse: [ aUrl, '/' ]!

Item was removed:
- ----- Method: Installer>>desc (in category 'accessing') -----
- desc
- 	 
- 	^ desc!

Item was removed:
- ----- Method: Installer>>smInstall (in category 'squeakmap') -----
- smInstall 
- 
- 	self log: ' installing '. 
- 	self withAnswersDo: [ self smThing install ].
- 	self log: ' done'.
- !

Item was removed:
- ----- Method: Installer>>markers (in category 'accessing') -----
- markers
- 
- 	^ markers ifNil: [ '<code st>..."test ...</code st>' ]!

Item was removed:
- ----- Method: Installer>>classHTTPSocket (in category 'class references') -----
- classHTTPSocket
- 
- 	^Smalltalk at: #HTTPSocket ifAbsent: [ self error: 'Network package not present' ]!

Item was removed:
- ----- Method: Installer class>>history (in category 'documentation') -----
- history
- 
- "
- 7 Jan 2007  
- !!Installer fixBug: <aBugNo>
- 
- aBugNo can now be a number or a string, beginning with a number. 
- This allows the mantis bug report summary to be used verbatim.
- It also provides more infomarion for Installer to support self documentation.
- 
- !!Install fix if not already installed
-  Installer ensureFix: <aBugNoOrString>
-  Installer ensureFixes: #(1 2 3 4)
- 
- Installer now keeps a list of fix <aBugNoOrString> that have been installed up to this point.
- #ensureFix: will only install the fix if it has not already been loaded.
- note that only the bugNumber not the description is significant in the check.
- 
- 8 Jan 2007
- !!Installer view: <webPageNameOrUrl>
- 
- Provided that web page based scripts follow some simple rules, installer can collate the scripts from 
- web pages into a single workspace where you can manually 'doit' portions as you wish.
- 
- The report generation is not very clever, it only matches on:
-  'Installer install:' ,  'Installer installUrl:', and 'Installer mantis fixBug:'
-  note these lines must be properly completed with an ending $. (period).
- 
- also invoked by commandline option VIEW=<webPageNameOrUrl>
- 
- 10 Jan 2007
- !!Now matches simpler html
- 
- Check for an html page, now matches
- '<!!DOCTYPE HTML' and <html> 
- the allows use of pbwiki's raw=bare option which returns iframe 
- embeddable html without the usual headers.
- 
- 8 May 2007
- Modified bug:fix:date: so that the fixesApplied history does not contain unnecessary duplicate entries.
- Fixed changeset naming for mantis bugs.
- 
- 25 July 2007
- Added Universes  Support
- "!

Item was removed:
- ----- Method: Installer class>>classUGlobalInstaller (in category 'accessing system') -----
- classUGlobalInstaller
- 
- 	^Smalltalk at: #UGlobalInstaller  ifAbsent: [ self error: 'Universes code not present' ]!

Item was removed:
- ----- Method: Installer class>>classUUniverse (in category 'accessing system') -----
- classUUniverse
- 
- 	^Smalltalk at: #UUniverse  ifAbsent: [ self error: 'Universes code not present' ]!

Item was removed:
- ----- Method: Installer>>wsm: (in category 'websqueakmap') -----
- wsm: aUrl
-  
- 	wsm := aUrl last = $/ ifTrue: [ aUrl ] ifFalse: [ aUrl, '/' ]!

Item was removed:
- ----- Method: Installer>>goran (in category 'instanciation-abbreviated') -----
- goran
- 
- 	^ self monticello http: 'squeak.krampe.se'; project: ''!

Item was removed:
- ----- Method: Installer>>maThing:date: (in category 'mantis') -----
- maThing: aFileName date: aDate
-  
- 	self logCR: 'obtaining ', aFileName, '...'.
- 
- 	pageDataStream := self maStreamForFile: aFileName.
- 
- 	self maCheckDateAgainst: aDate.
- 
- 	^ pageDataStream
- 	!

Item was removed:
- ----- Method: Installer>>actionMatch:reportOn:ifNoMatch: (in category 'action report') -----
- actionMatch: theLine reportOn: report ifNoMatch: aBlock
- 
- 	| line |	
- 	line := theLine withBlanksCondensed.
- 	((line beginsWith: 'Installer install:') | (line beginsWith: 'Installer do:')) 
- 		ifTrue: [ ^self webAction: theLine reportOn: report ].
- 		
- 	((line beginsWith: 'Installer installUrl:') and: 
- 		[ | ext |
- 		 ext :=  (line readStream upToAll: '''.') copyAfterLast: $..
- 		 (#( 'cs' 'st' 'mcz' 'sar') includes: ext) not ]) ifTrue: [ ^self urlAction: theLine reportOn: report ].
- 
- 	(line beginsWith: 'Installer mantis fixBug:') ifTrue: [ ^self mantisAction: theLine reportOn: report ].
- 	aBlock value.
- !

Item was removed:
- ----- Method: Installer>>ma (in category 'accessing') -----
- ma
- 
- 	^ ma!

Item was removed:
- ----- Method: Installer>>urlGet (in category 'url') -----
- urlGet
- 
- 	^ self urlGet: self urlToDownload!

Item was removed:
- ----- Method: Installer>>file (in category 'accessing') -----
- file
- 
- 	^ afile!

Item was removed:
- ----- Method: Installer>>bug:fix: (in category 'mantis') -----
- bug: aBugNo fix: aFileName
- 
- 	^ self bug: aBugNo fix: aFileName date: nil!

Item was removed:
- ----- Method: Installer class>>launchHelp (in category 'launcher support') -----
- launchHelp
- 
- ^'path=/dir/*.txt          Specify a search path for the item to install
- p=/dir1/*.txt;<url2>/    Multiple items delimited by ;
-                          The page name is typically appended to the path string, or
-                          if a "*" is present, it will be replaced by the page name.
- 					
- in,i,install=<page>      Page appended to the path to begin the install process
- url,u=<url>              Install using an explicit url from which to obtain a script or file
- file=<url>                Install using a local file
- +debug                   Do not trap errors
- view=<page>              Print the script that would have been installed.
- 
- For more options use Script eval="Installer ... " 
- '
- !

Item was removed:
- ----- Method: Installer>>packageAndVersionFrom: (in category 'squeakmap') -----
- packageAndVersionFrom: pkg
- 
- 	| p |
- 	p := ReadStream on: pkg .
- 	^Array with: (p upTo: $() with: (p upTo: $)).!

Item was removed:
- ----- Method: Installer>>mczInstall: (in category 'monticello') -----
- mczInstall: urlOrFile
- 
- 	self log: ('Loading ', urlOrFile, ' ...').
- 
- 	(urlOrFile beginsWith: 'http:')
- 		ifTrue: [  MczInstaller installStream: (HTTPSocket httpGet: urlOrFile) ]
- 		ifFalse: [ MczInstaller installFileNamed: urlOrFile ].
- 		
- 	self logCR: ' Loaded'.
- 
- 	
- 
- !

Item was removed:
- ----- Method: Installer>>classMCFtpRepository (in category 'class references') -----
- classMCFtpRepository
- 
- 	^Smalltalk at: #MCFtpRepository ifAbsent: [ self error: 'Monticello not present' ]
- 	!

Item was removed:
- ----- Method: Installer>>classMCMagmaRepository (in category 'class references') -----
- classMCMagmaRepository
- 
- 	^Smalltalk at: #MCMagmaRepository ifAbsent: [ self error: 'Magma not present' ]
- 	!

Item was removed:
- ----- Method: Installer>>maStreamForFile: (in category 'mantis') -----
- maStreamForFile: aFileName
- 
- 	| fileId  |
- 
-  	fileId :=  self maFiles at: aFileName ifAbsent: [ self error: aFileName, ' not found' ].
- 
-  	^ self httpGet: (self ma, 'file_download.php?file_id=' , fileId , '&type=bug').
- 	 !

Item was removed:
- ----- Method: Installer>>cache (in category 'monticello') -----
- cache
- 	
- 	mc := self classMCCacheRepository default.
- 	root := mc directory localName
-  !

Item was removed:
- ----- Method: Installer class>>installFile: (in category 'instanciation') -----
- installFile: fileName
-  
- 	^ (self file: fileName) install.
- !

Item was removed:
- ----- Method: Installer>>webBrowse (in category 'web install') -----
- webBrowse
-  
-  	 self webThing size > 0 
- 		ifTrue: [ self browse: url from: pageDataStream ]
- 		ifFalse: [ self logCR: 'NO DATA ',url,' was empty' ].
- 	 !

Item was removed:
- ----- Method: Installer>>fileBrowse (in category 'file') -----
- fileBrowse
- 	
- 	self browse: self file from:  (FileDirectory readOnlyFileNamed: self file).
- 
- 	!

Item was removed:
- ----- Method: Installer>>magma:port: (in category 'monticello') -----
- magma: host port: aport
- 	
- 	mc := (self classMCMagmaRepository new) host: host port: aport; yourself
-  !

Item was removed:
- ----- Method: Installer>>goods:port: (in category 'monticello') -----
- goods: host port: aport
- 	
- 	mc := (self classMCGOODSRepository new) host: host port: aport; yourself
-  !

Item was removed:
- ----- Method: Installer>>mcBrowse (in category 'monticello') -----
- mcBrowse
- 	 "Installer ss project: 'Installer'; browse: 'Installer-Core'."
- 
- 	| it |
- 	it := self mcThing.
- 	
- 	(it respondsTo: #browse) ifTrue: [ ^ it browse ].
- 	
- 	(MCSnapshotBrowser forSnapshot: it)
- 		showLabelled: 'Snapshot of ', self package!

Item was removed:
- ----- Method: Installer>>mcUrl (in category 'monticello') -----
- mcUrl
- 
- 	^ self mc, (self project ifNil: [''])!

Item was removed:
- ----- Method: Installer>>createRBforBug: (in category 'mantis') -----
- createRBforBug: aBugNo 
- 	| aStream  fileList selFile aFileName |
- 
- 	self setBug: aBugNo.
- fileList := self maFiles keys asOrderedCollection.
- fileList  addLast: 'none'.
- ReleaseBuilderFor3dot10 clear.
- [selFile := UIManager default chooseFrom: fileList title: 'Choose what files load '.
- selFile = fileList size ifFalse:[
- aFileName := fileList at: selFile.
- 	self logCR: 'obtaining ', aFileName, '...'.
- 
- 	aStream := self maStreamForFile: aFileName .
- 	ReleaseBuilderFor3dot10 current packagesInfluenced: aStream named: aFileName.
- 	
- 	self installCS: aFileName from: aStream].selFile = fileList size]whileFalse.
- 	
- 	ReleaseBuilderFor3dot10 current newUpdateFor: aBugNo
- 	
- 	
- 	!

Item was removed:
- ----- Method: Installer>>classMCGOODSRepository (in category 'class references') -----
- classMCGOODSRepository
- 
- 	^Smalltalk at: #MCGOODSRepository ifAbsent: [ self error: 'Monticello not present' ]
- 	!

Item was removed:
- ----- Method: Installer>>viewBug: (in category 'mantis') -----
- viewBug: aBugNo
- 
- 	^Workspace new contents: (self bug: aBugNo); openLabel: ('Mantis ', aBugNo printString).
- !

Item was removed:
- ----- Method: Installer>>bug:fix:date: (in category 'mantis') -----
- bug: aBugNo fix: aFileName date: aDate
-  
- 	| fixed |
- 	self setBug: aBugNo.
- 	self ditchOldChangeSetFor: aFileName.
- 	self install: aFileName from: (self maThing: aFileName date: aDate).
- 
- 	fixed := self class fixesApplied.
- 	(fixed isEmpty or: [ fixed last ~= aBugNo]) ifTrue: [ fixed add: aBugNo ].
- 		
- 	^ date!

Item was removed:
- ----- Method: Installer>>mc (in category 'accessing') -----
- mc
- 
- 	^ mc!

Item was removed:
- ----- Method: Installer>>markersBegin (in category 'url') -----
- markersBegin
- 		 	 
- 	 ^ self markers copyUpTo: $.!

Item was removed:
- ----- Method: Installer>>removeHtmlMarkupFrom: (in category 'url') -----
- removeHtmlMarkupFrom: in 
- 
- 	| out |
- 	out := ReadWriteStream on: (String new: 100).
- 	[ in atEnd ] whileFalse: [ 
- 		out nextPutAll: (in upTo: $<).
- 		(((in upTo: $>) asLowercase beginsWith: 'br') and: [ (in peek = Character cr) ]) ifTrue: [ in next ].	
- 	].
- 	
- 	^self replaceEntitiesIn: out reset.
- !

Item was removed:
- ----- Method: Installer>>sm: (in category 'accessing') -----
- sm: anObject
- 
- 	sm := anObject!

Item was removed:
- ----- Method: Installer>>urlToDownload (in category 'url') -----
- urlToDownload
- 
- 	^ (self url, (self package ifNil: [ '' ])) asUrl asString.
- 	
-  !

Item was removed:
- ----- Method: Installer class>>mczInstall: (in category 'documentation') -----
- mczInstall: urlOrFile
- 
- 	^ self new mczInstall: urlOrFile
- !

Item was removed:
- ----- Method: Installer>>classMCMczReader (in category 'class references') -----
- classMCMczReader
- 
- 	^Smalltalk at: #MCMczReader ifAbsent: [ nil ]
- 	!

Item was removed:
- ----- Method: Installer>>urlThing (in category 'url') -----
- urlThing
-  
- 	self logCR: 'retrieving ', self urlToDownload , ' ...'.
- 	(pageDataStream := self urlGet: self urlToDownload) 
- 		ifNil: [ self error: 'unable to contact host' ].
- 	 
- 	^ pageDataStream
- 	!

Item was removed:
- ----- Method: Installer>>project: (in category 'accessing') -----
- project: name
- 
- 	project := name.
- 	packages := nil.
- 	
- 	(mc respondsTo: #location:) ifTrue:[ mc := mc copy location: root , name ].
- 	(mc respondsTo: #directory:) ifTrue: [ mc := mc copy directory: root ,'/', name ].
- 		
- 	^self copy.!

Item was removed:
- ----- Method: Installer>>http:user:password: (in category 'monticello') -----
- http: aUrl user: name password: secret
- 	
- 	mc := self classMCHttpRepository location: aUrl user: name password: secret.
- 	root := mc locationWithTrailingSlash	
-  !

Item was removed:
- ----- Method: Installer>>ftp:directory:user:password: (in category 'monticello') -----
- ftp: host directory: dir user: name password: secret
- 	"Installer mc ftp: 'mc.gjallar.se' directory: '' user: 'gjallar' password: secret."
- 	
- 	mc := self classMCFtpRepository host: host directory: dir user: name password: ''.
- 	root :=  dir.	
-  !

Item was removed:
- ----- Method: Installer>>mcInstall (in category 'monticello') -----
- mcInstall
- 	 
- 	self withAnswersDo: [ self mcThing load ].
- 	self log: 'loaded'.
- !

Item was removed:
- ----- Method: Installer>>maPage (in category 'mantis') -----
- maPage
-   	"  self mantis bug: 5251."
- 
- 	| page |
- 	page :=  self httpGet: self maUrl.
-  	date := ((self maRead: page field: 'Date Updated') value copyUpTo: $ ).
- 	date isEmpty ifTrue: [ ^self error: bug, ' not found' ].
- 	date := date asDate.
-  	^page reset!

Item was removed:
- ----- Method: Installer class>>launchFrom: (in category 'launcher support') -----
- launchFrom: launcher
- 
- 	^self launchWith: launcher getParameters!

Item was removed:
- ----- Method: Installer>>url (in category 'accessing') -----
- url
- 
- 	^url!

Item was removed:
- ----- Method: Installer>>urlView (in category 'url') -----
- urlView
-  	 "(Installer debug url: 'http://installer.pbwiki.com/f/Installer.st') view.".
- 	
- 	self view: self urlToDownload from: self urlThing.
- 	
- 	
- !

Item was removed:
- ----- Method: Installer>>wsmDownloadUrl (in category 'websqueakmap') -----
- wsmDownloadUrl 
- 	| pkgAndVersion packageId packageName packageVersion releaseAutoVersion
-  	downloadPage |
- 
- 	pkgAndVersion := self packageAndVersionFrom: self package.
- 	packageName := pkgAndVersion first.
- 	packageVersion := pkgAndVersion last.
- 	packageVersion isEmpty ifTrue: [ packageVersion := #latest ].
- 
- 	packageId := self wsmPackagesByName at: packageName.
- 	releaseAutoVersion := (self wsmReleasesFor: packageId) at: packageVersion.
- 					 
- 	downloadPage := self httpGet: (self wsm,'packagebyname/', packageName,'/autoversion/', releaseAutoVersion,'/downloadurl') asUrl asString.
- 				 		 
- 	^ downloadPage contents
- 	
- !

Item was removed:
- ----- Method: Installer>>sake (in category 'websqueakmap') -----
- sake 
- 
- 	^ sake  !

Item was removed:
- ----- Method: Installer>>evaluate: (in category 'mantis') -----
- evaluate: stream
- 
- 	stream fileIn.!

Item was removed:
- ----- Method: Installer>>updateDirectoryOrNil (in category 'updates') -----
- updateDirectoryOrNil
- 
- 	^ (FileDirectory default directoryNames includes: 'updates')
- 		ifTrue: [FileDirectory default directoryNamed: 'updates']
- 		ifFalse: [self inform: 'Error: cannot find "updates" folder'.
- 				nil]!

Item was removed:
- ----- Method: Installer>>unload: (in category 'actions') -----
- unload: match 
- 
- 	(MCWorkingCopy allManagers select: [ :wc | match match: (wc package name) ])
- 		 do: [ :wc | 
-  			 	self logCR: 'Unloading ', wc package asString.
-  				wc unload.].
- 	self unloadCleanUp!

Item was removed:
- ----- Method: Installer>>smPackages (in category 'squeakmap') -----
- smPackages
- 	
- 	^self classSMSqueakMap default packagesByName!

Item was removed:
- ----- Method: Installer>>uniInstall (in category 'actions') -----
- uniInstall
- 
- 	| pkgAndVersion pkg version potentials |
- 	self packages do: [ :packageName |
- 	
- 		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.
- 	].
- 	self uniDoInstall!

Item was removed:
- ----- Method: Installer>>directory: (in category 'monticello') -----
- directory: dir
- 
- 	| directory |
- 	directory := dir isString 
- 		ifTrue: [  FileDirectory on: (FileDirectory default fullNameFor: dir) ]
- 		ifFalse: [ dir ].
- 		
- 	mc := self classMCDirectoryRepository new directory: directory; yourself.
-  	root := dir
- 	
-  !

Item was removed:
- ----- Method: Installer>>uniDoInstall (in category 'universes') -----
- uniDoInstall
- 
- 	self withAnswersDo: [ self universe doInstall ] !

Item was removed:
- ----- Method: Installer>>user: (in category 'accessing') -----
- user: anObject
- 
- 	user := anObject!

Item was removed:
- ----- Method: Installer>>classUVersion (in category 'class references') -----
- classUVersion
- 
- 	^Smalltalk at: #UVersion  ifAbsent: [ self error: 'Universes code not present' ]!

Item was removed:
- ----- Method: Installer class>>launchWith: (in category 'launcher support') -----
- launchWith: params
- 
-  	params at: 'P' ifPresent: [ :v | params at: 'PATH' put: v ].
-  	params at: 'I' ifPresent: [ :v | params at: 'INSTALL' put: v ].
-  	params at: 'IN' ifPresent: [ :v | params at: 'INSTALL' put: v ].
-  	params at: 'U' ifPresent: [ :v | params at: 'URL' put: v ].
- 
- 	params at: 'PATH' ifPresent: [ :v | 
- 		self webSearchPathFrom: v.
- 	].
- 
- 	params at: 'USER' ifPresent: [ :v | 
- 		Utilities setAuthorInitials: v
- 	].
- 	params at: 'VERSION' ifPresent: [ :v | 
- 		SystemVersion current version: v
- 	].
- 	params at: 'VIEW' ifPresent: [ :v |
- 		self view: v
- 	].
- 
- 	IsSetToTrapErrors := true.
- 	params at: 'DEBUG' ifPresent: [ :v | IsSetToTrapErrors := (v == true) not ].
- 
-  	params at: 'URL' ifPresent: [ :v | 
- 		 self installUrl: v
- 	].
- 
- 	params at: 'FILE' ifPresent: [ :v | 
- 		 self installFile: v
- 	].
-  
-  	params at: 'INSTALL' ifPresent: [ :v | 
- 		  self do: v
- 	].
- 	params at: 'DO' ifPresent: [ :v | 
- 		  self do: v
- 	].
-  
- 	 ^true
- 
- 	!

Item was removed:
- ----- Method: Installer>>wsmVersions (in category 'websqueakmap') -----
- wsmVersions
- 
- 	| pkgAndVersion packageId packageName packageVersion versions |
- 	pkgAndVersion := self packageAndVersionFrom: self package .
- 	packageName := pkgAndVersion first.
- 	packageVersion := pkgAndVersion last.
- 	packageVersion isEmpty ifTrue: [ packageVersion := #latest ].
- 	packageId := self wsmPackagesByName at: packageName.
- 	versions := (self wsmReleasesFor: packageId) keys.
- 	versions remove: #latest.
- 	^ versions collect: [ :version | self copy package: (packageName,'(', version ,')'); yourself ]. !

Item was removed:
- ----- Method: Installer>>file: (in category 'accessing') -----
- file: f
- 
-   afile := f!

Item was removed:
- ----- Method: Installer>>wsmInstall (in category 'websqueakmap') -----
- wsmInstall
- 	
- 	| it |
- 	it := self wsmThing.
- 	self install: it from: it asUrl retrieveContents contentStream.
- 
- 	!

Item was removed:
- ----- Method: Installer>>setBug: (in category 'mantis') -----
- setBug: stringOrNumber
- 
- 	| str |
- 	self logCR: stringOrNumber.
-  	stringOrNumber isInteger ifTrue: [ bug := stringOrNumber. desc := ''. ^self ].
-  	bug := stringOrNumber asInteger.
- 	str := str printString. 
- 	desc := stringOrNumber copyFrom: (str size + 1) to: (stringOrNumber size) 
- 
- !

Item was removed:
- ----- Method: Installer>>bug:view: (in category 'mantis') -----
- bug: aBugNo view: aFileName
- 	"Installer mantis bug: 6089 browse: 'TTFSpeedUp-dgd.1.cs'"
- 	
- 	 self setBug: aBugNo.
- 	^ self view: aFileName from: (self maThing: aFileName date: nil)!

Item was removed:
- ----- Method: Installer>>maRead:field: (in category 'mantis') -----
- maRead: page field: fieldKey
- 
- 	 | value |
-  
- 	value := page upToAll: ('!!-- ', fieldKey, ' -->'); upToAll: '<td'; upTo: $>; upToAll: '</td>'.
- 	
- 	page upTo: $<.
- 	
- 	page peek = $t ifTrue: [ value := page upToAll: 'td'; upTo: $>; upToAll: '</td>' ].
- 	  
- 	^Association key: fieldKey value: value withBlanksTrimmed!

Item was removed:
- ----- Method: Installer>>bug:retrieve: (in category 'mantis') -----
- bug: aBugNo retrieve: aFileName
- 
- 	 self setBug: aBugNo.
- 	^ (self maStreamForFile: aFileName) contents!

Item was removed:
- ----- Method: Installer>>url: (in category 'accessing') -----
- url: aUrl
-  
- 	url := aUrl!

Item was removed:
- ----- Method: Installer>>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 := pair first.  
- 		fileNames := pair last.
- 		strm nextPut: $#; nextPutAll: releaseTag; cr.
- 		fileNames do: [:fileName | strm nextPutAll: fileName; cr]].
- 	strm close!

Item was removed:
- ----- Method: Installer>>mcSortFileBlock (in category 'monticello') -----
- mcSortFileBlock
- 
- 	^ [:a :b | 
-         	[(a findBetweenSubStrs: #($.)) allButLast last asInteger > (b findBetweenSubStrs: #($.)) allButLast last asInteger] 
- 				on: Error do: [:ex | false]].!

Item was removed:
- ----- Method: Installer>>markers: (in category 'accessing') -----
- markers: anObject
- 
- 	markers := anObject!

Item was removed:
- ----- Method: Installer>>urlGet: (in category 'url') -----
- urlGet: aUrl
- 
- 	| page |
- 	page := HTTPSocket httpGet: aUrl accept: 'application/octet-stream'.  
- 	(page respondsTo: #reset)  ifFalse: [ ^ nil ].
- 	(self isHtmlStream: page) ifTrue: [ page := self extractFromHtml: page option: nil ].
- 	^ page reset
- 	!

Item was removed:
- ----- Method: Installer>>justFixBug: (in category 'mantis') -----
- justFixBug: aBugNo
- 
- 	^self class skipLoadingTests: true during: [ self fixBug: aBugNo date: nil ]!

Item was removed:
- ----- Method: Installer>>user (in category 'accessing') -----
- user
- 
- 	^ user ifNil: [ '' ]!

Item was removed:
- ----- Method: Installer>>urlBrowse (in category 'url') -----
- urlBrowse
-  	"(Installer debug url: 'http://installer.pbwiki.com/f/Installer.st') browse.".
- 	
- 	self browse: self urlToDownload from: self urlThing.
- 	
- 	
- !

Item was removed:
- ----- Method: Installer class>>smalltalkImage (in category 'accessing system') -----
- smalltalkImage
- 
- 	^ SmalltalkImage current!

Item was removed:
- ----- Method: Installer>>maScript (in category 'mantis') -----
- maScript 
- 
- 	^self extractFromHtml: self maPage option: #last
- !

Item was removed:
- ----- Method: Installer>>fileInstall (in category 'file') -----
- fileInstall
- 	
- 	self install: self file from: (FileDirectory default readOnlyFileNamed: self file)
- 
- 	!

Item was removed:
- ----- Method: Installer class>>entities (in category 'accessing') -----
- entities
- 
- 	^ Entities ifNil: [ Entities := 
- 				"enough entities to be going on with"
-   				Dictionary new.
- 				Entities at: 'lt' put: '<';
- 				at: 'gt' put: '>';
- 				at: 'amp' put: '&';
- 				at: 'star' put: '*';
- 				at: 'quot' put: '"';
- 				at: 'nbsp' put: ' ';
-  			yourself
- ]
- 
-  !

Item was removed:
- ----- Method: Installer>>wsmThing (in category 'websqueakmap') -----
- wsmThing
- 
- 	| downloadUrl |
- 	self logCR: 'finding ', self package, ' from websqueakmap(', self wsm, ') ...'.
- 	downloadUrl := self wsmDownloadUrl.
- 	self logCR: 'found at ', downloadUrl asString, ' ...'.
- 	^ downloadUrl
- 	!

Item was removed:
- ----- Method: Installer>>maUrl (in category 'mantis') -----
- maUrl
-  
- 	^ url := self ma, 'view.php?id=', bug asString
-  !

Item was removed:
- ----- Method: Installer>>classMCHttpRepository (in category 'class references') -----
- classMCHttpRepository
- 
- 	^Smalltalk at: #MCHttpRepository ifAbsent: [ self error: 'Monticello not present' ]
- 	!



More information about the Packages mailing list