;*; Updated on 19-Jul-90 at 8:54 PM by James A. Jarboe Iv.; edit time: 0:13:21
;***************************************************************************
;                                                                          *
;                         LINK125 Terminal Driver                          *
;                                                                          *
;***************************************************************************
; Copyright (c) 1983, 1984, 1985 - Distributed Management Systems, Inc.
;
; Edit History:
;
;[104] 04/08/87 Modified to work with LINK 125 terminal         /JAJ
;[102] 09/01/86 Updated to support AM-350.                      /BRH
;[101] 08/01/85 Driver brought up to AMOS/L 1.3 driver format.  /BRH
;[100] 05/22/84 Designed and implemented by Brett R. Halle.
;

       SEARCH  SYS
       SEARCH  SYSSYM
       SEARCH  TRM

       OBJNAM  0,0,[TDV]

; Define capability flags.
;
TDVFLG=TD$LID!TD$CID!TD$RVA!TD$DIM!TD$BLN!TD$UND!TD$EOS!TD$EOL!TD$MLT!TD$STS
TDVFLG=TDVFLG!TD$AMS!TD$SPL!TD$132!TD$SMT!TD$PRT

; Terminal impure area definition.
;
OFINI
OFDEF   TI.WID, 2                       ; Current terminal width.
OFDEF   TI.FLG, 1                       ; Terminal flags:

       TI%XXX  =     0                 ;  Don't use this one.
       TI%BSL  =     1                 ;  Processing bottom status line.
       TI%HMF  =     2                 ;  Processing host message field.
       TI%ITD  =     3                 ;  Ignore all output until DEL code.
       TI%RFL  =     4                 ;  Receiving flag as next character.
       TI%RPS  =     5                 ;  Receiving position as next char.

       TI$BSL  =     2                 ;  Processing bottom status line.
       TI$HMF  =     4                 ;  Prcoessing host message field.
       TI$ITD  =    10                 ;  Ignore all output until DEL code.
       TI$RFL  =    20                 ;  Receiving flag as next character.
       TI$RPS  =    40                 ;  Receiving position as next char.

OFDEF   TI.POS, 1                       ; Current position in status line.
       S..STL  =   140.                ; Size of status line buffer.
OFDEF   TI.BSL, S..STL                  ; Bottom status line buffer.
OFDEF   TI.TSL, S..STL                  ; Top status line buffer.
OFSIZ   S..IMP                          ; Size of impure area in bytes.

       PAGE

;****************
;     LINK125   *
;****************
; Terminal driver communications area.
;
LINK125:WORD    TD$NEW!TD$TCH           ; Terminal attributes.
       BR      JMPINP                  ; Input routine.
       BR      JMPOUT                  ; Output routine.
       BR      ECHO                    ; Echo routine.
       BR      JMPCRT                  ; Crt control.
       BR      JMPINI                  ; INIT routine.
       WORD    S..IMP                  ; Impure area.
       BYTE    24.                     ; Number of rows.
       BYTE    80.                     ; Number of columns.
       LWORD   TDVFLG                  ; Terminal has:
                                       ;   Insert/delete line.
                                       ;   Insert/delete character.
                                       ;   Reverse video attribute.
                                       ;   Dim video attribute.
                                       ;   Blinking video attribute.
                                       ;   Underlined video attribute.
                                       ;   Erase to end of screen.
                                       ;   Erase to end of line.
                                       ;   Line graphics.
                                       ;   Status lines.
                                       ;   80/132 column support.
                                       ;   Smooth scroll.
       BR      JMPTCH                  ; TRMCHR routine.

JMPINI: JMP     INI                     ; Go handle init routine.
JMPINP: JMP     INP                     ; Go handle input characters.
JMPOUT: JMP     OUT                     ; Go handle output characters.
JMPCRT: JMP     CRT                     ; Go handle TCRT codes.
JMPTCH: JMP     TCH                     ; Go handle TRMCHR call.

       PAGE

;****************
;      ECHO     *
;****************
; Special echo processing is performed here.
;  Rubouts will backspace and erase the previous character.
;  Control-U will erase the entire line by backspacing and erasing.
;
ECHO:   CMPB    D1, #25                 ; Control-U?
       BEQ     CTRLU                   ;  Yes, do it.
       CMPB    D1,#177                 ; Rubout?
       JNE     ECHX                    ;  Yes, do it.

; Rubouts are handled by the ols backspace-and-erase game.
;
; Special handling must be performed if we are rubbing out a TAB.
; D6 contains the character being rubbed out.
;
RUBOUT: CMPB    D6, #11                 ; Are we rubbing out a TAB?
       BEQ     20$                     ;  Yes, special handling required.
       CMPB    D6, #40                 ; Control character?
       BLO     5$                      ;  Yes...

; Rubout was of a printable character - queue up the backspace sequence.
;
       MOV     #3, D3                  ; Set character count.
       LEA     A6, 10$                 ; Get buffer address.
       MOV     A6, D1                  ;  Set it into proper register.
       TRMBFQ                          ; Queue it up for output...
5$:     RTN                             ; All done.
10$:    BYTE    10,40,10,0

; Rubout was of a tab...
;  We must calculate how big the TAB was and backup over it.
;
20$:    CLR     D3                      ; Preclear D3.
       MOVW    T.POB(A5), D3           ; Set beginning position count.
       MOV     T.ICC(A5), D2           ; Set input character count.
       MOV     T.IBF(A5), A6           ; Set input buffer base.
