Skip to content

Commit

Permalink
Merge branch 'druid' into fix-closure-creation
Browse files Browse the repository at this point in the history
  • Loading branch information
PalumboN committed Dec 15, 2023
2 parents 85a862f + 066eeba commit fc12b96
Show file tree
Hide file tree
Showing 11 changed files with 8,093 additions and 915 deletions.
1 change: 0 additions & 1 deletion CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,6 @@ set(APPNAME "Pharo" CACHE STRING "VM Application name"
set(FLAVOUR "CoInterpreter" CACHE STRING "The kind of VM to generate. Possible values: StackVM, CoInterpreter")
set(PHARO_LIBRARY_PATH "@executable_path/Plugins" CACHE STRING "The RPATH to use in the build")
set(ICEBERG_DEFAULT_REMOTE "scpUrl" CACHE STRING "If Iceberg uses HTTPS (httpsUrl) or tries first with SSH (scpUrl)")
set(IMAGE_FORMAT "SpurFormat" CACHE STRING "Image Format to use in the builtVM (SpurFormat / ComposedFormat)")

if(VERBOSE_BUILD)
set(CMAKE_VERBOSE_MAKEFILE TRUE)
Expand Down
25 changes: 23 additions & 2 deletions cmake/vmmaker.cmake
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,27 @@ else()
endif()
endif()

# Obtain all the parameters prefixed as VMMaker_
# Remove the prefix
function (getVMMakerParameters _resultVar)
getListOfVarsStartingWith("VMMaker_" matchedVars)
set (_pharoParameterArray "")
foreach (_var IN LISTS matchedVars)
# VMMaker_ has 8 characters
string(SUBSTRING ${_var} 8 -1 _name)
set (_pharoParameterArray ${_pharoParameterArray} "'${_name}'" "'${${_var}}'")
endforeach()
set (${_resultVar} "#( ${_pharoParameterArray} )" PARENT_SCOPE)
endfunction()

function (getListOfVarsStartingWith _prefix _resultVar)
get_cmake_property(_vars VARIABLES)
string (REGEX MATCHALL "(^|;)${_prefix}[A-Za-z0-9_]*" _matchedVars "${_vars}")
set (${_resultVar} ${_matchedVars} PARENT_SCOPE)
endfunction()

getVMMakerParameters(VM_Parameters)

set(PLUGIN_GENERATED_FILES
${PHARO_CURRENT_GENERATED}/plugins/src/FilePlugin/FilePlugin.c
${PHARO_CURRENT_GENERATED}/plugins/src/SurfacePlugin/SurfacePlugin.c
Expand Down Expand Up @@ -144,9 +165,9 @@ if(GENERATE_SOURCES)
#Custom command that generates the vm source code from VMMaker into the generated folder
add_custom_command(
OUTPUT ${VMSOURCEFILES} ${PLUGIN_GENERATED_FILES}
COMMAND ${VMMAKER_VM} --headless ${VMMAKER_IMAGE} --no-default-preferences eval \"PharoVMMaker generate: \#\'${FLAVOUR}\' outputDirectory: \'${CMAKE_CURRENT_BINARY_DIR_TO_OUT}\' imageFormat: \'${IMAGE_FORMAT}\'\"
COMMAND ${VMMAKER_VM} --headless ${VMMAKER_IMAGE} --no-default-preferences eval \"PharoVMMaker generate: \#\'${FLAVOUR}\' outputDirectory: \'${CMAKE_CURRENT_BINARY_DIR_TO_OUT}\' options: ${VM_Parameters}\"
DEPENDS vmmaker ${VMMAKER_IMAGE} ${VMMAKER_VM}
COMMENT "Generating VM files for flavour: ${FLAVOUR}")
COMMENT "Generating VM files for flavour: ${FLAVOUR} with options: ${VM_Parameters}")

add_custom_target(generate-sources DEPENDS ${VMSOURCEFILES} ${PLUGIN_GENERATED_FILES})

Expand Down
6 changes: 0 additions & 6 deletions smalltalksrc/VMMaker/CogObjectRepresentation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -194,12 +194,6 @@ CogObjectRepresentation >> genCreateClosureAt: bcpc numArgs: numArgs numCopied:
self subclassResponsibility
]

