The Inbox: Installer-Core-tpr.434.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
19 messages Options
Reply | Threaded
Open this post in threaded view
|

The Inbox: Installer-Core-tpr.434.mcz

commits-2
tim Rowledge uploaded a new version of Installer-Core to project The Inbox:
http://source.squeak.org/inbox/Installer-Core-tpr.434.mcz

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

Name: Installer-Core-tpr.434
Author: tpr
Time: 27 August 2019, 1:08:05.39831 pm
UUID: c1ea7dcd-9b59-4796-b66a-0f558e074ec9
Ancestors: Installer-Core-mt.433

Some possible cleanups for Installer.

Make InstallerWeb behave more like the other installer classes.
Remove a couple of redundant installer types.
Start adding some up to date copmments and make the Installer class comment appear in a HelpBrowser - more needed. Subclasses should get more extensive class specific commentary and that should be made to appear in the help browser pages.

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

Item was changed:
  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: 'tpr 8/25/2019 18:37' 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 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'.
+
- !Installer commentStamp: 'kph 3/30/2009 01:29' prior: 0!
- Documentation now available at http://installer.pbwiki.com/Installer
   
  useFileIn - flag to load source.st rather than using Monticello!
  Installer class
  instanceVariableNames: 'localRepository'!

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

Item was removed:
- ----- Method: Installer class>>cobalt (in category 'repositories') -----
- cobalt
-
- ^ self monticello http: '<a href="http://croquet-src-01.oit.duke.edu:8886'!">http://croquet-src-01.oit.duke.edu:8886'!

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

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

Item was removed:
- ----- Method: Installer class>>install: (in category 'action report') -----
- install: scriptName
-
- ^ (self scripts install: scriptName) ifNil:[ self web install: scriptName ]
- !

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

Item was changed:
  ----- Method: Installer class>>remoteRepositories (in category 'repository-overrides') -----
  remoteRepositories
+ ^ #(#ss #ss3 #gemsource #gs #krestianstvo #lukas #squeak #squeakfoundation #squeaksource #squeaksource3 #ss #ss3 #swa #swasource #wiresong )!
- ^ #(#ss #ss3 #cobalt #gemsource #goran #gs #impara #keith #krestianstvo #lukas #saltypickle #sophie #squeak #squeakfoundation #squeaksource #squeaksource3 #ss #ss3 #swa #swasource #wiresong )!

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

Item was removed:
- ----- Method: Installer class>>sake: (in category 'sake') -----
- sake: aSakePackagesClass
-
- ^ InstallerSake new sake: aSakePackagesClass!

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

Item was removed:
- ----- Method: Installer class>>setSakeToUse: (in category 'sake') -----
- setSakeToUse: aClass
-
- InstallerSake sake: aClass!

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

Item was removed:
- ----- Method: Installer class>>ssMirror (in category 'repositories') -----
- ssMirror
- "The Chilean mirror for the original SqueakSource."
- ^ self monticello http: 'http://dsal.cl/squeaksource/'!

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

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

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

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

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

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

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

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

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

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

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

Item was removed:
- ----- Method: InstallerUniverse class>>default (in category 'instance creation') -----
- default
-
- ^ self universe: (self classUGlobalInstaller universe: self classUUniverse systemUniverse)!

Item was removed:
- ----- Method: InstallerUniverse class>>universe: (in category 'instance creation') -----
- universe: u
-
- ^ self new universe: u!

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

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

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

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

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

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

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

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

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

Item was changed:
  ----- Method: InstallerWeb>>urlToDownload (in category 'web install') -----
  urlToDownload
  "while we look for a url which returns what we are looking for, we get the data anyway"
 
  | delay |
  delay := 0.
