[Cuis-dev] Integrate package installer and downloader

Mariano Montone marianomontone at gmail.com
Tue Dec 28 09:15:49 PST 2021


Hello Juan,

I'd like to integrate my package installer and downloader tools somehow,
so that they don't get "lost".

I attach their current versions.

PackageInstaller - Tool for installing local packages. Could be
integrated to Cuis core if it is good enough. Or as a package.

PackageDownloader - Tool for downloading and installing packages from
the internet. Integrate as a package.

PackageDownloaderUtils - Utilities for managing the lists of CSV/JSON
packages that the Downloader tool uses. (So that other than me can do it
too.)

Please let me know of anything I can do to move this forward.

Thanks,

Mariano

PD: I also attach ExamplesBrowser; would like to integrate that too as a
package if you think is good to have.
-------------- next part --------------
'From Cuis 5.0 [latest update: #4999] on 14 December 2021 at 12:18:30 pm'!
'Description '!
!provides: 'ExamplesBrowser' 1 14!
SystemOrganization addCategory: 'ExamplesBrowser'!


!classDefinition: #ExamplesBrowserWindow category: 'ExamplesBrowser'!
SystemWindow subclass: #ExamplesBrowserWindow
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ExamplesBrowser'!
!classDefinition: 'ExamplesBrowserWindow class' category: 'ExamplesBrowser'!
ExamplesBrowserWindow class
	instanceVariableNames: ''!

!classDefinition: #ExamplesBrowser category: 'ExamplesBrowser'!
Object subclass: #ExamplesBrowser
	instanceVariableNames: 'examples categoriesIndex subCategoriesIndex examplesListIndex subCategoriesList examplesList categoriesList'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'ExamplesBrowser'!
!classDefinition: 'ExamplesBrowser class' category: 'ExamplesBrowser'!
ExamplesBrowser class
	instanceVariableNames: ''!


