Skip to content

Commit

Permalink
New harmonize rule (#817)
Browse files Browse the repository at this point in the history
Simple new rule for harmonization

- change in the tests to adapt to new rule
- add some test for negative number
- test for a more non-destructive rule
  • Loading branch information
RenaudFondeur authored Jun 19, 2024
1 parent c012a6b commit 44ddd63
Show file tree
Hide file tree
Showing 6 changed files with 162 additions and 156 deletions.
52 changes: 33 additions & 19 deletions smalltalksrc/Melchor/MLVMCCodeGenerator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -292,28 +292,42 @@ MLVMCCodeGenerator >> emitGlobalCVariablesOn: aStream [
aStream newLine
]

{ #category : #'C code generator' }
{ #category : #'type inference' }
MLVMCCodeGenerator >> harmonizeIntegerIn: aSetOfTypes [
"help to decide if the element in a SetOfTypes will be treated as signed or unsigned.
only add sqInt to the types if an usqInt isn't here to prevent signing method returning usqInt."
| constantIntegers |
constantIntegers := aSetOfTypes select: [ :element |
element isInteger ].
constantIntegers notEmpty ifFalse: [ ^ self ].
aSetOfTypes removeAll: constantIntegers.
(aSetOfTypes includes: #usqInt) ifTrue: [ ^ self ].
aSetOfTypes add: #sqInt
]

{ #category : #'type inference' }
MLVMCCodeGenerator >> harmonizeReturnTypesIn: aSetOfTypes [
"Eliminate signed/unsigned conflicts in aSetOfTypes. Non-negative integers can be either
signed or unsigned. Ignore them unless there are no types, in which case default to sqInt."
| constantIntegers sqs usqs |
constantIntegers := aSetOfTypes select: [:element| element isInteger].
aSetOfTypes removeAll: constantIntegers.
signed or unsigned. if possible the type will default to the signed part"

| sqs usqs |
"N.B. Because of LP64 vs LLP64 issues do *not* rename #long to #sqInt or #'unsigned long' to #usqInt"
#(char short int #'long long' #'unsigned char' #'unsigned short' #'unsigned int' #'unsigned long long')
with: #(sqInt sqInt sqInt sqLong usqInt usqInt usqInt usqLong)
do: [:type :replacement|
(aSetOfTypes includes: type) ifTrue:
[aSetOfTypes remove: type; add: replacement]].
sqs := aSetOfTypes select: [:t| t beginsWith: 'sq'].
usqs := aSetOfTypes select: [:t| t beginsWith: 'usq'].
^(sqs size + usqs size = aSetOfTypes size
and: [sqs notEmpty
and: [sqs allSatisfy: [:t| usqs includes: 'u', t]]])
ifTrue: [sqs]
ifFalse: [(aSetOfTypes isEmpty and: [constantIntegers notEmpty])
ifTrue: [Set with: self defaultType]
ifFalse: [aSetOfTypes]]
#( char short int #'long long' #'unsigned char' #'unsigned short'
#'unsigned int' #'unsigned long long' )
with: #( sqInt sqInt sqInt sqLong usqInt usqInt usqInt usqLong )
do: [ :type :replacement |
(aSetOfTypes includes: type) ifTrue: [
aSetOfTypes
remove: type;
add: replacement ] ].
self harmonizeIntegerIn: aSetOfTypes.
sqs := aSetOfTypes select: [ :t | t beginsWith: 'sq' ].
usqs := aSetOfTypes select: [ :t | t beginsWith: 'usq' ].
^ (sqs size + usqs size = aSetOfTypes size and: [
sqs notEmpty and: [
sqs allSatisfy: [ :t | usqs includes: 'u' , t ] ] ])
ifTrue: [ sqs ]
ifFalse: [ aSetOfTypes ]
]

{ #category : #'C code generator' }
Expand Down
18 changes: 3 additions & 15 deletions smalltalksrc/Slang-Tests/SLTypeHarmonizationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -254,13 +254,13 @@ SLTypeHarmonizationTest >> testHarmonizedNumber [
]

{ #category : #harmonizeTwoType }
SLTypeHarmonizationTest >> testHarmonizedNumberAndAnythingNotWorking [
"return anything"
SLTypeHarmonizationTest >> testHarmonizedNumberAndAnything [
"doesn't harmonize and produce a notification"
| result |
types add: 7.
types add: #anything.
result := ccg harmonizeReturnTypesIn: types.
self assert: result equals: (Set new add: #anything ; yourself ).
self assert: result equals: (Set new add: #anything ; add: #sqInt ; yourself ).


]
Expand All @@ -274,18 +274,6 @@ SLTypeHarmonizationTest >> testHarmonizedNumbers [
self assert: result equals: (Set new add: #sqInt ; yourself ).


]

{ #category : #harmonizeTwoType }
SLTypeHarmonizationTest >> testHarmonizedNumbersNotWorking [
"the type always default to int"
| result |
types add: 7.
types add: -2147483648.
result := ccg harmonizeReturnTypesIn: types.
self assert: result equals: (Set new add: #sqInt ; yourself ).


]

{ #category : #harmonizeOneType }
Expand Down
Loading

0 comments on commit 44ddd63

Please sign in to comment.