+ self searchPath do: [ :pathSpec |
- self class webSearchPath 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
  !


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

marcel.taeumel
Deprecation first? 🙃 At least for the url methods...



On Tue, Aug 27, 2019 at 10:08 PM +0200, "[hidden email]" <[hidden email]> wrote:

tim Rowledge uploaded a new version of Installer-Core to project The Inbox:
http://source.squeak.org/inbox/Installer-Core-tpr.434.mcz

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

Name: Installer-Core-tpr.434
Author: tpr
Time: 27 August 2019, 1:08:05.39831 pm
UUID: c1ea7dcd-9b59-4796-b66a-0f558e074ec9
Ancestors: Installer-Core-mt.433

Some possible cleanups for Installer.

Make InstallerWeb behave more like the other installer classes.
Remove a couple of redundant installer types.
Start adding some up to date copmments and make the Installer class comment appear in a HelpBrowser - more needed. Subclasses should get more extensive class specific commentary and that should be made to appear in the help browser pages.

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

Item was changed:
  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: 'tpr 8/25/2019 18:37' 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 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'.
+ 
- !Installer commentStamp: 'kph 3/30/2009 01:29' prior: 0!
- Documentation now available at http://installer.pbwiki.com/Installer
   
  useFileIn - flag to load source.st rather than using Monticello!
  Installer class
  	instanceVariableNames: 'localRepository'!

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

Item was removed:
- ----- Method: Installer class>>cobalt (in category 'repositories') -----
- cobalt
- 
- 	^ self monticello http: 'http://croquet-src-01.oit.duke.edu:8886'!

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

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

Item was removed:
- ----- Method: Installer class>>install: (in category 'action report') -----
- install: scriptName
- 
- 	^ (self scripts install: scriptName) ifNil:[ self web install: scriptName ]
- !

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

Item was changed:
  ----- Method: Installer class>>remoteRepositories (in category 'repository-overrides') -----
  remoteRepositories
+ 	^ #(#ss #ss3 #gemsource #gs #krestianstvo #lukas #squeak #squeakfoundation #squeaksource #squeaksource3 #ss #ss3 #swa #swasource #wiresong )!
- 	^ #(#ss #ss3 #cobalt #gemsource #goran #gs #impara #keith #krestianstvo #lukas #saltypickle #sophie #squeak #squeakfoundation #squeaksource #squeaksource3 #ss #ss3 #swa #swasource #wiresong )!

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

Item was removed:
- ----- Method: Installer class>>sake: (in category 'sake') -----
- sake: aSakePackagesClass
- 
- 	^ InstallerSake new sake: aSakePackagesClass!

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

Item was removed:
- ----- Method: Installer class>>setSakeToUse: (in category 'sake') -----
- setSakeToUse: aClass
- 
- 	InstallerSake sake: aClass!

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

Item was removed:
- ----- Method: Installer class>>ssMirror (in category 'repositories') -----
- ssMirror
- 	"The Chilean mirror for the original SqueakSource."
- 	^ self monticello http: 'http://dsal.cl/squeaksource/'!

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

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

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

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

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

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

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

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

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

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

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

Item was removed:
- ----- Method: InstallerUniverse class>>default (in category 'instance creation') -----
- default
- 
- 	^ self universe: (self classUGlobalInstaller universe: self classUUniverse systemUniverse)!

Item was removed:
- ----- Method: InstallerUniverse class>>universe: (in category 'instance creation') -----
- universe: u
- 
- 	^ self new universe: u!

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

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

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

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

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

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

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

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

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

Item was changed:
  ----- Method: InstallerWeb>>urlToDownload (in category 'web install') -----
  urlToDownload
  	"while we look for a url which returns what we are looking for, we get the data anyway"
  	
  	| delay |
  	delay := 0.
+ 	self searchPath do: [ :pathSpec |
- 	self class webSearchPath 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
  !




Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

timrowledge


> On 2019-08-29, at 12:28 AM, Taeumel, Marcel <[hidden email]> wrote:
>
> Deprecation first? 🙃 At least for the url methods...

Sure, if that makes people happier; that's why I put it InBox.

The shortcuts to long-dead repositories should definitely go. I think the 'fixes' to InstallerWeb are fairly sensible, but may not be sufficient yet. The class comment is an improvement but needs more, and subclasses need specific info - and I'm not currently very familiar with feeding stuff into the HelpBrowser nicely.

It's a small part of the system but quite an important one, so it ought to be well documented and up to date.


tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Useful random insult:- Calling her stupid would be an insult to stupid people.



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

Hannes Hirzel
On 8/29/19, tim Rowledge <[hidden email]> wrote:
[snip]
> I'm not currently very familiar with feeding stuff into
> the HelpBrowser nicely.
[snip]

This might be considered as a request for a tutorial on how to write
Help browser entries with style and executable code. (within the help
browser)

>
> tim

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

David T. Lewis
On Thu, Aug 29, 2019 at 05:17:34PM +0000, H. Hirzel wrote:

> On 8/29/19, tim Rowledge <[hidden email]> wrote:
> [snip]
> > I'm not currently very familiar with feeding stuff into
> > the HelpBrowser nicely.
> [snip]
>
> This might be considered as a request for a tutorial on how to write
> Help browser entries with style and executable code. (within the help
> browser)
>

That's a good idea. And of course there is "Installer openHelpBrowser"
which feeds some basic things into a help browser, and might motivate
us to improve our class and method comments to give the help browser
something more useful to display.

Dave


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

timrowledge


> On 2019-08-29, at 3:55 PM, David T. Lewis <[hidden email]> wrote:
>
> On Thu, Aug 29, 2019 at 05:17:34PM +0000, H. Hirzel wrote:
>> On 8/29/19, tim Rowledge <[hidden email]> wrote:
>> [snip]
>>> I'm not currently very familiar with feeding stuff into
>>> the HelpBrowser nicely.
>> [snip]
>>
>> This might be considered as a request for a tutorial on how to write
>> Help browser entries with style and executable code. (within the help
>> browser)
>>
>
> That's a good idea.

definitely.

> And of course there is "Installer openHelpBrowser"
> which feeds some basic things into a help browser, and might motivate
> us to improve our class and method comments to give the help browser
> something more useful to display.

For the moment I just set it to put the class comment in a help page. I haven't spotted how to register it so that it automatically appears, nor how to add subclass comments. I'm sure it isn't too hard.

I would suggest that we might consider having every class comment (where there is one!) appear in the help browser by default. I'd love to see classes have actual meaningful comments that explain what they are for. Those could then be connected into subject help books/pages to explain how to use classes together.
Wouldn't it be nice if the Help included a real, up to date, introduction to Smalltalk/squeak? And real documentation for all the things one needs to know.

Yes, I know; a lot of work. But what else are you going to do? Watch cat videos?

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Strange OpCodes: CMN: Convert to Mayan Numerals



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

David T. Lewis
On Thu, Aug 29, 2019 at 04:15:45PM -0700, tim Rowledge wrote:

>
>
> > On 2019-08-29, at 3:55 PM, David T. Lewis <[hidden email]> wrote:
> >
> > On Thu, Aug 29, 2019 at 05:17:34PM +0000, H. Hirzel wrote:
> >> On 8/29/19, tim Rowledge <[hidden email]> wrote:
> >> [snip]
> >>> I'm not currently very familiar with feeding stuff into
> >>> the HelpBrowser nicely.
> >> [snip]
> >>
> >> This might be considered as a request for a tutorial on how to write
> >> Help browser entries with style and executable code. (within the help
> >> browser)
> >>
> >
> > That's a good idea.
>
> definitely.
>
> > And of course there is "Installer openHelpBrowser"
> > which feeds some basic things into a help browser, and might motivate
> > us to improve our class and method comments to give the help browser
> > something more useful to display.
>
> For the moment I just set it to put the class comment in a help page. I haven't spotted how to register it so that it automatically appears, nor how to add subclass comments. I'm sure it isn't too hard.
>
> I would suggest that we might consider having every class comment (where there is one!) appear in the help browser by default. I'd love to see classes have actual meaningful comments that explain what they are for. Those could then be connected into subject help books/pages to explain how to use classes together.
> Wouldn't it be nice if the Help included a real, up to date, introduction to Smalltalk/squeak? And real documentation for all the things one needs to know.
>
> Yes, I know; a lot of work. But what else are you going to do? Watch cat videos?
>

Playing with (working on?) Squeak is my personal equivalent of watching
cat videos. It was actually quite a bit more addictive back when we had
BFAV (https://wiki.squeak.org/squeak/3214) but that is way off topic.

Dave


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

Hannes Hirzel
On 8/29/19, David T. Lewis <[hidden email]> wrote:

> On Thu, Aug 29, 2019 at 04:15:45PM -0700, tim Rowledge wrote:
>>
>>
>> > On 2019-08-29, at 3:55 PM, David T. Lewis <[hidden email]> wrote:
>> >
>> > On Thu, Aug 29, 2019 at 05:17:34PM +0000, H. Hirzel wrote:
>> >> On 8/29/19, tim Rowledge <[hidden email]> wrote:
>> >> [snip]
>> >>> I'm not currently very familiar with feeding stuff into
>> >>> the HelpBrowser nicely.
>> >> [snip]
>> >>
>> >> This might be considered as a request for a tutorial on how to write
>> >> Help browser entries with style and executable code. (within the help
>> >> browser)
>> >>
>> >
>> > That's a good idea.
>>
>> definitely.
>>
>> > And of course there is "Installer openHelpBrowser"
>> > which feeds some basic things into a help browser, and might motivate
>> > us to improve our class and method comments to give the help browser
>> > something more useful to display.
>>
>> For the moment I just set it to put the class comment in a help page. I
>> haven't spotted how to register it so that it automatically appears, nor
>> how to add subclass comments. I'm sure it isn't too hard.
The WebClient might be an example as it shows the API of the classes
in the package.

   #asHelpTopic
is implemented in a custom subclass 'WebClientReference' . It iterates
over the classes.in the package.

This might be one approach. There are others ...

Ideally the installer (or installer help) would also give some
configuration options

>>
>> I would suggest that we might consider having every class comment (where
>> there is one!) appear in the help browser by default. I'd love to see
>> classes have actual meaningful comments that explain what they are for.
>> Those could then be connected into subject help books/pages to explain how
>> to use classes together.
>> Wouldn't it be nice if the Help included a real, up to date, introduction
>> to Smalltalk/squeak? And real documentation for all the things one needs
>> to know.
>>
>> Yes, I know; a lot of work. But what else are you going to do? Watch cat
>> videos?
>>
>
> Playing with (working on?) Squeak is my personal equivalent of watching
> cat videos. It was actually quite a bit more addictive back when we had
> BFAV (https://wiki.squeak.org/squeak/3214) but that is way off topic.
>
> Dave
>
>
>



asHelpTopic_Squeak5.3a_18828_2019-08-30.png (334K) Download Attachment
WebClientReference.st (1K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

Chris Muller-3
In reply to this post by Hannes Hirzel

On Thu, Aug 29, 2019 at 12:17 PM H. Hirzel <[hidden email]> wrote:
On 8/29/19, tim Rowledge <[hidden email]> wrote:
[snip]
> I'm not currently very familiar with feeding stuff into
> the HelpBrowser nicely.
[snip]

This might be considered as a request for a tutorial on how to write
Help browser entries with style and executable code. (within the help
browser)

1.  Open the Help entry in the Help browser.
2.  Type the updated text into the Help entry.
     - Cmd+6 = Colored text,  
       Cmd+7 = bold,  
       Cmd+8 = italics,   
       Cmd+_ = Underline
3.  Press Cmd+s to save the entry with the updated text.
4.  Note the dirty -Help package in Monticello browser.



>
> tim



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

Hannes Hirzel
Thank you Chris, for the start, an attempt at continuing
...............................................................................................................

1.  Open the Help entry in the Help browser.
2.  Type the updated text into the Help entry.
     - Cmd+6 = Colored text,
       Cmd+7 = bold,
       Cmd+8 = italics,
       Cmd+_ = Underline
3.  Press Cmd+s to save the entry with the updated text.
4.  Note the dirty -Help package in Monticello browser.

Note:
- you may also add your own *CustomHelp* subclass in your package
<<<<< explain how
- it is possible to add executable Smalltalk code ...... <<<<<<<
explain how to do it.
...................................................................................................................................


Issues:

a) in
     Squeak / Core Packages / Commonly used / Compression /
     I have a clickable link that is 'Archive' (black) which opens a
SystemBrowser on class 'Archive'


b)
     Squeak / Core Packages /  Commonly used / Installer /
......... NO LINKS and NO EXECUTABLE code


c)
     Squeak / Core Packages /  Commonly used / ToolBuilder
        there is a black (SystemBrowser) link to debugger and
        a blue (ClassBrowser) link to Toolbuilder

These formatting notes have to go into a book called 'Creating Help
Files' under 'Help on Help'.

How do I create a black (SystemBrowser) link?
How do I create a blue (ClassBrowser) link?

There also needs to be a note for in Squeak / Tutorials / Useful Expression /
      that any executable code may be selected and executed by CMD-D.

Noteworthy in this discussion is  that we could  add more content for
the Installer .....(see screen shot)


On 8/30/19, Chris Muller <[hidden email]> wrote:

> On Thu, Aug 29, 2019 at 12:17 PM H. Hirzel <[hidden email]> wrote:
>
>> On 8/29/19, tim Rowledge <[hidden email]> wrote:
>> [snip]
>> > I'm not currently very familiar with feeding stuff into
>> > the HelpBrowser nicely.
>> [snip]
>>
>> This might be considered as a request for a tutorial on how to write
>> Help browser entries with style and executable code. (within the help
>> browser)
>>
>
> 1.  Open the Help entry in the Help browser.
> 2.  Type the updated text into the Help entry.
>      - Cmd+6 = Colored text,
>        Cmd+7 = bold,
>        Cmd+8 = italics,
>        Cmd+_ = Underline
> 3.  Press Cmd+s to save the entry with the updated text.
> 4.  Note the dirty -Help package in Monticello browser.
>
>
>
>> >
>> > tim
>>
>>
>



HelpBrowser_Core-Packages_Commonly-Used_Installer.png (52K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

Hannes Hirzel
In reply to this post by Chris Muller-3
Thank you Chris, for the start, an attempt at continuing
...............................................................................................................

1.  Open the Help entry in the Help browser.
2.  Type the updated text into the Help entry.
     - Cmd+6 = Colored text,
       Cmd+7 = bold,
       Cmd+8 = italics,
       Cmd+_ = Underline
3.  Press Cmd+s to save the entry with the updated text.
4.  Note the dirty -Help package in Monticello browser.

Note:
- you may also add your own *CustomHelp* subclass in your package
<<<<< explain how
- it is possible to add executable Smalltalk code ...... <<<<<<<
explain how to do it.
...................................................................................................................................


Issues:

a) in
     Squeak / Core Packages / Commonly used / Compression /
     I have a clickable link that is 'Archive' (black) which opens a
SystemBrowser on class 'Archive'


b)
     Squeak / Core Packages /  Commonly used / Installer /
......... NO LINKS and NO EXECUTABLE code


c)
     Squeak / Core Packages /  Commonly used / ToolBuilder
        there is a black (SystemBrowser) link to debugger and
        a blue (ClassBrowser) link to Toolbuilder

