diff --git a/smalltalksrc/Slang/TParseNode.class.st b/smalltalksrc/Slang/TParseNode.class.st index 674fb93d7a..11896d43f1 100644 --- a/smalltalksrc/Slang/TParseNode.class.st +++ b/smalltalksrc/Slang/TParseNode.class.st @@ -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." @@ -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 ] ] diff --git a/smalltalksrc/Slang/TSendNode.class.st b/smalltalksrc/Slang/TSendNode.class.st index 3334a7204f..3bc494c956 100644 --- a/smalltalksrc/Slang/TSendNode.class.st +++ b/smalltalksrc/Slang/TSendNode.class.st @@ -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 [ @@ -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 ] diff --git a/smalltalksrc/Slang/TStatementListNode.class.st b/smalltalksrc/Slang/TStatementListNode.class.st index 648f115ea2..31f41b28a4 100644 --- a/smalltalksrc/Slang/TStatementListNode.class.st +++ b/smalltalksrc/Slang/TStatementListNode.class.st @@ -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" @@ -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 ] ] diff --git a/smalltalksrc/Slang/TSwitchStmtNode.class.st b/smalltalksrc/Slang/TSwitchStmtNode.class.st index 4f10b0fac9..5881d98755 100644 --- a/smalltalksrc/Slang/TSwitchStmtNode.class.st +++ b/smalltalksrc/Slang/TSwitchStmtNode.class.st @@ -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 [ @@ -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"