Skip to content

Commit

Permalink
prepare comment support
Browse files Browse the repository at this point in the history
  • Loading branch information
RenaudFondeur committed Aug 13, 2024
1 parent f20ba09 commit dea0ed9
Show file tree
Hide file tree
Showing 4 changed files with 32 additions and 4 deletions.
9 changes: 8 additions & 1 deletion smalltalksrc/Slang/TParseNode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -201,6 +201,13 @@ TParseNode >> hasExplicitReturn [
^false
]

{ #category : 'testing' }
TParseNode >> hasNothingButComments [
"an alternative to isEmpty related to inlining"

^ self children allSatisfy: [ :child | child isComment ]
]

{ #category : 'testing' }
TParseNode >> hasSideEffect [
"Answer if the parse tree rooted at this node has a side-effect or not. By default assume it has. Nodes that don't override."
Expand Down Expand Up @@ -452,7 +459,7 @@ TParseNode >> removeUnusedNodesInBranch: aChild [
"this method should be only called when cleaning an AST tree after an unused expression was found"

self children remove: aChild.
self children isEmpty ifTrue: [
(self children isEmpty or: [ self hasNothingButComments ]) ifTrue: [
self parent removeUnusedNodesInBranch: self ]
]

Expand Down
9 changes: 8 additions & 1 deletion smalltalksrc/Slang/TSendNode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,13 @@ TSendNode >> argumentsForInliningCodeGenerator: aCodeGen [
ifFalse: [arguments]
]

{ #category : 'testing' }
TSendNode >> argumentsHasNothingButComments [
"related to dead code elimination and inlining, see if the cases has nothing but comment meaning they are empty"

^ arguments allSatisfy: [ :arg | arg isComment ]
]

{ #category : 'tranforming' }
TSendNode >> asCASTAsFieldReferenceIn: aCodeGen [

Expand Down Expand Up @@ -567,7 +574,7 @@ TSendNode >> removeUnusedNodesInBranch: aChild [
| branchIndex |
branchIndex := arguments indexOf: aChild.
arguments := arguments select: [ :e | e ~= aChild ].
arguments isEmpty
(arguments isEmpty or: [ self argumentsHasNothingButComments ])
ifTrue: [
self transformReceiverAfterEmptyArguments.
self parent removeUnusedNodesInBranch: self ]
Expand Down
8 changes: 7 additions & 1 deletion smalltalksrc/Slang/TStatementListNode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -372,6 +372,12 @@ TStatementListNode >> initialize [
arguments := #()
]

{ #category : 'testing' }
TStatementListNode >> isComment [

^ self hasNothingButComments
]

{ #category : 'testing' }
TStatementListNode >> isEmptyStmtListNode [
"return true if the statement node is empty or has just a nil in it"
Expand Down Expand Up @@ -513,7 +519,7 @@ 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"

statements := statements select: [ :stmt | stmt ~~ aChild ].
statements isEmpty ifTrue: [
(statements isEmpty or: [ self hasNothingButComments ]) ifTrue: [
self parent removeUnusedNodesInBranch: self ]
]

Expand Down
10 changes: 9 additions & 1 deletion smalltalksrc/Slang/TSwitchStmtNode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -244,6 +244,13 @@ TSwitchStmtNode >> cases: anObject [
cases := anObject
]

{ #category : 'testing' }
TSwitchStmtNode >> casesHasNothingButComments [
"related to dead code elimination and inlining, see if the cases has nothing but comment meaning they are empty"

^ cases allSatisfy: [ :case | case second isComment ]
]

{ #category : 'accessing' }
TSwitchStmtNode >> children [

Expand Down Expand Up @@ -455,7 +462,8 @@ 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 ].
self cases isEmpty 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 dea0ed9

Please sign in to comment.