Skip to content

Commit

Permalink
change in removeUnusedNodesInBranch: to handle comments
Browse files Browse the repository at this point in the history
  • Loading branch information
RenaudFondeur committed Aug 14, 2024
1 parent 9320b5d commit d9798ac
Show file tree
Hide file tree
Showing 6 changed files with 216 additions and 19 deletions.
145 changes: 145 additions & 0 deletions smalltalksrc/Slang-Tests/SLDeadCodeEliminationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,66 @@ SLDeadCodeEliminationTest >> setUp [

]

{ #category : 'only-comment' }
SLDeadCodeEliminationTest >> testConditionalWithOnlyCommentNoSendInReceiver [
"currently the only way to get comments in a methods is through inlining, having only comments is equivalent to being empty so it shouldn't change the behavior of the dead code elimination process"

| translation tMethod |
tMethod := ccg methodNamed: #conditionalWithOnlyCommentNoSendInReceiver.

ccg doBasicInlining: true.
ccg currentMethod: tMethod.

sLDeadCodeEliminationVisitor visit: tMethod parseTree.

translation := self translate: tMethod.
translation := translation trimBoth.

self
assert: translation
equals:
'/* SLDeadCodeEliminationTestClass>>#conditionalWithOnlyCommentNoSendInReceiver */
static void
conditionalWithOnlyCommentNoSendInReceiver(SLDeadCodeEliminationTestClass * self_in_conditionalWithOnlyCommentNoSendInReceiver)
{
{
return;
}
}'
]

{ #category : 'only-comment' }
SLDeadCodeEliminationTest >> testConditionalWithOnlyCommentSendInReceiver [
"currently the only way to get comments in a methods is through inlining, having only comments is equivalent to being empty so it shouldn't change the behavior of the dead code elimination process"

| translation tMethod |
tMethod := ccg methodNamed:
#conditionalWithOnlyCommentSendInReceiver.

ccg doBasicInlining: true.
ccg currentMethod: tMethod.

sLDeadCodeEliminationVisitor visit: tMethod parseTree.

translation := self translate: tMethod.
translation := translation trimBoth.

self
assert: translation
equals:
'/* SLDeadCodeEliminationTestClass>>#conditionalWithOnlyCommentSendInReceiver */
static void
conditionalWithOnlyCommentSendInReceiver(SLDeadCodeEliminationTestClass * self_in_conditionalWithOnlyCommentSendInReceiver)
{
{
method(self_in_conditionalWithOnlyCommentSendInReceiver, method(self_in_conditionalWithOnlyCommentSendInReceiver));
}
{
return;
}
}'
]

{ #category : 'method-in-c-coerce' }
SLDeadCodeEliminationTest >> testMethodAddingCallInCoerce [

Expand Down Expand Up @@ -1053,6 +1113,34 @@ methodWithInstanceVariableInReturn(SLDeadCodeEliminationTestClass * self_in_meth
}'
]

{ #category : 'only-comment' }
SLDeadCodeEliminationTest >> testMethodWithOnlyComment [
"currently the only way to get comments in a methods is through inlining, having only comments is equivalent to being empty so it shouldn't change the behavior of the dead code elimination process"

| translation tMethod |
tMethod := ccg methodNamed: #methodWithOnlyComment.
ccg doBasicInlining: true.
ccg currentMethod: tMethod.
sLDeadCodeEliminationVisitor visit: tMethod parseTree.

translation := self translate: tMethod.
translation := translation trimBoth.

self
assert: translation
equals:
'/* SLDeadCodeEliminationTestClass>>#methodWithOnlyComment */
static void
methodWithOnlyComment(SLDeadCodeEliminationTestClass * self_in_methodWithOnlyComment)
{
/* begin method */
/* end method */
{
return;
}
}'
]

{ #category : 'unused-leaf' }
SLDeadCodeEliminationTest >> testMethodWithUnusedConstant [

Expand Down Expand Up @@ -3705,6 +3793,63 @@ methodWithVariableInReturn(SLDeadCodeEliminationTestClass * self_in_methodWithVa
}'
]

{ #category : 'only-comment' }
SLDeadCodeEliminationTest >> testSwitchWithOnlyCommentNoSendInReceiver [
"currently the only way to get comments in a methods is through inlining, having only comments is equivalent to being empty so it shouldn't change the behavior of the dead code elimination process"

| translation tMethod |
tMethod := ccg methodNamed: #switchWithOnlyCommentNoSendInReceiver:.
tMethod prepareMethodIn: ccg.
ccg doBasicInlining: true.
ccg currentMethod: tMethod.
sLDeadCodeEliminationVisitor visit: tMethod parseTree.

translation := self translate: tMethod.
translation := translation trimBoth.

self
assert: translation
equals:
'/* SLDeadCodeEliminationTestClass>>#switchWithOnlyCommentNoSendInReceiver: */
static void
switchWithOnlyCommentNoSendInReceiver(SLDeadCodeEliminationTestClass * self_in_switchWithOnlyCommentNoSendInReceiver, sqInt anInt)
{
{
return;
}
}'
]

{ #category : 'only-comment' }
SLDeadCodeEliminationTest >> testSwitchWithOnlyCommentSendInReceiver [
"currently the only way to get comments in a methods is through inlining, having only comments is equivalent to being empty so it shouldn't change the behavior of the dead code elimination process"

| translation tMethod |
tMethod := ccg methodNamed: #switchWithOnlyCommentSendInReceiver.
tMethod prepareMethodIn: ccg.
ccg doBasicInlining: true.
ccg currentMethod: tMethod.
sLDeadCodeEliminationVisitor visit: tMethod parseTree.

translation := self translate: tMethod.
translation := translation trimBoth.

self
assert: translation
equals:
'/* SLDeadCodeEliminationTestClass>>#switchWithOnlyCommentSendInReceiver */
static void
switchWithOnlyCommentSendInReceiver(SLDeadCodeEliminationTestClass * self_in_switchWithOnlyCommentSendInReceiver)
{
{
method(self_in_switchWithOnlyCommentSendInReceiver, method(self_in_switchWithOnlyCommentSendInReceiver));
}
{
return;
}
}'
]

{ #category : 'helpers' }
SLDeadCodeEliminationTest >> translate: tast [

Expand Down
50 changes: 50 additions & 0 deletions smalltalksrc/Slang-Tests/SLDeadCodeEliminationTestClass.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,34 @@ SLDeadCodeEliminationTestClass class >> instVarNamesAndTypesForTranslationDo: aB
otherwise: [ #sqInt ]) ]
]

{ #category : 'only-comment' }
SLDeadCodeEliminationTestClass >> conditionalWithOnlyCommentNoSendInReceiver [

<returnTypeC: #void>
true
ifTrue: [ self method ]
ifFalse: [ self method ]
]

{ #category : 'only-comment' }
SLDeadCodeEliminationTestClass >> conditionalWithOnlyCommentSendInReceiver [

<returnTypeC: #void>
(self method: self method)
ifTrue: [ self method ]
ifFalse: [ self method ]
]

{ #category : 'accessing' }
SLDeadCodeEliminationTestClass >> instancesVariable [
^ instancesVariable
]

{ #category : 'helpers' }
SLDeadCodeEliminationTestClass >> method [

<inline: true>

]

{ #category : 'helpers' }
Expand Down Expand Up @@ -332,6 +353,13 @@ SLDeadCodeEliminationTestClass >> methodWithInstanceVariableInReturn [
^ instancesVariable
]

{ #category : 'only-comment' }
SLDeadCodeEliminationTestClass >> methodWithOnlyComment [

<returnTypeC: #void>
self method
]

{ #category : 'unused-leaf' }
SLDeadCodeEliminationTestClass >> methodWithUnusedConstant [

Expand Down Expand Up @@ -1123,3 +1151,25 @@ SLDeadCodeEliminationTestClass >> methodWithVariableInReturn [
i.
^ i
]

{ #category : 'only-comment' }
SLDeadCodeEliminationTestClass >> switchWithOnlyCommentNoSendInReceiver: anInt [

<returnTypeC: #void>
anInt
caseOf: {
([ 5 ] -> [ self method ]).
([ 6 ] -> [ self method ]) }
otherwise: [ self method ]
]

{ #category : 'only-comment' }
SLDeadCodeEliminationTestClass >> switchWithOnlyCommentSendInReceiver [

<returnTypeC: #void>
(self method: self method)
caseOf: {
([ 5 ] -> [ self method ]).
([ 6 ] -> [ self method ]) }
otherwise: [ self method ]
]
9 changes: 5 additions & 4 deletions smalltalksrc/Slang/SlangReturnTypeConflictException.class.st
Original file line number Diff line number Diff line change
@@ -1,10 +1,11 @@
Class {
#name : #SlangReturnTypeConflictException,
#superclass : #SlangTyperException,
#category : #Slang
#name : 'SlangReturnTypeConflictException',
#superclass : 'SlangTyperException',
#category : 'Slang',
#package : 'Slang'
}

{ #category : #exceptions }
{ #category : 'exceptions' }
SlangReturnTypeConflictException class >> signalConflictIn: aMethod with: aCollectionOfType [

| message |
Expand Down
7 changes: 4 additions & 3 deletions smalltalksrc/Slang/SlangTyperException.class.st
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
Class {
#name : #SlangTyperException,
#superclass : #Error,
#category : #Slang
#name : 'SlangTyperException',
#superclass : 'Error',
#category : 'Slang',
#package : 'Slang'
}
18 changes: 9 additions & 9 deletions smalltalksrc/Slang/TStatementListNode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -437,9 +437,9 @@ TStatementListNode >> isComment [

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

statements isEmpty ifTrue: [ ^ true ].
(statements isEmpty or: [ self isComment ]) ifTrue: [ ^ true ].
^ false
]

Expand Down Expand Up @@ -586,6 +586,13 @@ TStatementListNode >> removeAssertions [
self setStatements: newStatements asArray
]

{ #category : 'transformations' }
TStatementListNode >> removeLast [
"the last statement can be a comment if the TStatementList has been through inlining, remove the actual last statement"

statements := self allButLastNonCommentStatement
]

{ #category : 'dead-code-elimination' }
TStatementListNode >> removeUnusedNodesInBranch: aChild [
"this method should be only called when cleaning an AST tree after an unused expression was found, remove aChild from the list of statements"
Expand All @@ -595,13 +602,6 @@ TStatementListNode >> removeUnusedNodesInBranch: aChild [
self parent removeUnusedNodesInBranch: self ]
]

{ #category : 'transformations' }
TStatementListNode >> removeLast [
"the last statement can be a comment if the TStatementList has been through inlining, remove the actual last statement"

statements := self allButLastNonCommentStatement
]

{ #category : 'inlining support' }
TStatementListNode >> renameLabelsForInliningInto: aTMethod [
"TMethod already has a method for this; hijack it..."
Expand Down
6 changes: 3 additions & 3 deletions smalltalksrc/Slang/TSwitchStmtNode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -460,10 +460,10 @@ 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 an empty TStatementListNode, hence the following code"

cases := cases select: [ :each | each second ~~ aChild ].
(cases isEmpty or: [ self casesHasNothingButComments ])
ifFalse: [ ^ self ].
(cases isEmpty or: [ self casesHasNothingButComments ]) 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"
Expand Down

0 comments on commit d9798ac

Please sign in to comment.