Skip to content

Commit

Permalink
add asAccessor
Browse files Browse the repository at this point in the history
  • Loading branch information
pavel-krivanek committed May 5, 2024
1 parent 7edd8e7 commit 527b88d
Show file tree
Hide file tree
Showing 2 changed files with 28 additions and 0 deletions.
11 changes: 11 additions & 0 deletions src/Collections-Strings-Tests/SymbolTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -285,6 +285,17 @@ SymbolTest >> subCollectionNotIn [
^ collectionNotIncluded
]

{ #category : 'tests' }
SymbolTest >> testAsAccessor [
self assert: #x: asAccessor equals: #x.
"return receiver if it is already a mutator"
self assert: #x asAccessor equals: #x.
self should: [ self assert: #x:: asAccessor ] raise: Error.
self should: [ self assert: #keyword:selector: asAccessor ] raise: Error.
self should: [ self assert: #+ asAccessor ] raise: Error.
self should: [ self assert: #'' asAccessor ] raise: Error.
]

{ #category : 'tests' }
SymbolTest >> testAsMutator [
self assert: #x asMutator equals: #x:.
Expand Down
17 changes: 17 additions & 0 deletions src/Collections-Strings/Symbol.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -316,6 +316,23 @@ Symbol >> = aSymbol [
^ super = aSymbol
]

{ #category : 'converting' }
Symbol >> asAccessor [
"Return a accessor (getter) message from a setter message.
Return self if it is already a getter."

"#name asAccessor >>> #name"
"#name: asAccessor >>> #name"

(((self count: [ :char | char = $: ]) > 1)
or: [ self isEmpty
or: [ self isBinary ]]) ifTrue: [
self error: 'This symbol cannot be converted to an accessor' ].

self endsWithAColon ifFalse:[ ^ self ].
^ (self withoutSuffix: ':') asSymbol
]

{ #category : 'converting' }
Symbol >> asMutator [
"Return a setter message from a getter message.
Expand Down

0 comments on commit 527b88d

Please sign in to comment.