[Pkg] Packages: Sake-Packages-kph.33.mcz

squeak-dev-noreply at lists.squeakfoundation.org squeak-dev-noreply at lists.squeakfoundation.org
Wed Jul 1 13:37:55 UTC 2009


A new version of Sake-Packages was added to project Packages:
http://www.squeaksource.com/Packages/Sake-Packages-kph.33.mcz

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

Name: Sake-Packages-kph.33
Author: kph
Time: 1 July 2009, 12:00 am
UUID: 921c3dd5-cd45-4885-9427-6bead7ffe9ca
Ancestors: Sake-Packages-kph.32

Simplified

merged in what were classes #beta to add an alternative load action #latest: which can be invoked using #beLatest.

Simplified the #findPath

Updated class comment

=============== Diff against Sake-Packages-kph.32 ===============

Item was changed:
  ----- Method: Packages class>>findPath (in category 'private') -----
  findPath
  
+ 	^ (self withAllSubclasses select: [ :ea  | ea priority < 9999 ]) asSortedCollection!
- 	^ { self current. self dev. Seaside29. self beta. Seaside29Beta }!

Item was changed:
  ----- Method: Packages class>>unload: (in category 'public') -----
  unload: aNameOrList
  
+ 	aNameOrList isString ifTrue: [ ^ (self providedAt: aNameOrList) beUnloading run].
- 	aNameOrList isString ifTrue: [ ^ (self providedAt: aNameOrList) unload run].
  	
+ 	^ (aNameOrList collect: [ :ea |  (self providedAt: aNameOrList) beUnloading ]) asTask run
- 	^ (aNameOrList collect: [ :ea |  (self providedAt: aNameOrList) unload ]) asTask run
   !

Item was changed:
  ----- Method: Packages>>defaultUnloadAction (in category 'defaults') -----
  defaultUnloadAction
  
+ 	Installer mc unload: self mcName!
- 	Installer mc unload: (self info mcName ifNil: [ self name])!

Item was added:
+ ----- Method: Packages>>latest: (in category 'accessing') -----
+ latest: aBlockOrListOfTasks
+ 
+ 	latest := aBlockOrListOfTasks!

Item was changed:
+ ----- Method: Packages>>addToPackageInfo (in category 'Sake-Packages') -----
- ----- Method: Packages>>addToPackageInfo (in category 'as yet unclassified') -----
  addToPackageInfo
  
      "
      Here we tell the PackageInfo instance what name was used to load it.
  
     if a package appears in PackageInfo under a different name to which it
      appears in Packages, the PackageInfo name can be told to us via
      metadata #mcName:  Example: 'Seaside' is in PackageInfo as 'Seaside2'.   
      "
  	