These formatting notes have to go into a book called 'Creating Help
Files' under 'Help on Help'.

How do I create a black (SystemBrowser) link?
How do I create a blue (ClassBrowser) link?

There also needs to be a note for in Squeak / Tutorials / Useful Expression /
      that any executable code may be selected and executed by CMD-D.

Noteworthy in this discussion is  that we could  add more content for
the Installer .....(see screen shot)


On 8/30/19, Chris Muller <[hidden email]> wrote:

> On Thu, Aug 29, 2019 at 12:17 PM H. Hirzel <[hidden email]> wrote:
>
>> On 8/29/19, tim Rowledge <[hidden email]> wrote:
>> [snip]
>> > I'm not currently very familiar with feeding stuff into
>> > the HelpBrowser nicely.
>> [snip]
>>
>> This might be considered as a request for a tutorial on how to write
>> Help browser entries with style and executable code. (within the help
>> browser)
>>
>
> 1.  Open the Help entry in the Help browser.
> 2.  Type the updated text into the Help entry.
>      - Cmd+6 = Colored text,
>        Cmd+7 = bold,
>        Cmd+8 = italics,
>        Cmd+_ = Underline
> 3.  Press Cmd+s to save the entry with the updated text.
> 4.  Note the dirty -Help package in Monticello browser.
>
>
>
>> >
>> > tim
>>
>>
>



