Skip to content

Commit

Permalink
xtract returns from conditionals for packages starting by p to r
Browse files Browse the repository at this point in the history
This makes the code more readable since we can directly know that the conditional will necessarily return something and the execution can be stoped.
  • Loading branch information
jecisc committed May 29, 2020
1 parent 9123795 commit fe0f36f
Show file tree
Hide file tree
Showing 18 changed files with 113 additions and 174 deletions.
10 changes: 4 additions & 6 deletions src/Polymorph-Widgets/UITheme.class.st
Expand Up @@ -1202,15 +1202,13 @@ UITheme >> chooseOrRequestIn: aThemedMorph title: title labels: labels values: v

| dialog choice |
dialog := (PopupChoiceOrRequestDialogWindow newWithTheme: aThemedMorph theme)
title: (title isEmpty ifTrue: ['Choose' translated] ifFalse: [title asString]);
title: (title ifEmpty: [ 'Choose' translated ] ifNotEmpty: #asString);
labels: labels;
lines: (lines ifNil: [#()]);
lines: (lines ifNil: [ #() ]);
model: values.
choice := dialog openModal choice.
dialog cancelled ifTrue: [ ^nil ].
choice
ifNotNil: [ ^choice ]
ifNil: [ ^dialog filterValue ]
dialog cancelled ifTrue: [ ^ nil ].
^ choice ifNil: [ dialog filterValue ]
]

{ #category : #'accessing colors' }
Expand Down
10 changes: 3 additions & 7 deletions src/Refactoring-Core/RBDeprecateMethodRefactoring.class.st
Expand Up @@ -50,13 +50,9 @@ RBDeprecateMethodRefactoring >> formNameFor: aSelector [
method := class methodFor: aSelector.
keywords := method parseTree keywords asOrderedCollection ifNil: [ '' ].
arguments := method parseTree arguments ifNil: [ '' ].

(keywords isNotEmpty and: [ arguments isNotEmpty ])
ifTrue: [ ^ String streamContents: [ :s|
keywords with: arguments do: [ :keyword :arg | s nextPutAll: keyword, ' ', arg name, ' ' ] ] ]
ifFalse: [ ^ aSelector asString ].


^ (keywords isNotEmpty and: [ arguments isNotEmpty ])
ifTrue: [ String streamContents: [ :s | keywords with: arguments do: [ :keyword :arg | s nextPutAll: keyword , ' ' , arg name , ' ' ] ] ]
ifFalse: [ aSelector asString ]
]

{ #category : #transforming }
Expand Down
10 changes: 5 additions & 5 deletions src/Refactoring-Core/RBExtractMethodRefactoring.class.st
Expand Up @@ -145,11 +145,11 @@ RBExtractMethodRefactoring >> createTemporariesInExtractedMethodFor: assigned [
{ #category : #transforming }
RBExtractMethodRefactoring >> existingSelector [
"Try to find an existing method instead of creating a new one"
|existSelector |
existSelector := self requestExistingSelector.
existSelector ifNotNil: [ ^ existSelector ] ifNil: [
^ class allSelectors detect: [:each | self isMethodEquivalentTo: each]
ifNone: [nil]]

^ self requestExistingSelector
ifNil: [ class allSelectors
detect: [ :each | self isMethodEquivalentTo: each ]
ifNone: [ nil ] ]
]

{ #category : #initialization }
Expand Down
19 changes: 7 additions & 12 deletions src/Refactoring-Core/RBMoveInstVarToClassRefactoring.class.st
Expand Up @@ -30,24 +30,19 @@ RBMoveInstVarToClassRefactoring >> collectSendersOfInstVar [
| brokenSenders subclasses hasInstVar |
hasInstVar := false.
brokenSenders := OrderedCollection new.
oldClass superclass instanceVariableNames
do: [ :each |
each = variableName
ifTrue: [ hasInstVar := true ] ].
hasInstVar
ifTrue: [ ^ brokenSenders ]
ifFalse: [
brokenSenders := (oldClass selectors
oldClass superclass instanceVariableNames do: [ :each | each = variableName ifTrue: [ hasInstVar := true ] ].
^ hasInstVar
ifTrue: [ brokenSenders ]
ifFalse: [ brokenSenders := (oldClass selectors
select: [ :each | (oldClass methodFor: each) source includesSubstring: variableName asString ]
thenCollect: [ :each | oldClass methodFor: each ]) asOrderedCollection.
subclasses := oldClass subclasses.
subclasses
do: [ :subclass |
subclass selectors
do: [ :each |
((subclass methodFor: each) source includesSubstring: ' ' , variableName asString , ' ')
ifTrue: [ brokenSenders add: (subclass methodFor: each) ] ] ].
^ brokenSenders ]
do:
[ :each | ((subclass methodFor: each) source includesSubstring: ' ' , variableName asString , ' ') ifTrue: [ brokenSenders add: (subclass methodFor: each) ] ] ].
brokenSenders ]
]

{ #category : #accessing }
Expand Down
6 changes: 3 additions & 3 deletions src/Refactoring-Core/RBRemoveMethodRefactoring.class.st
Expand Up @@ -61,9 +61,9 @@ RBRemoveMethodRefactoring >> checkBrowseOccurrenceOf: selector in: aRBMethod [

{ #category : #preconditions }
RBRemoveMethodRefactoring >> checkBrowseOccurrences: anCollectionOfOccurrences [
anCollectionOfOccurrences size = 1
ifTrue: [ ^ self checkBrowseOccurrenceOf: anCollectionOfOccurrences first key in: anCollectionOfOccurrences first value ]
ifFalse: [ ^ self checkBrowseAllOccurences: anCollectionOfOccurrences ]
^ anCollectionOfOccurrences size = 1
ifTrue: [ self checkBrowseOccurrenceOf: anCollectionOfOccurrences first key in: anCollectionOfOccurrences first value ]
ifFalse: [ self checkBrowseAllOccurences: anCollectionOfOccurrences ]
]

{ #category : #preconditions }
Expand Down
6 changes: 3 additions & 3 deletions src/Refactoring-Tests-Critics/RBSmalllintTestObject.class.st
Expand Up @@ -478,9 +478,9 @@ RBSmalllintTestObject >> transcriptMentioned [
RBSmalllintTestObject >> unaryAccessingBranchingStatementMethodWithReturn [
"shouldn't trigger the RBUnaryAccessingMethodWithoutReturnRule rule"

self value isString
ifTrue: [ ^ self value ]
ifFalse: [ ^ '' ]
^ self value isString
ifTrue: [ self value ]
ifFalse: [ '' ]
]

{ #category : #'accessing - bad' }
Expand Down
Expand Up @@ -88,10 +88,9 @@ RBRemoveMethodTransformation >> checkBrowseOccurrenceIn: aRBMethod [

{ #category : #preconditions }
RBRemoveMethodTransformation >> checkBrowseOccurrences: anCollectionOfOccurrences [

anCollectionOfOccurrences size = 1
ifTrue: [ ^ self checkBrowseOccurrenceIn: anCollectionOfOccurrences first value ]
ifFalse: [ ^ self checkBrowseAllOccurences: anCollectionOfOccurrences ]
^ anCollectionOfOccurrences size = 1
ifTrue: [ self checkBrowseOccurrenceIn: anCollectionOfOccurrences first value ]
ifFalse: [ self checkBrowseAllOccurences: anCollectionOfOccurrences ]
]

{ #category : #preconditions }
Expand Down
6 changes: 3 additions & 3 deletions src/Reflectivity/RFCondition.class.st
Expand Up @@ -68,7 +68,7 @@ RFCondition >> value [

{ #category : #accessing }
RFCondition >> valueSelector [
linkCondition numArgs isZero
ifTrue: [ ^ #value ]
ifFalse: [ ^ #cull: ]
^ linkCondition numArgs isZero
ifTrue: [ #value ]
ifFalse: [ #cull: ]
]
18 changes: 8 additions & 10 deletions src/Reflectivity/RFNewValueReification.class.st
Expand Up @@ -31,19 +31,17 @@ RFNewValueReification >> genForRBVariableNode [
{ #category : #preamble }
RFNewValueReification >> preambleForAssignment: aNode [
"balance stack for instead"
link control= #instead
ifTrue: [ ^RFStorePopIntoTempNode named: #RFNewValueReificationVar ]
ifFalse: [^RFStoreIntoTempNode named: #RFNewValueReificationVar ]



^ link control = #instead
ifTrue: [ RFStorePopIntoTempNode named: #RFNewValueReificationVar ]
ifFalse: [ RFStoreIntoTempNode named: #RFNewValueReificationVar ]
]

{ #category : #preamble }
RFNewValueReification >> preambleForVariable: aNode [
"balance stack for instead"
link control= #instead
ifTrue: [ ^RFStorePopIntoTempNode named: #RFNewValueReificationVar ]
ifFalse: [^RFStoreIntoTempNode named: #RFNewValueReificationVar ]



^ link control = #instead
ifTrue: [ RFStorePopIntoTempNode named: #RFNewValueReificationVar ]
ifFalse: [ RFStoreIntoTempNode named: #RFNewValueReificationVar ]
]
28 changes: 10 additions & 18 deletions src/Regex-Core/RxCharSetParser.class.st
Expand Up @@ -73,22 +73,17 @@ RxCharSetParser >> parse [

{ #category : #parsing }
RxCharSetParser >> parseCharOrRange [

| firstChar |

firstChar := lookahead.
self match: firstChar.
lookahead = $-
ifTrue: [ self match: $-.
lookahead
ifNil: [ ^ self
^ lookahead
ifNil: [ self
addChar: firstChar;
addChar: $-
]
addChar: $- ]
ifNotNil: [ self addRangeFrom: firstChar to: lookahead.
^ self match: lookahead
]
].
self match: lookahead ] ].
self addChar: firstChar
]

Expand All @@ -115,14 +110,11 @@ RxCharSetParser >> parseNamedSet [

{ #category : #parsing }
RxCharSetParser >> parseStep [

lookahead = $[ ifTrue:
[source peek = $:
ifTrue: [^self parseNamedSet]
ifFalse: [^self parseCharOrRange]].
lookahead = $\ ifTrue:
[^self parseEscapeChar].
lookahead = $- ifTrue:
[RxParser signalSyntaxException: 'invalid range' at: source position].
lookahead = $[
ifTrue: [ ^ source peek = $:
ifTrue: [ self parseNamedSet ]
ifFalse: [ self parseCharOrRange ] ].
lookahead = $\ ifTrue: [ ^ self parseEscapeChar ].
lookahead = $- ifTrue: [ RxParser signalSyntaxException: 'invalid range' at: source position ].
self parseCharOrRange
]
11 changes: 4 additions & 7 deletions src/Regex-Core/RxmPredicate.class.st
Expand Up @@ -46,13 +46,10 @@ RxmPredicate >> matchAgainst: aMatcher [

| original |
original := aMatcher currentState.
(aMatcher atEnd not
and: [(predicate value: aMatcher next)
and: [next matchAgainst: aMatcher]])
ifTrue: [^true]
ifFalse:
[aMatcher restoreState: original.
^false]
^ (aMatcher atEnd not and: [ (predicate value: aMatcher next) and: [ next matchAgainst: aMatcher ] ])
ifTrue: [ true ]
ifFalse: [ aMatcher restoreState: original.
false ]
]

{ #category : #initialization }
Expand Down
13 changes: 5 additions & 8 deletions src/Regex-Core/RxmSubstring.class.st
Expand Up @@ -51,14 +51,11 @@ RxmSubstring >> matchAgainst: aMatcher [
originalState := aMatcher currentState.
sampleStream := self sampleStream.
mismatch := false.
[sampleStream atEnd
or: [aMatcher atEnd
or: [mismatch := (compare value: sampleStream next value: aMatcher next) not]]] whileFalse.
(mismatch not and: [sampleStream atEnd and: [next matchAgainst: aMatcher]])
ifTrue: [^true]
ifFalse:
[aMatcher restoreState: originalState.
^false]
[ sampleStream atEnd or: [ aMatcher atEnd or: [ mismatch := (compare value: sampleStream next value: aMatcher next) not ] ] ] whileFalse.
^ (mismatch not and: [ sampleStream atEnd and: [ next matchAgainst: aMatcher ] ])
ifTrue: [ true ]
ifFalse: [ aMatcher restoreState: originalState.
false ]
]

{ #category : #private }
Expand Down
7 changes: 3 additions & 4 deletions src/Rubric/RubCharacterBlock.class.st
Expand Up @@ -27,10 +27,9 @@ RubCharacterBlock >> <= aCharacterBlock [

{ #category : #comparing }
RubCharacterBlock >> = aCharacterBlock [

self species = aCharacterBlock species
ifTrue: [^stringIndex = aCharacterBlock stringIndex]
ifFalse: [^false]
^ self species = aCharacterBlock species
ifTrue: [ stringIndex = aCharacterBlock stringIndex ]
ifFalse: [ false ]
]

{ #category : #comparing }
Expand Down
47 changes: 17 additions & 30 deletions src/Rubric/RubCharacterBlockScanner.class.st
Expand Up @@ -25,15 +25,9 @@ RubCharacterBlockScanner >> characterBlockAtPoint: aPoint index: index in: textL
self setStopConditions. "also sets font"
characterIndex := index. " == nil means scanning for point"
characterPoint := aPoint.
(characterPoint isNil or: [ characterPoint y > line bottom ])
ifTrue: [ characterPoint := line bottomRight ].
(text isEmpty
or: [
(characterPoint y < line top or: [ characterPoint x < line left ])
or: [ characterIndex notNil and: [ characterIndex < line first ] ] ])
ifTrue: [
^ (RubCharacterBlock new stringIndex: line first topLeft: line leftMargin @ line top extent: 0 @ textStyle lineGrid)
textLine: line ].
(characterPoint isNil or: [ characterPoint y > line bottom ]) ifTrue: [ characterPoint := line bottomRight ].
(text isEmpty or: [ (characterPoint y < line top or: [ characterPoint x < line left ]) or: [ characterIndex notNil and: [ characterIndex < line first ] ] ])
ifTrue: [ ^ (RubCharacterBlock new stringIndex: line first topLeft: line leftMargin @ line top extent: 0 @ textStyle lineGrid) textLine: line ].
destX := leftMargin := line leftMarginForAlignment: alignment.
destY := line top.
runLength := text runLengthFor: line first.
Expand All @@ -44,38 +38,31 @@ RubCharacterBlockScanner >> characterBlockAtPoint: aPoint index: index in: textL
lastCharacterExtent := 0 @ line lineHeight.
spaceCount := 0.
[ false ]
whileFalse: [
stopCondition := self
whileFalse: [ stopCondition := self
scanCharactersFrom: lastIndex
to: runStopIndex
in: text string
rightX: characterPoint x
stopConditions: stopConditions
kern: kern. "see setStopConditions for stopping conditions for character block operations."
self lastCharacterExtentSetX: (specialWidth ifNil: [ font widthOf: (text at: lastIndex) ] ifNotNil: [ specialWidth ]).
self
lastCharacterExtentSetX:
(specialWidth
ifNil: [ font widthOf: (text at: lastIndex) ]
ifNotNil: [ specialWidth ]).
(self perform: stopCondition)
ifTrue: [
characterIndex
ifNil: [
"Result for characterBlockAtPoint: "
(stopCondition ~~ #cr
and: [ lastIndex == line last and: [ aPoint x > (characterPoint x + (lastCharacterExtent x / 2)) ] ])
ifTrue: [
"Correct for right half of last character in line"
ifTrue: [ ^ characterIndex
ifNil: [ "Result for characterBlockAtPoint: "
(stopCondition ~~ #cr and: [ lastIndex == line last and: [ aPoint x > (characterPoint x + (lastCharacterExtent x / 2)) ] ])
ifTrue: [ "Correct for right half of last character in line"
^ (RubCharacterBlock new
stringIndex: lastIndex + 1
topLeft: characterPoint + (lastCharacterExtent x @ 0) + (font descentKern @ 0)
extent: 0 @ lastCharacterExtent y) textLine: line ].
^ (RubCharacterBlock new
stringIndex: lastIndex
topLeft: characterPoint + (font descentKern @ 0)
extent: lastCharacterExtent - (font baseKern @ 0)) textLine: line ]
ifNotNil: [
"Result for characterBlockForIndex: "
^ (RubCharacterBlock new
stringIndex: characterIndex
topLeft: characterPoint + ((font descentKern - kern) @ 0)
extent: lastCharacterExtent) textLine: line ] ] ]
(RubCharacterBlock new stringIndex: lastIndex topLeft: characterPoint + (font descentKern @ 0) extent: lastCharacterExtent - (font baseKern @ 0))
textLine: line ]
ifNotNil:
[ "Result for characterBlockForIndex: " (RubCharacterBlock new stringIndex: characterIndex topLeft: characterPoint + ((font descentKern - kern) @ 0) extent: lastCharacterExtent) textLine: line ] ] ]
]

{ #category : #private }
Expand Down
14 changes: 5 additions & 9 deletions src/Rubric/RubCharacterScanner.class.st
Expand Up @@ -480,13 +480,9 @@ RubCharacterScanner >> textColor: ignored [

{ #category : #'multilingual scanning' }
RubCharacterScanner >> widthOf: char inFont: aFont [

(char isMemberOf: CombinedChar) ifTrue: [
^ aFont widthOf: char base.
] ifFalse: [
^ aFont widthOf: char.
].



^ aFont
widthOf:
((char isMemberOf: CombinedChar)
ifTrue: [ char base ]
ifFalse: [ char ])
]
14 changes: 6 additions & 8 deletions src/Rubric/RubCompositionScanner.class.st
Expand Up @@ -129,18 +129,16 @@ RubCompositionScanner >> endOfRun [
false."

| runLength |
lastIndex = text size
ifTrue: [line stop: lastIndex.
^ lastIndex = text size
ifTrue: [ line stop: lastIndex.
spaceX := destX.
line paddingWidth: rightMargin - destX.
^true]
ifFalse: [
"(text at: lastIndex) charCode = 32 ifTrue: [destX := destX + spaceWidth]."
runLength := (text runLengthFor: (lastIndex := lastIndex + 1)).
true ]
ifFalse: [ "(text at: lastIndex) charCode = 32 ifTrue: [destX := destX + spaceWidth]."
runLength := text runLengthFor: (lastIndex := lastIndex + 1).
runStopIndex := lastIndex + (runLength - 1).
self setStopConditions.
^false]

false ]
]

{ #category : #'stop conditions' }
Expand Down

0 comments on commit fe0f36f

Please sign in to comment.