Primitive Index | Class-Selector Pairs |
1 | SmallInteger + |
2 | SmallInteger - |
3 | SmallInteger < |
4 | SmallInteger > |
5* | SmallInteger <= |
6* | SmallInteger >= |
7 | SmallInteger = |
8* | SmallInteger ~= |
9 | SmallInteger * |
10* | SmallInteger / |
11* | SmallInteger \\ |
12* | SmallInteger // |
13 | SmallInteger quo: |
14 | SmallInteger bitAnd: |
15 | SmallInteger bitOr: |
16 | SmallInteger bitXor: |
17 | SmallInteger bitShift: |
18* | Number @ |
19 | |
20 | |
21* | Integer +
LargePositiveInteger + |
22* | Integer -
LargePositiveInteger - |
23* | Integer <
LargePositiveInteger < |
24* | Integer >
LargePositiveInteger > |
25* | Integer <=
LargePositiveInteger <= |
26 | Integer >=
LargePositiveInteger >= |
27* | Integer =
LargePositiveInteger = |
28* | Integer ~=
LargePositiveInteger ~= |
29* | Integer *
LargePositiveInteger * |
30* | Integer /
LargePositiveInteger / |
31* | Integer \\
LargePositiveInteger \\ |
32* | Integer //
LargePositiveInteger // |
33* | Integer quo:
LargePositiveInteger quo: |
34* | Integer bitAnd:
LargePositiveInteger bitAnd: |
35* | Integer bitOr:
LargePositiveInteger bitOr: |
36* | Integer bitXor:
LargePositiveInteger bitXor: |
37* | Integer bitShift:
LargePositiveInteger bitShift: |
38 | |
39 | |
40 | SmallInteger asFloat |
41 | Float + |
42 | Float - |
43 | Float < |
44 | Float > |
45* | Float <= |
46* | Float >= |
47 | Float = |
48* | Float ~= |
49 | Float * |
50 | Float / |
51 | Float truncated |
52* | Float fractionPart |
53* | Float exponent |
54* | Float timesTwoPower: |
55 | |
56 | |
57 | |
58 | |
59 | |
60 | LargeNegativeInteger digitAt:
LargePositiveInteger digitAt: Object at: Object basicAt: |
61 | LargeNegativeInteger digitAt:put:
LargePositiveInteger digitAt:put: Object basicAt:put: Object at:put: |
62 | ArrayedCollection size
LargeNegativeInteger digitLength LargePositiveInteger digitLength Object basicSize Object size String size |
63 | String at:
String basicAt: |
64 | String basicAt:put:
String at:put: |
65* | ReadStream next
ReadWriteStream next |
66* | WriteStream nextPut: |
67* | PositionableStream atEnd |
68 | CompiledMethod objectAt: |
69 | CompiledMethod objectAt:put: |
70 | Behavior basicNew
Behavior new Interval class new |
71 | Behavior new:
Behavior basicNew: |
72 | Object become: |
73 | Object instVarAt: |
74 | Object instVarAt:put: |
75 | Object asOop
Object hash Symbol hash |
76 | SmallInteger asObject
SmallInteger asObjectNoFail |
77 | Behavior someInstance |
78 | Object nextInstance |
79 | CompiledMethod class newMethod:header: |
80* | ContextPart blockCopy: |
81 | BlockContext value:value:value:
BlockContext value BlockContext value: BlockContext value:value: |
82 | BlockContext valueWithArguments: |
83* | Object perform:with:with:with:
Object perform:with: Object perform:with:with: Object perform: |
84 | Object perform:withArguments: |
85 | Semaphore signal |
86 | Semaphore wait |
87 | Process resume |
88 | Process suspend |
89 | Behavior flushCache |
90* | InputSensor primMousePt
InputState primMousePt |
91 | InputState primCursorLocPut:
InputState primCursorLocPutAgain: |
92 | Cursor class cursorLink: |
93 | InputState primInputSemaphore: |
94 | InputState primSampleInterval: |
95 | InputState primInputWord |
96 | BitBlt copyBitsAgain
BitBlt copyBits |
97 | SystemDictionary snapshotPrimitive |
98 | Time class secondClockInto: |
99 | Time class millisecondClockInto: |
100 | ProcessorScheduler signal:atMilliseconds: |
101 | Cursor beCursor |
102 | DisplayScreen beDisplay |
103* | CharacterScanner scanCharactersFrom:to:in:rightX:stopConditions:displaying: |
104* | BitBlt drawLoopX:Y: |
105* | ByteArray primReplaceFrom:to:with:startingAt:
ByteArray replaceFrom:to:withString:startingAt: String replaceFrom:to:withByteArray:startingAt: String primReplaceFrom:to:with;startingAt: |
106 | |
107 | |
108 | |
109 | |
110 | Character =
Object == |
111 | Object class |
112 | SystemDictionary coreLeft |
113 | SystemDictionary quitPrimitive |
114 | SystemDictionary exitToDebugger |
115 | SystemDictionary oopsLeft |
116 | SystemDictionary signal:atOopsLeft:wordsLeft: |
117 | |
118 | |
119 | |
120 | |
121 | |
122 | |
123 | |
124 | |
125 | |
126 | |
127 |
newProcessWaiting | The newProcessWaiting register will be true if a process switch is called for and false otherwise. |
newProcess | If newProcessWaiting is true then the newProcess register will point to the Process to be transferred to. |
semaphoreList | The semaphoreList register points to an Array used by the interpreter to buffer Semaphores that should be signaled. This is an Array in Interpreter, not in the object memory. It will be a table in a machine-language interpreter. |
|
The semaphoreIndex register holds the
index of the last Semaphore in the semaphoreList buffer.
|
|
|
0 | Delta time (the parameter is the number of milliseconds since the last event of any type) |
1 | X location of the pointing device |
2 | Y location of the pointing device |
3 | Bi-state device turned on (the parameter indicates which device) |
4 | Bi-state device turned off (the parameter indicates which device) |
5 | Absolute time (the parameter is ignored, the
next two words in the buffer contain a 32-bit unsigned number that is the
absolute value of the millisecond clock)
|
key | parameter |
backspace | 8 |
tab | 9 |
line feed | 10 |
return | 13 |
escape | 27 |
space | 32 |
|
127
|
key | parameter |
left shift | 136 |
right shift | 137 |
control | 138 |
|
139
|
key | parameter |
left or top "pointing device" button | 130 |
center "pointing device" button | 129 |
right or bottom "pointing device" button | 128 |
|
131 through 135
|