HelpBrowser_Core-Packages_Commonly-Used_Installer.png (52K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

timrowledge
In reply to this post by Chris Muller-3


> On 2019-08-30, at 1:25 PM, Chris Muller <[hidden email]> wrote:
>
>
> On Thu, Aug 29, 2019 at 12:17 PM H. Hirzel <[hidden email]> wrote:
> On 8/29/19, tim Rowledge <[hidden email]> wrote:
> [snip]
> > I'm not currently very familiar with feeding stuff into
> > the HelpBrowser nicely.
> [snip]
>
> This might be considered as a request for a tutorial on how to write
> Help browser entries with style and executable code. (within the help
> browser)
>
> 1.  Open the Help entry in the Help browser.
> 2.  Type the updated text into the Help entry.
>      - Cmd+6 = Colored text,  
>        Cmd+7 = bold,  
>        Cmd+8 = italics,  
>        Cmd+_ = Underline
> 3.  Press Cmd+s to save the entry with the updated text.
> 4.  Note the dirty -Help package in Monticello browser.

This works really nicely in the right sort of help topics - the subclasses of CustomHelp that work with ClassBasedHelpTopic or DirectoryBasedHelpTopic, so far as I can see right now.

Given that editing works for these sort of entries it would be nice if someone knows how to prevent attempted editing in cases where something can't be edited.
For example,
HelpBrowser openOn: self all
opens a help book on all the classes and comments and methods etc - but you can't save anything even though you can edit. It would avoid a little confusion, which is always nice.

Even nicer but probably a tad harder would be to make editing work here; I could imagine it working for the class comments but the listed method names & first comments would be a bit odd to edit. Perhaps extend the linking attributes set for the method names to include the comment might help - that way any attempt to edit would open a 'proper' browser?

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
"Bother," said Pooh, reading his bank statement from Barings.



Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Installer-Core-tpr.434.mcz

Karl Ramberg
In reply to this post by Hannes Hirzel
It you look at tools help for the debugger. I made the help topic show some screenshots. That can be useful when explaining graphical tools. But I don't remember how I did that.... I think it was kind of a hack.
I'll see if I can find a way to recreate that and document it.

Best,
Karl

On Sat, Aug 31, 2019 at 1:24 AM H. Hirzel <[hidden email]> wrote:
Thank you Chris, for the start, an attempt at continuing
...............................................................................................................

1.  Open the Help entry in the Help browser.
2.  Type the updated text into the Help entry.
     - Cmd+6 = Colored text,
       Cmd+7 = bold,
       Cmd+8 = italics,
       Cmd+_ = Underline
3.  Press Cmd+s to save the entry with the updated text.
4.  Note the dirty -Help package in Monticello browser.

Note:
- you may also add your own *CustomHelp* subclass in your package
<<<<< explain how
- it is possible to add executable Smalltalk code ...... <<<<<<<
explain how to do it.
...................................................................................................................................


Issues:

a) in
     Squeak / Core Packages / Commonly used / Compression /
     I have a clickable link that is 'Archive' (black) which opens a