30$:    SUB     #1, D2                  ; Done with scan?
       BMI     70$                     ;  Yes.
       MOVB    (A6)+, D1               ; Scan forward calculating position.
       CMPB    D1, #11                 ; TAB?
       BEQ     50$                     ;  Yes.
       CMPB    D1, #15                 ; Carriage return?
       BEQ     60$                     ;  Yes.
       CMPB    D1, #33                 ; Escape?
       BEQ     40$                     ;  Yes.
       CMPB    D1, #32.                ; Control character?
       BLO     30$                     ;  Yes.
       CMPB    D1, #172                ; Non-printable character?
       BHI     30$                     ;  Yes.
40$:    ADD     #1, D3                  ; Bump position for one character.
       BR      30$                     ;  Go process another character.
50$:    ADD     #8., D3                 ; Adjust position for TAB.
       AND     #^C<7>, D3              ; Adjust modulo 8.
       BR      30$                     ;  Go process some more.
60$:    CLR     D3                      ; Clear position for CR.
       BR      30$                     ;  Go process more characters.
70$:    COM     D3                      ; Complement value to get remainder.
       AND     #7, D3                  ; Compute for last TAB.
       ADD     #1, D3                  ; Adjust for base 0.
       MOV     #8., D1                 ; Set immediate backspace character.
       TRMBFQ                          ; Queue the backspaces.
       RTN                             ; All done.

; Echo a control-U by erasing the entire line.
;
CTRLU:  TST     D6                      ; Anything to erase?
       BEQ     ECHX                    ;  No. No action neccessary.
       CLR     D3                      ;  Yes, preclear D3.
       MOVW    T.POO(A5), D3           ; Get current output position.
       SUBW    T.POB(A5), D3           ;  Subtract beginning position.
       BEQ     ECHX                    ;   Nothing to erase.
       CMP     D3, T.ILS(A5)           ; Line to erase > terminal width?
       BLOS    10$                     ;  No, erase it.
       MOV     T.ILS(A5), D3           ;  Yes, don't erase more than width.
10$:    MOV     #8., D1                 ; Get immediate backspace character.
       TRMBFQ                          ;  Backup.
       ASL     D1, #2                  ; Clever way to get a space character.
       TRMBFQ                          ;  Blank-out the line.
       MOV     #8., D1                 ; Get backspace character.
       TRMBFQ                          ;  Backup.
ECHX:   RTN                             ; Return to caller - all done.

       PAGE

;****************
;      INP      *
;****************
; Input character processing subroutine.
;
; Return a negative flag to indicate possible multi-byte key codes.
; Detect a negative flag which indicates the multi-byte processing return.
;
INP:    BMI     20$                     ; Skip if multi-byte processing.
       CMPB    D1, #1                  ; Function code?
       BEQ     10$                     ;  Yes - could be multi-byte sequence.
       CMPB    D1, #33                 ; Escape?
       BEQ     10$                     ;  Yes - could be multi-byte sequence.
       LCC     #0                      ;  No - normal processing.
       RTN                             ; All done.

10$:    LCC     #PS.N                   ; Possible multi-byte - return N flag.
       RTN                             ; All done.

; Multi-byte processing is done here.
; This occurs when TRMSER has accumulated all bytes of a multi-byte keystroke
; D0 contains the character count and A0 indexes the data string
; A5 indexes the terminal definition block and must be preserved
; The translated character must be returned in D1 for storage
;
; This routine may destroy only A0,A3,A6,D0,D6,D7
;
20$:    MOVB    (A0)+, D1               ; Get the first character.
       SUBB    #1, D0                  ; No translation if single character.
       BEQ     40$
       CMPB    D1, #1                  ; Function sequences start with SOH.
       BEQ     50$                     ;  Function sequence.

; Escape sequences are translated directly by setting bit 7 on.
;  This will cause them to map to 240-377.
;
       MOVB    (A0)+, D1               ; Get the second character.
30$:    ORB     #200, D1                ; Set bit 7 on.
       TST     T.FXT(A5)               ; External translation active?
       BNE     40$                     ;  Yes, use it.
;;;     BIT     #T$XLT, T.STS(A5)       ; Are we doing translation?
;;;     BEQ     60$                     ;  No - check for another translation.
       BR      60$                     ;  Check for translation.
40$:    LCC     #0                      ; Reset the flags.
45$:    RTN                             ; Return to caller.

; Function codes require additional translation so that they become 200-237.
;
50$:    MOVB    (A0)+, D1               ; Get the second character.
       SUBB    #'@, D1                 ; Offset so that F1 becomes 0
       BR      30$                     ;   and go finish up.

; Come here if program is not doing translation and we must do our own.
;
60$:    LEA     A6, XLTTBL              ; Index the translation table.
70$:    MOVB    (A6)+, D7               ; Get character.
       BEQ     40$                     ;  End of table - ignore the character.
       CMPB    D1, D7                  ; Is it in the table?
       BEQ     80$                     ;  Yes.
       ADD     #1, A6                  ;  No - bypass translation.
       BR      70$                     ; Loop for more.

; Come here to translate the character.
;
80$:    MOVB    @A6, D1                 ; Translate the character.
       BR      40$

; Translation table.
;
XLTTBL: BYTE    373,5                   ; Shift-HOME = Control-E.  [103]
       BYTE    312,18.                 ; Prev-PAGE  = Control-R.  [103]
       BYTE    313,20.                 ; Next-PAGE  = Control-T.  [103]
;       BYTE    321,6.                  ; Ins-Char   = Control-F.
       BYTE    327,4.                  ; Del-Char   = Control-D.  [103]
       BYTE    321,274                 ; Repl       = EXECUTE.    [104]
;       BYTE    361,276                 ; Ins        = Shift-EXECUTE.

       BYTE    000,000

       PAGE

;****************
;      OUT      *
;****************
; Output character processing subroutine.
;  Handle status line display processing.
;
OUT:    SAVE    A6, D6, D7              ; Save registers.
       MOV     T.IMP(A5), A6           ; Index the terminal impure area.
       MOVB    D1, D6                  ;  Get output character.
       ANDW    #177, D6                ;   Get the good stuff.

