Skip to content

Commit

Permalink
Merge pull request #6232 from jecisc/simplify-ifNil-conditions
Browse files Browse the repository at this point in the history
simplify-ifNil-conditions
  • Loading branch information
MarcusDenker committed Apr 25, 2020
2 parents 079b022 + 4362b2c commit 4b3893e
Show file tree
Hide file tree
Showing 38 changed files with 118 additions and 244 deletions.
5 changes: 1 addition & 4 deletions src/Athens-Morphic/Morph.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,7 @@ Extension { #name : #Morph }

{ #category : #'*Athens-Morphic' }
Morph >> athensSurface [

^ owner
ifNil: [ nil ]
ifNotNil: [ owner athensSurface ]
^ owner ifNotNil: [ owner athensSurface ]
]

{ #category : #'*Athens-Morphic' }
Expand Down
16 changes: 9 additions & 7 deletions src/Collections-Unordered/KeyedTree.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -121,13 +121,15 @@ KeyedTree >> postCopy [
original and the copy.
Copy any subtrees too!"

array := array collect: [:assoc |
assoc ifNil: [nil]
ifNotNil: [Association
key: assoc key
value: ((assoc value isKindOf: KeyedTree)
ifTrue: [assoc value copy]
ifFalse: [assoc value])]]
array := array
collect: [ :assoc |
assoc
ifNotNil: [ Association
key: assoc key
value:
((assoc value isKindOf: KeyedTree)
ifTrue: [ assoc value copy ]
ifFalse: [ assoc value ]) ] ]
]

{ #category : #printing }
Expand Down
13 changes: 6 additions & 7 deletions src/Collections-Weak/WeakKeyDictionary.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -242,13 +242,12 @@ WeakKeyDictionary >> postCopy [
"Must copy the associations, or later store will affect both the
original and the copy"

array := array collect: [:assoc |
assoc
ifNil: [nil]
ifNotNil: [
assoc expired
ifTrue: [ WeakKeyAssociation expired]
ifFalse: [WeakKeyAssociation key: assoc key value: assoc value]]]
array := array
collect: [ :assoc |
assoc
ifNotNil: [ assoc expired
ifTrue: [ WeakKeyAssociation expired ]
ifFalse: [ WeakKeyAssociation key: assoc key value: assoc value ] ] ]
]

{ #category : #private }
Expand Down
8 changes: 4 additions & 4 deletions src/DeprecatedFileStream/FileStream.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -239,10 +239,10 @@ FileStream class >> convertCRtoLF: fileName [

{ #category : #'instance creation' }
FileStream class >> detectFile: aBlock do: anotherBlock [

^aBlock value
ifNil: [nil]
ifNotNil: [:file| [anotherBlock value: file] ensure: [file close]]
^ aBlock value
ifNotNil: [ :file |
[ anotherBlock value: file ]
ensure: [ file close ] ]
]

{ #category : #'file reader services' }
Expand Down
10 changes: 4 additions & 6 deletions src/DeprecatedFileStream/RWBinaryOrTextStream.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -55,13 +55,11 @@ RWBinaryOrTextStream >> isBinary [

{ #category : #accessing }
RWBinaryOrTextStream >> next [

| byte |
^ isBinary
ifTrue: [byte := super next.
byte ifNil: [nil] ifNotNil: [byte asciiValue]]
ifFalse: [super next].

^ isBinary
ifTrue: [ byte := super next.
byte ifNotNil: [ byte asciiValue ] ]
ifFalse: [ super next ]
]

{ #category : #accessing }
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@ Extension { #name : #CharacterSetComplement }

{ #category : #'*GT-InspectorExtensions-Core' }
CharacterSetComplement >> gtInspectorItemsIn: composite [

"The default set is huge, inspect the Absent list, which is typically a manageable size"

^ composite fastList
Expand All @@ -15,10 +14,7 @@ CharacterSetComplement >> gtInspectorItemsIn: composite [
showOnly: 50;
helpMessage: 'Quick selection field. Given your INPUT, it executes: self select: [:each | INPUT ]'."
result
ifNil: [ nil ]
ifNotNil: [ result size = 1
ifTrue: [ result anyOne ]
ifFalse: [ self species withAll: result ]
]
]
ifFalse: [ self species withAll: result ] ] ]
]
6 changes: 1 addition & 5 deletions src/GT-InspectorExtensions-Core/Collection.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ Collection >> gtDisplayOn: stream [

{ #category : #'*GT-InspectorExtensions-Core' }
Collection >> gtInspectorItemsIn: composite [

<gtInspectorPresentationOrder: 0>
^ composite fastList
title: 'Items';
Expand All @@ -39,10 +38,7 @@ Collection >> gtInspectorItemsIn: composite [
showOnly: 50;
helpMessage: 'Quick selection field. Given your INPUT, it executes: self select: [:each | INPUT ]'."
result
ifNil: [ nil ]
ifNotNil: [ result size = 1
ifTrue: [ result anyOne ]
ifFalse: [ self species withAll: result ]
]
]
ifFalse: [ self species withAll: result ] ] ]
]
13 changes: 3 additions & 10 deletions src/GT-InspectorExtensions-Core/Dictionary.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@ Extension { #name : #Dictionary }

{ #category : #'*GT-InspectorExtensions-Core' }
Dictionary >> gtInspectorItemsIn: composite [

^ composite fastTable
title: 'Items';
display: [ self associations ];
Expand All @@ -16,24 +15,18 @@ Dictionary >> gtInspectorItemsIn: composite [
column: 'Value' evaluated: [ :each | GTObjectPrinter asTruncatedTextFrom: each value ];
selectionAct: [ :table |
table rawSelection do: [ :assoc | self removeKey: assoc key ].
table update
]
table update ]
entitled: 'Remove item(s)';
selectionPopulate: #selection
entitled: 'Open key'
with: [ :table | ( table rawSelection collect: #key ) gtInspectorInterestingObject ];
selectionPopulate: #selection entitled: 'Open key' with: [ :table | (table rawSelection collect: #key) gtInspectorInterestingObject ];
beMultiple;
send: [ :selection |
"withSmalltalkSearch;
showOnly: 50;
helpMessage: 'Quick selection field. Given your INPUT, it executes: self select: [:each | INPUT ]'"
selection
ifNil: [ nil ]
ifNotNil: [ selection size = 1
ifTrue: [ selection anyOne value ]
ifFalse: [ selection collect: #value ]
]
]
ifFalse: [ selection collect: #value ] ] ]
]

{ #category : #'*GT-InspectorExtensions-Core' }
Expand Down
13 changes: 3 additions & 10 deletions src/GT-InspectorExtensions-Core/OrderedDictionary.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@ Extension { #name : #OrderedDictionary }

{ #category : #'*GT-InspectorExtensions-Core' }
OrderedDictionary >> gtInspectorItemsIn: composite [

^ composite fastTable
title: 'Items';
display: [ self associations ];
Expand All @@ -16,22 +15,16 @@ OrderedDictionary >> gtInspectorItemsIn: composite [
column: 'Value' evaluated: [ :each | GTObjectPrinter asTruncatedTextFrom: each value ];
selectionAct: [ :table |
table rawSelection do: [ :assoc | self removeKey: assoc key ].
table update
]
table update ]
entitled: 'Remove item(s)';
selectionPopulate: #selection
entitled: 'Open key'
with: [ :table | ( table rawSelection collect: #key ) gtInspectorInterestingObject ];
selectionPopulate: #selection entitled: 'Open key' with: [ :table | (table rawSelection collect: #key) gtInspectorInterestingObject ];
beMultiple;
send: [ :selection |
"withSmalltalkSearch;
showOnly: 50;
helpMessage: 'Quick selection field. Given your INPUT, it executes: self select: [:each | INPUT ]'"
selection
ifNil: [ nil ]
ifNotNil: [ selection size = 1
ifTrue: [ selection anyOne value ]
ifFalse: [ selection collect: #value ]
]
]
ifFalse: [ selection collect: #value ] ] ]
]
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@ Extension { #name : #SequenceableCollection }

{ #category : #'*GT-InspectorExtensions-Core' }
SequenceableCollection >> gtInspectorItemsIn: composite [

^ composite fastTable
title: 'Items';
display: [ self ];
Expand All @@ -16,10 +15,7 @@ SequenceableCollection >> gtInspectorItemsIn: composite [
showOnly: 50;
helpMessage: 'Quick selection field. Given your INPUT, it executes: self select: [:each | INPUT ]'."
result
ifNil: [ nil ]
ifNotNil: [ result size = 1
ifTrue: [ result anyOne ]
ifFalse: [ self species withAll: result ]
]
]
ifFalse: [ self species withAll: result ] ] ]
]
13 changes: 3 additions & 10 deletions src/GT-InspectorExtensions-Core/SmallDictionary.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@ Extension { #name : #SmallDictionary }

{ #category : #'*GT-InspectorExtensions-Core' }
SmallDictionary >> gtInspectorItemsIn: composite [

^ composite fastTable
title: 'Items';
display: [ self associations ];
Expand All @@ -16,22 +15,16 @@ SmallDictionary >> gtInspectorItemsIn: composite [
column: 'Value' evaluated: [ :each | GTObjectPrinter asTruncatedTextFrom: each value ];
selectionAct: [ :table |
table rawSelection do: [ :assoc | self removeKey: assoc key ].
table update
]
table update ]
entitled: 'Remove item(s)';
selectionPopulate: #selection
entitled: 'Open key'
with: [ :table | ( table rawSelection collect: #key ) gtInspectorInterestingObject ];
selectionPopulate: #selection entitled: 'Open key' with: [ :table | (table rawSelection collect: #key) gtInspectorInterestingObject ];
beMultiple;
send: [ :selection |
"withSmalltalkSearch;
showOnly: 50;
helpMessage: 'Quick selection field. Given your INPUT, it executes: self select: [:each | INPUT ]'"
selection
ifNil: [ nil ]
ifNotNil: [ selection size = 1
ifTrue: [ selection anyOne value ]
ifFalse: [ selection collect: #value ]
]
]
ifFalse: [ selection collect: #value ] ] ]
]
3 changes: 1 addition & 2 deletions src/GT-Spotter-Processors/SptTransformation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,7 @@ Class {

{ #category : #accessing }
SptTransformation >> next [

^ inner next ifNil: [ nil ] ifNotNil:[ :aValue | self transform: aValue]
^ inner next ifNotNil: [ :aValue | self transform: aValue ]
]

{ #category : #tranforming }
Expand Down
25 changes: 12 additions & 13 deletions src/GT-Spotter/GTSpotterCandidatesList.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -215,24 +215,23 @@ GTSpotterCandidatesList >> previousProcessorLinkOf: aProcessorLink [
{ #category : #private }
GTSpotterCandidatesList >> privateAddCandidate: aCandidateLink inEmpty: aProcessorLink [
| head current |

current := aProcessorLink. "not nil"
head := nil. "nil"
[ head isNil and: [ current isNotNil ]] whileTrue: [
current := current nextLink. "next category"
"head of next category if not nil break loop"
current ifNotNil: [ head := current headLink ] ifNil: [ nil ] ].
head := nil. "nil"
[ head isNil and: [ current isNotNil ] ]
whileTrue: [ current := current nextLink. "next category"
"head of next category if not nil break loop"
current ifNotNil: [ head := current headLink ] ].

"means all next categories are empty, just add to the end"
current
ifNil: [ self candidates addLast: aCandidateLink ]
ifNotNil: [ self candidates add: aCandidateLink beforeLink: head ].
aProcessorLink
headLink: aCandidateLink;
tailLink: aCandidateLink.
aProcessorLink incrementSize.
aProcessorLink
headLink: aCandidateLink;
tailLink: aCandidateLink.

aProcessorLink incrementSize.

^ aCandidateLink
]

Expand Down
6 changes: 1 addition & 5 deletions src/Glamour-Core/GLMPresentation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1040,11 +1040,7 @@ GLMPresentation >> title: aStringOrBlock [

{ #category : #accessing }
GLMPresentation >> titleAction [

^ self titleActionBlock
ifNil: [ nil ]
ifNotNil: [ :aBlock |
aBlock glamourValue: self ]
^ self titleActionBlock ifNotNil: [ :aBlock | aBlock glamourValue: self ]
]

{ #category : #'scripting actions' }
Expand Down
20 changes: 6 additions & 14 deletions src/Glamour-Morphic-Renderer/GLMMorphicWidgetRenderer.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -51,35 +51,27 @@ GLMMorphicWidgetRenderer >> installKeystrokeActionsOnMorph: aMorph fromPresentat

{ #category : #private }
GLMMorphicWidgetRenderer >> labelActionBrickFor: aPresentation [

^ aPresentation titleAction
ifNil: [ nil ]
ifNotNil: [ :labelAction |
^ aPresentation titleAction
ifNotNil: [ :labelAction |
((labelAction isAvailableOn: aPresentation) and: [ labelAction hasIcon ])
ifTrue: [
GLMActionButtonBrick new
ifTrue: [ GLMActionButtonBrick new
icon: labelAction icon;
setBalloonText: labelAction title;
action: [ labelAction actOn: aPresentation ] ]
ifFalse: [ nil ] ]

]

{ #category : #private }
GLMMorphicWidgetRenderer >> labelActionMorphFor: aPresentation [

^ aPresentation titleAction
ifNil: [ nil ]
ifNotNil: [ :labelAction |
^ aPresentation titleAction
ifNotNil: [ :labelAction |
((labelAction isAvailableOn: aPresentation) and: [ labelAction hasIcon ])
ifTrue: [
MultistateButtonMorph new
ifTrue: [ MultistateButtonMorph new
extent: labelAction icon extent;
activeEnabledOverUpFillStyle: (ImageFillStyle form: labelAction icon);
setBalloonText: labelAction title;
addUpAction: [ labelAction actOn: aPresentation ] ]
ifFalse: [ nil ] ]

]

{ #category : #private }
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -94,8 +94,7 @@ GLMRubricSmalltalkTextModel >> selectedClassOrMetaClass [

{ #category : #accessing }
GLMRubricSmalltalkTextModel >> selectedMethod [

^ self doItContext ifNil: [ nil ] ifNotNil: [ :aContext | aContext method ]
^ self doItContext ifNotNil: [ :aContext | aContext method ]
]

{ #category : #shout }
Expand Down
5 changes: 1 addition & 4 deletions src/Glamour-Morphic-Widgets/GLMTreeMorphModel.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -331,10 +331,7 @@ GLMTreeMorphModel >> selection: aSelection [

{ #category : #accessing }
GLMTreeMorphModel >> selectionPathItems [

^ self selectedNodePath
ifNil: [ nil ]
ifNotNil: [ self selectedNodePath collect: [ :each | each item ] ]
^ self selectedNodePath ifNotNil: [ self selectedNodePath collect: [ :each | each item ] ]
]

{ #category : #stepping }
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -101,10 +101,7 @@ GLMSmalltalkCodePresentation >> evaluateSelectionAndDo: aBlock [

{ #category : #accessing }
GLMSmalltalkCodePresentation >> highlightSmalltalkContext [

^ highlightSmalltalkContext
ifNil: [ nil ]
ifNotNil: [ highlightSmalltalkContext glamourValue: self entity ]
^ highlightSmalltalkContext ifNotNil: [ highlightSmalltalkContext glamourValue: self entity ]
]

{ #category : #rendering }
Expand Down
5 changes: 1 addition & 4 deletions src/Glamour-Presentations/GLMTextPresentation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -37,10 +37,7 @@ GLMTextPresentation >> highlightSmalltalk [

{ #category : #accessing }
GLMTextPresentation >> highlightSmalltalkContext [

^ highlightSmalltalkContext
ifNil: [ nil ]
ifNotNil: [ highlightSmalltalkContext glamourValue: self entity ]
^ highlightSmalltalkContext ifNotNil: [ highlightSmalltalkContext glamourValue: self entity ]
]

{ #category : #rendering }
Expand Down

0 comments on commit 4b3893e

Please sign in to comment.