-
Notifications
You must be signed in to change notification settings - Fork 71
/
StackInterpreterSimulator.class.st
1766 lines (1508 loc) · 55.8 KB
/
StackInterpreterSimulator.class.st
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
"
This class defines basic memory access and primitive simulation so that the StackInterpreter can run simulated in the Squeak environment. It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.
To see the thing actually run, you could (after backing up this image and changes), execute
(StackInterpreterSimulator new openOn: Smalltalk imageName) test
((StackInterpreterSimulator newWithOptions: #(NewspeakVM true MULTIPLEBYTECODESETS true))
openOn: 'ns101.image') test
and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be. We usually do this with a small and simple benchmark image.
Here's an example of what Eliot uses to launch the simulator in a window. The bottom-right window has a menu packed with useful stuff:
| vm |
vm := StackInterpreterSimulator newWithOptions: #().
vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
vm setBreakSelector: #&.
vm openAsMorph; run
"
Class {
#name : #StackInterpreterSimulator,
#superclass : #StackInterpreterPrimitives,
#traits : 'TVMSimulator',
#classTraits : 'TVMSimulator classTrait',
#instVars : [
'parent',
'bootstrapping',
'byteCount',
'breakCount',
'sendCount',
'lookupCount',
'printSends',
'printReturns',
'traceOn',
'myBitBlt',
'filesOpen',
'imageName',
'pluginList',
'mappedPluginEntries',
'quitBlock',
'transcript',
'eventTransformer',
'printFrameAtEachStep',
'printBytecodeAtEachStep',
'systemAttributes',
'startMicroseconds',
'lastYieldMicroseconds',
'externalSemaphoreSignalRequests',
'externalSemaphoreSignalResponses',
'extSemTabSize',
'atEachStepBlock',
'disableBooleanCheat',
'performFilters',
'eventQueue',
'assertVEPAES',
'primTraceLog'
],
#category : #'VMMaker-InterpreterSimulation'
}
{ #category : #'instance creation' }
StackInterpreterSimulator class >> isNonArgumentImplicitReceiverVariableName: aName [
^ (self localSlots collect: [ :e | e name ]) includes: aName
]
{ #category : #'instance creation' }
StackInterpreterSimulator class >> new [
^self onObjectMemory: nil options: #()
]
{ #category : #'instance creation' }
StackInterpreterSimulator class >> newBasicWithOptions: optionsDictionaryOrArray [
^ self
onObjectMemory: nil
options: optionsDictionaryOrArray
initializer: [ :interpreter | interpreter basicInitialize ]
]
{ #category : #'instance creation' }
StackInterpreterSimulator class >> newWithOptions: optionsDictionaryOrArray [
^self onObjectMemory: nil options: optionsDictionaryOrArray
]
{ #category : #'instance creation' }
StackInterpreterSimulator class >> onObjectMemory: anObjectMemory [
^self onObjectMemory: anObjectMemory options: #()
]
{ #category : #'instance creation' }
StackInterpreterSimulator class >> onObjectMemory: anObjectMemory options: optionsDictionaryOrArray [
^ self
onObjectMemory: anObjectMemory
options: optionsDictionaryOrArray
initializer: [ :interpreter | interpreter initialize ]
]
{ #category : #'instance creation' }
StackInterpreterSimulator class >> onObjectMemory: anObjectMemory options: optionsDictionaryOrArray initializer: initializer [
| simulatorClass |
^self == StackInterpreterSimulator
ifTrue:
[simulatorClass := SmalltalkImage current endianness == #big
ifTrue: [self notYetImplemented"StackInterpreterSimulatorMSB"]
ifFalse: [StackInterpreterSimulatorLSB].
simulatorClass initializeWithOptions: optionsDictionaryOrArray
objectMemoryClass: (anObjectMemory ifNotNil: [anObjectMemory class]).
simulatorClass
onObjectMemory: (anObjectMemory ifNil:
[self objectMemoryClass simulatorClass new])
options: optionsDictionaryOrArray]
ifFalse: [initializer value: (super basicNew objectMemory: anObjectMemory)]
]
{ #category : #'debug support' }
StackInterpreterSimulator >> allObjectsSelect: objBlock [
"self allObjectsSelect: [:oop | (self baseHeader: oop) = 1234]"
| selected |
selected := OrderedCollection new.
objectMemory allObjectsDo:
[:obj|
(objBlock value: obj) ifTrue: [selected addLast: obj]].
^selected
]
{ #category : #'spur bootstrap' }
StackInterpreterSimulator >> argumentCount: n [
argumentCount := n
]
{ #category : #'debug support' }
StackInterpreterSimulator >> assertValidExecutionPointers [
assertVEPAES ifTrue:
[super assertValidExecutionPointers]
]
{ #category : #accessing }
StackInterpreterSimulator >> assertValidExecutionPointersAtEachStep [
^assertVEPAES
]
{ #category : #accessing }
StackInterpreterSimulator >> assertValidExecutionPointersAtEachStep: aBoolean [
assertVEPAES := aBoolean
]
{ #category : #testing }
StackInterpreterSimulator >> atEachStepBlock: aBlock [
atEachStepBlock := aBlock
]
{ #category : #initialization }
StackInterpreterSimulator >> basicInitialize [
"Initialize the StackInterpreterSimulator when running the interpreter
inside Smalltalk. The primary responsibility of this method is to allocate
Smalltalk Arrays for variables that will be declared as statically-allocated
global arrays in the translated code."
super initialize.
bootstrapping := false.
transcript := Transcript.
objectMemory ifNil:
[objectMemory := self class objectMemoryClass simulatorClass new].
objectMemory coInterpreter: self.
self assert: ConstMinusOne = (objectMemory integerObjectOf: -1).
methodCache := Array new: MethodCacheSize.
atCache := Array new: AtCacheTotalSize.
self flushMethodCache.
gcSemaphoreIndex := 0.
externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
externalPrimitiveTable := CArrayAccessor on: (Array
new: MaxExternalPrimitiveTableSize
withAll: 0).
externalPrimitiveTableFirstFreeIndex := 0.
primitiveTable := self class primitiveTable copy.
desiredNumStackPages := desiredEdenBytes := 0.
"This is initialized on loading the image, but convenient for testing stack page values..."
numStackPages := self defaultNumStackPages.
startMicroseconds := lastYieldMicroseconds := self ioUTCStartMicroseconds.
"initialize InterpreterSimulator variables used for debugging"
byteCount := sendCount := lookupCount := 0.
quitBlock := [^self close].
traceOn := true.
printSends := printReturns := printFrameAtEachStep := printBytecodeAtEachStep := false.
myBitBlt := BitBltSimulator new setInterpreter: self.
eventQueue := SharedQueue new.
suppressHeartbeatFlag := false.
systemAttributes := Dictionary new.
extSemTabSize := 256.
disableBooleanCheat := false.
assertVEPAES := false. "a flag so the assertValidExecutionPointers can be disabled for simulation speed and enabled when necessary."
"This will be overriden when calling initializePluginEntries"
mappedPluginEntries := OrderedCollection new.
imageReaderWriter := VMImageReaderWriter newWithMemory: objectMemory andInterpreter: self.
]
{ #category : #'spur bootstrap' }
StackInterpreterSimulator >> bootstrapping [
^bootstrapping
]
{ #category : #'spur bootstrap' }
StackInterpreterSimulator >> bootstrapping: aBoolean [
bootstrapping := aBoolean.
objectMemory ifNotNil:
[objectMemory bootstrapping: aBoolean]
]
{ #category : #accessing }
StackInterpreterSimulator >> breakCount [
^breakCount
]
{ #category : #'memory access' }
StackInterpreterSimulator >> byteAt: byteAddress [
"This is really only for the C library simulations memcpy:_:_: et al in VMClass.
Use objectMemory byteAt: directly where possible."
^objectMemory byteAt: byteAddress
]
{ #category : #'memory access' }
StackInterpreterSimulator >> byteAt: byteAddress put: byte [
self deprecated.
^objectMemory byteAt: byteAddress put: byte
]
{ #category : #'debug support' }
StackInterpreterSimulator >> byteCount [
"So you can call this from temp debug statements in, eg, Interpreter, such as
self byteCount = 12661 ifTrue: [self halt].
"
^ byteCount
]
{ #category : #UI }
StackInterpreterSimulator >> byteCountText [
^ byteCount asStringWithCommas asText
]
{ #category : #'indexing primitives' }
StackInterpreterSimulator >> bytecodePrimAtPut [
"self halt."
^super bytecodePrimAtPut
]
{ #category : #'translation support' }
StackInterpreterSimulator >> cCoerceSimple: value to: cTypeString [
"Type coercion for translation only; just return the value when running in Smalltalk."
^value
]
{ #category : #'plugin support' }
StackInterpreterSimulator >> callExternalPrimitive: mapIndex [
| entry |
entry := self pluginEntryFor: mapIndex.
"Spur needs the primitiveFunctionPointer to be set correctly
for accurate following of forwarders on primitive failure."
primitiveFunctionPointer := entry at: 2.
^ (entry at: 1) perform: (entry at: 2)
]
{ #category : #'object memory support' }
StackInterpreterSimulator >> checkStackIntegrity [
"Override to deal with incomplete initialization."
stackPages ifNil: [^true].
^super checkStackIntegrity
]
{ #category : #'debug support' }
StackInterpreterSimulator >> classAndSelectorOfMethod: meth forReceiver: rcvr [
| mClass dict length methodArray |
mClass := objectMemory fetchClassOf: rcvr.
[dict := objectMemory fetchPointer: MethodDictionaryIndex ofObject: mClass.
length := objectMemory numSlotsOf: dict.
methodArray := objectMemory fetchPointer: MethodArrayIndex ofObject: dict.
0 to: length-SelectorStart-1 do:
[:index |
meth = (objectMemory fetchPointer: index ofObject: methodArray)
ifTrue: [^ Array
with: mClass
with: (objectMemory fetchPointer: index + SelectorStart ofObject: dict)]].
mClass := self superclassOf: mClass.
mClass = objectMemory nilObject]
whileFalse.
^ Array
with: (objectMemory fetchClassOf: rcvr)
with: (objectMemory splObj: SelectorDoesNotUnderstand)
]
{ #category : #'plugin support' }
StackInterpreterSimulator >> classNameOf: aClass Is: className [
"Check if aClass' name is className"
| name |
(objectMemory lengthOf: aClass) <= classNameIndex ifTrue:
[^false]. "Not a class but maybe behavior"
name := objectMemory fetchPointer: classNameIndex ofObject: aClass.
(objectMemory isBytes: name) ifFalse:
[^false].
^ className = (self stringOf: name)
]
{ #category : #'I/O primitives' }
StackInterpreterSimulator >> clipboardRead: sz Into: actualAddress At: zeroBaseIndex [
| str |
str := Clipboard clipboardText.
1 to: sz do:
[:i | objectMemory byteAt: actualAddress + zeroBaseIndex + i - 1 put: (str at: i) asciiValue]
]
{ #category : #'I/O primitives' }
StackInterpreterSimulator >> clipboardSize [
^ Clipboard clipboardText size
]
{ #category : #'debug support' }
StackInterpreterSimulator >> cloneSimulation [
| savedAtEachStepBlock savedQuitBlock savedTranscript |
savedAtEachStepBlock := atEachStepBlock.
atEachStepBlock := nil.
savedQuitBlock := quitBlock.
quitBlock := nil.
savedTranscript := transcript.
transcript := nil.
^ [
| theClone |
Smalltalk garbageCollect.
theClone := self veryDeepCopy.
theClone
parent: self;
transcript: Transcript.
theClone objectMemory parent: objectMemory.
theClone ] ensure: [
atEachStepBlock := savedAtEachStepBlock.
quitBlock := savedQuitBlock.
transcript := savedTranscript ]
]
{ #category : #initialization }
StackInterpreterSimulator >> close [ "close any files that ST may have opened, etc"
pluginList do: [:assoc| | plugin | plugin := assoc value. plugin ~~ self ifTrue: [plugin close]]
]
{ #category : #'primitive support' }
StackInterpreterSimulator >> codeGeneratorToComputeAccessorDepth [
^ codeGeneratorToComputeAccessorDepth ifNil: [
^(VMMaker new
vmmakerConfiguration: VMMakerConfiguration;
buildCodeGeneratorForInterpreter: self class primitivesClass
includeAPIMethods: false
initializeClasses: false)
logger: self transcript;
yourself ]
]
{ #category : #'simulation only' }
StackInterpreterSimulator >> cogit [
"We don't have a cogit; try and get by on our own devices."
^self
]
{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> copyBits [
^ myBitBlt copyBits
]
{ #category : #'debug printing' }
StackInterpreterSimulator >> cr [
traceOn ifTrue: [ transcript cr; flush ].
]
{ #category : #UI }
StackInterpreterSimulator >> desiredDisplayExtent [
^(savedWindowSize
ifNil: [640@480]
ifNotNil: [savedWindowSize >> 16 @ (savedWindowSize bitAnd: 16rFFFF)])
min: Display extent * 2 // 3
]
{ #category : #initialization }
StackInterpreterSimulator >> desiredEdenBytes: anInteger [
desiredEdenBytes := anInteger
]
{ #category : #initialization }
StackInterpreterSimulator >> desiredNumStackPages: anInteger [
desiredNumStackPages := anInteger
]
{ #category : #testing }
StackInterpreterSimulator >> disableBooleanCheat: aBoolean [
disableBooleanCheat := aBoolean
]
{ #category : #'interpreter shell' }
StackInterpreterSimulator >> dispatchCurrentBytecode [
self dispatchOn: currentBytecode in: BytecodeTable.
]
{ #category : #'plugin primitive support' }
StackInterpreterSimulator >> dispatchMappedPluginEntry: n [
^(mappedPluginEntries at: n) first
perform: (mappedPluginEntries at: n) second
]
{ #category : #'interpreter shell' }
StackInterpreterSimulator >> dispatchOn: anInteger in: selectorArray [
"Simulate a case statement via selector table lookup.
The given integer must be between 0 and selectorArray size-1, inclusive.
For speed, no range test is done, since it is done by the at: operation.
Note that, unlike many other arrays used in the Interpreter, this method expect NO CArrayAccessor wrapping - it would duplicate the +1. Maybe this would be better updated to make it all uniform"
self perform: (selectorArray at: (anInteger + 1)).
]
{ #category : #'debugging traps' }
StackInterpreterSimulator >> divorceFrame: theFP andContext: ctxt [
"(theFP = -208 or: [ctxt = 22189568]) ifTrue:
[self halt]."
^super divorceFrame: theFP andContext: ctxt
]
{ #category : #'process primitive support' }
StackInterpreterSimulator >> doSignalExternalSemaphores: minTableSize [
"This is a non-thread-safe simulation. See platforms/Cross/vm/sqExternalSemaphores.c
for the real code. For the benefit of the SocketPluginSimulator, do a yield every 100
virtual microseconds."
| now switched |
now := self ioUTCMicroseconds.
now - lastYieldMicroseconds >= 100 ifTrue:
[lastYieldMicroseconds := now.
Processor yield].
switched := false.
1 to: (minTableSize min: externalSemaphoreSignalRequests size) do:
[:i| | responses |
responses := externalSemaphoreSignalResponses at: i.
[responses < (externalSemaphoreSignalRequests at: i)] whileTrue:
[(self doSignalSemaphoreWithIndex: i) ifTrue:
[switched := true].
externalSemaphoreSignalResponses at: i put: (responses := responses + 1)]].
^switched
]
{ #category : #'error handling' }
StackInterpreterSimulator >> doesNotUnderstand: aMessage [
"If this is a doit and the objectMemory understands, pass it on."
(thisContext findContextSuchThat: [:ctxt| ctxt selector == #evaluate:in:to:notifying:ifFail:logged:]) ifNotNil:
[(objectMemory class whichClassIncludesSelector: aMessage selector) ifNotNil:
[:implementingClass|
(implementingClass inheritsFrom: Object) ifTrue: "i.e. VMClass and below"
[thisContext sender selector ~~ #DoIt ifTrue:
[Transcript nextPutAll: 'warning: redirecting ', aMessage selector, ' in ', thisContext sender printString, ' to objectMemory'; cr; flush].
aMessage lookupClass: nil.
^aMessage sentTo: objectMemory]]].
^super doesNotUnderstand: aMessage
]
{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> drawLoopX: xDelta Y: yDelta [
^ myBitBlt drawLoopX: xDelta Y: yDelta
]
{ #category : #'debug support' }
StackInterpreterSimulator >> dumpMethodHeader: hdr [
^ String streamContents:
[:strm |
strm nextPutAll: '<nArgs=', ((hdr >> 25) bitAnd: 16r1F) printString , '>'.
strm nextPutAll: '<nTemps=', ((hdr >> 19) bitAnd: 16r3F) printString , '>'.
strm nextPutAll: '<lgCtxt=', ((hdr >> 18) bitAnd: 16r1) printString , '>'.
strm nextPutAll: '<nLits=', ((hdr >> 10) bitAnd: 16rFF) printString , '>'.
strm nextPutAll: '<prim=', ((hdr >> 1) bitAnd: 16r1FF) printString , '>'.
]
]
{ #category : #'debug printing' }
StackInterpreterSimulator >> elementsPerPrintOopLine [
^4
]
{ #category : #'compiled methods' }
StackInterpreterSimulator >> endPCOf: aMethod [
"Determine the endPC of a method in the heap using interpretation that looks for returns and uses branches to skip intervening bytecodes."
| pc end farthestContinuation prim encoderClass inst is |
(prim := self primitiveIndexOf: aMethod) > 0 ifTrue:
[(self isQuickPrimitiveIndex: prim) ifTrue:
[^(self startPCOfMethod: aMethod) - 1]].
encoderClass := self encoderClassForHeader: (objectMemory methodHeaderOf: aMethod).
is := (InstructionStream
on: (VMCompiledMethodProxy new
for: aMethod
coInterpreter: self
objectMemory: objectMemory)).
pc := farthestContinuation := self startPCOfMethod: aMethod.
end := objectMemory numBytesOf: aMethod.
is pc: pc + 1.
[pc <= end] whileTrue:
[inst := encoderClass interpretNextInstructionFor: MessageCatcher new in: is.
inst selector
caseOf: {
[#pushClosureCopyNumCopiedValues:numArgs:blockSize:]
-> [is pc: is pc + inst arguments last.
farthestContinuation := farthestContinuation max: pc].
[#jump:] -> [farthestContinuation := farthestContinuation max: pc + inst arguments first].
[#jump:if:] -> [farthestContinuation := farthestContinuation max: pc + inst arguments first].
[#methodReturnConstant:] -> [pc >= farthestContinuation ifTrue: [end := pc]].
[#methodReturnReceiver] -> [pc >= farthestContinuation ifTrue: [end := pc]].
[#methodReturnTop] -> [pc >= farthestContinuation ifTrue: [end := pc]].
"This is for CompiledBlock/FullBlockClosure. Since the response to pushClosure... above
skips over all block bytecoes, we will only see a blockReturnTop if it is at the top level,
and so it must be a blockReturnTop in a CompiledBlock for a FullBlockClosure."
[#blockReturnTop] -> [pc >= farthestContinuation ifTrue: [end := pc]].
[#branchIfInstanceOf:distance:]
-> [farthestContinuation := farthestContinuation max: pc + inst arguments last].
[#branchIfNotInstanceOf:distance:]
-> [farthestContinuation := farthestContinuation max: pc + inst arguments last] }
otherwise: [].
pc := is pc - 1].
^end
]
{ #category : #'interpreter shell' }
StackInterpreterSimulator >> fetchByte [
^objectMemory byteAt: (instructionPointer := instructionPointer + 1).
]
{ #category : #'control primitives' }
StackInterpreterSimulator >> filterPerformOf: selector to: receiver [
"This is to allow simulator to filter start-up items to avoid as-yet unsimulatable plugins."
performFilters ifNil: [^false].
(performFilters at: (self shortPrint: receiver) ifAbsent: []) ifNotNil:
[:messages|
^messages includes: (self stringOf: selector)].
^false
]
{ #category : #'memory access' }
StackInterpreterSimulator >> firstIndexableField: oop [
"This is in ObjectMemory and overridden in the obj mem simulators"
self shouldNotImplement
]
{ #category : #'debug printing' }
StackInterpreterSimulator >> flush [
traceOn ifTrue: [transcript flush]
]
{ #category : #'plugin support' }
StackInterpreterSimulator >> flushExternalPrimitives [
self initializePluginEntries.
super flushExternalPrimitives
]
{ #category : #'control primitives' }
StackInterpreterSimulator >> forShortPrintString: shortPrintString filterPerformMessages: aCollection [
performFilters ifNil:
[performFilters := Dictionary new].
performFilters at: shortPrintString put: aCollection
]
{ #category : #'frame access' }
StackInterpreterSimulator >> frameOfMarriedContext: aContext [
| senderOop |
senderOop := objectMemory fetchPointer: SenderIndex ofObject: aContext.
self assert: (objectMemory isIntegerObject: senderOop).
^self withoutSmallIntegerTags: senderOop
]
{ #category : #'spur bootstrap' }
StackInterpreterSimulator >> framePointer [
^framePointer
]
{ #category : #'interpreter shell' }
StackInterpreterSimulator >> functionPointerFor: primIndex inClass: lookupClass [
"Override Interpreter to handle the external primitives caching. See also
internalExecuteNewMethod."
^(primIndex between: 1 and: MaxPrimitiveIndex)
ifTrue: [primitiveTable at: primIndex + 1]
ifFalse: [0]
]
{ #category : #'debugging traps' }
StackInterpreterSimulator >> getErrorObjectFromPrimFailCode [
(primFailCode > 1 and: [(#(primitiveNew primitiveNewWithArg primitiveFetchNextMourner primitiveAdoptInstance) includes: primitiveFunctionPointer) not]) ifTrue: [self halt].
^super getErrorObjectFromPrimFailCode
]
{ #category : #'memory access' }
StackInterpreterSimulator >> halfWordHighInLong32: long32 [
^self subclassResponsibility
]
{ #category : #'memory access' }
StackInterpreterSimulator >> halfWordLowInLong32: long32 [
^self subclassResponsibility
]
{ #category : #'debug support' }
StackInterpreterSimulator >> headerStart: oop [
^ (objectMemory extraHeaderBytes: oop) negated
]
{ #category : #'image save/restore' }
StackInterpreterSimulator >> imageName [
^imageName
]
{ #category : #'spur bootstrap' }
StackInterpreterSimulator >> imageName: aString [
imageName := aString
]
{ #category : #'file primitives' }
StackInterpreterSimulator >> imageNameGet: p Length: sz [
1 to: sz do:
[:i |
objectMemory
byteAt: p + i - 1
put: (imageName at: i) asInteger]
]
{ #category : #'file primitives' }
StackInterpreterSimulator >> imageNamePut: p Length: sz [
| newName |
newName := ByteString new: sz.
1 to: sz do: [ :i |
newName
at: i
put: (Character value: (objectMemory byteAt: p + i - 1)) ].
imageName := newName
]
{ #category : #'file primitives' }
StackInterpreterSimulator >> imageNameSize [
^imageName size
]
{ #category : #'interpreter shell' }
StackInterpreterSimulator >> incrementByteCount [
(byteCount := byteCount + 1) = breakCount ifTrue:
[ self halt: 'breakCount reached' ].
byteCount \\ 1000 = 0 ifTrue:
[ self forceInterruptCheck ]
]
{ #category : #initialization }
StackInterpreterSimulator >> initialize [
"Initialize the StackInterpreterSimulator when running the interpreter
inside Smalltalk. The primary responsibility of this method is to allocate
Smalltalk Arrays for variables that will be declared as statically-allocated
global arrays in the translated code."
super initialize.
self basicInitialize.
self initializePluginEntries.
]
{ #category : #'plugin support' }
StackInterpreterSimulator >> initializePluginEntries [
mappedPluginEntries := OrderedCollection new.
primitiveAccessorDepthTable := Array new: primitiveTable size.
pluginList := { }.
self loadNewPlugin: ''
]
{ #category : #'interpreter shell' }
StackInterpreterSimulator >> insufficientMemorySpecifiedError [
self error: 'Insufficient memory for this image'
]
{ #category : #'interpreter shell' }
StackInterpreterSimulator >> interpret [
"This is the main interpreter loop. It normally loops forever, fetching and executing bytecodes.
When running in the context of a web browser plugin VM, however, it must return control to the
web browser periodically. This should done only when the state of the currently running Squeak
thread is safely stored in the object heap. Since this is the case at the moment that a check for
interrupts is performed, that is when we return to the browser if it is time to do so. Interrupt
checks happen quite frequently.
Override for simulation to insert bytecode breakpoint support."
"If stacklimit is zero then the stack pages have not been initialized."
<inline: false>
stackLimit = 0 ifTrue: [ ^ self initStackPagesAndInterpret ].
self initExtensions.
self fetchNextBytecode.
[ true ] whileTrue: [
self assertValidExecutionPointers.
atEachStepBlock value. "N.B. may be nil"
self dispatchCurrentBytecode.
self incrementByteCount ].
instructionPointer := instructionPointer - 1. "undo the pre-increment of IP before returning"
^ nil
]
{ #category : #'stack pages' }
StackInterpreterSimulator >> interpreterAllocationReserveBytes [
^bootstrapping
ifTrue: [0]
ifFalse: [super interpreterAllocationReserveBytes]
]
{ #category : #'interpreter shell' }
StackInterpreterSimulator >> invalidCompactClassError: name [
self error: 'Class ', name, ' does not have the required compact class index'
]
{ #category : #security }
StackInterpreterSimulator >> ioCanRenameImage [
^true
]
{ #category : #security }
StackInterpreterSimulator >> ioCanWriteImage [
^true
]
{ #category : #'primitive support' }
StackInterpreterSimulator >> ioExit [
quitBlock value "Cause return from #test"
]
{ #category : #'primitive support' }
StackInterpreterSimulator >> ioExitWithErrorCode: ec [
quitBlock value "Cause return from #test"
]
{ #category : #'process primitive support' }
StackInterpreterSimulator >> ioGetMaxExtSemTableSize [
^extSemTabSize
]
{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> ioHeartbeatMilliseconds [
^1
]
{ #category : #initialization }
StackInterpreterSimulator >> ioInitHeartbeat [
"No-op in the simulator. We cause a poll every 1000 bytecodes instead."
]
{ #category : #'plugin support' }
StackInterpreterSimulator >> ioLoadFunction: functionString From: pluginString [
"Load and return the requested function from a module"
| firstTime plugin fnSymbol |
firstTime := false.
fnSymbol := functionString asSymbol.
transcript
cr;
show: '(', byteCount printString, ') Looking for ', functionString, ' in ',
(pluginString isEmpty ifTrue: ['vm'] ifFalse: [pluginString]).
(breakSelector notNil
and: [(pluginString size = breakSelector size
and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0])
or: [functionString size = breakSelector size
and: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
[self halt: pluginString, '>>', functionString].
plugin := pluginList
detect: [:any| any key = pluginString asString]
ifNone:
[firstTime := true.
self loadNewPlugin: pluginString].
plugin ifNil:
[firstTime ifTrue: [transcript cr; show: '... FAILED; no plugin found'].
^0].
plugin := plugin value.
mappedPluginEntries withIndexDo:
[:pluginAndName :index|
((pluginAndName at: 1) == plugin
and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:
[^index]].
(plugin respondsTo: fnSymbol) ifFalse:
[firstTime ifTrue: [transcript cr; show: '... FAILED; primitive not in plugin'].
^0].
mappedPluginEntries addLast: { plugin. fnSymbol }.
transcript show: ' ... okay'.
^mappedPluginEntries size
]
{ #category : #'plugin support' }
StackInterpreterSimulator >> ioLoadFunction: functionString From: pluginString AccessorDepthInto: accessorDepthPtr [
"Load and return the requested function from a module.
Assign the accessor depth through accessorDepthPtr.
N.B. The actual code lives in platforms/Cross/vm/sqNamedPrims.h"
| firstTime plugin fnSymbol |
firstTime := false.
fnSymbol := functionString asSymbol.
transcript
cr;
show: '(', byteCount printString, ') Looking for ', functionString, ' in ',
(pluginString isEmpty ifTrue: ['vm'] ifFalse: [pluginString]).
(breakSelector notNil
and: [(pluginString size = breakSelector size
and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0])
or: [functionString size = breakSelector size
and: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
[self halt: pluginString, '>>', functionString].
plugin := pluginList
detect: [:any| any key = pluginString asString]
ifNone:
[firstTime := true.
self loadNewPlugin: pluginString].
plugin ifNil:
[firstTime ifTrue: [transcript show: '... FAILED; no plugin found'].
^0].
plugin := plugin value.
mappedPluginEntries withIndexDo:
[:pluginAndName :index|
((pluginAndName at: 1) == plugin
and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:
[firstTime ifTrue: [transcript show: ' ... okay'].
accessorDepthPtr at: 0 put: (pluginAndName at: 4).
^index]].
firstTime ifTrue: [transcript show: '... FAILED; primitive not in plugin'].
^0
]
{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> ioMSecs [
"Return the value of the millisecond clock."
"NOT. Actually, we want something a lot slower and, for exact debugging,
something more repeatable than real time. I have an idea: use the byteCount... (di 7/1/2004 13:55)"
^self microsecondsToMilliseconds: self ioUTCMicroseconds
"At 20k bytecodes per second, this gives us about 200 ticks per second, or about 1/5 of what you'd expect for the real time clock. This should still service events at one or two per second"
]
{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> ioMicroMSecs [
"Answer the value of the high-resolution millisecond clock."
^ Time millisecondClockValue
]
{ #category : #'I/O primitives' }
StackInterpreterSimulator >> ioProcessEvents [
]
{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> ioRelinquishProcessorForMicroseconds: microseconds [
"In the simulator give an indication that we're idling and check for input."
Processor activeProcess == UIManager default uiProcess ifTrue:
[World doOneCycle].
microseconds >= 1000
ifTrue: [(Delay forMilliseconds: microseconds + 999 // 1000) wait]
ifFalse: [Processor yield].
"And increase the byteCount form which the microsecond clock is derived..."
byteCount := byteCount + microseconds - 1.
self incrementByteCount
]
{ #category : #'I/O primitives' }
StackInterpreterSimulator >> ioScreenDepth [
^DisplayScreen actualScreenDepth.
]
{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> ioScreenScaleFactor [
^ 1.0
]
{ #category : #'process primitive support' }
StackInterpreterSimulator >> ioSetMaxExtSemTableSize: anInteger [
"Inform the VM of the maximum size the image will grow the exernal semaphore table (specialObjectsArray at: 39) to.
This allows the VM to allocate storage such that external semaphores can be signalled without locking."
extSemTabSize := anInteger
]
{ #category : #'process primitive support' }
StackInterpreterSimulator >> ioSynchronousCheckForEvents [
"Hook allowing the platform to do anything it needs to do synchronously."
]
{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> ioUTCMicroseconds [
"Return the value of the microsecond clock."
"NOT. Actually, we want something a lot slower and, for exact debugging,
something more repeatable than real time. Dan had an idea: use the byteCount..."
^(byteCount // 50) + startMicroseconds
]
{ #category : #'I/O primitives support' }
StackInterpreterSimulator >> ioUTCStartMicroseconds [
"Answer the value of the microsecond clock at startup."
^startMicroseconds ifNil:
[self class initializationOptions
at: #startMicroseconds
ifAbsent: [[Time utcMicrosecondClock] on: Error do: [Time totalSeconds * 1000000]]]
]
{ #category : #'primitive support' }
StackInterpreterSimulator >> isPrimitiveFunctionPointerAnIndex [
"We save slots in the method cache by using the primitiveFunctionPointer
to hold either a function pointer or the index of a quick primitive. Since
quick primitive indices are small they can't be confused with function
addresses. But since we use 1001 and up for external primitives that
would be functions in the C VM but are indices under simulation we treat
values above 1000 as if they were pointers (actually indices into the
externalPrimitiveTable)"
^primitiveFunctionPointer isInteger
and: [primitiveFunctionPointer ~= 0
and: [primitiveFunctionPointer <= MaxQuickPrimitiveIndex]]
]
{ #category : #'compiled methods' }
StackInterpreterSimulator >> literal: offset [
"trap pushes of forwarded literals to help debug following forwarded primitive args.
it is not an error to push a forwarded literal, but we'd like to step through any resulting
primtive failure code.
Use #literalMaybeForwarder: for resolve forwarders if nedeed
"
| lit |
lit := super literal: offset.
(objectMemory isOopForwarded: lit) ifTrue:
[self halt: 'forwarded literal in ', thisContext selector].
^lit
]
{ #category : #'plugin support' }
StackInterpreterSimulator >> loadNewPlugin: pluginString [
breakSelector ifNotNil:
[(self strncmp: pluginString _: breakSelector _: pluginString size) = 0 ifTrue:
[self halt: pluginString]].
^(self tryLoadNewPlugin: pluginString pluginEntries: mappedPluginEntries) ifNotNil:
[:entry|
pluginList := pluginList copyWith: entry.
entry]
]
{ #category : #'memory access' }
StackInterpreterSimulator >> longAt: byteAddress [
self deprecated.
^objectMemory longAt: byteAddress
]
{ #category : #'memory access' }
StackInterpreterSimulator >> longAt: byteAddress put: a32BitValue [
self deprecated.
^objectMemory longAt: byteAddress put: a32BitValue
]
{ #category : #'callback support' }
StackInterpreterSimulator >> lookupOrdinaryNoMNUEtcInClass: class [
lookupCount := lookupCount + 1.
^super lookupOrdinaryNoMNUEtcInClass: class
]
{ #category : #'plugin support' }
StackInterpreterSimulator >> mappedPluginEntries [
^mappedPluginEntries
]
{ #category : #'frame access' }
StackInterpreterSimulator >> markContextAsDead: oop [
"(self withoutSmallIntegerTags: (objectMemory fetchPointer: SenderIndex ofObject: oop)) = -16r26824 ifTrue:
[self halt]."
^super markContextAsDead: oop
]
{ #category : #'simulation only' }
StackInterpreterSimulator >> methodForContext: aContextOop [
self assert: (objectMemory isContext: aContextOop).
^objectMemory fetchPointer: MethodIndex ofObject: aContextOop
]