Skip to content

Commit

Permalink
The API of Protocol is, currently, misleading. A protocol has a metho…
Browse files Browse the repository at this point in the history
…d #methods but this one does not return methods but selectors.

In this PR I updated the API to #methodSelectors to be explicit.
  • Loading branch information
jecisc committed Oct 10, 2019
1 parent dbf8f03 commit f6cdfb6
Show file tree
Hide file tree
Showing 8 changed files with 79 additions and 56 deletions.
6 changes: 2 additions & 4 deletions src/Calypso-SystemQueries/ClassDescription.extension.st
Expand Up @@ -7,9 +7,7 @@ ClassDescription >> tagsForAllMethods [
| allProtocols |
allProtocols := self organization protocols reject: [ :each | each name = Protocol unclassified | each isExtensionProtocol ].

^ allProtocols select: [ :protocol |
protocol methods
ifEmpty: [ true ]
ifNotEmpty: [ :methods | methods anySatisfy: [ :method | self selectors includes: method ] ] ]
^ allProtocols
select: [ :protocol | protocol methodSelectors ifEmpty: [ true ] ifNotEmpty: [ :methods | methods anySatisfy: [ :method | self selectors includes: method ] ] ]
thenCollect: #name
]
31 changes: 31 additions & 0 deletions src/Deprecated80/Protocol.extension.st
@@ -0,0 +1,31 @@
Extension { #name : #Protocol }

{ #category : #'*Deprecated80' }
Protocol >> addMethod: aSymbol [
self deprecated: 'Use #addMethodSelector: instead' transformWith: '`@receiver addMethod: `@arg' -> '`@receiver addMethodSelector: `@arg'.
^ self addMethodSelector: aSymbol
]

{ #category : #'*Deprecated80' }
Protocol >> methods [
self deprecated: 'Use #methodSelectors instead.' transformWith: '`@receiver methods' -> '`@receiver methodSelectors'.
^ self methodSelectors
]

{ #category : #'*Deprecated80' }
Protocol >> methods: aCollection [
self deprecated: 'Use #methodSelectors: instead.' transformWith: '`@receiver methods: `@arg' -> '`@receiver methodSelectors: `@arg'.
^ self methodSelectors: aCollection
]

{ #category : #'*Deprecated80' }
Protocol >> removeAllMethods [
self deprecated: 'Use #removeAllMethodSelectors instead' transformWith: '`@receiver removeAllMethods' -> '`@receiver removeAllMethodSelectors'.
^ self removeAllMethodSelectors
]

{ #category : #'*Deprecated80' }
Protocol >> removeMethod: aSymbol [
self deprecated: 'Use #removeMethodSelector: instead' transformWith: '`@receiver removeMethod: `@arg' -> '`@receiver removeMethodSelector: `@arg'.
^ self removeMethodSelector: aSymbol
]
7 changes: 7 additions & 0 deletions src/Deprecated80/ProtocolOrganizer.extension.st
@@ -0,0 +1,7 @@
Extension { #name : #ProtocolOrganizer }

{ #category : #'*Deprecated80' }
ProtocolOrganizer >> allMethods [
self deprecated: 'Use #allMethodSelectors instead' transformWith: '`@receiver allMethods' -> '`@receiver allMethodSelectors'.
^ self allMethodSelectors
]
10 changes: 5 additions & 5 deletions src/Kernel-Tests/ClassOrganizationTest.class.st
Expand Up @@ -62,17 +62,17 @@ ClassOrganizationTest >> testListAtCategoryNamed [
self assertEmpty: methods.

methods := self organization listAtCategoryNamed: 'one'.
self assert: methods size = 1.
self assert: methods first = #one
self assert: methods size equals: 1.
self assert: methods first equals: #one
]

{ #category : #tests }
ClassOrganizationTest >> testRemoveCategory [
self assert: self organization categories size = 2.
self assert: self organization categories size equals: 2.
self should: [ self organization removeCategory: 'one' ] raise: Error.
self organization removeCategory: 'empty'.
self assert: self organization categories size = 1.
self assert: self organization categories first = 'one'
self assert: self organization categories size equals: 1.
self assert: self organization categories first equals: 'one'
]

{ #category : #tests }
Expand Down
1 change: 1 addition & 0 deletions src/Kernel-Tests/MagnitudeTest.class.st
Expand Up @@ -25,6 +25,7 @@ MagnitudeTest >> testBeBetweenAnd [
self assert: (30 beBetween: 20 and: 5) equals: 20.
]

{ #category : #'as yet unclassified' }
MagnitudeTest >> testBetweenAnd [
self assert: (3 between: 0 and: 5).
self assert: (5.0 between: 5.0 and: 5.0).
Expand Down
8 changes: 3 additions & 5 deletions src/Kernel/AllProtocol.class.st
Expand Up @@ -40,15 +40,13 @@ AllProtocol >> isVirtualProtocol [
]

{ #category : #accessing }
AllProtocol >> methods [

^ self protocolOrganizer allMethods
AllProtocol >> methodSelectors [
^ self protocolOrganizer allMethodSelectors
]

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

^ (self methods isEmpty and: [ protocolOrganizer protocols isEmpty])
^ (self isEmpty and: [ protocolOrganizer protocols isEmpty ])
ifTrue: [ self class nullCategory ]
ifFalse: [ name ]
]
Expand Down
43 changes: 18 additions & 25 deletions src/Kernel/Protocol.class.st
Expand Up @@ -6,8 +6,8 @@ Class {
#name : #Protocol,
#superclass : #Object,
#instVars : [
'methods',
'name'
'name',
'methodSelectors'
],
#category : #'Kernel-Protocols'
}
Expand Down Expand Up @@ -58,13 +58,12 @@ Protocol class >> unclassified [

{ #category : #accessing }
Protocol >> addAllMethodsFrom: aProtocol [

aProtocol methods do: [ :each | self addMethod: each ].
aProtocol methodSelectors do: [ :each | self addMethodSelector: each ]
]

{ #category : #accessing }
Protocol >> addMethod: aSymbol [
^ methods add: aSymbol
Protocol >> addMethodSelector: aSymbol [
^ methodSelectors add: aSymbol
]

{ #category : #private }
Expand All @@ -80,22 +79,21 @@ Protocol >> canBeRenamed [
{ #category : #testing }
Protocol >> includesSelector: selector [

^ methods includes: selector
^ methodSelectors includes: selector
]

{ #category : #initialization }
Protocol >> initialize [

super initialize.

methods := IdentitySet new.
methodSelectors := IdentitySet new.
name := self class defaultName.
]

{ #category : #testing }
Protocol >> isEmpty [

^ self methods isEmpty
^ self methodSelectors isEmpty
]

{ #category : #testing }
Expand All @@ -110,15 +108,13 @@ Protocol >> isVirtualProtocol [
]

{ #category : #accessing }
Protocol >> methods [

^ methods
Protocol >> methodSelectors [
^ methodSelectors
]

{ #category : #accessing }
Protocol >> methods: anObject [

methods := anObject
Protocol >> methodSelectors: anObject [
methodSelectors := anObject
]

{ #category : #accessing }
Expand All @@ -134,26 +130,23 @@ Protocol >> name: anObject [

{ #category : #printing }
Protocol >> printOn: aStream [

aStream
aStream
nextPutAll: self class name;
nextPutAll: ' (';
nextPutAll: self name;
nextPutAll: ') - ';
print: self methods size;
print: self methodSelectors size;
nextPutAll: ' selector(s)'
]

{ #category : #accessing }
Protocol >> removeAllMethods [

^ methods removeAll.
Protocol >> removeAllMethodSelectors [
^ methodSelectors removeAll
]

{ #category : #accessing }
Protocol >> removeMethod: aSymbol [

^ methods remove: aSymbol
Protocol >> removeMethodSelector: aSymbol [
^ methodSelectors remove: aSymbol
]

{ #category : #accessing }
Expand Down
29 changes: 12 additions & 17 deletions src/Kernel/ProtocolOrganizer.class.st
Expand Up @@ -33,9 +33,8 @@ ProtocolOrganizer >> addProtocolNamed: aName [
]

{ #category : #accessing }
ProtocolOrganizer >> allMethods [

^ self protocols flatCollect: [:p | p methods ].
ProtocolOrganizer >> allMethodSelectors [
^ self protocols flatCollect: [ :p | p methodSelectors ]
]

{ #category : #accessing }
Expand All @@ -57,19 +56,16 @@ ProtocolOrganizer >> allProtocolsNames [
]

{ #category : #'protocol - adding' }
ProtocolOrganizer >> classify: aSymbol inProtocolNamed: aProtocolName [
ProtocolOrganizer >> classify: aSymbol inProtocolNamed: aProtocolName [
| name protocol |

name := aProtocolName.
name = allProtocol name
ifTrue: [ name := Protocol unclassified ].

name = allProtocol name ifTrue: [ name := Protocol unclassified ].

"maybe here we should check if this method already belong to another protocol"
(self protocolsOfSelector: aSymbol) do: [:p | p removeMethod: aSymbol ].
(self protocolsOfSelector: aSymbol) do: [ :p | p removeMethodSelector: aSymbol ].
protocol := self getProtocolNamed: name ifNone: [ self addProtocolNamed: name ].

protocol addMethod: aSymbol


protocol addMethodSelector: aSymbol
]

{ #category : #private }
Expand Down Expand Up @@ -119,10 +115,9 @@ ProtocolOrganizer >> initialize [

{ #category : #'backward compatibility' }
ProtocolOrganizer >> methodsInProtocolNamed: aName [
aName = AllProtocol defaultName
ifTrue: [ ^ self allMethods ].
aName = AllProtocol defaultName ifTrue: [ ^ self allMethodSelectors ].

^ (self protocolNamed: aName) methods
^ (self protocolNamed: aName) methodSelectors
]

{ #category : #private }
Expand All @@ -133,7 +128,7 @@ ProtocolOrganizer >> moveMethodsFrom: fromProtocolNamed to: toProtocolNamed [
toProtocol := self protocolNamed: toProtocolNamed.

toProtocol addAllMethodsFrom: fromProtocol.
fromProtocol removeAllMethods.
fromProtocol removeAllMethodSelectors.

^ toProtocol.
]
Expand Down Expand Up @@ -190,7 +185,7 @@ ProtocolOrganizer >> removeEmptyProtocols [
{ #category : #accessing }
ProtocolOrganizer >> removeMethod: aSymbol [

(self protocolsOfSelector: aSymbol) do: [ :p | p removeMethod: aSymbol ]
(self protocolsOfSelector: aSymbol) do: [ :p | p removeMethodSelector: aSymbol ]
]

{ #category : #'protocol - removing' }
Expand Down

0 comments on commit f6cdfb6

Please sign in to comment.