SystemOrganization addCategory: #'Gofer-Core'! SystemOrganization addCategory: #'Gofer-Test'! !MCRepositoryGroup methodsFor: '*gofer-testing' stamp: 'lr 9/24/2009 17:01'! isRepositoryGroup ^ true! ! Object subclass: #Gofer instanceVariableNames: 'packages options' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !Gofer commentStamp: 'lr 9/21/2009 13:44' prior: 0! : Gofer, a person who runs errands. Origin 1960s: from go for, i.e. go and fetch. : ''The New Oxford American Dictionary'' Gofer is a small tool on top of Monticello that loads, updates, merges, diffs, reverts, commits, recompiles and unloads groups of Monticello packages. Contrary to existing tools Gofer makes sure that these operations are performed as clean as possible: - Gofer treats packages from one or more repository in one operation. - Gofer works with fixed versions or tries to find the "latest" version using a given name prefix. - Gofer automatically assigns repositories to all packages, so that the other tools are ready to be used on individual packages. - Gofer makes sure that there is only one repository instance registered for a single physical location. - Gofer works with Monticello dependencies and uniformly treats them like the primary package. - Gofer cleans up after Monticello, no empty class categories and no empty method protocols are to be expected. To get started with Gofer in Pharo use the following script: == ScriptLoader new installGofer To use Gofer to load the "latest" Seaside 2.8 together with its prerequisites and the Scriptaculous package one would write and evaluate the following code: == Gofer new == squeaksource: 'KomHttpServer'; == addAll: #( 'DynamicBindings' 'KomServices' 'KomHttpServer' ); == squeaksource: 'Seaside'; == addAll: #( 'Seaside2.8a' 'Scriptaculous' ); == load However, that's only the beginning. Developers might want to keep the Gofer specification around to perform other actions on the specified set of packages: == gofer := Gofer new. == gofer == squeaksource: 'KomHttpServer'; == addAll: #( 'DynamicBindings' 'KomServices' 'KomHttpServer' ); == squeaksource: 'Seaside'; == addAll: #( 'Seaside2.8a' 'Scriptaculous' ). Now the following expressions can be used at any time: | ==gofer load== | Load all packages. | ==gofer update== | Update all packages. | ==gofer merge== | Merge all packages into their working copies. | ==gofer diff== | Display the difference between the working copy and the base version of all packages. | ==gofer commit== | Commit all modified packages. | ==gofer revert== | Revert all packages to their base version. | ==gofer recompile== | Recompile all packages. | ==gofer unload== | Unload all packages. Some of the operations have additional parameters, for example you can specify a commit message using ==gofer message: 'fixes issue 123'==.! !Gofer class methodsFor: 'examples' stamp: 'lr 8/20/2009 20:22'! gofer "Create a Gofer instance of Gofer." ^ self new renggli: 'flair'; add: 'Gofer'; yourself! ! !Gofer class methodsFor: 'examples' stamp: 'lr 8/20/2009 20:15'! komanche "Create a Gofer instance of Komanche." ^ self new squeaksource: 'KomHttpServer'; add: 'DynamicBindings'; add: 'KomServices'; add: 'KomHttpServer'; yourself! ! !Gofer class methodsFor: 'examples' stamp: 'lr 8/20/2009 20:15'! magritte "Create a Gofer instance of Magritte." ^ self new renggli: 'magritte'; add: 'Magritte-Model'; add: 'Magritte-Tests'; add: 'Magritte-Seaside'; add: 'Magritte-Morph'; yourself! ! !Gofer class methodsFor: 'instance creation' stamp: 'lr 8/20/2009 09:54'! new ^ self basicNew initialize! ! !Gofer class methodsFor: 'examples' stamp: 'lr 8/20/2009 20:15'! omnibrowser "Create a Gofer instance of OmniBrowser." ^ self new renggli: 'omnibrowser'; add: 'OmniBrowser-lr'; add: 'OB-Standard-lr'; add: 'OB-Morphic-lr'; add: 'OB-Refactory-lr'; add: 'OB-Regex-lr'; add: 'OB-SUnitIntegration-lr'; yourself! ! !Gofer class methodsFor: 'examples' stamp: 'lr 8/20/2009 20:15'! pier "Create a Gofer instance of Pier." ^ self new renggli: 'pier'; add: 'Pier-Model'; add: 'Pier-Tests'; add: 'Pier-Seaside'; add: 'Pier-Blog'; add: 'Pier-Security'; add: 'Pier-Squeak-Persistency'; yourself! ! !Gofer class methodsFor: 'examples' stamp: 'lr 8/20/2009 20:17'! pierAddons "Create a Gofer instance of Pier Addons." ^ self new renggli: 'pieraddons'; add: 'Pier-Design'; add: 'Pier-Documents'; add: 'Pier-EditorEnh'; add: 'Pier-Google'; add: 'Pier-Links'; add: 'Pier-Randomizer'; add: 'Pier-TagCloud'; add: 'Pier-Slideshow'; add: 'Pier-Setup'; yourself! ! !Gofer class methodsFor: 'examples' stamp: 'lr 8/20/2009 20:15'! refactoring "Create a Gofer instance of the refactoring tools." ^ self new squeaksource: 'AST'; add: 'AST-lr'; squeaksource: 'RefactoringEngine'; add: 'Refactoring-Core-lr'; add: 'Refactoring-Spelling-lr'; yourself! ! !Gofer class methodsFor: 'examples' stamp: 'lr 8/20/2009 20:15'! seaside28 "Create a Gofer instance of Seaside 2.8." ^ self new squeaksource: 'Seaside'; add: 'Seaside2.8a1-lr'; add: 'Scriptaculous-lr'; add: 'Comet-lr'; squeaksource: 'rsrss'; add: 'RSRSS2'; yourself! ! !Gofer class methodsFor: 'examples' stamp: 'lr 8/20/2009 20:17'! tools "Create a Gofer instance of several development tools." ^ self new renggli: 'unsorted'; add: 'Shout'; add: 'RoelTyper'; add: 'ECompletion'; add: 'ECompletionOmniBrowser'; yourself! ! !Gofer methodsFor: 'packages' stamp: 'lr 9/3/2009 11:32'! add: aString "Add the package named aString." self packages addLast: (GoferPackage name: aString repository: (self optionAt: #repository ifAbsent: [ nil ]))! ! !Gofer methodsFor: 'packages' stamp: 'lr 8/20/2009 09:48'! addAll: aCollection "Add aCollecton of package names to the list." aCollection do: [ :each | self add: each ]! ! !Gofer methodsFor: 'actions' stamp: 'lr 8/20/2009 10:14'! commit "Commit the specified packages." ^ self execute: GoferCommit! ! !Gofer methodsFor: 'actions' stamp: 'lr 9/24/2009 16:01'! commit: aString "Commit the specified packages with the given commit message aString." ^ self message: aString; commit! ! !Gofer methodsFor: 'repositories' stamp: 'lr 7/10/2009 16:27'! croquet: aString self url: 'http://hedgehog.software.umn.edu:8888/' , aString! ! !Gofer methodsFor: 'actions' stamp: 'lr 8/20/2009 10:14'! diff "Display the differences between the working copy and the base of the specified packages." ^ self execute: GoferDiff! ! !Gofer methodsFor: 'packages' stamp: 'lr 8/20/2009 20:09'! do: aBlock "Enumerate over the packages." self packages do: aBlock! ! !Gofer methodsFor: 'private' stamp: 'lr 8/20/2009 12:01'! execute: anOperationClass ^ (anOperationClass on: self copy) execute! ! !Gofer methodsFor: 'repositories' stamp: 'lr 7/10/2009 16:27'! impara: aString self url: 'http://source.impara.de/' , aString! ! !Gofer methodsFor: 'initialization' stamp: 'lr 8/20/2009 12:12'! initialize packages := OrderedCollection new. options := Dictionary new! ! !Gofer methodsFor: 'actions' stamp: 'lr 8/20/2009 10:14'! load "Load the specified packages." ^ self execute: GoferLoad! ! !Gofer methodsFor: 'actions' stamp: 'lr 8/20/2009 10:14'! merge "Merge the specified packages." ^ self execute: GoferMerge! ! !Gofer methodsFor: 'options' stamp: 'lr 8/20/2009 12:18'! message: aString "The commit message, if not set a dialog will ask for a message." self optionAt: #message put: aString! ! !Gofer methodsFor: 'accessing-options' stamp: 'lr 8/20/2009 20:49'! optionAt: aSymbol ^ self optionAt: aSymbol ifAbsent: [ nil ]! ! !Gofer methodsFor: 'accessing-options' stamp: 'lr 8/20/2009 20:49'! optionAt: aSymbol ifAbsent: aBlock ^ options at: aSymbol ifAbsent: aBlock! ! !Gofer methodsFor: 'accessing-options' stamp: 'lr 8/20/2009 12:11'! optionAt: aSymbol put: anObject ^ options at: aSymbol put: anObject! ! !Gofer methodsFor: 'accessing' stamp: 'lr 8/20/2009 09:47'! packages "Answer a list of packages." ^ packages! ! !Gofer methodsFor: 'copying' stamp: 'lr 8/20/2009 12:12'! postCopy super postCopy. packages := packages copy. options := options copy! ! !Gofer methodsFor: 'actions' stamp: 'lr 8/20/2009 11:44'! recompile "Recompile the specified packages." ^ self execute: GoferRecompile! ! !Gofer methodsFor: 'repositories' stamp: 'lr 7/10/2009 16:25'! renggli: aString self url: 'http://source.lukas-renggli.ch/' , aString! ! !Gofer methodsFor: 'accessing' stamp: 'lr 8/20/2009 20:49'! repository "Answer a current repository or nil." ^ self optionAt: #repository! ! !Gofer methodsFor: 'options' stamp: 'lr 9/7/2009 20:15'! repository: aRepository "Set the repository aRepository as the location for the following package additions." | repository | MCRepositoryGroup default addRepository: aRepository. repository := MCRepositoryGroup default repositories detect: [ :each | each = aRepository ] ifNone: [ self error: 'Internal error' ]. repository copyFrom: aRepository. self optionAt: #repository put: repository! ! !Gofer methodsFor: 'actions' stamp: 'lr 8/20/2009 10:15'! revert "Revert the specified packages to the currently loaded version." ^ self execute: GoferRevert! ! !Gofer methodsFor: 'repositories' stamp: 'lr 7/10/2009 16:29'! saltypickle: aString self url: 'http://squeak.saltypickle.com/' , aString! ! !Gofer methodsFor: 'repositories' stamp: 'lr 7/10/2009 16:28'! squeakfoundation: aString self url: 'http://source.squeakfoundation.org/' , aString! ! !Gofer methodsFor: 'repositories' stamp: 'lr 7/10/2009 16:28'! squeaksource: aString self url: 'http://www.squeaksource.com/' , aString! ! !Gofer methodsFor: 'actions' stamp: 'lr 9/3/2009 11:57'! unload "Update the specified packages, this is the same as loading." ^ self execute: GoferUnload! ! !Gofer methodsFor: 'actions' stamp: 'lr 9/18/2009 18:12'! update "Update the specified packages." ^ self execute: GoferUpdate! ! !Gofer methodsFor: 'options-repository' stamp: 'lr 9/7/2009 20:11'! url: aString "Set the repository URL aString as the location for the following package additions." self url: aString username: String new password: String new! ! !Gofer methodsFor: 'options-repository' stamp: 'lr 9/7/2009 20:12'! url: aString username: aUsernameString password: aPasswordString "Set the repository URL aString as the location for the following package additions." self repository: (MCHttpRepository location: aString user: aUsernameString password: aPasswordString)! ! !Gofer methodsFor: 'repositories' stamp: 'lr 7/10/2009 16:26'! wiresong: aString self url: 'http://source.wiresong.ca/' , aString! ! Object subclass: #GoferOperation instanceVariableNames: 'gofer model' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! GoferOperation subclass: #GoferLoad instanceVariableNames: 'versions repositories' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferLoad methodsFor: 'private' stamp: 'lr 9/24/2009 16:42'! addPackage: aPackage | version | version := aPackage findVersion. version withAllDependenciesDo: [ :dependency | versions addLast: dependency. (repositories at: dependency ifAbsentPut: [ Set new ]) add: aPackage repository ]. model addVersion: version! ! !GoferLoad methodsFor: 'private' stamp: 'lr 9/3/2009 11:00'! defaultModel ^ MCVersionLoader new! ! !GoferLoad methodsFor: 'running' stamp: 'lr 9/3/2009 11:00'! execute self model load. self updateRepositories. self updateCategories! ! !GoferLoad methodsFor: 'initialization' stamp: 'lr 9/3/2009 11:00'! initialize super initialize. versions := OrderedCollection new. repositories := Dictionary new! ! !GoferLoad methodsFor: 'initialization' stamp: 'lr 9/3/2009 11:00'! initializeOn: aGofer super initializeOn: aGofer. self gofer do: [ :package | self addPackage: package ]! ! !GoferLoad methodsFor: 'private' stamp: 'lr 9/20/2009 13:43'! updateCategories "This method makes sure that the categories are ordered in load-order and as specified in the packages." | categories | categories := OrderedCollection new. versions do: [ :version | version snapshot definitions do: [ :definition | definition isOrganizationDefinition ifTrue: [ definition categories do: [ :category | (categories includes: category) ifFalse: [ categories addLast: category ] ] ] ] ]. (MCOrganizationDefinition categories: categories) postloadOver: nil! ! !GoferLoad methodsFor: 'private' stamp: 'lr 9/3/2009 10:51'! updateRepositories "This code makes sure that all packages have a propre repository assigned, including the dependencies." repositories keysAndValuesDo: [ :version :collection | collection do: [ :repository | version workingCopy repositoryGroup addRepository: repository ] ]! ! !GoferOperation class methodsFor: 'instance creation' stamp: 'lr 9/3/2009 10:28'! new self shouldNotImplement! ! !GoferOperation class methodsFor: 'instance creation' stamp: 'lr 8/20/2009 12:01'! on: aGofer ^ self basicNew initializeOn: aGofer! ! !GoferOperation methodsFor: 'private' stamp: 'lr 8/19/2009 14:01'! defaultModel ^ nil! ! !GoferOperation methodsFor: 'running' stamp: 'lr 8/17/2009 14:40'! execute "Execute the receiving action." self subclassResponsibility! ! !GoferOperation methodsFor: 'accessing' stamp: 'lr 8/20/2009 10:19'! gofer "Answer the Gofer model of this operation." ^ gofer! ! !GoferOperation methodsFor: 'initialization' stamp: 'lr 8/19/2009 14:01'! initialize model := self defaultModel! ! !GoferOperation methodsFor: 'initialization' stamp: 'lr 8/20/2009 12:00'! initializeOn: aGofer gofer := aGofer. self initialize! ! !GoferOperation methodsFor: 'accessing' stamp: 'lr 8/20/2009 10:13'! model "Answer the Monticello model of this operation." ^ model! ! !GoferOperation methodsFor: 'accessing-options' stamp: 'lr 8/20/2009 12:13'! optionAt: aSymbol ^ self gofer optionAt: aSymbol! ! GoferOperation subclass: #GoferWorking instanceVariableNames: 'workingCopies' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! GoferWorking subclass: #GoferCommit instanceVariableNames: 'repositories message' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferCommit methodsFor: 'private' stamp: 'lr 9/24/2009 16:59'! addPackage: aPackage requiredCopy: aWorkingCopy repository: aRepository super addPackage: aPackage requiredCopy: aWorkingCopy repository: aRepository. repositories at: aWorkingCopy put: aRepository! ! !GoferCommit methodsFor: 'running' stamp: 'lr 9/24/2009 17:32'! execute self workingCopies do: [ :workingCopy | workingCopy needsSaving ifTrue: [ self execute: workingCopy ] ]! ! !GoferCommit methodsFor: 'running' stamp: 'lr 9/24/2009 16:57'! execute: aWorkingCopy | version | version := [ aWorkingCopy newVersion ] on: MCVersionNameAndMessageRequest do: [ :notifcation | self message isNil ifTrue: [ message := notifcation outer last ]. notifcation resume: (Array with: notifcation suggestedName with: self message) ]. (repositories at: aWorkingCopy) storeVersion: version! ! !GoferCommit methodsFor: 'initialization' stamp: 'lr 8/20/2009 12:14'! initialize super initialize. repositories := Dictionary new! ! !GoferCommit methodsFor: 'accessing' stamp: 'lr 8/20/2009 12:13'! message ^ message ifNil: [ message := self optionAt: #message ]! ! GoferWorking subclass: #GoferDiff instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferDiff methodsFor: 'private' stamp: 'lr 9/24/2009 18:00'! addPackage: aPackage requiredCopy: aWorkingCopy repository: aRepository | source target patch | super addPackage: aPackage requiredCopy: aWorkingCopy repository: aRepository. source := aWorkingCopy package. target := aWorkingCopy ancestors isEmpty ifTrue: [ aPackage findVersion ] ifFalse: [ aRepository versionWithInfo: aWorkingCopy ancestors first ]. patch := source snapshot patchRelativeToBase: target snapshot. aWorkingCopy modified: patch isEmpty not. self model operations addAll: patch operations! ! !GoferDiff methodsFor: 'private' stamp: 'lr 8/19/2009 14:02'! defaultModel ^ MCPatch operations: OrderedCollection new! ! !GoferDiff methodsFor: 'running' stamp: 'lr 8/19/2009 14:06'! execute self model isEmpty ifFalse: [ self model browse ]! ! GoferWorking subclass: #GoferRecompile instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferRecompile methodsFor: 'running' stamp: 'lr 8/20/2009 11:44'! execute self workingCopies do: [ :copy | self recompile: copy ]! ! !GoferRecompile methodsFor: 'running' stamp: 'lr 8/20/2009 11:47'! recompile: aWorkingCopy aWorkingCopy packageInfo methods do: [ :each | each actualClass recompile: each methodSymbol ]! ! GoferWorking subclass: #GoferUnload instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferUnload methodsFor: 'private' stamp: 'lr 8/19/2009 14:01'! defaultModel ^ MCMultiPackageLoader new! ! !GoferUnload methodsFor: 'running' stamp: 'lr 9/3/2009 11:15'! execute self workingCopies do: [ :copy | self unloadClasses: copy; unloadPackage: copy ]. self model load. self workingCopies do: [ :copy | self cleanup: copy; unregister: copy ]! ! !GoferUnload methodsFor: 'unloading' stamp: 'lr 8/19/2009 13:50'! unloadClasses: aWorkingCopy aWorkingCopy packageInfo classes do: [ :class | (class selectors includes: #unload) ifTrue: [ class unload ] ]! ! !GoferUnload methodsFor: 'unloading' stamp: 'lr 8/19/2009 14:00'! unloadPackage: aWorkingCopy self model unloadPackage: aWorkingCopy package! ! !GoferUnload methodsFor: 'unregistering' stamp: 'lr 8/19/2009 13:49'! unregister: aWorkingCopy self unregisterWorkingCopy: aWorkingCopy. self unregisterRepositories: aWorkingCopy. self unregisterPackageInfo: aWorkingCopy! ! !GoferUnload methodsFor: 'unregistering' stamp: 'lr 8/19/2009 13:50'! unregisterPackageInfo: aWorkingCopy PackageOrganizer default unregisterPackage: aWorkingCopy packageInfo! ! !GoferUnload methodsFor: 'unregistering' stamp: 'lr 8/19/2009 13:50'! unregisterRepositories: aWorkingCopy aWorkingCopy repositoryGroup repositories allButFirst do: [ :repository | MCWorkingCopy allManagers do: [ :copy | (copy repositoryGroup includes: repository) ifTrue: [ ^ self ] ]. MCRepositoryGroup default removeRepository: repository ]! ! !GoferUnload methodsFor: 'unregistering' stamp: 'lr 8/20/2009 11:54'! unregisterWorkingCopy: aWorkingCopy aWorkingCopy unregister! ! GoferWorking subclass: #GoferUpdate instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! GoferUpdate subclass: #GoferMerge instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferMerge methodsFor: 'private' stamp: 'lr 8/19/2009 14:01'! defaultModel ^ MCVersionMerger new! ! !GoferMerge methodsFor: 'running' stamp: 'lr 9/24/2009 17:39'! execute [ [ self model merge ] on: MCMergeResolutionRequest do: [ :request | request merger conflicts isEmpty ifTrue: [ request resume: true ] ifFalse: [ request pass ] ] ] valueSupplyingAnswers: #(('No Changes' true)). self workingCopies do: [ :each | self cleanup: each ]! ! GoferUpdate subclass: #GoferRevert instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferRevert methodsFor: 'running' stamp: 'lr 9/19/2009 13:15'! execute self workingCopies do: [ :each | each modified: false ]. super execute! ! !GoferRevert methodsFor: 'private' stamp: 'lr 9/24/2009 17:44'! findPackageVersion: aPackage workingCopy: aWorkingCopy repository: aRepository ^ aRepository versionWithInfo: aWorkingCopy ancestors first! ! !GoferUpdate methodsFor: 'private' stamp: 'lr 9/24/2009 17:44'! addPackage: aPackage workingCopy: aWorkingCopy repository: aRepository super addPackage: aPackage workingCopy: aWorkingCopy repository: aRepository. self model addVersion: (self findPackageVersion: aPackage workingCopy: aWorkingCopy repository: aRepository)! ! !GoferUpdate methodsFor: 'private' stamp: 'lr 9/18/2009 18:13'! defaultModel ^ MCVersionLoader new! ! !GoferUpdate methodsFor: 'running' stamp: 'lr 9/19/2009 13:15'! execute self model load. self workingCopies do: [ :each | self cleanup: each ]! ! !GoferUpdate methodsFor: 'private' stamp: 'lr 9/24/2009 17:44'! findPackageVersion: aPackage workingCopy: aWorkingCopy repository: aRepository ^ aPackage findVersion: aPackage name in: aRepository! ! !GoferWorking methodsFor: 'private' stamp: 'lr 9/24/2009 16:51'! addPackage: aPackage | workingCopy repository | workingCopy := aPackage findWorkingCopy. repository := aPackage repository ifNil: [ workingCopy repositoryGroup ]. self addPackage: aPackage workingCopy: workingCopy repository: repository! ! !GoferWorking methodsFor: 'private' stamp: 'lr 9/24/2009 16:56'! addPackage: aPackage requiredCopy: aWorkingCopy repository: aRepository (workingCopies includes: aWorkingCopy) ifFalse: [ workingCopies addLast: aWorkingCopy. aWorkingCopy requiredPackages reverseDo: [ :each | self addPackage: aPackage requiredCopy: each workingCopy repository: aRepository ] ]! ! !GoferWorking methodsFor: 'private' stamp: 'lr 9/24/2009 16:52'! addPackage: aPackage workingCopy: aWorkingCopy repository: aRepository self addPackage: aPackage requiredCopy: aWorkingCopy repository: aRepository! ! !GoferWorking methodsFor: 'cleaning' stamp: 'lr 8/19/2009 13:50'! cleanup: aWorkingCopy self cleanupCategories: aWorkingCopy. self cleanupProtocols: aWorkingCopy! ! !GoferWorking methodsFor: 'cleaning' stamp: 'lr 8/19/2009 14:50'! cleanupCategories: aWorkingCopy aWorkingCopy packageInfo systemCategories do: [ :category | (SystemOrganization classesInCategory: category) isEmpty ifTrue: [ SystemOrganization removeSystemCategory: category ] ]! ! !GoferWorking methodsFor: 'cleaning' stamp: 'lr 8/19/2009 14:50'! cleanupProtocols: aWorkingCopy aWorkingCopy packageInfo foreignClasses do: [ :class | (aWorkingCopy packageInfo foreignExtensionCategoriesForClass: class) do: [ :category | (class organization listAtCategoryNamed: category) isEmpty ifTrue: [ class organization removeCategory: category ] ] ]! ! !GoferWorking methodsFor: 'initialization' stamp: 'lr 8/19/2009 13:14'! initialize super initialize. workingCopies := OrderedCollection new! ! !GoferWorking methodsFor: 'initialization' stamp: 'lr 9/24/2009 16:49'! initializeOn: aGofer super initializeOn: aGofer. self gofer do: [ :each | self addPackage: each ]! ! !GoferWorking methodsFor: 'accessing' stamp: 'lr 9/24/2009 16:55'! workingCopies "Answer the working copies to be operated on." ^ workingCopies! ! Object subclass: #GoferPackage instanceVariableNames: 'name repository' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferPackage class methodsFor: 'instance creation' stamp: 'lr 8/19/2009 10:27'! name: aString repository: aRepository ^ self basicNew initializeName: aString repository: aRepository! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/24/2009 16:43'! findVersion "Find the latest version." ^ self findVersion: self name! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/24/2009 16:44'! findVersion: aString "Find the latest version with the prefix aString." ^ self findVersion: aString in: self repository! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/24/2009 16:45'! findVersion: aString in: aRepository "Find the latest version with the prefix aString in the repository aRepository." ^ self findVersion: aString in: aRepository ifAbsent: [ self error: 'Unable to find version ' , aString printString , ' in ' , aRepository printString , '.' ]! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/24/2009 17:05'! findVersion: aString in: aRepository ifAbsent: aBlock "Find the latest version with the prefix aString in the repository aRepository. Evaluate aBlock if not found." | repositories versions | repositories := OrderedCollection new. versions := SortedCollection sortBlock: [ :a :b | (a key copyAfterLast: $.) asNumber <= (b key copyAfterLast: $.) asNumber ]. aRepository isRepositoryGroup ifFalse: [ repositories add: aRepository ] ifTrue: [ repositories addAll: (aRepository repositories select: [ :each | each isValid ]) ]. repositories do: [ :repo | repo allVersionNames do: [ :each | (each beginsWith: aString) ifTrue: [ versions add: each -> repo ] ] ]. versions isEmpty ifTrue: [ ^ aBlock value ]. ^ versions last value loadVersionFromFileNamed: versions last key, '.mcz'! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/24/2009 16:43'! findWorkingCopy "Find the working copy." ^ self findWorkingCopy: (self name copyUpTo: $-)! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/24/2009 16:21'! findWorkingCopy: aString "Find the working copy with the package name aString." ^ self findWorkingCopy: aString ifAbsent: [ self error: 'Working copy named ' , aString printString , ' not found.' ] ! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/24/2009 16:35'! findWorkingCopy: aString ifAbsent: aBlock "Find the working copy with the package name aString, evaluate aBlock if not found." ^ MCWorkingCopy allManagers detect: [ :each | each packageName = aString ] ifNone: [ ^ aBlock value ]! ! !GoferPackage methodsFor: 'initialization' stamp: 'lr 8/19/2009 14:49'! initializeName: aString repository: aRepository name := aString. repository := aRepository! ! !GoferPackage methodsFor: 'accessing' stamp: 'lr 8/19/2009 10:30'! name "Answer the package name or prefix." ^ name! ! !GoferPackage methodsFor: 'printing' stamp: 'lr 8/19/2009 10:30'! printOn: aStream super printOn: aStream. aStream nextPutAll: ' name: '; print: self name! ! !GoferPackage methodsFor: 'accessing' stamp: 'lr 8/17/2009 13:55'! repository "Answer the repository instance of this package, or nil." ^ repository! ! !MCRepository methodsFor: '*gofer-testing' stamp: 'lr 9/24/2009 17:02'! isRepositoryGroup ^ false! ! TestCase subclass: #GoferPackageTest instanceVariableNames: 'package' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Test'! !GoferPackageTest methodsFor: 'running' stamp: 'lr 9/24/2009 17:13'! createPackage: aString package := GoferPackage name: aString repository: self goferRepository! ! !GoferPackageTest methodsFor: 'accessing' stamp: 'lr 9/24/2009 17:13'! goferRepository ^ MCHttpRepository location: 'http://source.lukas-renggli.ch/flair' user: '' password: ''! ! !GoferPackageTest methodsFor: 'testing-querying' stamp: 'lr 9/24/2009 17:23'! testFindVersionWithExactNumber | version | self createPackage: 'Gofer-lr.42'. version := package findVersion. self assert: (version isKindOf: MCVersion). self assert: (version info id asString = 'd918ea63-8d1c-4f52-aadd-46e035aabbbe'). version := package findVersion: package name. self assert: (version isKindOf: MCVersion). self assert: (version info id asString = 'd918ea63-8d1c-4f52-aadd-46e035aabbbe'). version := package findVersion: package name in: package repository. self assert: (version isKindOf: MCVersion). self assert: (version info id asString = 'd918ea63-8d1c-4f52-aadd-46e035aabbbe'). version := package findVersion: package name in: package repository ifAbsent: [ nil ]. self assert: (version isKindOf: MCVersion). self assert: (version info id asString = 'd918ea63-8d1c-4f52-aadd-46e035aabbbe')! ! !GoferPackageTest methodsFor: 'testing-querying' stamp: 'lr 9/24/2009 17:24'! testFindVersionWithInvalidName self createPackage: 'Gopher'. self should: [ package findVersion ] raise: Error. self should: [ package findVersion: package name ] raise: Error. self should: [ package findVersion: package name in: self goferRepository ] raise: Error. self assert: (package findVersion: package name in: self goferRepository ifAbsent: [ true ])! ! !GoferPackageTest methodsFor: 'testing-querying' stamp: 'lr 9/24/2009 17:27'! testFindVersionWithPackageName | version | self createPackage: 'Gofer'. version := package findVersion. self assert: (version isKindOf: MCVersion). self assert: (version info name beginsWith: 'Gofer'). version := package findVersion: package name. self assert: (version isKindOf: MCVersion). self assert: (version info name beginsWith: 'Gofer'). version := package findVersion: package name in: self goferRepository. self assert: (version isKindOf: MCVersion). self assert: (version info name beginsWith: 'Gofer'). version := package findVersion: package name in: self goferRepository ifAbsent: [ nil ]. self assert: (version isKindOf: MCVersion). self assert: (version info name beginsWith: 'Gofer')! ! !GoferPackageTest methodsFor: 'testing-querying' stamp: 'lr 9/24/2009 16:35'! testFindWorkingCopyWithExactVersion | workingCopy | self createPackage: 'Gofer-lr.42'. workingCopy := package findWorkingCopy. self assert: (workingCopy isKindOf: MCWorkingCopy). self assert: (workingCopy packageName = 'Gofer'). self should: [ package findWorkingCopy: package name ] raise: Error. self assert: (package findWorkingCopy: package name ifAbsent: [ true ])! ! !GoferPackageTest methodsFor: 'testing-querying' stamp: 'lr 9/24/2009 16:33'! testFindWorkingCopyWithPackageName | workingCopy | self createPackage: 'Gofer'. workingCopy := package findWorkingCopy. self assert: (workingCopy isKindOf: MCWorkingCopy). self assert: (workingCopy packageName = 'Gofer'). workingCopy := package findWorkingCopy: package name. self assert: (workingCopy isKindOf: MCWorkingCopy). self assert: (workingCopy packageName = 'Gofer'). workingCopy := package findWorkingCopy: package name ifAbsent: [ self fail ]. self assert: (workingCopy isKindOf: MCWorkingCopy). self assert: (workingCopy packageName = 'Gofer')! ! !GoferPackageTest methodsFor: 'testing-querying' stamp: 'lr 9/24/2009 16:35'! testFindWorkingCopyWithPrefix self createPackage: 'Gofe'. self should: [ package findWorkingCopy ] raise: Error. self should: [ package findWorkingCopy: package name ] raise: Error. self assert: (package findWorkingCopy: package name ifAbsent: [ true ])! ! !GoferPackageTest methodsFor: 'testing-accessing' stamp: 'lr 9/24/2009 16:34'! testingName self createPackage: 'Gofer'. self assert: package name = 'Gofer'! ! !GoferPackageTest methodsFor: 'testing-printing' stamp: 'lr 9/24/2009 16:34'! testingPrintString self createPackage: 'Gofer'. self assert: package printString = 'a GoferPackage name: ''Gofer'''! ! !GoferPackageTest methodsFor: 'testing-accessing' stamp: 'lr 9/24/2009 16:34'! testingRepository self createPackage: 'Gofer'. self assert: package repository locationWithTrailingSlash = 'http://source.lukas-renggli.ch/flair/'! ! TestCase subclass: #GoferScenarioTest instanceVariableNames: 'gofer' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Test'! !GoferScenarioTest methodsFor: 'assertions' stamp: 'lr 8/20/2009 20:58'! assertClass: aClassSymbol self assert: (Smalltalk hasClassNamed: aClassSymbol)! ! !GoferScenarioTest methodsFor: 'assertions' stamp: 'lr 8/20/2009 21:04'! assertClass: aClassSymbol selector: aMethodSymbol self assertClass: aClassSymbol. self assert: ((Smalltalk at: aClassSymbol) includesSelector: aMethodSymbol)! ! !GoferScenarioTest methodsFor: 'utilities' stamp: 'lr 8/20/2009 21:03'! compile: aClassSelector method: aString self assertClass: aClassSelector. (Smalltalk at: aClassSelector) compile: aString.! ! !GoferScenarioTest methodsFor: 'utilities' stamp: 'lr 8/20/2009 21:04'! evaluate: aClassSelector selector: aMethodSelector self assertClass: aClassSelector selector: aMethodSelector. ^ (Smalltalk at: aClassSelector) new perform: aMethodSelector! ! !GoferScenarioTest methodsFor: 'utilities' stamp: 'lr 8/20/2009 21:14'! hasPackage: aString | package | package := MCWorkingCopy allManagers detect: [ :each | each packageName = aString ] ifNone: [ nil ]. ^ package notNil! ! !GoferScenarioTest methodsFor: 'running' stamp: 'lr 8/20/2009 20:45'! setUp gofer := Gofer new. gofer wiresong: 'ob'; add: 'BogusInfo'! ! !GoferScenarioTest methodsFor: 'running' stamp: 'lr 8/20/2009 21:12'! tearDown [ gofer unload ] on: Error do: [ :err | "assume it is not there" ]! ! !GoferScenarioTest methodsFor: 'testing' stamp: 'lr 8/20/2009 21:13'! testCommit self assert: false "dunno how to test yet"! ! !GoferScenarioTest methodsFor: 'testing' stamp: 'lr 8/20/2009 21:13'! testDiff self assert: false "dunno how to test yet"! ! !GoferScenarioTest methodsFor: 'testing' stamp: 'lr 8/20/2009 21:15'! testLoad self shouldnt: [ gofer load ] raise: Error. self assert: (self hasPackage: 'Bogus'); assertClass: #BogusA. self assert: (self hasPackage: 'BogusExt'); assertClass: #BogusA selector: #isFake. self assert: (self hasPackage: 'BogusInfo'); assertClass: #BogusInfo! ! !GoferScenarioTest methodsFor: 'testing' stamp: 'lr 8/20/2009 21:13'! testMerge self assert: false "dunno how to test yet"! ! !GoferScenarioTest methodsFor: 'testing' stamp: 'lr 8/20/2009 21:13'! testRecompile gofer load. self shouldnt: [ gofer recompile ] raise: Error! ! !GoferScenarioTest methodsFor: 'testing' stamp: 'lr 8/20/2009 21:09'! testRevert gofer load. self assert: (self evaluate: #BogusA selector: #isFake). self compile: #BogusA method: 'isFake ^ false'. self deny: (self evaluate: #BogusA selector: #isFake). self shouldnt: [ gofer revert ] raise: Error. self assert: (self evaluate: #BogusA selector: #isFake)! ! !GoferScenarioTest methodsFor: 'testing' stamp: 'lr 8/20/2009 21:15'! testUnload gofer load. self shouldnt: [ gofer unload ] raise: Error. self deny: (self hasPackage: 'Bogus'). self deny: (self hasPackage: 'BogusExt'). self deny: (self hasPackage: 'BogusInfo')! ! !GoferScenarioTest methodsFor: 'testing' stamp: 'lr 9/19/2009 14:13'! testUpdate gofer load. self shouldnt: [ gofer update ] raise: Error. self assert: (self hasPackage: 'Bogus'). self assert: (self hasPackage: 'BogusExt'). self assert: (self hasPackage: 'BogusInfo')! ! TestCase subclass: #GoferTest instanceVariableNames: 'gofer' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Test'! !GoferTest methodsFor: 'running' stamp: 'lr 8/20/2009 20:47'! setUp super setUp. gofer := Gofer new! ! !GoferTest methodsFor: 'testing' stamp: 'lr 8/19/2009 14:54'! testAdd gofer add: 'Foo'. self assert: gofer packages size = 1. self assert: gofer packages first name = 'Foo'. self assert: gofer packages first repository isNil. gofer url: 'http://foo.com'; add: 'Bar'. self assert: gofer packages size = 2. self assert: gofer packages last name = 'Bar'. self assert: gofer packages last repository locationWithTrailingSlash = 'http://foo.com/'! ! !GoferTest methodsFor: 'testing' stamp: 'lr 8/19/2009 14:54'! testAddAll gofer addAll: #('Foo' 'Bar'). self assert: gofer packages size = 2. self assert: gofer packages first name = 'Foo'. self assert: gofer packages first repository isNil. self assert: gofer packages last name = 'Bar'. self assert: gofer packages last repository isNil! ! !GoferTest methodsFor: 'testing-repositories' stamp: 'lr 8/20/2009 20:50'! testCroquet gofer croquet: 'Hermes'. self assert: gofer repository locationWithTrailingSlash = 'http://hedgehog.software.umn.edu:8888/Hermes/'! ! !GoferTest methodsFor: 'testing-repositories' stamp: 'lr 8/20/2009 20:50'! testImpara gofer impara: 'Tweak'. self assert: gofer repository locationWithTrailingSlash = 'http://source.impara.de/Tweak/'! ! !GoferTest methodsFor: 'testing' stamp: 'lr 8/19/2009 14:54'! testInitialized self assert: gofer repository isNil. self assert: gofer packages isEmpty! ! !GoferTest methodsFor: 'testing-repositories' stamp: 'lr 7/10/2009 16:56'! testRenggli gofer renggli: 'pier'. self assert: gofer repository locationWithTrailingSlash = 'http://source.lukas-renggli.ch/pier/'! ! !GoferTest methodsFor: 'testing-accessing' stamp: 'lr 7/10/2009 16:47'! testRepository gofer repository: MCDirectoryRepository new. self assert: (gofer repository isKindOf: MCDirectoryRepository)! ! !GoferTest methodsFor: 'testing-repositories' stamp: 'lr 7/10/2009 16:53'! testSaltypickle gofer saltypickle: 'GraphViz'. self assert: gofer repository locationWithTrailingSlash = 'http://squeak.saltypickle.com/GraphViz/'! ! !GoferTest methodsFor: 'testing-repositories' stamp: 'lr 7/10/2009 16:57'! testSqueakfoundation gofer squeakfoundation: '39a'. self assert: gofer repository locationWithTrailingSlash = 'http://source.squeakfoundation.org/39a/'! ! !GoferTest methodsFor: 'testing-repositories' stamp: 'lr 7/10/2009 16:54'! testSqueaksource gofer squeaksource: 'Seaside29'. self assert: gofer repository locationWithTrailingSlash = 'http://www.squeaksource.com/Seaside29/'! ! !GoferTest methodsFor: 'testing-accessing' stamp: 'lr 9/7/2009 20:13'! testUrl gofer url: 'http://source.lukas-renggli.ch/pier'. self assert: (gofer repository isKindOf: MCHttpRepository). self assert: (gofer repository locationWithTrailingSlash = 'http://source.lukas-renggli.ch/pier/'). self assert: (gofer repository user isEmpty). self assert: (gofer repository password isEmpty)! ! !GoferTest methodsFor: 'testing-accessing' stamp: 'lr 9/7/2009 20:13'! testUrlUsernamePassword gofer url: 'http://source.lukas-renggli.ch/pier' username: 'foo' password: 'bar'. self assert: (gofer repository isKindOf: MCHttpRepository). self assert: (gofer repository locationWithTrailingSlash = 'http://source.lukas-renggli.ch/pier/'). self assert: (gofer repository user = 'foo'). self assert: (gofer repository password = 'bar')! ! !GoferTest methodsFor: 'testing-repositories' stamp: 'lr 7/10/2009 16:55'! testWiresong gofer wiresong: 'ob'. self assert: gofer repository locationWithTrailingSlash = 'http://source.wiresong.ca/ob/'! !