Skip to content

Commit

Permalink
cleaner code thamks to mutation testing
Browse files Browse the repository at this point in the history
  • Loading branch information
RenaudFondeur committed Jul 24, 2024
1 parent 3830e5b commit f20ba09
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 32 deletions.
7 changes: 3 additions & 4 deletions smalltalksrc/Slang/SLDeadCodeEliminationVisitor.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -93,11 +93,10 @@ SLDeadCodeEliminationVisitor >> visitStatementListNode: aStatementListNode [

{ #category : 'visiting' }
SLDeadCodeEliminationVisitor >> visitSwitchStatementNode: aSwitchStatementNode [

aSwitchStatementNode cases do: [ :case | self visit: case second ].
(aSwitchStatementNode otherwiseOrNil isNil or: [
aSwitchStatementNode otherwiseOrNil isNilConstantStmtListNode ]) ifTrue: [ ^ self ].
self visit: aSwitchStatementNode otherwiseOrNil
aSwitchStatementNode otherwiseOrNil ifNil: [ ^ self ].
self visit: aSwitchStatementNode otherwiseOrNil
]

{ #category : 'visiting' }
Expand Down
11 changes: 4 additions & 7 deletions smalltalksrc/Slang/TSendNode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -274,11 +274,9 @@ TSendNode >> children [

{ #category : 'dead-code-elimination' }
TSendNode >> collectSendInArguments: sendToCollect [

arguments do: [ :child |
child isSend
ifTrue: [ child collectSendInSelf: sendToCollect ]
]

child isSend ifTrue: [ child collectSendInSelf: sendToCollect ] ]
]

{ #category : 'dead-code-elimination' }
Expand Down Expand Up @@ -549,8 +547,6 @@ TSendNode >> receiver: aNode [
TSendNode >> reduceConditionalSend: branchIndex [
"branch index is either 1 or 2, called when an argument of a conditional send have been removed, if the method has multiple branches we can reduce the branch number to match the transformation"

(#( #ifTrue:ifFalse: #ifFalse:ifTrue: #ifNil:ifNotNil:
#ifNotNil:ifNil: ) includes: self selector) ifFalse: [ ^ self ].
branchIndex = 1
ifTrue: [ self selector: self selector keywords second ]
ifFalse: [ self selector: self selector keywords first ]
Expand Down Expand Up @@ -705,6 +701,7 @@ TSendNode >> structTargetKindIn: aCodeGen [

{ #category : 'dead-code-elimination' }
TSendNode >> transformReceiverAfterEmptyArguments [
"keep any send that isn't a comparaison in the receiver to the parent of self. Since this method is called in a dead code cleaning processus the parent should only be a statement list or another conditional send"

| sendToCollect |
receiver isSend ifFalse: [ ^ self ].
Expand All @@ -713,7 +710,7 @@ TSendNode >> transformReceiverAfterEmptyArguments [
sendToCollect isNotEmpty ifTrue: [
self parent
replaceChild: self
with: (TStatementListNode new statements: sendToCollect) ]
with: (TStatementListNode statements: sendToCollect) ]
]

{ #category : 'type inference' }
Expand Down
10 changes: 4 additions & 6 deletions smalltalksrc/Slang/TStatementListNode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -373,12 +373,11 @@ TStatementListNode >> initialize [
]

{ #category : 'testing' }
TStatementListNode >> isNilConstantStmtListNode [
TStatementListNode >> isEmptyStmtListNode [
"return true if the statement node is empty or has just a nil in it"

| stmt |
statements size = 1 ifFalse: [ ^ false ].
stmt := statements at: 1.
^ stmt isConstant and: [ stmt value isNil ]
statements isEmpty ifTrue: [ ^ true ].
^ false
]

{ #category : 'testing' }
Expand Down Expand Up @@ -604,7 +603,6 @@ TStatementListNode >> statements [
{ #category : 'accessing' }
TStatementListNode >> statements: anObject [

| oldStatements |
statements := anObject asOrderedCollection.
statements do: [ :e | e parent: self ]
]
Expand Down
25 changes: 10 additions & 15 deletions smalltalksrc/Slang/TSwitchStmtNode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -452,21 +452,16 @@ TSwitchStmtNode >> removeAssertions [

{ #category : 'dead-code-elimination' }
TSwitchStmtNode >> removeUnusedNodesInBranch: aChild [
"when removing a node from a switch, we have to be careful of if it comes from a caseOf: or a caseOf:otherwise:. if it comes from a caseOf:, otherwise is nil and must be kept it will be translated as a no case found error. To indicate that otherwise does nothing Slang use a TStatementListNode with a nil in it, hence the following code"

(otherwiseOrNil isNotNil and:[ otherwiseOrNil isNilConstantStmtListNode not and: [ otherwiseOrNil = aChild ]]) ifTrue: [
otherwiseOrNil := TStatementListNode new statements:
(TConstantNode new setValue: nil) ].
"when removing a node from a switch, we have to be careful of if it comes from a caseOf: or a caseOf:otherwise:. if it comes from a caseOf:, otherwise is nil and must be kept it will be translated as a no case found error. To indicate that otherwise does nothing Slang use an empty TStatementListNode, hence the following code"

cases := cases select: [ :each | each second ~~ aChild ].
"check if we can suppress the node"
self cases isEmpty
ifTrue: [
otherwiseOrNil ifNil: [ "we're from a simple caseOf: so we're keeping otherwise"
^ self ].
otherwiseOrNil isNilConstantStmtListNode ifTrue: [
self transformExpressionAfterEmptyCasesAndOtherwise.
self parent removeUnusedNodesInBranch: self ] ]
ifFalse: [ ^ self ]
self cases isEmpty ifFalse: [ ^ self ].
"we're from a caseOf: so we keep the node"
otherwiseOrNil ifNil: [ ^ self ].
"otherwiseOrNil may have been empty from the start or during the cleaning process, either way the node is now completely empty so we can supress it"
otherwiseOrNil isEmptyStmtListNode ifFalse: [ ^ self ].
self transformExpressionAfterEmptyCasesAndOtherwise.
self parent removeUnusedNodesInBranch: self
]

{ #category : 'transformations' }
Expand Down Expand Up @@ -508,5 +503,5 @@ TSwitchStmtNode >> transformExpressionAfterEmptyCasesAndOtherwise [
sendToCollect isNotEmpty ifTrue: [
self parent
replaceChild: self
with: (TStatementListNode new statements: sendToCollect) ]
with: (TStatementListNode statements: sendToCollect) ]
]

0 comments on commit f20ba09

Please sign in to comment.