Skip to content

Commit

Permalink
Refactor and add support to get/set the bytecode size from the byteco…
Browse files Browse the repository at this point in the history
…de table.
  • Loading branch information
Hernán Morales Durand committed Apr 5, 2023
1 parent ae2538a commit 42351f7
Show file tree
Hide file tree
Showing 2 changed files with 120 additions and 118 deletions.
31 changes: 31 additions & 0 deletions smalltalksrc/Melchor/AbstractInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,37 @@ Class {
#category : #Melchor
}

{ #category : #initialization }
AbstractInterpreter class >> bytecodeTable: anArray from: specArray [
"SpecArray is an array of one of (index selector) or (index1
index2 selector) or (index nil) or (index1 index2 nil). If selector
then the entry is the selector, but if nil the entry is the index."
| contiguous |

contiguous := 0.
specArray do: [ : bytecodeSizeSpec |
(bytecodeSizeSpec at: 2) do: [ : spec |
(spec at: 1) = contiguous
ifFalse: [ self error: 'Non-contiguous table entry' ].
spec size = 2
ifTrue: [ anArray
at: (spec at: 1) + 1
put: ((spec at: 2) ifNil: [ spec at: 1 ] ifNotNil: [: sym | sym ]).
contiguous := contiguous + 1 ]
ifFalse: [
(spec at: 1) to: (spec at: 2) do: [ : i |
anArray
at: i + 1
put: ( (spec at: 3)
ifNil: [ i ]
ifNotNil: [ : sym | sym ]) ].
contiguous := contiguous + ((spec at: 2) - (spec at: 1)) + 1 ] ] ].
anArray doWithIndex: [ : entry : index |
entry isSymbol
ifTrue: [ (self shouldIncludeMethodForSelector: entry)
ifFalse: [ anArray at: index put: 0 ] ] ]
]

