[squeak-dev] The Inbox: Installer-Core-mt.449.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jul 14 14:12:04 UTC 2022


A new version of Installer-Core was added to project The Inbox:
http://source.squeak.org/inbox/Installer-Core-mt.449.mcz

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

Name: Installer-Core-mt.449
Author: mt
Time: 1 July 2022, 10:01:49.817329 am
UUID: 6e05aebc-f7f2-6c4b-bc7f-af346eadd93b
Ancestors: Installer-Core-mt.448

More HTTPS whenever possible.

=============== Diff against Installer-Core-mt.448 ===============

Item was removed:
- SystemOrganization addCategory: #'Installer-Core'!

Item was removed:
- Object subclass: #Installer
- 	instanceVariableNames: 'answers packages messagesToSuppress useFileIn noiseLevel'
- 	classVariableNames: 'InstallerBindings IsSetToTrapErrors Repositories SkipLoadingTests ValidationBlock'
- 	poolDictionaries: ''
- 	category: 'Installer-Core'!
- Installer class
- 	instanceVariableNames: 'localRepository'!
- 
- !Installer commentStamp: 'ct 10/3/2021 15:45' prior: 0!
- Installer is a mechanism for listing, examining and installing software from a variety of sources. It is intended to help in building install scripts for package setups etc.
- 
- Currently it can use
- 	- files; a file specified by a filename. Relative filenames will be treated as based form the current default directory. See InstallerFile.
- 	- urls; a file specified by a url or a script embedded in a webpage. See InstallerWeb.
- 	- squeakmap; see InstallerSqueakMap
- 	- monticello;  by ftp or http access, or a local directory, or a Magma or GOODS database. There is a list of shortcuts to popular repositories in this class protocol 'repositories'. See InstallerMonticello.
- 	- mantis; accessing code attached to a mantis bug report. See InstallerMantis.
- 
- Simple example usages - 
- Installer new merge: #osProcess.
- Installer squeakmap install: 'DynamicBindings'.
- Installer squeakmap search: '*scratch'.
- Installer squeakmap search: 'author:*rowledge'.
- Installer squeaksource project: 'ss2'; install: 'TinyWiki'.
- Installer ss project: 'Installer'; browse: 'Installer-Core'.
- 
-  
- useFileIn - flag to load source.st rather than using Monticello!
- Installer class
- 	instanceVariableNames: 'localRepository'!

Item was removed:
- ----- Method: Installer class>>actionMatch:reportOn:ifNoMatch: (in category 'action report') -----
- actionMatch: theLine reportOn: report ifNoMatch: aBlock
- 
- 	| line |	
- 	line := theLine withBlanksCondensed.
- 	self allSubclassesDo: [:class |
- 		(class canReportLine: line)
- 		ifTrue: [ ^ class new action: theLine reportOn: report ]].
- 	^ aBlock value!

Item was removed:
- ----- Method: Installer class>>airplaneMode (in category 'repository-overrides') -----
- airplaneMode
- 	self overrideRemoteRepostoriesWith: self packageCache!

Item was removed:
- ----- Method: Installer class>>asHelpTopic (in category 'documentation') -----
- asHelpTopic
- 	^HelpTopic
- 		title: 'Installer'
- 		contents: self class comment!

Item was removed:
- ----- Method: Installer class>>bootstrapTheRestOfInstaller (in category 'action report') -----
- bootstrapTheRestOfInstaller
- 
- 	(Installer url: 'www.squeaksource.com/Installer/Installer-Scripts')  
- 			fileInSource;
- 			logCR: 'installer bootstrap - loaded'.!

Item was removed:
- ----- Method: Installer class>>bug:fix: (in category 'mantis') -----
- bug: n fix: filename
- 
- 	Transcript cr; show: 'Code script in Mantis:', n asString, ' should read Installer mantis bug: ',n asString, ' fix: ', filename printString,'.'.
- 	
- 	^ self mantis bug: n fix: filename!

Item was removed:
- ----- Method: Installer class>>cache (in category 'monticello') -----
- cache
- 	^ self monticello cache!

Item was removed:
- ----- Method: Installer class>>canReportLine: (in category 'action report') -----
- canReportLine: line
- 	^ false!

Item was removed:
- ----- Method: Installer class>>cancelSkipLoadingTests (in category 'accessing') -----
- cancelSkipLoadingTests
- 	"sets a flag to un-ignore loading of the testing portion of scripts embedded in pages"
- 	
- 	SkipLoadingTests := false.
-  !

Item was removed:
- ----- Method: Installer class>>clearOverrides (in category 'repository-overrides') -----
- clearOverrides
- 	"Remove all repository overrides and load everthing from the specified default repositories when using #merge:."
- 	Repositories := Dictionary new!

Item was removed:
- ----- Method: Installer class>>debug (in category 'debug') -----
- debug
- 
- 	IsSetToTrapErrors := false!

Item was removed:
- ----- Method: Installer class>>defaultLocalRepository (in category 'repository-overrides') -----
- defaultLocalRepository
- 	"Check for a personal, Magma-indexed SqueakSource server first, if none running, the the 'mc' directory in the current directory."
- 	| localSqueaksource |
- 	localSqueaksource := Installer monticello http: 'http://localhost:8079'.
- 	^ localSqueaksource mc isIndexed
- 		ifTrue: [localSqueaksource]
- 		ifFalse: [self localMcDir]!

Item was removed:
- ----- Method: Installer class>>defaultMcDir (in category 'private') -----
- defaultMcDir
- 	^ FileDirectory default / 'mc'!

Item was removed:
- ----- Method: Installer class>>defaultRepositoryFor: (in category 'private') -----
- defaultRepositoryFor: anAssociation
- 	"private -- answer the MC repository specified by anAssociation."
- 	^ (self perform: anAssociation key)
- 		 project: anAssociation value ;
- 		 mc!

Item was removed:
- ----- Method: Installer class>>do: (in category 'launcher support') -----
- do: webPageName
- 
- 	| rs |
- 	rs := webPageName readStream.
- 	[ rs atEnd ] whileFalse: [ self install: (rs upTo: $;) ].
- !

