Skip to content

Commit

Permalink
Adding log entries for the snapshot and quit primitives
Browse files Browse the repository at this point in the history
  • Loading branch information
tesonep committed Aug 11, 2021
1 parent 54488d3 commit e793384
Show file tree
Hide file tree
Showing 3 changed files with 37 additions and 16 deletions.
5 changes: 5 additions & 0 deletions smalltalksrc/VMMaker/InterpreterPrimitives.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -3542,6 +3542,11 @@ InterpreterPrimitives >> primitiveProfileStart [
{ #category : #'system control primitives' }
InterpreterPrimitives >> primitiveQuit [

self isLogDebug
ifTrue: [
self logDebug: 'Quit requested by the image'.
self printAllStacks ].

self ioExitWithErrorCode: (argumentCount = 1 ifTrue: [objectMemory integerValueOf: self stackTop] ifFalse: [0])
]

Expand Down
27 changes: 11 additions & 16 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -15227,8 +15227,7 @@ StackInterpreter >> slowPrimitiveResponse [
{ #category : #'image save/restore' }
StackInterpreter >> snapshot: embedded [
"update state of active context"
| activeContext activeProc rcvr setMacType stackIndex |
<var: #setMacType type: #'void *'>
| activeContext activeProc rcvr stackIndex |

"For now the stack munging below doesn't deal with more than one argument.
It can, and should."
Expand All @@ -15247,11 +15246,15 @@ StackInterpreter >> snapshot: embedded [
withValue: activeContext.

tempOop := activeContext.

self logDebug: 'Garbage Collect for Snapshot'.

objectMemory garbageCollectForSnapshot.
"Nothing moves from here on so it is safe to grab the activeContext again."
activeContext := tempOop.
tempOop := 0.


self successful ifTrue:
["Without contexts or stacks simulate
rcvr := self popStack. ''pop rcvr''
Expand All @@ -15263,13 +15266,8 @@ StackInterpreter >> snapshot: embedded [
storePointerUnchecked: stackIndex + CtxtTempFrameStart - 1
ofObject: activeContext
withValue: objectMemory trueObject.
"now attempt to write the snapshot file"
"now attempt to write the snapshot file"
self writeImageFileIO.
(self successful and: [embedded not]) ifTrue:
["set Mac file type and creator; this is a noop on other platforms"
setMacType := self ioLoadFunction: 'setMacFileTypeAndCreator' From: 'FilePlugin'.
setMacType = 0 ifFalse:
[self cCode: '((sqInt (*)(char *, char *, char *))setMacType)(imageName, "STim", "FAST")']].
"Without contexts or stacks simulate
self pop: 1"
objectMemory
Expand Down Expand Up @@ -16804,18 +16802,13 @@ StackInterpreter >> writeImageFileIO [
<var: #imageName declareC: 'extern char imageName[]'>

self cCode: [] inSmalltalk: [imageName := 'sooth compiler'. ^self writeImageFileIOSimulation].

"If the security plugin can be loaded, use it to check for write permission.
If not, assume it's ok"
sCWIfn := self ioLoadFunction: 'secCanWriteImage' From: 'SecurityPlugin'.
sCWIfn ~= 0 ifTrue:
[okToWrite := self cCode: '((sqInt (*)(void))sCWIfn)()'.
okToWrite ifFalse:[^self primitiveFail]].

"local constants"
headerStart := 0.
headerSize := objectMemory wordSize = 4 ifTrue: [64] ifFalse: [128]. "header size in bytes; do not change!"

self logDebug: 'Writing snapshot file %s' _: imageName.

f := self sqImageFile: imageName Open: 'wb'.
f = nil ifTrue: "could not open the image file for writing"
[^self primitiveFail].
Expand Down Expand Up @@ -16869,7 +16862,9 @@ StackInterpreter >> writeImageFileIO [
File: imageBytes
Write: f].
self success: bytesWritten = imageBytes.
self sqImageFileClose: f
self sqImageFileClose: f.

self logDebug: 'Snapshot file %s done' _: imageName.
]

{ #category : #'image save/restore' }
Expand Down
21 changes: 21 additions & 0 deletions smalltalksrc/VMMaker/VMClass.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -745,6 +745,27 @@ VMClass >> logError: aFormat withArgs: args [
Error signal: (aFormat printf: args)
]

{ #category : #'debug support' }
VMClass >> logWarn: aMessage [

<doNotGenerate>
self logWarn: aMessage withArgs: #()
]

{ #category : #'debug support' }
VMClass >> logWarn: aMessage _: anArgument [

<doNotGenerate>
self logWarn: aMessage withArgs: { anArgument }
]

{ #category : #'debug support' }
VMClass >> logWarn: aFormat withArgs: args [

<doNotGenerate>
(aFormat printf: args) traceCr
]

{ #category : #'memory access' }
VMClass >> long64AtPointer: pointer [
"This gets implemented by Macros in C, where its types will also be checked.
Expand Down

0 comments on commit e793384

Please sign in to comment.