Skip to content

Commit

Permalink
Merge pull request #20 from janvrany/pr/misc-improvements-V
Browse files Browse the repository at this point in the history
Misc improvements and bug fixes IV
  • Loading branch information
janvrany authored Jun 17, 2023
2 parents f6590e8 + 8d8a75a commit 1782398
Show file tree
Hide file tree
Showing 36 changed files with 4,187 additions and 3,922 deletions.
2 changes: 1 addition & 1 deletion opcodesgen/opcodesgen.m4
Original file line number Diff line number Diff line change
Expand Up @@ -154,7 +154,7 @@ OPCODE_NAME($1): arguments
^ self build: OPCODE_NAME($1) arguments: arguments
!
])
!TRILBuilder methodsFor:'building'!
!TRILBuilderBase methodsFor:'building'!
include(opcodes.m4)
!
undefine([OPCODE_MACRO])
Expand Down
2 changes: 1 addition & 1 deletion src/Tinyrossa-POWER/TRPPC64RegisterKinds.class.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Class {
#name : #TRPPC64RegisterKinds,
#superclass : #SharedPool,
#superclass : #TRSharedPool,
#classVars : [
'GPR',
'FPR',
Expand Down
2 changes: 1 addition & 1 deletion src/Tinyrossa-POWER/TRPPC64Registers.class.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Class {
#name : #TRPPC64Registers,
#superclass : #SharedPool,
#superclass : #TRSharedPool,
#classVars : [
'cr0',
'cr1',
Expand Down
2 changes: 1 addition & 1 deletion src/Tinyrossa-RISCV/TRRV64GRegisters.class.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Class {
#name : #TRRV64GRegisters,
#superclass : #SharedPool,
#superclass : #TRSharedPool,
#classVars : [
'zero',
'ra',
Expand Down
14 changes: 13 additions & 1 deletion src/Tinyrossa/TRCFG.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ TRCFG >> addBlockNamed: aStringOrNil [

block := TRILBlock forCFG: self named: name.
blocks add: block.
entry isNil ifTrue:[entry := block].
entry isNil ifTrue:[self entry: block].

^ block
]
Expand All @@ -59,6 +59,18 @@ TRCFG >> entry [
^ entry
]

{ #category : #accessing }
TRCFG >> entry: aTRILBlock [
"Set the entry block.
Please note that entry block is set automatically when first block
is allocated. This method is for internal use in cases one need
modify entry block after TRIL is generated (for example, CFG simplifier
removing empty entry block)."

entry := aTRILBlock
]

{ #category : #initialization }
TRCFG >> initializeWithCompilation: aTRCompilation [
compilation := aTRCompilation.
Expand Down
15 changes: 13 additions & 2 deletions src/Tinyrossa/TRCFGSimplifier.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -58,11 +58,11 @@ TRCFGSimplifier >> simplify [
modified := true.
].

(self tryRemove: block) ifTrue: [
(self tryCombine: block) ifTrue: [
modified := true.
].

(self tryCombine: block) ifTrue: [
(self tryRemove: block) ifTrue: [
modified := true.
].

Expand Down Expand Up @@ -185,6 +185,17 @@ TRCFGSimplifier >> tryRemove: block [
block precedessors do: [:precedessor |
self relink: block to: block successor1 in: precedessor
].

"Handle the case we're removing (empty) entry block.
In this case we have to set CFG's entry block to
successor1 - but only if there's one, otherwise we'd
make CFG with no entry block which is illegal!"
block == compilation cfg entry ifTrue:[
block successor1 notNil ifTrue:[
compilation cfg entry: block successor1
]
].

^ true.
].
^ false.
Expand Down
14 changes: 0 additions & 14 deletions src/Tinyrossa/TRCodeEvaluator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -66,20 +66,6 @@ TRCodeEvaluator >> evaluate_bbend: node [
TRCodeEvaluator >> evaluate_bbstart: node [
| label |

node block isExtension ifFalse: [
| automatics parameters |

automatics := codegen compilation symbolManager lookupSymbolsByType: TRAutomaticSymbol.
automatics do: [:automatic |
automatic setRegister: nil.
].

parameters := codegen compilation symbolManager lookupSymbolsByType: TRParameterSymbol.
parameters do: [:parameter |
parameter setRegister: nil.
].
].

label := self compilation symbolManager lookupLabelByBlock: node block.
(label notNil and: [label isUsed]) ifTrue: [
generate label: label name.
Expand Down
2 changes: 1 addition & 1 deletion src/Tinyrossa/TRCompilationConfigOptions.class.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Class {
#name : #TRCompilationConfigOptions,
#superclass : #SharedPool,
#superclass : #TRSharedPool,
#classVars : [
'OptionAOT',
'OptionLinkage',
Expand Down
24 changes: 24 additions & 0 deletions src/Tinyrossa/TRCompilationExamples.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -526,6 +526,30 @@ TRCompilationExamples >> example09_signum_2 [
compilation codeBuffer. "Only convenience inspection."
]

{ #category : #examples }
TRCompilationExamples >> example12_call_external_function [
| builder |

builder := compilation builder.
builder defineName: 'caller' type: Int32.

"Here we define function named 'callee' returning Int32
at address 0xCAFECAFECAFECAFE."
(builder defineFunction: 'callee' type: Int32)
setAddress: 16r000000007AFECAFE.

builder ireturn:
{ builder icall:
{ 'callee' } }.


compilation optimize.

compilation compile.

compilation codeBuffer. "Only convenience inspection."
]

{ #category : #running }
TRCompilationExamples >> setUp [
super setUp.
Expand Down
62 changes: 59 additions & 3 deletions src/Tinyrossa/TRDataType.class.st
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
Class {
#name : #TRDataType,
#superclass : #Object,
#pools : [
'TRILOpcodeTables'
],
#category : #'Tinyrossa-Datatypes'
}

Expand All @@ -20,6 +23,60 @@ TRDataType class >> named: aString [
"
]

{ #category : #queries }
TRDataType >> arithmeticOpcodeFor: arithmeticOpFlag [
"Return opcode for peforming arithmetic operation on two values
of receiver's type.
`arithmeticOpFlag` specifies the kind of operation wanted as
one of `Add`, `Sub`, `Mul`. `Div` or `Rem` (see pool `TRILOpcodeProps1`).
"
^ (ArithmeticOpcodes at: self)
at: arithmeticOpFlag ifAbsent: [ self error:'No opcode for requested arithmetic operation' ]

"
Add := 16r00000008.
Sub := 16r00000010.
Mul := 16r00000020.
Div := 16r00000040.
Rem := 16r00000080.
(TRDataType named: 'Int32') arithmeticOpcodeFor: 16r00000020
(TRDataType named: 'Address') compareOpcodeFor: 16r00000008.
(TRDataType named: 'Void') compareOpcodeFor: 16r00000008.
"
]

{ #category : #queries }
TRDataType >> compareOpcodeFor: compareFlags [
"Return opcode for comparing two values of receiver's type.
`compareFlags` specify the kind of comparison wanted as
bit mask of `CompareTrueIfEqual`, `CompareTrueIfGreater`, `CompareTrueIfLess`
or: `CompareTrueIfUnordered` (see pool `TRILOpcodeProps3`).
"
^ (CompareOpcodes at: self)
at: compareFlags ifAbsent: [ self error:'No opcode for requested comparison' ]

"
CompareTrueIfLess := 16r00000100.
CompareTrueIfGreater := 16r00000200.
CompareTrueIfEqual := 16r00000400.
CompareTrueIfUnordered := 16r00000800.
(TRDataType named: 'Int32') compareOpcodeFor: 16r00000100 | 16r00000400.
(TRDataType named: 'Address') compareOpcodeFor: 16r00000100.
(TRDataType named: 'Void') compareOpcodeFor: 16r00000100.
"
]

{ #category : #queries }
TRDataType >> constOpcode [
"Return opcode that can be used to load a constant of receiver's type"
^ ConstOpcodes at: self

"
(TRDataType named:'Float') constOpcode
"
]

{ #category : #testing }
TRDataType >> isCompatibleWith: anotherType [
self assert: (anotherType isKindOf: TRDataType).
Expand Down Expand Up @@ -47,11 +104,10 @@ TRDataType >> isVoidType [

{ #category : #queries }
TRDataType >> loadOpcode [
^ self subclassResponsibility
^ LoadOpcodes at: self

"
(TRDataType named:'Int32') loadOpcode
TRILOpcodes initialize
"
]

Expand All @@ -70,7 +126,7 @@ TRDataType >> printOn:aStream [

{ #category : #queries }
TRDataType >> storeOpcode [
^ self subclassResponsibility
^ StoreOpcodes at: self

"
(TRDataType named:'Int32') storeOpcode
Expand Down
10 changes: 0 additions & 10 deletions src/Tinyrossa/TRDataTypeAddress.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -12,21 +12,11 @@ TRDataTypeAddress >> isIntegerType [
^ true
]

{ #category : #queries }
TRDataTypeAddress >> loadOpcode [
^ aload
]

{ #category : #accessing }
TRDataTypeAddress >> name [
^ 'Address'
]

{ #category : #queries }
TRDataTypeAddress >> storeOpcode [
^ astore
]

{ #category : #validation }
TRDataTypeAddress >> validateConstant: aNumber [
" TODO: care for 32bit archs somehow"
Expand Down
10 changes: 0 additions & 10 deletions src/Tinyrossa/TRDataTypeDouble.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -12,21 +12,11 @@ TRDataTypeDouble >> isFloatingPointType [
^ true
]

{ #category : #queries }
TRDataTypeDouble >> loadOpcode [
^ dload
]

{ #category : #accessing }
TRDataTypeDouble >> name [
^ 'Double'
]

{ #category : #queries }
TRDataTypeDouble >> storeOpcode [
^ dstore
]

{ #category : #validation }
TRDataTypeDouble >> validateConstant: aNumber [
self assert: aNumber isFloat
Expand Down
10 changes: 0 additions & 10 deletions src/Tinyrossa/TRDataTypeFloat.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -12,21 +12,11 @@ TRDataTypeFloat >> isFloatingPointType [
^ true
]

{ #category : #queries }
TRDataTypeFloat >> loadOpcode [
^ fload
]

{ #category : #accessing }
TRDataTypeFloat >> name [
^ 'Float'
]

{ #category : #queries }
TRDataTypeFloat >> storeOpcode [
^ fstore
]

{ #category : #validation }
TRDataTypeFloat >> validateConstant: aNumber [
self assert: aNumber isFloat
Expand Down
10 changes: 0 additions & 10 deletions src/Tinyrossa/TRDataTypeInt16.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -12,21 +12,11 @@ TRDataTypeInt16 >> isIntegerType [
^ true
]

{ #category : #queries }
TRDataTypeInt16 >> loadOpcode [
^ sload
]

{ #category : #accessing }
TRDataTypeInt16 >> name [
^ 'Int16'
]

{ #category : #queries }
TRDataTypeInt16 >> storeOpcode [
^ sstore
]

{ #category : #validation }
TRDataTypeInt16 >> validateConstant: aNumber [
self assert: (aNumber between: -16r8000 and: 16r7FFF) description: 'Invalid constant'
Expand Down
10 changes: 0 additions & 10 deletions src/Tinyrossa/TRDataTypeInt32.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -12,21 +12,11 @@ TRDataTypeInt32 >> isIntegerType [
^ true
]

{ #category : #queries }
TRDataTypeInt32 >> loadOpcode [
^ iload
]

{ #category : #accessing }
TRDataTypeInt32 >> name [
^ 'Int32'
]

{ #category : #queries }
TRDataTypeInt32 >> storeOpcode [
^ istore
]

{ #category : #validation }
TRDataTypeInt32 >> validateConstant: aNumber [
self assert: (aNumber between: -16r80000000 and: 16r7FFFFFFF) description: 'Invalid constant'
Expand Down
10 changes: 0 additions & 10 deletions src/Tinyrossa/TRDataTypeInt64.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -12,21 +12,11 @@ TRDataTypeInt64 >> isIntegerType [
^ true
]

{ #category : #queries }
TRDataTypeInt64 >> loadOpcode [
^ lload
]

{ #category : #accessing }
TRDataTypeInt64 >> name [
^ 'Int64'
]

{ #category : #queries }
TRDataTypeInt64 >> storeOpcode [
^ lstore
]

{ #category : #validation }
TRDataTypeInt64 >> validateConstant: aNumber [
self assert: (aNumber between: -16r8000000000000000 and: 16r7FFFFFFFFFFFFFFF) description: 'Invalid constant'
Expand Down
10 changes: 0 additions & 10 deletions src/Tinyrossa/TRDataTypeInt8.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -12,21 +12,11 @@ TRDataTypeInt8 >> isIntegerType [
^ true
]

{ #category : #queries }
TRDataTypeInt8 >> loadOpcode [
^ bload
]

{ #category : #accessing }
TRDataTypeInt8 >> name [
^ 'Int8'
]

{ #category : #queries }
TRDataTypeInt8 >> storeOpcode [
^ bstore
]

{ #category : #validation }
TRDataTypeInt8 >> validateConstant: aNumber [
self assert: (aNumber between: -16r80 and: 16r7F) description: 'Invalid constant'
Expand Down
Loading

0 comments on commit 1782398

Please sign in to comment.