Skip to content

Commit

Permalink
Merge pull request #248 from akgrant43/Issue233
Browse files Browse the repository at this point in the history
Limit the gloablSessionID (which is signed 64 bits) to 31 bits
  • Loading branch information
guillep authored Jun 15, 2021
2 parents 6c98da9 + 08832c2 commit bd08b32
Show file tree
Hide file tree
Showing 3 changed files with 48 additions and 4 deletions.
17 changes: 13 additions & 4 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -8175,6 +8175,18 @@ StackInterpreter >> initializeExtraClassInstVarIndices [
[classNameIndex := i - 1]]
]

{ #category : #initialization }
StackInterpreter >> initializeGlobalSessionID [
"Initialize the globalSessionID.
To ensure compatibility with old plugins, keep the value to a postive signed 32 bit integer"

[globalSessionID = 0] whileTrue:
[globalSessionID := self
cCode: [((self time: #NULL) + self ioMSecs) bitAnd: 16r7FFFFFFF]
inSmalltalk: [((self time: #NULL) + self ioMSecs) bitAnd: 16r7FFFFFFF]].

]

{ #category : #initialization }
StackInterpreter >> initializeInterpreter: bytesToShift [
"Initialize Interpreter state before starting execution of a new image."
Expand All @@ -8191,10 +8203,7 @@ StackInterpreter >> initializeInterpreter: bytesToShift [
self initialCleanup.
profileSemaphore := profileProcess := profileMethod := objectMemory nilObject.
interruptKeycode := 2094. "cmd-. as used for Mac but no other OS"
[globalSessionID = 0] whileTrue:
[globalSessionID := self
cCode: [(self time: #NULL) + self ioMSecs]
inSmalltalk: [(Random new next * (SmallInteger maxVal min: 16rFFFFFFFF)) asInteger]].
self initializeGlobalSessionID.
metaAccessorDepth := -2.
super initializeInterpreter: bytesToShift
]
Expand Down
7 changes: 7 additions & 0 deletions smalltalksrc/VMMaker/StackInterpreterSimulator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -2590,6 +2590,13 @@ StackInterpreterSimulator >> testWithFramePrint [
self test
]

{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> time: ignored [
"Simulate the glibc time() function"

^ DateAndTime now asUnixTime
]

{ #category : #UI }
StackInterpreterSimulator >> toggleTranscript [
| transcriptPane |
Expand Down
28 changes: 28 additions & 0 deletions smalltalksrc/VMMakerTests/VMSessionIdTest.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
Class {
#name : #VMSessionIdTest,
#superclass : #VMInterpreterTests,
#category : #'VMMakerTests-InterpreterTests'
}

{ #category : #tests }
VMSessionIdTest >> testGlobalSessionID [
"The globalSessionID is stored as a 64 bit number, but for compatibility with older plugins, is restricted to postive signed 32 bit values"
| vm predicted diff |

"The globalSessionID is the Unix time at startup + startMicroseconds.
The simulator allows startMicroseconds to be set, so we can force the value to have the top bit set in a 32 bit signed integer"
vm := StackInterpreterSimulator newWithOptions: {
#ObjectMemory -> #Spur64BitMemoryManager.
#startMicroseconds -> 16r80000000. } asDictionary.
vm initializeGlobalSessionID.

"Check that startMicroseconds is the expected value"
self assert: vm ioUTCStartMicroseconds equals: 16r80000000.
"Check that the globalSessionID is close to what we expect (allowing for a generous execution time"
predicted := DateAndTime now asUnixTime + (vm ioUTCMicroseconds // 1000).
diff := (predicted - vm getThisSessionID) abs.
self assert: diff < 180.

"Ensure that bit 32 isn't set"
self assert: vm getThisSessionID < 16r80000000.
]

0 comments on commit bd08b32

Please sign in to comment.