29a78a1245e05d7efb3e0c85946525fd872ccbc6
[its.git] / sysdoc / usets.120
1 Copyright (c) 1999 Massachusetts Institute of Technology
2
3 This program is free software; you can redistribute it and/or modify
4 it under the terms of the GNU General Public License as published by
5 the Free Software Foundation; either version 2 of the License, or (at
6 your option) any later version.
7
8 This program is distributed in the hope that it will be useful, but
9 WITHOUT ANY WARRANTY; without even the implied warranty of
10 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
11 General Public License for more details.
12
13 You should have received a copy of the GNU General Public License
14 along with this program; if not, write to the Free Software
15 Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
16 ------------------------------
17
18 ITS USETS:
19
20 This file attempts to maintain up-to-date documentation on
21 all user variables hacked by .USET/.SUSET.  Those wonderful
22 souls who update the information in any way (additions,
23 deletions, corrections) should describe their
24 modifications in a brief note to INFO-ITS@AI so
25 that interested parties can correct their copies or
26 conceptions without needing to print or read the
27 entire file again.  For example:
28
29         :QMAIL INFO-ITS@AI I added more details to the .FOO user var ^C
30
31 If you want to be put on the INFO-ITS mailing list,
32 just say so in a message to it.
33 -------------------------------------------------
34 Each job running under ITS has a large number of variables
35 associated with it maintained by the system.  In order to
36 examine and set these variables, the .USET and .SUSET
37 uuo's are provided.  The .USET uuo allows the specification
38 of the job whose variables are to be accessed.  The .SUSET
39 uuo always accesses the variables of the job which executes it
40 (SUSET = Self USET).
41
42 The .USET uuo is used like this:        .USET CHNL,SPEC
43 and the .SUSET uuo like this:           .SUSET SPEC
44 The ac field CHNL of the USET must be the number of
45 an input/output channel for which a job is open,
46 as either the USR, JOB, or BOJ device.
47 The .USET may modify the variables only
48 if it has modification rights to the job (the job
49 is a JOB device, or is a direct inferior).
50
51 The contents of the effective address SPEC are of this form:
52         4.9     0 = read variable, 1 = set variable.
53         4.8     Block mode (see below).
54         4.7-3.1 Number of user variable to access.
55         2.9-2.1 Address of a location within the caller which
56                 is to receive the value of the variable, or which
57                 contains the new value for the variable.
58 If bit 4.8 is 1, then the word at location SPEC is really
59 an AOBJN pointer to a block of specifications.  This is
60 useful for getting several variables at a time easily.
61 The AOBJN pointer is updated as the operation progresses,
62 and so must be in a writable area.  Block mode may not be nested.
63 If an illegal specification is given to .USET or .SUSET,
64 the job will receive an illegal operation word 1 interrupt
65 (bit 1.6 of the .PIRQC user variable).
66
67 The variables are described in this document by the names which
68 DDT knows for them; the first character of each name is a ".".
69 If you open up a location by using one of these names, DDT
70 treats it specially and actually accesses the corresponding
71 variable and not a location in the job's core.
72
73 When writing .USET's and .SUSET's in MIDAS code,
74 one may use the symbols defined by MIDAS for accessing them.
75 These are the same as the names known to DDT, except that
76 the "." is followed by "R" for reading or "S" for setting.
77
78 If you open a location containing a SPEC, try typing
79 .R$?? if it is positive, or .S$?? if it is negative; this will
80 use bit typeout mode to print out the spec as it might have been
81 assembled; for example, 400001,,500  .S$??  gives .SVAL,,500 .
82
83 Examples:
84
85 To read your own runtime in 4-microsecond ticks into FOO:
86
87         .SUSET [.RRUNT,,FOO]
88
89 To set your word 1 interrupt mask:
90
91         .SUSET [.SMASK,,[%PIDWN\%PIPDL]]
92                 ;enable "pdl overflow" and "sys going down" interrupts
93
94 To read your input/output status word for channel 13 into FOO:
95
96         .SUSET [.RIOS+13,,FOO]
97
98 To start a job (your immediate inferior!) open on channel
99         USRC at its location QUUX, with its option
100         bits indicating your readiness to supply JCL:
101
102         .USET USRC,[.SOPTION,,[%OPCMD,,]]
103         .USET USRC,[.SUPC,,[QUUX]]
104         .USET USRC,[.SUSTP,,[0]]
105
106 Another way to do the same thing is:
107
108         MOVE AC,[-3,,USBLOK]
109         .USET USRC,AC
110           . . .
111 USBLOK: .SOPTION,,[%OPCMD,,]
112         .SUPC,,[QUUX]
113         .SUSTP,,[0]
114 \f
115 FORM OF DESCRIPTIONS:
116
117 The descriptions of the various variables accessible by
118 .USET and .SUSET are in the following form:
119
120 <DDT name>      <access>        <mnemonic explanation for name>
121
122         <long-winded paragraph describing variable>
123
124 The <access> descriptor contains four characters "wx yz".
125 The first two ("wx") refer to the access for .USET;
126 the last two ("yz") to the access for .SUSET.
127 In each case these characters are chosen from these sets:
128         --      May neither read nor set.
129         +-      May read but not set.
130         +*      May read and set.
131         +?      May read, may sometimes set (please read on...)
132 That is, + means may read, * may set, - denies access,
133 while ? says that things are more complicated.
134 \f
135 .40ADDR         +* +*   "40" address
136
137         The right half:
138
139         Initially 40 octal.  Whenever the system
140         references locations "40" through "44" specifically,
141         (e.g. giving the user interrupts, or returning uuo's 50-77),
142         the system really references the 5-word block that
143         .40ADDR points to.  Thus, if .40ADDR is set to 500, the
144         system expects location 502 to contain the address of
145         the interrupt routine.  This is especially useful to
146         distinguish system-returned uuo's (0 and 50-77) from
147         standard user-mode uuo's (1-37); the latter always
148         trap through location 40, while the former trap
149         through .40ADDR.
150         The various words accessed through .40ADDR are
151         as follows (indexed by "normal" location #):
152                 40      System places a uuo here when it wants
153                         to give it to the user.
154                 41      Should contain the address of the uuo handler.
155                         If .40ADDR is not indeed 40, this
156                         may be a different uuo handler from the
157                         one which handles uuo's 1-37.
158                         If .40ADDR is actually 40, then unless
159                         41's index and indirect fileds are 0 and its
160                         opcode is either 0 or JSR, all system-returned
161                         UUOs will cause ILOPR interrupts instead.
162                         This is to protect programs that want their
163                         hardware user-UUOs to be handled by a PUSHJ
164                         from being clobbered when they accidentally
165                         execute a meaningless UUO.
166                 42      If the job's %OPINT bit in its
167                         .OPTION variable (q.v.) is 0, then
168                         this is a JSR to the user's old-style
169                         interrupt handler.  The three words addressed
170                         by the JSR are, in order, the word in
171                         which the interrupt bits are placed, the
172                         return address for the interrupt, and the
173                         first instruction of the handler.
174                         If the %OPINT bit is 1, then this
175                         is an AOBJN pointer to a vector of
176                         5-word blocks describing the various
177                         interrupt handlers and their priorities.
178                         See ITS INTRUP for details.
179                 43      If the job's %OPLOK bit is set in
180                         its .OPTION variable, then this is
181                         the pointer to the list of switches
182                         to be reset if the job is killed.
183                 44      If the job's %OPLOK bit is set,
184                         this is an AOBJN pointer to a block
185                         of critical code region descriptors.
186                         See ITS LOCKS for details.
187
188         The left half:
189
190         Initially 20 octal.  This is the address of a block of
191         20 octal words which a job's superior may use to hack
192         that job.  For compatibility, if LH(.40ADDR) is zero,
193         the default of 20 will be assumed.
194 \f
195 .ADF1           +* +*   ANDCAM into .DF1
196
197         Like .DF1 (q.v.) when reading.
198         Performs ANDCAM into .DF1 when writing.
199
200 \1f
201 .ADF2           +* +*   ANDCAM into .DF2
202
203         Like .DF2 (q.v.) when reading.
204         Performs ANDCAM into .DF2 when writing.
205
206 \1f
207 .AIFPIR         +* +*   ANDCAM into .IFPIR
208
209         Like .IFPIR (q.v.) when reading.
210         Performs ANDCAM into .IFPIR when writing.
211
212 \1f
213 .AMASK          +* +*   ANDCAM into .MASK
214
215         Like .MASK (q.v.) when reading.
216         Performs ANDCAM into .MASK when writing.
217
218 \1f
219 .AMSK2          +* +*   ANDCAM into .MSK2
220
221         Like .MSK2 (q.v.) when reading.
222         Performs ANDCAM into .MSK2 when writing.
223
224 \1f
225 .APIRQC         +* +*   ANDCAM into .PIRQ
226
227         Like .PIRQC (q.v.) when reading.
228         Performs ANDCAM into .PIRQC when writing.
229 \f
230 .APRC           +- +-   APR CONO
231
232         4.9     Procedure is in a disowned tree.
233         4.7     (BUMRTL)  Tree will be gunned if hasn't run for an hour
234                 (meaningful only in top level job).  Cleared by reowning or
235                 attaching.  See the DETACH and DISOWN system calls.
236         4.6     Core request pending for this job.
237         4.5     User disabled, waiting to be flushed by SYS job.
238                 The SYS job will delete the job tree eventually.
239         4.4-4.1 .BCHN user variable (q.v.).
240         3.9     In process of deleting or logging out this job.
241                 Bit 4.5 will probably be set eventually.
242         3.5-3.1 Must be zero.
243         2.9-1.1 CONO'ed to APR whenever job is about
244                 to be run.  Initially 447.  Modified by
245                 altering the .MASK user variable.
246
247 \1f
248 .BCHN           +* +*   bad channel number
249
250         Initially 0.
251         Number of channel most recently in error.
252         Typically after reading this variable one does a
253         .STATUS or a STATUS symbolic system call
254         to get the status word for the channel.  This word
255         can then be fed to the ERR device.
256         .BCHN is actually part of the .APRC variable.
257         See also the .IOS variable.
258
259 \1f
260 .CNSL           +- +-   console tty number
261
262         If the job is in a console-controlled tree, this
263         variable contains the console's number, even if
264         the job doesn't own the console.  If the job is
265         in a non-console-controlled tree, .CNSL is -1
266         if the job is scheduled as part of the system,
267         -2 if the job is scheduled as a disowned job;
268         for a job-device-handler job, .CNSL is the same
269         as it is for the job it is serving.
270
271 \1f
272 .DF1            +* +*   defer bits, word 1
273
274         Initially 0.
275         Defer bits for word 1 interrupts (see .PIRQC
276         and .MASK).  If an interrupt bit is set in both
277         .PIRQC and .MASK, but is also set in .DF1,
278         it is temporarily deferred.
279
280 \1f
281 .DF2            +* +*   defer bits, word 2
282
283         Initially 0.
284         Defer bits for word 2 interrupts (see .IFPIR
285         and .MSK2).  If an interrupt bit is set in both
286         .IFPIR and .MSK2, but is also set in .DF2,
287         it is temporarily deferred.
288 \f
289 .EBO1           +- +-   KL-10 Ebox counter
290
291         This is the low-order word of the KL-10 Ebox counter
292         value for the job. It contains garbage on KA-10's.
293         Its location is .EBOX+1, for convenience.
294
295 \1f
296 .EBOX           +- +-   KL-10 Ebox counter
297
298         This is the high-order word of the KL-10 Ebox counter
299         value for the job. It contains garbage on KA-10's.
300
301 \1f
302 .FLS            +- --   flush instruction
303
304         Initially 0.
305         The instruction which is blocking the running of
306         the job.  Zero if user not blocked (user can run
307         if .USTP is also zero).
308         (The scheduler tests a job for runnability by first
309         checking the .USTP variable, and if it is zero,
310         then executing the flush instruction.  The job is
311         runnable iff the flush instruction skips.)
312
313 \1f
314 .FTL1           +- +-   Fatal interrupt first word
315
316         After a fatal interrupt, this variable contains the
317         .PIRQC bits which caused the error.  At any other time
318         it contains garbage.
319 \1f
320 .FTL2           +- +-   Fatal interrupt second word
321
322         After a fatal interrupt, this variable contains the
323         .IFPIR bits which caused the error.  At any other time
324         it contains garbage.
325
326 \1f
327 .HSNAME         +* +*   Home System Name
328
329         This is a word of sixbit like .SNAME (q.v.).  It
330         is initialized to be the same as the UNAME on creation
331         of a not-logged-in tree, and when a job is created
332         as an inferior or as a job device, it's .HSNAME is
333         copied from that of it's creator.  The LOGIN system call
334         sets it to be the same as the UNAME, although this should
335         be changed to be the XUNAME.
336
337         This is not used by ITS for anything, but is intended to
338         associate a directory with a specific XUNAME for the sake
339         of init and mail files of people without a directory of
340         the same name as their XUNAME.  DDT will soon initialize
341         it by looking up information in the INQUIR database for
342         the particular user.
343 \1f
344 .IDF1           +* +*   IORM into .DF1
345
346         Like .DF1 (q.v.) when reading.
347         Performs IORM into .DF1 when writing.
348 \f
349 .IDF2           +* +*   IORM into .DF2
350
351         Like .DF2 (q.v.) when reading.
352         Performs IORM into .DF2 when writing.
353
354 \1f
355 .IFPIR          +* +*   inferior procedure and i/o requests (?)
356
357         Initially 0.
358         This variable contains bits for pending word 2 interrupts.
359
360         Bit 3.n is the interrupt bit for the n'th job directly
361         inferior to the specified job (see the .INTB user variable).
362         These therefore occupy bits 3.8-3.1.
363         An inferior interrupt bit is set if an a class 1
364         or untrapped class 2 interrupt occurs in the inferior,
365         or if the inferior is using new-style interrupts
366         (see ITS INTRUP, and the %OPINT bit of the .OPTION
367         user variable) and any unhandled interrupt occurs.
368         Performing a .UCLOSE on an inferior clears the
369         inferior interrupt bit in the .IFPIR variable
370         of the job performing the .UCLOSE.
371
372         Bit 1.n is the interrupt bit for input/output
373         channel n-1 (actually, these occupy bits 2.7-1.1).
374         Thus bit 1.1 = channel 0, 1.2 = channel 1,
375         1.3 = channel 2, . . ., bit 2.7 = channel 17.
376         When an input/output interrupt is detected, the
377         system call WHYINT shoud be used to discover the
378         cause (see ITS .CALLS).
379
380         The following devices can cause channel interrupts:
381
382         TTY     Input:  A character was typed which according
383                         to the job's TTYST1 and TTYST2 variables
384                         (see ITS TTY) should be treated as an interrupt
385                         character.  If the tty is opened for input
386                         on more than one channel, only one channel,
387                         if any, receives the interrupt.
388                 Output: The **MORE** condition has occurred.
389                         See ITS TTY.
390         STY     Input:  Input is pending (i.e. the corresponding TTY
391                         has attempted output).  If the STY is open
392                         for input on more than one channel, only
393                         one channel, if any, receives the interrupt.
394                         See ITS TTY.
395                 Output: The STY's alter ego is waiting for input,
396                         or at least was (it isn't guaranteed not to
397                         stop waiting and do something else).
398         STK     Input is available.  Interrupts occur on all enabled channels.
399         USR     A foreign job open on the channel has been killed.
400                 If the job went away while the channel was pushed
401                 on the I/O pdl, this interrupt will occur when the
402                 channel is popped.  See the .UCLOSE, .IOPUSH, and
403                 .IOPOP uuo's.
404                 If the job is the PDP-6, the PDP-6 has requested an interrupt.
405         JOB     Various conditions, some programmable.  See ITS JOB.
406         BOJ     Various conditions, some programmable.  See ITS JOB.
407         NET     One of the following conditions has occurred:
408                         The IMP has gone down.
409                         RFC received.
410                         After RFC sent, the connection is now open.
411                         Input available.
412                         Connection closed.
413                         Net interrupt received (INR or INS).
414         MSP     Message has been sent.
415 \f
416 .IIFPIR         +* +*   IORM into .IFPIR
417
418         Like .IFPIR (q.v.) when reading.
419         Performs IORM into .IFPIR when writing.
420
421 \1f
422 .IMASK          +* +*   IORM into .MASK
423
424         Like .MASK (q.v.) when reading.
425         Performs IORM into .MASK when writing.
426
427 \1f
428 .IMSK2          +* +*   IORM into .MSK2
429
430         Like .MSK2 (q.v.) when reading.
431         Performs IORM into .MSK2 when writing.
432
433 \1f
434 .INTB           +- +-   interrupt bit
435
436         Gets the interrupt bit for the procedure.  This is
437         the word 2 interrupt bit which the procedure's
438         superior will see when the procedure interrupts
439         its superior.  This variable will therefore have
440         exactly one of bits 3.1-3.8 set, and no others.
441         If the procedure is top level (has no superior),
442         then this variable is negative.
443
444 \1f
445 .IOC +<n>       +- +-   input/output channel
446
447         The variable .IOC+<n> is the input/output channel
448         word for channel <n>, for n between 0 and 17 octal.
449         Normally zero for a closed channel.
450
451 \1f
452 .IOP +<n>       +- +-   input/output pdl
453
454         The input/output pdl is a pdl of two-word entries
455         used by the .IOPUSH, .IOPOP, and .IOPDL uuo's.
456         The first word of each pair is the .IOC word for
457         the stacked channel, and the second is the .IOS word.
458         In addition, bits 4.9-4.6 of the .IOS word of each
459         pair contain the channel number which the channel was
460         pushed from (this is used by the .IOPDL uuo).
461         The pdl has eight entries; thus <n> should be between
462         0 and 17 (0 is the .IOC word for the least recently
463         pushed entry, etc.).
464 \f
465 .IOS +<n>       +- +-   input/output status
466
467         The variable .IOS+<n> is the input/output status
468         word for channel <n>, for <n> between 0 and 17 octal.
469         Normally zero for a closed channel.
470         This word contains various bits describing the status
471         of the channel.  The left half is a set of error
472         codes if non-zero; the .IOS word can be given to
473         the ERR device to obtain an ascii message for
474         the error.  The right half contains various bits
475         describing the state of the device.  (Internally to
476         ITS, the right half contains an access pointer;
477         the right half bits supplied for .IOS are the
478         same as those generated by the .STATUS uuo or
479         the STATUS symbolic system call.)
480
481         The various bits in the .IOS word are as follows:
482         4.9-4.6 Always zero (see the .IOP variable).
483         4.5-4.1 If non-zero, the number of a non-display
484                 input/output error (see table below).
485         3.9-3.7 If non-zero, the number of an IDS interpreted
486                 display input/output error (see table below).
487         3.6-3.1 If non-zero, the number of a standard error.
488                 Set primarily by failing .OPEN's and
489                 .FDELE's.  These are the same as the error
490                 codes returned by failing .CALL's (see
491                 table below).
492         2.9-2.3 Device dependent.
493         2.2     Buffering capacity empty.
494         2.1     Buffering capacity full.
495         1.9-1.7 Mode in which device was opened.
496                 1.9     0 = ascii, 1 = image.
497                 1.8     0 = unit, 1 = block.
498                 1.7     0 = input, 1 = output.
499         1.6-1.1 ITS internal physical device code
500                 (see table below).
501
502         The error messages indicated by bits 4.5-4.1 are:
503           1     DEVICE HUNG OR REPORTING NON-DATA ERROR
504           2     END OF FILE
505           3     NON-RECOVERABLE DATA ERROR
506           4     NON-EXISTENT SUB-DEVICE
507           5     OVER IOPOP
508           6     OVER IOPUSH
509           7     USR OP CHNL DOES NOT HAVE USR OPEN
510          10     CHNL NOT OPEN
511          11     DEVICE FULL (or directory full)
512          12     CHNL IN ILLEGAL MODE ON IOT
513          13     ILLEGAL CHR AFTER CNTRL P ON TTY DISPLAY
514          14     DIRECTORY FULL
515          15     DIRECTORY'S ALLOCATION EXHAUSTED
516
517         The error messages indicated by bits 3.9-3.7 are:
518           1     IDS ILLEGAL SCOPE MODE
519           2     IDS SCOPE HUNG
520           3     MORE THAN 1K SCOPE BUFFER
521           4     IDS MEM PROTECT
522           5     IDS ILLEGAL SCOPE OP
523           6     IDS MEM PROTECT ON PDL PNTR
524           7     IDS ILLEGAL PARAMETER SET
525
526         The error messages indicated by bits 3.6-3.1 are:
527           1     NO SUCH DEVICE
528           2     WRONG DIRECTION
529           3     TOO MANY TRANSLATIONS
530           4     FILE NOT FOUND
531           5     DIRECTORY FULL
532           6     DEVICE FULL
533           7     DEVICE NOT READY
534          10     DEVICE NOT AVAILABLE
535          11     ILLEGAL FILE NAME
536          12     MODE NOT AVAILABLE
537          13     FILE ALREADY EXISTS
538          14     BAD CHANNEL NUMBER
539          15     TOO MANY ARGUMENTS (CALL)
540          16     PACK NOT MOUNTED
541          17     DIRECTORY NOT AVAIL
542          20     NON-EXISTENT DIRECTORY NAME
543          21     LOCAL DEVICE ONLY
544          22     SELF-CONTRADICTORY OPEN
545          23     FILE LOCKED
546          24     M.F.D. FULL
547          25     DEVICE NOT ASSIGNABLE TO THIS PROCESSOR
548          26     DEVICE WRITE-LOCKED
549          27     LINK DEPTH EXCEEDED
550          30     TOO FEW ARGUMENTS (CALL)
551          31     CAN'T MODIFY JOB
552          32     CAN'T GET THAT ACCESS TO PAGE
553          33     MEANINGLESS ARGS
554          34     WRONG TYPE DEVICE
555          35     NO SUCH JOB
556          36     VALID CLEAR OR STORED SET
557          37     NO CORE AVAILABLE
558          40     NOT TOP LEVEL
559          41     OTHER END OF PIPELINE GONE OR NOT OPEN
560          42     JOB GONE OR GOING AWAY
561          43     ILLEGAL SYSTEM CALL NAME
562          44     CHANNEL NOT OPEN
563          45     INPUT BUFFER EMPTY OR OUTPUT BUFFER FULL
564          46     UNRECOGNIZABLE FILE (LOAD)
565          47     LINK TO NON-EXISTENT FILE
566
567         The physical device codes from bits 1.6-1.1 are as
568         follows.  Note that, as a half-hearted rule, bit 1.6
569         indicates that file names are significant, and bit 1.5
570         indicates a software-implemented device.
571         This list is subject to additions and deletions!
572         CODE    SYMBOL  DEVICE  DESCRIPTION
573          0              TTY     Console input.
574          1      SNTTY   TTY     Printing console output.
575          2      SNTDS   TTY     Display console output.
576          3      SNLPD   LPT     Data Products line printer.
577          4      SNVID   VID     Vidisector ???
578          5      SNBAT           Vidisector ???
579          6      SNPLT   PLT     Calcomp plotter.
580          7      SNPTP   PTP     Paper tape punch.
581         10      SNIMPX  IMX     Input multiplexor.
582         11      SNOMPX  OMX     Output multiplexor.
583         12      SNPTR   PTR     Paper tape reader.
584         13      SN340   DIS     DEC 340 display, Ascii output.
585         14      SN340I  IDS     Interpreted 340 display.        ???
586         15      SNMTC   MTn     Magnetic tape.
587         16      SNCOD   COD     Morse code device.
588         17      SNTAB   TAB     Tablet. ???
589         21      SNNUL   NUL     Source of zeroes, or output sink.
590         22      SNJOB   JOB     Job device.
591         23      SNBOJ   BOJ     Inverse of JOB.
592         24      SNSPY   SPY     Spy on another console.
593         25      SNSTY   STY     Pseudo-teletype.
594         26      SNNET   NET     ARPAnet (NCP).
595         27      SNLPV   LPT     Vogue line printer (yech!)
596         30      SNSTK   STK     Stanford keyboard.
597         31      SNMSP   MSP     (DM) Interprocess message protocol.
598         32      SNCHA   CHAOS   CHAOS net.
599         33      SNTCP   TCP     TCP Internet.
600         34      SNTRAP  TRAP    Trap "device"
601         35      SNIPQ   IPQ     Internet IP Queue.
602         36      SNUBI   UBI     KS10 Unibus interrupt.
603         41      SNUTC   UTn     Microtape (DECtape).
604         43      SN2311  DSK     2311 disk drives or equivalent.
605         60      SNFUSR  USR     A foreign (not immediately inferior) procedure.
606         61      SNUSR   USR     An immediately inferior procedure.
607         62      SNCLK   CLx     Various core link devices (x \ 6 {AIOU})
608         63      SNDIR   ---     File directory or ERR device.
609         64      SNPDP   USR     The PDP-6.
610         65      SNDIRH  DIRHNG  Directory hang "device"
611         66      SNLCK   LOCK    Lock "device"
612 \f
613 .IPIRQC         +* +*   IORM into .PIRQC
614
615         Like .PIRQC (q.v.) when reading.
616         Performs IORM into .PIRQC when writing.
617
618 \1f
619 .JNAME          +* +?   job name
620
621         The name of the job as a word of sixbit characters.
622         The uname-jname pair must be unique to a job
623         (there are some exceptions involving system-created
624         jobs or jobs not logged in).
625         The uname and jname are used as file names when
626         creating or subsequently opening the job on the USR
627         device.  See also the .UNAME user variable.
628         The .JNAME variable may be set by a .SUSET only in a
629         top-level job, and then only if the job has no
630         inferiors.
631         Attempting to set a jname to zero causes an
632         illegal operation interrupt (bit 1.6 of the .PIRQC
633         user variable).  So does attempting to set it such that
634         the uname-jname pair would no longer be unique.
635         So does attempting to illegally set one's own jname.
636
637 \1f
638 .JPC            +* +*   jump program counter
639
640         The PC as of the most recent jump instruction,
641         i.e. an instruction which changed the PC by other
642         than 1 or 2.  This is actually a register in the
643         paging box when running.
644
645 \1f
646 .MARA           +* +*   MAR (memory address register) address
647
648         Initially 0.
649         The address for the MAR register in the paging box,
650         which gives a %PIMAR interrupt when the specified operation
651         is performed on the specified address.
652                 3.3     0 = exec mode, 1 = user mode.
653                         This is forced to 1 when set with
654                         .SUSET or .USET; exec mode is for very
655                         obscure system hacks only.
656                 3.2-3.1 0  Never interrupt.
657                         1  Interrupt on instruction fetch.
658                         2  Interrupt on write.
659                         3  Interrupt on any reference.
660                 2.9-2.1 Address for MAR.
661         The MAR does not work well on accumulators.
662         See also the .PIRQC user variable, bit %PIMAR;
663         and ITS INTRUP and ITS USR.
664 \f
665 .MARPC          +* +*   MAR program counter
666
667         The PC as of the instruction that most recently
668         tripped the MAR interrupt, if any.  In addition,
669         the indirect bit will be set if that instruction
670         completed successfully (was not aborted by the MAR
671         hit).  See the .MARA user variable.
672
673 \1f
674 .MASK           +* +*   word 1 interrupt mask
675
676         Initially 0.
677         This is a mask for word 1 interrupts which indicates
678         which interrupts the job is prepared to handle.
679         If a class 2 or class 3 word 1 interrupt tries to
680         occur, but the corresponding bit in .MASK is not
681         set, then the interrupt is converted to class 1 or
682         ignored, respectively.  The bits in .MASK directly
683         correspond to those in .PIRQC (q.v.).  Bits for class
684         1 interrupts are AND'ed out before setting the .MASK
685         variable.
686
687 \1f       
688 .MBO1           +- +-   KL-10 Mbox counter
689
690         This is the low-order word of the KL-10 Mbox counter
691         value for the job.  On KA-10's, it holds garbage.
692         Its location is .MBOX+1, for convenience.
693
694 \1f       
695 .MBOX           +- +-   KL-10 Mbox counter
696
697         This is the high-order word of the KL-10 Mbox counter
698         value for the job.  On KA-10's, it holds garbage.
699
700 \1f
701 .MEMT           +* +*   memory top
702
703         This variable contains 1 plus the highest legal
704         address in the job (the accessible word with the
705         largest address).  Setting this variables is like
706         performing an equivalent .CORE uuo (q.v.):
707                 .SUSET [.SMEMT,,[FOO]]
708         is like doing:
709                 .CORE <FOO+1777>_12
710
711 \1f
712 .MPVA           +- +-   memory protect violation address
713
714         The address which the last instruction to cause a memory protection
715         violation (or a write into read only memory violation) attempted to
716         reference, on KA-10's rounded down to a page boundary.  Thus an
717         attempt to reference the non-existent location 317435 would cause
718         .MPVA to be set to 316000 octal on a KA-10, or 317435 on a KL-10.
719
720         On the KS-10, .MPVA also holds the non-existant IO register address
721         after a %PINXI.
722
723         See also the .PIRQC variable.
724 \f
725 .MSK2           +* +*   word 2 interrupt mask
726
727         Initially 0.
728         This is a mask for word 2 interrupts which indicates
729         which interrupts the job is prepared to handle.
730         If a class 2 or class 3 word 2 interrupt tries to
731         occur, but the corresponding bit in .MSK2 is not
732         set, then the interrupt is converted to class 1 or
733         ignored, respectively.  The bits in .MSK2 directly
734         correspond to those in .IFPIR (q.v.).
735
736 \1f
737 .OPC            +- +-   old program counter
738
739         The PC just before the last instruction was executed.
740         This corresponds to a register in the paging box.
741         It doesn't exist on KL-10's.
742 \f
743 .OPTION         +* +*   option bits
744
745         Initially 0.
746         The bits in this word correspond to various options
747         as follows:
748         4.9     %OPTRP  Same as the .UTRP user variable.  See ITS UUO.
749         4.8     %OPDET  ** This bit is OBSOLETE and NO LONGER EXISTS **
750                         It is documented for historical purposes only.
751                         Nowadays, fatal interrupts always cause top-level
752                         jobs to be detached.  Once upon a time, top-level
753                         jobs with consoles would be reloaded instead of
754                         detached, unless they had set %OPDET=1.
755                         See the DETACH and RELOAD symbolic system calls.
756         4.7     %OPDEC  Uuo's 40, 41, and 47 (that is,
757                         .IOT, .OPEN, and .ACCESS)
758                         should trap to the user as uuos
759                         via the .40ADDR user variable (q.v.).
760                         This is useful for programs which wish to
761                         interpret DEC TOPS-10 UUO's, since those are the
762                         only ones which conflict with ITS UUOs.
763                         Luckily, those ITS UUOs are not essential since
764                         there are symbolic system calls to do the same things.
765         4.6     %OPCMD  Superior claims it has JCL which
766                         it will cheerfully supply in response to
767                         the appropriate .BREAK 12, command.
768         4.5     %OPBRK  Superior claims to handle all .BREAK's.
769         4.4     %OPDDT  Superior claims to be DDT.
770         4.3     %OPINT  Job desires new-style (vectored
771                         and stacked) interrupts.  See also the
772                         .40ADDR variable.  See ITS INTRUP for
773                         information on old- and new-style
774                         interrupts.
775         4.2     %OPOJB  Other jobs may open this job
776                         as the OJB device, thereby turning it
777                         into a JOB device.  See ITS JOB.
778         4.1     %OPLOK  Job desires the switch locking
779                         and unlocking synchronization feature.
780                         See also the .40ADDR variable.
781                         See ITS LOCKS for information on locks.
782         3.9     %OPLIV  The job tree of which this is the
783                         top-level job is permitted to survive a
784                         system shutdown -- it should take care
785                         of logging itself out.  See the .SHUTDN uuo.
786                         Meaningful only for top-level jobs.
787                         Primarily useful for system demons which need to
788                         survive system death (e.g. the statistics
789                         demon PFTHMG DRAGON).
790         3.8     %OPOPC  Job desires that instruction-aborting interrupts
791                         such as MPV leave the PC pointing before the
792                         instruction that lost, instead of the old
793                         convention of leaving it pointing after.
794                         The new convention is far better and all new
795                         programs should use it.
796         3.7     %OPLSP  Superior claims to be MacLisp.
797         3.6     %OPLKF  Unlock locks on fatal interrupt.  When a
798                         non-disowned top-level job receives a fatal
799                         interrupt, if it has set this bit, its locks will
800                         be unlocked by the system job as part of the
801                         process of detaching it.  See the %OPLOK bit and
802                         ITS LOCKS.
803 \f
804 .PAGAHEAD       +* +*   page-ahead control
805
806         Normally zero, this word is set nonzero to enable
807         sequential paging through a part of the address space
808         specified by .PAGRANGE.  The right half of .PAGAHEAD is
809         the page-ahead interval width and the left half is the page-behind
810         distance.  Each time a page in the designated range is
811         touched for the first time, the next few pages, forming the
812         page-ahead interval begin to swap in, and a page a certain
813         distance behind (specified by the page-behind distance) is
814         swapped out or marked for swap out in the near future.  The
815         precise treatment depends on how loaded the system is.
816
817         Exactly one of the page-ahead interval width and the
818         page-behind distance should be negative.  The page-behind
819         distance should be negative, if memory is being used from low
820         addresses to high ones.  The page-ahead width should be
821         negative if moving from high addresses to low ones.
822
823         Example: -2,,4 means on first reference to page n, start
824         reading in pages n+1 through n+4 and possibly swap out page n-2.
825         Page n-1 is not affected until page n+1 is touched.  A
826         page-behind distance of 2 means that two consecutive pages are
827         always available.
828 \f
829 .PAGRANGE       +* +*   page-ahead range
830
831         Normally zero, this word is made nonzero together with .PAGAHEAD
832         to enable the sequential paging feature.  The two halves of
833         .PAGRANGE are page numbers which specify the region of the 
834         address space in which sequential paging should go on.
835         The left half specifies the first page in the sequentially
836         paged region, and the right half specifies the first page
837         after the end of that region.
838 \f
839 .PICLR          +* +*   priority interrupt clear
840
841         Initially -1.
842         If non-zero, the job may take interrupts.  If zero,
843         interupts are deferred.  This variable is cleared
844         when an old-style interrupt occurs (but not by new-style
845         interupts!), and is set to -1 by the .DISMISS uuo
846         and the DISMIS symbolic system call.  Attempts
847         to set this variable will convert the value to -1 or 0
848         depending on bit 4.9.
849
850 \1f       
851 .PIRQC          +* +*   priority interrupt request cruft (?)
852
853         This word contains bits for pending word 1 interrupts.
854         Setting bits in this causes the corresponding interrupts
855         to attempt to take place, subject to .MASK, .DF1,
856         .PICLR (q.v.), and the %OPINT bit of the .OPTION user
857         variable (see ITS INTRUP).
858
859         Interrupts are of three classes:
860         1       Very serious.  The job is stopped and its
861                 superior interrupted.
862         2       Semi-serious.  The job may request to handle
863                 such an interrupt by setting the corresponding
864                 bit in .MASK (q.v.); otherwise it is treated
865                 as a class 1 interrupt.
866         3       Trivial.  The job receives the interrupt if it
867                 has requested to handle it; otherwise the
868                 interrupt condition is ignored.  (Under the
869                 new-style interrupt scheme, a class 3 interrupt
870                 may become a class 1 interrupt.)
871         See also the .IFPIR variable for word 2 interrupts.
872
873         The interrupt bits and their classes are as follows.
874         The character * denotes a class 1 interrupt, and + a
875         class 2 interrupt.
876                 4.9     Must be zero.
877         %PIRLT  4.8     Clock break (see the .REALT uuo).
878         %PIRUN  4.7     Run time interrupt (see the .RTMR user variable).
879         %PINXI  4.6  +  Non-Existent IO register
880                         A Job in User IOT mode referenced a non-existent IO
881                         register on the KS10 Unibus.  The PC is left
882                         pointing before the guilty instruction.  The address
883                         of the non-existant register may be found in .MPVA.
884         %PIJST  4.5     Job Status display request.
885                         The sequence ^_J was typed on the console owned
886                         by this process or some inferior.
887         %PIDCL  4.4  *  A defered call was typed while the job had the TTY.
888         %PIATY  4.3     The tty was given back to the job by
889                         its superior.  Indicates that the screen has
890                         probably been written on and its contents
891                         have changed unpredictably.
892         %PITTY  4.2  +  Attempt to use tty when not possessing it.
893         %PIPAR  4.1  +  Parity error.
894         %PIFOV  3.9     Arithmetic floating overflow.
895         %PIWRO  3.8  +  Attempt to write into read only memory.
896                         See the .MPVA user variable.
897         %PIFET  3.7  +  Pure page trap (attempt to fetch an instruction from
898                         writable memory when bit 4.2 of the PC set).
899                         This feature doesn't exist on KL-10's, instead
900                         this interrupt is signalled for "Illegal entry
901                         to concealed mode" which you probably can't make
902                         happen.  (See the KI10 Processor Reference Manual.)
903                         See bit 4.2 of the .UPC user variable.
904         %PITRP  3.6  *  System uuo to user trap (see the .UTRP user variable).
905                 3.5     Arm tip break 3 (OBSOLETE).
906                 3.4     Arm tip break 2 (OBSOLETE).
907                 3.3     Arm tip break 1 (OBSOLETE).
908         %PIDBG  3.2     System being debugged.
909                         Occurs when someone uses the .SETLOC or .IFSET uuo
910                         to alter SYSDBG and the new contents are non-zero
911                         and the old contents non-negative.
912                         (See also the SSTATU symbolic system call.)
913         %PILOS  3.1  +  A .LOSE UUO or LOSE system call was executed
914                         (their purpose is to signal the superior).
915         %PICLI  2.9     CLI device interrupt.
916         %PIPDL  2.8     Pdl overflow.
917         %PILTP  2.7     Light pen interrupt on 340.
918                         Program stop or hit stop on E&S display.
919         %PIMAR  2.6  +  MAR interrupt.
920                         (See the .MARA and .MARPC user variables.)
921         %PIMPV  2.5  +  Memory protection violation (attempt to reference
922                         a page not in the job's page map).
923                         (See the .MPVA user variable.)
924         %PICLK  2.4     Slow clock interrupt (every .5 second).
925         %PI1PR  2.3  *  Single intruction proceed interrupt.
926                         Used by DDT for ^N commands.
927         %PIBRK  2.2  *  Breakpoint interrupt (.BREAK uuo executed).
928         %PIOOB  2.1  +  Illegal user address. (OBSOLETE)
929         %PIIOC  1.9  +  Input/output channel error.
930                         (See the .BCHN and .IOS user variables.)
931         %PIVAL  1.8  *  Value interrupt (.VALUE uuo executed).
932         %PIDWN  1.7     System going down or being revived.
933                         (See the .SHUTDN, .REVIVE, and .DIETIME uuo's,
934                         and the SSTATU symbolic call.)
935         %PIILO  1.6  +  Illegal instruction operation.
936         %PIDIS  1.5  +  Display memory protection violation (340 or E&S).
937         %PIARO  1.4     Arithmetic overflow.
938         %PIB42  1.3  *  Bad location 42.
939                         (See the .40ADDR user variable, and ITS INTRUP.)
940         %PIC.Z  1.2  *  ^Z typed when this job had the TTY.
941         %PITYI  1.1     Character enabled for interrupt was typed on TTY.
942                         (Semi-obsolete; see the .IFPIR user variable,
943                         and ITS TTY.) 
944 \f
945 .PMAP +<n>      +- +-   page map word
946
947         This is the page map word for page <n> of the job,
948         for <n> between 0 and 377 octal (256.K = 400 1K pages).
949         The map word read has this form:
950         4.9     %CBWRT  Page is writable.
951         4.8     %CBRED  Page exists (if this bit is zero, then the
952                         whole word is zero).
953         4.7     ???     Page is in core (as opposed to swapped out).
954         4.6     %CBPUB  Page is public (any job can write into it
955                         which wants to).
956         4.2     %CBLOK  Page is locked in core
957                         (inhibited from swapout)
958         3.9     %CBSLO  Page is in slow memory
959                         (Doesn't work; Moon says it never will)
960         3.8-3.1 Number of times the page is shared.
961                 (See the CORTYP symbolic system call,
962                 right half of value 4.)
963         2.9-2.1 Absolute page number, or page number in next
964                 sharer in the circular list of sharers.
965                 (See CORTYP, value 3.)
966         1.9-1.1 0       Page is absolute.
967                 777     Page is not shared.
968                 <m>     Next sharer in circular list of sharers
969                         is the job with user index <m>.
970
971 \1f
972 .RTMR           +* +*   runtime timer
973
974         Initially -1.
975         If non-negative, the amount of run time remaining until the job
976         will receive a word 1 runtime interrupt.  (See bit %PIRUN of the
977         .PIRQC variable.)  The time is measured in slightly different units
978         on different CPUs.  On the KA in 4.069 microsecond units, on the KL
979         in 4 microsecond units, and on the KS in 3.9 microsecond units.
980
981 \1f
982 .RUNT           +- +-   run time
983
984         Initially 0.
985         This is the run time used so far by the job,
986         measured in units of 4 microseconds.
987 \1f
988 .SERVER         +* +*   server job
989
990         Initially -1.
991         This is the user index of a job that has been given special
992         permission to modify this job, or -1 if there is no such job.
993
994         This can be used to implement various oddball client/server
995         protocols between jobs.  The client job will request some service
996         from the server job and will set his .SERVER variable to the server's
997         user index to allow the service to be performed.
998
999         If the server job is killed, all of the client jobs will have their
1000         .SERVER variables set back to -1.
1001
1002         Although it is safe to set .SERVER to -1 using .SUSET or .USET,
1003         there can be timing errors if a client loads his .SERVER variable
1004         by simply writing the server's user index into it.  Specifically,
1005         during the time the server's user index is sitting in the client's
1006         memory, the server job might be killed and another job started with
1007         the same user index.  This can be guarded against by handling
1008         interrupts on the USR: channel, but this is clumsy.  A better
1009         method is to use the SSERVE system call.  (See .INFO.;ITS .CALLS)
1010 \1f
1011 .SNAME          +* +*   system name
1012
1013         This is a word of six sixbit characters which is
1014         the default "directory name" for various input/output
1015         operations.  It is initially the same as the job's
1016         .UNAME (q.v.).  It can be overridden by supplying the
1017         directory name explicitly to a symbolic system call.
1018         The other uuo's such as .OPEN and .FDELE always use .SNAME.
1019 \f
1020 .SUPPRO         +- +-   superior
1021
1022         This is -1 if the job is top-level, or the user index
1023         of the job's superior.  See .UIND.
1024
1025 \1f
1026 .SV40           +- +-   saved 40
1027
1028         The contents of absolute location 40 (i.e., the last
1029         uuo that trapped to the system for this job).
1030         See also the .UUOH user variable.
1031         Note that only uuo's 40-47 are really used for
1032         communication with the system.  All other uuo's are
1033         handed back to the executing job via its .40ADDR
1034         user variable (q.v.).
1035
1036 \1f
1037 .TR1INS         +? +?   Trap 1 instruction.
1038
1039         This is the instruction to be executed when arithmetic
1040         overflow occurs.  Op-code 0 is special, and uses
1041         its E.A. as interrupt bits to turn on in the RH of .PIRQC.
1042         The default contents of .TR1INS are simply %PIARO to
1043         set the overflow interrupt.  On the KA-10, writing the
1044         variable doesn't change it.
1045
1046 \1f
1047 .TR2INS         +? +?   Trap 2 instruction.
1048
1049         This is the instruction to be executed when pdl
1050         overflow occurs.  Op-code 0 is special, and uses
1051         its E.A. as interrupt bits to turn on in the RH of .PIRQC.
1052         The default contents of .TR2INS are simply %PIPDL to
1053         set the pdl overflow interrupt.  On the KA-10, writing the
1054         variable doesn't change it.
1055
1056 \1f
1057 .TTST           +- +-   saved TTYSTS
1058
1059         In a job which does not have the TTY, this variable
1060         holds the saved contents of TTYSTS (what would be in
1061         TTYSTS if the job were given a TTY).   This is primarily
1062         useful for examining from DDT.
1063         See ITS TTY for a description of the contents of TTYSTS.
1064         See also the TTYGET and TTYSET symbolic system calls.
1065
1066 \1f
1067 .TTS1           +- +-   saved TTYST1
1068
1069         Like .TTST, but for the TTYST1 variable instead of the
1070         TTYSTS variable.
1071
1072 \1f
1073 .TTS2           +- +-   saved TTYST2
1074
1075         Like .TTST, but for the TTYST2 variable rather than the
1076         TTYSTS variable.
1077 \f
1078 .TTY            +* +*   random TTY variable
1079
1080         This variable indicates the status of the job with
1081         respect to the console controlling its job tree.
1082         The %TBNVR, %TBINT, %TBWAT, %TBOUT, %TBINF, %TBOIG, and %TBIIN bits
1083         are settable. %TBWAT may be set only by the superior.
1084         4.9     %TBNOT  Does not have TTY now.
1085         4.8     %TBNVR  If 1, an OPEN on the tty will fail
1086                         rather than hanging, unless %TBWAT is on.
1087         4.7     %TBINT  An attempt to use the console without owning
1088                         it will cause a %PITTY interrupt (LH of
1089                         the .PIRQC user variable), unless
1090                         %TBWAT is set to 1.
1091                         In particular an OPEN on the tty
1092                         will interrupt instead of failing or
1093                         hanging.
1094         4.6     %TBWAT  If 1, overrides the setting of %TBINT
1095                         and %TBNVR, and makes the system act
1096                         as if they were 0.  Settable only with
1097                         .USET.  DDT sets this bit when $P'ing a
1098                         job, so that even if the job loses the tty
1099                         momentarily it will not get upset.
1100         4.4     %TBDTY  If the TTY was taken from the job,
1101                         then when it gets it back, this bit says
1102                         that the TTY should stay with the job
1103                         and not be passed down to an inferior.
1104         4.3     %TBOUT  Allow this job to type out, even if it
1105                         doesn't have the TTY.  Some operations,
1106                         and all input will still require the job
1107                         to have the TTY.  Not effective unless
1108                         the superior enables it by setting %TBINF
1109                         in the superior's .TTY var.
1110         4.2     %TBINF  Enable this job's inferiors to take
1111                         advantage of their %TBOUT's.
1112         4.1     %TBOIG  Ignore output.  Overrides %TBWAT, %TBINT.
1113         3.9     %TBIIN  Interrupt on attempt to do input.  Overrides
1114                         %TBWAT.
1115         3.6-3.1 $TBECL  Number if echo lines, if the job
1116                         doesn't currently have the TTY.
1117         2.9-1.1 If the job has the TTY, this is the TTY number.
1118                 If it doesn't, and doesn't want it, this is the
1119                 (internal) user number of the immediately
1120                 inferior job to give the TTY to.
1121 \f
1122 .TVCREG         +* +*   TV console register
1123
1124         Initially -1.
1125         This variable is placed in the console register
1126         when the job is run if it is non-negative.
1127         It controls which video buffer memory is used
1128         when writing into the job's tty's TV buffer     
1129         (see the CORBLK symbolic system call).
1130         The format of the console register is as follows:
1131         4.9-4.2 ALU function, used when writing into TV memory:
1132                 VALUE   SYMBOL  FUNCTION
1133                 0       CSETC   SETCAM
1134                 1       CNOR    ANDCBM
1135                 2       CANDC   ANDCAM
1136                 3       CSETZ   SETZM
1137                 4       CNAND   ORCBM
1138                 5       CCOMP   SETCMM
1139                 6       CXOR    XORM
1140                 7       CANCSD  ANDCMM
1141                 10      CORCSD  ORCAM
1142                 11      CEQV    EQVM
1143                 12      CSAME   SETMM/MOVES/JFCL
1144                 13      CAND    ANDM
1145                 14      CSETO   SETOM
1146                 15      CORSCD  ORCMM
1147                 16      CIOR    IORM
1148                 17      CSET    SETAM/MOVEM
1149         Note that those symbols are not predefined in MIDAS.
1150         4.1-3.3 Video buffer number (video switch input number).
1151                 See the VIDSW symbolic system call.
1152
1153 \1f
1154 .UIND           +- +-   user index      
1155
1156         The unique number assigned to the job by the system     
1157         when the job was created.  These numbers typically
1158         are between 0 and 77 octal or so (the exact maximum value
1159         is a function of the particular incarnation of the
1160         system).  When a job is killed, its user index is
1161         freed for re-use.
1162         Most symbolic system calls  which require a job
1163         to be specified will accept 400000+the user index
1164         in lieu of a channel with the job open on it if the
1165         call is only to examine the job and not to modify it.
1166         The .GUN and DETACH commands require a user index.
1167         Jobs 0 and 1 are special in that they always stand for
1168         the system itself and for the CORE job, respectively.
1169         (The CORE job manages core allocation for the system.)
1170         This may have various implications depending on context;
1171         for example, when sharing a page with a job via the
1172         CORBLK symbolic system call, sharing with
1173         job 0 means sharing with an absolute page, and "sharing"
1174         with job 1 means getting a fresh page.
1175 \f
1176 .UNAME          +- +?   user name
1177
1178         A word of sixbit characters which is the user
1179         name of the job.  All jobs in a given job
1180         tree must all have the same user name.  Furthermore,
1181         a console-controlled tree may not log in if another
1182         console-controlled tree is logged in under the same
1183         uname.  When a new console-controlled tree is created
1184         by typing ^Z on a free console, the uname of the newly
1185         created top-level job of the tree is set to "___nnn",
1186         where "nnn" is the user index of the newly-created
1187         job.  A non-disowned non-console controlled job is also given
1188         such a uname initially.  This may subsequently be changed to
1189         something more reasonable by using the LOGIN symbolic
1190         system call.
1191         The uname of a newly created inferior job is initialized
1192         to the uname of its creator.
1193         If a disowned job tree is re-owned, the unames of all the
1194         jobs in the re-owned job tree are set to the uname of the
1195         re-owning job tree.
1196         The .UNAME user variable may be set only with a .SUSET, and
1197         only by a top level job which has no direct inferiors;
1198         furthermore, attempting to set the uname to zero or the left
1199         half to -1 causes an illegal operation interrupt (bit 1.6 of
1200         the .PIRQC user variable), as does attempting to make the
1201         uname-jname pair of the job non-unique.
1202         See also the .JNAME user variable.
1203 \f
1204 .UPC            +* +-   user program counter
1205
1206         The PC for the job.  This word, of course,
1207         contains the PC flags in the left half;
1208         a job may set these flags for itself only by
1209         using JRST 2,@[<word with flags and pc>].
1210         On KA's, the flags in the left half are as follows:
1211         (- = .USET may not set; % = peculiar to ITS)
1212         %PCARO==400000  Overflow.
1213         %PCCR0==200000  Carry 0.
1214         %PCCR1==100000  Carry 1.
1215         %PCFOV==40000   Floating overflow.
1216         %PCFPD==20000   First part of instruction already done.
1217         %PCUSR==10000 - User mode.
1218         %PCUIO==4000  - User I/O.
1219         %PCPUR==2000  % Pure.  Instructions may only be fetched from
1220                         read-only memory.  See bit 3.7 of the .PIRQC user
1221                         variable.  This feature is not available on
1222                         all machines -- beware!
1223         %PCSPC==1000  - Unused.  (A PDP6 feature)
1224         %PC1PR==400   % One proceed.  An interrupt will occur at the end
1225                         of the next instruction.  See bit 2.3 of the .PIRQC
1226                         user variable.  Used by DDT for ^N commands.
1227         %PCX17==200   % AI KA-10 computer only.  Index-off-the-PC hack.
1228                         When this bit is set, an index field of 17 means
1229                         index off the PC instead of ac 17.
1230         %PCFXU==100     Floating underflow.
1231         %PCDIV==40      No divide.
1232                 3.5-3.1 Always zero.  May not be set non-zero.
1233
1234         On KL's the flags are as follows (note the "|" at the front
1235         of lines that differ significantly from those for KA's):
1236
1237 |       %PSPCP==400000  "Previous Context Public" - this applies only
1238                         in exec mode; in user mode this bit is the same
1239                         as in KA (%PCARO, Arithmetic overflow).
1240         %PSCR0==200000  Carry 0.
1241         %PSCR1==100000  Carry 1.
1242         %PSFOV==40000   Floating overflow.
1243         %PSFPD==20000   First part of instruction already done.
1244         %PSUSR==10000 - User mode.
1245         %PSUIO==4000  - User I/O.
1246 |       %PSPUB==2000    "Public Mode" - not used in ITS
1247 |       %PSINH==1000    Inhibits MAR-breaks and trap3 (one-proceed trap)
1248 |                       for one instruction.
1249 |       %PSTR2==400     Set by pdl overflow;  causes the "trap 2 instruction"
1250 |                       to be executed.  That instruction is kept in .TR2INS
1251 |       %PSTR1==200     Set by arithmetic overflow;  causes the
1252 |                       "trap 1 instruction" in .TR1INS to be executed.
1253 |                       Both %PSTR1 and %PSTR2 set generates a one-proceed
1254 |                       trap. 
1255 |       %PS1PR==160   % %PSINH+%PSTR2+%PSTR1.  Setting those bits
1256 |                       causes a single instruction proceed.
1257         %PSFXU==100     Floating underflow.
1258         %PSDIV==40      No divide.
1259                 3.5-3.1 Always zero.  May not be set non-zero.
1260
1261         The user mode (4.4) is always set to 1.
1262         The user I/O bit (4000, bit 4.3) is set according
1263         to whether the job is in .IOTLSR mode.
1264
1265         If the .UPC user variable for one job is read by another while
1266         the first is running, an exec mode PC may be seen (bit 4.4 = 0);
1267         this reflects the fact that the job is in the middle
1268         of a system call or something.  The .UUOH user variable
1269         should then be examined (this is precisely what DDT does
1270         for the evaluation of \e.).
1271 \f
1272 .USTP           +* --   user stop bits
1273
1274         Initially <100000,,>.
1275         If this variable is non-zero, the job is being blocked
1276         from running for one reason or another.  If zero, the
1277         .FLS variable controls whether the job may run.
1278         The form of the .USTP variable is as follows:
1279         4.9     BCSTOP  Job is being moved in core.
1280         4.8     BUCSTP  Core job is stopping this job
1281                         in order to get more core for another job.
1282         4.7     BUSRC   User control bit.  Only this
1283                         bit may be modified, and only by the
1284                         procedure's superior.  Any attempt to
1285                         set the .USTP variable non-zero
1286                         will set this bit; any attempt to set it
1287                         to zero will clear this bit.
1288         4.6     BSSTP   Set while superior is altering the page
1289                         map for the job.  (Not directly settable
1290                         by superior.)
1291         2.9-1.1 Count of transient reasons for stopping the job.
1292                 If non-zero, inhibits relocation of the job by
1293                 the core job.
1294         PEEK displays this variable by printing the high six bits
1295         in octal, then a "!", then the rest in octal.  This is
1296         why one normally sees "10!0" for a stopped job.
1297
1298 \1f
1299 .UTRP           +* --   user trap switch
1300
1301         When non-zero, this switch specifies that all uuo's
1302         which trap to the system should, instead of performing
1303         their usual actions, should cause a word 1 class 1
1304         interrupt to the job executing the uuo.  This allows
1305         simulators, etc., to trap all uuo's executed by a job.
1306         An attempt to set this variable will use only bit 1.1.
1307
1308         This is the same as the %OPTRP bit of the .OPTION user variable.
1309
1310 \1f
1311 .UUOH           +- +-   system uuo PC
1312
1313         The program counter as of the last uuo which trapped
1314         to absolute location 40 (not location 40 in the job,
1315         nor the location specified by .40ADDR!)
1316         See also the variable .SV40.
1317
1318 \1f
1319 .VAL            +* +*   value or error code of job
1320
1321         .VALUE instructions set this word to the contents
1322         of the memory location they address.  That is useless.
1323         More importantly, .LOSE instructions, and the LOSE
1324         system call, set .VAL to <error code>,,<addr of losing
1325         instruction>, so that the superior can decode the
1326         error.
1327 \f
1328 .WHO1           +* +*   user who-line control word
1329
1330         This variable controls the printing of .WHO2 and .WHO3
1331         at the end of the TV who-line (see ITS TV).
1332         4.9     If 1, suppress the who-line entirely when focused
1333                 on this job.
1334         4.8     Suppress space between halves of .WHO2.
1335         4.7-4.5 Mode for printing left half of .WHO2:
1336                 0       Do not print.
1337                 1       Date in packed form:
1338                         4.9-4.3 Year (mod 100.).
1339                         4.2-3.8 Month.
1340                         3.7-3.3 Day.
1341                         3.2-3.1 Unused.
1342                         See the RQDATE symbolic system call, but
1343                         note that here the date is shifted.
1344                 2       Time in fortieths of a second, printed in tenths
1345                         in the form HH:MM:SS.T.
1346                 3       Time in half-seconds, printed in the form HH:MM:SS.
1347                 4       Octal halfword.
1348                 5       Decimal halfword (no . is supplied).
1349                 6       Three sixbit characters.
1350                 7       Unused.
1351         4.4-4.2 Mode for printing right half of .WHO2.
1352         4.1     Print 3.9-3.3 twice (doubled character).
1353         3.9-3.3 If non-zero, character to print after left half of .WHO2.
1354         3.2     If 1, suppress the space between .WHO2 and .WHO3 printout.
1355         3.1     If 1, suppress the space between halves of .WHO3.
1356         2.9-2.7 Mode for printing left half of .WHO3.
1357         2.6-2.4 Mode for printing right half of .WHO3.
1358         2.3     Print 2.2-1.5 twice.
1359         2.2-1.5 If non-zero, character to print after left half of .WHO3.
1360         1.4-1.1 Unused.
1361         That is, if the who-line is printed at all, what appears
1362         at the end is these characters:
1363                         AAAAXX-BBBB=CCCCYY+DDDD
1364         where:  AAAA is the result of printing the left half of .WHO2.
1365                 BBBB right half of .WHO2.
1366                 CCCC left half of .WHO3.
1367                 DDDD right half of .WHO3.
1368                 XX one or two characters specified by .WHO1 4.1-3.3.
1369                 YY one or two characters specified by .WHO1 2.3-1.5.
1370                 - space, unless .WHO1 4.8 is 1.
1371                 = space, unless .WHO1 3.2 is 1.
1372                 + space, unless .WHO1 3.1 is 1.
1373         Note that the specifications fall neatly into 8-bit bytes
1374         (for the convenience of the PDP-11); hence it is easiest
1375         to specify this word using .BYTE 8 in MIDAS.
1376         Example:
1377                 .SUSET [.SWHO1,,[ .BYTE 8 ? 166 ? 0 ? 144 ? 200+", ]]
1378         causes .WHO2 to appear as a word of sixbit, and .WHO3 to
1379         appear as octal halfword typeout in mmm,,nnn format.
1380
1381 \1f
1382 .WHO2           +* +*   first user who-line variable
1383
1384         See .WHO1 for details.
1385
1386 \1f
1387 .WHO3           +* +*   second user who-line variable
1388
1389         See .WHO1 for details.
1390 \f
1391 .XJNAME         +* +*   "intended" job name.
1392
1393         This variable holds what the job's name was "intended"
1394         to be, by its creator.  Why might the job's name not
1395         actually be what it was intended to be?  Perhaps because
1396         that name was already in use by some other job, and the
1397         creator had to find a second choice.  For example, when
1398         :NEW T in DDT creates a job named T0 because there was
1399         already a job named T, the job T0's .XJNAME will be "T".
1400         In any case, when using the common technique of having
1401         several programs be links to one file, which figures
1402         out what name it was invoked under and behaves
1403         accordingly, the .XJNAME is the right place to look to
1404         find out what behavior the invoker desires.
1405
1406         When a job is first created, its .XJNAME is the same as it's .JNAME.
1407
1408 \1f
1409 .XUNAME         +* +*   "real" user name.
1410
1411         This variable holds what says who you really are,
1412         as opposed to what you are logged in as.
1413         It should be a word of sixbit, just like .UNAME.
1414         For example, if you are logged in as FOO1 then
1415         your XUNAME will probably be FOO, because that's
1416         what DDT will normally set it to.  However, though
1417         the .UNAME may change because of reowning or attaching,
1418         the .XUNAME will ot change iunless requested specifically.
1419         However, the user may alter DDT's .XUNAME by depositing in
1420         ..XUNAME, which works by informing DDT and having DDT
1421         tell ITS.
1422         Whenever an inferior is created, its .XUNAME is initialized
1423         from its superior's.