SystemBrowser on class 'Archive'


b)
     Squeak / Core Packages /  Commonly used / Installer /
......... NO LINKS and NO EXECUTABLE code


c)
     Squeak / Core Packages /  Commonly used / ToolBuilder
        there is a black (SystemBrowser) link to debugger and
        a blue (ClassBrowser) link to Toolbuilder

These formatting notes have to go into a book called 'Creating Help
Files' under 'Help on Help'.

How do I create a black (SystemBrowser) link?
How do I create a blue (ClassBrowser) link?

There also needs to be a note for in Squeak / Tutorials / Useful Expression /
      that any executable code may be selected and executed by CMD-D.

Noteworthy in this discussion is  that we could  add more content for
the Installer .....(see screen shot)


On 8/30/19, Chris Muller <[hidden email]> wrote:
> On Thu, Aug 29, 2019 at 12:17 PM H. Hirzel <[hidden email]> wrote:
>
>> On 8/29/19, tim Rowledge <[hidden email]> wrote:
>> [snip]
>> > I'm not currently very familiar with feeding stuff into
>> > the HelpBrowser nicely.
>> [snip]
>>
>> This might be considered as a request for a tutorial on how to write
>> Help browser entries with style and executable code. (within the help
>> browser)
>>
>
> 1.  Open the Help entry in the Help browser.
> 2.  Type the updated text into the Help entry.
>      - Cmd+6 = Colored text,
>        Cmd+7 = bold,
>        Cmd+8 = italics,
>        Cmd+_ = Underline
> 3.  Press Cmd+s to save the entry with the updated text.
> 4.  Note the dirty -Help package in Monticello browser.
>
>
>
>> >
>> > tim
>>
>>
>