{ #category : #initialization }
AbstractInterpreter class >> table: anArray from: specArray [
"SpecArray is an array of one of (index selector) or (index1
Expand Down
207 changes: 89 additions & 118 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -497,6 +497,85 @@ StackInterpreter class >> bytecodeTable [
^ BytecodeTable
]

{ #category : #initialization }
StackInterpreter class >> bytecodeTableArray [

^ #( #( 1 #( #( 0 15 pushReceiverVariableBytecode )
#( 16 31 pushLiteralVariable16CasesBytecode )
#( 32 63 pushLiteralConstantBytecode )
#( 64 75 pushTemporaryVariableBytecode )
#( 76 pushReceiverBytecode ) #( 77 pushConstantTrueBytecode )
#( 78 pushConstantFalseBytecode )
#( 79 pushConstantNilBytecode )
#( 80 pushConstantZeroBytecode )
#( 81 pushConstantOneBytecode )
#( 82 extPushPseudoVariable )
#( 83 duplicateTopBytecode ) #( 84 87 unknownBytecode )
#( 88 returnReceiver ) #( 89 returnTrue )
#( 90 returnFalse ) #( 91 returnNil ) #( 92 returnTopFromMethod )
#( 93 returnNilFromBlock ) #( 94 returnTopFromBlock )
#( 95 extNopBytecode ) #( 96 bytecodePrimAdd )
#( 97 bytecodePrimSubtract ) #( 98 bytecodePrimLessThanSistaV1 )
#( 99 bytecodePrimGreaterThanSistaV1 )
#( 100 bytecodePrimLessOrEqualSistaV1 )
#( 101 bytecodePrimGreaterOrEqualSistaV1 )
#( 102 bytecodePrimEqualSistaV1 )
#( 103 bytecodePrimNotEqualSistaV1 )
#( 104 bytecodePrimMultiply )
#( 105 bytecodePrimDivide ) #( 106 bytecodePrimMod )
#( 107 bytecodePrimMakePoint )
#( 108 bytecodePrimBitShift )
#( 109 bytecodePrimDiv ) #( 110 bytecodePrimBitAnd )
#( 111 bytecodePrimBitOr ) #( 112 bytecodePrimAt )
#( 113 bytecodePrimAtPut ) #( 114 bytecodePrimSize )
#( 115 bytecodePrimNext ) #( 116 bytecodePrimNextPut )
#( 117 bytecodePrimAtEnd ) #( 118 bytecodePrimIdenticalSistaV1 )
#( 119 bytecodePrimClass ) #( 120 bytecodePrimNotIdenticalSistaV1 )
#( 121 bytecodePrimValue ) #( 122 bytecodePrimValueWithArg )
#( 123 bytecodePrimDo ) #( 124 bytecodePrimNew )
#( 125 bytecodePrimNewWithArg )
#( 126 bytecodePrimPointX ) #( 127 bytecodePrimPointY )
#( 128 143 sendLiteralSelector0ArgsBytecode )
#( 144 159 sendLiteralSelector1ArgBytecode )
#( 160 175 sendLiteralSelector2ArgsBytecode )
#( 176 183 shortUnconditionalJump )
#( 184 191 shortConditionalJumpTrue )
#( 192 199 shortConditionalJumpFalse )
#( 200 207 storeAndPopReceiverVariableBytecode )
#( 208 215 storeAndPopTemporaryVariableBytecode )
#( 216 popStackBytecode ) #( 217 unconditionnalTrapBytecode )
#( 218 223 unknownBytecode ) ) )
#( 2 #( #( 224 extABytecode ) #( 225 extBBytecode )
#( 226 extPushReceiverVariableBytecode )
#( 227 extPushLiteralVariableBytecode )
#( 228 extPushLiteralBytecode )
#( 229 longPushTemporaryVariableBytecode )
#( 230 unknownBytecode ) #( 231 pushNewArrayBytecode )
#( 232 extPushIntegerBytecode )
#( 233 extPushCharacterBytecode )
#( 234 extSendBytecode ) #( 235 extSendSuperBytecode )
#( 236 callMappedInlinedPrimitive )
#( 237 extUnconditionalJump )
#( 238 extJumpIfTrue ) #( 239 extJumpIfFalse )
#( 240 extStoreAndPopReceiverVariableBytecode )
#( 241 extStoreAndPopLiteralVariableBytecode )
#( 242 longStoreAndPopTemporaryVariableBytecode )
#( 243 extStoreReceiverVariableBytecode )
#( 244 extStoreLiteralVariableBytecode )
#( 245 longStoreTemporaryVariableBytecode )
#( 246 247 unknownBytecode ) ) )
#( 3 #( #( 248 callPrimitiveBytecode )
#( 249 extPushFullClosureBytecode )
#( 250 unknownBytecode ) #( 251 pushRemoteTempLongBytecode )
#( 252 storeRemoteTempLongBytecode )
#( 253 storeAndPopRemoteTempLongBytecode )
#( 254 255 unknownBytecode ) ) ) ) "1 byte bytecodes" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "i.e. a 0 arg special selector" "i.e. a 1 arg special selector" "for booleanCheatSistaV1:" "was blockCopy:" "i.e. a 1 arg special selector" "i.e. a 0 arg special selector" "i.e. a 1 arg special selector" "i.e. a 0 arg special selector" "i.e. a 0 arg special selector"

"2 byte bytecodes"

"3 byte bytecodes" "was extPushClosureBytecode"
]

{ #category : #translation }
StackInterpreter class >> declareCVarsIn: aCCodeGenerator [
| vmClass |
Expand Down Expand Up @@ -640,133 +719,25 @@ StackInterpreter class >> initializeBytecodeTable [
{ #category : #initialization }
StackInterpreter class >> initializeBytecodeTableForSistaV1 [
"See e.g. the cass comment for EncoderForSistaV1"

"StackInterpreter initializeBytecodeTableForSistaV1"

"Note: This table will be used to generate a C switch statement."

InitializationOptions at: #SistaV1BytecodeSet put: (SistaV1BytecodeSet := true).
InitializationOptions
at: #SistaV1BytecodeSet
put: (SistaV1BytecodeSet := true).

BytecodeTable := Array new: 256.
BytecodeEncoderClassName := #EncoderForSistaV1.
BytecodeSetHasDirectedSuperSend := true.
BytecodeSetHasExtensions := true.
LongStoreBytecode := 245.
self table: BytecodeTable from:
#( "1 byte bytecodes"
( 0 15 pushReceiverVariableBytecode)
( 16 31 pushLiteralVariable16CasesBytecode)
( 32 63 pushLiteralConstantBytecode)
( 64 75 pushTemporaryVariableBytecode)
( 76 pushReceiverBytecode)
( 77 pushConstantTrueBytecode)
( 78 pushConstantFalseBytecode)
( 79 pushConstantNilBytecode)
( 80 pushConstantZeroBytecode)
( 81 pushConstantOneBytecode)
( 82 extPushPseudoVariable)
( 83 duplicateTopBytecode)

( 84 87 unknownBytecode)
( 88 returnReceiver)
( 89 returnTrue)
( 90 returnFalse)
( 91 returnNil)
( 92 returnTopFromMethod)
( 93 returnNilFromBlock)
( 94 returnTopFromBlock)
( 95 extNopBytecode)

( 96 bytecodePrimAdd)
( 97 bytecodePrimSubtract)
( 98 bytecodePrimLessThanSistaV1) "for booleanCheatSistaV1:"
( 99 bytecodePrimGreaterThanSistaV1) "for booleanCheatSistaV1:"
(100 bytecodePrimLessOrEqualSistaV1) "for booleanCheatSistaV1:"
(101 bytecodePrimGreaterOrEqualSistaV1) "for booleanCheatSistaV1:"
(102 bytecodePrimEqualSistaV1) "for booleanCheatSistaV1:"
(103 bytecodePrimNotEqualSistaV1) "for booleanCheatSistaV1:"
(104 bytecodePrimMultiply)
(105 bytecodePrimDivide)
(106 bytecodePrimMod)
(107 bytecodePrimMakePoint)
(108 bytecodePrimBitShift)
(109 bytecodePrimDiv)
(110 bytecodePrimBitAnd)
(111 bytecodePrimBitOr)

(112 bytecodePrimAt)
(113 bytecodePrimAtPut)
(114 bytecodePrimSize)
(115 bytecodePrimNext) "i.e. a 0 arg special selector"
(116 bytecodePrimNextPut) "i.e. a 1 arg special selector"
(117 bytecodePrimAtEnd)
(118 bytecodePrimIdenticalSistaV1) "for booleanCheatSistaV1:"
(119 bytecodePrimClass)
(120 bytecodePrimNotIdenticalSistaV1) "was blockCopy:"
(121 bytecodePrimValue)
(122 bytecodePrimValueWithArg)
(123 bytecodePrimDo) "i.e. a 1 arg special selector"
(124 bytecodePrimNew) "i.e. a 0 arg special selector"
(125 bytecodePrimNewWithArg) "i.e. a 1 arg special selector"
(126 bytecodePrimPointX) "i.e. a 0 arg special selector"
(127 bytecodePrimPointY) "i.e. a 0 arg special selector"

(128 143 sendLiteralSelector0ArgsBytecode)
(144 159 sendLiteralSelector1ArgBytecode)
(160 175 sendLiteralSelector2ArgsBytecode)

(176 183 shortUnconditionalJump)
(184 191 shortConditionalJumpTrue)
(192 199 shortConditionalJumpFalse)

(200 207 storeAndPopReceiverVariableBytecode)
(208 215 storeAndPopTemporaryVariableBytecode)
(216 popStackBytecode)
(217 unconditionnalTrapBytecode)

(218 223 unknownBytecode)

"2 byte bytecodes"
(224 extABytecode)
(225 extBBytecode)

(226 extPushReceiverVariableBytecode)
(227 extPushLiteralVariableBytecode)
(228 extPushLiteralBytecode)
(229 longPushTemporaryVariableBytecode)
(230 unknownBytecode)
(231 pushNewArrayBytecode)
(232 extPushIntegerBytecode)
(233 extPushCharacterBytecode)

(234 extSendBytecode)
(235 extSendSuperBytecode)

(236 callMappedInlinedPrimitive)

(237 extUnconditionalJump)
(238 extJumpIfTrue)
(239 extJumpIfFalse)

(240 extStoreAndPopReceiverVariableBytecode)
(241 extStoreAndPopLiteralVariableBytecode)
(242 longStoreAndPopTemporaryVariableBytecode)

(243 extStoreReceiverVariableBytecode)
(244 extStoreLiteralVariableBytecode)
(245 longStoreTemporaryVariableBytecode)

(246 247 unknownBytecode)

"3 byte bytecodes"
(248 callPrimitiveBytecode)
(249 extPushFullClosureBytecode)

(250 unknownBytecode) "was extPushClosureBytecode"
(251 pushRemoteTempLongBytecode)
(252 storeRemoteTempLongBytecode)
(253 storeAndPopRemoteTempLongBytecode)

(254 255 unknownBytecode)
)
self bytecodeTable: BytecodeTable from: self bytecodeTableArray "1 byte bytecodes" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "for booleanCheatSistaV1:" "i.e. a 0 arg special selector" "i.e. a 1 arg special selector" "for booleanCheatSistaV1:" "was blockCopy:" "i.e. a 1 arg special selector" "i.e. a 0 arg special selector" "i.e. a 1 arg special selector" "i.e. a 0 arg special selector" "i.e. a 0 arg special selector"

"2 byte bytecodes"

"3 byte bytecodes" "was extPushClosureBytecode"
]

{ #category : #initialization }
Expand Down

0 comments on commit 42351f7

Please sign in to comment.