; ADITC - Adit driver (COMSER compatible version) ; (C) 1988 Macrotech International, Inc. All rights reserved. ; for use with AMOS 1.3C or later. ;[101] 14 March 1989 10:27 Edited by MACROTECH ; ; Added receiver disable routine. ; Changed break interrupt handling. ; Changed vector jump table to accomodate four or more ADIT boards. ; Added conditional assembly of header for 1.xD or later releases ; Added assembly option to input flow control on SCCRTS instead of SCCDTR. ; Revised COMSER variables to use CS prefix instead of CM prefix due ; to inconsistencies between various AM UNV files. VMAJOR = 2 VMINOR = 0 VWHO = 0 VSUB = 0 VEDIT = 101. ; Assembly options: ; 0 - Driver for AMOS/L up to and including 1.3C ; 1 - Driver for AMOS/L under 1.3D or later (includes header) ; 2 - Driver for AMOS/L 1.3C or earlier, in flow control pin swapped. ; 3 - Driver for AMOS/L under 1.3D or later, in flow control pin swapped. ; mapping of signal names and pin numbers ; Signal name function DB-25 pin # DB-9 pin # ; RS%TXD output to terminal 2 2 ; RS%RXD input from terminal 3 3 ; RS%CTS input (device busy) 20 4 ; RS%RTS output (port busy) 6 5 ; RS%DTR output (modem control) 5 9 ; RS%DCD input (modem DCD) 4 8 ; ; Standard release configuration: ; port = E0h ; interrupt level = 7 SEARCH SYS SEARCH SYSSYM SEARCH TRM OBJNAM 0, 0, [IDV] SY$M30 = 100000 ; just in case it gets to S-100 buss! SY$M20 = 20000 ; in case not defined in SYSSYM ; macro to define immediate op codes not implemented in M68. DEFINE IMMOPC ARG, OPCODE, OPNAME, MASK NTYPE ...EA, ARG NEVAL ...EV, ARG IF EQ, ...EA-^O74 IFT IF B, MASK IFT WORD OPCODE, ...EV IFF WORD OPCODE, ...EV&MASK ENDC IFF ASMMSG 'OPNAM requires immediate argument' ENDC ENDM ; macro to define OR IMMEDIATE to STATUS REGISTER op code. DEFINE ORISR ARG=IMMOPC ARG, ^O0174, ORISR ; COMSER communications support definitions ; CS.xxx defines the format of the A6 argument stack for COMSET calls .=0 CS.BAU: BLKW 1 ; baud rate CS.DAT: BLKW 1 ; data bits (encoded) CS.STP: BLKW 1 ; stop bits " CS.FLA: BLKW 1 ; flags CS.STS: BLKL 1 ; status mask CS.SIZ=. .=0 ; COMSER field definitions that may not be in SYS or SYSSYM ; macro to define bit field and word field parameters in one statement DEFINE SDEF PRE, SUF, BITVAL PRE'$'SUF = 1_BITVAL PRE'%'SUF = BITVAL ENDM SDEF CS, PAR, 0 ; parity enable bit SDEF CS, ODD, 1 ; parity is odd bit SDEF CS, TRTS, 2 ; transmitter controls RS%RTS pin SDEF CS, RRTS, 3 ; receiver controls RS%RTS pin SDEF CS, CTS, 4 ; RS%CTS pin controls transmitter SDEF CS, BRK, 5 ; break function enable SDEF CS, BON, 6 ; set/reset (1/0) break bit IF NDF,MTSRES, MTSRES=^O2354 ; define montst reset q head ID$ASNC = ^H01 ; asynchronous interface ID$SYNC = ^H02 ; synchronous interface ID$TRTS = ^H04 ; transmitter can control RS%RTS ID$RRTS = ^H08 ; receiver can control RS%RTS ID$CTS = ^H10 ; RS%CTS can control transmitter ID$BGEN = ^H20 ; can generate breaks ID$DRCV = ^H40 ; can disable receive interrupts ID$SMRT = ^H80000000 ; IDV has intelligent capabilities ; Build IDV characteristics flag. IDVFLG = ID$ASNC!ID$RRTS!ID$BGEN!ID$DRCV ; Adit I/O port address offsets from base address. ; AIC = 0 ;command register AIR1 = 1 ;interface register 1 AIR2 = 2 ;interface register 2 AIR3 = 3 ;interface register 3 ASEMA4 = 4 ;semaphore register AIACK = 5 ;interrupt acknowledge register ; ABUSY = 0 ;semaphore busy bit = bit 0 ; ; immediate command definitions issued thru aic. ; ASTAT = 0 ;request io status ARSET = ^H10 ;io channel reset AERSET = ^H20 ;io channel error reset ARECN = ^H30 ;io channel reconfiguration ASDI = ^H40 ;single data in AISDA = ^H50 ;interrupt on single data in ASDO = ^H60 ;single data out AISDOB = ^H70 ;interrupt on single out buffer space AEXT = ^H80 ;io extended command AEXTI = ^H90 ;aext with interrupt on completion ARES1 = ^H0A0 ;reserved for future use ASPCL = ^H0B0 ;special conditions command AFRSET = ^H0C0 ;full board reset AMTST = ^H0C1 ;nondestructive ram test ANONE = ^H0F0 ;illegal command ; ; ; extended command definitions ; SYNRCN = 1 ;synchronous line reconfiguration SETECB = 2 ;set/clr ecb host address OUTWBC = ^H10 ;dma out with byte count OUTWEM = ^H12 ;dma out with eom character search INWBC = ^H30 ;dma input with byte count INWEOM = ^H32 ;dma input with eom character search ; ; subcommand definitions for special condition command ; TOGCON = ^H10 ;toggle control lines INTCON = ^H20 ;interrupt on external int CANDMA = ^H31 ;cancel extended command CANINT = ^H32 ;cancel interrupt attention requests IDCHRD = ^H40 ; receiver hardware reverse flow control IDCXON = ^H41 ; receiver XON/XOFF flow control ; ; special conditions bit definitions in AIR2 ; SCCRTS = 2 ;to toggle SCC rts (DB-25 pin 5, DB-9 pin 9, RS%DTR) SCCDTR = ^H80 ;to toggle SCC dtr (DB-25 pin 6, DB-9 pin 5, RS%RTS) SCCBRK = ^H10 ;start/stop reverse break condition ; ; bit definitions for request status returned values ; values adit returns in AIR1 ; ST$IN = 1 ;input buffer has data ST%IN = 0 ST$OT = 2 ;output data will be accepted ST%OT = 1 ST$AC = 4 ;channel had active command ST%AC = 2 ST$OB = 8. ;out buffer still has data to send ST%OB = 3 ST$CD = ^H10 ;non-latched dcd flag (flow control input) ST%CD = 4 SD$BR = ^H20 ;latched break flag SD%BR = 5 SD$PE = ^H40 ;latched parity error flag SD%PE = 6 SD$OV = ^H80 ;latched overrun (lost data) flag SD%OV = 7 ; bit definitions for ZILOG 8530 bits on AIR2 ZL$BR = ^H80 ; 8530 detected a break ZL$EOM = ^H40 ; tx underrun or EOM (always 1 in async) ZL$CTS = ^H20 ; status of SCC CTS pin (used for DCD) ZL%CTS = 5 ; ZL$HNT = ^H10 ; SYNC/HUNT flag ZL$M1C = ^H08 ; ONE clock missing ZL$M2C = ^H04 ; TWO clocks missing ZL$LSA = ^H02 ; loop mode send active ZL$ONL = ^H01 ; on loop SDLC mode ; bit definitions for 8530 bits on AIR3 ZP$END = ^H80 ; end of SDLC frame ZP$CFE = ^H40 ; CRC or framing error ZP$ROV = ^H20 ; receiver overrun flag ZP$PE = ^H10 ; parity error ZP$RS2 = ^H08 ; residue code 2 ZP$RS1 = ^H04 ; residue code 1 ZP$RS0 = ^H02 ; residue code 0 ZP$AS = ^H01 ; all sent flag ; bit definitions for pin status interrupt IE%CTS = 5. ; SCC CTS interrupt enable bit IE%DCD = 3. ; SCC DCD interrupt enable bit ; ; ; reconfiguration command parameters ; B81N = ^H0C4 ;8 bits, 1 stop, no parity BXONOF = ^H10 ;set xon xoff onboard protocol BMULT = ^H20 ;use multiple output buffers ONDTR = ^H80 ;SCC dtr active - include with hi time constant ONRTS = ^H40 ;SCC rts active - include with hi time constant ONBOTH = ONDTR + ONRTS ;both SCC dtr and SCC rts active ; ; RS%PGD = ^H01 ; protective ground RS%TXD = ^H02 ; transmit data RS%RXD = ^H03 ; receive data RS%RTS = ^H04 ; request to send RS%CTS = ^H05 ; clear to send RS%DSR = ^H06 ; data set ready RS%SGD = ^H07 ; signal ground RS%DCD = ^H08 ; receive line signal or data carrier detect RS%SRL = ^H0C ; secondary receive line signal RS%SCT = ^H0D ; secondary clear to send RS%STX = ^H0E ; secondary transmit data RS%TSC = ^H0F ; transmitter signal element timing (DCE) RS%SRX = ^H10 ; secondary receive data RS%RSC = ^H11 ; receiver signal element timing (DCE) RS%SRT = ^H13 ; secondary request to send RS%DTR = ^H14 ; data terminal ready RS%SQD = ^H15 ; signal quality detector RS%RGI = ^H16 ; ring indicator RS%DSS = ^H17 ; data signal rate selector (DCE/DTE) RS%TST = ^H18 ; transmitter signal element timing (DTE) ; macro to wait for ADIT busy semaphore DEFINE WAITBZY 10$$: BTST #ABUSY, ASEMA4(A3) ;test busy bit of semaphore port BNE 10$$ ;continue testing til not busy ENDM ; define storage for each TCB. .=0 A.TDEF: BLKL 1 ; pointer to TCB A.STS: BLKB 1 ; last INTERRUPT status byte constructed A.CMD: BLKB 1 ; extended comand byte EVEN A.CNT: ; word format buffer count A.LOWC: BLKB 1 ; buffer count low byte A.HIC: BLKB 1 ; buffer count high byte A.DMA: ; low word format DMA address A.ADLO: BLKB 1 ; DMA address low A.ADMI: BLKB 1 ; adresss middle A.ADHI: BLKB 1 ; adresss high A.IMSK: BLKB 1 ; interrupt status bit mask A.SPIN: BLKB 1 ; last output pin status asserted A.RFLG: BLKB 1 ; flag to arm revr interrupts A.RCNT: BLKB 1 ; received byte count A.BUFF: OBFSIZ = 128.-A.BUFF BLKB OBFSIZ ; DMA buffer area A.SIZ=. .=0 TOTBUF=0 ; This macro defines the board parms and interrupt header code. DEFINE BOARD BRDADD, ILEVEL, INITED 10$$: WORD BRDADD!^H0FF00 BYTE ILEVEL*4, INITED ; this vector entry routine is duplicated for each board for speed. SVLOK SAVE A2-A6, D0-D7 MOV #TOTBUF, D7 ; get base port # MOVW 10$$, A3 ; A3 gets base address of board JMP INTCOM ; continue interrupt processing TOTBUF=TOTBUF+16. CBISIZ=.-10$$ ENDM NVALU OPTION ; pick off assembly options PSECT IF NE,OPTION&1 IFT ASMMSG "Assembling ADITC with HEADER for AMOS/L 1.3D or later!!" PHDR -1,0,0 ENDC BR CHROUT ; output init routine BR 30$ ; interface init routine BR 10$ ; GETPIN vector BR 20$ ; SETPIN vector WORD ^H0A5A5 ; new IDV format signature LWORD IDVFLG ; ASYNC, RCV-RTS,XMT-CTS,can break BR DBLRCV ; disable rec interrupts 10$: JMP GETPIN 20$: JMP SETPIN 30$: JMP INADIT ; add additional driver entry points here to remain compatible. WORD [VCT] ; search label for board address table SPUCNT: LWORD 0 ; count of spurious interrupts ; DBLRCV: SAVE A3,A4,D2 CALL IDXADT CALL IDXTBL ; index A4 to table entry MOVB D1,A.RFLG(A4) ; flag no more receiver interrupts BNE 10$ ; no other action needed ; turn interrupt back on - issue command! ANDB #17,D2 ORB #AISDA, D2 ; this will make interrupt when ready CALL ISSUE1 ; issue command to arm receiver ints 10$: REST A3,A4,D2 RTN ; ; This routine initializes output by arming transmit interrupts. CHROUT: SAVE A3, D2 CALL IDXADT ; A3 gets board address. ANDB #17, D2 ; mask D2 channel to 0-15. ORB #AISDOB, D2 ; this will make interrupt when ready CALL ISSUE1 ; issue command to arm xmitter REST A3, D2 RTN ; This table defines all ADIT boards in the system, up to a maximum of 8. ; The first entry defines ports 0-17 octal, the second defines 20-37, etc. ; Each entry must use a unique and otherwise unused interrupt. ; No table termination is needed. CBITBL: BOARD ^H0E0, 7 ; port ^H0E0, interrupt 7 ; add extra BOARD definitions for more ADITs here. MAXPRT: WORD TOTBUF ; total ports defined ; ; INADIT initilizes ADIT card, interrupt vector for card and ADIT channel. ; INADIT is called by the TRMDEF program (D0 is positive), or ; by the COMSET monitor call. (D0 is negative {-1}) INADIT: SAVE D1-D7, A0,A3,A4 MOV A6,A0 ; save ptr to possible CS.xxx parms JLOCK LEA A6,PRVVIO ; index PRVVIO i-code routine MOVW #^H20,A3 PUSH @A3 ; save old value MOV A6,@A3 ; put in our vector SSTS D1 ; get status word POP @A3 ; restore old vector JUNLOK BTST #13.,D1 ; SHOWING SV STATE? BNE 10$ ; YES SUPVR 10$: MOV A0,A6 ; A6 gets back ptr to args ORB #PS.Z, D1 ; preset Z flag bit for exit status LINK A1, #-CS.SIZ ; allocate storage on stack ; check port number range MOV T.IHM(A5), D2 ; D2 gets channel number LEA A0, MAXPRT ; index maximum port CMPW D2, @A0 ; legal JHIS NOTDEF ; board not defined ; index local storage area for the channel CALL IDXTBL ; index A4 to D2 IDV table entry MOV A5, A.TDEF(A4) ; set TCB pointer ; check to see if TRMDEF program or COMSET is caller. TST D0 ; D0 is -1 if COMSET is caller. BMI 20$ ; comset is caller-use A6 args ; build COMSET compatible area on stack with TRMDEF's baud rate MOV SP, A6 ; index work area we built on stack MOVW D0, CS.BAU(A6) ; set new baud rate for comser MOVW #8.-5., CS.DAT(A6) ; set default data bits MOVW #CS$RRTS, CS.FLA(A6) ; default to reverse flow on MOVW #1, CS.STP(A6) ; set default stop bits (1) MOV #0, CS.STS(A6) ; set default interrupt status mask ; get the board address and interrupt level from channel/board/interrupt table 20$: MOV D2, D3 ; dupe T.IHM image into D3 AND #16.-1, D2 ; D2 gets channel number mod 16. LSR D3, #4. ; D3 gets board number. MUL D3, #CBISIZ ; then multiply by CBI entry size LEA A0, CBITBL ; index the table ADD D3, A0 ; add offset to proper entry in table MOVW (A0)+, A3 ; A3 gets sign-ext board base address MOV A3, T.IHW(A5) ; set board address in TCB CLR D5 ; preclear MOVB (A0)+, D5 ; D5 gets interrupt level * 4 CALL INIZ80 ; make sure the board has been inited ; see if this is a break command, and skip baud rate stuff if so MOVW CS.FLA(A6), D7 ANDW #CS$BON, D7 ; break command? BEQ 25$ ; no - handle normal channel init CALL PROBRK ; yes-just change break status BR INITXT 25$: CALL SETCHN ; reset channel parms, baud, etc. CALL PROINT ; process pin interrupt requests CALL SETEXT ; set extended DMA command address CALL PROBRK ; process break & output pin states CALL PROREV ; process reverse flow control TSTB @A5 ; is output in progress? BPL 30$ ; no - no need to arm output MOV T.IHW(A5),A3 ; yes-arm output interrupts MOV T.IHM(A5),D2 ANDB #17,D2 ORB #AISDOB, D2 ; this will make interrupt when ready CALL ISSUE1 30$: INITXT: UNLNK A1 ; deallocate our data area LSTS D1 ; restore caller's status ; Z flag is set if successful REST D1-D7, A0,A3,A4 ; restore regs RTN ; special illegal instruction routine to prevent AMOS/L from changing the ; MOVE SR,D1 to a MOVE CCR,D1. PRVVIO: CLR D1 ; fake psw as a 0 if in user mode ADD #2,2(SP) ; bypass offending opcode RTE NOTDEF: TYPECR COMERR: ANDB #^C, D1 ; reset Z bit for errors BR INITXT ; process possible break commands ; At entry, A3 indexs the hardware, A6 indexs COMSET block ; A4 indexs the local table entry for the port ; At exit, D7 contains flag words which will be used by PROREV routine! PROBRK: MOVB A.SPIN(A4), D4 ; get current pin status ANDB #^C,D4 ; mask out break pin MOVW CS.FLA(A6), D7 ; get flags word ; handle break requests/clears BTST #CS%BRK, D7 ; break handling required? BEQ 10$ ; no-don't even look at break switch BTST #CS%BON, D7 ; user requests breaking? BEQ 10$ ; no-clear the break ORB #SCCBRK, D4 ; set break flag 10$: ORB #ASPCL, D2 ; set special conditions command MOVB D4,A.SPIN(A4) ; store break status MOVB #TOGCON, D5 ; setpin subcommand CALL ISSUE3 RTN ; process request for interrupt on pin changes. ; At entry, A3 indexs the hardware, A6 indexs COMSET block ; A4 indexs the local table entry for the port PROINT: CLR D4 ; preset for no status i-rupts MOV CS.STS(A6), D7 ; get status bits BEQ 40$ ; user does not want status BTST #RS%DCD, D7 ; does user want DCD status? BEQ 20$ ; no ORB #1_IE%CTS, D4 ; yes-SCC name is CTS 20$: BTST #RS%CTS, D7 ; does user want CTS status? BEQ 30$ ; no ORB #1_IE%DCD, D4 ; yes-SCC name is DCD 30$: MOVB D4, A.IMSK(A4) ; store interrupt mask BEQ 40$ ; no interrupts required CALL ARMSPL ; arm special interrupts 40$: RTN ; process possible reverse flow control request ; At entry, A3 indexs the hardware ; D7 word contains options flags PROREV: CLR D4 ; preclear options byte ORB #ASPCL, D2 ; set special control command MOVB #IDCHRD, D5 ; reverse flow control subcommand BTST #CS%RRTS, D7 ; user requests reverse flow control? BEQ 10$ ; no IF NE,OPTION&2 IFT ASMMSG "Input Flow control on DB-25 pin 6, DB-9 pin 9" ORB #SCCRTS, D4 ; reverse flow on RS%DTR output IFF ASMMSG "Input Flow control on DB-25 pin 5, DB-9 pin 5" ORB #SCCDTR, D4 ; reverse flow on RS%RTS output ENDC 10$: CALL ISSUE3 RTN ; SETCHN resets and then configures the channel for baud, stops, data bits. ; At entry, A3 indexs the hardware, A6 indexs COMSET block ; A4 indexs the local table entry for the port SETCHN: ; create AIR1 byte MOVW CS.DAT(A6), D3 ; get data bits ANDW #7, D3 ; mask to those defined LEA A0, DBTBL ; index small xlate table MOVB 0(A0)[~D3], D3 ; get the right bits to bits 5-4 for now MOVW CS.STP(A6), D5 ; get stop bits arg ANDB #3, D5 ; mask to defined bits ORB D5, D3 ; add in the stop bits ADDB #1, D3 ; adjust to Adit's base of 0 ROLB D3, #2 ; move data to 7-6, stop to 3-2 MOVW CS.FLA(A6), D5 ; get parity bits ANDB #CS$PAR!CS$ODD, D5 ; mask to defined bits ORB D5, D3 ; fold in parity bits BCHG #CS%ODD, D3 ; reverse sense of odd/even flag MOVW CS.BAU(A6), D6 ; D6 gets system baud code LEA A0, BTABLE-2 ; index baud rate table -4 20$: ADDW #2, A0 ; pre-increment MOVB (A0)+, D7 ; compare to possible BMI 40$ ; end of list CMPB D6, D7 ; match ? BNE 20$ ; no-try next 25$: MOVW D6, T.BAU(A5) ; yes-set new rate in TCB 30$: SVLOK ORB #ARSET, D2 ; form io channel reset command SVLOK CALL ISSUE1 ; issue cmd w/ no args SVUNLK ORB #ARECN, D2 ; form reconfigure command MOVB (A0)+, D4 ; set AIR2 value MOVB (A0)+, D5 ; set AIR3 value CALL ISSUE3 ; issue cmd w/args SVUNLK LCC D1 ; Z will be set if port inited ok RTN ; come here on unsupported baud rate 40$: PUSH A6 TYPECR SLEEP #5000. POP A6 AND #^C,D1 ; clear Z bit in D1 LEA A0,DFABAU ; index default baud entry (9600) MOVB (A0)+,D6 ; pick up T.BAU code BR 25$ ; and finish port init ; set up permanent extended command pointer for output dma ops, and set up ; initial request for input interrupts ; At entry, A3 indexs the hardware ; A4 indexs the local table entry for the port SETEXT: MOVB #SETECB, A.CMD(A4) ; set extended command byte MOV #A.BUFF, D7 ADD A4, D7 ; D7 gets address of buffer MOVW D7, A.DMA(A4) ; set DMA buffer address for low 16 SWAP D7 MOVB D7, A.ADHI(A4) ; set high byte of 24 bit address MOV A4, D7 ADD #A.CMD, D7 ; D7 indexs extended command byte MOVB D7, D3 ; AIR1 gets LSB LSR D7, #8. MOVB D7, D4 ; AIR2 gets middle LSR D7, #8. MOVB D7, D5 ; AIR3 gets MSB ORB #AEXT, D2 SVLOK CALL ISSUE3 ORB #AISDA, D2 ; form i-rupt on data in cmd CALL ISSUE1 ; issue cmd w/o args SVUNLK RTN ; This routine returns pin status for COMRST monitor call ; This routine is always called in supervisor mode. GETPIN: SAVE D2-D5, A3 CALL IDXADT ; A3 gets board address. ANDB #17, D2 ; mask D2 channel to 0-15. ORB #ASTAT, D2 ; special conditions command SSTS D5 ; get status ORISR #23400 ; insure cpu is locked CALL ISSUE1 ; issue the command MOVB AIR1(A3), D2 MOVB AIR2(A3), D3 MOVB AIR3(A3), D4 ; pick up status bytes LSTS D5 ; restore prior ps ; interpret the bits ; due to difference in ADIT terminology, ADIT's CD is RS-232's CTS, and ; ADIT's signal named CTS serves as RS-232 DCD. CLR D6 BTST #ST%CD, D2 ; is SCC DCD (RS%CTS) active? BEQ 10$ ; no BSET #RS%CTS, D6 ; yes-say CTS is active 10$: BTST #ZL%CTS, D3 ; is SCC CTS (RS%DCD) active? BEQ 20$ ; no BSET #RS%DCD, D6 ; yes-DCD is active. 20$: MOV ALLPIN, D7 ; D7 gets bit mask off all RS$xxx pins REST D2-D5, A3 RTN ; SETPIN intreprets the COMWST monitor calls pinmap, and sets the ; available pins. ; This routine is always called in supervisor mode. SETPIN: SAVE D2-D5, A3,A4 CALL IDXADT ; A3 gets board address. ; D2 gets FULL channel # CALL IDXTBL ; index A4 to IDV table entry ANDB #17, D2 ; mask D2 channel to 0-15. MOVB A.SPIN(A4),D4 ; get current pin status ANDB #^C,D4 ; toss output pin bits BTST #RS%RTS, D0 ; set RS%RTS output pin? BEQ 10$ ; no ORB #SCCDTR, D4 ; set SCC flag 10$: BTST #RS%DTR, D0 ; set DTR? BEQ 20$ ; no ORB #SCCRTS, D4 ; set SCC flag 20$: MOV #TOGCON, D5 ; AIR3 gets toggle control sub command ORB #ASPCL, D2 ; special conditions command MOVB D4, A.SPIN(A4) ; save pin status SSTS D3 ; save ps word ORISR #23400 ; do an SVLOK CALL ISSUE3 ; issue the command LSTS D3 ; restore prior ps REST D2-D5, A3,A4 RTN ; This command arms special status interrupts on input pin changes. ; This routine is called by INIT to arm ; and by interrupt processor to re-arm pin drop interrupts. ARMSPL: ORB #ASPCL, D2 ; form command MOVB #INTCON, D5 ; form subcommand CALL ISSUE3 ; issue interrupt subcommand RTN ; INIZ80 - init each ADIT board as TCBs are defined. Once a board has ; been inited, do NOT init it for other channels. ; At entry A0 indexs the flag that indicates if this has already happened. ; D5 contains the interrupt offset value from interrupt 0 INIZ80: TSTB @A0 ; test for board already inited. BNE 20$ ; already inited. ; init interrupt vector and ADIT SETB (A0)+ ; flag we have inited this board PUSH A6 MOVW #^H100+<4.*7.>, A6 ; get address of interrupt vector 0 SUB D5, A6 ; subtract ILVL * 4 MOV A0, @A6 ; install interrupt vector POP A6 SVLOK PUSHB D2 ; save channel # MOVB #AFRSET, D2 ; issue full board reset command CALL ISSUE1 ; reset the whole board POPB D2 ; rest channel # SVUNLK ; init output pin status bits so ports will assert both outputs when used. SAVE A4,D2 ANDW #^C<16.-1>, D2 ; mask port number to 1st port of board CALL IDXTBL ; index A4 to that port's entries MOV #16.-1, D7 ; init 16 ports via DBF 10$: MOVB #SCCRTS!SCCDTR, A.SPIN(A4) ; preset both pins on, no break ADD #A.SIZ, A4 ; next port's base address DBF D7, 10$ ; loop till whole board's ports done. ; insert entry into MONTST reset chain to shut down all ADITS on MONTST LEA A4,RESLNK ; index reset link block MOV MTSRES,@A4 ; store link to rest of chain MOV A4,MTSRES ; insert this entry at head REST A4, D2 ; restore what we used 20$: RTN RESLNK: LWORD 0 ; link to rest of MONTST chain ; MONTST calls this routine prior to loading new monitor for warm boot. SAVE A0,A3, D0,D2 ; save what we use LEA A0,CBITBL ; index table of boards MOV #-1, D0 ; get # of boards less one for DBF 10$: MOVW @A0,A3 ; get sign ext board address MOVB #AFRSET, D2 ; issue full board reset command CALL ISSUE1 ; reset the whole board ADDW #CBITBL,A0 ; advance to next entry DBF D0,10$ ; loop till all boards reset REST A0,A3,D0,D2 ; restore regs RTN ; This routine indexs A3 to the ADIT's base port and places the board port # ; in D2. IDXADT: MOV T.IHW(A5), A3 ;get board base address MOV T.IHM(A5), D2 ;get channel number RTN ; This routine indexs A4 to the IDV's port table entry (based on port in D2) IDXTBL: LEA A4, ADTBL MOV D2, D7 ; D7 gets full channel # LSL D7, #7. ; D7 gets offset to port's entry ADD D7, A4 ; A4 now indexs the port entry RTN ; ISSUEx give commands to the ADIT thru AIR1-AIR3 and AIC ADIT regs ; Before issueing a command, it waits for semphore clear. ; argument bytes in D3-D5 are passed to the ADIT first (ISSUE3 only); ; then the command byte (generally with channel #) is written to the ADIT. ; Before exit, it waits for a semaphore clear state to ; insure AIR regs are valid. ; At exit, it clears the command bits from D2., leaving the channel # in D2 ISSUE1: WAITBZY ; wait for all clear BCALL ISSCMD RTN ISSUE3: WAITBZY MOVB D3, AIR1(A3) ; load parms for command 1st MOVB D4, AIR2(A3) MOVB D5, AIR3(A3) BCALL ISSCMD ; issue command & wait for return RTN ISSCMD: MOVB D2, AIC(A3) ; issue it ANDB #^H0F, D2 ; clear D2 to just channel bits WAITBZY ; wait for completion RTN ; general interrupt processor ; At entry, D0-D7, A2-A6 have been SAVEd (see BOARD macro) ; A3 indexs base port of interrupting board. ; D7 contains lowest port on the board (e.g. 0.,16.,32., etc.) INTCOM: CLR D0 MOVB AIACK(A3), D0 ; acknowledge int, get chan/cmnd MOV D0, D2 ANDB #^H00F, D2 ; D2 = channel number mod 16. ANDB #^H0F0, D0 ; D0 = original command ; find TCB entry for this channel LEA A4, ADTBL ADD D2, D7 ; D7 gets full channel # ASL D7, #7. ; D7 gets offset to port's entry ADD D7, A4 ; A4 now indexs the port entry MOV A.TDEF(A4), D7 ; get TCB ptr & set flags BEQ SHUTDN ; no TCB defined - shut it down MOV D7, A5 ; A5 gets TCB address ; do directed jump to function that completes the interrupt MOV D0, D6 LSRW D6, #3. ; create offset of command x 2 MOVW DISTBL[~D6], D6 ; get offset CALL DISTBL[~D6] REST D0-D7, A2-A6 ; restore regs we used RTE ; back to whatever we interrupted ; an undefined channel has interrupted, probably related to MONTST use. ; shut down the channel & treat it as a spurious interrupt SHUTDN: ANDB #^H00F, D2 ; mask to channel only ORB #ARSET, D2 ; make it channel reset CALL ISSUE1 ; shut down the port ; drop thru to SPUR to note spurious interrupts ; spurious interrupt - an interrupt without a cause. ; Bump a count and toss it SPUR: ORB D2, D0 ; combine bits LEA A6, SPUCNT ; index spurious count INC @A6 ; bump spurious count RTN DEFINE OFFIT X=WORD X-DISTBL DISTBL: ; DISPATCH table for interrupts OFFIT SPUR ; 00 STATUS OFFIT SPUR ; 10 ARSET OFFIT SPUR ; 20 AERSET OFFIT SPUR ; 30 ARECN OFFIT IOINP ; 40 ASDI OFFIT IOINP ; 50 AISDA OFFIT SPUR ; 60 ASDO OFFIT IOTDMA ; 70 AISDOB OFFIT SPUR ; 80 AEXT OFFIT IOTDMA ; 90 AEXTI OFFIT SPUR ; A0 ---- OFFIT IOSTS ; B0 ASPCL OFFIT SPUR ; Cx VARIED OFFIT SPUR ; Dx VARIED OFFIT SPUR ; Ex VARIED OFFIT SPUR ; Fx SPURIOUS ; process input interrupts ; At entry, D2 contains interrupt command/channel byte. ; We will pick up all the bytes that are available for this port for maximum ; efficiency. IOINP: MOVB #40.,A.RCNT(A4) ; set max receive count 10$: ORB #ASDI, D2 ; pick up the data CALL ISSUE1 ; issue the command & wait for data MOVB AIR2(A3), D1 ; get data byte MOV T.INC(A5), D7 ; is there an alternate input routine? BEQ 30$ ; no, use TRMICP MOV D7, A6 ; yes, transfer address to address reg CLR D6 MOVB AIR1(A3), D6 ; get ADIT status byte LSRB D6, #5 ; shift & mask bits BEQ 20$ ; no UART errors MOVB ISTBL[~D6], D6 ; translate to alpha's standard format ; before calling interrupt routine, clear latched error flags in ADIT ORB #AERSET, D2 CALL ISSUE1 ; clear UART error flag latch ; D6 has character error status for routine. 20$: CALL @A6 ; call the alternate routine BR 40$ ; continue with check for more data 30$: SAVE D2, A3 ; save em TRMICP ; give data to system REST D2, A3 ; restore em 40$: TSTB A.RFLG(A4) ; receiver interrupts still on? BNE 50$ ; no, end interrupt DECB A.RCNT(A4) ; count down BEQ 45$ ; limit receive bytes BTST #ST%IN, AIR1(A3) ; get new status byte BNE 10$ ; yes-get next byte now 45$: ORB #AISDA, D2 ; no more input, re-arm interrupts CALL ISSUE1 ; issue command 50$: RTN ; This table translates the input character status bits into the standard ; alpha micro status bits for overrun, parity, and break. ISTBL: BYTE 0.,8.,4.,12.,2.,10.,6.,14. ; routine to process status change interrupt events if user has elected ; to install his routine at T.EXC(A5) for the TCB in question ; These special interrupts will occur on each change of pin 4 & 20, so this ; routine filters out those changes port is not flagged to use. IOSTS: MOV T.EXC(A5), D7 ; does port have routine? BEQ 100$ ; no-done MOV D7, A6 ; change regs ; see if port is set up to monitor these changes MOVB A.IMSK(A4), D7 ; get port's hot bits ; see if the port wants to know about this particular kind of interrupt ORB #ASTAT, D2 CALL ISSUE1 ; send status command MOVB AIR1(A3), D3 MOVB AIR2(A3), D4 ; construct standard (ala RS%xx) status lword in D6 ; and internal format mask-check byte in D1. CLR D1 CLR D6 ; preclear BTST #ST%CD, D3 ; test ADIT DCD (which is CTS, really) BEQ 20$ ; no DCD BSET #RS%CTS, D6 ; flag CTS present ORB #1_IE%DCD, D1 ; set bytewise 20$: BTST #ZL%CTS, D4 ; check for CTS BEQ 40$ ; not active BSET #RS%DCD, D6 ; flag DCD present ORB #1_IE%CTS, D1 ; set bytewise bit 40$: MOVB A.STS(A4), D5 ; get old status XORB D1, D5 ; D1 gets bits that changed BEQ 50$ ; nothing changed... MOVB D1, A.STS(A4) ; save new status ANDB A.IMSK(A4), D5 ; does it concern user? BEQ 50$ ; no MOV ALLPIN, D7 ; D7 gets bit mask off all RS$xxx pins CALL @A6 ; yes-D6 is now masked to what user ; wants to see! 50$: TSTB A.IMSK(A4) ; are we after an interrupt? BEQ 100$ ; no, so don't re-arm interrupt CALL ARMSPL ; re-arm interrupt if enabled 100$: RTN ; ; process dma out completion interrupts IOTDMA: LEA A2, A.BUFF(A4) ; index output buffer PUSHB D2 ; save channel & command byte CLR D2 ; D2 will count output bytes SAVE A2-A4 10$: MOV T.OTC(A5), D7 ; is there an alternate output routine BEQ 20$ ; no use TRMOCP MOV D7, A6 ; yes, transfer address to address reg CALL @A6 ; call the alternate routine BR 30$ 20$: TRMOCP ; get data byte (trashes A4 for sure) 30$: TST D1 ; check for no more data BMI 40$ ; no (more) output MOVB D1, (A2)+ ; move to DMA buffer in ADTBL INC D2 CMPB D2, #OBFSIZ ; room for more? BLO 10$ ; yes 40$: REST A2-A4 MOVW D2, A.CNT(A4) ; no, or end, so save count POPB D2 ; restore channel bits TSTW A.CNT(A4) ; anything to output ? BEQ OIPLOW ; no-clear OIP bit ; do extended DMA output, even for single char output. MOV A2,D7 ; get buffer base address MOVW D7, A.DMA(A4) ; yes set low 16 bits SWAP D7 ; swap 16 bit words MOVB D7, A.ADHI(A4) ; set high 8 bits MOVB #OUTWBC, A.CMD(A4) ; set extended command in ecb ANDB #^H0F, D2 ORB #AEXTI, D2 ; form extended out command CALL ISSUE1 RTN ; do not clear OIP in status til all ; data has been output. ; come here when all output is complete. OIPLOW: BCLR #7, @A5 ; clear OIP in status word RTN ; done till CHROUT executes... ; This table contains the extended DMA command and data buffers for each ; channel and the TCB address of each defined channel. Each board defined ; requires 16.*128. bytes, even if all ports are not defined. ; The board entries are mapped in the same order as the CBITBL. Entry points ; are calculated by the board offset in each interrupt header (DEFINE CBITBL) ; and by the port number stored in T.IHM(A5). At interrupt level, the ADIT ; card itself defines the port number mod 16. ADTBL: BLKB TOTBUF*128. DEFINE BBITS RATE, AIR2, AIR3 BYTE RATE, AIR2, AIR3 ENDM ; This table defines the standard system baud rates supported by ADIT. ; the numbers in this table are obtained from x= (153600/baud'rate)-2 ; AIR3 gets the MS byte, AIR2 gets the LS byte. BTABLE: BBITS 21, 002, 0!ONBOTH ; 38400 BBITS 20, 006, 0!ONBOTH ; 19200 DFABAU: BBITS 17, 016, 0!ONBOTH ; 9600 BBITS 16, 023, 0!ONBOTH ; 7200 (off by 1.5%) BBITS 15, 036, 0!ONBOTH ; 4800 BBITS 14, 051, 0!ONBOTH ; 3600 (off by 0.8%) BBITS 13, 076, 0!ONBOTH ; 2400 BBITS 12, 113, 0!ONBOTH ; 2000 (off by 0.3%) BBITS 11, 123, 0!ONBOTH ; 1800 (off by 0.4%) BBITS 10, 176, 0!ONBOTH ; 1200 BBITS 07, 376, 0!ONBOTH ; 600 BBITS 06, 376, 1!ONBOTH ; 300 BBITS 05, 376, 2!ONBOTH ; 200 BBITS 04, 376, 3!ONBOTH ; 150 BBITS 03, 164, 4!ONBOTH ; 134.5 baud BBITS 02, 162, 5!ONBOTH ; 110 (off by .02%) BBITS 01, 376, 7!ONBOTH ; 75 BBITS 00, 376, 13!ONBOTH ; 50 BYTE -1 ; 8530 (and ADIT) bit settings are not sequential,they are 5,7,6,8 bits ; since we have to rotate them anyway, this table also shifts the bits to ; their final destination for the reconfigure channel command. DBTBL: BYTE 0._4., 2._4., 1._4., 3._4. EVEN ; This is the available input/output pin mask. We use the standard Alpha Micro ; pin numbers even though the adit uses different pins on the RS-232 interfaces. ALLPIN: LWORD <1_RS%DCD>!<1_RS%CTS>!<1_RS%DTR>!<1_RS%RTS> END .