Reply | Threaded
Open this post in threaded view
|

Installer cleverness (was Re: The Inbox: Installer-Core-tpr.434.mcz)

timrowledge
In reply to this post by timrowledge
Outside the general discussion about HelpBrowser etc, I've just noticed the extremely clever parts of Installer that use the methods in the 'package-definitions' protocol.

It's a whole parallel set of ways to load packages that wasn't mentioned in the pbwiki doc I was originally looking at and stealing from. It means of course, another tranche of stuff to try to describe ;-)

Take a look at, for example,
`Installer new merge: #osProcess`

a) I'd say adding a class side #merge: to avoid the #new is worth it
b) way easier to tell someone to use than the whole open monticello, find the repository, click on... etc etc
c) possibly easier to describe even than
`Installer ss package: 'OSProcess'; install`
and its relatives, since you don't need to know where packages live once they are specified.
d) it does make another place that needs checking as part of release to make sure the package definitions are up to date etc

There are also a bunch of utilities that I suspect are primarily aimed at supporting PersonalSqueakSource usage and that manipulate repository connections and locality. I have read the swiki page (http://wiki.squeak.org/squeak/6366) but honestly it's just too succinct to  work for me. More explanation would certainly help!

This yet another example of how we collectively manage to hide so much stuff under bushels; there's loads of seriously cool things we ought to be using more and making more noise about.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Useful Latin Phrases:- Fac ut gaudeam = Make my day.



Reply | Threaded
Open this post in threaded view
|

Re: Installer cleverness (was Re: The Inbox: Installer-Core-tpr.434.mcz)

Chris Muller-3
On Sat, Aug 31, 2019 at 12:30 PM tim Rowledge <[hidden email]> wrote:
Outside the general discussion about HelpBrowser etc, I've just noticed the extremely clever parts of Installer that use the methods in the 'package-definitions' protocol.

It's a whole parallel set of ways to load packages that wasn't mentioned in the pbwiki doc I was originally looking at and stealing from. It means of course, another tranche of stuff to try to describe ;-)

Take a look at, for example,
`Installer new merge: #osProcess`

a) I'd say adding a class side #merge: to avoid the #new is worth it
b) way easier to tell someone to use than the whole open monticello, find the repository, click on... etc etc
c) possibly easier to describe even than
`Installer ss package: 'OSProcess'; install`
and its relatives, since you don't need to know where packages live once they are specified. 

Yes, I like and use it too.
 
d) it does make another place that needs checking as part of release to make sure the package definitions are up to date etc

Not as part of the release process, but simply regular development of the packages affected by new dependency requirements.  These are logical package hierarchies (i.e., just the names and repositories, no notion of physical "versions" anywhere), so its only when a developer enhances a package to suddenly need an all-new dependent that they would update its package-definition in Installer.
 

There are also a bunch of utilities that I suspect are primarily aimed at supporting PersonalSqueakSource usage and that manipulate repository connections and locality.

Of which utilities do you speak?   There's no utilities specific to PersonalSqueakSource that I can recall.  PersonalSqueakSource is entirely its own external package.

I have read the swiki page (http://wiki.squeak.org/squeak/6366) but honestly it's just too succinct to  work for me. More explanation would certainly help!

I just looked at it and it seems to all be there -- perhaps as the author it's hard for me to understand which parts need more explanation.  A lot of things which express a somewhat complex concept require more than one reading...

 - Chris
 

This yet another example of how we collectively manage to hide so much stuff under bushels; there's loads of seriously cool things we ought to be using more and making more noise about.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Useful Latin Phrases:- Fac ut gaudeam = Make my day.





Reply | Threaded
Open this post in threaded view
|

Re: Installer cleverness (was Re: The Inbox: Installer-Core-tpr.434.mcz)

Jakob Reschke
Hi everyone,

Oh, another dependency management facility. Is this specific to Monticello repositories or can it install from other sources as well? I am wondering whether or not much of this code rather belongs in InstallerMonticello.

It seems unclear to me where you are supposed to maintain your project's dependency tree with this one. In Squeak trunk or in your project's repository? Unless your project's dependency tree listing is admitted into trunk, you need your own Installer subclass or extension and make sure to have it loaded before loading the actual project. Similar to loading the latest Metacello before being able to use the Metacello install snippets from GitHub projects.

On the positive side, this code in Installer is arguably easier to understand than the one in Metacello.

Am Sa., 31. Aug. 2019 um 23:43 Uhr schrieb Chris Muller <[hidden email]>:
On Sat, Aug 31, 2019 at 12:30 PM tim Rowledge <[hidden email]> wrote:
It's a whole parallel set of ways to load packages that wasn't mentioned in the pbwiki doc I was originally looking at and stealing from. It means of course, another tranche of stuff to try to describe ;-)

