[Cuis-dev] Package Downloader - First demo

Mariano Montone marianomontone at gmail.com
Sat Nov 27 06:07:49 PST 2021


Hello.

I'm attaching a first demo of a package downloader tool I'm developing.

It depends on PackageInstaller atm (btw, I attach an update on the
package installer that warns the user that package scanning can take
time before continuing, suggested by Ken).

This is how the PackageDownloader works atm:

- The list of remote packages is maintained in a CSV file. That list of
files contains package only name of the package and raw package url. It
is here at the moment:
https://gist.github.com/mmontone/f43e8c36fa8d3954163289b40670b1d9. This
is the only list of packages that need to be maintained.

- I have a script that processes that list and produces a JSON spec of
the packages, that the download tool can work with.
It is here for now:
https://bitbucket.org/mmontone/cuis-smalltalk-packageinstaller/downloads/packages.json

- The PackageDownloader tool downloads that json file and works with it.

- For downloading and installing a package, package dependencies are
downloaded too, but taking into account the locally installed packages.

- There's no effort for supporting packages versions. The
PackageDownloader looks at the names of the packages and downloads if
necessary, but Cuis inner machinery is used for dealing with package
loads and features.

It would be great if someone can take a look and give me some feedback.
Main issue right now is that the list of local packages may be
out-of-sync, because determining the list of local packages needs a
costly disk scan.

One last thing, may I suggest you try with one of my packages? They live
at bitbucket at the moment, and the package downloader makes it easy to
install.

Open PackageDownloader and download and install the 'Props-Preferences'
package.

Then you can do two things:

1) Open Preferences -> All preferences , and see a tool for editing
preferences.

2) Open halos on any Morph, and you'll have a new green halo for editing
the Morph's properties with a tool.

Thank you!,

Mariano

El 25/11/21 a las 19:30, Mariano Montone escribió:
> I'm attaching an update.
> 
> Review this version please instead. It is more compact. It consists of
> only two classes.
> 
> Mariano
> 
> El 25/11/21 a las 17:18, Mariano Montone escribió:
>> Hello Juan,
>>
>> I'm submitting (see attached) an initial version of the Package
>> Installer for review.
>>
>> The code needs to be better commented, methods classified, etc. But I
>> would like to know if there are any major objections first; my plan is
>> to clean things up once it is on a git repository.
>>
>> Can you have a look and give me some feedback?
>>
>> To run select: World Menu -> Open -> Package Installer.
>>
>> Thanks!
>>
>> Mariano
>>
> 

-------------- next part --------------
'From Cuis 5.0 [latest update: #4975] on 26 November 2021 at 8:04:54 pm'!
'Description Package Installer for Cuis.'!
!provides: 'PackageInstaller' 1 29!
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 methodsFor: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 13:56:23'!
buildDetailPane
	^ TextModelMorph textProvider:  self textGetter: #packageDescription! !

!PackageInstallerWindow methodsFor: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 15:29:21'!
buildPackageListMorph
	
	^ PluggableListMorph model: self listGetter: #packageListNames indexGetter: #currentIndex indexSetter: #currentIndex:.! !

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

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

!PackageInstallerWindow methodsFor: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 14:18:16'!
getFilter
	^ [:str :el | el printString includesSubstring: str caseSensitive: false]! !

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

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

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

!PackageInstallerWindow methodsFor: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 16:12:17'!
packageListNames

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

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

!PackageInstallerWindow methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 15:30:07'!
updatePackageList

	model updatePackageList.
	self changed: #packageListNames! !

!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 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 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 14:24:04'!
packageList
	"Answer the value of packageList"

	^ packageList! !

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

	packageList add: aPackageSpec! !

!PackageInstaller methodsFor: 'as yet unclassified' 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: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 16:15:28'!
initialize
	packageList _ PackageList ifNil: [self updatePackageList]! !

!PackageInstaller methodsFor: 'as yet unclassified' 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: 'as yet unclassified' 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! !

!CodePackageFile methodsFor: '*PackageInstaller' stamp: 'MM 11/19/2021 14:30:09'!
packageDescription
	^ description! !
-------------- next part --------------
'From Cuis 5.0 [latest update: #4973] on 26 November 2021 at 7:59:21 pm'!
'Description '!
!provides: 'PackageDownloader' 1 24!
!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'
	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 methodsFor: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 21:23:05'!
buildDetailPane
	^ TextModelMorph textProvider:  self textGetter: #packageDescription! !

!PackageDownloaderWindow methodsFor: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 21:23:05'!
buildPackageListMorph
	
	^ PluggableListMorph model: self listGetter: #packageListNames indexGetter: #currentIndex indexSetter: #currentIndex:.! !

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

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

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

!PackageDownloaderWindow methodsFor: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 21:23:05'!
getFilter
	^ [:str :el | el printString includesSubstring: str caseSensitive: false]! !

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

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

!PackageDownloaderWindow methodsFor: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 21:23:05'!
packageListNames

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

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

!PackageDownloaderWindow methodsFor: 'as yet unclassified' 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'!
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'!
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 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 11/25/2021 21:16:11'!
packageList
	"Answer the value of packageList"

	^ packageList! !

!PackageDownloader methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 21:16:11'!
addPackage: aPackageSpec

	packageList add: aPackageSpec! !

!PackageDownloader methodsFor: 'as yet unclassified' 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: 'as yet unclassified' 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: 'as yet unclassified' 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: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/26/2021 12:04:20'!
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 downloadDirectory // (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: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/26/2021 13:34:58'!
downloadPackage: packageName from: aUrl

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

!PackageDownloader methodsFor: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/26/2021 13:33:29'!
downloadUrl: url into: aFileEntry
	Transcript show: 'Downloading ', url, ' ... '; newLine.
	aFileEntry fileContents: (WebClient httpGet: url) content! !

!PackageDownloader methodsFor: 'as yet unclassified' stamp: 'MM 11/26/2021 11:23:15'!
findPackageDescription: packageName

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

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

!PackageDownloader methodsFor: 'as yet unclassified' stamp: 'MM 11/26/2021 11:57:37'!
isPackageLocallyAvailable: packageName

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

!PackageDownloader methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 22:23:50'!
jsonPackagesFile

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

!PackageDownloader methodsFor: 'as yet unclassified' 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: 'as yet unclassified' 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: 'as yet unclassified' 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: 'as yet unclassified' 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: 'as yet unclassified' stamp: 'MM 11/25/2021 23:36:23'!
updatePackageList

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

!PackageDownloader methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 22:22:07'!
writePackagesListToJsonFile: aFileEntry

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

!PackageDownloader class methodsFor: 'as yet unclassified' stamp: 'MM 11/25/2021 21:31:34'!
downloadDirectory

	^ ((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: 'as yet unclassified' stamp: 'MM 11/25/2021 21:44:00'!
download
	Transcript show: 'Downloading ', packageName; newLine.
	(PackageListBuilder packagesDirectory // (packageName, '.pck.st')) 
		fileContents: (WebClient httpGet: downloadUrl) content! !

!RemotePackageDescription methodsFor: 'as yet unclassified' 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! !


More information about the Cuis-dev mailing list