!ExamplesBrowserWindow methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 12:05:09'!
buildMorphicWindow

	| navigationLayout categoriesList subCategoriesList examplesList content buttons docsMorph |
	
	navigationLayout _ LayoutMorph newColumn.
	
	categoriesList _ PluggableListMorph model: model 
					listGetter: #examplesCategories 
					indexGetter: #examplesCategoriesIndex 
					indexSetter: #examplesCategoriesIndex:.
					
	subCategoriesList _ PluggableListMorph model: model 
						listGetter: #examplesSubCategories
						indexGetter: #examplesSubCategoriesIndex 
						indexSetter: #examplesSubCategoriesIndex:.
						
	examplesList _ PluggableListMorph model: model 
						listGetter: #examplesList
						indexGetter: #examplesListIndex
						indexSetter: #examplesListIndex:.
						
	navigationLayout 
		addMorph: categoriesList proportionalHeight: 0.33;
		addAdjusterAndMorph: subCategoriesList proportionalHeight: 0.33;
		addAdjusterAndMorph: examplesList proportionalHeight: 0.33.
		
	layoutMorph addMorph: navigationLayout proportionalWidth: 0.33.
	
	content _ LayoutMorph newColumn.
	
	docsMorph _ TextModelMorph textProvider: model textGetter: #exampleDocumentation.
	content addMorphUseAll: docsMorph.
	
	buttons _ LayoutMorph newRow.
	
	buttons addMorph: (PluggableButtonMorph model: model action: #runExample label: 'Run').
	buttons addMorph: (PluggableButtonMorph model: model action: #inspectExample label: 'Inspect').
	buttons addMorph: (PluggableButtonMorph model: model action: #exploreExample label: 'Explore').
	buttons addMorph: (PluggableButtonMorph model: model action: #browseExample label: 'Browse').
	content addMorph: buttons fixedHeight: 30.
	
	layoutMorph addAdjusterAndMorph: content layoutSpec: LayoutSpec useAll.! !

!ExamplesBrowserWindow methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 11:12:16'!
initialize

	super initialize.
	
	self beRow.! !

!ExamplesBrowserWindow class methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 11:51:07'!
open
	"self open"
	^ self open: ExamplesBrowser new label: 'Examples browser'! !

!ExamplesBrowserWindow class methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 13:31:57'!
worldMenuForOpenGroup
	^ `{{
			#itemGroup 				-> 	10.
			#itemOrder 				-> 	50.
			#label 				->	'Examples Browser'.
			#object 				-> 	ExamplesBrowserWindow.
			#selector 				-> 	#open.
			#icon 				-> 	#morphsIcon.
			#balloonText 				-> 	'A browser tool for running examples'.
		} asDictionary}`! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 12:11:46'!
browseExample

	self currentExample ifNotNil: [:example | example browse]
		! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/14/2021 12:09:03'!
collectExamples

	"Collect examples in Smalltalk system"
	
	"Traverse all system classes looking for class methods that start with #example or are annotated with an 'example' pragma."
	
	examples _ Dictionary new.

	Smalltalk organization categories do: [:cat |
		(Smalltalk organization classesAt: cat) do: [:class | | annotatedMethods namedMethods exampleMethods |
			annotatedMethods _ (Pragma allNamed: #example in: class) collect: #method.
			namedMethods _ class class methodsSelect: [:method | method selector asString includesSubstring: 'example' caseSensitive: false].
			exampleMethods _ (annotatedMethods, namedMethods) asSet asOrderedCollection.
			exampleMethods ifNotEmpty: [ | catExamples |
				examples at: cat ifAbsent: [examples at: cat asSymbol put: Dictionary new].
				catExamples _ examples at: cat.
				catExamples at: class name put: exampleMethods]]].! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 11:49:59'!
currentCategory

	^ categoriesIndex ifNotNil: [:index | categoriesList at: index]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 11:49:41'!
currentExample

	^ examplesListIndex ifNotNil: [:index | examplesList at: index]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 11:49:21'!
currentSubCategory

	^ subCategoriesIndex ifNotNil: [:index | subCategoriesList at: index]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 12:07:19'!
exampleDocumentation

	^ self currentExample 
		ifNotNil: [:example | 
			String streamContents: [:s |
				s nextPutAll: example getSource]]
		ifNil: ['']! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/14/2021 12:13:01'!
examplesCategories
	^ categoriesList! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 10:40:42'!
examplesCategoriesIndex
	^ categoriesIndex ifNil: [0]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/12/2021 11:00:21'!
examplesCategoriesIndex: anIndex

	anIndex isZero ifTrue: [^ categoriesIndex _ nil].

	categoriesIndex _ anIndex.
	
	subCategoriesList _ (examples at: self currentCategory) keys asSortedCollection: [:x :y | x < y] .
	self changed: #examplesSubCategories.
	
	self examplesSubCategoriesIndex: 1! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 10:24:11'!
examplesInCategory: aCategory
	^ examples at: aCategory! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 13:06:35'!
examplesList
	^ examplesList collect: [:example | self formatExampleName: example selector asString]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 10:43:04'!
examplesListIndex
	^ examplesListIndex ifNil: [0]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 12:09:19'!
examplesListIndex: anIndex

	anIndex isZero ifTrue: [^ examplesListIndex _ nil].
	examplesListIndex _ anIndex.
	self changed: #exampleDocumentation! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 11:53:07'!
examplesSubCategories

	^ subCategoriesList ! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 10:42:10'!
examplesSubCategoriesIndex
	^ subCategoriesIndex ifNil: [0]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/12/2021 11:03:00'!
examplesSubCategoriesIndex: anIndex
	anIndex isZero ifTrue: [^ subCategoriesIndex _ nil].
	subCategoriesIndex _ anIndex.
	
	examplesList _ ((examples at: self currentCategory) at: self currentSubCategory)
					asSortedCollection: [:x :y | x selector < y selector].
	self changed: #examplesList.
	self examplesListIndex: 1.! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 12:35:32'!
exploreExample
	self currentExample ifNotNil: [:example | (example methodClass soleInstance perform: example selector) explore]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 13:09:46'!
formatExampleName: aString

	^ String streamContents: [:s |
		s nextPut: aString first asUppercase.
		aString allButFirstDo: [:char |
			char isDigit ifTrue: [
				s nextPut: Character space; nextPut: char]
			ifFalse: [
				char isUppercase ifTrue: [
					s nextPut: Character space;					nextPut: char asLowercase]
				ifFalse: [s nextPut: char]]]]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/14/2021 12:13:29'!
initialize

	self collectExamples.
	
	categoriesList _ examples keys asSortedCollection: [:x :y | x < y].
	subCategoriesList _ OrderedCollection new.
	examplesList _ OrderedCollection new.! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 12:35:24'!
inspectExample
	self currentExample ifNotNil: [:example | (example methodClass soleInstance perform: example selector) inspect]! !

!ExamplesBrowser methodsFor: 'as yet unclassified' stamp: 'MM 12/11/2021 12:37:28'!
runExample
	self currentExample ifNotNil: [:example | |result|
		result _ example methodClass soleInstance perform: example selector.
		(result isKindOf: Morph) ifTrue: [result openInWorld]]! !

!ExamplesBrowser class methodsFor: 'as yet unclassified' stamp: 'MM 12/12/2021 10:57:10'!
windowColor
	^ Color r: 0.2 g: 1.0 b: 0.6! !
-------------- next part --------------
'From Cuis 5.0 [latest update: #5007] on 27 December 2021 at 8:34:11 pm'!
'Description '!
!provides: 'PackageDownloader' 1 30!
!requires: 'WebClient' 1 22 nil!
!requires: 'JSON' 1 19 nil!
!requires: 'PackageInstaller' 1 28 nil!
SystemOrganization addCategory: 'PackageDownloader'!


!classDefinition: #PackageDownloaderWindow category: 'PackageDownloader'!
SystemWindow subclass: #PackageDownloaderWindow
	instanceVariableNames: 'filterString filterInput currentIndex'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'PackageDownloader'!
!classDefinition: 'PackageDownloaderWindow class' category: 'PackageDownloader'!
PackageDownloaderWindow class
	instanceVariableNames: ''!

!classDefinition: #PackageDownloader category: 'PackageDownloader'!
Object subclass: #PackageDownloader
	instanceVariableNames: 'packageList downloadDirectory'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'PackageDownloader'!
!classDefinition: 'PackageDownloader class' category: 'PackageDownloader'!
PackageDownloader class
	instanceVariableNames: ''!

!classDefinition: #RemotePackageDescription category: 'PackageDownloader'!
Object subclass: #RemotePackageDescription
	instanceVariableNames: 'packageName description provides requires downloadUrl homepage tags'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'PackageDownloader'!
!classDefinition: 'RemotePackageDescription class' category: 'PackageDownloader'!
RemotePackageDescription class
	instanceVariableNames: ''!


!PackageDownloaderWindow commentStamp: '<historical>' prior: 0!
I'm a tool for downloading and installing Cuis packages from the internet.!

!PackageDownloader commentStamp: '<historical>' prior: 0!
I'm the model for PackageDownloaderWindow.!

!RemotePackageDescription commentStamp: '<historical>' prior: 0!
I'm a description of a remote package.!

!PackageDownloaderWindow methodsFor: 'initialization' stamp: 'MM 11/25/2021 21:23:05'!
initialize
	super initialize.
	filterString _ ''.! !

!PackageDownloaderWindow methodsFor: 'GUI building' stamp: 'MM 11/26/2021 14:03:24'!
buildActionsBar

	| actionsBar | 
	
	actionsBar _ LayoutMorph newRow.
	
	actionsBar addMorph:
		(PluggableButtonMorph 
				model: self 
				action: #downloadAndInstallPackage
				label: 'Download and install package').
	actionsBar addMorph:
		(PluggableButtonMorph
				model: self
				action: #updatePackageList
				label: 'Update package list').
	
	actionsBar addMorph: (LabelMorph contents: 'Search: ').
	
	filterInput _ TextModelMorph textProvider: self textGetter: #filterString textSetter: #filterString:.
	filterInput acceptOnCR: true;
		askBeforeDiscardingEdits: false.
	actionsBar addMorph: filterInput layoutSpec: (LayoutSpec fixedHeight: 30).
	
	^ actionsBar! !

!PackageDownloaderWindow methodsFor: 'GUI building' stamp: 'MM 11/25/2021 21:23:05'!
buildDetailPane
	^ TextModelMorph textProvider:  self textGetter: #packageDescription! !

!PackageDownloaderWindow methodsFor: 'GUI building' stamp: 'MM 11/25/2021 21:23:05'!
buildMorphicWindow

	|layout|
		
	layout _ LayoutMorph newRow.
	layout addMorph: self buildPackageListMorph layoutSpec: (LayoutSpec proportionalWidth: 0.5).
	layout addAdjusterAndMorph: self buildDetailPane layoutSpec: (LayoutSpec proportionalWidth: 0.5).
	self addMorph: layout layoutSpec: (LayoutSpec proportionalWidth: 1).
	self addMorph: self buildActionsBar layoutSpec: (LayoutSpec new fixedHeight: 30; proportionalWidth: 1; yourself). 
	! !

!PackageDownloaderWindow methodsFor: 'GUI building' stamp: 'MM 11/25/2021 21:23:05'!
buildPackageListMorph
	
	^ PluggableListMorph model: self listGetter: #packageListNames indexGetter: #currentIndex indexSetter: #currentIndex:.! !

!PackageDownloaderWindow methodsFor: 'GUI building' stamp: 'MM 12/27/2021 20:32:43'!
windowColor

	^ Color fromHexString: '#d0e973'! !

!PackageDownloaderWindow methodsFor: 'actions' stamp: 'MM 11/26/2021 14:02:26'!
downloadAndInstallPackage
	self selectedPackage ifNotNil: [:package | 
		model downloadAndInstall: package]! !

!PackageDownloaderWindow methodsFor: 'actions' stamp: 'MM 11/25/2021 21:23:05'!
open
	self buildMorphicWindow.
	labelString _ 'Package Installer'.
	self openInWorld! !

!PackageDownloaderWindow methodsFor: 'actions' stamp: 'MM 11/25/2021 21:23:05'!
updatePackageList

	model updatePackageList.
	self changed: #packageListNames! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
currentIndex
	^ currentIndex ifNil: [0]! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
currentIndex: index
	currentIndex _ index.
	self changed: #acceptedContents! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
filterInput
	"Answer the value of filterInput"

	^ filterInput! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
filterInput: anObject
	"Set the value of filterInput"

	filterInput _ anObject! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
filterString
	"Answer the value of filterString"

	^ filterString! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
filterString: aString
	"Set the value of filterString"

	filterString _ aString.
	filterInput hasUnacceptedEdits: false.
	self currentIndex: nil.
	self changed: #packageListNames! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
filteredPackageList

	| packageList |
	
	packageList _ model packageList.
	
	^ filterString isEmpty
		ifTrue: [packageList]
		ifFalse: [packageList select: [:package | package packageName includesSubstring: filterString caseSensitive: false]]! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
getFilter
	^ [:str :el | el printString includesSubstring: str caseSensitive: false]! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
model
	"Answer the value of model"

	^ model! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
model: anObject
	"Set the value of model"

	model _ anObject! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 22:29:27'!
packageDescription

	|package|
	
	package _ self selectedPackage.
	
	package ifNil: [^''].
	
	^ String streamContents: [:s | 
		s nextPutAll: package packageName;
			newLine.
		60 timesRepeat: [	s nextPut: $-].
		s newLine; newLine.
		
		package packageDescription ifNotEmpty: [:description |
			s nextPutAll: description;
				newLine;
				newLine].
		
		s nextPutAll: 'Download url: '; nextPutAll: package downloadUrl]! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
packageListNames

	^ self filteredPackageList collect: [:package | package packageName].
	
	! !

!PackageDownloaderWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:23:05'!
selectedPackage
	currentIndex ifNil: [^nil].
	currentIndex isZero ifTrue: [^nil].
	^ self filteredPackageList at: currentIndex.! !

!PackageDownloaderWindow class methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 22:30:18'!
open

	^ self open: PackageDownloader new label: 'Package Downloader'! !

!PackageDownloaderWindow class methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 21:23:57'!
worldMenuForOpenGroup
	^ `{{
			#itemGroup 		-> 		20.
			#itemOrder 		-> 		10.
			#label 			->	'Package Downloader'.
			#object 			-> 	PackageDownloaderWindow.
			#selector 		-> 		#open.
			#icon 			-> 		#packageIcon.
			#balloonText 	-> 		'A tool for downloading Cuis packages.'.
		} asDictionary}`! !

!PackageDownloader methodsFor: 'accessing' stamp: 'MM 12/27/2021 19:56:59'!
downloadDirectory

	^ downloadDirectory ifNil: [self class defaultDownloadDirectory ]! !

!PackageDownloader methodsFor: 'accessing' stamp: 'MM 11/25/2021 22:23:50'!
jsonPackagesFile

	^ (CodePackage named: 'PackageDownloader' createIfAbsent: false registerIfNew: false)
		packageDirectory // 'packages.json'! !

!PackageDownloader methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:16:11'!
packageList
	"Answer the value of packageList"

	^ packageList! !

!PackageDownloader methodsFor: 'initialization' stamp: 'MM 11/25/2021 23:38:10'!
initialize
	
	self loadPackageList ! !

!PackageDownloader methodsFor: 'packages-collecting' stamp: 'MM 11/25/2021 22:09:55'!
collectPackagesFromDirectory: aDirectory

	"Create a collection of PackageSpec with package files found in aDirectory."
	
	| packageFiles |
	
	packageFiles _ aDirectory fileNamesMatching: '*.pck.st'.
		
	packageFiles do: [:packageFile | | codePackage |
		codePackage _ CodePackageFile onFileEntry: (aDirectory // packageFile).
		self addPackage: codePackage]! !

!PackageDownloader methodsFor: 'packages-collecting' stamp: 'MM 11/25/2021 21:16:11'!
collectPackagesFromDisk

	"Collect PackageSpec with package files found in Cuis packages directories."
	
	self placesToLookForPackagesDo: [:aDirectory | 
		self collectPackagesFromDirectory: aDirectory]! !

!PackageDownloader methodsFor: 'packages-collecting' stamp: 'MM 11/26/2021 11:21:39'!
collectPackagesFromJsonFile: aJsonFile

	aJsonFile readStreamDo: [:fs | |ps|
		ps _ Json readFrom: fs.
		
		ps do: [:p | |package|
			package _ RemotePackageDescription new.
			package packageName: (p at: 'name');
					description: (p at: 'description');
					downloadUrl: (p at: 'downloadUrl');
					homepage: (p at: 'homepage');
					requires: (p at: 'requires');
					provides: (p at: 'provides').
			self addPackage: package]]
					! !

!PackageDownloader methodsFor: 'packages-collecting' stamp: 'MM 12/27/2021 19:53:48'!
collectRemotePackagesFromFile: aCSVFile

	aCSVFile readStreamDo: [ :f | | line splitLine packageName downloadUrl packageFile |
		
		[f atEnd] whileFalse: [ | package codePackage |
			line _ f nextLine.
			splitLine _ line subStrings: (Array with: $,).
			packageName _ splitLine first.
			downloadUrl _ splitLine second.
			packageFile _ PackageDownloader defaultDownloadDirectory // (packageName, '.pck.st').
			
			self downloadUrl: downloadUrl into: packageFile.
			
			codePackage _ CodePackageFile onFileEntry: packageFile.
			
			package _ RemotePackageDescription new.
			package downloadUrl: downloadUrl.
			self populatePackage: package from: codePackage.
			
			self addPackage: package]]! !

!PackageDownloader methodsFor: 'packages-collecting' stamp: 'MM 11/25/2021 21:16:11'!
placesToLookForPackagesDo: aBlock

	| base packagesDirectory |

	"Look in Cuis image folder and reasonable subfolders"
	base _ DirectoryEntry smalltalkImageDirectory.
	aBlock value: base.
	packagesDirectory _ base / 'Packages'.
	aBlock value: packagesDirectory.
	packagesDirectory allRegularDirectoriesDo: aBlock.
	base regularDirectoriesDo: [ :child |
		child = packagesDirectory ifFalse: [
			aBlock value: child.
			child allRegularDirectoriesDo: aBlock]].
	
	"Look in parent directory and reasonable subfolders. 
	Useful when image is stored in a subdirectory of the main app directory.
	This could be the case when the package comes from a 'main' git repo, and image is copied from gitHub.
	First try directories including the word Cuis in the name. Then try others."
	base parent regularDirectoriesDo: [ :dir |
		dir ~= base ifTrue: [
			('*Cuis*' match: dir name)
				ifTrue: [aBlock value: dir. dir allRegularDirectoriesDo: aBlock]]].
	base parent regularDirectoriesDo: [ :dir |
		dir ~= base ifTrue: [
			('*Cuis*' match: dir name)
				ifFalse: [aBlock value: dir. dir allRegularDirectoriesDo: aBlock]]].

	"Also look in host OS current directory"
	(base ~= DirectoryEntry currentDirectory and: [base parent ~= DirectoryEntry currentDirectory])
		ifTrue: [
			base _ DirectoryEntry currentDirectory.
			base allRegularDirectoriesDo: aBlock ]! !

!PackageDownloader methodsFor: 'packages-update' stamp: 'MM 11/26/2021 11:57:37'!
isPackageLocallyAvailable: packageName

	^ (PackageInstaller new packageList 
		detect: [:package | package packageName = packageName]
		ifNone: [nil]) isNil not! !

!PackageDownloader methodsFor: 'packages-update' stamp: 'MM 11/25/2021 23:39:26'!
loadPackageList

	packageList _ OrderedCollection new.
	
	self jsonPackagesFile exists ifFalse: [
		self updatePackageList ].	
	
	self collectPackagesFromJsonFile: self jsonPackagesFile.
	
	packageList sort: [:p1 :p2 | p1 packageName < p2 packageName].
	
	self changed: #packageList.! !

!PackageDownloader methodsFor: 'packages-update' stamp: 'MM 11/26/2021 19:24:56'!
packagesFileUrl

	"^ 'https://gist.githubusercontent.com/mmontone/f43e8c36fa8d3954163289b40670b1d9/raw/cuis-packages.json?a={1}'
		format: 1000 atRandom printString"
		
	^ 'https://bitbucket.org/mmontone/cuis-smalltalk-packageinstaller/downloads/packages.json'! !

!PackageDownloader methodsFor: 'packages-update' stamp: 'MM 11/25/2021 23:36:23'!
updatePackageList

	(self confirm: 'Download list of packages?')
		ifTrue: [self downloadPackagesFile]
		ifFalse: [^ self].
		
	self loadPackageList .	
	! !

!PackageDownloader methodsFor: 'packages' stamp: 'MM 11/25/2021 21:16:11'!
addPackage: aPackageSpec

	packageList add: aPackageSpec! !

!PackageDownloader methodsFor: 'packages' stamp: 'MM 11/26/2021 14:05:54'!
calculatePackageDependenciesOf: aPackageDescription

	| deps packages |
	
	deps _ Set new.
	packages _ OrderedCollection new
				addFirst: aPackageDescription;
				yourself.
				
	[packages isEmpty] whileFalse: [ |package|
		package _ packages removeFirst.
		package requires do: [:req | |pd|
			(req name = 'Cuis-Base') ifFalse: [
				deps add: req name.
				pd _ (self findPackageDescription: req name) ifNil: [
						PackageInstaller new packageList 
							detect: [:p | p packageName = req name]
							ifNone: [self error: 'Cannot satisfy requirement: ', req name]].
				packages addFirst: pd]]].
		
	^ deps! !

!PackageDownloader methodsFor: 'packages' stamp: 'MM 11/26/2021 11:23:15'!
findPackageDescription: packageName

	^ packageList 
		detect: [:packageDescription | packageDescription packageName = packageName]
		ifNone: [nil]! !

!PackageDownloader methodsFor: 'packages' stamp: 'MM 11/26/2021 11:57:37'!
packagesThatNeedDownload: packageNames
	"Return the list of packages that need to be downloaded (are not available locally)."
	
	^ packageNames select: [:packageName |
		(self isPackageLocallyAvailable: packageName) not]! !

!PackageDownloader methodsFor: 'packages' stamp: 'MM 11/25/2021 22:22:07'!
writePackagesListToJsonFile: aFileEntry

	aFileEntry writeStreamDo: [:file |
		self packageList jsonWriteOn: file].! !

!PackageDownloader methodsFor: 'packages-download' stamp: 'MM 11/26/2021 13:35:39'!
downloadAndInstall: aPackageDescription

	| dependencies needDownload filePath |
	
	(self isPackageLocallyAvailable: aPackageDescription packageName)
		ifTrue: [
			(self confirm: ('There''s a version of {1} available in your system. Download anyway?'
						format: {aPackageDescription packageName}))
				ifFalse: [^ nil]].
			
	(self confirm: ('Download and install {1}?' format: {aPackageDescription packageName}))
		ifFalse: [^ nil].
		
	dependencies _ self calculatePackageDependenciesOf: aPackageDescription.
	needDownload _ self packagesThatNeedDownload: dependencies.
	
	needDownload ifNotEmpty: [
		(self confirm: ('The following dependencies need to be downloaded: {1}. Download?'
					format: {', ' join: needDownload}))
			ifFalse: [^ nil].
			
		needDownload do: [:packageName | | depDesc |
			depDesc _ self findPackageDescription: packageName.
			depDesc ifNil: [self inform: 'Don''t know how to download ', packageName. ^ nil].
			self downloadPackage: depDesc packageName from: depDesc downloadUrl]].
	
	filePath _ self downloadPackage: aPackageDescription packageName from: aPackageDescription downloadUrl.
	
	(FeatureRequirement name: aPackageDescription packageName)
		pathName: filePath asString;
		satisfyRequirementsAndInstall
	
	
	
	! !

!PackageDownloader methodsFor: 'packages-download' stamp: 'MM 12/27/2021 19:56:39'!
downloadPackage: packageName from: aUrl

	"Download a Cuis package from aUrl."
	
	| filePath |
	
	filePath _ self downloadDirectory // (packageName, '.pck.st').
	
	self downloadUrl: aUrl into: filePath.
		
	^ filePath! !

!PackageDownloader methodsFor: 'packages-download' stamp: 'MM 11/25/2021 23:19:46'!
downloadPackagesFile

	Transcript show: 'Downloading ', self packagesFileUrl, ' ... '; newLine.
	self jsonPackagesFile fileContents: (WebClient httpGet: self packagesFileUrl) content
	! !

!PackageDownloader methodsFor: 'packages-download' stamp: 'MM 11/26/2021 13:33:29'!
downloadUrl: url into: aFileEntry
	Transcript show: 'Downloading ', url, ' ... '; newLine.
	aFileEntry fileContents: (WebClient httpGet: url) content! !

!PackageDownloader class methodsFor: 'as yet unclassified' stamp: 'MM 12/27/2021 19:53:48'!
defaultDownloadDirectory

	^ ((CodePackage named: 'PackageDownloader' createIfAbsent: false registerIfNew: false)
		packageDirectory / 'download')
			assureExistence ;
			yourself! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 22:25:35'!
description
	^ description! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
description: anObject
	"Set the value of description"

	description _ anObject! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/21/2021 10:49:22'!
downloadUrl
	"Answer the value of downloadUrl"

	^ downloadUrl! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/21/2021 10:49:22'!
downloadUrl: anObject
	"Set the value of downloadUrl"

	downloadUrl _ anObject! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
homepage
	"Answer the value of homepage"

	^ homepage! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
homepage: anObject
	"Set the value of homepage"

	homepage _ anObject! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 22:24:48'!
packageDescription
	^ description! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
packageName
	"Answer the value of packageName"

	^ packageName! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
packageName: anObject
	"Set the value of packageName"

	packageName _ anObject! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
provides
	"Answer the value of provides"

	^ provides! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
provides: anObject
	"Set the value of provides"

	provides _ anObject! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
requires
	"Answer the value of requires"

	^ requires! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
requires: anObject
	"Set the value of requires"

	requires _ anObject! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
tags
	"Answer the value of tags"

	^ tags! !

!RemotePackageDescription methodsFor: 'accessing' stamp: 'MM 11/25/2021 21:03:41'!
tags: anObject
	"Set the value of tags"

	tags _ anObject! !

!RemotePackageDescription methodsFor: 'json' stamp: 'MM 11/26/2021 10:17:11'!
jsonWriteOn: aStream

	{
		'name' -> packageName.
		'downloadUrl' -> downloadUrl.
		'description' -> (String streamContents: [ :s |
			description ifNotEmpty: [s nextPutAll: description; newLine; newLine].
			s nextPutAll: 'Provides: '.
			provides printDetailsOn: s.
			s newLine.
			(self requires sorted: [:a :b | a name < b name]) do: [ :req |
				s nextPutAll: 'Requires: '.
				req printDetailsOn: s]]).
		'homepage' -> homepage.
		'tags' -> tags.
		'requires' -> (requires collect: [:req | 
					{'name' -> req name.
						'minVersion' -> req minVersion.
						'maxVersion' -> req maxVersion.
						'minRevision' -> req minRevision .
						} asDictionary]).
		'provides' -> {'name' -> provides name.
					'version' -> provides version.
					'revision' -> provides revision} asDictionary.
	} asDictionary jsonWriteOn: aStream! !
-------------- next part --------------
'From Cuis 5.0 [latest update: #5004] on 18 December 2021 at 2:03:43 am'!
'Description '!
!provides: 'PackageDownloaderUtils' 1 8!
!requires: 'PackageDownloader' 1 25 nil!
SystemOrganization addCategory: 'PackageDownloaderUtils'!


!classDefinition: #PackageDownloaderUtils category: 'PackageDownloaderUtils'!
Object subclass: #PackageDownloaderUtils
	instanceVariableNames: 'packageList csvFileUrl csvFile jsonFile'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'PackageDownloaderUtils'!
!classDefinition: 'PackageDownloaderUtils class' category: 'PackageDownloaderUtils'!
PackageDownloaderUtils class
	instanceVariableNames: ''!


!PackageDownloaderUtils commentStamp: 'MM 12/17/2021 21:41:00' prior: 0!
I download a file with a list of packages in CSV format, and produce a JSON file with information of the packages, that can be used with PackageDownloader.

The procedure works as follows:

- A CSV file is downloaded from the specified url.
- The packages listed in the CSV files are downloaded to some directory.
- The directory with the packages is scanned to fetch package information.
- A JSON file is produced.

That JSON file should be uploaded to an url address where PackageDownloader downloads the package list.

Example usage:

PackageDownloaderUtils new
	csvFileUrl: 'https://gist.githubusercontent.com/mmontone/f43e8c36fa8d3954163289b40670b1d9/raw/cuis-packages.csv?c=', 1000 atRandom printString;
	csvFile: '/home/marian/src/Cuis/packages.csv';
	jsonFile: '/home/marian/src/Cuis/packages.json';
	run.!

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/19/2021 12:38:30'!
addPackage: aPackageSpec

	packageList add: aPackageSpec! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/21/2021 20:49:56'!
clearPackageList
	packageList _ OrderedCollection new! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/20/2021 20:38:10'!
collectPackagesFromDirectory: aDirectory

	"Create a collection of PackageSpec with package files found in aDirectory."
	
	|packageFiles|
	
	packageFiles _ aDirectory fileNamesMatching: '*.pck.st'.
		
	packageFiles do: [:packageFile | | packageSpec codePackage |
		codePackage _ CodePackageFile onFileEntry: (aDirectory // packageFile).
		packageSpec _ self specFromCodePackage: codePackage.
		self addPackage: packageSpec]
			
	! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 21:20:39'!
collectPackagesFromJsonFile: aJsonFile

	aJsonFile readStreamDo: [:fs | |ps|
		ps _ Json readFrom: fs.
		
		ps do: [:p | |package|
			package _ RemotePackageDescription new.
			package name: (p at: 'name');
					description: (p at: 'description');
					downloadUrl: (p at: 'downloadUrl');
					homepage: (p at: 'homepage').
			self addPackage: package]]
					
			! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 21:25:30'!
collectPackagesFromUrls: urls

	| dir |
	dir _ '/home/marian/src/Cuis/PackageInstaller/packages' asDirectoryEntry.
	urls do: [ :url | | filePath |
		filePath _ dir // (url at: 'fileName').
		filePath fileContents: (WebClient httpGet: (url at: 'url')) content ].! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 12/17/2021 21:30:52'!
collectRemotePackagesFromFile: aCSVFile

	aCSVFile readStreamDo: [ :f | | line splitLine packageName downloadUrl packageFile |
		
		[f atEnd] whileFalse: [ | package codePackage |
			line _ f nextLine.
			splitLine _ line findTokens: (Array with: $,).
			packageName _ splitLine first.
			downloadUrl _ splitLine second.
			packageFile _ PackageDownloaderUtils downloadDirectory // (packageName, '.pck.st').
			
			self downloadPackage: downloadUrl into: packageFile.
			
			codePackage _ CodePackageFile onFileEntry: packageFile.
			
			package _ RemotePackageDescription new.
			package downloadUrl: downloadUrl.
			self populatePackage: package from: codePackage.
			
			self addPackage: package]]! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 12/17/2021 21:46:49'!
defaultCSVFile

	^ ((CodePackage named: 'PackageDownloaderUtils' createIfAbsent: false registerIfNew: false)
		packageDirectory // 'packages.csv') asString! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 12/17/2021 21:46:57'!
defaultJSONFile

	^ ((CodePackage named: 'PackageDownloaderUtils' createIfAbsent: false registerIfNew: false)
		packageDirectory // 'packages.json') asString! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/28/2021 14:42:18'!
downloadPackage: url into: aFileEntry

	| response |
	
	Transcript show: 'Downloading ', url, ' ... '; newLine.
	
	response _ WebClient httpGet: url.
	(response code >=400) ifTrue: [self error: ('Error downloading: {1}. HTTP status: {2}'
										format: {url. response code})].
									
	aFileEntry fileContents: response content! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/20/2021 20:34:26'!
downloadPackagesFromUrls: arg1
	| temp2 |
	temp2 _ '/home/marian/src/Cuis/PackageInstaller/packages' asDirectoryEntry.
	arg1 do: [ :argm1_3 | | temp1_4 |
		Transcript
			show: 'Downloading ' , (argm1_3 at: 'name') , ' ... ';
			newLine.
		temp1_4 _ temp2 // ((argm1_3 at: 'name'), '.pck.st').
		temp1_4 fileContents: (WebClient httpGet: (argm1_3 at: 'url')) content ].! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/20/2021 20:49:31'!
downloadPackagesFromUrls: arg1 into: aDirectory
	
	arg1 do: [ :argm1_3 | | temp1_4 |
		Transcript
			show: 'Downloading ' , (argm1_3 at: 'name') , ' ... ';
			newLine.
		temp1_4 _ aDirectory // ((argm1_3 at: 'name'), '.pck.st').
		temp1_4 fileContents: (WebClient httpGet: (argm1_3 at: 'url')) content ].! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/19/2021 12:03:43'!
initialize
	packageList _ OrderedCollection new! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/19/2021 12:06:44'!
package: packageName properties: aBlock

	|package|
	
	package _ PackageSpec new
				name: packageName;
				yourself.
	aBlock value: package.
	self addPackage: package! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/19/2021 12:04:43'!
packageList
	^ packageList! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/19/2021 12:33:55'!
placesToLookForPackagesDo: aBlock

	| base packagesDirectory |

	"Look in Cuis image folder and reasonable subfolders"
	base _ DirectoryEntry smalltalkImageDirectory.
	aBlock value: base.
	packagesDirectory _ base / 'Packages'.
	aBlock value: packagesDirectory.
	packagesDirectory allRegularDirectoriesDo: aBlock.
	base regularDirectoriesDo: [ :child |
		child = packagesDirectory ifFalse: [
			aBlock value: child.
			child allRegularDirectoriesDo: aBlock]].
	
	"Look in parent directory and reasonable subfolders. 
	Useful when image is stored in a subdirectory of the main app directory.
	This could be the case when the package comes from a 'main' git repo, and image is copied from gitHub.
	First try directories including the word Cuis in the name. Then try others."
	base parent regularDirectoriesDo: [ :dir |
		dir ~= base ifTrue: [
			('*Cuis*' match: dir name)
				ifTrue: [aBlock value: dir. dir allRegularDirectoriesDo: aBlock]]].
	base parent regularDirectoriesDo: [ :dir |
		dir ~= base ifTrue: [
			('*Cuis*' match: dir name)
				ifFalse: [aBlock value: dir. dir allRegularDirectoriesDo: aBlock]]].

	"Also look in host OS current directory"
	(base ~= DirectoryEntry currentDirectory and: [base parent ~= DirectoryEntry currentDirectory])
		ifTrue: [
			base _ DirectoryEntry currentDirectory.
			base allRegularDirectoriesDo: aBlock ]! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/26/2021 09:39:09'!
populatePackage: aPackageSpec from: aCodePackage

	"Populate a PackageSpec from aCodePackage."
	
	aPackageSpec packageName: aCodePackage packageName;
		description: aCodePackage packageDescription;
		requires: aCodePackage requires;
		provides: aCodePackage provides.
	
	^ aPackageSpec! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 12/17/2021 21:54:54'!
run

	"Download list of packages"
 
	Transcript show: 'Downloading list of packages from: '; show: csvFileUrl; newLine.
	self csvFile asFileEntry fileContents: (WebClient httpGet: csvFileUrl) content.
	
	"Process the list of packages to generate json definitions"
	Transcript show: 'Download and scan packages...'; newLine.
	self	collectRemotePackagesFromFile: self csvFile asFileEntry.
	
	Transcript show: 'Writing list of packages to JSON file: '; show: self jsonFile; newLine.
	self writePackagesListToJsonFile: self jsonFile asFileEntry.! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/19/2021 14:33:49'!
specFromCodePackage: aCodePackage

	"Create a PackageSpec from aCodePackage."
	
	| packageSpec |
	
	packageSpec _ FilePackageSpec new.
	
	packageSpec name: aCodePackage packageName;
		description: (String streamContents: [:s | s nextPutAll: aCodePackage packageDescription;
											newLine;
											newLine;
											nextPutAll: aCodePackage description]);
		requires: aCodePackage requires;
		provides: aCodePackage provides;
		codePackageFile: aCodePackage.
	
	^ packageSpec! !

!PackageDownloaderUtils methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 22:20:55'!
writePackagesListToJsonFile: aFileEntry

	aFileEntry writeStreamDo: [:file |
		self packageList jsonWriteOn: file].! !

!PackageDownloaderUtils methodsFor: 'accessing' stamp: 'MM 12/17/2021 21:45:29'!
csvFile
	"Answer the value of csvFile"

	^ csvFile ifNil: [self defaultCSVFile]! !

!PackageDownloaderUtils methodsFor: 'accessing' stamp: 'MM 12/17/2021 21:38:38'!
csvFile: anObject
	"Set the value of csvFile"

	csvFile _ anObject! !

!PackageDownloaderUtils methodsFor: 'accessing' stamp: 'MM 12/17/2021 21:38:38'!
csvFileUrl
	"Answer the value of csvFileUrl"

	^ csvFileUrl! !

!PackageDownloaderUtils methodsFor: 'accessing' stamp: 'MM 12/17/2021 21:38:38'!
csvFileUrl: anObject
	"Set the value of csvFileUrl"

	csvFileUrl _ anObject! !

!PackageDownloaderUtils methodsFor: 'accessing' stamp: 'MM 12/17/2021 21:45:44'!
jsonFile
	"Answer the value of jsonFile"

	^ jsonFile ifNil: [self defaultJSONFile]! !

!PackageDownloaderUtils methodsFor: 'accessing' stamp: 'MM 12/17/2021 21:38:38'!
jsonFile: anObject
	"Set the value of jsonFile"

	jsonFile _ anObject! !

!PackageDownloaderUtils methodsFor: 'accessing' stamp: 'MM 12/17/2021 21:38:38'!
packageList: anObject
	"Set the value of packageList"

	packageList _ anObject! !

!PackageDownloaderUtils class methodsFor: 'as yet unclassified' stamp: 'MM 12/17/2021 21:43:19'!
downloadDirectory

	^ ((CodePackage named: 'PackageDownloaderUtils' createIfAbsent: false registerIfNew: false)
		packageDirectory / 'packageDownloaderPackages')
			assureExistence ;
			yourself! !

!WebClient methodsFor: '*PackageDownloaderUtils' stamp: 'MM 11/26/2021 16:43:49'!
httpPatch: urlString content: postData type: contentType do: aBlock
	"PUT the data to the given url"

	| request |
	self initializeFromUrl: urlString.
	request := self requestWithUrl: urlString.
	request method: 'PATCH'.
	contentType ifNotNil:[request headerAt: 'Content-Type' put: contentType].
	request headerAt: 'Content-Length' put: postData size.
	userAgent ifNotNil:[request headerAt: 'User-Agent' put: userAgent].
	aBlock value: request.
	^self sendRequest: request content: postData readStream size: postData size! !
-------------- next part --------------
'From Cuis 5.0 [latest update: #5007] on 27 December 2021 at 8:34:17 pm'!
'Description Package Installer for Cuis.'!
!provides: 'PackageInstaller' 1 31!
SystemOrganization addCategory: 'PackageInstaller'!


!classDefinition: #PackageInstallerWindow category: 'PackageInstaller'!
SystemWindow subclass: #PackageInstallerWindow
	instanceVariableNames: 'filterString filterInput currentIndex'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'PackageInstaller'!
!classDefinition: 'PackageInstallerWindow class' category: 'PackageInstaller'!
PackageInstallerWindow class
	instanceVariableNames: ''!

!classDefinition: #PackageInstaller category: 'PackageInstaller'!
Object subclass: #PackageInstaller
	instanceVariableNames: 'packageList'
	classVariableNames: 'PackageList'
	poolDictionaries: ''
	category: 'PackageInstaller'!
!classDefinition: 'PackageInstaller class' category: 'PackageInstaller'!
PackageInstaller class
	instanceVariableNames: ''!


!PackageInstallerWindow commentStamp: '<historical>' prior: 0!
I'm a tool for listing locally available Cuis packages and installing them.!

!PackageInstaller commentStamp: '<historical>' prior: 0!
I'm the model of PackageInstallerWindow.!

!PackageInstallerWindow methodsFor: 'GUI building' stamp: 'MM 11/25/2021 15:21:52'!
buildActionsBar

	| actionsBar | 
	
	actionsBar _ LayoutMorph newRow.
	
	actionsBar addMorph:
		(PluggableButtonMorph 
				model: self 
				action: #installPackage
				label: 'Install package').
	actionsBar addMorph:
		(PluggableButtonMorph
				model: self
				action: #updatePackageList
				label: 'Update package list').
	
	actionsBar addMorph: (LabelMorph contents: 'Search: ').
	
	filterInput _ TextModelMorph textProvider: self textGetter: #filterString textSetter: #filterString:.
	filterInput acceptOnCR: true;
		askBeforeDiscardingEdits: false.
	actionsBar addMorph: filterInput layoutSpec: (LayoutSpec fixedHeight: 30).
	
	^ actionsBar! !

!PackageInstallerWindow methodsFor: 'GUI building' stamp: 'MM 11/25/2021 13:56:23'!
buildDetailPane
	^ TextModelMorph textProvider:  self textGetter: #packageDescription! !

!PackageInstallerWindow methodsFor: 'GUI building' stamp: 'MM 11/25/2021 15:23:37'!
buildMorphicWindow

	|layout|
		
	layout _ LayoutMorph newRow.
	layout addMorph: self buildPackageListMorph layoutSpec: (LayoutSpec proportionalWidth: 0.5).
	layout addAdjusterAndMorph: self buildDetailPane layoutSpec: (LayoutSpec proportionalWidth: 0.5).
	self addMorph: layout layoutSpec: (LayoutSpec proportionalWidth: 1).
	self addMorph: self buildActionsBar layoutSpec: (LayoutSpec new fixedHeight: 30; proportionalWidth: 1; yourself). 
	! !

!PackageInstallerWindow methodsFor: 'GUI building' stamp: 'MM 11/25/2021 15:29:21'!
buildPackageListMorph
	
	^ PluggableListMorph model: self listGetter: #packageListNames indexGetter: #currentIndex indexSetter: #currentIndex:.! !

!PackageInstallerWindow methodsFor: 'GUI building' stamp: 'MM 12/27/2021 20:33:57'!
windowColor
	^ Color fromHexString: '#88e6d8'! !

!PackageInstallerWindow methodsFor: 'initialization' stamp: 'MM 11/25/2021 15:18:18'!
initialize
	super initialize.
	filterString _ ''.! !

!PackageInstallerWindow methodsFor: 'actions' stamp: 'MM 11/25/2021 19:26:26'!
installPackage
	self selectedPackage ifNotNil: [:package | 
		(FeatureRequirement name: package packageName)
		pathName: package fullName;
		satisfyRequirementsAndInstall]! !

!PackageInstallerWindow methodsFor: 'actions' stamp: 'MM 11/25/2021 14:04:10'!
open
	self buildMorphicWindow.
	labelString _ 'Package Installer'.
	self openInWorld! !

!PackageInstallerWindow methodsFor: 'actions' stamp: 'MM 11/25/2021 15:30:07'!
updatePackageList

	model updatePackageList.
	self changed: #packageListNames! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 15:17:00'!
currentIndex
	^ currentIndex ifNil: [0]! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 15:17:08'!
currentIndex: index
	currentIndex _ index.
	self changed: #acceptedContents! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 13:43:45'!
filterInput
	"Answer the value of filterInput"

	^ filterInput! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 13:43:45'!
filterInput: anObject
	"Set the value of filterInput"

	filterInput _ anObject! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 13:43:45'!
filterString
	"Answer the value of filterString"

	^ filterString! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 16:53:16'!
filterString: aString
	"Set the value of filterString"

	filterString _ aString.
	filterInput hasUnacceptedEdits: false.
	self currentIndex: nil.
	self changed: #packageListNames! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 16:18:21'!
filteredPackageList

	| packageList |
	
	packageList _ model packageList.
	
	^ filterString isEmpty
		ifTrue: [packageList]
		ifFalse: [packageList select: [:package | package packageName includesSubstring: filterString caseSensitive: false]]! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 14:18:16'!
getFilter
	^ [:str :el | el printString includesSubstring: str caseSensitive: false]! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 13:43:45'!
model
	"Answer the value of model"

	^ model! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 13:43:45'!
model: anObject
	"Set the value of model"

	model _ anObject! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 19:19:54'!
packageDescription

	|package|
	
	package _ self selectedPackage.
	
	package ifNil: [^''].
	
	^ String streamContents: [:s | 
		s nextPutAll: package packageName;
			newLine.
		60 timesRepeat: [	s nextPut: $-].
		s newLine; newLine.
		
		package packageDescription ifNotEmpty: [:description |
			s nextPutAll: description;
				newLine;
				newLine].
		
		s nextPutAll: package description]! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 16:12:17'!
packageListNames

	^ self filteredPackageList collect: [:package | package packageName].
	
	! !

!PackageInstallerWindow methodsFor: 'accessing' stamp: 'MM 11/25/2021 16:10:59'!
selectedPackage
	currentIndex ifNil: [^nil].
	currentIndex isZero ifTrue: [^nil].
	^ self filteredPackageList at: currentIndex.! !

!PackageInstallerWindow class methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 15:11:25'!
open

	^ self open: PackageInstaller new label: 'Package Installer'! !

!PackageInstallerWindow class methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 17:15:50'!
worldMenuForOpenGroup
	^ `{{
			#itemGroup 		-> 		20.
			#itemOrder 		-> 		10.
			#label 			->	'Package Installer'.
			#object 			-> 	PackageInstallerWindow.
			#selector 		-> 		#open.
			#icon 			-> 		#packageIcon.
			#balloonText 	-> 		'A tool for installing local Cuis packages.'.
		} asDictionary}`! !

!PackageInstaller methodsFor: 'accessing' stamp: 'MM 11/25/2021 15:12:28'!
addPackage: aPackageSpec

	packageList add: aPackageSpec! !

!PackageInstaller methodsFor: 'accessing' stamp: 'MM 11/25/2021 14:24:04'!
packageList
	"Answer the value of packageList"

	^ packageList! !

!PackageInstaller methodsFor: 'actions' stamp: 'MM 11/25/2021 19:16:55'!
collectPackagesFromDirectory: aDirectory

	"Create a collection of PackageSpec with package files found in aDirectory."
	
	|packageFiles|
	
	packageFiles _ aDirectory fileNamesMatching: '*.pck.st'.
		
	packageFiles do: [:packageFile | | codePackage |
		codePackage _ CodePackageFile onFileEntry: (aDirectory // packageFile).
		self addPackage: codePackage]! !

!PackageInstaller methodsFor: 'actions' stamp: 'MM 11/25/2021 14:39:54'!
collectPackagesFromDisk

	"Collect PackageSpec with package files found in Cuis packages directories."
	
	self placesToLookForPackagesDo: [:aDirectory | 
		self collectPackagesFromDirectory: aDirectory]! !

!PackageInstaller methodsFor: 'actions' stamp: 'MM 11/25/2021 14:40:18'!
placesToLookForPackagesDo: aBlock

	| base packagesDirectory |

	"Look in Cuis image folder and reasonable subfolders"
	base _ DirectoryEntry smalltalkImageDirectory.
	aBlock value: base.
	packagesDirectory _ base / 'Packages'.
	aBlock value: packagesDirectory.
	packagesDirectory allRegularDirectoriesDo: aBlock.
	base regularDirectoriesDo: [ :child |
		child = packagesDirectory ifFalse: [
			aBlock value: child.
			child allRegularDirectoriesDo: aBlock]].
	
	"Look in parent directory and reasonable subfolders. 
	Useful when image is stored in a subdirectory of the main app directory.
	This could be the case when the package comes from a 'main' git repo, and image is copied from gitHub.
	First try directories including the word Cuis in the name. Then try others."
	base parent regularDirectoriesDo: [ :dir |
		dir ~= base ifTrue: [
			('*Cuis*' match: dir name)
				ifTrue: [aBlock value: dir. dir allRegularDirectoriesDo: aBlock]]].
	base parent regularDirectoriesDo: [ :dir |
		dir ~= base ifTrue: [
			('*Cuis*' match: dir name)
				ifFalse: [aBlock value: dir. dir allRegularDirectoriesDo: aBlock]]].

	"Also look in host OS current directory"
	(base ~= DirectoryEntry currentDirectory and: [base parent ~= DirectoryEntry currentDirectory])
		ifTrue: [
			base _ DirectoryEntry currentDirectory.
			base allRegularDirectoriesDo: aBlock ]! !

!PackageInstaller methodsFor: 'actions' stamp: 'MM 11/26/2021 20:04:16'!
updatePackageList
	
	(PopUpMenu confirm: 'I need to scan for packages. This takes some time. Continue?')
		ifFalse: [^ nil].
	packageList _ OrderedCollection new.
	self collectPackagesFromDisk.
	packageList sort: [:p1 :p2 | p1 packageName < p2 packageName].
	PackageList _ packageList.
	self changed: #packageList.
	^ packageList! !

!PackageInstaller methodsFor: 'initialization' stamp: 'MM 11/25/2021 16:15:28'!
initialize
	packageList _ PackageList ifNil: [self updatePackageList]! !

!CodePackageFile methodsFor: '*PackageInstaller' stamp: 'MM 11/19/2021 14:30:09'!
packageDescription
	^ description! !


More information about the Cuis-dev mailing list