Take a look at, for example,
`Installer new merge: #osProcess`

a) I'd say adding a class side #merge: to avoid the #new is worth it
b) way easier to tell someone to use than the whole open monticello, find the repository, click on... etc etc
c) possibly easier to describe even than
`Installer ss package: 'OSProcess'; install`
and its relatives, since you don't need to know where packages live once they are specified. 

Yes, I like and use it too.

From the author timestamps it also looks like you wrote it, Chris.
 
 
d) it does make another place that needs checking as part of release to make sure the package definitions are up to date etc

Not as part of the release process, but simply regular development of the packages affected by new dependency requirements.  These are logical package hierarchies (i.e., just the names and repositories, no notion of physical "versions" anywhere), so its only when a developer enhances a package to suddenly need an all-new dependent that they would update its package-definition in Installer.

It seems to offer at least in part what Metacello does with its baselines (dependency names and locations), but omits its configurations (stating versions of the packages). If the dependency versions cannot be locked down, things might break in the future if dependencies change in a backwards-incompatible manner. Can the versions be pinned?

 
I have read the swiki page (http://wiki.squeak.org/squeak/6366) but honestly it's just too succinct to  work for me. More explanation would certainly help!

I just looked at it and it seems to all be there -- perhaps as the author it's hard for me to understand which parts need more explanation.  A lot of things which express a somewhat complex concept require more than one reading...

As a developer and knowing Monticello I think I understood what is written on that page.
@tim: What specifically did you miss or not understand?
@Chris: May I suggest you put your name in the example section ("Seamless partition ...") on that page? Because now the text reads "I", but without knowing that the things prefixed with Ma are yours, one does not know who "I" is.

The sudden switch from Installer to MyInstaller, without first defining what the latter is or where it comes from, is a little confusing though.

Facilities like copyLocalVersionsToRemoteFor:... don't belong into a class called "Installer" IMHO. This is rather a Monticello utility.

In which cases would you suggest that newcomers use this mechanism for their project? What are the use cases, compared to Metacello, or SqueakMap, since the wiki page claims that "It is not intended to replace any [of them]"?

Kind regards,
Jakob


Reply | Threaded
Open this post in threaded view
|

Re: Installer cleverness (was Re: The Inbox: Installer-Core-tpr.434.mcz)

timrowledge
In reply to this post by Chris Muller-3


> On 2019-08-31, at 2:43 PM, Chris Muller <[hidden email]> wrote:
>
> On Sat, Aug 31, 2019 at 12:30 PM tim Rowledge <[hidden email]> wrote:
>
> d) it does make another place that needs checking as part of release to make sure the package definitions are up to date etc
>
> Not as part of the release process, but simply regular development of the packages affected by new dependency requirements.  These are logical package hierarchies (i.e., just the names and repositories, no notion of physical "versions" anywhere), so its only when a developer enhances a package to suddenly need an all-new dependent that they would update its package-definition in Installer.

Yes, sure; but I'd argue that we should try to make sure they all actually work as part of the release process. Things get broken...

>  
>
> There are also a bunch of utilities that I suspect are primarily aimed at supporting PersonalSqueakSource usage and that manipulate repository connections and locality.
>
> Of which utilities do you speak?   There's no utilities specific to PersonalSqueakSource that I can recall.  PersonalSqueakSource is entirely its own external package.

OK; there are methods that look(ed) to me (with my already declared mild confusion) as if they are PSS related.
eg
Installer>>#copyLocalVersionsToRemoteFor:
Installer class>>#airplaneMode
Installer class>>#overrideRemoteRepostoriesWith:
Installer class>>#suspendRepositoryOverridesWhile:

>
> I have read the swiki page (http://wiki.squeak.org/squeak/6366) but honestly it's just too succinct to  work for me. More explanation would certainly help!
>
> I just looked at it and it seems to all be there -- perhaps as the author it's hard for me to understand which parts need more explanation.  A lot of things which express a somewhat complex concept require more than one reading...

Exactly. The problem is that we all tend to write documentation (on the far too rare occasions when we write anything at all) that makes perfect sense once you know what it means. This is why good documenters are so valuable.

It's late enough now that I'll leave more explanation for tomorrow in the hope it will not add confusion.


tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Press [ESC] to detonate or any other key to explode.



Reply | Threaded
Open this post in threaded view
|

Re: Installer cleverness (was Re: The Inbox: Installer-Core-tpr.434.mcz)

Chris Muller-4
In reply to this post by Jakob Reschke
Hi Jakob,
 
Oh, another dependency management facility.

I don't think of it that way.  They're just documentation in literal arrays which happen to facilitate a few use cases.
 
Is this specific to Monticello repositories or can it install from other sources as well? I am wondering whether or not much of this code rather belongs in InstallerMonticello.

I would rather deprecate every subclass below Installer that currently resides in trunk.  Sake and Universe can extend Installer subclasses in their own packages, if anyone is still using them.  Installer's responsibility is to help users get stuff installed, so IMO we should simplify Installer to have just what we settled on for our core SCM tool, and let it advance with things like these more expressive package-definitions and stuff.
 
It seems unclear to me where you are supposed to maintain your project's dependency tree with this one. In Squeak trunk or in your project's repository?

It's entirely up to you.  There's generally no opposition if you want to include your own project-definition in Installer-Core (trunk).  The cost (one method returning an Array literal) is infinitesimal relative to the potential brought by easy access to your system.  Squeak's most core projects which are generally useful, like FFI and OSProcess, are certainly useful to document in Installer-Core (trunk).
 
Unless your project's dependency tree listing is admitted into trunk, you need your own Installer subclass or extension and make sure to have it loaded before loading the actual project. Similar to loading the latest Metacello before being able to use the Metacello install snippets from GitHub projects.

Yes.  I organize my public packages that work together like Magma and Maui into MaInstaller.  But then, I have a set of private Maui applications which I put into a deeper subclass, MaCommercialInstaller.

That way, IDE configuration is equally seamless with one's own private projects as for public ones -- for example, the "mc revisions" and "origin" setup is done by configuring MC repositories, I can just say:

    Installer addLocalRepositories

it's enumerates all loaded projects, calculates and adds their local repository to each WorkingCopy.
 
On the positive side, this code in Installer is arguably easier to understand than the one in Metacello.

It's all positive, I hope!  :)   It really is just about advancing Installer.  It can't replace Metacello.  The two serve different purposes.

d) it does make another place that needs checking as part of release to make sure the package definitions are up to date etc

Not as part of the release process, but simply regular development of the packages affected by new dependency requirements.  These are logical package hierarchies (i.e., just the names and repositories, no notion of physical "versions" anywhere), so its only when a developer enhances a package to suddenly need an all-new dependent that they would update its package-definition in Installer.

It seems to offer at least in part what Metacello does with its baselines (dependency names and locations), but omits its configurations (stating versions of the packages). If the dependency versions cannot be locked down, things might break in the future if dependencies change in a backwards-incompatible manner. Can the versions be pinned?

Yes, Installer>>#primMerge:from: first checks for an exact match on the specified "packageName" (e.g., as a version name) before choosing the #highestNumberedVersionForPackageNamed:.

But it hasn't been used that way.  Just imagining the idea of starting to add a bunch of version-specific methods -- it would really dilute the efficiency of its presence.  Not worth it, IMO, especially when we already have Metacello and SqueakMap to do that.  But, it's a rational behavior and a nice potential backstop for a possible special needs case...
 

 
I have read the swiki page (http://wiki.squeak.org/squeak/6366) but honestly it's just too succinct to  work for me. More explanation would certainly help!

I just looked at it and it seems to all be there -- perhaps as the author it's hard for me to understand which parts need more explanation.  A lot of things which express a somewhat complex concept require more than one reading...

As a developer and knowing Monticello I think I understood what is written on that page.
@tim: What specifically did you miss or not understand?
@Chris: May I suggest you put your name in the example section ("Seamless partition ...") on that page? Because now the text reads "I", but without knowing that the things prefixed with Ma are yours, one does not know who "I" is.

The sudden switch from Installer to MyInstaller, without first defining what the latter is or where it comes from, is a little confusing though.

Okay, thanks for the feedback.  I'll take a look.
 

Facilities like copyLocalVersionsToRemoteFor:... don't belong into a class called "Installer" IMHO. This is rather a Monticello utility.

In which cases would you suggest that newcomers use this mechanism for their project? What are the use cases, compared to Metacello, or SqueakMap, since the wiki page claims that "It is not intended to replace any [of them]"?

Even if you use Metacello, setting up these literal arrays can be very useful in helping to configure your repositories on your WorkingCopies.  Especially if you use Personal SqueakSource, but even if you don't, the #addLocalRepositories example above can be really nice.   It ensures there's one for your local directory, one for remote repository and, if it finds a Personal SqueakSource running on localhost, the http entry for it (so that revisions and origin can work)).  That's three per package -- can you imagine having to do that manually?!

Regards,
  Chris 



Kind regards,
Jakob


Reply | Threaded
Open this post in threaded view
|

Re: Installer cleverness (was Re: The Inbox: Installer-Core-tpr.434.mcz)

Chris Muller-3
In reply to this post by timrowledge
> Not as part of the release process, but simply regular development of the packages affected by new dependency requirements.  These are logical package hierarchies (i.e., just the names and repositories, no notion of physical "versions" anywhere), so its only when a developer enhances a package to suddenly need an all-new dependent that they would update its package-definition in Installer.

Yes, sure; but I'd argue that we should try to make sure they all actually work as part of the release process. Things get broken...

You're welcome to, but keep in mind they could start failing again the very next day.  These are for loading the (head) versions so can never be guaranteed to work.  That's why we make fixed versions entry's for each release, to have one that provides that guarantee.

 - Chris