SystemOrganization addCategory: #'Gofer-Core'! !SystemOrganizer methodsFor: '*gofer-core-accessing' stamp: 'lr 12/3/2009 21:04'! goferClassesInCategory: category ^ (self listAtCategoryNamed: category) collect: [ :className | Smalltalk at: className ]! ! !MCDictionaryRepository methodsFor: '*gofer-core-accessing' stamp: 'lr 12/11/2009 22:31'! goferPriority ^ 10! ! !MCDictionaryRepository methodsFor: '*gofer-core-accessing' stamp: 'TestRunner 12/12/2009 11:12'! goferReferences ^ self allVersionInfos collect: [ :each | GoferResolvedReference name: each name repository: self ]! ! !MCDictionaryRepository methodsFor: '*gofer-core-accessing' stamp: 'TestRunner 12/13/2009 14:57'! goferVersionFrom: aVersionReference ^ self dictionary detect: [ :version | version info name = aVersionReference name ]! ! Object subclass: #Gofer instanceVariableNames: 'references repositories errorBlock packageCacheRepository resolvedReferencesCache' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !Gofer commentStamp: 'lr 1/30/2010 14:42' prior: 0! : Gofer, a person who runs errands. Origin 1960s: from go for, i.e. go and fetch. : ''The New Oxford American Dictionary'' !! Synopsis 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 package name. - 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 prefers to work with faster repositories if there is a choice. - Gofer cleans up after Monticello, no empty class categories and no empty method protocols are to be expected. - Gofer supports operations to sync remote and local repositories with each other. !! Installation Gofer is included with the latest Pharo and GemStone distributions. To update to the latest version you can use Gofer itself: == Gofer upgrade In case you are missing Gofer in your image, grab it from *http://source.lukas-renggli.ch/gofer.html*. !! Description Gofer is very simple by design, the basic useage scenario is always the same and consists of three steps: # You specify one or more Monticello repository URLs. You can do this using the methods ==url:==, ==url:username:password:== (HTTP, FTP), ==directory:==, or ==repository:== if you need full control. You might also use the convenience methods like ==squeaksource:==, ==wiresong:==, or ==gemsource:== for well known repositories. Additionally the following settings are available: #- Gofer implicitly declares the local package cache as a repository. To disable the local package cache use the method ==disablePackageCache==, to re-enable use ==enablePackageCache==. #- Gofer throws an error if a repository is not reachable. To silently ignore repository erros use the message ==disableRepositoryErrors==, to re-enable use ==enableRepositoryErrors==. # You specify one or more Monticello packages you want to work with, by adding them to the Gofer instance. Use ==version:== to add a specific version, or use ==package:== to add the "latest" version in the given repository. Furthermore there is ==package:constraint:== that allows you to further constraint the version to be loaded in a block passed in as the second argument. # You specify one or more actions to be performed on the specified packages: | ==load== | Load the specified packages. | ==update== | Update the specified packages. | ==merge== | Merge the specified packages into their working copies. | ==localChanges== | Answer the changes between the base version and the working copy. | ==browseLocalChanges== | Browse the changes between the base version and the working copy. | ==remoteChanges== | Answer the changes between the working copy and the remote changes. | ==browseRemoteChanges== | Browse the changes between the working copy and the remote changes. | ==cleanup== | Cleans the specified packages. | ==commit== | Commit the modified specified packages. | ==commit:== | Commit the modified specified packages with the given commit message. | ==revert== | Revert the specified packages to the currently loaded version. | ==recompile== | Recompile the specified packages. | ==reinitialize== | Call the class side initializers on the specified packages. | ==unload== | Unload the specified packages. | ==fetch== | Download versions from remote repositories into the local cache. | ==push== | Upload local versions from local cache into remote repositories. !! Example To use Gofer to update to exact versions of the Kom Server, the 'latest' code of Seaside 2.8 and the 'latest' code of the Scriptaculous package that is committed by the author with the initials 'lr' one could evaluate: == Gofer new == squeaksource: 'KomHttpServer'; == version: 'DynamicBindings-gc.7'; == version: 'KomServices-gc.19'; == version: 'KomHttpServer-gc.32'; == update. == Gofer new == squeaksource: 'Seaside'; == package: 'Seaside2.8a'; == package: 'Scriptaculous' constraint: [ :version | version author = 'lr' ]; == load! !Gofer class methodsFor: 'private' stamp: 'lr 1/5/2010 10:45'! gofer "Create a Gofer instance of Gofer." ^ self new renggli: 'gofer'; package: 'Gofer-Core'; package: 'Gofer-Tests'; yourself! ! !Gofer class methodsFor: 'instance creation' stamp: 'lr 11/6/2009 10:50'! it ^ self new! ! !Gofer class methodsFor: 'instance creation' stamp: 'lr 8/20/2009 09:54'! new ^ self basicNew initialize! ! !Gofer class methodsFor: 'private' stamp: 'lr 1/12/2010 19:39'! upgrade "Update Gofer to the latest version using itself." | working | [ self gofer load ] on: Error do: [ :err | err retry ]. self new unload unregister: (MCWorkingCopy forPackage: (MCPackage named: 'Gofer')). self gofer recompile; cleanup! ! !Gofer methodsFor: 'deprecated' stamp: 'lr 12/14/2009 20:08'! addPackage: aString self deprecated: 'Instead of #addPackage: simply use #package:'. self package: aString! ! !Gofer methodsFor: 'deprecated' stamp: 'lr 12/14/2009 20:08'! addPackage: aString constraint: aBlock self deprecated: 'Instead of #addPackage:constraint: simply use #package:constraint:'. self package: aString constraint: aBlock! ! !Gofer methodsFor: 'deprecated' stamp: 'lr 12/14/2009 20:08'! addVersion: aString self deprecated: 'Instead of #addVersion: simply use #version:'. self version: aString! ! !Gofer methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:17'! allResolved "Answer all sorted references within the configured repositories." | resolved | resolved := OrderedCollection new. self repositories do: [ :repository | resolved addAll: (self allResolvedIn: repository) ]. ^ resolved asSortedCollection asArray! ! !Gofer methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:17'! allResolvedIn: aRepository "Answer all sorted references within aRepository. For efficiency cache the references." ^ (resolvedReferencesCache ifNil: [ resolvedReferencesCache := Dictionary new ]) at: aRepository ifAbsentPut: [ self basicReferencesIn: aRepository ]! ! !Gofer methodsFor: 'private' stamp: 'lr 12/13/2009 16:28'! basicReferencesIn: aRepository ^ [ aRepository goferReferences asSortedCollection asArray ] on: GoferRepositoryError do: errorBlock! ! !Gofer methodsFor: 'repositories-places' stamp: 'lr 2/7/2010 15:11'! blueplane: aString self url: 'http://squeaksource.blueplane.jp/' , aString! ! !Gofer methodsFor: 'operations-ui' stamp: 'lr 12/14/2009 23:51'! browseLocalChanges "Browse the changes between the base version and the working copy." ^ self execute: GoferBrowseLocalChanges! ! !Gofer methodsFor: 'operations-ui' stamp: 'lr 12/14/2009 23:51'! browseRemoteChanges "Browse the changes between the working copy and the remote changes." ^ self execute: GoferBrowseRemoteChanges! ! !Gofer methodsFor: 'operations' stamp: 'lr 10/3/2009 11:31'! cleanup "Cleans the specified packages." ^ self execute: GoferCleanup! ! !Gofer methodsFor: 'operations' stamp: 'lr 11/10/2009 10:08'! commit "Commit the modified packages." ^ self execute: GoferCommit! ! !Gofer methodsFor: 'operations' stamp: 'lr 11/10/2009 10:08'! commit: aString "Commit the modified packages with the given commit message." ^ self execute: GoferCommit do: [ :operation | operation message: aString ]! ! !Gofer methodsFor: 'repositories-places' stamp: 'lr 7/10/2009 16:27'! croquet: aString self url: 'http://hedgehog.software.umn.edu:8888/' , aString! ! !Gofer methodsFor: 'repositories' stamp: 'TestRunner 1/11/2010 22:57'! directory: aDirectoryOrString "Add a file-system repository at aDirectoryOrString." | repository | repository := (aDirectoryOrString isString and: [ aDirectoryOrString endsWith: '*' ]) ifTrue: [ (Smalltalk at: #MCSubDirectoryRepository ifAbsent: [ self error: aDirectoryOrString printString , ' is an unsupported repository type' ]) new directory: (FileDirectory on: aDirectoryOrString allButLast); yourself ] ifFalse: [ MCDirectoryRepository new directory: (aDirectoryOrString isString ifTrue: [ FileDirectory on: aDirectoryOrString ] ifFalse: [ aDirectoryOrString ]); yourself ]. self repository: repository! ! !Gofer methodsFor: 'repositories-options' stamp: 'lr 12/13/2009 16:33'! disablePackageCache "Disable the use of the package-cache repository." packageCacheRepository := nil! ! !Gofer methodsFor: 'repositories-options' stamp: 'lr 12/13/2009 16:32'! disableRepositoryErrors "Silently swallow all repository errors." errorBlock := [ :error | error resume: #() ]! ! !Gofer methodsFor: 'repositories-options' stamp: 'lr 12/13/2009 16:33'! enablePackageCache "Enable the use of the package-cache repository." packageCacheRepository := MCCacheRepository default! ! !Gofer methodsFor: 'repositories-options' stamp: 'lr 12/13/2009 16:32'! enableRepositoryErrors "Throw an exception when repositories are not available." errorBlock := [ :error | error pass ]! ! !Gofer methodsFor: 'private' stamp: 'lr 10/2/2009 10:11'! execute: anOperationClass ^ self execute: anOperationClass do: nil! ! !Gofer methodsFor: 'private' stamp: 'lr 12/13/2009 16:43'! execute: anOperationClass do: aBlock | operation result | operation := anOperationClass on: self copy. aBlock isNil ifFalse: [ aBlock value: operation ]. ^ operation execute! ! !Gofer methodsFor: 'operations' stamp: 'lr 12/3/2009 21:06'! fetch "Download versions from remote repositories into the local cache." ^ self execute: GoferFetch! ! !Gofer methodsFor: 'repositories-places' stamp: 'dkh 10/16/2009 10:04'! gemsource: aString self url: 'http://seaside.gemstone.com/ss/' , aString! ! !Gofer methodsFor: 'repositories-places' stamp: 'lr 7/10/2009 16:27'! impara: aString self url: 'http://source.impara.de/' , aString! ! !Gofer methodsFor: 'initialization' stamp: 'lr 12/13/2009 16:33'! initialize self enablePackageCache; enableRepositoryErrors. references := OrderedCollection new. repositories := OrderedCollection new! ! !Gofer methodsFor: 'operations' stamp: 'lr 11/30/2009 14:17'! load "Load the specified packages into the image." ^ self execute: GoferLoad! ! !Gofer methodsFor: 'operations' stamp: 'lr 12/14/2009 23:51'! localChanges "Answer the changes between the base version and the working copy." ^ self execute: GoferLocalChanges! ! !Gofer methodsFor: 'operations' stamp: 'lr 11/10/2009 10:06'! merge "Merge the specified packages into their working copies." ^ self execute: GoferMerge! ! !Gofer methodsFor: 'references' stamp: 'lr 12/13/2009 13:25'! package: aString "Add the package aString to the receiver." references addLast: (GoferPackageReference name: aString)! ! !Gofer methodsFor: 'references' stamp: 'lr 12/13/2009 13:25'! package: aString constraint: aOneArgumentBlock "Add the package aString to the receiver, constraint the resulting versions further with aOneArgumentBlock." references addLast: (GoferConstraintReference name: aString constraint: aOneArgumentBlock)! ! !Gofer methodsFor: 'copying' stamp: 'lr 12/13/2009 16:52'! postCopy references := references copy. repositories := repositories copy. resolvedReferencesCache := nil! ! !Gofer methodsFor: 'operations' stamp: 'lr 12/3/2009 21:06'! push "Upload local versions from local cache into remote repositories." ^ self execute: GoferPush! ! !Gofer methodsFor: 'operations' stamp: 'lr 8/20/2009 11:44'! recompile "Recompile the specified packages." ^ self execute: GoferRecompile! ! !Gofer methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:18'! references "Answer the configured references." ^ Array withAll: references! ! !Gofer methodsFor: 'operations' stamp: 'lr 12/30/2009 11:27'! reinitialize "Calls the class side initializers on all package code." ^ self execute: GoferReinitialize! ! !Gofer methodsFor: 'operations' stamp: 'lr 12/12/2009 12:49'! remoteChanges "Display the changes between the working copy and the remote changes." ^ self execute: GoferRemoteChanges! ! !Gofer methodsFor: 'repositories-places' stamp: 'lr 7/10/2009 16:25'! renggli: aString self url: 'http://source.lukas-renggli.ch/' , aString! ! !Gofer methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:18'! repositories "Answer the configured monticello repositories." | result | result := OrderedCollection withAll: repositories. packageCacheRepository isNil ifFalse: [ result addFirst: packageCacheRepository ]. ^ result asArray! ! !Gofer methodsFor: 'repositories' stamp: 'lr 1/11/2010 10:34'! repository: aRepository "Add aRepository to the repository configuration. If there is already a repository defined in the global configuration with that URL take this one instead." | repository | repository := MCRepositoryGroup default repositories detect: [ :each | each = aRepository ] ifNone: [ aRepository ]. repositories addLast: repository! ! !Gofer methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:14'! resolved "Answer the resolved references of the receiver." ^ self references collect: [ :each | each resolveWith: self ]! ! !Gofer methodsFor: 'operations' stamp: 'lr 8/20/2009 10:15'! revert "Revert the specified packages to the currently loaded version." ^ self execute: GoferRevert! ! !Gofer methodsFor: 'repositories-places' stamp: 'lr 7/10/2009 16:29'! saltypickle: aString self url: 'http://squeak.saltypickle.com/' , aString! ! !Gofer methodsFor: 'repositories-places' stamp: 'lr 7/10/2009 16:28'! squeakfoundation: aString self url: 'http://source.squeakfoundation.org/' , aString! ! !Gofer methodsFor: 'repositories-places' stamp: 'lr 7/10/2009 16:28'! squeaksource: aString self url: 'http://www.squeaksource.com/' , aString! ! !Gofer methodsFor: 'operations' stamp: 'lr 11/10/2009 10:07'! unload "Unload the specified packages." ^ self execute: GoferUnload! ! !Gofer methodsFor: 'operations' stamp: 'lr 9/18/2009 18:12'! update "Update the specified packages." ^ self execute: GoferUpdate! ! !Gofer methodsFor: 'repositories' stamp: 'lr 12/9/2009 22:17'! url: anUrlString "Add anUrlString as a repository for the following package operations." self url: anUrlString username: String new password: String new! ! !Gofer methodsFor: 'repositories' stamp: 'lr 1/11/2010 22:41'! url: anUrlString username: aUsernameString password: aPasswordString "Add anUrlString as a repository for the following package operations." | repository | repository := (anUrlString beginsWith: 'ftp://') ifTrue: [ (Smalltalk at: #MCFtpRepository ifAbsent: [ self error: anUrlString printString , ' is an unsupported repository type' ]) host: ((anUrlString allButFirst: 6) copyUpTo: $/) directory: ((anUrlString allButFirst: 6) copyAfter: $/) user: aUsernameString password: aPasswordString ] ifFalse: [ MCHttpRepository location: anUrlString user: aUsernameString password: aPasswordString ]. self repository: repository! ! !Gofer methodsFor: 'references' stamp: 'lr 12/13/2009 13:25'! version: aString "Add the version aString to the receiver." references addLast: (GoferVersionReference name: aString)! ! !Gofer methodsFor: 'repositories-places' 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: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferLoad methodsFor: 'private' stamp: 'lr 12/18/2009 12:56'! addResolved: aResolvedReference | version reference | version := aResolvedReference version. (self versions includes: version) ifTrue: [ ^ self ]. self versions addLast: version. version dependencies do: [ :dependency | self addResolved: (GoferResolvedReference name: dependency versionInfo name repository: aResolvedReference repository) ]! ! !GoferLoad methodsFor: 'private' stamp: 'lr 9/3/2009 11:00'! defaultModel ^ MCVersionLoader new! ! !GoferLoad methodsFor: 'running' stamp: 'dkh 10/12/2009 12:56'! execute self model goferHasVersions ifTrue: [ self model load ]. self updateRepositories. self updateCategories! ! !GoferLoad methodsFor: 'initialization' stamp: 'TestRunner 12/13/2009 14:49'! initializeOn: aGofer super initializeOn: aGofer. aGofer resolved do: [ :each | self addResolved: each ] displayingProgress: 'Loading Versions'! ! !GoferLoad methodsFor: 'private' stamp: 'lr 12/18/2009 12:55'! updateCategories "This method makes sure that the categories are ordered in load-order and as specified in the packages." | categories | categories := OrderedCollection new. self 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 12/18/2009 12:55'! updateRepositories "This code makes sure that all packages have a repository assigned, including the dependencies." self versions do: [ :version | gofer repositories do: [ :repository | version workingCopy repositoryGroup addRepository: repository ] ]! ! !GoferLoad methodsFor: 'accessing' stamp: 'lr 12/18/2009 12:55'! versions ^ model goferVersions! ! !GoferOperation class methodsFor: 'instance creation' stamp: 'TestRunner 12/12/2009 11:09'! new self error: 'Gofer operations can only work on Gofer instances.'! ! !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 10/3/2009 11:38'! gofer "Answer the Gofer instance that triggered this operation." ^ gofer! ! !GoferOperation methodsFor: 'initialization' stamp: 'lr 8/19/2009 14:01'! initialize model := self defaultModel! ! !GoferOperation methodsFor: 'initialization' stamp: 'TestRunner 12/12/2009 11:09'! 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 subclass: #GoferSynchronize instanceVariableNames: 'cacheReferences' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! GoferSynchronize subclass: #GoferFetch instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferFetch methodsFor: 'private' stamp: 'lr 11/30/2009 13:46'! defaultModel ^ Set new! ! !GoferFetch methodsFor: 'running' stamp: 'lr 12/13/2009 17:22'! execute self model do: [ :reference | self cacheRepository storeVersion: reference version ] displayingProgress: 'Fetching Versions'! ! !GoferFetch methodsFor: 'initialization' stamp: 'TestRunner 12/13/2009 19:56'! initializeOn: aGofer super initializeOn: aGofer. self gofer references do: [ :reference | self gofer allResolved do: [ :resolved | ((reference matches: resolved) and: [ (cacheReferences includes: resolved) not ]) ifTrue: [ self model add: resolved ] ] ]! ! GoferSynchronize subclass: #GoferPush instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferPush methodsFor: 'private' stamp: 'lr 11/30/2009 13:46'! defaultModel ^ OrderedCollection new! ! !GoferPush methodsFor: 'running' stamp: 'lr 12/13/2009 17:23'! execute self model do: [ :assocation | assocation value storeVersion: assocation key version ] displayingProgress: 'Pushing Versions'! ! !GoferPush methodsFor: 'initialization' stamp: 'TestRunner 12/13/2009 20:08'! initializeOn: aGofer super initializeOn: aGofer. self gofer references do: [ :reference | cacheReferences do: [ :resolved | (reference matches: resolved) ifTrue: [ self gofer repositories do: [ :repository | ((self gofer allResolvedIn: repository) includes: resolved) ifFalse: [ self model add: resolved -> repository ] ] ] ] ]! ! !GoferSynchronize methodsFor: 'accessing' stamp: 'lr 12/12/2009 14:29'! cacheRepository ^ MCCacheRepository default! ! !GoferSynchronize methodsFor: 'initialization' stamp: 'TestRunner 12/13/2009 19:54'! initializeOn: aGofer super initializeOn: aGofer disablePackageCache. MCFileBasedRepository flushAllCaches. cacheReferences := self gofer allResolvedIn: self cacheRepository! ! GoferOperation subclass: #GoferWorking instanceVariableNames: 'workingCopies' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! GoferWorking subclass: #GoferChanges instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferChanges methodsFor: 'private' stamp: 'lr 12/12/2009 12:56'! addReference: aReference super addReference: aReference. self model operations addAll: (self patchsetOf: aReference) operations! ! !GoferChanges methodsFor: 'private' stamp: 'lr 8/19/2009 14:02'! defaultModel ^ MCPatch operations: OrderedCollection new! ! !GoferChanges methodsFor: 'running' stamp: 'lr 12/14/2009 23:50'! execute ^ self model! ! !GoferChanges methodsFor: 'queries' stamp: 'lr 12/12/2009 13:06'! patchsetOf: aReference "Answer the source snapshot of aReference." | source target | source := self sourceSnapshotOf: aReference. target := self targetSnapshotOf: aReference. ^ target patchRelativeToBase: source! ! !GoferChanges methodsFor: 'queries' stamp: 'lr 12/12/2009 13:00'! sourceSnapshotOf: aReference "Answer the source snapshot of aReference." self subclassResponsibility! ! !GoferChanges methodsFor: 'queries' stamp: 'lr 12/12/2009 12:59'! targetSnapshotOf: aReference "Answer the source snapshot of aReference." self subclassResponsibility! ! GoferChanges subclass: #GoferLocalChanges instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! GoferLocalChanges subclass: #GoferBrowseLocalChanges instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferBrowseLocalChanges methodsFor: 'running' stamp: 'lr 12/14/2009 23:50'! execute ^ super execute browse! ! !GoferLocalChanges methodsFor: 'queries' stamp: 'TestRunner 12/13/2009 18:02'! sourceSnapshotOf: aReference | ancestors reference | ancestors := aReference workingCopy ancestry ancestors. ancestors isEmpty ifTrue: [ ^ MCSnapshot new ]. reference := GoferVersionReference name: ancestors first name. ^ (reference resolveWith: self gofer) version snapshot! ! !GoferLocalChanges methodsFor: 'queries' stamp: 'lr 12/12/2009 13:01'! targetSnapshotOf: aReference ^ aReference workingCopy package snapshot! ! GoferChanges subclass: #GoferRemoteChanges instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! GoferRemoteChanges subclass: #GoferBrowseRemoteChanges instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferBrowseRemoteChanges methodsFor: 'running' stamp: 'lr 12/14/2009 23:50'! execute ^ super execute browse! ! !GoferRemoteChanges methodsFor: 'queries' stamp: 'lr 12/12/2009 13:00'! sourceSnapshotOf: aReference ^ aReference workingCopy package snapshot! ! !GoferRemoteChanges methodsFor: 'private' stamp: 'TestRunner 12/13/2009 19:27'! targetSnapshotOf: aReference ^ (aReference resolveWith: self gofer) version snapshot! ! GoferWorking subclass: #GoferCleanup instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferCleanup methodsFor: 'cleaning' stamp: 'lr 10/3/2009 11:37'! cleanup: aWorkingCopy self cleanupCategories: aWorkingCopy. self cleanupProtocols: aWorkingCopy! ! !GoferCleanup methodsFor: 'cleaning' stamp: 'dkh 10/12/2009 12:59'! cleanupCategories: aWorkingCopy aWorkingCopy packageInfo systemCategories do: [ :category | (SystemOrganization goferClassesInCategory: category) isEmpty ifTrue: [ SystemOrganization removeSystemCategory: category ] ]! ! !GoferCleanup methodsFor: 'cleaning' stamp: 'lr 10/3/2009 11:37'! cleanupProtocols: aWorkingCopy aWorkingCopy packageInfo extensionClasses do: [ :class | (aWorkingCopy packageInfo extensionCategoriesForClass: class) do: [ :category | (class organization listAtCategoryNamed: category) isEmpty ifTrue: [ class organization removeCategory: category ] ] ]. aWorkingCopy packageInfo classesAndMetaClasses do: [ :class | (aWorkingCopy packageInfo coreCategoriesForClass: class) do: [ :category | (class organization listAtCategoryNamed: category) isEmpty ifTrue: [ class organization removeCategory: category ] ] ]! ! !GoferCleanup methodsFor: 'running' stamp: 'lr 10/3/2009 11:30'! execute self workingCopies do: [ :each | self cleanup: each ]! ! GoferWorking subclass: #GoferCommit instanceVariableNames: 'message' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferCommit methodsFor: 'running' stamp: 'lr 12/13/2009 18:44'! execute self workingCopies do: [ :each | self execute: each ]! ! !GoferCommit methodsFor: 'running' stamp: 'lr 12/27/2009 17:21'! execute: aWorkingCopy | repositories version | repositories := self gofer repositories reject: [ :repository | (aWorkingCopy changesRelativeToRepository: repository) isEmpty ]. repositories isEmpty ifTrue: [ ^ self ]. version := [ aWorkingCopy newVersion ] on: MCVersionNameAndMessageRequest do: [ :notifcation | self message isNil ifTrue: [ message := notifcation outer last ]. notifcation resume: (Array with: notifcation suggestedName with: self message) ]. self gofer repositories do: [ :repository | repository storeVersion: version ]! ! !GoferCommit methodsFor: 'running' stamp: 'lr 12/13/2009 19:20'! initializeOn: aGofer super initializeOn: aGofer disablePackageCache! ! !GoferCommit methodsFor: 'accessing' stamp: 'lr 10/2/2009 10:12'! message ^ message! ! !GoferCommit methodsFor: 'accessing' stamp: 'lr 10/2/2009 10:12'! message: aString message := aString! ! GoferWorking subclass: #GoferRecompile instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferRecompile methodsFor: 'running' stamp: 'lr 12/13/2009 19:12'! execute self workingCopies do: [ :each | self execute: each ]! ! !GoferRecompile methodsFor: 'running' stamp: 'lr 12/13/2009 19:12'! execute: aWorkingCopy aWorkingCopy packageInfo methods do: [ :each | each actualClass recompile: each methodSymbol ]! ! GoferWorking subclass: #GoferReinitialize instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferReinitialize methodsFor: 'running' stamp: 'lr 12/30/2009 11:14'! execute self workingCopies do: [ :each | self execute: each ]! ! !GoferReinitialize methodsFor: 'running' stamp: 'lr 12/30/2009 11:26'! execute: aWorkingCopy aWorkingCopy packageInfo methods do: [ :each | (each classIsMeta and: [ each selector = #initialize ]) ifTrue: [ each actualClass theNonMetaClass initialize ] ]! ! GoferWorking subclass: #GoferUnload instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferUnload methodsFor: 'private' stamp: 'dkh 12/15/2009 11:35'! defaultModel ^ (Smalltalk at: #MCMultiPackageLoader ifAbsent: [ MCPackageLoader ]) new! ! !GoferUnload methodsFor: 'running' stamp: 'lr 10/3/2009 11:45'! execute self workingCopies do: [ :copy | self unload: copy ]. self model load. self gofer cleanup. self workingCopies do: [ :copy | self unregister: copy ]! ! !GoferUnload methodsFor: 'unloading' stamp: 'lr 10/3/2009 11:46'! unload: aWorkingCopy self unloadClasses: aWorkingCopy. self unloadPackage: aWorkingCopy ! ! !GoferUnload methodsFor: 'unloading' stamp: 'lr 12/30/2009 11:27'! unloadClasses: aWorkingCopy aWorkingCopy packageInfo methods do: [ :each | (each classIsMeta and: [ each selector = #unload ]) ifTrue: [ each actualClass theNonMetaClass 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 10/3/2009 11: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 gofer cleanup! ! 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: 'TestRunner 12/13/2009 18:09'! referenceFor: aReference | ancestors reference | ancestors := aReference workingCopy ancestry ancestors. ancestors isEmpty ifTrue: [ ^ MCSnapshot new ]. ^ GoferVersionReference name: ancestors first name! ! !GoferUpdate methodsFor: 'private' stamp: 'TestRunner 12/13/2009 18:09'! addReference: aReference super addReference: aReference. self model addVersion: ((self referenceFor: aReference) resolveWith: self gofer) version! ! !GoferUpdate methodsFor: 'private' stamp: 'lr 9/18/2009 18:13'! defaultModel ^ MCVersionLoader new! ! !GoferUpdate methodsFor: 'running' stamp: 'dkh 10/12/2009 12:55'! execute self model goferHasVersions ifTrue: [ self model load ]. self gofer cleanup! ! !GoferUpdate methodsFor: 'private' stamp: 'TestRunner 12/13/2009 18:08'! referenceFor: aReference ^ aReference! ! !GoferWorking methodsFor: 'private' stamp: 'lr 12/18/2009 20:56'! addReference: aReference | workingCopy | workingCopy := aReference workingCopy. (self workingCopies includes: workingCopy) ifTrue: [ ^ self ]. self workingCopies addLast: workingCopy. workingCopy requiredPackages do: [ :package | self addReference: (GoferPackageReference name: package name) ]! ! !GoferWorking methodsFor: 'initialization' stamp: 'lr 8/19/2009 13:14'! initialize super initialize. workingCopies := OrderedCollection new! ! !GoferWorking methodsFor: 'initialization' stamp: 'lr 12/13/2009 19:16'! initializeOn: aGofer super initializeOn: aGofer. aGofer references do: [ :each | self addReference: each ]! ! !GoferWorking methodsFor: 'accessing' stamp: 'lr 9/24/2009 16:55'! workingCopies "Answer the working copies to be operated on." ^ workingCopies! ! Object subclass: #GoferReference instanceVariableNames: 'name' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferReference commentStamp: 'lr 1/30/2010 14:38' prior: 0! A GoferReference is an abstract superclass for various kinds of references to Monticello packages and versions.! GoferReference subclass: #GoferPackageReference instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferPackageReference commentStamp: 'lr 12/9/2009 22:47' prior: 0! A GoferPackageReference refers to the latest version of a Monticello package.! GoferPackageReference subclass: #GoferConstraintReference instanceVariableNames: 'constraintBlock' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferConstraintReference commentStamp: 'lr 1/30/2010 14:37' prior: 0! A GoferPackageReference refers to the latest version of a Monticello package satisfying an additional constraint.! !GoferConstraintReference class methodsFor: 'instance creation' stamp: 'lr 12/9/2009 22:44'! name: aString constraint: aBlock ^ self basicNew initializeName: aString constraint: aBlock! ! !GoferConstraintReference methodsFor: 'initialization' stamp: 'TestRunner 12/12/2009 00:18'! initializeName: aString constraint: aBlock self initializeName: aString. constraintBlock := aBlock! ! !GoferConstraintReference methodsFor: 'private' stamp: 'lr 1/21/2010 00:17'! matches: aResolvedReference ^ (super matches: aResolvedReference) and: [ constraintBlock value: aResolvedReference ]! ! !GoferPackageReference methodsFor: 'private' stamp: 'lr 1/21/2010 00:16'! matches: aResolvedReference ^ self packageName = aResolvedReference packageName! ! !GoferPackageReference methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:12'! packageName ^ name! ! !GoferReference class methodsFor: 'instance creation' stamp: 'lr 12/9/2009 22:42'! name: aString ^ self basicNew initializeName: aString! ! !GoferReference class methodsFor: 'instance creation' stamp: 'lr 12/9/2009 22:42'! new self error: 'Use #name: to initialize the receiver.'! ! !GoferReference methodsFor: 'comparing' stamp: 'lr 12/12/2009 13:33'! = aReference ^ self class = aReference class and: [ self name = aReference name ]! ! !GoferReference methodsFor: 'comparing' stamp: 'lr 12/12/2009 13:33'! hash ^ self name hash! ! !GoferReference methodsFor: 'initialization' stamp: 'lr 12/9/2009 22:57'! initializeName: aString name := aString! ! !GoferReference methodsFor: 'private' stamp: 'lr 1/21/2010 00:16'! matches: aResolvedReference "Answer true if the receiver matches aResolvedReference." self subclassResponsibility! ! !GoferReference methodsFor: 'accessing' stamp: 'lr 12/11/2009 22:02'! name "Answer the name of this reference." ^ name! ! !GoferReference methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:09'! packageName "Answer the package name." self subclassResponsibility! ! !GoferReference methodsFor: 'printing' stamp: 'lr 12/11/2009 22:02'! printOn: aStream super printOn: aStream. aStream nextPutAll: ' name: '; print: self name! ! !GoferReference methodsFor: 'querying' stamp: 'lr 12/13/2009 17:20'! resolveAllWith: aGofer "Answer a sorted collection of all resolved references within aGofer." ^ aGofer allResolved select: [ :each | self matches: each ]! ! !GoferReference methodsFor: 'querying' stamp: 'lr 12/13/2009 17:20'! resolveWith: aGofer "Answer a single resolved reference with aGofer configuration, throw an error if the version can't be found.'" | references | references := self resolveAllWith: aGofer. ^ references isEmpty ifTrue: [ self error: 'Unable to resolve ' , self name ] ifFalse: [ references last ]! ! !GoferReference methodsFor: 'querying' stamp: 'lr 12/13/2009 17:10'! workingCopy "Answer a working copy or throw an error if not present." ^ MCWorkingCopy allManagers detect: [ :each | self packageName = each packageName ] ifNone: [ self error: 'Working copy for ' , self name , ' not found' ]! ! GoferReference subclass: #GoferVersionReference instanceVariableNames: 'package author branch versionNumber' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferVersionReference commentStamp: 'lr 12/9/2009 22:50' prior: 0! A GoferVersionReference refers to a specific version of a Monticello package.! GoferVersionReference subclass: #GoferResolvedReference instanceVariableNames: 'repository' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferResolvedReference commentStamp: 'lr 1/30/2010 14:38' prior: 0! A GoferVersionReference refers to a specific version of a Monticello package in a particular repository. This class is the only one that can actually load the version, because it is the only one knowing where to find it.! !GoferResolvedReference class methodsFor: 'instance creation' stamp: 'lr 12/9/2009 22:55'! name: aString repository: aRepository ^ self basicNew initializeName: aString repository: aRepository! ! !GoferResolvedReference methodsFor: 'comparing' stamp: 'lr 3/5/2010 07:19'! <= aResolvedReference "Sort versions according to: 1. package name 2. branch name, list versions without branch last 3. version number 4. author name 5. repository priority" self packageName = aResolvedReference packageName ifFalse: [ ^ self packageName <= aResolvedReference packageName ]. self branch = aResolvedReference branch ifFalse: [ ^ (self branch isEmpty or: [ aResolvedReference branch isEmpty ]) ifTrue: [ self branch size > aResolvedReference branch size ] ifFalse: [ self branch <= aResolvedReference branch ] ]. self versionNumber = aResolvedReference versionNumber ifFalse: [ ^ self versionNumber <= aResolvedReference versionNumber ]. self author = aResolvedReference author ifFalse: [ ^ self author <= aResolvedReference author ]. self repository goferPriority = aResolvedReference repository goferPriority ifFalse: [ ^ self repository goferPriority <= aResolvedReference repository goferPriority ]. ^ true! ! !GoferResolvedReference methodsFor: 'initialization' stamp: 'lr 12/9/2009 22:55'! initializeName: aString repository: aRepository self initializeName: aString. repository := aRepository! ! !GoferResolvedReference methodsFor: 'accessing' stamp: 'lr 12/11/2009 22:33'! repository "Answer the repository of the receiver." ^ repository! ! !GoferResolvedReference methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:22'! version "Answer a Monticello version of the receiver." ^ self repository goferVersionFrom: self! ! !GoferVersionReference methodsFor: 'accessing' stamp: 'lr 12/11/2009 22:22'! author "Answer the author of the receiver." ^ author! ! !GoferVersionReference methodsFor: 'accessing' stamp: 'lr 12/11/2009 22:23'! branch "Answer the branch of the receiver." ^ branch! ! !GoferVersionReference methodsFor: 'initialization' stamp: 'lr 12/11/2009 22:17'! initializeName: aString super initializeName: aString. self parseName: aString! ! !GoferVersionReference methodsFor: 'private' stamp: 'lr 1/21/2010 00:17'! matches: aResolvedReference ^ self name = aResolvedReference name! ! !GoferVersionReference methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:12'! packageName "Answer the package of the receiver." ^ package! ! !GoferVersionReference methodsFor: 'initialization' stamp: 'lr 12/13/2009 17:20'! parseName: aString | basicName | basicName := aString last isDigit ifTrue: [ aString ] ifFalse: [ (aString copyUpToLast: $.) copyUpTo: $( ]. package := basicName copyUpToLast: $-. author := (basicName copyAfterLast: $-) copyUpTo: $.. versionNumber := (basicName copyAfterLast: $-) copyAfter: $.. versionNumber isEmpty ifTrue: [ branch := ''. versionNumber := 0 ] ifFalse: [ (versionNumber allSatisfy: [ :each | each isDigit ]) ifTrue: [ branch := ''. versionNumber := versionNumber asInteger ] ifFalse: [ branch := versionNumber copyUpToLast: $.. versionNumber := (versionNumber copyAfterLast: $.) asInteger ] ]! ! !GoferVersionReference methodsFor: 'accessing' stamp: 'lr 12/13/2009 17:20'! versionNumber "Answer the version of the receiver." ^ versionNumber! ! !MCRepository methodsFor: '*gofer-core-accessing' stamp: 'lr 12/11/2009 22:31'! goferPriority ^ 0! ! !MCRepository methodsFor: '*gofer-core-accessing' stamp: 'lr 12/9/2009 20:50'! goferReferences ^ #()! ! !MCRepository methodsFor: '*gofer-core-accessing' stamp: 'lr 12/12/2009 11:29'! goferVersionFrom: aVersionReference self error: 'Unable to load from ' , self printString! ! !MCDirectoryRepository methodsFor: '*gofer-core-accessing' stamp: 'lr 12/11/2009 22:32'! goferPriority ^ 5! ! !MCFileBasedRepository methodsFor: '*gofer-core-accessing' stamp: 'TestRunner 12/12/2009 11:12'! goferReferences | versionNames | versionNames := [ self allVersionNames ] on: Error do: [ :error | ^ GoferRepositoryError signal: error messageText repository: self ]. ^ versionNames collect: [ :each | GoferResolvedReference name: each repository: self ]! ! !MCFileBasedRepository methodsFor: '*gofer-core-accessing' stamp: 'lr 12/12/2009 11:29'! goferVersionFrom: aVersionReference ^ self loadVersionFromFileNamed: aVersionReference name , '.mcz'! ! !MCVersionLoader methodsFor: '*gofer-core-accessing' stamp: 'lr 12/18/2009 12:43'! goferHasVersions ^ versions isEmpty not! ! !MCVersionLoader methodsFor: '*gofer-core-accessing' stamp: 'lr 12/18/2009 12:43'! goferVersions ^ versions! ! Error subclass: #GoferRepositoryError instanceVariableNames: 'repository' classVariableNames: '' poolDictionaries: '' category: 'Gofer-Core'! !GoferRepositoryError commentStamp: 'lr 1/30/2010 14:39' prior: 0! A GoferRepositoryError is the error thrown when a repository cannot be accessed.! !GoferRepositoryError class methodsFor: 'instance creation' stamp: 'lr 12/9/2009 19:15'! signal: aString repository: aRepository ^ self new repository: aRepository; signal: aString! ! !GoferRepositoryError methodsFor: 'private' stamp: 'lr 12/9/2009 22:32'! isResumable ^ true! ! !GoferRepositoryError methodsFor: 'accessing' stamp: 'lr 12/9/2009 19:14'! repository ^ repository! ! !GoferRepositoryError methodsFor: 'accessing' stamp: 'lr 12/9/2009 19:14'! repository: aRepository repository := aRepository! !