Skip to content

Commit

Permalink
Cleanup implementation.
Browse files Browse the repository at this point in the history
Remove duplicated code
Make sure the wrong API is not accessible
  • Loading branch information
guillep committed Apr 7, 2023
1 parent 0ca22b6 commit 0f93a4e
Showing 1 changed file with 27 additions and 39 deletions.
66 changes: 27 additions & 39 deletions smalltalksrc/VMMaker/Cogit.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -3260,31 +3260,51 @@ Cogit >> allMethodsHaveCorrectHeader [
{ #category : #initialization }
Cogit >> allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes [
"Allocate the various arrays needed to compile abstract instructions.
Notionally we only need as many fixups as there are bytecodes. But we
reuse fixups to record pc-dependent instructions in generateInstructionsAt:
and so need at least as many as there are abstract opcodes."
<inline: true>
self ensureAndClearAbstractOpcodes: numberOfAbstractOpcodes.
self zeroOpcodeIndexForNewOpcodes.
labelCounter := 0
self
allocateOpcodes: numberOfAbstractOpcodes
bytecodes: numberOfBytecodes
ifFail: [ self error: 'Cannot allocate requested opcodes' ]
]
{ #category : #initialization }
Cogit >> allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes ifFail: failBlock [
"Allocate the various arrays needed to compile abstract instructions, failing if the size
needed is considered too high. Notionally we only need as many fixups as there are
bytecodes. But we reuse fixups to record pc-dependent instructions in
generateInstructionsAt: and so need at least as many as there are abstract opcodes."
<inline: true>
numberOfAbstractOpcodes > MaxNumberOfAbstractOpcodes ifTrue: [
numberOfAbstractOpcodes > MaxNumberOfAbstractOpcodes ifTrue: [
^ failBlock value ].
"Remember how many opcodes were allocated, then lazy initialize to max"
numAbstractOpcodes := numberOfAbstractOpcodes.
abstractOpcodes ifNil: [
| opcodeBytes fixupBytes allocBytes |
opcodeBytes := (self sizeof: CogAbstractInstruction)
* MaxNumberOfAbstractOpcodes.
fixupBytes := (self sizeof: CogBytecodeFixup)
* MaxNumberOfAbstractOpcodes.
allocBytes := opcodeBytes + fixupBytes.
self ensureAndClearAbstractOpcodes: numberOfAbstractOpcodes.
self
cCode: [
abstractOpcodes := self malloc: allocBytes.
fixups := (abstractOpcodes asUnsignedInteger + opcodeBytes)
asVoidPointer ]
inSmalltalk: [
abstractOpcodes := CArrayAccessor on:
((1 to: MaxNumberOfAbstractOpcodes) collect: [
:ign | CogCompilerClass for: self ]).
fixups := CArrayAccessor on:
((1 to: MaxNumberOfAbstractOpcodes) collect: [ :ign |
self bytecodeFixupClass for: self ]) ] ].
self zeroOpcodeIndexForNewOpcodes.
labelCounter := 0
Expand Down Expand Up @@ -6172,38 +6192,6 @@ Cogit >> endPCOf: aMethod [
^end
]
{ #category : #initialization }
Cogit >> ensureAndClearAbstractOpcodes: numberOfAbstractOpcodes [
| opcodeBytes fixupBytes allocBytes clearFixupsBytes clearOpcodesBytes |
numAbstractOpcodes := numberOfAbstractOpcodes.
opcodeBytes := (self sizeof: CogAbstractInstruction)
* MaxNumberOfAbstractOpcodes.
fixupBytes := (self sizeof: CogBytecodeFixup)
* MaxNumberOfAbstractOpcodes.
allocBytes := opcodeBytes + fixupBytes.
clearOpcodesBytes := (self sizeof: CogAbstractInstruction)
* numberOfAbstractOpcodes.
clearFixupsBytes := (self sizeof: CogBytecodeFixup)
* numberOfAbstractOpcodes.
abstractOpcodes ifNil: [
self
cCode: [
abstractOpcodes := self malloc: allocBytes.
fixups := (abstractOpcodes asUnsignedInteger + opcodeBytes)
asVoidPointer ]
inSmalltalk: [
abstractOpcodes := CArrayAccessor on:
((1 to: MaxNumberOfAbstractOpcodes) collect: [
:ign | CogCompilerClass for: self ]).
fixups := CArrayAccessor on:
((1 to: MaxNumberOfAbstractOpcodes) collect: [ :ign |
self bytecodeFixupClass for: self ]) ] ]
]
{ #category : #'compile abstract instructions' }
Cogit >> ensureFixupAt: targetPC [
"Make sure there's a flagged fixup at the target pc in fixups.
Expand Down

0 comments on commit 0f93a4e

Please sign in to comment.