Skip to content

Commit

Permalink
Merge pull request #824 from guillep/unspill
Browse files Browse the repository at this point in the history
Add unspill and new translations using static type prediction
  • Loading branch information
guillep authored Jul 4, 2024
2 parents 198b95b + 63c6cff commit f331bc2
Show file tree
Hide file tree
Showing 16 changed files with 16,007 additions and 1,448 deletions.
30 changes: 23 additions & 7 deletions smalltalksrc/Melchor/VMClass.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -287,13 +287,6 @@ VMClass class >> objectRepresentationClass [
^self objectMemoryClass objectRepresentationClass
]

{ #category : #accessing }
VMClass class >> resetInitializationOptions [

self release.
InitializationOptions := nil
]

{ #category : #translation }
VMClass class >> renameSelectorIfStaticallyResolved: aString [

Expand All @@ -302,6 +295,13 @@ VMClass class >> renameSelectorIfStaticallyResolved: aString [
ifFalse: [ ^ aString ]
]

{ #category : #accessing }
VMClass class >> resetInitializationOptions [

self release.
InitializationOptions := nil
]

{ #category : #translation }
VMClass class >> shouldGenerateTypedefFor: aStructClass [
"Hack to work-around multiple definitions. Sometimes a type has been defined in an include."
Expand Down Expand Up @@ -577,6 +577,14 @@ VMClass >> druidForceIntepretation [
"Ignore in the interpreter"
]

{ #category : #'druid support' }
VMClass >> druidIf: conditionToCompile do: aBlock [

"Execute the block during interpretation, ignore it during compilation unless the compile option is given.
Should be used only to avoid extra fast-cases during compilation"
^ aBlock value
]

{ #category : #'druid support' }
VMClass >> druidIgnore: aBlock [

Expand All @@ -585,6 +593,14 @@ VMClass >> druidIgnore: aBlock [
^ aBlock value
]

{ #category : #'druid support' }
VMClass >> druidStageable: aBlock [

"Execute the block during interpretation, stage it during compilation.
Should be used only with expressions that are known to be constant at JIT-compile time"
^ aBlock value
]

{ #category : #'memory access' }
VMClass >> fetchSingleFloatAtPointer: pointer into: aFloat [
"This gets implemented by Macros in C, where its types will also be checked.
Expand Down
2 changes: 1 addition & 1 deletion smalltalksrc/VMMaker/CogARMv8Compiler.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -5668,7 +5668,7 @@ CogARMv8Compiler >> rewriteCallFullAt: callSiteReturnAddress target: callTargetA
^self
rewriteFullTransferAt: callSiteReturnAddress
target: callTargetAddress
expectedInstruction: 16rE12FFF3C
expectedInstruction: 16rD63F0200
]

{ #category : #'inline cacheing' }
Expand Down
Loading

0 comments on commit f331bc2

Please sign in to comment.