Skip to content

Commit

Permalink
Fixing warnings and errors in C translation
Browse files Browse the repository at this point in the history
  • Loading branch information
tesonep committed Oct 4, 2022
1 parent f61f801 commit 11e5a7d
Show file tree
Hide file tree
Showing 10 changed files with 67 additions and 40 deletions.
3 changes: 3 additions & 0 deletions smalltalksrc/Melchor/VMBasicConstants.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ Class {
'IMMUTABILITY',
'MULTIPLEBYTECODESETS',
'NewspeakVM',
'PRIdSQINT',
'PharoVM',
'PrimErrBadArgument',
'PrimErrBadIndex',
Expand Down Expand Up @@ -122,6 +123,8 @@ VMBasicConstants class >> namesDefinedAtCompileTime [
WIN32 _WIN32 _WIN32_WCE
WIN64 _WIN64 _WIN64_WCE
PRIdSQINT
FEATURE_FFI
FEATURE_THREADED_FFI
FEATURE_MESSAGE_COUNT)
Expand Down
30 changes: 22 additions & 8 deletions smalltalksrc/VMMaker/AbstractComposedImageAccess.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -43,9 +43,10 @@ AbstractComposedImageAccess >> existSegment: segmentIndex inImage: imageFileName

{ #category : #'as yet unclassified' }
AbstractComposedImageAccess >> fieldFormat [

<inline: true>
^ '\t#%s : %lld'.

<cmacro: '() "\t#%s : %" PRIdSQINT'>

^ '\t#%s : %' , PRIdSQINT.
]

{ #category : #'file operations' }
Expand Down Expand Up @@ -105,15 +106,20 @@ AbstractComposedImageAccess >> headerFileNameinImage: imageFileName into: buffer

^ self
cCode: [
self snprintf: buffer _: bufferSize _: '%s/%s' _: imageFileName _: headerFileName.
self
snprintf: buffer
_: bufferSize
_: '%s/%s'
_: (self cCoerce: imageFileName to: #'char *')
_: (self cCoerce: headerFileName to: #'char *').
buffer ]
inSmalltalk: [ imageFileName , '/', headerFileName ]
]

{ #category : #'perm - space' }
AbstractComposedImageAccess >> permSpaceDataFileInImage: imageFileName [

<inline: true>
<inline: #always>
<var: #buffer declareC: 'char buffer[255]'>

| buffer |
Expand All @@ -128,15 +134,19 @@ AbstractComposedImageAccess >> permSpaceFileName: fileName inImage: imageFileNam

^ self
cCode: [
self snprintf: buffer _: bufferSize _: '%s/%s' _: imageFileName _: fileName.
self
snprintf: buffer
_: bufferSize
_: '%s/%s'
_: (self cCoerce: imageFileName to: #'char *') _: (self cCoerce: fileName to: #'char *').
buffer ]
inSmalltalk: [ imageFileName , '/', fileName ].
]

{ #category : #'perm - space' }
AbstractComposedImageAccess >> permSpaceMetadataFileNameInImage: imageFileName [

<inline: true>
<inline: #always>
<var: #buffer declareC: 'char buffer[255]'>

| buffer |
Expand Down Expand Up @@ -165,7 +175,11 @@ AbstractComposedImageAccess >> segmentFileName: segmentIndex withExtension: exte

^ self
cCode: [
self snprintf: buffer _: bufferSize _: '%s/seg%d%s' _: imageFileName _: segmentIndex _: extension.
self snprintf: buffer _: bufferSize
_: '%s/seg%d%s'
_: (self cCoerce: imageFileName to: #'char *')
_: (self cCoerce: segmentIndex to: #'int')
_: extension.
buffer ]
inSmalltalk: [ imageFileName , '/seg', segmentIndex asString , extension ]
]
Expand Down
42 changes: 25 additions & 17 deletions smalltalksrc/VMMaker/CoInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -538,7 +538,7 @@ CoInterpreter >> activateNewFullClosure: blockClosure method: theMethod numArgs:
the last block method we failed to compile and avoid recompiling it."
(self methodWithHeaderShouldBeCogged: methodHeader)
ifTrue:
[(instructionPointer < objectMemory getMemoryMap startOfObjectMemory "If from machine code (via value primitive) attempt jitting"
[(self isInstructionPointerInInterpreter not "If from machine code (via value primitive) attempt jitting"
or: [theMethod = lastCoggableInterpretedBlockMethod]) "If from interpreter and repeat block, attempt jitting"
ifTrue:
[theMethod ~= lastUncoggableInterpretedBlockMethod ifTrue:
Expand All @@ -564,7 +564,7 @@ CoInterpreter >> activateNewFullClosure: blockClosure method: theMethod numArgs:
then make sure we restore the saved instruction pointer and avoid pushing
ceReturnToInterpreterPC which is only valid between an interpreter caller
frame and a machine code callee frame."
(inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory) ifFalse:
(inInterpreter := self isInstructionPointerInInterpreter) ifFalse:
[instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
[instructionPointer := self iframeSavedIP: framePointer]].

Expand Down Expand Up @@ -624,7 +624,7 @@ CoInterpreter >> activateNewMethod [
then make sure we restore the saved instruction pointer and avoid pushing
ceReturnToInterpreterPC which is only valid between an interpreter caller
frame and a machine code callee frame."
(inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory) ifFalse:
(inInterpreter := self isInstructionPointerInInterpreter) ifFalse:
[instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
[instructionPointer := self iframeSavedIP: framePointer]].
self push: instructionPointer.
Expand Down Expand Up @@ -968,7 +968,8 @@ CoInterpreter >> baseFrameReturn [
stackPointer := theSP.
framePointer := theFP.
instructionPointer := self pointerForOop: self stackTop.
instructionPointer asUnsignedInteger < objectMemory getMemoryMap startOfObjectMemory

self isInstructionPointerInInterpreter not
ifTrue: [
instructionPointer asUnsignedInteger
~= cogit ceReturnToInterpreterPC ifTrue: [ "localIP in the cog method zone indicates a return to machine code."
Expand Down Expand Up @@ -1112,7 +1113,7 @@ CoInterpreter >> callbackEnter: callbackID [
jmpDepth := jmpDepth + 1.

wasInMachineCode := self isMachineCodeFrame: framePointer.
calledFromMachineCode := instructionPointer <= objectMemory getMemoryMap startOfObjectMemory.
calledFromMachineCode := self isInstructionPointerInInterpreter not.

"Suspend the currently active process"
suspendedCallbacks at: jmpDepth put: self activeProcess.
Expand Down Expand Up @@ -1166,15 +1167,15 @@ CoInterpreter >> callbackEnter: callbackID [
self assert: wasInMachineCode = (self isMachineCodeFrame: framePointer).
calledFromMachineCode
ifTrue:
[instructionPointer asUnsignedInteger >= objectMemory getMemoryMap startOfObjectMemory ifTrue:
[self isInstructionPointerInInterpreter ifTrue:
[self iframeSavedIP: framePointer put: instructionPointer.
instructionPointer := cogit ceReturnToInterpreterPC]]
ifFalse:
["Even if the context was flushed to the heap and rebuilt in transferTo:from:
above it will remain an interpreted frame because the context's pc would
remain a bytecode pc. So the instructionPointer must also be a bytecode pc."
self assert: (self isMachineCodeFrame: framePointer) not.
self assert: instructionPointer > objectMemory getMemoryMap startOfObjectMemory].
self assert: self isInstructionPointerInInterpreter].
self assert: primFailCode = 0.
jmpDepth := jmpDepth-1.
^true
Expand Down Expand Up @@ -2410,8 +2411,8 @@ CoInterpreter >> commonCallerReturn [
stackPointer := framePointer
+ (self frameStackedReceiverOffset: framePointer).
framePointer := callersFPOrNull.
instructionPointer asUnsignedInteger < objectMemory getMemoryMap startOfObjectMemory
ifTrue: [
self isInstructionPointerInInterpreter
ifFalse: [
instructionPointer asUnsignedInteger
~= cogit ceReturnToInterpreterPC ifTrue: [ "localIP in the cog method zone indicates a return to machine code."
^ self returnToMachineCodeFrame ].
Expand Down Expand Up @@ -2802,7 +2803,7 @@ CoInterpreter >> ensurePushedInstructionPointer [
from the interpreter, either directly or via a machine code primitive. We
could have come from machine code. The instructionPointer tells us where
from. Make sure the instruction pointer is pushed and/or saved."
instructionPointer asUnsignedInteger >= objectMemory getMemoryMap startOfObjectMemory
self isInstructionPointerInInterpreter
ifTrue:
"invoked directly from the interpreter"
[self iframeSavedIP: framePointer put: instructionPointer.
Expand Down Expand Up @@ -2957,7 +2958,7 @@ CoInterpreter >> executeNewMethod [
the method cache (i.e. primitivePerform et al).
Eagerly compile it if appropriate so that doits are fast."
| methodHeader inInterpreter |
inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory.
inInterpreter := self isInstructionPointerInInterpreter.
primitiveFunctionPointer ~= 0 ifTrue:
[self isPrimitiveFunctionPointerAnIndex ifTrue:
[self externalQuickPrimitiveResponse.
Expand All @@ -2981,7 +2982,7 @@ CoInterpreter >> executeNewMethod [
"if not primitive, or primitive failed, activate the method"
(self isCogMethodReference: methodHeader)
ifTrue:
[instructionPointer asUnsignedInteger >= objectMemory getMemoryMap startOfObjectMemory ifTrue:
[self isInstructionPointerInInterpreter ifTrue:
[self iframeSavedIP: framePointer put: instructionPointer asInteger.
instructionPointer := cogit ceReturnToInterpreterPC].
self activateCoggedNewMethod: inInterpreter]
Expand Down Expand Up @@ -4148,6 +4149,14 @@ CoInterpreter >> isCogMethodReference: methodHeader [
^objectMemory isNonIntegerObject: methodHeader
]

{ #category : #testing }
CoInterpreter >> isInstructionPointerInInterpreter [

<inline: true>

^ instructionPointer asUnsignedInteger >= objectMemory getMemoryMap startOfObjectMemory
]

{ #category : #'frame access' }
CoInterpreter >> isMachineCodeFrame: theFP [
<var: #theFP type: #'char *'>
Expand All @@ -4156,7 +4165,7 @@ CoInterpreter >> isMachineCodeFrame: theFP [

{ #category : #'debug support' }
CoInterpreter >> isMachineCodeIP: anInstrPointer [
^anInstrPointer < objectMemory getMemoryMap startOfObjectMemory
^anInstrPointer asUnsignedInteger < objectMemory getMemoryMap startOfObjectMemory
]

{ #category : #'internal interpreter access' }
Expand Down Expand Up @@ -4201,7 +4210,7 @@ CoInterpreter >> justActivateNewMethod: mustBeInterpreterFrame [
self assert: (objectMemory isOopForwarded: rcvr) not.

(cogMethod notNil
and: [instructionPointer asUnsignedInteger >= objectMemory getMemoryMap startOfObjectMemory]) ifTrue:
and: [self isInstructionPointerInInterpreter]) ifTrue:
[self iframeSavedIP: framePointer put: instructionPointer.
instructionPointer := cogit ceReturnToInterpreterPC].
self push: instructionPointer.
Expand Down Expand Up @@ -4618,7 +4627,7 @@ CoInterpreter >> mapVMRegisters [
| mapInstructionPointer |
(objectMemory shouldRemapObj: method) ifTrue:
["i.e. interpreter instructionPointer in method as opposed to machine code?"
(mapInstructionPointer := instructionPointer > method) ifTrue:
(mapInstructionPointer := instructionPointer asUnsignedInteger > method) ifTrue:
[instructionPointer := instructionPointer - method]. "*rel to method"
method := objectMemory remapObj: method.
mapInstructionPointer ifTrue:
Expand Down Expand Up @@ -6197,8 +6206,7 @@ CoInterpreter >> returnToMachineCodeFrame [

<inline: true>
cogit assertCStackWellAligned.
self assert:
instructionPointer asUnsignedInteger < objectMemory getMemoryMap startOfObjectMemory.
self assert: self isInstructionPointerInInterpreter not.
self assert: (self isMachineCodeFrame: framePointer).
self
assertValidExecutionPointe: instructionPointer asUnsignedInteger
Expand Down
14 changes: 7 additions & 7 deletions smalltalksrc/VMMaker/CoInterpreterPrimitives.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ CoInterpreterPrimitives >> doWaitSemaphore: sema reEnterInterpreter: hasToReente
know from whence we came. We could have come from the interpreter,
either directly or via a machine code primitive. We could have come from
machine code. The instructionPointer tells us where from:"
inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory.
inInterpreter := self isInstructionPointerInInterpreter.
activeProc := self activeProcess.
self addLastLink: activeProc toList: sema.
self transferTo: self wakeHighestPriority from: CSWait.
Expand Down Expand Up @@ -285,7 +285,7 @@ CoInterpreterPrimitives >> primitiveEnterCriticalSection [
know from whence we came. We could have come from the interpreter,
either directly or via a machine code primitive. We could have come from
machine code. The instructionPointer tells us where from:"
inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory.
inInterpreter := self isInstructionPointerInInterpreter.
self addLastLink: activeProc toList: criticalSection.
self transferTo: self wakeHighestPriority from: CSEnterCriticalSection.
self forProcessPrimitiveReturnToExecutivePostContextSwitch: inInterpreter
Expand All @@ -309,7 +309,7 @@ CoInterpreterPrimitives >> primitiveExitCriticalSection [
know from whence we came. We could have come from the interpreter,
either directly or via a machine code primitive. We could have come from
machine code. The instructionPointer tells us where from:"
inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory.
inInterpreter := self isInstructionPointerInInterpreter.
owningProcess := self removeFirstLinkOfList: criticalSection.
"store check unnecessary because aSemaphore referred to owningProcess
via its FirstLinkIndex slot before owningProcess was removed."
Expand Down Expand Up @@ -608,7 +608,7 @@ CoInterpreterPrimitives >> primitiveResume [
we have to know from whence we came. We could have come from the
interpreter, either directly or via a machine code primitive. We could have
come from machine code. The instructionPointer tells us where from:"
inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory.
inInterpreter := self isInstructionPointerInInterpreter.
(self resume: proc preemptedYieldingIf: preemptionYields from: CSResume) ifTrue:
[self forProcessPrimitiveReturnToExecutivePostContextSwitch: inInterpreter]

Expand Down Expand Up @@ -643,7 +643,7 @@ CoInterpreterPrimitives >> primitiveSignal [
we have to know from whence we came. We could have come from the
interpreter, either directly or via a machine code primitive. We could have
come from machine code. The instructionPointer tells us where from:"
inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory.
inInterpreter := self isInstructionPointerInInterpreter.
(self synchronousSignal: self stackTop) ifTrue:
[self forProcessPrimitiveReturnToExecutivePostContextSwitch: inInterpreter]
]
Expand Down Expand Up @@ -679,7 +679,7 @@ CoInterpreterPrimitives >> primitiveSuspend [
either directly or via a machine code primitive. We could have come from
machine code. The instructionPointer tells us where from:"
self pop: 1 thenPush: objectMemory nilObject.
inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory.
inInterpreter := self isInstructionPointerInInterpreter.
self transferTo: self wakeHighestPriority from: CSSuspend.
^self forProcessPrimitiveReturnToExecutivePostContextSwitch: inInterpreter].
myList := objectMemory fetchPointer: MyListIndex ofObject: process.
Expand Down Expand Up @@ -963,7 +963,7 @@ CoInterpreterPrimitives >> primitiveYield [
know from whence we came. We could have come from the interpreter,
either directly or via a machine code primitive. We could have come from
machine code. The instructionPointer tells us where from:"
inInterpreter := instructionPointer >= objectMemory getMemoryMap startOfObjectMemory.
inInterpreter := self isInstructionPointerInInterpreter.
self addLastLink: activeProc toList: processList.
self transferTo: self wakeHighestPriority from: CSYield.
self forProcessPrimitiveReturnToExecutivePostContextSwitch: inInterpreter
Expand Down
2 changes: 1 addition & 1 deletion smalltalksrc/VMMaker/ComposedImageReader.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ ComposedImageReader >> readFieldsSTONFrom: file into: aStruct [
fscanf: file
_: self fieldFormat
_: fieldName
_: (self addressOf: fieldValue).
_: (self cCoerce: (self addressOf: fieldValue) to: #'sqInt*').

aStruct setField: (self contentsOf: fieldName) to: (self contentsOf: fieldValue).

Expand Down
2 changes: 1 addition & 1 deletion smalltalksrc/VMMaker/ComposedImageWriter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -152,7 +152,7 @@ ComposedImageWriter >> writeSTON: struct toFile: f [
<inline: true>
struct withStructNameDo: [ :name | self fprintf: f _: self headFormat _: name ].
struct withFieldsDo: [ :fieldName :fieldValue |
self fprintf: f _: self fieldFormat _: fieldName _: fieldValue]
self fprintf: f _: self fieldFormat _: fieldName _: (self cCoerce: fieldValue to: #sqInt)]
separatedBy: [ self fprintf: f _: ',\n'].

self fprintf: f _: '\n}'.
Expand Down
3 changes: 2 additions & 1 deletion smalltalksrc/VMMaker/VMClass.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,8 @@ VMClass class >> initializeMiscConstants [

"And not these; they're compile-time"
IMMUTABILITY := InitializationOptions at: #IMMUTABILITY ifAbsent: [SPURVM]. "Default as enabled for Spur VMs"
WIN32 := InitializationOptions at: #WIN32 ifAbsent: [false]
WIN32 := InitializationOptions at: #WIN32 ifAbsent: [false].
PRIdSQINT := InitializationOptions at: #FormatSqInt ifAbsent: [ 'ld' ].
]

{ #category : #'*VMMaker' }
Expand Down
2 changes: 1 addition & 1 deletion smalltalksrc/VMMaker/VMMemoryMap.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -724,5 +724,5 @@ VMMemoryMap >> startOfObjectMemory [
<api>

"The first object space in the memory map is the newSpace."
^ self newSpaceStart
^ self newSpaceStart
]
8 changes: 4 additions & 4 deletions smalltalksrc/VMMaker/VMRememberedSet.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -150,14 +150,14 @@ VMRememberedSet >> growRememberedSet [
base := self rememberedSetArrayPointerFromObject: newObj.

0 to: rememberedSetSize - 1 do:
[:i| base at: i put: (rememberedSetArray at: i)].
[:i| base at: i put: (self rememberedSetArray at: i)].
"if growing in the middle of a GC, need to preserve marked status."
(manager isMarked: obj) ifTrue:
[manager
setIsMarkedOf: newObj to: true;
setIsMarkedOf: obj to: false].
manager freeObject: obj.
rememberedSetArray := base.
self rememberedSetArray: base.
self rememberedSetLimit: (manager numSlotsOf: newObj).
self setRememberedSetRedZone

Expand Down Expand Up @@ -186,7 +186,7 @@ VMRememberedSet >> initializeRememberedSetShouldStartEmpty: shouldStartEmpty [

self assert: (manager formatOf: obj) = manager wordIndexableFormat.
self assert: (manager isPinned: obj).
rememberedSetArray := self rememberedSetArrayPointerFromObject: obj.
self rememberedSetArray: (self rememberedSetArrayPointerFromObject: obj).

self rememberedSetLimit: (manager numSlotsOf: obj).

Expand Down Expand Up @@ -300,7 +300,7 @@ VMRememberedSet >> referenceCountRememberedReferents: population maxRefCount: ma
VMRememberedSet >> relocateRememberedSet [

"For SpurPlanningCompactor"
rememberedSetArray := self rememberedSetArrayPointerFromObject: self objectOop
self rememberedSetArray: (self rememberedSetArrayPointerFromObject: self objectOop)
]

{ #category : #accessing }
Expand Down
1 change: 1 addition & 0 deletions smalltalksrc/VMMaker/VMStackPages.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -251,6 +251,7 @@ VMStackPages >> initializeStack: theStackPages numSlots: stackSlots pageSize: sl
VMStackPages >> initializeWithByteSize: byteSize inMemoryMap: aMemoryMap for: anInterpreter [

<inline: true>
<var: #aMemoryMap type:#'VMMemoryMap *'>

| stackAddress |

Expand Down

0 comments on commit 11e5a7d

Please sign in to comment.