; Handle ignoring of output (to support non-existant status line).
;
       BTST    #TI%ITD, TI.FLG(A6)     ; Ignore all output till DEL code?
       BEQ     10$                     ;  No.
       CMPB    D6, #13.                ;  Yes, carriage return?
       BEQ     5$                      ;   Yes, we're done.
       CMPB    D6, #177                ;   No, DEL code?
       JNE     80$                     ;    No, ignore this character.
5$:     BCLR    #TI%ITD, TI.FLG(A6)     ;    Yes, we're done with this.
       JMP     80$                     ;    All done.

; Check for position character pending.
;
10$:    BTST    #TI%RPS, TI.FLG(A6)     ; Receiving position character?
       BEQ     20$                     ;  No.
       SUBB    #32., D1                ;  Yes, adjust it.
       BPL     15$                     ;   Positive value.                     [102]
       CLRB    D1                      ;   Negative value, set to zero.        [102]
15$:    MOVB    D1, TI.POS(A6)          ;   Set it.
       BCLR    #TI%RPS, TI.FLG(A6)     ; Clear flag.
       JMP     80$                     ;   All done.

; Check for status line display.
;
20$:    MOVB    TI.FLG(A6), D7          ; Get flags.
       ANDB    #TI$BSL!TI$HMF, D7      ;  Outputting to a status line?
       JEQ     50$                     ;   Nope.
       CMPB    D6, #13.                ;   Yes, carriage return?
       BEQ     23$                     ;    Yes, we're done.
       CMPB    D6, #177                ;    No, DEL code?
       JNE     40$                     ;     No.
23$:    CLR     D1                      ; Preclear D1.
       MOVW    TI.WID(A6), D1          ;  Get width of terminal in chars.
       SAVE    A0, A2, A3, D2          ; Save registers.                       [103]
       CLR     D2                      ;  Clear space character counter.       [103]

; Handle output to bottom status line.
;
       BTST    #TI%BSL, TI.FLG(A6)     ; Output to bottom status line?
       BEQ     25$                     ;  No.
       BCLR    #TI%BSL, TI.FLG(A6)     ;  Yes, clear flag.
       LEA     A0, BSTLLD              ;  Index bottom status line leadin.     [103]
       LEA     A2, TI.BSL(A6)          ;   Index the text.                     [103]
       SUB     #2, D1                  ;   Adjust for bottom status line.
       BR      30$                     ;   All done here.

; Handle output to host message field.
;
25$:    BCLR    #TI%HMF, TI.FLG(A6)     ; Clear flag.
       SUB     #32., D1                ; Adjust for shortened top line. [104]
       LEA     A0, TSTLLD              ; Index top status line leadin.         [103]
       LEA     A2, TI.TSL(A6)          ; Index the top status line.
27$:    CMPB    (A2)+, #32.             ;  Leading space?
       BEQ     27$                     ;   Yes, bypass it.
       SUB     #1, A2                  ;   No, adjust the index.
       MOV     T.IMP(A5), A6           ; Index the impure area.                [103]
       LEA     A6, TI.TSL+S..STL(A6)   ; Index end of status line buffer.      [103]
       MOV     A6, D6                  ;  Save it.                             [103]
       LEA     A6, 0(A2)[D1]           ; Index end of status line.             [103]
       CMP     A6, D6                  ; Are we going past end of buffer?      [103]
       BLO     30$                     ;  No.                                  [103]
       SUB     D6, A6                  ;  Yes, by how much?                    [103]
       MOV     A6, D2                  ;   Get into proper register.           [103]
       MOV     D1, D6                  ; Save display size.                    [103]
       SUB     D2, D1                  ;  Adjust display size.                 [103]
       CMP     D1, #2                  ;  Valid size?                          [103]
       BGE     30$                     ;   Yes.                                [103]
       CLR     D1                      ;   No, just output command sequence.   [103]
       MOV     D6, D2                  ;    Fill line with spaces.             [103]

; Start output to status line.
;
30$:    TST     D2                      ;    Spaces needed?                     [103]
       BEQ     35$                     ;     No.                               [103]
       LEA     A3, T.OQX(A5)           ;     Index the output queue.
       QINS    A3                      ;     Insert a queue block.             [103]
       MOV     D2, 4(A3)               ;      Set output count.                [103]
       MOV     #32., 10(A3)            ;       Set character.                  [103]
35$:    TST     D1                      ;   Null message?                       [103]
       BEQ     37$                     ;    Yes, bypass it.                    [103]
       LEA     A3, T.OQX(A5)           ;   Index the output queue.
       QINS    A3                      ;   Insert a queue block.               [103]
       MOV     D1, 4(A3)               ;    Set output count.                  [103]
       MOV     A2, 10(A3)              ;    Set address.                       [103]
37$:    LEA     A3, T.OQX(A5)           ;   Index the output queue.
       QINS    A3                      ;   Insert a queue block.               [103]
       MOV     #S..SLD, 4(A3)          ;    Set output count.                  [103]
       MOV     A0, 10(A3)              ;    Set address.                       [103]
       REST    A0, A2, A3, D2          ; Restore registers.                    [103]
       MOV     T.IDV(A5), A6           ; Index the interface driver.           [102]
       CMP     -4(A6), #<[AM3]_16.>![50 ]      ; Dealing with AM350?           [102]
       BNE     80$                             ;  No.                          [102]
       CLR     D0                              ;  Yes, make sure D0 := 0.      [102]
       BR      80$                     ;  All done.

; Handle output for rest of status line.
;  Output all control characters as spaces.
;
40$:    CMPB    D6, #32.                ; Outputting a control character?
       BHIS    45$                     ;  No.
       CMPB    D6, #30.                ; Special characters?                   [102]
       BHIS    80$                     ;  Yes, ignore them.                    [102]
       MOVB    #32., D6                ;  No, output a space instead.
