Skip to content

Commit

Permalink
Extract assignations from conditionals for packages starting by a
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 611d269 commit cc7db5e
Showing 1 changed file with 7 additions and 9 deletions.
16 changes: 7 additions & 9 deletions src/AST-Core/RBParseTreeRewriter.class.st
Expand Up @@ -131,19 +131,17 @@ RBParseTreeRewriter class >> replaceLiteral: literal with: newLiteral [
]

{ #category : #accessing }
RBParseTreeRewriter class >> replaceStatements: code with: newCode in: aParseTree onInterval: anInterval [
RBParseTreeRewriter class >> replaceStatements: code with: newCode in: aParseTree onInterval: anInterval [
| tree replaceStmt |
tree := self buildTree: code method: false.
tree isSequence
ifFalse: [tree := RBSequenceNode statements: (Array with: tree)].
tree isSequence ifFalse: [ tree := RBSequenceNode statements: (Array with: tree) ].
tree temporaries: (Array with: (RBPatternVariableNode named: '`@temps')).
tree addNodeFirst: (RBPatternVariableNode named: '`@.S1').
tree lastIsReturn
ifTrue: [replaceStmt := '| `@temps | `@.S1. ^' , newCode]
ifFalse:
[tree addNode: (RBPatternVariableNode named: '`@.S2').
replaceStmt := '| `@temps | `@.S1. ' , newCode , '. `@.S2'].
^self
replaceStmt := tree lastIsReturn
ifTrue: [ '| `@temps | `@.S1. ^' , newCode ]
ifFalse: [ tree addNode: (RBPatternVariableNode named: '`@.S2').
'| `@temps | `@.S1. ' , newCode , '. `@.S2' ].
^ self
replace: tree formattedCode
with: replaceStmt
in: aParseTree
Expand Down

0 comments on commit cc7db5e

Please sign in to comment.