{ #category : #'bytecode generator support' }
CogObjectRepresentation >> genCreateFullClosureInLiteral: index numCopied: numCopied ignoreContext: ignoreContext contextNumArgs: contextNumArgs large: contextIsLarge inBlock: contextIsBlock intoRegister: anObject [
"Create a full closure"
self subclassResponsibility
]

{ #category : #'primitive generators' }
CogObjectRepresentation >> genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil [
<option: #DPFPReg0>
Expand Down
14 changes: 2 additions & 12 deletions smalltalksrc/VMMaker/CogObjectRepresentationForSpur.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -486,11 +486,12 @@ CogObjectRepresentationForSpur >> genCreateFullClosureInIndex: anIndex numCopied
ignoreContext
ifTrue: [ cogit genMoveNilR: ClassReg ]
ifFalse: [
cogit voidReceiverResultRegContainsSelf.
self
genGetActiveContextNumArgs: contextNumArgs
large: contextIsLarge
inBlock: contextIsBlock.
cogit MoveR: destinationRegister R: ClassReg ].
cogit MoveR: ReceiverResultReg R: ClassReg ].

numSlots := FullClosureFirstCopiedValueIndex + numCopied.
byteSize := objectMemory smallObjectBytesForSlots: numSlots.
Expand Down Expand Up @@ -3131,17 +3132,6 @@ CogObjectRepresentationForSpur >> maybeMarkCounters: theCounters [
[objectMemory markAndTrace: theCounters - objectMemory baseHeaderSize]
]

{ #category : #compilation }
CogObjectRepresentationForSpur >> maybeNoteDescriptor: descriptor blockStart: blockStart [
"Override to note inst var refs in blocks. Used to avoid checking
for forwarded receivers in blocks that don't refer to inst vars."
<var: #blockStart type: #'BlockStart *'>
<var: #descriptor type: #'BytecodeDescriptor *'>
<inline: true>
descriptor isInstVarRef ifTrue:
[blockStart hasInstVarRef: true]
]

{ #category : #'method cacheing' }
CogObjectRepresentationForSpur >> maybeShiftClassTagRegisterForMethodCacheProbe: classTagReg [
"Generate a shift of the register containing the class tag in a method cache probe.
Expand Down
107 changes: 67 additions & 40 deletions smalltalksrc/VMMaker/Cogit.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -7309,6 +7309,35 @@ Cogit >> genReturnTrampolineFor: aRoutine called: aString arg: regOrConst0 [
appendOpcodes: false
]
{ #category : #initialization }
Cogit >> genSendTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 [
"Generate a trampoline with four arguments.
Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
<var: #aRoutine type: #'void *'>
<var: #aString type: #'char *'>
| startAddress |
startAddress := methodZoneBase.
self zeroOpcodeIndex.
objectRepresentation selectorIndexDereferenceRoutine ifNotNil: [
:routine |
backEnd hasLinkRegister ifTrue: [ self PushR: LinkReg ].
self Call: routine.
backEnd hasLinkRegister ifTrue: [ self PopR: LinkReg ] ].
self genTrampolineFor: aRoutine
called: aString
numArgs: 4
arg: regOrConst0
arg: regOrConst1
arg: regOrConst2
arg: regOrConst3
regsToSave: self emptyRegisterMask
pushLinkReg: true
resultReg: NoReg
appendOpcodes: true.
^ startAddress
]
{ #category : #'trampoline support' }
Cogit >> genSmalltalkToCStackSwitch: pushLinkReg [
"If the client requires, then on an ARM-like RISC processor, the return address needs to
Expand Down Expand Up @@ -8091,48 +8120,46 @@ Cogit >> generateRunTimeTrampolines [
{ #category : #initialization }
Cogit >> generateSendTrampolines [
0 to: NumSendTrampolines - 1 do:
[:numArgs|
ordinarySendTrampolines
at: numArgs
put: (self genTrampolineFor: #ceSend:super:to:numArgs:
called: (self trampolineName: 'ceSend' numArgs: numArgs)
arg: ClassReg
arg: (self trampolineArgConstant: false)
arg: ReceiverResultReg
arg: (self numArgsOrSendNumArgsReg: numArgs))].
0 to: NumSendTrampolines - 1 do: [ :numArgs |
ordinarySendTrampolines at: numArgs put: (self
genSendTrampolineFor: #ceSend:super:to:numArgs:
called: (self trampolineName: 'ceSend' numArgs: numArgs)
arg: ClassReg
arg: (self trampolineArgConstant: false)
arg: ReceiverResultReg
arg: (self numArgsOrSendNumArgsReg: numArgs)) ].
"Generate these in the middle so they are within [firstSend, lastSend]."
BytecodeSetHasDirectedSuperSend ifTrue:
[0 to: NumSendTrampolines - 1 do:
[:numArgs|
directedSuperSendTrampolines
at: numArgs
put: (self genTrampolineFor: #ceSend:above:to:numArgs:
called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
arg: ClassReg
arg: TempReg
arg: ReceiverResultReg
arg: (self numArgsOrSendNumArgsReg: numArgs)).
directedSuperBindingSendTrampolines
at: numArgs
put: (self genTrampolineFor: #ceSend:aboveClassBinding:to:numArgs:
called: (self trampolineName: 'ceDirectedSuperBindingSend' numArgs: numArgs)
arg: ClassReg
arg: TempReg
arg: ReceiverResultReg
arg: (self numArgsOrSendNumArgsReg: numArgs))]].
0 to: NumSendTrampolines - 1 do:
[:numArgs|
superSendTrampolines
at: numArgs
put: (self genTrampolineFor: #ceSend:super:to:numArgs:
called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
arg: ClassReg
arg: (self trampolineArgConstant: true)
arg: ReceiverResultReg
arg: (self numArgsOrSendNumArgsReg: numArgs))].
BytecodeSetHasDirectedSuperSend ifTrue: [
0 to: NumSendTrampolines - 1 do: [ :numArgs |
directedSuperSendTrampolines at: numArgs put: (self
genSendTrampolineFor: #ceSend:above:to:numArgs:
called:
(self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
arg: ClassReg
arg: TempReg
arg: ReceiverResultReg
arg: (self numArgsOrSendNumArgsReg: numArgs)).
directedSuperBindingSendTrampolines at: numArgs put: (self
genSendTrampolineFor: #ceSend:aboveClassBinding:to:numArgs:
called:
(self
trampolineName: 'ceDirectedSuperBindingSend'
numArgs: numArgs)
arg: ClassReg
arg: TempReg
arg: ReceiverResultReg
arg: (self numArgsOrSendNumArgsReg: numArgs)) ] ].
0 to: NumSendTrampolines - 1 do: [ :numArgs |
superSendTrampolines at: numArgs put: (self
genSendTrampolineFor: #ceSend:super:to:numArgs:
called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
arg: ClassReg
arg: (self trampolineArgConstant: true)
arg: ReceiverResultReg
arg: (self numArgsOrSendNumArgsReg: numArgs)) ].
firstSend := ordinarySendTrampolines at: 0.
lastSend := superSendTrampolines at: NumSendTrampolines - 1
]
Expand Down
28 changes: 13 additions & 15 deletions smalltalksrc/VMMaker/DruidJIT.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -473,8 +473,8 @@ DruidJIT class >> bytecodeTable [
{ 2. 245. 245. #gen_LongStoreTemporaryVariableBytecode }.
{ 2. 246. 246. #unknownBytecode }.
{ 2. 247. 247. #unknownBytecode }.
{ 3. 248. 248. #unknownBytecode }.
{ 3. 249. 249. #gen_ExtPushFullClosureBytecode }.
{ 3. 248. 248. #gen_CallPrimitiveBytecode }.
{ 3. 249. 249. #unknownBytecode }.
{ 3. 250. 250. #unknownBytecode }.
{ 3. 251. 251. #unknownBytecode }.
{ 3. 252. 252. #unknownBytecode }.
Expand Down Expand Up @@ -705,11 +705,12 @@ DruidJIT >> genCreateFullClosureInIndex: anIndex numCopied: numCopied ignoreCont
ignoreContext
ifTrue: [ self genMoveNilR: ClassReg ]
ifFalse: [
self voidReceiverResultRegContainsSelf.
self
genGetActiveContextNumArgs: contextNumArgs
large: contextIsLarge
inBlock: contextIsBlock.
self MoveR: destinationRegister R: ClassReg ].
self MoveR: ReceiverResultReg R: ClassReg ].

numSlots := FullClosureFirstCopiedValueIndex + numCopied.
byteSize := objectMemory smallObjectBytesForSlots: numSlots.
Expand Down Expand Up @@ -1232,18 +1233,6 @@ DruidJIT >> genJumpTo: targetBytecodePC [
^ 0
]

{ #category : #'trait candidates' }
DruidJIT >> genJumpTo: targetBytecodePC followDeadCode: followDeadCode [

| eventualTarget fixup |
eventualTarget := self eventualTargetOf: targetBytecodePC.
self ssFlushTo: simStackPtr.
fixup := self ensureFixupAt: eventualTarget.
deadCode := followDeadCode.
self Jump: fixup.
^ 0
]

{ #category : #'trait candidates' }
DruidJIT >> genLoadSlot: index sourceReg: sourceReg destReg: destReg [

Expand Down Expand Up @@ -2096,6 +2085,15 @@ DruidJIT >> gen_BytecodePrimValueWithArg [
^ 0
]

{ #category : #generated }
DruidJIT >> gen_CallPrimitiveBytecode [
"AutoGenerated by Druid"

| live currentBlock |
live := 0.
^ 0
]

{ #category : #generated }
DruidJIT >> gen_DuplicateTopBytecode [
"AutoGenerated by Druid"
Expand Down

0 comments on commit fc12b96

Please sign in to comment.