+ 	(PackageOrganizer default packageNamed: self mcName ifAbsent: [ ^ self ])
- 	(self info mcName ifNil: [ self name ]) ifNotNilDo: [ :mcName |
- 		(PackageOrganizer default packageNamed: mcName ifAbsent: [ ^ self ])
  			in: [ :pkgInfo |
  				(pkgInfo respondsTo: #propertyAt:put:)
  					ifTrue: [ pkgInfo propertyAt: #packages put: self name ].
  			].
+ 	
- 	]. 
  	!

Item was added:
+ ----- Method: Packages class>><= (in category 'private') -----
+ <= pkgClass
+ 
+ 	^ self priority <= pkgClass priority!

Item was changed:
  ----- Method: Packages class>>theUUniverse (in category 'accessors') -----
  theUUniverse
  
+ 	^ theUUniverse 	ifNil: [ theUUniverse := (Smalltalk classNamed: 'UUniverse') perform: self universeSelector asSymbol ]!
- 	^ theUUniverse 
- 	ifNil: [ theUUniverse := (Smalltalk classNamed: 'UUniverse') perform: self universeSelector asSymbol ]!

Item was changed:
  ----- Method: Packages>>unload (in category 'accessing') -----
  unload
  
+ 	^ unload!
- 	^ self copy beUnloading !

Item was changed:
  ----- Method: Packages class>>update (in category 'public') -----
  update
  	"load the latest definitions"
+ 	Packages load: 'Packages'.
- 	Packages current load: 'Packages'.
  !

Item was added:
+ ----- Method: Packages>>mcName: (in category 'accessing') -----
+ mcName: n
+ 
+ 	mcName := n!

Item was changed:
  ----- Method: Packages>>doActionEnd (in category 'as yet unclassified') -----
  doActionEnd
  
  	self isUnloading ifTrue: [ ^ self ].
  	
  	self class provided in: [ :reg |
  		info dependsOn: (self dependsOn collect: [ :ea | ea asString ]).
  		info provides: self provides.
  		info class: self class name.
  		self provides do: [ :each | reg at: each put: info ].
  	].
  
- 	"if a package appears in Packages under an obscure name, it can
- 	tell the PackageInfo instance what name was used to load it via metadata
- 	at mcName"
- 	
  	self addToPackageInfo.
  	!

Item was changed:
  ----- Method: Packages>>= (in category 'comparing') -----
  = other 
  
+ 	^ (super = other) and: [ self version = other version ]
- ^ (super = other) and: [ self version = other version ]
  !

Item was changed:
+ ----- Method: Packages>>beUnloading (in category 'mode') -----
- ----- Method: Packages>>beUnloading (in category 'as yet unclassified') -----
  beUnloading
  
  	isUnload := true.
  	hasRun := false.!

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

Item was changed:
+ ----- Method: Packages>>action (in category 'defaults') -----
+ action 
- ----- Method: Packages>>action (in category 'accessing') -----
- action
  
+ 	self useLatest ifTrue: [ ^ latest ifNil: [ self defaultLatestAction ] ].
+ 
+ 	^ actionBlock ifNil: [ self defaultAction ]!
- 	^ self isUnloading 
- 		ifTrue: [ unloadBlock ifNil: [ [ self defaultUnloadAction ] ] ]
- 		ifFalse: [ super action ].!

Item was changed:
  ----- Method: Packages class>>unloadStepping: (in category 'public') -----
  unloadStepping: aNameOrList
  
+ 	aNameOrList isString ifTrue: [ ^ (self providedAt: aNameOrList) beUnloading runStepping].
- 	aNameOrList isString ifTrue: [ ^ (self providedAt: aNameOrList) unload runStepping].
  	
+ 	^ (aNameOrList collect: [ :ea |  (self providedAt: aNameOrList) beUnloading ]) asTask runStepping
- 	^ (aNameOrList collect: [ :ea |  (self providedAt: aNameOrList) unload ]) asTask runStepping
   !

Item was changed:
  ----- Method: Packages class>>findNamed: (in category 'private') -----
  findNamed: packageName 
  	 
  	| sel |
  	
  	sel := self asSelector: packageName.
  	
+ 	(self canPerform: sel) ifTrue: [ ^ self basicNamed: packageName ].
+ 	
  	^ (self findPath detect: [ :ea | ea canPerform: sel ] ifNone: [ ^nil ]) basicNamed: packageName!

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

Item was changed:
  ----- Method: MCWorkingCopy>>myMenuForPackages: (in category '*sake-packages') -----
  myMenuForPackages: aMenu
  
  	(self packageInfo propertyAt: #packages) ifNotNilDo: [ :pkgName |
  		aMenu
  			add: 'load latest release using Sake/Packages' 
+ 			target: (Packages named: pkgName) 
- 			target: (Packages current named: pkgName) 
  			selector: #run.
  		
  		aMenu 
  			add: 'load latest code using Sake/Packages' 
+ 			target: (Packages named: pkgName) beLatest
- 			target: (Packages beta named: pkgName) 
  			selector: #run.		
  	]. !

Item was added:
+ ----- Method: Packages class>>relevantVersions (in category 'private') -----
+ relevantVersions
+ 
+ 	^ #()!

Item was added:
+ ----- Method: Packages>>defaultLatestAction (in category 'defaults') -----
+ defaultLatestAction
+ 
+ 	^ [ self info url ifNotNilDo: [ :url | (Installer fromUrl: url) latest install ] ]!

Item was added:
+ ----- Method: Packages>>beLatest (in category 'mode') -----
+ beLatest
+ 
+ 	self versionIndefinite.
+ 	useLatest := true!

Item was added:
+ ----- Method: Packages class>>priority (in category 'private') -----
+ priority
+ 
+ 	"ignore universes"
+ 	(self name last =  $U) ifTrue: [ ^ 9999 ].
+ 
+ 	"any class that has the image version explicitly listed is a front runner" 
+ 	(self relevantVersions includes: SystemVersion current majorMinorVersion) ifTrue: [ ^ 100 ].
+ 		
+ 	self name = #PackagesAll ifTrue: [ ^ 500 ].
+ 		
+ 	^ 9999
+ 	
+ 	"
+ 	self findPath
+ 	"
+ 
+ !

Item was changed:
  ----- Method: Packages>>unload: (in category 'accessing') -----
+ unload: aBlockOrListOfTasks
- unload: aBlock
  
+ 	unload := aBlockOrListOfTasks!
- 	unloadBlock := aBlock!

Item was changed:
+ ----- Method: Packages>>allDependants (in category 'as yet unclassified') -----
- ----- Method: Packages>>allDependants (in category 'Packages-Core') -----
  allDependants
  
  	| list |
  
  	list := OrderedCollection new.
  
  	self provides in: [ :tgt |
  
  		self class allPackagesDo: [ :package |
  
  			package withAllPriorTasksIgnoringErrorsDo: [ :ea |
  				(ea dependsOn includesAnyOf: tgt) ifTrue: [ (list includes: package) ifFalse: [ list add: package ] ].
  			] 	
  		]
  	].
  
  	^ list
  	
  "
  String streamContents: [ :str | (Packages current named:'Seaside') allDependants do: [ :ea | str << ea info name << String cr << ea info description << String cr << '======='; cr ] ]
  "!

Item was changed:
  ----- Method: Packages>>defaultAction (in category 'defaults') -----
  defaultAction
+ 	
- 
  	^ [ self info url ifNotNilDo: [ :url |  (Installer fromUrl: url) install  ] ]!

Item was changed:
  ----- Method: Packages class>>launchWith: (in category 'launcher') -----
  launchWith: params
  
  	| packagesClass task | 
  	
+ 	packagesClass := self.
- 	packagesClass := self current.
  	
-  	params at: 'B' ifPresent: [ :v | params at: 'BETA' put: v ].
   	params at: 'U' ifPresent: [ :v | params at: 'UNLOAD' put: v ].
   	params at: 'L' ifPresent: [ :v | params at: 'LOAD' put: v ].
+  	params at: 'B' ifPresent: [ :v | params at: 'BETA' put: v ].
-  
- 	params at: 'BETA' ifPresent: [ :v | 
- 		v ifTrue: [ packagesClass := self beta ].
- 	].
  
  	params at: 'LOAD' ifPresent: [ :v | 
  		task := packagesClass collection: (v findTokens: ';')		
  	].
   
  	params at: 'UNLOAD' ifPresent: [ :v | 
+ 		task := SakeTask collection: ((v findTokens: ';') collect: [ :ea | (self named: ea) beUnloading ])	
+ 	].
- 		task := SakeTask collection: ((v findTokens: ';') collect: [ :ea | (self named: ea) unload ])	
- 	].
  
+ 	params at: 'BETA' ifPresent: [ :v | 
+ 		task := SakeTask collection: ((v findTokens: ';') collect: [ :ea | (self named: ea) beLatest ])	
+ 	].
   
  	task launch: params.
  	
  	^ true!

Item was added:
+ ----- Method: Packages>>taskFrom: (in category 'initialize') -----
+ taskFrom: aDependent
+ 
+ 	| task |
+ 	
+ 	task := super taskFrom: aDependent.
+ 	
+ 	self useLatest ifTrue: [ task beLatest ].
+ 	
+ 	^ task!

Item was added:
+ ----- Method: Packages>>mcName (in category 'accessing') -----
+ mcName
+ 
+ 	"The name that monticello uses for this package"
+ 	
+ 	^ mcName ifNil: [ self name ]!

Item was changed:
  ----- Method: Packages>>isAlreadyProvided (in category 'comparing') -----
  isAlreadyProvided
  
+ 	"means the package is being loaded without specifying any fixed version"
+ 	self version last = $+  ifTrue: [ ^ false ]. 
- 	(self class isBeta or: [ self version last = $+ ]) ifTrue: [ ^ false ]. "means the package is being loaded without specifying any fixed version"
- 
- 	^ (self class provided at: self name ifAbsent: [ ^ false ]) version = self version
  
+ 	^ (self class provided at: self name ifAbsent: [ ^ false ]) version = self version
+ 
  !

Item was changed:
  SakeTask subclass: #Packages
+ 	instanceVariableNames: 'unload latest useLatest unloadPriors provides name mcName version isUnload'
- 	instanceVariableNames: 'unloadBlock unloadPriors provides name version isUnload'
  	classVariableNames: 'Provided'
  	poolDictionaries: ''
  	category: 'Sake-Packages'!
  Packages class
  	instanceVariableNames: 'lastUpdate theUUniverse'!
  
+ !Packages commentStamp: 'kph 7/1/2009 03:03' prior: 0!
- !Packages commentStamp: 'test 1/17/2009 00:22' prior: 0!
  Sake/Packages usage:
  
+ Definitions Search Path
+ ============================
+ Packages named: 'PackageName'.
- Public API
- ============
- Package definition for your current version of Squeak are found using the following path.
- 
- For SystemVersion Squeak3.7
- 
- Packages findPath  -> {PackagesSqueak37 . PackagesDev . PackagesBeta} *the default is #current
- Packages current findPath  -> {PackagesSqueak37 . PackagesDev . PackagesBeta}
- Packages dev findPath  {PackagesDev. PackagesSqueak37 . PackagesBeta}
- Packages beta findPath {PackagesBeta . PackagesSqueak37 . PackagesDev}
- 
- Packages current load: 'Seaside'.
- Packages beta load: 'Seaside'.
  
+ Will obtain a package definition. Subclasses of Packages are searched using the order defined by #findPath which is specified by #priority.
+ 
+ e.g. Packages findPath => {PackagesSqueak310 . PackagesDev . PackagesAll . PackagesSeaside29}
+ 
+ Packages-#priority is used to sort classes like so:
+ 
+ The class with defns for a relevant version (listed in #relevantVersions) => 100
+ The class with defns for dev version (PackagesDev) => 400
+ The class with defns for all versions (PackagesAll) => 500
- or
- 
- (Packages current named: 'Seaside') run.  " or runQuietly, runStepping, runLogging"
- (Packages beta named: 'Seaside') run.
- 
- multiples:
- 
- Packages current load: #('Seaside' 'Magma' 'Logging')  
  
+ Additional package "universes" can define their own priority in order to specify where to appear in the #findPath.
+ PackagesSeaside29
+ PackagesGjaller
+ PackagesBeach
+ 
+ Usage:
+ ========
+ verbose usage specifying run style.
+ 
+ (Packages named: 'Seaside') run.  " or runQuietly, runStepping, runLogging"
- Run-variants
- =========
  
  #runStepping , - presents a confirm/debug dialog before each action.
+ #run            - default.
+ #runQuietly    - auto-confirms any SakeConfirm dialogs.
+ #runLogging   - Writes any SakeStop warnings to self log.
+ 
+ default usage:
- #run                 - default.
- #runQuietly     - auto-confirms any SakeConfirm dialogs.
- #runLogging    - Writes any SakeStop warnings to self log.
- 
- Unloading
- ========
- Unloading comes in two variants.
- 
- Each package task loaded by Sake/Packages is remembered in the 'provided' list
- If you perform:
- 
-     Packages unload: 'Seaside' .
- 
-     Packages unloadStepping: 'Seaside' .
- 
- Then the 'historical' unload scripts are used, as defined when the original load tasks were run.
- 
- If instead you perform:
- 
-     (Packages current named: 'Seaside') unload runStepping.
-  
- Then the most recently defined unload script will be run.
- 
- Note: If packages such as "Magma server" and "Magma client" provides "Magma", then
- 
-     Packages unload: 'Magma'.
- 
- Will unload whichever of the two are loaded.
- ===
- Misc notes...
- 
- Universes are using 'instance side' task definition, so the task extensions mechanism does not work in this context.
- 
- If a package appears in Packages under an obscure name, it can
- tell the PackageInfo instance what name was used to load it via metadata
- at mcName:
  
+ Packages load: 'Seaside'.
+ Packages latest: 'Seaside'. "as above, but use latest versions of everything"
+ Packages unload: 'Seaside'.
+ 
+ multiples:
+ 
+ Packages load: #('Seaside' 'Magma' 'Logging')  
+ 
+ Unloading
+ ========
+ Unloading comes in two variants.
+ 
+ Each package task loaded by Sake/Packages is remembered in the 'provided' list
+ If you perform:
+ 
+     Packages unload: 'Seaside' .
+ 
+     Packages unloadStepping: 'Seaside' .
+ 
+ Then the 'historical' unload scripts are used, as defined when the original load tasks were run.
+ 
+ If instead you perform:
+ 
+     (Packages current named: 'Seaside') beUnloading runStepping.
+  
+ Then the most recently defined unload script will be run.
+ 
+ Note: If packages such as "Magma server" and "Magma client" provides "Magma", then
+ 
+     Packages unload: 'Magma'.
+ 
+ Will unload whichever of the two are loaded.
+ ===
+ Misc notes...
+ 
+ Universes are using 'instance side' task definition, so the task extensions mechanism does not work in this context.
+ 
+ If a package appears in Packages under an obscure name, it can
+ tell the PackageInfo instance what name was used to load it via #mcName:
+ 
+ If a package has a version number with a '+' after it, then 'Packages upgrade' will always attempt to load the latest code, leaving Monticello to determine if there are any code changed that need to be applied.
- If a package has a version number with a '+' after it, then 'Packages upgrade' will always attempt to load the latest code, leaving Monticello to determing if there are any code changed that need to be applied.
  
  To generate all of the methods based upon universes definitions:
  	
   	Packages taskGenerateAllUniverses run.
  	or
  	Packages taskGenerateAll  run.!

Item was removed:
- ----- Method: Packages class>>beta (in category 'public') -----
- beta
- 
- 	^ PackagesBeta!

Item was removed:
- ----- Method: Packages class>>isBeta (in category 'testing') -----
- isBeta
- 	^ self name endsWith: 'Beta' !

Item was removed:
- ----- Method: Packages class>>UUniverse (in category 'public') -----
- UUniverse
- 
- 	^ Smalltalk classNamed: 'UUniverse'
- !



More information about the Packages mailing list