45$:    MOV     T.IMP(A5), A6           ; Index the impure area.
       CLR     D7                      ;  Preclear D7.
       MOVB    TI.POS(A6), D7          ;   Get the output position.
       ADDB    #1, TI.POS(A6)          ;   Bump output position.
       BTST    #TI%BSL, TI.FLG(A6)     ;  Bottom status line?
       BEQ     47$                     ;   No, top.
       LEA     A6, TI.BSL(A6)          ;  Index the bottom status line buff.
       BR      48$                     ;     All done.
47$:    LEA     A6, TI.TSL(A6)          ;  Index the top status line buff.
48$:    MOVB    D6, 0(A6)[D7]           ;   Set the character.
       BR      80$                     ;     All done.

; If next character is a flag character, set the flag.
;
50$:    BTST    #TI%RFL, TI.FLG(A6)     ; Are we receiving a flag character?
       BEQ     60$                     ;  No, but check for indicator.
       ORB     D1, TI.FLG(A6)          ;  Yes, set the flag (s).
       BCLR    #TI%RFL, TI.FLG(A6)     ;   Clear indicator flag.
       BR      80$                     ;    All done.

; Check for indicator character (377 octal) which signifies that the
;  following character is a flag.
;
60$:    CMPB    D1, #377                ; Special character passed?
       BNE     70$                     ;  Nope, normal character.
       BSET    #TI%RFL, TI.FLG(A6)     ;  Yes, signal receiving flag char.
       BR      80$                     ;   All done.

; No special processing needed ... flag it.
;
70$:    LCC     #PS.N                   ; Signal normal processing.
       BR      90$                     ;  All done.

; We did something ... zap the output character and set the Z-flag.
;
80$:    CLRB    D1                      ; Zap this character (set Z flag).

; All done.
;
90$:    REST    A6, D6, D7              ; Restore registers.
       RTN                             ; Return to caller.

