Skip to content

Commit

Permalink
Cleanup Gofer packages
Browse files Browse the repository at this point in the history
Fix #9694
  • Loading branch information
astares committed Jul 23, 2021
1 parent 94343c6 commit 3fa33dc
Show file tree
Hide file tree
Showing 30 changed files with 216 additions and 42 deletions.
30 changes: 15 additions & 15 deletions src/Gofer-Core/Gofer.class.st
Expand Up @@ -81,7 +81,7 @@ Class {

{ #category : #private }
Gofer class >> gofer [
"Create a Gofer instance of Gofer."
"Create a Gofer instance"

^ self new
renggli: 'gofer';
Expand Down Expand Up @@ -127,7 +127,7 @@ Gofer >> basicReferencesIn: aRepository [
do: errorBlock
]

{ #category : #'repositories-places' }
{ #category : #'repositories - places' }
Gofer >> blueplane: aString [
self url: 'http://squeaksource.blueplane.jp/' , aString
]
Expand Down Expand Up @@ -186,28 +186,28 @@ Gofer >> directory: aDirectoryOrString [
self repository: repository
]

{ #category : #'repositories-options' }
{ #category : #'repositories - options' }
Gofer >> disablePackageCache [
"Disable the use of the package-cache repository."

packageCacheRepository := nil
]

{ #category : #'repositories-options' }
{ #category : #'repositories - options' }
Gofer >> disableRepositoryErrors [
"Silently swallow all repository errors."

errorBlock := [ :error | error resume: #() ]
]

{ #category : #'repositories-options' }
{ #category : #'repositories - options' }
Gofer >> enablePackageCache [
"Enable the use of the package-cache repository."

packageCacheRepository := MCCacheRepository uniqueInstance.
]

{ #category : #'repositories-options' }
{ #category : #'repositories - options' }
Gofer >> enableRepositoryErrors [
"Throw an exception when repositories are not available."

Expand All @@ -234,12 +234,12 @@ Gofer >> fetch [
^ self execute: GoferFetch
]

{ #category : #'repositories-places' }
{ #category : #'repositories - places' }
Gofer >> gemsource: aString [
self url: 'http://seaside.gemstone.com/ss/' , aString
]

{ #category : #'repositories-places' }
{ #category : #'repositories - places' }
Gofer >> impara: aString [
self url: 'http://source.impara.de/' , aString
]
Expand Down Expand Up @@ -361,7 +361,7 @@ Gofer >> remoteChanges [
^ self execute: GoferRemoteChanges
]

{ #category : #'repositories-places' }
{ #category : #'repositories - places' }
Gofer >> renggli: aString [
self url: 'http://source.lukas-renggli.ch/' , aString
]
Expand All @@ -370,7 +370,7 @@ Gofer >> renggli: aString [
Gofer >> repositories [
"Answer the configured monticello repositories."

| result |
| result |
result := OrderedCollection withAll: repositories.
packageCacheRepository ifNotNil: [ result addFirst: packageCacheRepository ].
^ result asArray
Expand Down Expand Up @@ -401,22 +401,22 @@ Gofer >> revert [
^ self execute: GoferRevert
]

{ #category : #'repositories-places' }
{ #category : #'repositories - places' }
Gofer >> smalltalkhubUser: aUserName project: aProjectName [
self repository: (MCSmalltalkhubRepository owner: aUserName project: aProjectName)
]

{ #category : #'repositories-places' }
{ #category : #'repositories - places' }
Gofer >> squeakfoundation: aString [
self url: 'http://source.squeakfoundation.org/' , aString
]

{ #category : #'repositories-places' }
{ #category : #'repositories - places' }
Gofer >> squeaksource3: aProjectName [
self repository: (MCGemstoneRepository location: 'http://ss3.gemtalksystems.com/ss/' , aProjectName)
]

{ #category : #'repositories-places' }
{ #category : #'repositories - places' }
Gofer >> squeaksource: aProjectName [
self repository: (MCSqueaksourceRepository location: 'http://www.squeaksource.com/' , aProjectName)
]
Expand Down Expand Up @@ -462,7 +462,7 @@ Gofer >> version: aString [
references addLast: (GoferVersionReference name: aString)
]

{ #category : #'repositories-places' }
{ #category : #'repositories - places' }
Gofer >> wiresong: aString [
self url: 'http://source.wiresong.ca/' , aString
]
8 changes: 8 additions & 0 deletions src/Gofer-Core/GoferChanges.class.st
Expand Up @@ -7,8 +7,15 @@ Class {
#category : #'Gofer-Core-Operations'
}

{ #category : #testing }
GoferChanges class >> isAbstract [

^ self == GoferChanges
]

{ #category : #private }
GoferChanges >> addReference: aReference [

super addReference: aReference.
self model operations
addAll: (self patchsetOf: aReference) operations
Expand All @@ -21,6 +28,7 @@ GoferChanges >> defaultModel [

{ #category : #running }
GoferChanges >> execute [

^ self model
]

Expand Down
10 changes: 8 additions & 2 deletions src/Gofer-Core/GoferCleanup.class.st
Expand Up @@ -9,23 +9,28 @@ Class {

{ #category : #cleaning }
GoferCleanup >> cleanup: aWorkingCopy [
self cleanupCategories: aWorkingCopy.
self cleanupProtocols: aWorkingCopy

self
cleanupCategories: aWorkingCopy;
cleanupProtocols: aWorkingCopy
]

{ #category : #cleaning }
GoferCleanup >> cleanupCategories: aWorkingCopy [

aWorkingCopy packageSet systemCategories do: [ :category |
(Smalltalk organization classesInCategory: category) isEmpty
ifTrue: [ Smalltalk organization removeSystemCategory: category ] ]
]

{ #category : #cleaning }
GoferCleanup >> cleanupProtocols: aWorkingCopy [

aWorkingCopy packageSet extendedClasses do: [ :class |
(aWorkingCopy packageSet extensionCategoriesForClass: class) do: [ :category |
(class organization listAtCategoryNamed: category) isEmpty
ifTrue: [ class organization removeCategory: category ] ] ].

aWorkingCopy packageSet classesAndMetaClasses do: [ :class |
(aWorkingCopy packageSet coreCategoriesForClass: class) do: [ :category |
(class organization listAtCategoryNamed: category) isEmpty
Expand All @@ -34,6 +39,7 @@ GoferCleanup >> cleanupProtocols: aWorkingCopy [

{ #category : #running }
GoferCleanup >> execute [

self workingCopies
do: [ :each | self cleanup: each ]
]
5 changes: 4 additions & 1 deletion src/Gofer-Core/GoferCommit.class.st
Expand Up @@ -12,12 +12,14 @@ Class {

{ #category : #running }
GoferCommit >> execute [

self workingCopies
do: [ :each | self execute: each ]
]

{ #category : #running }
GoferCommit >> execute: aWorkingCopy [

| repositories version |
repositories := self gofer repositories
reject: [ :repository | (aWorkingCopy changesRelativeToRepository: repository) isEmpty ].
Expand All @@ -32,8 +34,9 @@ GoferCommit >> execute: aWorkingCopy [
do: [ :repository | repository storeVersion: version ]
]

{ #category : #running }
{ #category : #initialization }
GoferCommit >> initializeOn: aGofer [

super initializeOn: aGofer disablePackageCache
]

Expand Down
6 changes: 6 additions & 0 deletions src/Gofer-Core/GoferConfigurationReference.class.st
Expand Up @@ -9,30 +9,36 @@ Class {

{ #category : #accessing }
GoferConfigurationReference >> configurationClass [

^ Smalltalk globals at: self configurationName asSymbol
]

{ #category : #accessing }
GoferConfigurationReference >> configurationName [

^ 'ConfigurationOf', name
]

{ #category : #testing }
GoferConfigurationReference >> isConfigurationReference [

^ true
]

{ #category : #accessing }
GoferConfigurationReference >> name [

^ self configurationName
]

{ #category : #accessing }
GoferConfigurationReference >> packageName [

^ self configurationName
]

{ #category : #accessing }
GoferConfigurationReference >> project [

^ self configurationClass project
]
10 changes: 8 additions & 2 deletions src/Gofer-Core/GoferConstraintReference.class.st
Expand Up @@ -12,16 +12,22 @@ Class {

{ #category : #'instance creation' }
GoferConstraintReference class >> name: aString constraint: aBlock [
^ self basicNew initializeName: aString constraint: aBlock

^ self basicNew
initializeName: aString constraint: aBlock;
yourself
]

{ #category : #initialization }
GoferConstraintReference >> initializeName: aString constraint: aBlock [

self initializeName: aString.
constraintBlock := aBlock
]

{ #category : #private }
GoferConstraintReference >> matches: aResolvedReference [
^ (super matches: aResolvedReference) and: [ constraintBlock value: aResolvedReference ]

^ (super matches: aResolvedReference) and: [
constraintBlock value: aResolvedReference ]
]
2 changes: 2 additions & 0 deletions src/Gofer-Core/GoferLocalChanges.class.st
Expand Up @@ -9,6 +9,7 @@ Class {

{ #category : #queries }
GoferLocalChanges >> sourceSnapshotOf: aReference [

| ancestors reference |
ancestors := aReference workingCopy ancestry ancestors.
ancestors isEmpty ifTrue: [ ^ MCSnapshot new ].
Expand All @@ -18,5 +19,6 @@ GoferLocalChanges >> sourceSnapshotOf: aReference [

{ #category : #queries }
GoferLocalChanges >> targetSnapshotOf: aReference [

^ aReference workingCopy package snapshot
]
2 changes: 2 additions & 0 deletions src/Gofer-Core/GoferMerge.class.st
Expand Up @@ -9,11 +9,13 @@ Class {

{ #category : #private }
GoferMerge >> defaultModel [

^ MCVersionMerger new
]

{ #category : #running }
GoferMerge >> execute [

[ self model merge ]
on: MCMergeResolutionRequest
do: [ :request | request autoMerge ].
Expand Down
6 changes: 6 additions & 0 deletions src/Gofer-Core/GoferOperation.class.st
Expand Up @@ -11,6 +11,12 @@ Class {
#category : #'Gofer-Core-Operations'
}

{ #category : #testing }
GoferOperation class >> isAbstract [

^ self == GoferOperation
]

{ #category : #'instance creation' }
GoferOperation class >> new [
self error: 'Gofer operations can only work on Gofer instances.'
Expand Down
2 changes: 2 additions & 0 deletions src/Gofer-Core/GoferPackageReference.class.st
Expand Up @@ -9,10 +9,12 @@ Class {

{ #category : #private }
GoferPackageReference >> matches: aResolvedReference [

^ self packageName = aResolvedReference packageName
]

{ #category : #accessing }
GoferPackageReference >> packageName [

^ name
]
13 changes: 8 additions & 5 deletions src/Gofer-Core/GoferPush.class.st
Expand Up @@ -9,23 +9,26 @@ Class {

{ #category : #private }
GoferPush >> defaultModel [

^ OrderedCollection new
]

{ #category : #running }
GoferPush >> execute [

self model
do: [ :assocation | assocation value storeVersion: assocation key version ]
displayingProgress: 'Pushing Versions'
]

{ #category : #initialization }
GoferPush >> 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)
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 ] ] ] ] ]
]
2 changes: 2 additions & 0 deletions src/Gofer-Core/GoferRecompile.class.st
Expand Up @@ -9,12 +9,14 @@ Class {

{ #category : #running }
GoferRecompile >> execute [

self workingCopies
do: [ :each | self execute: each ]
]

{ #category : #running }
GoferRecompile >> execute: aWorkingCopy [

aWorkingCopy packageSet methods
do: [ :each | each methodClass recompile: each selector ]
]

0 comments on commit 3fa33dc

Please sign in to comment.