Skip to content

Commit

Permalink
Add parentheses to r-value to correctly generate C code during comple…
Browse files Browse the repository at this point in the history
…x inlining cases. For instance if the AST root is #at:, with a TSendNode(#+) as child, then we should generate:

	pTo1[i] = (pFrom + anInteger)[i];
	
	instead of the (incorrect):
	
	pTo1[i] = pFrom + anInteger[i];
	
Fix the test case.
  • Loading branch information
Hernán Morales Durand committed Sep 6, 2023
1 parent 9ef48d3 commit 24ff9e1
Show file tree
Hide file tree
Showing 3 changed files with 45 additions and 37 deletions.
60 changes: 30 additions & 30 deletions smalltalksrc/Slang-Tests/SlangBasicTranslationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1178,6 +1178,35 @@ SlangBasicTranslationTest >> testGoto [
self assert: translation equals: 'goto lab'
]
{ #category : #'tests-inlinemethod' }
SlangBasicTranslationTest >> testInlineMethodIfExpressionWithShiftRight [
| translation codeGenerator inlinedMethod cast printedString |
translation := (self getTMethodFrom: #methodToBeTranslatedWithIfAndShiftRight).
inlinedMethod := ((SlangBasicTranslationTestClass >> #methodWithIfAndShiftRight:) asTranslationMethodOfClass: TMethod).
codeGenerator := CCodeGeneratorGlobalStructure new.
codeGenerator
addMethod: translation;
addMethod: inlinedMethod;
doInlining: true.
cast := translation asCASTIn: codeGenerator.
printedString := String streamContents: [ :str | cast prettyPrintOn: str ].
self assert: cast isCompoundStatement.
self assert: printedString equals: '/* SlangBasicTranslationTestClass>>#methodToBeTranslatedWithIfAndShiftRight */
static sqInt
methodToBeTranslatedWithIfAndShiftRight(void)
{
/* begin methodWithIfAndShiftRight: */
((usqInt) (((2 < 0)
? 0
: 2)) ) >> ((2 - 1) * 32);
return 0;
}
'.
]
{ #category : #'tests-inline-builtins' }
SlangBasicTranslationTest >> testInlineMethodSumArgumentsWithAnnotations [
| tMethod translation |
Expand All @@ -1201,7 +1230,7 @@ methodUseParametersWithAnnotationstowith(unsigned int *pFrom, unsigned int *pTo,
/* begin methodFromWithAnnotations:to:len: */
pTo1 = ((unsigned int *) (yourself(pTo)) );
for (i = 0; i < 5; i += 1) {
pTo1[i] = pFrom + anInteger[i];
pTo1[i] = (pFrom + anInteger)[i];
};
return 0;
}'
Expand Down Expand Up @@ -1246,35 +1275,6 @@ methodUseParametersWithAnnotationsBuiltIntowith(unsigned int *pFrom, unsigned in
}'
]
{ #category : #'tests-inlinemethod' }
SlangBasicTranslationTest >> testInlineMethodIfExpressionWithShiftRight [
| translation codeGenerator inlinedMethod cast printedString |
translation := (self getTMethodFrom: #methodToBeTranslatedWithIfAndShiftRight).
inlinedMethod := ((SlangBasicTranslationTestClass >> #methodWithIfAndShiftRight:) asTranslationMethodOfClass: TMethod).
codeGenerator := CCodeGeneratorGlobalStructure new.
codeGenerator
addMethod: translation;
addMethod: inlinedMethod;
doInlining: true.
cast := translation asCASTIn: codeGenerator.
printedString := String streamContents: [ :str | cast prettyPrintOn: str ].
self assert: cast isCompoundStatement.
self assert: printedString equals: '/* SlangBasicTranslationTestClass>>#methodToBeTranslatedWithIfAndShiftRight */
static sqInt
methodToBeTranslatedWithIfAndShiftRight(void)
{
/* begin methodWithIfAndShiftRight: */
((usqInt) (((2 < 0)
? 0
: 2)) ) >> ((2 - 1) * 32);
return 0;
}
'.
]
{ #category : #'tests-inlinenode' }
SlangBasicTranslationTest >> testInlineNodeDoesNotInitializeReadBeforeWrittenArrayTemp [
Expand Down
12 changes: 6 additions & 6 deletions smalltalksrc/Slang-Tests/SlangBasicTranslationTestClass.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -103,6 +103,12 @@ SlangBasicTranslationTestClass >> methodFromWithAnnotations: pFrom to: pTo len:
^ 0
]

{ #category : #inline }
SlangBasicTranslationTestClass >> methodToBeTranslatedWithIfAndShiftRight [

self methodWithIfAndShiftRight: 2
]

{ #category : #'generation-targets' }
SlangBasicTranslationTestClass >> methodUseParametersWithAnnotations: pFrom to: pTo with: anInteger [

Expand All @@ -125,12 +131,6 @@ SlangBasicTranslationTestClass >> methodUseParametersWithAnnotationsBuiltIn: pFr
to: pTo
]

{ #category : #inline }
SlangBasicTranslationTestClass >> methodToBeTranslatedWithIfAndShiftRight [

self methodWithIfAndShiftRight: 2
]

{ #category : #inline }
SlangBasicTranslationTestClass >> methodUsingSingleArrayVariable [

Expand Down
10 changes: 9 additions & 1 deletion smalltalksrc/Slang/CCodeGenerator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1530,9 +1530,17 @@ CCodeGenerator >> generateCASTAsVoidPointer: tast [
{ #category : #'CAST translation' }
CCodeGenerator >> generateCASTAt: tast [
"Add parentheses to r-value to correctly generate C code during complex inlining cases. For instance if the AST root is #at:, with a TSendNode(#+) as child, then we should generate:

pTo1[i] = (pFrom + anInteger)[i];

instead of the (incorrect):

pTo1[i] = pFrom + anInteger[i];

"
^ CArrayAccessNode
array: (tast receiver asCASTExpressionIn: self)
array: ((tast receiver asCASTExpressionIn: self) needsParentheses: true)
index: (tast arguments first asCASTExpressionIn: self)
]
Expand Down

0 comments on commit 24ff9e1

Please sign in to comment.