; Status line leadin characters.
;
BSTLLD: BYTE    233, 'z, '(             ; Bottom status line leadin.[103]
TSTLLD: BYTE    0,233, 'F               ; Top status line leadin.   [103]
       BYTE    0
       EVEN

       S..SLD  = 3                     ; Status line leadin size.

       PAGE

;****************
;      INI      *
;****************
; Handle initialization of the terminal.
;  Set up the function keys to look like AM-60 function keys.
;
INI:    MOV     T.IDV(A5), A6           ; Index the interface driver.
       CMP     -(A6), #<[PSE]_16.>![UDO]       ; PSEUDO interface driver?
       BEQ     10$                             ;  Yes, no messages please.
       CMP     QFREE, #12.             ; Do we have enough queue blocks?
       BLO     10$                     ;  No.

; Output initialization strings...
;
       SAVE    D1,D3                   ; Save registers.
       MOV     #INISZ1, D3             ; Get size of string to send.
       LEA     A6, INIST1              ; Index the string.
       MOV     A6, D1                  ;  Set into correct register.
       TRMBFQ                          ; Output the string.
       SLEEP   #2500.                  ; Wait for process to complete.
       MOV     #INISZ2, D3             ; Get size of string to send.
       LEA     A6, INIST2              ; Index the string.
       MOV     A6, D1                  ;  Set into correct register.
       TRMBFQ                          ; Output the string.
       SLEEP   #2500.                  ; Wait for process to complete.
       MOV     #INISZ3, D3             ; Get size of string to send.
       LEA     A6, INIST3              ; Index the string.
       MOV     A6, D1                  ;  Set into correct register.
       TRMBFQ                          ; Output the string.
       SLEEP   #2500.                  ; Wait for process to complete.
       MOV     #78., D3                ; Output 78 spaces.
       MOV     #32., D1                ; Select space character.
       TRMBFQ                          ;  Output the spaces.
       SLEEP   #2500.                  ; Wait for process to complete.
       MOV     #1., D3                 ; Output single character.
       MOV     #13., D1                ; Select carriage return.
       TRMBFQ                          ;  Output the character.
       SLEEP   #2500.                  ; Wait for process to complete.
       REST    D1,D3                   ; Restore registers.

; Clear the top status line buffer with spaces.
;
10$:    MOV     T.IMP(A5)
, A6            ; Index the impure area.
       LEA     A6, TI.TSL(A6)          ; Index the top status line buffer.
       MOV     #S..STL-1, D6           ;  Get size of status line buffer.
15$:    MOVB    #32., (A6)+             ; Fill with a space.
       DBF     D6, 15$                 ;  Do it all.

; Clear the bottom status line buffer with spaces.
;
       MOV     T.IMP(A5), A6           ; Index the impure area.
       LEA     A6, TI.BSL(A6)          ; Index the bottom status line buffer.
       MOV     #S..STL-1, D6           ;  Get size of status line buffer.
20$:    MOVB    #32., (A6)+             ; Fill with a space.
       DBF     D6, 20$                 ;  Do it all.

; All done.
;
90$:    MOV     T.IMP(A5), A6           ; Index the impure area.
       MOVW    #80., TI.WID(A6)        ; Reset to 80 column mode.
       RTN                             ; Return to caller.

INIST1: BYTE    233,'+                  ; Clear all to spaces.
       BYTE    233,'`,':               ; Set into 80 column mode.
       BYTE    200,200,200,200,200,200 ;    Nulls...
       BYTE    233,'x,'0               ; Set into normal display format.
       BYTE    200,200,200,200,200,200 ;    Nulls...
       BYTE    233,'#                  ; Lock the keyboard.
       BYTE    233,'z,'@,33,'5,177     ; Set up F1 (unshifted).
       BYTE    233,'z,'`,33,'7,177     ; Set up F1 (shifted).
       BYTE    233,'z,'A,33,'4,177     ; Set up F2 (unshifted).
       BYTE    233,'z,'a,33,'6,177     ; Set up F2 (shifted).
       BYTE    233,'z,'B,33,'S,177     ; Set up F3 (unshifted).
       BYTE    233,'z,'b,33,'s,177     ; Set up F3 (shifted).
       BYTE    233,'z,'C,33,'@,177     ; Set up F4 (unshifted).
       BYTE    233,'z,'c,33,'P,177     ; Set up F4 (shifted).
       BYTE    233,'z,'D,01,'@,177     ; Set up F5 (unshifted).
       BYTE    233,'z,'d,01,'H,177     ; Set up F5 (shifted).
       BYTE    233,'z,'E,01,'A,177     ; Set up F6 (unshifted).
       BYTE    233,'z,'e,01,'I,177     ; Set up F6 (shifted).
       BYTE    233,'z,'F,01,'B,177     ; Set up F7 (unshifted).
       BYTE    233,'z,'f,01,'J,177     ; Set up F7 (shifted).
       BYTE    233,'z,'G,01,'C,177     ; Set up F8 (unshifted).
       BYTE    233,'z,'g,01,'K,177     ; Set up F8 (shifted).
       BYTE    233,'z,'H,01,'D,177     ; Set up F9 (unshifted).
       BYTE    233,'z,'h,01,'L,177     ; Set up F9 (shifted).
       BYTE    233,'z,'I,01,'E,177     ; Set up F10 (unshifted).
       BYTE    233,'z,'i,01,'M,177     ; Set up F10 (shifted).
       BYTE    233,'z,'J,01,'F,177     ; Set up F11 (unshifted).
       BYTE    233,'z,'j,01,'N,177     ; Set up F11 (shifted).
       BYTE    233,'z,'K,01,'G,177     ; Set up F12 (unshifted).
       BYTE    233,'z,'k,01,'O,177     ; Set up F12 (shifted).
       BYTE    233,'z,'L,33,'E,177     ; Set up F13 (unshifted).
       BYTE    233,'z,'l,33,'|,177     ; Set up F13 (shifted).
       BYTE    233,'z,'M,33,'R,177     ; Set up F14 (unshifted).
       BYTE    233,'z,'m,33,'~,177     ; Set up F14 (shifted).
       BYTE    233,'z,'N,33,'T,177     ; Set up F15 (unshifted).
       BYTE    233,'z,'n,33,'t,177     ; Set up F15 (shifted).
       BYTE    233,'z,'O,33,'Y,177     ; Set up F16 (unshifted).
       BYTE    233,'z,'o,33,'y,177     ; Set up F16 (shifted).
INISZ1=.-INIST1

INIST2: BYTE    233,'F                  ; Select top status line.
       ASCII   /System booting - please wait . . . /
       BYTE    13.
INISZ2=.-INIST2

INIST3: BYTE    233,'z, '(              ; Select bottom status line.
INISZ3=.-INIST3

       EVEN

       PAGE

;****************
;      TCH      *
;****************
; TRMCHR call.
;
; Passed:
;
;       A1      => Argument block.
;       A2      => TDV.
;       D2      := Flags.
;
;       Only A1,A2,A6,D1,D2,D6,D7 may be modified.
;
TCH:    MOV     TD.FLG(A2), TC.FLG(A1)  ; Return flags.
       MOV     JOBCUR, A6              ; Index JCB.
       MOV     JOBTRM(A6), A6          ;  Index TRMDEF block.
       MOV     T.IMP(A6), A6           ;   Index inpure area.
       CLR     D6                      ; Preclear D6.
       MOVB    TD.ROW(A2), D6          ;  Get row count.
       MOVW    D6, TC.ROW(A1)          ;   Return row count.
       MOVW    TI.WID(A6), TC.COL(A1)  ; Return column count.
       CLRW    TC.CLR(A1)              ; No colors.
       MOVW    TI.WID(A6), TC.TSL(A1)  ; Set length of top status line.
       SUBW    #33., TC.TSL(A1)        ;  Adjust for shortened top status line.
       CLRW    TC.SSL(A1)              ; Set length of shifted status line.
       MOVW    TI.WID(A6), TC.USL(A1)  ; Set length of unshifted status line.
       MOV     D2, D7                  ; Get flags.
       AND     #TC$BMP, D7             ; Return bitmap?
       BEQ     90$                     ;  No.

; Return bitmap.
;
       PUSH    A1                      ; Save register.
       ADD     #TC.BMP, A1             ;  Index bitmap return area.
       LEA     A6, TCHBMP              ; Index our bitmap.
       MOV     #<256./16.>-1, D7       ; Get size in words (adjusted for DBF).
10$:    MOVW    (A6)+, (A1)+            ; Return bitmap information.
       DBF     D7, 10$                 ; Loop until done.
       POP     A1                      ; Restore register.

; All done.
;
90$:    RTN                             ; Return to caller.

; Define feature bitmap.
;
TCHBMP: BYTE    ^B11111111              ;   0 -   7
       BYTE    ^B11111111              ;   8 -  15
       BYTE    ^B11111111              ;  16 -  23
       BYTE    ^B11111001              ;  24 -  31 (No horiz or vert pos)
       BYTE    ^B11111111              ;  32 -  39
       BYTE    ^B11111111              ;  40 -  47
       BYTE    ^B01111111              ;  48 -  55 (no shifted f-key line)
       BYTE    ^B11100011              ;  56 -  63 (no vertical split)
       BYTE    ^B00000000              ;  64 -  71 (no special characters)
       BYTE    ^B10000000              ;  72 -  79 (no special characters)
       BYTE    ^B00001111              ;  80 -  87 (no alternate page)
       BYTE    ^B10000000              ;  88 -  95 (no box commands)
       BYTE    ^B11111111              ;  96 - 103
       BYTE    ^B00000011              ; 104 - 111 (no non-space attributes)
       BYTE    ^B00000000              ; 112 - 119 (no non-space attributes)
       BYTE    ^B00001111              ; 120 - 127 (spare)
       BYTE    ^B00000111              ; 128 - 135 (no AM-70 style color)
       BYTE    ^B00000000              ; 136 - 143
       BYTE    ^B00000000              ; 144 - 151
       BYTE    ^B00000000              ; 152 - 159
       BYTE    ^B00000000              ; 160 - 167
       BYTE    ^B00000000              ; 168 - 175
       BYTE    ^B00000000              ; 176 - 183
       BYTE    ^B00000000              ; 184 - 191
       BYTE    ^B00000000              ; 192 - 199
       BYTE    ^B00000000              ; 200 - 207
       BYTE    ^B00000000              ; 208 - 215
       BYTE    ^B00000000              ; 216 - 223
       BYTE    ^B00000000              ; 224 - 231
       BYTE    ^B00000000              ; 232 - 239
       BYTE    ^B00000000              ; 240 - 247
       BYTE    ^B00000000              ; 248 - 255

       EVEN

       PAGE

;****************
;      CRT      *
;****************
; Special CRT control processing.
;
; D1 contains the control code for X,Y positioning or special commands.
;
; If D1 is positive, do screen positioning (high byte = row, low byte = col).
; If D1 is negative, do special command (low byte = code).
;
CRT:    TSTW    D1                      ; Is it a cursor position?
       BMI     10$                     ;  No, handle special command.

; Do cursor positioning - D1 contains X,Y coordinates.
;  Use short form addressing whenever possible.
;
       MOV     T.IMP(A5), A6           ; Index the terminal impure area.
       CMPW    TI.WID(A6), #80.        ; Extended form addressing needed?
       BHI     5$                      ;  Yes.
       ADDW    #<31._8.>+31., D1       ; Add position offset.
       TTYI                            ; Send cursor position command.
       BYTE    233, '=, 0              ; <ESC> =
       EVEN
       RORW    D1, #8.                 ; Get X value in low byte.
       TTY                             ;   Output row position.
       ROLW    D1, #8.                 ; Get Y value in low byte.
       TTY                             ;   Output column position.
       RTN                             ; Return to caller.

; Do cursor positioning (extended form) - D1 contains X,Y coordinates.
;
5$:     TTYI                            ; Send cursor position command.
       BYTE    233, 'a, 0              ; <ESC> a
       EVEN
       PUSHW   D1                      ; Save D1.
       ASR     D1, #8.                 ; Get X value in low byte.
       AND     #377, D1                ;  Just save byte data.
       DCVT    0,OT$TRM                ;   Output row.
       MOVB    #'R, D1                 ; Get row indicator.
       TTY                             ;  Output to terminal.
       MOV     @SP, D1                 ; Restore a copy of D1.
       AND     #377, D1                ;  Just save byte data.
       DCVT    0,OT$TRM                ;   Output column.
       MOVB    #'C, D1                 ; Get column indicator.
       TTY                             ;  Output to terminal.
       POPW    D1                      ; Restore D1.
       RTN                             ; Return to caller.

; Special commands - D1 contains the command code in the low byte.
;
10$:    AND     #377, D1                ; Save only the command code.
       BNE     20$                     ;  Non-zero....process codes.
       TTYI                            ;  Code zero...clear screen.
       BYTE    233, '+, 0              ;   <ESC> +
       EVEN
       BR      80$                     ; Go add trailing nulls.

; Handle setting wide and narrow format.
;
20$:    CMPB    D1, #80.                ; Set to wide format?
       BNE     25$                     ;  No.
       TTYI                            ;  Yes, do it.
       BYTE    233,'`,';,0             ;   Set into 132 column mode.
       EVEN
       MOV     #132., D6               ; Set column count.
       BR      29$                     ;  Finish up.
25$:    CMPB    D1, #81.                ; Set to narrow format?
       BNE     30$                     ;  No.
       TTYI                            ;  Yes, do it.
       BYTE    233,'`,':,0             ;   Set into 80 column mode.
       EVEN
       MOV     #80., D6                ; Set column count.
29$:    MOV     T.IMP(A5), A6           ; Get impure area index.
       MOVW    D6, TI.WID(A6)          ;  Set terminal width.
       SLEEP   #7500.                  ;   Snooze for 3/4 second.
       BR      80$                     ;   All done (output some nulls).

; Output codes to terminal as per director tables.
;
30$:    ASL     D1, #1                  ; Compute byte offset (word entries).
       CMP     D1, #CRCB-CRCA          ; Is code valid?
       BHI     90$                     ;  Nope.
       LEA     A6, CRCA-2[D1]          ;  Yes, index into table.
       ADDW    @A6, A6                 ;    Add in offset to codes.
       TTYL    @A6                     ; Output terminal code.
       BR      90$                     ;  All done.

; Snooze after long command.
;
80$:    TTYL    CRTNUL                  ; Send filler...

; All done.
;
90$:    RTN                             ; Return to caller.

; Null characters for long commands.
;
CRTNUL: BYTE 200,200,200,200,200,200,200,200,200,200,200
       BYTE 200,200,200,200,200,200,200,200,200,200,200, 0
;       BYTE 200,200,200,200,200,200,0
       EVEN

; Byte offset and data tables follow for all commands.
;
CRCA:   WORD    C01-.,C02-.,C03-.,C04-.,C05-.,C06-.,C07-.,C08-.,C09-.,C10-.
       WORD    C11-.,C12-.,C13-.,C14-.,C15-.,C16-.,C17-.,C18-.,C19-.,C20-.
       WORD    C21-.,C22-.,C23-.,C24-.,C25-.,C26-.,C27-.,C28-.,C29-.,C30-.
       WORD    C31-.,C32-.,C33-.,C34-.,C35-.,C36-.,C37-.,C38-.,C39-.,C40-.
       WORD    C41-.,C42-.,C43-.,C44-.,C45-.,C46-.,C47-.,C48-.,C49-.,C50-.
       WORD    C51-.,C52-.,C53-.,C54-.,C55-.,C56-.,C57-.,C58-.,C59-.,C60-.
       WORD    C61-.,C62-.,C63-.,C64-.,C65-.,C66-.,C67-.,C68-.,C69-.,C70-.
       WORD    C71-.,C72-.,C73-.,C74-.,C75-.,C76-.,C77-.,C78-.,C79-.,C80-.
       WORD    C81-.,C82-.,C83-.,C84-.,C85-.,C86-.,C87-.,C88-.,C89-.,C90-.
       WORD    C91-.,C92-.,C93-.,C94-.,C95-.,C96-.,C97-.,C98-.,C99-.,C100-.
       WORD    C101-.,C102-.,C103-.,C104-.,C105-.,C106-.,C107-.,C108-.,C109-.,C110-.
       WORD    C111-.,C112-.,C113-.,C114-.,C115-.,C116-.,C117-.,C118-.,C119-.,C120-.
       WORD    C121-.,C122-.,C123-.,C124-.,C125-.,C126-.,C127-.,C128-.,C129-.,C130-.
       WORD    C131-.,C132-.,C133-.,C134-.,C135-.,C136-.,C137-.,C138-.,C139-.,C140-.
       WORD    C141-.,C142-.,C143-.,C144-.,C145-.,C146-.,C147-.
CRCB:

       PAGE

C01:    BYTE    30.,0                   ; Cursor Home (move to column 1,1).
C02:    BYTE    200+13.,0               ; Cursor Return (move to column 1).
C03:    BYTE    11.,0                   ; Cursor Up.
C04:    BYTE    10.,0                   ; Cursor Down.
C05:    BYTE    8.,0                    ; Cursor Left.
C06:    BYTE    12.,0                   ; Cursor Right.
C07:    BYTE    233,43,0                ; Lock Keyboard.
C08:    BYTE    233,42,0                ; Unlock Keyboard.
C09:    BYTE    233,'T,0                ; Erase to End of Line.
C10:    BYTE    233,'Y,0                ; Erase to End of Screen.
C11:    BYTE    233,'),0                ; Enter Backgroud Display mode (reduced intensity).
C12:    BYTE    233,'(,0                ; Enter Foreground Display mode (normal intensity).
C13:    BYTE    233,'&,0                ; Enable Protected  fields.
C14:    BYTE    233,'',0                ; Disable Protected Fields.
C15:    BYTE    233,'R,0                ; Delete Line.
C16:    BYTE    233,'E,0                ; Insert Line.
C17:    BYTE    233,'W,0                ; Delete Character.
C18:    BYTE    233,'Q,0                ; Insert Character.
C19:    BYTE    233,'b,0                ; Read Cursor Address.
C20:    BYTE    233,'M,0                ; Read Character at Current Cursor Position.
C21:    BYTE    233,'G,'2,0             ; Start Blinking Field.
C22:    BYTE    233,'G,'0               ; End Blinking Field.
C23:                                    ; Start Line Drawing Mode (enable alt char set).
C24:                                    ; End Line Drawing Mode (disable alt char set).
C25:                                    ; Set Horizontal Position.
C26:    BYTE    0                       ; Set Vertical Position.
C27:    BYTE    233,'A,0                ; Set Terminal Attributes.
C28:    BYTE    233,'`,'1,0             ; Cursor on.
C29:    BYTE    233,'`,'0,0             ; Cursor Off.
C30:    BYTE    32.,233,'G,'8,0         ; Start Underlined Field.     [104]
C31:    BYTE    233,'G,'0,32.,0         ; End Underlined Field.       [104]
C32:    BYTE    32.,233,'G,'4,0         ; Start Reversed Field.       [104]
C33:    BYTE    233,'G,'0,32.,0         ; End Reversed Field.         [104]
C34:    BYTE    32.,233,'G,'6,0         ; Start Reversed/Blinking Field.[104]
C35:    BYTE    233,'G,'0,32.,0         ; End Reversed/Blinking Field.  [104]
C36:    BYTE    233,'`,'8,0             ; Turn off screen display.
C37:    BYTE    233,'`,'9,0             ; Turn on screen display.
C38:    BYTE    233,'H,'2,0             ; Top left corner.              [104]
C39:    BYTE    233,'H,'3,0             ; Top right corner.             [104]
C40:    BYTE    233,'H,'1,0             ; Bottom left.                  [104]
C41:    BYTE    233,'H,'5,0             ; Bottom right.                 [104]
C42:    BYTE    233,'H,'0,0             ; Top intersect.                [104]
C43:    BYTE    233,'H,'9,0             ; Right intersect.              [104]
C44:    BYTE    233,'H,'4,0             ; Left intersect.               [104]
C45:    BYTE    233,'H,'=,0             ; Bottom intersect.             [104]
C46:    BYTE    233,'H,':,0             ; Horizontal line.              [104]
C47:    BYTE    233,'H,'6,0             ; Vertical line.                [104]
C48:    BYTE    233,'H,'8,0             ; Center intersect.             [104]
C49:    BYTE    233,'H,'7,0             ; Solid block.                  [104]
C50:    BYTE    233,'H,'?,0             ; Slant block.                  [104]
C51:    BYTE    233,'H,073,0            ; Cross-hatch block.            [104]
C52:    BYTE    233,'H,'<,0             ; Double line horizontal.       [104]
C53:    BYTE    233,'H,'>,0             ; Double line vertical.         [104]
C54:    BYTE    377,TI$BSL!TI$RPS,0     ; Send message to function key line.
C55:    BYTE    377,TI$ITD,0            ; Send message to shifted function key line.
C56:    BYTE    233,'x,'0,0             ; Set normal display format.
C57:    BYTE    233,'x,'1               ; Set horizontal split (follow with row code).
C58:                                    ; Set vertical split (39 char columns).
C59:                                    ; Set vertical split (40 char columns).
C60:    BYTE    0                       ; Set vertical split column to next char.
C61:    BYTE    233,'],0                ; Activate split segment 0.
C62:    BYTE    233,'},0                ; Activate split segment 1.     [104]
C63:    BYTE    377,TI$HMF!TI$RPS,0     ; Send message to host message field.
C64:    BYTE    '^,0                    ; Up-arrow.
C65:    BYTE    'v,0                    ; Down-arrow.
C66:    BYTE    '',0                    ; Raised dot.
C67:    BYTE    '~,0                    ; End of line marker.
C68:    BYTE    '[,0                    ; Horizontal tab symbol.
C69:                                    ; Paragraph.
C70:                                    ; Dagger.
C71:                                    ; Section.
C72:                                    ; Cent sign.
C73:                                    ; One-quarter.
C74:                                    ; One-half.
C75:                                    ; Degree.
C76:    BYTE    32.,0                   ; Trademark.
C77:    BYTE    32.,0                   ; Copyright.                    [104]
C78:    BYTE    32., 0                  ; Registered.
C79:    BYTE    233,'P                  ; Print screen.
C80:                                    ; Reserved for set to wide mode.
C81:    BYTE    0                       ; Reserved for set to normal mode.
C82:    BYTE    'X-100,0                ; Enter transparent print mode. [104]
C83:    BYTE    'T-100                  ; Exit transparent print mode.  [104]
C84:                                    ; Begin writing to alternate page.
C85:                                    ; End writing to alternate page.
C86:                                    ; Toggle page.
C87:                                    ; Copy to alternate page.
C88:                                    ; Insert a column.
C89:                                    ; Delete a column.
C90:                                    ; Block fill with attribute.
C91:                                    ; Block fill with character.
C92:                                    ; Draw a box.
C93:                                    ; Scroll box up one line.
C94:    BYTE    0                       ; Scroll box down one line.
C95:    BYTE    233,'`,'@,0             ; Select jump scroll.
C96:    BYTE    233,'`,'?,0             ; Select fast smooth scroll.
C97:    BYTE    233,'`,'>,0             ; Select medium fast smooth scroll.
C98:    BYTE    233,'`,'=,0             ; Select medium slow smooth scroll.
C99:    BYTE    233,'`,'<,0             ; Select slow smooth scroll.
C100:   BYTE    233,'G,':,32.,0         ; Select underscrore/blink.     [104]
C101:   BYTE    233,'G,'0,32.,0         ; End underscore/blink.         [104]
C102:   BYTE    233,'G,'<,32.,0         ; Select underscore/reverse.    [104]
C103:   BYTE    233,'G,'0,32.,0         ; End underscore/reverse.       [104]
C104:   BYTE    233,'G,'>,32.,0         ; Select underscore/reverse/blink.[104]
C105:   BYTE    233,'G,'0,32.,0         ; End underscore/reverse/blink. [104]
C106:                                   ; Start underscore w/o space.
C107:                                   ; End underscore w/o space.
C108:                                   ; Start reverse w/o space.
C109:                                   ; End reverse w/o space.
C110:                                   ; Start reverse/blinking w/o space.
C111:                                   ; End reverse/blinking w/o space.
C112:                                   ; Start reverse/blinking w/o space.
C113:                                   ; End reverse/blinking w/o space.
C114:                                   ; Start underscore/reverse w/o space.
C115:                                   ; End underscore/reverse w/o space.
C116:                                   ; Start underscore/reverse/blink w/o space.
C117:                                   ; End underscore/reverse/blink w/o space.
C118:                                   ; Start blink w/o space.
C119:   BYTE    0                       ; End blink w/o space.
C120:   BYTE    233,'`,'5,0             ; Set cursor to blinking block.
C121:   BYTE    233,'`,'2,0             ; Set cursor to steady block.
C122:   BYTE    233,'`,'3,0             ; Set cursor to blinking underline.
C123:   BYTE    233,'`,'4               ; Set cursor to steady underline.
C124:                                   ; SPARE.
C125:                                   ; SPARE.
C126:                                   ; SPARE.
C127:   BYTE    0                       ; SPARE.
C128:   BYTE    377,TI$HMF!TI$RPS,32.,0 ; Select top status line w/o address.
C129:   BYTE    177,0                   ; End status line.
C130:   BYTE    377,TI$BSL!TI$RPS,32.,0 ; Select unshifted status line w/o addr.
C131:   BYTE    377,TI$ITD              ; Select shifted status line w/o addr.
C132:                                   ; Select black text.
C133:                                   ; Select white text.
C134:                                   ; Select blue text.
C135:                                   ; Select magenta text.
C136:                                   ; Select red text.
C137:                                   ; Select yellow text.
C138:                                   ; Select green text.
C139:                                   ; Select cyan text.
C140:                                   ; Select black reverse text.
C141:                                   ; Select white reverse text.
C142:                                   ; Select blue reverse text.
C143:                                   ; Select magenta reverse text.
C144:                                   ; Select red reverse text.
C145:                                   ; Select yellow reverse text.
C146:                                   ; Select green reverse text.
C147:   BYTE    0                       ; Select cyan reverse text.

       EVEN

       END