Skip to content

Commit

Permalink
Having a new version of the initialization of abstractOpcodes to clea…
Browse files Browse the repository at this point in the history
…n only the ones that are going to be used.

Like this, this version has the same speed than before when allocating in the stack.
  • Loading branch information
tesonep committed Oct 5, 2022
1 parent b19eba2 commit 77e6110
Showing 1 changed file with 19 additions and 12 deletions.
31 changes: 19 additions & 12 deletions smalltalksrc/VMMaker/Cogit.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -3093,29 +3093,31 @@ Cogit >> allocateBlockStarts: numBlocks [

{ #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.
self ensureAndClearAbstractOpcodes: numberOfAbstractOpcodes.
self zeroOpcodeIndexForNewOpcodes.
labelCounter := 0
]

{ #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:
[^failBlock value].
<inline: true>
numberOfAbstractOpcodes > MaxNumberOfAbstractOpcodes ifTrue: [
^ failBlock value ].

self ensureAndClearAbstractOpcodes.
self ensureAndClearAbstractOpcodes: numberOfAbstractOpcodes.

self zeroOpcodeIndexForNewOpcodes.
labelCounter := 0
Expand Down Expand Up @@ -6298,22 +6300,27 @@ Cogit >> endPCOf: aMethod [
]

{ #category : #initialization }
Cogit >> ensureAndClearAbstractOpcodes [
Cogit >> ensureAndClearAbstractOpcodes: numberOfAbstractOpcodes [

| opcodeBytes fixupBytes allocBytes |
numAbstractOpcodes := MaxNumberOfAbstractOpcodes.
opcodeBytes := (self sizeof: CogAbstractInstruction) * numAbstractOpcodes.
fixupBytes := (self sizeof: CogBytecodeFixup) * numAbstractOpcodes.
| 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.

self
cCode:
[abstractOpcodes
ifNil: [
abstractOpcodes := self malloc: allocBytes.
fixups := (abstractOpcodes asUnsignedInteger + opcodeBytes) asVoidPointer].

self b: abstractOpcodes zero: allocBytes]
self b: abstractOpcodes zero: clearOpcodesBytes.
self b: fixups zero: clearFixupsBytes]
inSmalltalk:
[abstractOpcodes := CArrayAccessor on: ((1 to: numAbstractOpcodes) collect: [:ign| CogCompilerClass for: self]).
fixups := CArrayAccessor on: ((1 to: numAbstractOpcodes) collect: [:ign| self bytecodeFixupClass for: self])].
Expand Down

0 comments on commit 77e6110

Please sign in to comment.