diff --git a/src/Kernel-BytecodeEncoders/EncoderForSistaV1.class.st b/src/Kernel-BytecodeEncoders/EncoderForSistaV1.class.st index 32307c42920..bb46fefdf36 100644 --- a/src/Kernel-BytecodeEncoders/EncoderForSistaV1.class.st +++ b/src/Kernel-BytecodeEncoders/EncoderForSistaV1.class.st @@ -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 diff --git a/src/Kernel-CodeModel/CompiledCode.class.st b/src/Kernel-CodeModel/CompiledCode.class.st index 583d5657af4..a688e07b386 100644 --- a/src/Kernel-CodeModel/CompiledCode.class.st +++ b/src/Kernel-CodeModel/CompiledCode.class.st @@ -39,6 +39,12 @@ Class { #tag : 'Methods' } +{ #category : 'class initialization' } +CompiledCode class >> LargeFrame [ + + ^ LargeFrame +] + { #category : 'instance creation' } CompiledCode class >> basicNew [ diff --git a/src/OpalCompiler-Core/OCASTTranslator.class.st b/src/OpalCompiler-Core/OCASTTranslator.class.st index 5c98c498a31..8745424f1a2 100644 --- a/src/OpalCompiler-Core/OCASTTranslator.class.st +++ b/src/OpalCompiler-Core/OCASTTranslator.class.st @@ -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 ] @@ -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:. diff --git a/src/OpalCompiler-Core/OCIRBuilder.class.st b/src/OpalCompiler-Core/OCIRBuilder.class.st index 793f42bafa2..769cf7b82b2 100644 --- a/src/OpalCompiler-Core/OCIRBuilder.class.st +++ b/src/OpalCompiler-Core/OCIRBuilder.class.st @@ -33,7 +33,8 @@ Class { 'jumpAheadStacks', 'currentSequence', 'sourceMapNodes', - 'sourceMapByteIndex' + 'sourceMapByteIndex', + 'stackSize' ], #category : 'OpalCompiler-Core-IR-Manipulation', #package : 'OpalCompiler-Core', @@ -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 ] @@ -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)" @@ -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" diff --git a/src/OpalCompiler-Core/OCIRInstruction.class.st b/src/OpalCompiler-Core/OCIRInstruction.class.st index d94fcc580e5..55d390cf914 100644 --- a/src/OpalCompiler-Core/OCIRInstruction.class.st +++ b/src/OpalCompiler-Core/OCIRInstruction.class.st @@ -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 [ diff --git a/src/OpalCompiler-Core/OCIRPop.class.st b/src/OpalCompiler-Core/OCIRPop.class.st index 82f7855fa1d..24b807ae52b 100644 --- a/src/OpalCompiler-Core/OCIRPop.class.st +++ b/src/OpalCompiler-Core/OCIRPop.class.st @@ -14,6 +14,12 @@ OCIRPop >> accept: aVisitor [ ^ aVisitor visitPop: self ] +{ #category : 'stack' } +OCIRPop >> deltaStack [ + + ^ -1 +] + { #category : 'testing' } OCIRPop >> isPop [ ^true diff --git a/src/OpalCompiler-Core/OCIRPopIntoInstVar.class.st b/src/OpalCompiler-Core/OCIRPopIntoInstVar.class.st index 0c29e19f19a..d45e8563006 100644 --- a/src/OpalCompiler-Core/OCIRPopIntoInstVar.class.st +++ b/src/OpalCompiler-Core/OCIRPopIntoInstVar.class.st @@ -13,3 +13,9 @@ Class { OCIRPopIntoInstVar >> accept: aVisitor [ ^ aVisitor visitPopIntoInstVar: self ] + +{ #category : 'stack' } +OCIRPopIntoInstVar >> deltaStack [ + + ^ -1 +] diff --git a/src/OpalCompiler-Core/OCIRPopIntoLiteralVariable.class.st b/src/OpalCompiler-Core/OCIRPopIntoLiteralVariable.class.st index d2e9c15b935..8fa5b193237 100644 --- a/src/OpalCompiler-Core/OCIRPopIntoLiteralVariable.class.st +++ b/src/OpalCompiler-Core/OCIRPopIntoLiteralVariable.class.st @@ -13,3 +13,9 @@ Class { OCIRPopIntoLiteralVariable >> accept: aVisitor [ ^ aVisitor visitPopIntoLiteralVariable: self ] + +{ #category : 'stack' } +OCIRPopIntoLiteralVariable >> deltaStack [ + + ^ -1 +] diff --git a/src/OpalCompiler-Core/OCIRPopIntoRemoteTemp.class.st b/src/OpalCompiler-Core/OCIRPopIntoRemoteTemp.class.st index 7a1f602e35f..2e41e814376 100644 --- a/src/OpalCompiler-Core/OCIRPopIntoRemoteTemp.class.st +++ b/src/OpalCompiler-Core/OCIRPopIntoRemoteTemp.class.st @@ -13,3 +13,9 @@ Class { OCIRPopIntoRemoteTemp >> accept: aVisitor [ ^ aVisitor visitPopIntoRemoteTemp: self ] + +{ #category : 'stack' } +OCIRPopIntoRemoteTemp >> deltaStack [ + + ^ -1 +] diff --git a/src/OpalCompiler-Core/OCIRPopIntoTemp.class.st b/src/OpalCompiler-Core/OCIRPopIntoTemp.class.st index 483e2135a39..b795719ae73 100644 --- a/src/OpalCompiler-Core/OCIRPopIntoTemp.class.st +++ b/src/OpalCompiler-Core/OCIRPopIntoTemp.class.st @@ -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" diff --git a/src/OpalCompiler-Core/OCIRPushArray.class.st b/src/OpalCompiler-Core/OCIRPushArray.class.st index 118f909bee3..6db4d7922fa 100644 --- a/src/OpalCompiler-Core/OCIRPushArray.class.st +++ b/src/OpalCompiler-Core/OCIRPushArray.class.st @@ -15,6 +15,12 @@ Class { #tag : 'IR-Nodes' } +{ #category : 'accessing' } +OCIRPushArray class >> sizeLimit [ + + ^ 127 +] + { #category : 'visiting' } OCIRPushArray >> accept: aVisitor [ ^ aVisitor visitPushArray: self @@ -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. diff --git a/src/OpalCompiler-Core/OCIRPushDup.class.st b/src/OpalCompiler-Core/OCIRPushDup.class.st index 938f1b73e2c..a412a3e38a7 100644 --- a/src/OpalCompiler-Core/OCIRPushDup.class.st +++ b/src/OpalCompiler-Core/OCIRPushDup.class.st @@ -16,6 +16,12 @@ OCIRPushDup >> accept: aVisitor [ ^ aVisitor visitPushDup: self ] +{ #category : 'stack' } +OCIRPushDup >> deltaStack [ + + ^ 1 +] + { #category : 'testing' } OCIRPushDup >> isRemovableByPop [ diff --git a/src/OpalCompiler-Core/OCIRPushFullClosure.class.st b/src/OpalCompiler-Core/OCIRPushFullClosure.class.st index 334e7a1ec05..a64629d70ad 100644 --- a/src/OpalCompiler-Core/OCIRPushFullClosure.class.st +++ b/src/OpalCompiler-Core/OCIRPushFullClosure.class.st @@ -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 diff --git a/src/OpalCompiler-Core/OCIRPushInstVar.class.st b/src/OpalCompiler-Core/OCIRPushInstVar.class.st index 9b769210215..96edd06e2fb 100644 --- a/src/OpalCompiler-Core/OCIRPushInstVar.class.st +++ b/src/OpalCompiler-Core/OCIRPushInstVar.class.st @@ -19,6 +19,12 @@ OCIRPushInstVar >> canBeQuickReturn [ ^ true ] +{ #category : 'stack' } +OCIRPushInstVar >> deltaStack [ + + ^ 1 +] + { #category : 'testing' } OCIRPushInstVar >> isRemovableByPop [ diff --git a/src/OpalCompiler-Core/OCIRPushLiteral.class.st b/src/OpalCompiler-Core/OCIRPushLiteral.class.st index 6f4e0df5191..dd6f247cdc4 100644 --- a/src/OpalCompiler-Core/OCIRPushLiteral.class.st +++ b/src/OpalCompiler-Core/OCIRPushLiteral.class.st @@ -27,6 +27,12 @@ OCIRPushLiteral >> canBeQuickReturn [ ^ #( nil true false -1 0 1 2 ) includes: literal ] +{ #category : 'stack' } +OCIRPushLiteral >> deltaStack [ + + ^ 1 +] + { #category : 'testing' } OCIRPushLiteral >> isPushLiteral [ diff --git a/src/OpalCompiler-Core/OCIRPushLiteralVariable.class.st b/src/OpalCompiler-Core/OCIRPushLiteralVariable.class.st index 4cdbdb38a70..165694ce300 100644 --- a/src/OpalCompiler-Core/OCIRPushLiteralVariable.class.st +++ b/src/OpalCompiler-Core/OCIRPushLiteralVariable.class.st @@ -13,3 +13,9 @@ Class { OCIRPushLiteralVariable >> accept: aVisitor [ ^ aVisitor visitPushLiteralVariable: self ] + +{ #category : 'stack' } +OCIRPushLiteralVariable >> deltaStack [ + + ^ 1 +] diff --git a/src/OpalCompiler-Core/OCIRPushReceiver.class.st b/src/OpalCompiler-Core/OCIRPushReceiver.class.st index ac4e5f8e9c7..e98e712067b 100644 --- a/src/OpalCompiler-Core/OCIRPushReceiver.class.st +++ b/src/OpalCompiler-Core/OCIRPushReceiver.class.st @@ -19,6 +19,12 @@ OCIRPushReceiver >> canBeQuickReturn [ ^ true ] +{ #category : 'stack' } +OCIRPushReceiver >> deltaStack [ + + ^ 1 +] + { #category : 'testing' } OCIRPushReceiver >> isRemovableByPop [ diff --git a/src/OpalCompiler-Core/OCIRPushRemoteTemp.class.st b/src/OpalCompiler-Core/OCIRPushRemoteTemp.class.st index 085e21bdf14..f3561e70d18 100644 --- a/src/OpalCompiler-Core/OCIRPushRemoteTemp.class.st +++ b/src/OpalCompiler-Core/OCIRPushRemoteTemp.class.st @@ -14,6 +14,12 @@ OCIRPushRemoteTemp >> accept: aVisitor [ ^ aVisitor visitPushRemoteTemp: self ] +{ #category : 'stack' } +OCIRPushRemoteTemp >> deltaStack [ + + ^ 1 +] + { #category : 'testing' } OCIRPushRemoteTemp >> isRemovableByPop [ diff --git a/src/OpalCompiler-Core/OCIRPushTemp.class.st b/src/OpalCompiler-Core/OCIRPushTemp.class.st index 62883048279..1bfd6de2324 100644 --- a/src/OpalCompiler-Core/OCIRPushTemp.class.st +++ b/src/OpalCompiler-Core/OCIRPushTemp.class.st @@ -14,6 +14,12 @@ OCIRPushTemp >> accept: aVisitor [ ^ aVisitor visitPushTemp: self ] +{ #category : 'stack' } +OCIRPushTemp >> deltaStack [ + + ^ 1 +] + { #category : 'testing' } OCIRPushTemp >> isRemovableByPop [ diff --git a/src/OpalCompiler-Core/OCIRPushThisContext.class.st b/src/OpalCompiler-Core/OCIRPushThisContext.class.st index 5de439aac0f..c694420cc79 100644 --- a/src/OpalCompiler-Core/OCIRPushThisContext.class.st +++ b/src/OpalCompiler-Core/OCIRPushThisContext.class.st @@ -14,6 +14,12 @@ OCIRPushThisContext >> accept: aVisitor [ ^ aVisitor visitPushThisContext: self ] +{ #category : 'stack' } +OCIRPushThisContext >> deltaStack [ + + ^ 1 +] + { #category : 'testing' } OCIRPushThisContext >> isRemovableByPop [ diff --git a/src/OpalCompiler-Core/OCIRPushThisProcess.class.st b/src/OpalCompiler-Core/OCIRPushThisProcess.class.st index d593cf47351..a896efbe087 100644 --- a/src/OpalCompiler-Core/OCIRPushThisProcess.class.st +++ b/src/OpalCompiler-Core/OCIRPushThisProcess.class.st @@ -14,6 +14,12 @@ OCIRPushThisProcess >> accept: aVisitor [ ^ aVisitor visitPushThisProcess: self ] +{ #category : 'stack' } +OCIRPushThisProcess >> deltaStack [ + + ^ 1 +] + { #category : 'testing' } OCIRPushThisProcess >> isRemovableByPop [ diff --git a/src/OpalCompiler-Core/OCIRSend.class.st b/src/OpalCompiler-Core/OCIRSend.class.st index 84bbecb1009..b4d28c6b118 100644 --- a/src/OpalCompiler-Core/OCIRSend.class.st +++ b/src/OpalCompiler-Core/OCIRSend.class.st @@ -18,6 +18,12 @@ OCIRSend >> accept: aVisitor [ ^ aVisitor visitSend: self ] +{ #category : 'stack' } +OCIRSend >> deltaStack [ + + ^ (selector occurrencesOf: $:) negated +] + { #category : 'testing' } OCIRSend >> isSend [ ^true diff --git a/src/OpalCompiler-Tests/OCArrayLiteralTest.class.st b/src/OpalCompiler-Tests/OCArrayLiteralTest.class.st index 9bdc3d8c4df..546b196b87f 100644 --- a/src/OpalCompiler-Tests/OCArrayLiteralTest.class.st +++ b/src/OpalCompiler-Tests/OCArrayLiteralTest.class.st @@ -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 [ diff --git a/src/OpalCompiler-Tests/OCOpalExamples.class.st b/src/OpalCompiler-Tests/OCOpalExamples.class.st index 28d841d8177..3a0ca1b54c6 100644 --- a/src/OpalCompiler-Tests/OCOpalExamples.class.st +++ b/src/OpalCompiler-Tests/OCOpalExamples.class.st @@ -136,6 +136,18 @@ OCOpalExamples >> exampleDoublePrimitive [ ] +{ #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. diff --git a/src/UIManager/Object.extension.st b/src/UIManager/Object.extension.st index 1c6ddf8efe0..3009ba6df8d 100644 --- a/src/UIManager/Object.extension.st +++ b/src/UIManager/Object.extension.st @@ -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