Item was removed:
- ----- Method: Installer class>>ensureRecentMetacello (in category 'scripts') -----
- ensureRecentMetacello
- 	"Copied and adapted from https://github.com/Metacello/metacello/blob/master/README.md"
- 	
- 	| metacello |
- 	((Smalltalk classNamed: #WebClient)
- 		ifNil: [ false ]
- 		ifNotNil: [ :webClient | 
- 			[ (webClient httpHead: 'https://github.com') isSuccess ] 
- 				on: Error
- 				do: [ false ] ])
- 		ifFalse: [ ^self inform: 'Could not connect to "https://github.com".\\You need an internet connection and SSL support\to install (or update) Metacello.\\Please fix those issues and try again.' translated withCRs ].
- 	
- 	self isMetacelloInstalled ifFalse: [
- 		| response |
- 		"Download base archive of Metacello."
- 		response := WebClient httpGet: 'https://files.squeak.org/metacello/metacello-squeak60.sar'.
- 		response isSuccess ifFalse: [
- 			self error: ('Could not download Metacello archive: {1}' translated format: {response status})].
- 		"Prepare a clean environment and install it."
- 		Smalltalk globals removeKey: #Metacello ifAbsent: ["Ignore prior attempts."].
- 		SARInstaller new fileInFrom: response content asByteArray readStream].
- 
- 	metacello := Smalltalk classNamed: #Metacello.
- 
- 	"Now load latest version of Metacello"
- 	metacello new
- 		baseline: 'Metacello';
- 		repository: 'github://Metacello/metacello:master/repository';
- 		get.
- 	metacello new
- 		baseline: 'Metacello';
- 		repository: 'github://Metacello/metacello:master/repository';
- 		load: #('default' 'Metacello-Help').!

Item was removed:
- ----- Method: Installer class>>file (in category 'file') -----
- file
- 
- 	^ InstallerFile new!

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

Item was removed:
- ----- Method: Installer class>>fromUrl: (in category 'url') -----
- fromUrl: aUrl
- 
- 	"try and pick an Installer appropriate for the Url"
- 	| inst | 
- 	((aUrl endsWith: '.mcz') or: [ aUrl endsWith: '.mcm' ])
- 	ifTrue: [ inst := Installer mc fromUrl: aUrl.
- 		inst packages isEmpty ifFalse: [ ^ inst ]
- 	] .
- 	
- 	^ Installer url: aUrl 
- 	!

Item was removed:
- ----- Method: Installer class>>gemsource (in category 'repositories') -----
- gemsource
- 
- 	^ self monticello http: 'http://seaside.gemtalksystems.com/ss'!

Item was removed:
- ----- Method: Installer class>>gs (in category 'repositories') -----
- gs
- 
- 	^ self gemsource!

Item was removed:
- ----- Method: Installer class>>installAndOpenGitBrowser (in category 'scripts') -----
- installAndOpenGitBrowser
- 	self installGitInfrastructure.
- 	(Smalltalk at: #SquitBrowser) open.!

Item was removed:
- ----- Method: Installer class>>installAndOpenSqueakInboxTalk (in category 'scripts') -----
- installAndOpenSqueakInboxTalk
- 	"For more information on Squeak Inbox Talk, visit https://github.com/hpi-swa-lab/squeak-inbox-talk"
- 
- 	self installSqueakInboxTalk.
- 	(Smalltalk at: #TalkInboxBrowser) open.!

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

Item was removed:
- ----- Method: Installer class>>installGitInfrastructure (in category 'scripts') -----
- installGitInfrastructure
- | priorSetting |
- "for INIFileTest>>#testComplexRead"
- priorSetting := Scanner allowUnderscoreAsAssignment.
- [Scanner allowUnderscoreAsAssignment: true. 
- 
- 	(Smalltalk at: #Metacello) new
- 		  baseline: 'Squot';
- 		  repository: 'github://hpi-swa/Squot:latest-release/src';
- 		 "repository: 'github://hpi-swa/Squot:develop/src';"
- 		  load.
- 
- 	"Remove '(click to install)' note in 'Tools' menu."
- 	TheWorldMainDockingBar updateInstances.
- 
- ] ensure: [Scanner allowUnderscoreAsAssignment: priorSetting]!

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

Item was removed:
- ----- Method: Installer class>>installSqueakInboxTalk (in category 'scripts') -----
- installSqueakInboxTalk
- 	"For more information on Squeak Inbox Talk, visit https://github.com/hpi-swa-lab/squeak-inbox-talk"
- 	
- 	(Smalltalk at: #Metacello) new
- 		baseline: 'SqueakInboxTalk';
- 		repository: 'github://hpi-swa-lab/squeak-inbox-talk:main/packages';
- 		load.
- 	
- 	"Remove '(click to install)' note in 'Tools' menu."
- 	TheWorldMainDockingBar updateInstances.!

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

Item was removed:
- ----- Method: Installer class>>isMetacelloInstalled (in category 'scripts') -----
- isMetacelloInstalled
- 	"Squeak is shipped with the global #Metacello referring to lightweight MetacelloStub.  After the first message is sent, the latest Metacello is installed, replacing the stub."
- 
- 	^ (Smalltalk at: #Metacello ifAbsent: nil)
- 		ifNil: [false "Installation was interrupted."]
- 		ifNotNil: [:mcClass | mcClass ~= MetacelloStub]!

Item was removed:
- ----- Method: Installer class>>krestianstvo (in category 'repositories') -----
- krestianstvo
- 	"Krestianstvo SDK code repository."
- 	^ self monticello http: 'http://sdk.krestianstvo.org/sdk/'!

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

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 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 authorInitials: 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 class>>local (in category 'repositories') -----
- local
- 	^ self localRepository!

Item was removed:
- ----- Method: Installer class>>localMcDir (in category 'repositories') -----
- localMcDir
- 	^ self monticello directory: self defaultMcDir!

Item was removed:
- ----- Method: Installer class>>localRepository (in category 'repository-overrides') -----
- localRepository
- 	^ localRepository ifNil: [localRepository := self defaultLocalRepository]!

Item was removed:
- ----- Method: Installer class>>localRepository: (in category 'repository-overrides') -----
- localRepository: aMCRepository 
- 	localRepository := aMCRepository!

Item was removed:
- ----- Method: Installer class>>log: (in category 'logging') -----
- log: aString
- 
- 	Transcript show: aString; cr.!

Item was removed:
- ----- Method: Installer class>>lukas (in category 'repositories') -----
- lukas
- 
- 	^ self monticello http: 'http://source.lukas-renggli.ch'!

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

Item was removed:
- ----- Method: Installer class>>mantis: (in category 'mantis') -----
- mantis: host
- 
- 	^ InstallerMantis host: host!

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

Item was removed:
- ----- Method: Installer class>>monticello (in category 'monticello') -----
- monticello
- 
- 	^ InstallerMonticello new!

Item was removed:
- ----- Method: Installer class>>noDebug (in category 'debug') -----
- noDebug
- 
- 	IsSetToTrapErrors := true!

Item was removed:
- ----- Method: Installer class>>noProgressDuring: (in category 'during') -----
- noProgressDuring: block
- 	[ block value: self ] 
- 		on: ProgressInitiationException 
- 		do: [ : note | note sendNotificationsTo: [ :min :max :curr | "ignore" ] ]!

Item was removed:
- ----- Method: Installer class>>overrideRemoteRepostoriesWith: (in category 'repository-overrides') -----
- overrideRemoteRepostoriesWith: aMCRepositoryOrGroup
- 	self remoteRepositories do:
- 		[ : each | self
- 			overrideRepository: each
- 			with: aMCRepositoryOrGroup ]!

Item was removed:
- ----- Method: Installer class>>overrideRepository:with: (in category 'repository-overrides') -----
- overrideRepository: scope with: anMCRepository 
- 	"When configuring the image with #merge:, override the standard repository specified by scope with anMCRepository."
- "Installer
- 	override: #ss3->'htmlcssparser'
- 	with: (MCDirectoryRepository directory: (FileDirectory default / 'mc'))."
- "Installer
- 		override: #ss
- 		with: #ssMirror."
- 	self repositories
- 		at: scope
- 		put: anMCRepository!

Item was removed:
- ----- Method: Installer class>>packageCache (in category 'repositories') -----
- packageCache
- 	^ MCCacheRepository default!

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

Item was removed:
- ----- Method: Installer class>>privateUpgradeTheRest (in category 'instanciation') -----
- privateUpgradeTheRest
- 
- 	Installer ss project: 'Installer'; 
- 		installQuietly: 'Installer-Scripts';
- 		installQuietly: 'Installer-Formats'..
- 		
- 	^ self!

Item was removed:
- ----- Method: Installer class>>remoteRepositories (in category 'repository-overrides') -----
- remoteRepositories
- 	^ #(#ss #ss3 #gemsource #gs #krestianstvo #lukas #squeak #squeakfoundation #squeaksource #squeaksource3 #ss #ss3 #swa #swasource #wiresong )!

Item was removed:
- ----- Method: Installer class>>removeOverride: (in category 'repository-overrides') -----
- removeOverride: scope
- 	"Remove override specified by scope and return to using the default repository for packages within that scope."
- 	^ self repositories
- 		removeKey: scope
- 		ifAbsent: [  ]!

Item was removed:
- ----- Method: Installer class>>repositories (in category 'accessing') -----
- repositories
- 	^ Repositories ifNil: [ Repositories := Dictionary new ]!

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

Item was removed:
- ----- Method: Installer class>>repositoryFor: (in category 'private') -----
- repositoryFor: anAssociation
- 	"private -- anAssociation key is the repository selector Symbol understood by Intsaller class.  It's value is the project name within that HTTP repository."
- 	| rep |
- 	rep := self repositories
- 		at: anAssociation  "<-- check for #rep->project overrides first"
- 		ifAbsent:
- 			[ self repositories
- 				at: anAssociation key "<-- override an entire repository."
- 				ifAbsent: [ ^ self defaultRepositoryFor: anAssociation ]  ].
- 	^ rep isSymbol
- 		ifTrue: [ self defaultRepositoryFor: rep -> anAssociation value ]
- 		ifFalse: [ rep ]!

Item was removed:
- ----- Method: Installer class>>resetDefaultLocalRepository (in category 'repository-overrides') -----
- resetDefaultLocalRepository
- 	self localRepository: nil!

Item was removed:
- ----- Method: Installer class>>sf (in category 'documentation') -----
- sf
- 
- 	^ self squeakfoundation
-  !

Item was removed:
- ----- Method: Installer class>>skipLoadingTests (in category 'accessing') -----
- skipLoadingTests
- 	"sets a flag to ignore loading of the testing portion of scripts embedded in pages"
- 	
- 	SkipLoadingTests := true.
-  !

Item was removed:
- ----- Method: Installer class>>skipLoadingTestsDuring: (in category 'during') -----
- skipLoadingTestsDuring: block
- 
- 	| oldValue |
- 
- 	oldValue := SkipLoadingTests.
- 	SkipLoadingTests := true.
- 	
- 	[ block value: self ] ensure:[ SkipLoadingTests := oldValue ].!

Item was removed:
- ----- Method: Installer class>>sm (in category 'squeakmap') -----
- sm
- 
- 	^ self squeakmap!

Item was removed:
- ----- Method: Installer class>>squeak (in category 'repositories') -----
- squeak
- 
- 	^self monticello http: 'source.squeak.org'!

Item was removed:
- ----- Method: Installer class>>squeakInbox (in category 'repositories') -----
- squeakInbox
- 
- 	^self squeak project: 'inbox'!

Item was removed:
- ----- Method: Installer class>>squeakTrunk (in category 'repositories') -----
- squeakTrunk
- 
- 	^self squeak project: 'trunk'!

Item was removed:
- ----- Method: Installer class>>squeakfoundation (in category 'repositories') -----
- squeakfoundation
- 
- 	^ self monticello http: 'source.squeakfoundation.org'!

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

Item was removed:
- ----- Method: Installer class>>squeaksource (in category 'repositories') -----
- squeaksource
- 
- 	^ self monticello http: 'http://www.squeaksource.com'!

Item was removed:
- ----- Method: Installer class>>squeaksource3 (in category 'repositories') -----
- squeaksource3
- 	^ self monticello http: 'http://ss3.gemtalksystems.com/ss/'!

Item was removed:
- ----- Method: Installer class>>ss (in category 'repositories') -----
- ss
- 
- 	^ self squeaksource
-  !

Item was removed:
- ----- Method: Installer class>>ss3 (in category 'repositories') -----
- ss3
- 	^ self squeaksource3.!

Item was removed:
- ----- Method: Installer class>>suspendRepositoryOverridesWhile: (in category 'repository-overrides') -----
- suspendRepositoryOverridesWhile: aBlock 
- 	| priorOverrides |
- 	[ priorOverrides := Repositories.
- 	self clearOverrides.
- 	aBlock value ] ensure: [ Repositories := priorOverrides ]!

Item was removed:
- ----- Method: Installer class>>swa (in category 'repositories') -----
- swa
- 
- 	^ self swasource!

Item was removed:
- ----- Method: Installer class>>swasource (in category 'repositories') -----
- swasource
- 	"Visit: https://www.hpi.uni-potsdam.de/hirschfeld/trac/SqueakCommunityProjects
- 		Installer swasource project: 'MetacelloRepository'; open.
- 		Installer swasource project: 'SwaUtilities'; open.
- 	"
- 		
- 	^ self monticello http: 'http://www.hpi.uni-potsdam.de/hirschfeld/squeaksource'!

Item was removed:
- ----- Method: Installer class>>symbolicPackages (in category 'accessing') -----
- symbolicPackages
- 	^ self methodsInCategory: 'package-definitions'!

Item was removed:
- ----- Method: Installer class>>upgrade (in category 'instanciation') -----
- upgrade
- 
- 	Installer ss project: 'Installer'; 
- 		installQuietly: 'Installer-Core'.
- 			 
- 	self privateUpgradeTheRest.
- 	
- 	^ self!

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

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

Item was removed:
- ----- Method: Installer class>>useLocalMcDir (in category 'repository-overrides') -----
- useLocalMcDir
- 	self overrideRemoteRepostoriesWith: #localMcDir!

Item was removed:
- ----- Method: Installer class>>useLocalRepository (in category 'repository-overrides') -----
- useLocalRepository
- 	self overrideRemoteRepostoriesWith: #local!

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

Item was removed:
- ----- Method: Installer class>>validationBlock: (in category 'accessing') -----
- validationBlock: aBlock
- 
- 	ValidationBlock := aBlock!

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

Item was removed:
- ----- Method: Installer class>>web (in category 'web') -----
- web 
- 	^ InstallerWeb new!

Item was removed:
- ----- Method: Installer class>>webInstall: (in category 'web') -----
- webInstall: webPageName
- 
- 	^ self web install: webPageName
- !

Item was removed:
- ----- Method: Installer class>>webSearchPath (in category 'web') -----
- webSearchPath
- 	"a search path item, has the following format. prefix*suffix"
- 
- 	^ self web searchPath!

Item was removed:
- ----- Method: Installer class>>webSearchPathFrom: (in category 'web') -----
- 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 removed:
- ----- Method: Installer class>>websqueakmap (in category 'websqueakmap') -----
- websqueakmap
- 
- 	^ InstallerWebSqueakMap new wsm: 'http://map.squeak.org'; yourself!

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

Item was removed:
- ----- Method: Installer class>>wiresong (in category 'repositories') -----
- wiresong
- 
- 	^ self monticello http: 'http://source.wiresong.ca'!

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

Item was removed:
- ----- Method: Installer>>addLocalRepositories (in category 'configure') -----
- addLocalRepositories
- 	"For all MC packages defined in my
- 	'package-definitions', add the local directory
- 	repository where they reside."
- 	self class suspendRepositoryOverridesWhile:
- 		[ #(#useLocalRepository #useLocalMcDir) do:
- 			[ : eachUseDirective | self class perform: eachUseDirective.
- 			self allPackages do:
- 				[ : eachPackageSpec | self addRepositoryFor: eachPackageSpec ] ] ]!

Item was removed:
- ----- Method: Installer>>addPackage: (in category 'public interface') -----
- addPackage: anObject
- 
- 	self packages add: anObject!

Item was removed:
- ----- Method: Installer>>addRemoteRepositories (in category 'configure') -----
- addRemoteRepositories
- 	"For all MC packages defined in my 'package-definitions', add the remote repository where they reside."
- 	self allPackages do:
- 		[ : each | self class suspendRepositoryOverridesWhile: [ self addRepositoryFor: each ] ]!

Item was removed:
- ----- Method: Installer>>addRepositoryFor: (in category 'configure') -----
- addRepositoryFor: structureOrSymbol
- 	self
- 		packageDependenciesFor: structureOrSymbol
- 		do:
- 			[ : eachPackageName : eachRepositorySpec | MCWorkingCopy allManagers
- 				detect: [ : eachWorkingCopy | eachWorkingCopy packageName = eachPackageName ]
- 				ifFound: [ : foundWorkingCopy | foundWorkingCopy repositoryGroup addRepository: (self class repositoryFor: eachRepositorySpec) ]
- 				ifNone: [ nil ] ]!

Item was removed:
- ----- Method: Installer>>allPackages (in category 'accessing') -----
- allPackages
- 	 | installerClasses | installerClasses := self class withAllSuperclasses.
- 	installerClasses := installerClasses copyFrom: 1 to: (installerClasses indexOf: Installer).
- 	^ (installerClasses
- 		inject: OrderedCollection new
- 		into:
- 			[ : coll : each | coll
- 				 addAll: each symbolicPackages ;
- 				 yourself ]) sort!

Item was removed:
- ----- Method: Installer>>answer:with: (in category 'auto answering') -----
- answer: aString with: anAnswer
- 
- 	^self answers add: ( Array with: aString with: anAnswer )!

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

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

Item was removed:
- ----- Method: Installer>>availablePackages (in category 'public interface') -----
- availablePackages
- 	
- 	^ self basicAvailablePackages!

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

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

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

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

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

Item was removed:
- ----- Method: Installer>>bindingOf: (in category 'script bindings') -----
- bindingOf: aString 
- self isThisEverCalled: 'Want to get rid of this and the class-var'.
- 	InstallerBindings isNil ifTrue: [ InstallerBindings := Dictionary new].
- 
- 	(InstallerBindings includesKey: aString)
- 		ifFalse: [InstallerBindings at: aString put: nil].
- 
- 	^ InstallerBindings associationAt: aString.!

Item was removed:
- ----- Method: Installer>>bootstrap (in category 'public interface') -----
- bootstrap
- 	"keep for compatability"
- 	
- 	self deprecatedApi.
- 
- 	useFileIn := true.
- 	self install.!

Item was removed:
- ----- Method: Installer>>broomMorphsBase (in category 'package-definitions') -----
- broomMorphsBase
- 	"Morph alignment user-interface tool."
- 	^ { #ss -> 'Connectors'. 
- 	'BroomMorphs-Base' }!

Item was removed:
- ----- Method: Installer>>browse (in category 'public interface') -----
- browse
- 	self logErrorDuring: [self basicBrowse]!

Item was removed:
- ----- Method: Installer>>browse: (in category 'public interface') -----
- browse: packageNameCollectionOrDetectBlock
- 
- 	self package: packageNameCollectionOrDetectBlock.
- 	self browse!

Item was removed:
- ----- Method: Installer>>browse:from: (in category 'mantis') -----
- browse: aFileName from: stream
- 	
- 	| mcThing ext browseSelector |
- 		 
- 	self log: ' browsing...'.
-  
- 		mcThing := self classMCReader ifNotNil: [ self mcThing: aFileName from: stream ].
- 		
- 		mcThing 
- 			ifNotNil: [ (mcThing respondsTo: #snapshot) 
- 						ifTrue: [ mcThing browse ]
- 				        	ifFalse: [ (MCSnapshotBrowser forSnapshot: mcThing) showLabelled: 'Browsing ', aFileName ]
- 			]
- 			ifNil: [ 
- 		
- 				ext := aFileName copyAfterLast: $..
- 				browseSelector := ('browse', ext asUppercase, ':from:') asSymbol.
- 	
- 				(self respondsTo: browseSelector)
- 					ifTrue: [ self perform: browseSelector with: aFileName with: stream ]
- 					ifFalse: [ self browseDefault: aFileName from: stream ].
- 			]!

Item was removed:
- ----- Method: Installer>>browseCS:from: (in category 'mantis') -----
- browseCS: aFileName from: stream
-  	
- 	| list |
- 	
- 	list := self classChangeList new
- 			scanFile: stream from: 1 to: stream size.
- 		 
- 	self classChangeList open: list name: aFileName
- 		multiSelect: true.
- !

Item was removed:
- ----- Method: Installer>>browseDefault:from: (in category 'mantis') -----
- browseDefault: aFileName from: stream
- 
- 	self view: aFileName from: stream!

Item was removed:
- ----- Method: Installer>>browseGZ:from: (in category 'mantis') -----
- browseGZ: aFileName from: stream 
- 	"FileIn the contents of a gzipped stream"
- 
- 	| zipped unzipped |
- 	zipped := self classGZipReadStream on: stream.
- 	unzipped := MultiByteBinaryOrTextStream with: zipped contents asString.
- 	unzipped reset.
- 	ChangeList browseStream: unzipped
- 	!

Item was removed:
- ----- Method: Installer>>changeSetNamed: (in category 'utils') -----
- changeSetNamed: aName
- 
- 	(ChangeSet respondsTo: #named:)
- 		ifTrue: [ ^ ChangeSet named: aName ].
- 		
- 	^ ChangeSorter changeSetNamed: aName.!

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

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

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

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

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

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

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

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

Item was removed:
- ----- Method: Installer>>connectors (in category 'package-definitions') -----
- connectors
- 	"Connect Morphs together.  Make diagrams."
- 	^ { self broomMorphsBase.
- 	#ss -> 'Connectors'.
- 	'CGPrereqs'. 
- 	'FSM'. 
- 	'Connectors'. 
- 	'ConnectorsText'. 
- 	'ConnectorsShapes'. 
- 	'ConnectorsTools'. 
- 	'ConnectorsGraphLayout'. 
- 	'BroomMorphs-Connectors' }!

Item was removed:
- ----- Method: Installer>>copyLocalVersionsToRemoteFor: (in category 'configure') -----
- copyLocalVersionsToRemoteFor: structureOrSymbol
- 	"Ensure the currently loaded MCVersion is present in each repository which holds the packages represented by structureOrSymbol.  Use as a single 'commit' of all changes across multiple packages (which reside in their own repositories).
- 	Make sure id's and passwords are already set up on your repositories.  Recommend using the mcSettings file for doing this, see MCHttpRepository>>#userAndPasswordFromSettingsDo: for details."
- 	(self remoteRepositoriesFor: structureOrSymbol) do:
- 		[ : each | each copyImageVersions ]!

Item was removed:
- ----- Method: Installer>>core (in category 'package-definitions') -----
- core
- 	"A minimum core capable of expanding itself."
- 	^ { #squeak -> MCMcmUpdater defaultUpdateURL asUrl path last.
- 	'Kernel'.
- 	'Collections'.
- 	'Exceptions'.
- 	'Files'.
- 	'Network'.
- 	'Monticello'.
- 	'MonticelloConfigurations'.
- 	'Installer-Core' }!

Item was removed:
- ----- Method: Installer>>curvedSpaceExplorer (in category 'package-definitions') -----
- curvedSpaceExplorer
- 	"Explore curved 3D spaces."
- 	^ { self openGL.
- 	#krestianstvo -> 'ccse'.
- 	'CCSpaceExplorer' }!

Item was removed:
- ----- Method: Installer>>depthFirstOf:do: (in category 'private') -----
- depthFirstOf: structure do: oneArgBlock 
- 	self
- 		depthFirstOf: structure
- 		do: oneArgBlock
- 		ifNotIn: Set new!

Item was removed:
- ----- Method: Installer>>depthFirstOf:do:ifNotIn: (in category 'private') -----
- depthFirstOf: structure do: oneArgBlock ifNotIn: aSet 
- 	(aSet includes: structure) ifTrue: [ ^ self ].
- 	"Respect all repository directives even if encountered more than once."
- 	(structure isVariableBinding) ifFalse: [ aSet add: structure ].
- 	structure isArray
- 		ifTrue:
- 			[ structure do:
- 				[ : each | self
- 					depthFirstOf: each
- 					do: oneArgBlock
- 					ifNotIn: aSet ] ]
- 		ifFalse: [ oneArgBlock value: structure ]!

Item was removed:
- ----- Method: Installer>>ditchOldChangeSetFor: (in category 'utils') -----
- ditchOldChangeSetFor: aFileName 
- 
- 	| changeSetName changeSet |
-  	changeSetName := (self validChangeSetName: aFileName) sansPeriodSuffix.
- 	changeSet := self changeSetNamed: changeSetName.
- 	
- 	changeSet ifNotNil: [
- 		
- 		(self logCR:'Removing old change set ', changeSetName) cr.
- 		self  removeChangeSet: changeSet 
- 	].!

Item was removed:
- ----- Method: Installer>>ffi (in category 'package-definitions') -----
- ffi
- 	"Foreign Function Interface. Please use Metacello to install the FFI for the current system version. The Installer can only install bleeding edge, which typically only works on Trunk. See also PreferenceWizardMorph >> #installFFI"
- 	
- 	^ { #squeak -> 'FFI'.
- 	'FFI-Pools'.
- 	'FFI-Kernel'.
- 	'FFI-Libraries'.
- 	'FFI-Callbacks'.
- 	'FFI-Tools'}!

Item was removed:
- ----- Method: Installer>>ffiTests (in category 'package-definitions') -----
- ffiTests
- 	"Tests for Foreign Function Interface."
- 	^ { self ffi.
- 	#squeak -> 'FFI'.
- 	'FFI-Tests'.
- 	'FFI-PoolsTests'.
- 	'FFI-CallbacksTests' }!

Item was removed:
- ----- Method: Installer>>fileInSource (in category 'public interface') -----
- fileInSource
- 
- 	useFileIn := true.
- 	self install.!

Item was removed:
- ----- Method: Installer>>graphQlEngine (in category 'package-definitions') -----
- graphQlEngine
- 	^ { #ss -> 'graphql'.
- 	'GraphQL-Core'.
- 	'GraphQL-Engine' }!

Item was removed:
- ----- Method: Installer>>graphQlTestsEngine (in category 'package-definitions') -----
- graphQlTestsEngine
- 	^ { self graphQlEngine.
- 	'GraphQL-Tests-Core'.
- 	'GraphQL-Tests-Engine' }!

Item was removed:
- ----- Method: Installer>>htmlValidator (in category 'package-definitions') -----
- htmlValidator
- 	"Validates HTML and CSS pages against W3C DTD."
- 	^ { #ss3 -> 'htmlcssparser'.
- 	'HTML' }!

Item was removed:
- ----- Method: Installer>>initialize (in category 'public interface') -----
- initialize
- 
- 	useFileIn := false..!

Item was removed:
- ----- Method: Installer>>install (in category 'public interface') -----
- install
- 	
- 	noiseLevel = #quiet ifTrue: [ ^ self installQuietly ].
- 	noiseLevel = #silent ifTrue: [ ^ self installSilently ].
- 	
- 	^ self installLogging!

Item was removed:
- ----- Method: Installer>>install: (in category 'public interface') -----
- install: packageNameCollectionOrDetectBlock
- 	"The parameter specifies the package to be installed in one of the following ways:
- 		- By Name e.g. install: 'Kernel'
- 		- Acceptable Versions e.g. install: #('Comet-lr' 'Comet-pmm') i.e. either of these
- 		- Specific version e.g. install: 'Scriptaculous-lr.148'
- 		- By Predicate e.g. install: [ :packageName | packageName beginsWith: 'Dynamic' ]"
- 
- 	self addPackage: packageNameCollectionOrDetectBlock.
- 	self install!

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

Item was removed:
- ----- Method: Installer>>install:from:using: (in category 'mantis') -----
- install: aFileName from: stream using: installSelector
- 
- 		(self respondsTo: installSelector)
- 			ifTrue: [ self perform: installSelector with: aFileName with: stream ]
- 			ifFalse: [ self installDefault: aFileName from: stream ].
- !

Item was removed:
- ----- Method: Installer>>installCS:from: (in category 'mantis') -----
- installCS: aFileName from: stream
- 
-  	self ditchOldChangeSetFor: aFileName.
- 	self newChangeSetFromStream: stream named: (self validChangeSetName: aFileName).
- !

Item was removed:
- ----- Method: Installer>>installDefault:from: (in category 'mantis') -----
- installDefault: aFileName from: stream
- 	"Check for UTF-8 input before filing it in"
- 	| pos |
- 	pos := stream position.
- 	(stream next: 3) asByteArray = #[16rEF 16rBB 16rBF]	"BOM"
- 		ifTrue: [(RWBinaryOrTextStream on: stream upToEnd utf8ToSqueak) fileIn]
- 		ifFalse: [stream position: pos; fileIn]
- !

Item was removed:
- ----- Method: Installer>>installGZ:from: (in category 'mantis') -----
- installGZ: aFileName from: stream 
- 	"FileIn the contents of a gzipped stream"
- 	| zipped unzipped |
- 	zipped := self classGZipReadStream on: stream.
- 	unzipped := MultiByteBinaryOrTextStream with: zipped contents asString.
- 	unzipped reset.
- 	self 
- 		newChangeSetFromStream: unzipped 
- 		named: (FileDirectory localNameFor: aFileName)!

Item was removed:
- ----- Method: Installer>>installLogging (in category 'public interface') -----
- installLogging
- 
- 	self logErrorDuring: [
- 		self basicInstall.
- 		packages := nil].
- !

Item was removed:
- ----- Method: Installer>>installMCZ:from: (in category 'mantis') -----
- installMCZ: aFileName from: stream 
- 
- 	| source pkg wc |
- 	
- 	pkg := aFileName copyUpToLast: $-.
- 	
- 	wc := Smalltalk at: #MCWorkingCopy ifAbsent: [ nil ].
- wc ifNotNil: [ 
- 	(wc allManagers select:  [:each | each packageName = pkg ]) do: [ :ea | ea unregister ] 
- ].
- 	
- 	self classMczInstaller ifNotNil: [^ self classMczInstaller install: aFileName stream: stream].  
- 
- 	source :=  ((ZipArchive new readFrom:stream) memberNamed: 'snapshot/source.st') contents.
- 
- 	[
- 		SystemChangeNotifier uniqueInstance doSilently: [ 
- 			source  readStream fileInAnnouncing: 'Booting ' , aFileName.
-  		]
- 	] on: Warning do: [ :ex | ex resume: true ].!

Item was removed:
- ----- Method: Installer>>installMCZBasic:from: (in category 'mantis') -----
- installMCZBasic: aFileName from: stream 
- 
- 	| source |
- 	
-  
- 	self classMczInstaller ifNotNil: [^ self classMczInstaller install: aFileName stream: stream].  
- 
- 	source :=  ((ZipArchive new readFrom:stream) memberNamed: 'snapshot/source.st') contents.
- 
- 	[
- 		SystemChangeNotifier uniqueInstance doSilently: [ 
- 			source  readStream fileInAnnouncing: 'Booting ' , aFileName.
-  		]
- 	] on: Warning do: [ :ex | ex resume: true ].!

Item was removed:
- ----- Method: Installer>>installMCcs:from: (in category 'mantis') -----
- installMCcs: aFileName from: stream 
- 
- 	| reader |
- 	
- 	reader := Smalltalk at: #MCCsReader ifPresent: [:class | class on: stream].!

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

Item was removed:
- ----- Method: Installer>>installQuietly: (in category 'public interface') -----
- installQuietly: packageNameCollectionOrDetectBlock
- 
- 	self quietly install: packageNameCollectionOrDetectBlock.
-  !

Item was removed:
- ----- Method: Installer>>installSAR:from: (in category 'mantis') -----
- installSAR: aFileName from: stream 
- 
- 	| newCS |
- 	newCS := self classSARInstaller withCurrentChangeSetNamed: aFileName
- 		do: [:cs | self classSARInstaller new fileInFrom: stream].
- 	newCS isEmpty ifTrue: [ self removeChangeSet: newCS ]!

Item was removed:
- ----- Method: Installer>>installSilently (in category 'public interface') -----
- installSilently
- 
- 	SystemChangeNotifier uniqueInstance doSilently: [ self installLogging ]
- 
- 	!

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

Item was removed:
- ----- Method: Installer>>jsonParser (in category 'package-definitions') -----
- jsonParser
- 	^ { #ss -> 'JSON'.
- 	'JSON' }!

Item was removed:
- ----- Method: Installer>>log: (in category 'logging') -----
- log: text
- 
- 	^Transcript show: text.!

Item was removed:
- ----- Method: Installer>>logCR: (in category 'logging') -----
- logCR: text
- 
- 	self validate.
- 	^ Transcript show: text; cr!

Item was removed:
- ----- Method: Installer>>logErrorDuring: (in category 'logging') -----
- logErrorDuring: block
- 
- 	(IsSetToTrapErrors = true) ifFalse: [ ^ block value ].
- 
- 	block on: Error 
- 		do: [ :e |
- 			self halt. 
- 			self logCR: '****', e class name, ': ', (e messageText ifNil: [ '']). 
- 		
- 			(e isKindOf: MessageNotUnderstood) 
- 				ifTrue: [ e pass ]
- 				ifFalse: [ e isResumable ifTrue:[ e resume: true ]]]!

Item was removed:
- ----- Method: Installer>>maInstaller (in category 'package-definitions') -----
- maInstaller
- 	"Select from a family of related packages for application development."
- 	^ { #ss -> 'MaInstaller'.
- 	'Ma-Installer-Core' }!

Item was removed:
- ----- Method: Installer>>match: (in category 'searching') -----
- match: aMatch
- 
- 	^self packagesMatching: aMatch!

Item was removed:
- ----- Method: Installer>>mathMorphs (in category 'package-definitions') -----
- mathMorphs
- 	"MathMorphs is a project that combines mathematics and Smalltalk.  See http://www.dm.uba.ar/MathMorphs/ and chapter 10 of the 'new blue book'."
- 	^ { self morphicWrappers.
- 	#ss -> 'MathMorphsRevival'.
- 	'Functions' }!

Item was removed:
- ----- Method: Installer>>mcThing:from: (in category 'mantis') -----
- mcThing: aFileName from: stream
- 		
- 	"dont use monticello for .cs or for .st use monticello for .mcs"
- 
- 	| reader |
- 	
- 	useFileIn ifTrue: [ ^ nil ].
- 	
- 	reader := self classMCReader readerClassForFileNamed: aFileName.
- 	reader name = 'MCStReader' ifTrue: [ ^ nil ].
- 	reader ifNil: [ ^ nil ].
- 	(reader respondsTo: #on:fileName:) 
- 		ifTrue: [ reader := reader on: stream fileName: aFileName.
- 					^ reader version  ]
- 		ifFalse: [ reader := reader on: stream. 
- 				    ^ reader snapshot  ].!

Item was removed:
- ----- Method: Installer>>merge: (in category 'public interface') -----
- merge: structureOrSymbol 
- 	| toUncache |
- 	toUncache := Set new.
- 	self
- 		packageDependenciesFor: structureOrSymbol
- 		do:
- 			[ : eachPackageName : eachRepositorySpec | | repo version tried |
- 			tried := false.
- 			repo := [ (self class repositoryFor: eachRepositorySpec) cacheAllFilenames ]
- 				on: Error
- 				do:
- 					[ : err | tried
- 						ifTrue: [ err pass ]
- 						ifFalse:
- 							[ tried := true.
- 							self class resetDefaultLocalRepository.
- 							err retry ] ].
- 			toUncache add: repo.
- 			version := self
- 				primMerge: eachPackageName
- 				from: repo.
- 			"Lazy code, polite MC won't add duplicates if they already exist."
- 			version ifNotNil:
- 				[ version workingCopy repositoryGroup
- 					 addRepository: repo ;
- 					 addRepository: (self class defaultRepositoryFor: eachRepositorySpec) ] ].
- 	toUncache do:
- 		[ : each | each flushAllFilenames ]!

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

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

Item was removed:
- ----- Method: Installer>>morphicWrappers (in category 'package-definitions') -----
- morphicWrappers
- 	"Provides 'type on air' workspaces.  Results of evaluated expressions are represented as domain objects in the world."
- 	^ { #ss -> 'MathMorphsRevival'.
- 	'MorphicWrappers' }!

Item was removed:
- ----- Method: Installer>>newChangeSetFromStream:named: (in category 'mantis') -----
- newChangeSetFromStream: aStream named: aName 
- 
- 	"This code is based upon ChangeSet-c-#newChangesFromStream:named: which is in 3.9,
- 	implemented here for previous versions. The second branch is for 3.8, where ChangeSets
- 	are loaded by ChangeSorter. "
- 
- 	| oldChanges newName newSet |
- 
- 	(self classChangeSet respondsTo: #newChangesFromStream:named:) 
- 		ifTrue: [ ^self classChangeSet newChangesFromStream: aStream named:aName ].
- 
- 	(self classChangeSorter respondsTo: #newChangesFromStream:named:)
- 		ifTrue: [ ^self classChangeSorter newChangesFromStream: aStream named: aName ].
- 
- 	oldChanges := ChangeSet current.
-  
- 	"so a Bumper update can find it"
- 	newName := aName sansPeriodSuffix.
- 
- 	newSet := self classChangeSet basicNewNamed: newName.
- 
- 	[ | newStream |
- 	newSet
- 		ifNotNil: [(aStream respondsTo: #converter:)
- 				ifTrue: [newStream := aStream]
- 				ifFalse: [newStream := self classMultiByteBinaryOrTextStream with: aStream contentsOfEntireFile.
- 					newStream reset].
- 			self classChangeSet newChanges: newSet.
- 			newStream setConverterForCode.
- 			newStream fileInAnnouncing: 'Loading ' , newName , '...'.
- 			Transcript cr; show: 'File ' , aName , ' successfully filed in to change set ' , newName].
- 	aStream close]
- 		ensure: [self classChangeSet newChanges: oldChanges].
- 	 
- 	^ newSet!

Item was removed:
- ----- Method: Installer>>oCompletion (in category 'package-definitions') -----
- oCompletion
- 	"Adds code-completion to the IDE."
- 	^ { #ss -> 'OCompletion'.
- 	'OcompletionSqueakCompatibility'.
- 	'Ocompletion' }!

Item was removed:
- ----- Method: Installer>>open (in category 'public interface') -----
- open!

Item was removed:
- ----- Method: Installer>>openGL (in category 'package-definitions') -----
- openGL
- 	"3D library."
- 	^ { self threeDtransform.
- 	#krestianstvo -> 'ccse'.
- 	'OpenGL-Pools'.
- 	'OpenGL-Core'.
- 	'OpenGL-NameManager' }!

Item was removed:
- ----- Method: Installer>>osProcess (in category 'package-definitions') -----
- osProcess
- 	"Launch external executable programs."
- 	^ { #ss -> 'OSProcess'.
- 	'OSProcess' }!

Item was removed:
- ----- Method: Installer>>package (in category 'accessing') -----
- package
- 
- 	^ self packages isEmpty ifTrue: [ nil ] ifFalse: [ self packages last ]!

Item was removed:
- ----- Method: Installer>>package: (in category 'accessing') -----
- package: anObject
- 
- 	self addPackage: anObject.!

Item was removed:
- ----- Method: Installer>>packageAndVersionFrom: (in category 'squeakmap') -----
- packageAndVersionFrom: pkg
- 	| p |
- 	p := ReadStream on: pkg .
- 	^{(p upTo: $(). p upTo: $)} collect: [:s | s withBlanksTrimmed].!

Item was removed:
- ----- Method: Installer>>packageDependenciesFor:do: (in category 'private') -----
- packageDependenciesFor: structureOrSymbol do: twoArgBlock 
- 	"Value twoArgBlock with each package name and the currently-specified repository where that package resides."
- 	| currentRepository |
- 	structureOrSymbol isSymbol
- 		ifTrue:
- 			[ self
- 				packageDependenciesFor: (self perform: structureOrSymbol)
- 				do: twoArgBlock ]
- 		ifFalse:
- 			[ self
- 				depthFirstOf: structureOrSymbol
- 				do:
- 					[ : each | each isVariableBinding
- 						ifTrue: [ currentRepository := each ]
- 						ifFalse:
- 							[ each isString
- 								ifTrue:
- 									[ twoArgBlock
- 										value: each
- 										value: currentRepository ]
- 								ifFalse: [ self error: 'invalid specification' ] ] ] ]!

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

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

Item was removed:
- ----- Method: Installer>>packagesFor: (in category 'configure') -----
- packagesFor: structureOrSymbol 
- 	^ Array streamContents:
- 		[ : stream | self
- 			packageDependenciesFor: structureOrSymbol
- 			do:
- 				[ : eachPackageName : eachRepositorySpec | stream nextPut: eachPackageName ] ]!

Item was removed:
- ----- Method: Installer>>packagesMatching: (in category 'searching') -----
- packagesMatching: aMatch
- 	^'search type not supported'!

Item was removed:
- ----- Method: Installer>>primMerge:from: (in category 'private') -----
- primMerge: packageName from: aMCRepository
- 	| version |
- 	version := (aMCRepository includesVersionNamed: packageName)
- 		ifTrue: [ aMCRepository versionNamed: packageName ]
- 		ifFalse: [ aMCRepository highestNumberedVersionForPackageNamed: packageName ].
- 	[ version shouldMerge
- 		ifTrue: [ version merge ]
- 		ifFalse: [ version load ] ]
- 		on: MCNoChangesException
- 		do: [ : req | req resume ]
- 		on: MCMergeResolutionRequest
- 		do:
- 			[ : request | request merger conflicts isEmpty
- 				ifTrue: [ request resume: true ]
- 				ifFalse: [ request pass ] ].
- 	^ version!

Item was removed:
- ----- Method: Installer>>quietly (in category 'public interface') -----
- quietly
- 
- 	noiseLevel := #quiet!

Item was removed:
- ----- Method: Installer>>remoteRepositoriesFor: (in category 'configure') -----
- remoteRepositoriesFor: structureOrSymbol
- 	| reps |
- 	reps := Set new.
- 	self class suspendRepositoryOverridesWhile:
- 		[ self
- 			packageDependenciesFor: structureOrSymbol
- 			do:
- 				[ : eachPackageName : eachRepositorySpec | | rep |
- 				rep := self class repositoryFor: eachRepositorySpec.
- 				"Collect up the repositories in the default MCRepositoryGroup, because those ones will have user and password specified."
- 				reps add:
- 					(MCRepositoryGroup default repositories
- 						detect: [ : each | each = rep ]
- 						ifNone: [ rep ]) ] ].
- 	^ reps!

Item was removed:
- ----- Method: Installer>>removeChangeSet: (in category 'utils') -----
- removeChangeSet: cs
- 
- 	(self classChangeSet respondsTo: #removeChangeSet:)
- 		ifTrue: [ ^ChangeSet removeChangeSet: cs ].
- 		
- 	^ self classChangeSorter removeChangeSet: cs .!

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.
- 		Installer actionMatch: line reportOn: report ifNoMatch: [ report nextPutAll: line; cr. ]].!

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>>search: (in category 'searching') -----
- search: aMatch
- 	^'search type not supported'!

Item was removed:
- ----- Method: Installer>>silently (in category 'public interface') -----
- silently
- 
- 	noiseLevel := #silent!

Item was removed:
- ----- Method: Installer>>squeakRelease (in category 'package-definitions') -----
- squeakRelease
- 	^ { self system.
- 	'311Deprecated'.
- 	'39Deprecated'.
- 	'45Deprecated'.
- 	'Nebraska'.
- 	'SmallLand-ColorTheme'.
- 	'ST80'.
- 	'ST80Tools'.
- 	'SystemReporter'.
- 	'Universes'.
- 	'XML-Parser' }!

Item was removed:
- ----- Method: Installer>>squeaksource (in category 'package-definitions') -----
- squeaksource
- 	"A source code repository."
- 	^ { #squeak -> 'ss'.
- 	'RFB'.
- 	'SmaCC'.
- 	'DynamicBindings'.
- 	'KomServices'.
- 	'KomHttpServer'.
- 	'Seaside2'.
- 	'Mewa'.
- 	'TinyWiki'.
- 	'SqueakSource' }!

Item was removed:
- ----- Method: Installer>>suppress: (in category 'auto answering') -----
- suppress: aMessage
- 
- 	messagesToSuppress add: aMessage!

Item was removed:
- ----- Method: Installer>>system (in category 'package-definitions') -----
- system
- 	"Packages forming the Smalltalk development system."
- 	^ { self core.
- 	'System' }!

Item was removed:
- ----- Method: Installer>>threeDtransform (in category 'package-definitions') -----
- threeDtransform
- 	^ { self ffiTests.
- 	#ss -> 'CroquetGL'.
- 	'3DTransform' }!

Item was removed:
- ----- Method: Installer>>tools (in category 'package-definitions') -----
- tools
- 	"A minimum core capable of expanding itself."
- 	^ { self core.
- 	'ToolBuilder-Kernel'.
- 	'Tools' }!

Item was removed:
- ----- Method: Installer>>updateStream (in category 'package-definitions') -----
- updateStream
- 	^ { self tools.
- 	'UpdateStream' }!

Item was removed:
- ----- Method: Installer>>validChangeSetName: (in category 'url') -----
- validChangeSetName: aFileName
- 	" dots in the url confuses the changeset loader. I replace them with dashes"
- 	
-  	(aFileName beginsWith:'http:') ifTrue: [ | asUrl |
- 		asUrl := Url absoluteFromText: aFileName.
- 		^String streamContents: [:stream |
- 			stream nextPutAll: (asUrl authority copyReplaceAll: '.' with: '-').
- 			asUrl path allButLastDo: [:each |
- 				stream
- 					nextPutAll: '/';
- 					nextPutAll: (each copyReplaceAll: '.' with: '-') ].
- 			stream
- 				nextPutAll: '/';
- 				nextPutAll: asUrl path last ] ].
- 	^aFileName!

Item was removed:
- ----- Method: Installer>>validate (in category 'logging') -----
- validate
- 
- 	ValidationBlock value = false ifTrue: [ self error: 'Validation failed' ].!

Item was removed:
- ----- Method: Installer>>versions (in category 'public interface') -----
- versions
- 	
- 	^ self basicVersions!

Item was removed:
- ----- Method: Installer>>view (in category 'public interface') -----
- view
- 	self logErrorDuring: [self basicView]!

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

Item was removed:
- ----- Method: Installer>>view:from: (in category 'mantis') -----
- view: aFileName from: stream
- 	
- 	self log: ' viewing...'.
-  	
- 	Workspace new contents: (stream contents); openLabel: aFileName.
-  
- 	 
- 
- 				 !

Item was removed:
- ----- Method: Installer>>webClientSsp (in category 'package-definitions') -----
- webClientSsp
- 	"WebClient supports NTLM/SPNEGO authentication via the Microsoft SSP interface (Windows only)."
- 	^ { self ffiTests. 
- 	#ss -> 'WebClient'.
- 	'WebClient-SSP' }!

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

Item was removed:
- Installer subclass: #InstallerFile
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Installer-Core'!

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

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

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

Item was removed:
- ----- Method: InstallerFile>>file (in category 'accessing') -----
- file
- 
- 	^ self package!

Item was removed:
- ----- Method: InstallerFile>>file: (in category 'accessing') -----
- file: f
- 	self package: f!

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

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerInternetBased>>classHTTPSocket (in category 'class references') -----
- classHTTPSocket
- 
- 	^Smalltalk at: #HTTPSocket ifAbsent: [ self error: 'Network package not present' ]!

Item was removed:
- ----- Method: InstallerInternetBased>>extractFromHtml:option: (in category 'private') -----
- extractFromHtml: html option: allOrLast
- 
- 	|  start stop test in |
- 
- 	start := self markersBegin.
- 	stop :=  self markersEnd.
- 	test := self markersTest.
- 			 
- 	in := WriteStream 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 readStream
- 	 
- !

Item was removed:
- ----- Method: InstallerInternetBased>>hasPage (in category 'url') -----
- hasPage
- 
- 	^ pageDataStream notNil and: [ pageDataStream size > 0 ]
- 			!

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: InstallerInternetBased>>markers (in category 'private - accessing') -----
- markers
- 
- 	^ markers ifNil: [ '<code st>..."test ...</code st>' ]!

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

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

Item was removed:
- ----- Method: InstallerInternetBased>>markersEnd (in category 'private') -----
- 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: InstallerInternetBased>>markersTest (in category 'private') -----
- markersTest
- 		 	 
- 	^ self markers readStream upToAll: '...'; upToAll: '...'!

Item was removed:
- ----- Method: InstallerInternetBased>>removeHtmlMarkupFrom: (in category 'private') -----
- removeHtmlMarkupFrom: in 
- 
- 	| out |
- 	out := WriteStream 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 readStream.
- !

Item was removed:
- ----- Method: InstallerInternetBased>>replaceEntitiesIn: (in category 'url') -----
- replaceEntitiesIn: in
- 
- 	| out |
- 	out := WriteStream 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 readStream!

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerInternetBased>>wasPbwikiSpeedWarning (in category 'url') -----
- wasPbwikiSpeedWarning
- 		
- 		^ self hasPage and: [pageDataStream contents includesSubstring: 'Please slow down a bit' ] 
-  
- !

Item was removed:
- InstallerWebBased subclass: #InstallerMantis
- 	instanceVariableNames: 'ma bug desc date array data status'
- 	classVariableNames: 'Fixes Status'
- 	poolDictionaries: ''
- 	category: 'Installer-Core'!
- 
- !InstallerMantis commentStamp: 'test 1/14/2009 00:11' prior: 0!
- Search feature is based upon a custom mantis query ceveloped and maintained by Ken Causey <ken at kencausey.com>
- 
- Installer mantis bugsAll select: [ :ea | ea status = 'testing' ].!

Item was removed:
- ----- Method: InstallerMantis class>>canReportLine: (in category 'action report') -----
- canReportLine: line
- 	^ line beginsWith: 'Installer mantis fixBug:'!

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

Item was removed:
- ----- Method: InstallerMantis class>>host: (in category 'instanciation') -----
- host: host
- 
- 	^self new	ma: host; 
- 			markers: '"fix begin"..."fix test"..."fix end"'; 
- 			yourself.
- !

Item was removed:
- ----- Method: InstallerMantis class>>initialize (in category 'instanciation') -----
- initialize
- 
- 	Status := Dictionary new
- 		at: '10' put: 'new';
- 		at: '20' put: 'feedback';
- 		at: '30' put: 'acknowledged';
- 		at: '40' put: 'confirmed';
- 		at: '50' put: 'assigned';
- 		at: '60' put: 'pending';
- 		at: '70' put: 'testing';
- 		at: '80' put: 'resolved';
- 		at: '90' put: 'closed';
- 		yourself !

Item was removed:
- ----- Method: InstallerMantis>>= (in category 'accessing') -----
- = other
- 	self == other ifTrue: [ ^ true ].
- 	self species = other species ifFalse: [ ^ false ].
- 	^ array = other array!

Item was removed:
- ----- Method: InstallerMantis>>action:reportOn: (in category 'action report') -----
- action: 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: InstallerMantis>>array (in category 'accessing') -----
- array
- 
- 	^ array!

Item was removed:
- ----- Method: InstallerMantis>>browseFile: (in category 'public interface') -----
- browseFile: aFileName
- 
- 	^ self browse: aFileName from: (self maThing: aFileName date: nil)!

Item was removed:
- ----- Method: InstallerMantis>>bug (in category 'accessing') -----
- bug
- 	
- 	^ bug ifNil: [ 
- 		
- 		date := ((self dataAtName: 'Updated') replaceAll: $  with: $T) asDateAndTime. 
- 		desc := (self dataAtName: 'Summary').
- 		bug := (self dataAtName: 'Id'). 
- 		self statusInit.
-  	]!

Item was removed:
- ----- Method: InstallerMantis>>bug: (in category 'public interface') -----
- bug: aBugNo
- 
- 	| page |
- 	self setBug: aBugNo.
- 	
- 	page := self maPage.
- 	date := ((self maRead: page field: 'Date Updated') value replaceAll: $  with: $T) asDateAndTime.
- 	status := (self maRead: page field: 'Status') value.
- "	
- Installer mantis bug: 7235 
- "!

Item was removed:
- ----- Method: InstallerMantis>>bug:browse: (in category 'public interface') -----
- bug: aBugNo browse: aFileName
- 
- 	 self setBug: aBugNo.
- 	^ self browseFile: aFileName!

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

Item was removed:
- ----- Method: InstallerMantis>>bug:fix:date: (in category 'public interface') -----
- bug: aBugNo fix: aFileName date: aDate
-  
- 	| |
- 	self setBug: aBugNo.
- 	self ditchOldChangeSetFor: aFileName.
- 	self install: aFileName from: (self maThing: aFileName date: aDate).
- 		
- 	^ date!

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

Item was removed:
- ----- 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 removed:
- ----- 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; files!

Item was removed:
- ----- Method: InstallerMantis>>bugFilesView: (in category 'public interface') -----
- bugFilesView: aBugNo
-  	"provide a list of files associated with the bug in id order"
- 	"
- 	Installer mantis bugFiles: 6660.
- 	"
- 	self setBug: aBugNo; viewFiles!

Item was removed:
- ----- Method: InstallerMantis>>bugScript: (in category 'public interface') -----
- bugScript: aBugNo
- 
- 	^ (self setBug: aBugNo) script
- 	
- 	
- !

Item was removed:
- ----- Method: InstallerMantis>>bugsAll (in category 'action report') -----
- bugsAll
- 
- 	^ array ifNil: [
- 		
- 		array := ( self bugsSqueak ,  (self dataGetFrom: '/installer_export.php') ) asSet sorted: [ :a :b | a date > b date ]
- 		
- 	].
- 
- "
- 
- Installer mantis bugsAll
- 
- "
- 	
- !

Item was removed:
- ----- Method: InstallerMantis>>bugsClosed (in category 'searching') -----
- bugsClosed
- 
- 	^ array ifNil: [ array := self dataGetFrom: '/installer_export.php?closed' ]!

Item was removed:
- ----- Method: InstallerMantis>>bugsRelease: (in category 'searching') -----
- bugsRelease: version
- 
- 	^self bugsAll select: [ :ea | (ea status = 'resolved') and: [ ea fixedIn = version ]]!

Item was removed:
- ----- Method: InstallerMantis>>bugsSqueak (in category 'searching') -----
- bugsSqueak
- 
- 	^ array ifNil: [ array := self dataGetFrom: '/installer_export.php?project=Squeak' ]
- 	
- "
- Installer mantis bugsSqueak.
- Installer mantis bugsAll.
- Installer mantis bugsClosed.
- 
- "!

Item was removed:
- ----- Method: InstallerMantis>>bugsTesting: (in category 'searching') -----
- bugsTesting: version
- 
- 	^self bugsAll select: [ :ea | ea status = 'testing' and: [ ea fixedIn = version ]]!

Item was removed:
- ----- Method: InstallerMantis>>category (in category 'searching') -----
- category
- 
- 	^ self dataAtName: 'Category'
- 	
-  "
- s bugs collect: [ :ea | ea category ]
- "!

Item was removed:
- ----- Method: InstallerMantis>>dataAtName: (in category 'searching') -----
- dataAtName: key
- 	
- 	^ array at: (self dataNames indexOf: key)!

Item was removed:
- ----- Method: InstallerMantis>>dataAtName:put: (in category 'searching') -----
- dataAtName: key put: v
- 	
- 	^ array at: (self dataNames indexOf: key) put: v!

Item was removed:
- ----- Method: InstallerMantis>>dataClosed (in category 'searching') -----
- dataClosed
- 
- 	^ array ifNil: [ array := self dataGetFrom: '/installer_export.php?closed' ]!

Item was removed:
- ----- Method: InstallerMantis>>dataGetFrom: (in category 'public interface') -----
- dataGetFrom: aPath
- 
- 	| rs line first col row out |
- 		
- 	rs := HTTPSocket httpGet: ma, aPath.
- 	
- 	rs isString ifTrue: [ ^ ProtocolClientError signal: 'notFound' ].
- 	
- 	first := true.
- 	
- 	out := OrderedCollection new.
- 	
- 	[ rs atEnd ] whileFalse: [ 
- 		
- 		line := rs nextLine readStream.
- 		col := 1.
- 		row := Array new: 9.
- 		[ (line atEnd or: [ col > 9 ]) ] whileFalse: [ row at: col put: (line upTo: $|). col := col + 1 ].	
- 
- 		rs next.
- 		[ out add: (self class new in: self row: row) ] ifError: []
- 		
- 	 ].
- 		
- 	^ out
- "
- self reset.
- self getBugsList 
- "!

Item was removed:
- ----- Method: InstallerMantis>>dataNames (in category 'public interface') -----
- dataNames
- 
- 	^ #(Id Project Category Assigned Updated Status Severity FixedIn Summary)!

Item was removed:
- ----- Method: InstallerMantis>>date (in category 'accessing') -----
- date 
- 
- 	^ date !

Item was removed:
- ----- Method: InstallerMantis>>date: (in category 'accessing') -----
- date: anObject
- 
- 	date := anObject ifNotNil: [anObject asDate ]!

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

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

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

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

Item was removed:
- ----- Method: InstallerMantis>>ensureFix:date: (in category 'public interface') -----
- ensureFix: aBugNo date: aDate
- 
- 	self setBug: aBugNo.
- 	self date: aDate.
- 	
- 	self ensureFix.!

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

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

Item was removed:
- ----- Method: InstallerMantis>>fixBug (in category 'public interface') -----
- fixBug
- 
-  	self install: self maUrl from: self maScript.
- 	self maCheckDateAgainst: date.
- 		
- 	self fixesAppliedNumbers in: [ :fixed |
- 		(fixed isEmpty or: [ (fixed includes: bug asInteger) not]) 
- 		ifTrue: [ self fixesApplied add: (bug asString, ' ', desc) ]].
- 
- 	
- 	
- !

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

Item was removed:
- ----- Method: InstallerMantis>>fixBug:date: (in category 'public interface') -----
- fixBug: aBugNo date: aDate
- 
- 	self setBug: aBugNo.
-  	self date: aDate.
- 	self fixBug.
- 	
- !

Item was removed:
- ----- Method: InstallerMantis>>fixedIn (in category 'searching') -----
- fixedIn
- 
- 	^ self dataAtName: 'FixedIn'
- !

Item was removed:
- ----- Method: InstallerMantis>>fixesApplied (in category 'public interface') -----
- fixesApplied
- 
- 	^ Fixes ifNil: [ Fixes := OrderedCollection new ].!

Item was removed:
- ----- Method: InstallerMantis>>fixesAppliedNumbers (in category 'public interface') -----
- fixesAppliedNumbers
- 	^ self fixesApplied collect: [ :fixDesc | fixDesc asInteger ]. !

Item was removed:
- ----- Method: InstallerMantis>>getView (in category 'accessing') -----
- getView
- 
- 	"Installer mantis viewBug: 5639."
- 	| page text | 
- 	
- 	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: InstallerMantis>>hash (in category 'accessing') -----
- hash
- 
- 	^ array hash!

Item was removed:
- ----- Method: InstallerMantis>>in:row: (in category 'public interface') -----
- in: parent row: dataRow
- 
- 	self ma: parent ma.
- 	self markers: parent markers.
- 	self setArray: dataRow.!

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 asString, ' not found' ].
- 	date := date asDate.
-  	^page reset!

Item was removed:
- ----- 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: (self removeHtmlMarkupFrom: value withBlanksTrimmed readStream) contents!

Item was removed:
- ----- 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 lf with: Character cr.
- 		notes add: note  
- 	].
- 	
- 	^notes!

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: InstallerMantis>>maUrl (in category 'mantis') -----
- maUrl
-  
- 	^ url := self ma, 'view.php?id=', bug asString
-  !

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

Item was removed:
- ----- Method: InstallerMantis>>printOn: (in category 'accessing') -----
- printOn: stream
- 
- 	super printOn: stream.
- 	
- 	(array ifNil: [ ^ self ]) printOn: stream.!

Item was removed:
- ----- Method: InstallerMantis>>project (in category 'searching') -----
- project
- 
- 	^ self dataAtName: 'Project'
- !

Item was removed:
- ----- Method: InstallerMantis>>report (in category 'public interface') -----
- report
- 
- 	"Installer mantis viewBug: 5639."
- 	| page text | 
- 	
- 	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: InstallerMantis>>script (in category 'public interface') -----
- script
- 
-  	^ self maScript contents.
- 	 
- 	
- 	
- !

Item was removed:
- ----- Method: InstallerMantis>>selectCategoryCollections (in category 'public interface') -----
- selectCategoryCollections
- 
- 	^ self select: [ :ea | ea category = 'Collections' ]!

Item was removed:
- ----- Method: InstallerMantis>>setArray: (in category 'public interface') -----
- setArray: dataRow
- 
- 	(array := dataRow) ifNotNil: [ self bug ].!

Item was removed:
- ----- Method: InstallerMantis>>setBug: (in category 'mantis') -----
- setBug: stringOrNumber
- 
- 	| newBug |
- 	
- 	(newBug := stringOrNumber asInteger) = bug ifTrue: [ ^ self ].
- 	
- 	self logCR: 'Installer accessing bug: ' , stringOrNumber asString.
- 
-  	bug := newBug.
- 	
-  	stringOrNumber = bug ifTrue: [ desc := ''. ^ self ].
- 
- 	desc := stringOrNumber withoutLeadingDigits  !

Item was removed:
- ----- Method: InstallerMantis>>status (in category 'accessing') -----
- status 
- 
- 	^ status!

Item was removed:
- ----- Method: InstallerMantis>>statusInit (in category 'accessing') -----
- statusInit
- 
- 	status ifNil: [ status := Status at: (self dataAtName: 'Status').
- 		self dataAtName:'Status' put: status.
- 	].
- 
- 	!

Item was removed:
- ----- Method: InstallerMantis>>summary (in category 'searching') -----
- summary
- 
- 	^ self dataAtName: 'Summary'!

Item was removed:
- ----- Method: InstallerMantis>>validChangeSetName: (in category 'action report') -----
- validChangeSetName: aFileName
- 
- 	| csn prefix |
- 
- 	csn := super validChangeSetName: aFileName.
- 	prefix := 'M' , self bug asInteger asString.
- 
- 	csn := csn replaceAll: ('-', prefix) with: ''.
- 	csn := csn replaceAll: (prefix,'-') with: ''.
- 	csn := csn replaceAll: prefix with: ''.
- 	
- 	^ prefix, '-', csn 	
- 	!

Item was removed:
- ----- Method: InstallerMantis>>view (in category 'public interface') -----
- view
- 	
- 	^ Workspace new contents: self report; openLabel: ('Mantis ', bug printString).
- !

Item was removed:
- ----- Method: InstallerMantis>>viewBug: (in category 'public interface') -----
- viewBug: aBugNo
- 
- 	self setBug: aBugNo; view!

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

Item was removed:
- ----- Method: InstallerMantis>>viewFiles (in category 'public interface') -----
- viewFiles
- 	
- 	^ self files do: [ :ea | self viewFile: ea ].!

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

Item was removed:
- ----- Method: InstallerMonticello>>basicAvailablePackages (in category 'basic interface') -----
- basicAvailablePackages
- 	^ self mc allPackageNames!

Item was removed:
- ----- Method: InstallerMonticello>>basicBrowse (in category 'basic interface') -----
- basicBrowse
- 	 "Installer ss project: 'Installer'; browse: 'Installer-Core'."
- 
- 	| it |
- 	it := self mcThing.
- 	
- 	(it class includesSelector: #browse) ifTrue: [ ^ it browse ].
- 	
- 	(it instVarNamed: 'versions') do: [ :each | each browse ].!

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

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerMonticello>>basicView (in category 'basic interface') -----
- basicView
- 	 "Installer ss project: 'Installer'; view: 'Installer-Core'. "
- 	| it |
- 	
- 	packages isEmptyOrNil ifTrue: [ self mc morphicOpen: nil ].
- 	
- 	it := self mcThing. 
- 	(it respondsTo: #open) ifTrue: [ ^ it open ].
- 
- 	"in case an old mc doesnt have #open"
- 	
- 	(it instVarNamed: 'versions') do: [ :each | each open ].
- !

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

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

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

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

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

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

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

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

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

Item was removed:
- ----- Method: InstallerMonticello>>directory: (in category 'instance creation') -----
- 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: InstallerMonticello>>fromUrl: (in category 'accessing') -----
- fromUrl: aUrl
- 
- 	| url  path |
- 	
- 	url := aUrl asUrl.
- 
- 	self http: url authority.
- 	
- 	path := url path.
- 	
- 	path size = 2 ifTrue: [ 
- 		self project: path first.
- 		path removeFirst.
-  	].	
- 	
- 	path size = 1 ifTrue: [ self package: path first ].!

Item was removed:
- ----- Method: InstallerMonticello>>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."
- 	
- 	mc := self classMCFtpRepository host: host directory: dir user: name password: secret.
- 	root :=  dir.	
-  !

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

Item was removed:
- ----- Method: InstallerMonticello>>http: (in category 'instance creation') -----
- http: aUrl  
- 	
- 	self http: aUrl user: '' password: ''
- 		
-  !

Item was removed:
- ----- Method: InstallerMonticello>>http:user:password: (in category 'instance creation') -----
- http: aUrl user: name password: secret
- 	| url |
- 	url := (aUrl includesSubstring: '://')
- 		ifTrue: [aUrl]
- 		ifFalse: ['http://', aUrl].
- 	mc := self classMCHttpRepository location: url user: name password: secret.
- 	root := mc locationWithTrailingSlash	
-  !

Item was removed:
- ----- Method: InstallerMonticello>>initialize (in category 'public interface') -----
- initialize
- 	super initialize.
- 	mc := MCRepositoryGroup default!

Item was removed:
- ----- Method: InstallerMonticello>>latest (in category 'accessing') -----
- latest 
- 	| newPackage |
- 	newPackage := self package copyUpToLast: $-.
- 	self packages removeLast.
- 	self package: newPackage
- 	
- "
- Installer mc fromUrl: 'http://www.squeaksource.com/Installer/Installer-Core-kph.100.mcz'.
- "!

Item was removed:
- ----- Method: InstallerMonticello>>latestFromUsers: (in category 'accessing') -----
- latestFromUsers: list
- 
- 	| newPackage |
- 	newPackage := self package copyUpToLast: $-.
- 	self packages removeLast.
- 	self package: (list collect: [ :ea | newPackage, '-', ea ])!

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

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

Item was removed:
- ----- Method: InstallerMonticello>>mc: (in category 'accessing') -----
- mc: aRepo
- 
- 	mc := aRepo!

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerMonticello>>mcThing (in category 'monticello') -----
- mcThing
- 	| loader |
- 	loader := self classMCVersionLoader new.
- 
- 	"several attempts to read files - repository readableFileNames
- 	sometimes fails"
- 	self packages
- 		do: [:pkg |
- 			| mcVersion versionNames sortedVersions fileToLoad version |
- 			mcVersion := pkg asMCVersionName .
- 			versionNames := mc versionNamesForPackageNamed:
- 				(mcVersion versionNumber = 0 
- 					ifTrue: [ "Just a package name specified, use it whole." pkg ] 
- 					ifFalse: [mcVersion packageName]).
- 			sortedVersions := versionNames sorted: self mcSortFileBlock.
- 			fileToLoad := self versionToLoad: mcVersion fromVersions: sortedVersions.
- 			fileToLoad
- 				ifNotNil: [version := mc versionNamed: fileToLoad.
- 					(version isKindOf: MCConfiguration)
- 						ifTrue: [^ version]
- 						ifFalse: [self normalizedRepositories do: [:repo |
- 								MCRepositoryGroup default addRepository: repo].
- 							self normalizedRepositories do: [:repo |
- 								version workingCopy repositoryGroup addRepository: repo].
- 							loader addVersion: version].
- 					self logCR: ' found ' , version fileName , '...']].
- 	^ loader!

Item was removed:
- ----- Method: InstallerMonticello>>mcUrl (in category 'monticello') -----
- mcUrl
- 
- 	^ self mc description 
- 	!

Item was removed:
- ----- Method: InstallerMonticello>>normalizedRepositories (in category 'monticello') -----
- normalizedRepositories
- "Find an existing instance of any active repository so that we use whatever name and password the user usually uses. If not found, answer a copy"
- 	^ mc repositories replace: [:repo |
- 		(MCRepositoryGroup default repositories includes: repo)
- 			ifTrue: [repo]
- 			ifFalse: [repo copy]]!

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

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerMonticello>>project (in category 'accessing') -----
- project
- 
- 	^ project!

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerMonticello>>unload (in category 'public interface') -----
- unload
- 	(MCWorkingCopy allManagers select: [ : each | self package match: each package name ]) do:
- 		[ : each | self logCR: 'Unloading ' , each package name.
- 		each unload.
- 		MCMcmUpdater disableUpdatesOfPackage: each package name ].
- 	self unloadCleanUp!

Item was removed:
- ----- Method: InstallerMonticello>>unload: (in category 'public interface') -----
- unload: match 
- 
- 	self addPackage: match.
- 	self unload.!

Item was removed:
- ----- Method: InstallerMonticello>>unloadCleanUp (in category 'public interface') -----
- 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 ] ].
- 	Smalltalk fixObsoleteReferences.!

Item was removed:
- ----- Method: InstallerMonticello>>versionToLoad:fromVersions: (in category 'monticello') -----
- versionToLoad: mcVersion fromVersions: sortedVersions
- 	"From a list of sortedVersions, answer the most recent version or the
- 	exact version if explicitly specified."
- 	^ sortedVersions
- 		detect: [:aMCVersionName | aMCVersionName = mcVersion "explicit version specified"]
- 		ifNone: [sortedVersions
- 				detect: [:aMCVersionName | (mcVersion beginsWith: aMCVersionName packageAndBranchName)
- 						and: [aMCVersionName beginsWith: mcVersion "most recent version that matches"]]
- 				ifNone: []]!

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerSqueakMap>>basicView (in category 'basic interface') -----
- basicView
- 
- 	self smThing explore!

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerSqueakMap>>search: (in category 'searching') -----
- search: 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: InstallerSqueakMap>>sm (in category 'accessing') -----
- sm
- 
- 	^ sm ifNil: [ false ]!

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

Item was removed:
- ----- Method: InstallerSqueakMap>>smPackageAndVersion (in category 'squeakmap') -----
- smPackageAndVersion
- 	^ self packageAndVersionFrom: self package.!

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

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

Item was removed:
- ----- 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]]]) asArray
- 				sort: [:a :b | a name < b name])
- 					do: [:aChangeSet | aStream cr; nextPutAll: aChangeSet summaryString]]
- 
- 
- 
- !

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

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

Item was removed:
- ----- Method: InstallerUrl class>>canReportLine: (in category 'action report') -----
- canReportLine: line
- 	^ ((line beginsWith: 'Installer installUrl:') and: 
- 		[ | ext |
- 		 ext :=  (line readStream upToAll: '''.') copyAfterLast: $..
- 		 (#( 'cs' 'st' 'mcz' 'sar') includes: ext) not ])!

Item was removed:
- ----- Method: InstallerUrl>>action:reportOn: (in category 'action report') -----
- action: 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: InstallerUrl>>addPackage: (in category 'public interface') -----
- addPackage: aPackageName
- 	super addPackage: aPackageName.
- 	(self url endsWith: '/') ifFalse: [self url: self url, '/'].!

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerUrl>>basicInstall (in category 'basic interface') -----
- basicInstall 
-  	 
- 	self install: self urlToDownload from: self urlThing.
- 	^ pageDataStream 
- !

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerUrl>>fileInSource (in category 'accessing') -----
- fileInSource
- 
- "
- (Installer url: 'http://www.squeaksource.com/Sake/Sake-Core-kph.47.mcz') bootstrap.
- "
- 
- 
- | pkg splitPos repo getFileName fileName |
- 
- useFileIn := true.
- 
- splitPos := url lastIndexOf: $/. 
- 
- pkg := url copyFrom: splitPos + 1 to: url size.
- repo := url copyFrom: 1 to: splitPos.
- 
- getFileName := [ :pkgName | pkgName , ((HTTPSocket httpGet: repo) upToAll: pkgName; upTo: $") ].
-  
- fileName := getFileName value: pkg.
- 
- url := repo,fileName.
- 
- self install!

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

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

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

Item was removed:
- ----- Method: InstallerWeb class>>canReportLine: (in category 'action report') -----
- canReportLine: line
- 	^ ((line beginsWith: 'Installer install:') | (line beginsWith: 'Installer do:'))!

Item was removed:
- ----- Method: InstallerWeb class>>initialize (in category 'instanciation') -----
- initialize
- 	
- 	WebSearchPath := nil!

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

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

Item was removed:
- ----- Method: InstallerWeb>>basicInstall (in category 'basic interface') -----
- basicInstall
-  
-  	 self thing 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: InstallerWeb>>basicView (in category 'basic interface') -----
- basicView
-  
-  	 self thing size > 0 
- 		ifTrue: [ self view: url from: pageDataStream ]
- 		ifFalse: [ self logCR: 'NO DATA ',url,' was empty' ].
- 	 !

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

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- Method: InstallerWebSqueakMap>>basicInstall (in category 'basic interface') -----
- basicInstall
- 	
- 	| it |
- 	it := self wsmThing.
- 	self install: it from: it asUrl retrieveContents contentStream.
- 
- 	!

Item was removed:
- ----- 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 asSet.
- 	versions remove: #latest.
- 	^ versions collect: [ :version | self copy package: (packageName,'(', version ,')'); yourself ]. !

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

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

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

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- Object subclass: #MetacelloStub
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Installer-Core'!
- 
- !MetacelloStub commentStamp: 'cmm 4/8/2019 14:00' prior: 0!
- MetacelloStub is a loose reference to the class Metacello in its host repository.  It's kept at both its real name, #MetacelloStub, as well as the name #Metacello.  This is done to allow Squeak to respond to messages sent to Metacello (e.g., as referenced in external installation scripts), without the need to ship with Metacello pre-installed.!

Item was removed:
- ----- Method: MetacelloStub class>>doesNotUnderstand: (in category 'overriding') -----
- doesNotUnderstand: aMessage
- 	"Handle any messages sent to Metacello class, too."
- 	Installer ensureRecentMetacello.
- 	^ aMessage sendTo: (Smalltalk classNamed: #Metacello)!

Item was removed:
- ----- Method: MetacelloStub class>>initialize (in category 'initialize-release') -----
- initialize
- 	Smalltalk
- 		at: #Metacello
- 		ifAbsentPut: [ self ]!

Item was removed:
- ----- Method: MetacelloStub class>>isMetacelloConfig (in category 'overriding') -----
- isMetacelloConfig
- 	"Sent during Metacello's bootstrap initialization to all classes in the system.  Respond false."
- 	^ false!

Item was removed:
- ----- Method: MetacelloStub class>>new (in category 'overriding') -----
- new
- 	Installer ensureRecentMetacello.
- 	^ (Smalltalk at: #Metacello) new!



More information about the Squeak-dev mailing list