SystemOrganization addCategory: #'Gofer-Core'! SystemOrganization addCategory: #'Gofer-Test'! Notification subclass: #GoferRepositoryCache instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferRepositoryCache class methodsFor: 'as yet unclassified' stamp: 'lr 9/28/2009 23:24'! allVersionsFor: aRepository ^ self signal at: aRepository ifAbsentPut: [ aRepository allVersionNames ]! ! !GoferRepositoryCache class methodsFor: 'as yet unclassified' stamp: 'lr 9/28/2009 23:24'! during: aBlock | cache | cache := Dictionary new. ^ aBlock on: self do: [ :notification | notification resume: cache ]! ! !GoferRepositoryCache methodsFor: 'accessing' stamp: 'lr 9/28/2009 23:23'! defaultAction ^ Dictionary new! ! Object subclass: #Gofer instanceVariableNames: 'packages options' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !Gofer commentStamp: 'lr 8/19/2009 16:17' prior: 0! Gofer loads, updates, merges, diffs, reverts and unloads Monticello packages. When loading/updating/merging a package with Gofer, it ... - cleanly loads the code from one or more repositories, - finds the "latest" version of a package matching the given name prefix, - makes sure that dependencies are correctly loaded as well, - makes sure that the repository is assigned to the working copy, and - makes sure that the repository is shared among all packages of the same repository. When unloading a package with Gofer, it ... - cleanly unloads one or more packages from the image, - detects dependencies and automatically unloads these as well, - removes class categories and method protocols that belong to the packages, - unregisters repositories that are no longer in use. " Example: Working with Seaside 2.8 " " 1. Specify the packages (and repositories) to work with " gofer := Gofer new. gofer squeaksource: 'KomHttpServer'; addAll: #( 'DynamicBindings' 'KomServices' 'KomHttpServer' ); squeaksource: 'Seaside'; addAll: #( 'Seaside2.8a' 'Scriptaculous' ). " 2. Perform one or more operations on the packages " gofer load. gofer merge. gofer diff. gofer commit. gofer commit: 'something chnaged' gofer revert. gofer unload.! !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: '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 9/28/2009 23:25'! execute: anOperationClass ^ GoferRepositoryCache during: [ (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/3/2009 11:00'! addPackage: aPackage | version | version := aPackage findLatestVersion. 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/3/2009 10:55'! updateCategories "This method makes sure that the categories are ordered in load-order and as specified in the packages." | orderedCategories | orderedCategories := versions gather: [ :version | (version snapshot definitions select: [ :definition | definition isOrganizationDefinition ]) gather: [ :definition | definition categories ] ]. (MCOrganizationDefinition categories: orderedCategories) 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 8/19/2009 16:19'! addRequiredCopy: aWorkingCopy repository: aRepository super addRequiredCopy: aWorkingCopy repository: aRepository. repositories at: aWorkingCopy put: (aRepository ifNil: [ aWorkingCopy repositoryGroup repositories detect: [ :each | each isKindOf: MCHttpRepository ] ifNone: [ self error: 'No repository found for ' , aWorkingCopy package name printString ] ])! ! !GoferCommit methodsFor: 'running' stamp: 'lr 8/20/2009 20:22'! commit: 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: 'running' stamp: 'lr 8/19/2009 14:37'! execute self workingCopies do: [ :each | each needsSaving ifTrue: [ self commit: each ] ]! ! !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 8/19/2009 16:32'! addRequiredCopy: aWorkingCopy repository: aRepository | repository patch | super addRequiredCopy: aWorkingCopy repository: aRepository. repository := aRepository ifNil: [ aWorkingCopy repositoryGroup ]. patch := aWorkingCopy package snapshot patchRelativeToBase: (repository versionWithInfo: aWorkingCopy ancestors first) snapshot. aWorkingCopy modified: patch isEmpty not. patch isEmpty ifTrue: [ self workingCopies remove: aWorkingCopy ] ifFalse: [ 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/19/2009 13:41'! execute [ self model merge ] on: MCMergeResolutionRequest do: [ :request | request merger conflicts isEmpty ifTrue: [ request resume: true ] ifFalse: [ request pass ] ]. 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/19/2009 13:21'! versionFor: aWorkingCopy repository: aRepository ^ (aRepository ifNil: [ aWorkingCopy repositoryGroup ]) versionWithInfo: aWorkingCopy ancestors first! ! !GoferUpdate methodsFor: 'private' stamp: 'lr 9/19/2009 13:20'! addWorkingCopy: aWorkingCopy repository: aRepository super addWorkingCopy: aWorkingCopy repository: aRepository. self model addVersion: (self versionFor: 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/19/2009 13:22'! versionFor: aWorkingCopy repository: aRepository | package | package := GoferPackage name: aWorkingCopy packageName repository: (aRepository ifNil: [ aWorkingCopy repositoryGroup ]). ^ package findLatestVersion! ! !GoferWorking methodsFor: 'private' stamp: 'lr 8/19/2009 14:19'! addRequiredCopy: aWorkingCopy repository: aRepository (workingCopies includes: aWorkingCopy) ifTrue: [ ^ self ]. workingCopies addLast: aWorkingCopy. aWorkingCopy requiredPackages reverseDo: [ :each | self addRequiredCopy: each workingCopy repository: aRepository ]! ! !GoferWorking methodsFor: 'private' stamp: 'lr 8/19/2009 14:18'! addWorkingCopy: aWorkingCopy repository: aRepository self addRequiredCopy: 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 8/20/2009 20:21'! initializeOn: aGofer super initializeOn: aGofer. self gofer do: [ :package | self addWorkingCopy: package findWorkingCopy repository: package repository ]! ! !GoferWorking methodsFor: 'accessing' stamp: 'lr 8/19/2009 13:43'! 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/18/2009 18:21'! findLatestVersion ^ self findLatestVersionIfAbsent: [ self error: 'No version named ' , self name printString , ' found' ]! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/28/2009 23:22'! findLatestVersionIfAbsent: aBlock | repositories versions | versions := OrderedCollection new. repositories := OrderedCollection new. (self repository respondsTo: #repositories) ifFalse: [ repositories add: self repository ] ifTrue: [ repositories addAll: (self repository repositories select: [ :each | each isValid and: [ each isKindOf: MCFileBasedRepository ] ]) ]. repositories do: [ :repo | (GoferRepositoryCache allVersionsFor: repo) do: [ :each | (each beginsWith: self name) ifTrue: [ versions add: each -> repo ] ] ]. versions isEmpty ifTrue: [ ^ aBlock value ]. versions := versions asSortedCollection: [ :a :b | (a key copyAfterLast: $.) asNumber <= (b key copyAfterLast: $.) asNumber ]. ^ versions last value loadVersionFromFileNamed: versions last key, '.mcz'! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/3/2009 11:44'! findWorkingCopy ^ self findWorkingCopyIfAbsent: [ self error: 'Working copy ' , self name printString , ' not found' ] ! ! !GoferPackage methodsFor: 'querying' stamp: 'lr 9/3/2009 11:44'! findWorkingCopyIfAbsent: aBlock | candidates | candidates := MCWorkingCopy registry values select: [ :each | self name beginsWith: each packageName ]. candidates isEmpty ifTrue: [ ^ aBlock value ]. candidates := candidates asSortedCollection: [ :a :b | a packageName > b packageName ]. ^ candidates first! ! !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! ! TestCase subclass: #GoferModelTest instanceVariableNames: 'gofer' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Test'! !GoferModelTest methodsFor: 'running' stamp: 'lr 8/20/2009 20:47'! setUp super setUp. gofer := Gofer new! ! !GoferModelTest 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/'! ! !GoferModelTest 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! ! !GoferModelTest 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/'! ! !GoferModelTest methodsFor: 'testing-repositories' stamp: 'lr 8/20/2009 20:50'! testImpara gofer impara: 'Tweak'. self assert: gofer repository locationWithTrailingSlash = 'http://source.impara.de/Tweak/'! ! !GoferModelTest methodsFor: 'testing' stamp: 'lr 8/19/2009 14:54'! testInitialized self assert: gofer repository isNil. self assert: gofer packages isEmpty! ! !GoferModelTest 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/'! ! !GoferModelTest methodsFor: 'testing-accessing' stamp: 'lr 7/10/2009 16:47'! testRepository gofer repository: MCDirectoryRepository new. self assert: (gofer repository isKindOf: MCDirectoryRepository)! ! !GoferModelTest methodsFor: 'testing-repositories' stamp: 'lr 7/10/2009 16:53'! testSaltypickle gofer saltypickle: 'GraphViz'. self assert: gofer repository locationWithTrailingSlash = 'http://squeak.saltypickle.com/GraphViz/'! ! !GoferModelTest methodsFor: 'testing-repositories' stamp: 'lr 7/10/2009 16:57'! testSqueakfoundation gofer squeakfoundation: '39a'. self assert: gofer repository locationWithTrailingSlash = 'http://source.squeakfoundation.org/39a/'! ! !GoferModelTest methodsFor: 'testing-repositories' stamp: 'lr 7/10/2009 16:54'! testSqueaksource gofer squeaksource: 'Seaside29'. self assert: gofer repository locationWithTrailingSlash = 'http://www.squeaksource.com/Seaside29/'! ! !GoferModelTest 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)! ! !GoferModelTest 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')! ! !GoferModelTest methodsFor: 'testing-repositories' stamp: 'lr 7/10/2009 16:55'! testWiresong gofer wiresong: 'ob'. self assert: gofer repository locationWithTrailingSlash = 'http://source.wiresong.ca/ob/'! ! 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')! !