Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 5 additions & 2 deletions src/Kernel-BytecodeEncoders/EncoderForSistaV1.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1030,10 +1030,13 @@ EncoderForSistaV1 >> genPushCharacter: aCharacterOrCode [

{ #category : 'bytecode generation' }
EncoderForSistaV1 >> genPushConsArray: size [
(size < 0 or: [size > 127]) ifTrue:
[^self outOfRangeError: 'size' index: size range: 0 to: 127].
"231 11100111 jkkkkkkk Push (Array new: kkkkkkk) (j = 0)
& Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)"
| limit |
limit := OCIRPushArray sizeLimit.
(size < 0 or: [size > limit]) ifTrue:
[^self outOfRangeError: 'size' index: size range: 0 to: limit].

stream
nextPut: 231;
nextPut: size + 128
Expand Down
6 changes: 6 additions & 0 deletions src/Kernel-CodeModel/CompiledCode.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,12 @@ Class {
#tag : 'Methods'
}

{ #category : 'class initialization' }
CompiledCode class >> LargeFrame [

^ LargeFrame
]

{ #category : 'instance creation' }
CompiledCode class >> basicNew [

Expand Down
11 changes: 6 additions & 5 deletions src/OpalCompiler-Core/OCASTTranslator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -555,12 +555,13 @@ OCASTTranslator >> visitAnnotationMarkNode: aAnnotationValueNode [
{ #category : 'visitor - double dispatching' }
OCASTTranslator >> visitArrayNode: anArrayNode [

| elementNodes |

anArrayNode statements size > 32 ifTrue: [^ self visitLargeArrayNode: anArrayNode ].
| elementNodes stackLimit |
stackLimit := CompiledCode LargeFrame min: OCIRPushArray sizeLimit.
methodBuilder stackSize + anArrayNode statements size > stackLimit ifTrue: [
^ self visitLargeArrayNode: anArrayNode ].

elementNodes := anArrayNode children.
elementNodes do: [:node | self visitNode: node].
elementNodes do: [ :node | self visitNode: node ].
methodBuilder pushConsArray: elementNodes size
]

Expand Down Expand Up @@ -706,7 +707,7 @@ OCASTTranslator >> visitInlinedBlockNode: anOptimizedBlockNode [

{ #category : 'visitor - double dispatching' }
OCASTTranslator >> visitLargeArrayNode: anArrayNode [
"Long form: using at:put:"
"Long approach using at:put:"
methodBuilder pushLiteralVariable: Array binding.
methodBuilder pushLiteral: anArrayNode statements size.
methodBuilder send: #new:.
Expand Down
12 changes: 11 additions & 1 deletion src/OpalCompiler-Core/OCIRBuilder.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,8 @@ Class {
'jumpAheadStacks',
'currentSequence',
'sourceMapNodes',
'sourceMapByteIndex'
'sourceMapByteIndex',
'stackSize'
],
#category : 'OpalCompiler-Core-IR-Manipulation',
#package : 'OpalCompiler-Core',
Expand All @@ -56,6 +57,8 @@ OCIRBuilder >> add: instr [
"Associate instr with current parse node or byte range"
instr sourceNode: self sourceNode.
instr bytecodeIndex: self sourceByteIndex.

stackSize := stackSize + instr deltaStack.
^ currentSequence add: instr
]

Expand Down Expand Up @@ -175,6 +178,7 @@ OCIRBuilder >> initialize [
jumpBackTargetStacks := IdentityDictionary new.
sourceMapNodes := OrderedCollection new. "stack"
currentScope := Stack new.
stackSize := 0.
self pushScope: ir.

"Leave an empty sequence up front (guaranteed not to be in loop)"
Expand Down Expand Up @@ -425,6 +429,12 @@ OCIRBuilder >> sourceNode [
ifNotEmpty: [sourceMapNodes last]
]

{ #category : 'accessing' }
OCIRBuilder >> stackSize [

^ stackSize
]

{ #category : 'private' }
OCIRBuilder >> startNewSequence [
"End current instruction sequence and start a new sequence to add instructions to. If ending block just falls through to new block then add an explicit jump to it so they stay linked"
Expand Down
12 changes: 12 additions & 0 deletions src/OpalCompiler-Core/OCIRInstruction.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -250,6 +250,18 @@ OCIRInstruction >> delete [
sequence remove: self
]

{ #category : 'stack' }
OCIRInstruction >> deltaStack [

"This method indicates the number of elements that the current instruction introduces or removes from the execution stack.
n > 0 -> push n elements to the stack
n = 0 -> the stack does not change
n < 0 -> pop n elements from the stack
"

^ 0
]

{ #category : 'testing' }
OCIRInstruction >> isBlockReturnTop [

Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPop.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,12 @@ OCIRPop >> accept: aVisitor [
^ aVisitor visitPop: self
]

{ #category : 'stack' }
OCIRPop >> deltaStack [

^ -1
]

{ #category : 'testing' }
OCIRPop >> isPop [
^true
Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPopIntoInstVar.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -13,3 +13,9 @@ Class {
OCIRPopIntoInstVar >> accept: aVisitor [
^ aVisitor visitPopIntoInstVar: self
]

{ #category : 'stack' }
OCIRPopIntoInstVar >> deltaStack [

^ -1
]
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPopIntoLiteralVariable.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -13,3 +13,9 @@ Class {
OCIRPopIntoLiteralVariable >> accept: aVisitor [
^ aVisitor visitPopIntoLiteralVariable: self
]

{ #category : 'stack' }
OCIRPopIntoLiteralVariable >> deltaStack [

^ -1
]
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPopIntoRemoteTemp.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -13,3 +13,9 @@ Class {
OCIRPopIntoRemoteTemp >> accept: aVisitor [
^ aVisitor visitPopIntoRemoteTemp: self
]

{ #category : 'stack' }
OCIRPopIntoRemoteTemp >> deltaStack [

^ -1
]
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPopIntoTemp.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,12 @@ OCIRPopIntoTemp >> accept: aVisitor [
^ aVisitor visitPopIntoTemp: self
]

{ #category : 'stack' }
OCIRPopIntoTemp >> deltaStack [

^ -1
]

{ #category : 'accessing' }
OCIRPopIntoTemp >> nextBytecodeOffsetAfterJump [
"if we are in to:do: answers the next byte code offset"
Expand Down
14 changes: 14 additions & 0 deletions src/OpalCompiler-Core/OCIRPushArray.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,12 @@ Class {
#tag : 'IR-Nodes'
}

{ #category : 'accessing' }
OCIRPushArray class >> sizeLimit [

^ 127
]

{ #category : 'visiting' }
OCIRPushArray >> accept: aVisitor [
^ aVisitor visitPushArray: self
Expand All @@ -30,6 +36,14 @@ OCIRPushArray >> cons: aBool [
cons := aBool
]

{ #category : 'stack' }
OCIRPushArray >> deltaStack [

^ cons
ifTrue: [ (size - 1) negated ]
ifFalse: [ 1 ]
]

{ #category : 'initialization' }
OCIRPushArray >> initialize [
size := 0.
Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushDup.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,12 @@ OCIRPushDup >> accept: aVisitor [
^ aVisitor visitPushDup: self
]

{ #category : 'stack' }
OCIRPushDup >> deltaStack [

^ 1
]

{ #category : 'testing' }
OCIRPushDup >> isRemovableByPop [

Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushFullClosure.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,12 @@ OCIRPushFullClosure >> copiedValues: anObject [
copiedValues := anObject
]

{ #category : 'stack' }
OCIRPushFullClosure >> deltaStack [

^( copiedValues size - 1) negated
]

{ #category : 'debugging' }
OCIRPushFullClosure >> indexForVarNamed: aName [
^ sourceNode ir indexForVarNamed: aName
Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushInstVar.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,12 @@ OCIRPushInstVar >> canBeQuickReturn [
^ true
]

{ #category : 'stack' }
OCIRPushInstVar >> deltaStack [

^ 1
]

{ #category : 'testing' }
OCIRPushInstVar >> isRemovableByPop [

Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushLiteral.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,12 @@ OCIRPushLiteral >> canBeQuickReturn [
^ #( nil true false -1 0 1 2 ) includes: literal
]

{ #category : 'stack' }
OCIRPushLiteral >> deltaStack [

^ 1
]

{ #category : 'testing' }
OCIRPushLiteral >> isPushLiteral [

Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushLiteralVariable.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -13,3 +13,9 @@ Class {
OCIRPushLiteralVariable >> accept: aVisitor [
^ aVisitor visitPushLiteralVariable: self
]

{ #category : 'stack' }
OCIRPushLiteralVariable >> deltaStack [

^ 1
]
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushReceiver.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,12 @@ OCIRPushReceiver >> canBeQuickReturn [
^ true
]

{ #category : 'stack' }
OCIRPushReceiver >> deltaStack [

^ 1
]

{ #category : 'testing' }
OCIRPushReceiver >> isRemovableByPop [

Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushRemoteTemp.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,12 @@ OCIRPushRemoteTemp >> accept: aVisitor [
^ aVisitor visitPushRemoteTemp: self
]

{ #category : 'stack' }
OCIRPushRemoteTemp >> deltaStack [

^ 1
]

{ #category : 'testing' }
OCIRPushRemoteTemp >> isRemovableByPop [

Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushTemp.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,12 @@ OCIRPushTemp >> accept: aVisitor [
^ aVisitor visitPushTemp: self
]

{ #category : 'stack' }
OCIRPushTemp >> deltaStack [

^ 1
]

{ #category : 'testing' }
OCIRPushTemp >> isRemovableByPop [

Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushThisContext.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,12 @@ OCIRPushThisContext >> accept: aVisitor [
^ aVisitor visitPushThisContext: self
]

{ #category : 'stack' }
OCIRPushThisContext >> deltaStack [

^ 1
]

{ #category : 'testing' }
OCIRPushThisContext >> isRemovableByPop [

Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRPushThisProcess.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,12 @@ OCIRPushThisProcess >> accept: aVisitor [
^ aVisitor visitPushThisProcess: self
]

{ #category : 'stack' }
OCIRPushThisProcess >> deltaStack [

^ 1
]

{ #category : 'testing' }
OCIRPushThisProcess >> isRemovableByPop [

Expand Down
6 changes: 6 additions & 0 deletions src/OpalCompiler-Core/OCIRSend.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,12 @@ OCIRSend >> accept: aVisitor [
^ aVisitor visitSend: self
]

{ #category : 'stack' }
OCIRSend >> deltaStack [

^ (selector occurrencesOf: $:) negated
]
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

We should think about if OCIRSend should not betterknow the number of arguments of the send (it could be set once when we create it). Bu this is a future improvement.


{ #category : 'testing' }
OCIRSend >> isSend [
^true
Expand Down
17 changes: 17 additions & 0 deletions src/OpalCompiler-Tests/OCArrayLiteralTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,23 @@ OCArrayLiteralTest >> testByteArrayWithinArray [
self assert: array last first equals: 2
]

{ #category : 'tests' }
OCArrayLiteralTest >> testLiteralArrayLongHavingAnotherArrayLong [

| method array elements |
elements := ((1 to: 32) inject: ' ' into: [ :r :e | r , ' . ' , e asString ]).
array := ' { ' , elements , ' }'.
array := array copyReplaceAll: '32' with: array.

method := self compile: 'array ^' , array.
array := method valueWithReceiver: #().

self assert: ( array isKindOf: Array).
self assert: array size equals: 32.
1 to: 31 do: [ :index | self assert: (array at: index) equals: index ].
1 to: 32 do: [ :index | self assert: ((array at: 32) at: index) equals: index ].
]

{ #category : 'tests' }
OCArrayLiteralTest >> testReservedIdentifiers [

Expand Down
12 changes: 12 additions & 0 deletions src/OpalCompiler-Tests/OCOpalExamples.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,18 @@ OCOpalExamples >> exampleDoublePrimitive [
<primitive: 1>
]

{ #category : 'examples - misc' }
OCOpalExamples >> exampleDynamicLiteralArraySize32AndSize32 [

^ { 255 . 255 . 255 . 255 .255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . { 255 . 255 . 255 . 255 .255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 } }
]

{ #category : 'examples - misc' }
OCOpalExamples >> exampleDynamicLiteralArraySize33AndSize33 [

^ { 255 . 255 . 255 . 255 .255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . { 255 . 255 . 255 . 255 .255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 . 255 } }
]

{ #category : 'examples - blocks' }
OCOpalExamples >> exampleEffectValues [
#getMe.
Expand Down
2 changes: 1 addition & 1 deletion src/UIManager/Object.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ Object >> confirm: queryString [
{ #category : '*UIManager' }
Object >> inform: aString [
"Display a message for the user to read and then dismiss."

self halt.
"DO NOT CALL THIS METHOD!"
aString isEmptyOrNil
Expand Down