Skip to content

Commit

Permalink
Merge pull request #14678 from jecisc/packages/rely-less-on-categorie…
Browse files Browse the repository at this point in the history
…s-in-organization-definition

RPackage: Rely less on categories in MCOrganizationDefinition
  • Loading branch information
MarcusDenker committed Sep 18, 2023
2 parents c2b8c02 + 19f7b03 commit 5f21d49
Show file tree
Hide file tree
Showing 152 changed files with 2,396 additions and 2,181 deletions.
2 changes: 1 addition & 1 deletion src/Monticello-Tests/MCStWriterTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ MCMethodDeclaration className: #MCMockClassD selector: #one category: #''''as ye

{ #category : 'data' }
MCStWriterTest >> expectedOrganizationDefinition [
^ 'SystemOrganization addCategory: #MonticelloMocks!
^ 'self packageOrganizer ensurePackage: #MonticelloMocks withTags: #()!
'
]

Expand Down
4 changes: 2 additions & 2 deletions src/Monticello/Behavior.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #Behavior }
Extension { #name : 'Behavior' }

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
Behavior >> mcType [
"Answer the symbol that Monticello uses internally to encode layouts"
^self classLayout class mcTypeSymbol
Expand Down
4 changes: 2 additions & 2 deletions src/Monticello/ByteLayout.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #ByteLayout }
Extension { #name : 'ByteLayout' }

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
ByteLayout class >> mcTypeSymbol [
^ #bytes
]
4 changes: 2 additions & 2 deletions src/Monticello/ChangeRecord.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #ChangeRecord }
Extension { #name : 'ChangeRecord' }

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
ChangeRecord >> asMCMethodDefinition [
"Creates a MCMethodDefinition from the receiver when this was created for a method (type=#method)"

Expand Down
6 changes: 3 additions & 3 deletions src/Monticello/Class.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #Class }
Extension { #name : 'Class' }

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
Class >> asClassDefinition [
"we use a very ugly hack to encode complex slots as string with MC... later MC should model Slots directly"

Expand Down Expand Up @@ -42,7 +42,7 @@ Class >> asClassDefinition [
^ definition
]

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
Class >> classDefinitions [
^ { self asClassDefinition }
]
8 changes: 4 additions & 4 deletions src/Monticello/CompiledMethod.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #CompiledMethod }
Extension { #name : 'CompiledMethod' }

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
CompiledMethod >> asMCMethodDefinition [
"Creates a MCMethodDefinition from the receiver"
| cached |
Expand All @@ -19,7 +19,7 @@ CompiledMethod >> asMCMethodDefinition [
^ cached
]

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
CompiledMethod >> basicAsMCMethodDefinition [

"Creates a MCMethodDefinition from the receiver"
Expand All @@ -33,7 +33,7 @@ CompiledMethod >> basicAsMCMethodDefinition [
source: self sourceCode
]

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
CompiledMethod >> sameAsMCDefinition: anMCMethodDefinition [

^ anMCMethodDefinition selector = self selector and: [
Expand Down
4 changes: 2 additions & 2 deletions src/Monticello/CompiledMethodLayout.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #CompiledMethodLayout }
Extension { #name : 'CompiledMethodLayout' }

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
CompiledMethodLayout class >> mcTypeSymbol [
^ #compiledMethod
]
4 changes: 2 additions & 2 deletions src/Monticello/EphemeronLayout.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #EphemeronLayout }
Extension { #name : 'EphemeronLayout' }

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
EphemeronLayout class >> mcTypeSymbol [
^ #ephemeron
]
4 changes: 2 additions & 2 deletions src/Monticello/FixedLayout.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #FixedLayout }
Extension { #name : 'FixedLayout' }

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
FixedLayout class >> mcTypeSymbol [
^ #normal
]
4 changes: 2 additions & 2 deletions src/Monticello/HashedCollection.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #HashedCollection }
Extension { #name : 'HashedCollection' }

{ #category : #'*Monticello-Storing' }
{ #category : '*Monticello-Storing' }
HashedCollection >> comeFullyUpOnReload: smartRefStream [
"Symbols have new hashes in this image."

Expand Down
4 changes: 2 additions & 2 deletions src/Monticello/ImmediateLayout.extension.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Extension { #name : #ImmediateLayout }
Extension { #name : 'ImmediateLayout' }

{ #category : #'*Monticello' }
{ #category : '*Monticello' }
ImmediateLayout class >> mcTypeSymbol [
^ #immediate
]
32 changes: 17 additions & 15 deletions src/Monticello/MCAddition.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -2,70 +2,72 @@
A MCAddition represents the operation to add an entity to a snapshot.
"
Class {
#name : #MCAddition,
#superclass : #MCPatchOperation,
#name : 'MCAddition',
#superclass : 'MCPatchOperation',
#instVars : [
'definition'
],
#category : #'Monticello-Patching'
#category : 'Monticello-Patching',
#package : 'Monticello',
#tag : 'Patching'
}

{ #category : #'instance creation' }
{ #category : 'instance creation' }
MCAddition class >> of: aDefinition [
^ self new intializeWithDefinition: aDefinition
]

{ #category : #accessing }
{ #category : 'accessing' }
MCAddition >> baseDefinition [
^ nil
]

{ #category : #accessing }
{ #category : 'accessing' }
MCAddition >> basicApplyTo: anObject [
anObject addDefinition: definition
]

{ #category : #accessing }
{ #category : 'accessing' }
MCAddition >> definition [
^ definition
]

{ #category : #accessing }
{ #category : 'accessing' }
MCAddition >> fromSource [
^ ''
]

{ #category : #initializing }
{ #category : 'initializing' }
MCAddition >> intializeWithDefinition: aDefinition [
definition := aDefinition
]

{ #category : #accessing }
{ #category : 'accessing' }
MCAddition >> inverse [
^ MCRemoval of: definition
]

{ #category : #testing }
{ #category : 'testing' }
MCAddition >> isAddition [
^ true
]

{ #category : #testing }
{ #category : 'testing' }
MCAddition >> isClassPatch [
^definition isClassDefinition
]

{ #category : #accessing }
{ #category : 'accessing' }
MCAddition >> targetClass [
^definition actualClass
]

{ #category : #accessing }
{ #category : 'accessing' }
MCAddition >> targetDefinition [
^ definition
]

{ #category : #accessing }
{ #category : 'accessing' }
MCAddition >> toSource [
^ definition diffSource
]
44 changes: 23 additions & 21 deletions src/Monticello/MCAncestry.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -2,62 +2,64 @@
Abstract superclass of records of ancestry.
"
Class {
#name : #MCAncestry,
#superclass : #Object,
#name : 'MCAncestry',
#superclass : 'Object',
#instVars : [
'ancestors',
'stepChildren'
],
#category : #'Monticello-Versioning'
#category : 'Monticello-Versioning',
#package : 'Monticello',
#tag : 'Versioning'
}

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> allAncestorsDo: aBlock [
self ancestors do:
[:ea |
aBlock value: ea.
ea allAncestorsDo: aBlock]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> allAncestorsOnPathTo: aVersionInfo [
^ MCFilteredVersionSorter new
target: aVersionInfo;
addAllVersionInfos: self ancestors;
sortedVersionInfos
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> ancestorString [
^ String streamContents:
[:s | self ancestors do: [:ea | s nextPutAll: ea name] separatedBy: [s nextPutAll: ', ']]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> ancestorStringWithout: packageName [
^ String streamContents:
[:s | self ancestors do: [:ea | s nextPutAll: (ea nameWithout: packageName)] separatedBy: [s nextPutAll: ', ']]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> ancestors [
^ ancestors ifNil: [#()]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> ancestorsDoWhileTrue: aBlock [
self ancestors do:
[:ea |
(aBlock value: ea) ifTrue:
[ea ancestorsDoWhileTrue: aBlock]]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> breadthFirstAncestors [
^ Array streamContents: [:s | self breadthFirstAncestorsDo: [:ea | s nextPut: ea]]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> breadthFirstAncestorsDo: aBlock [
| seen todo next |
seen := Set with: self.
Expand All @@ -72,14 +74,14 @@ MCAncestry >> breadthFirstAncestorsDo: aBlock [
todo add: ea]]]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> commonAncestorWith: aNode [
| commonAncestors |
commonAncestors := self commonAncestorsWith: aNode.
^ commonAncestors at: 1 ifAbsent: [nil]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> commonAncestorsWith: aVersionInfo [

| sharedAncestors mergedOrder sorter |
Expand All @@ -91,14 +93,14 @@ MCAncestry >> commonAncestorsWith: aVersionInfo [
^ mergedOrder select: [:ea | sharedAncestors includes: ea]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> hasAncestor: aVersionInfo [
^ self
hasAncestor: aVersionInfo
alreadySeen: OrderedCollection new
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> hasAncestor: aVersionInfo alreadySeen: aList [
(aList includes: self) ifTrue: [^ false].
aList add: self.
Expand All @@ -107,32 +109,32 @@ MCAncestry >> hasAncestor: aVersionInfo alreadySeen: aList [

]

{ #category : #initialization }
{ #category : 'initialization' }
MCAncestry >> initialize [
super initialize.
ancestors := #().
stepChildren := #()
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> isRelatedTo: aVersionInfo [
^ aVersionInfo timeStamp < self timeStamp
ifTrue: [self hasAncestor: aVersionInfo]
ifFalse: [aVersionInfo hasAncestor: self]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> stepChildren [
^ stepChildren ifNil: [#()]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> stepChildrenString [
^ String streamContents:
[:s | self stepChildren do: [:ea | s nextPutAll: ea name] separatedBy: [s nextPutAll: ', ']]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> topologicalAncestors [

^ Array streamContents:
Expand All @@ -144,7 +146,7 @@ MCAncestry >> topologicalAncestors [
f isEmpty] whileFalse]
]

{ #category : #ancestry }
{ #category : 'ancestry' }
MCAncestry >> withBreadthFirstAncestors [
^ (Array with: self), self breadthFirstAncestors
]
Loading

0 comments on commit 5f21d49

Please sign in to comment.