home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
OS/2 Shareware BBS: 10 Tools
/
10-Tools.zip
/
ddkx86v5.zip
/
DDKX86
/
SRC
/
DEV
/
ATCOM
/
ATINTRPT.ASM
< prev
next >
Wrap
Assembly Source File
|
1995-04-14
|
69KB
|
1,995 lines
;*DDK*************************************************************************/
;
; COPYRIGHT (C) Microsoft Corporation, 1989
; COPYRIGHT Copyright (C) 1995 IBM Corporation
;
; The following IBM OS/2 WARP source code is provided to you solely for
; the purpose of assisting you in your development of OS/2 WARP device
; drivers. You may use this code in accordance with the IBM License
; Agreement provided in the IBM Device Driver Source Kit for OS/2. This
; Copyright statement may not be removed.;
;*****************************************************************************/
; SCCSID = @(#)atintrpt.asm 6.12 92/03/03
; ***************************************************************************
; *
; *
; *
; ***************************************************************************
;********************** START OF SPECIFICATIONS ********************
;*
;* SOURCE FILE NAME: ATINTRPT.ASM
;*
;* DESCRIPTIVE NAME: CBIOS Async Driver Interrupt Handler module
;*
;* STATUS: RELEASE 1 LEVEL 2
;*
;* FUNCTION: This module contains interrupt service routines for up
;* to 3 Async Communications devices on up to 2 interrupt levels.
;* Interrupts are serviced through the interrupt entry point,
;* using the Operating System Transfer convention via DevHlp Mgr.
;*
;* Specific subroutines service the following types of 16550 UART
;* interrupts (listed in order of high to low priority):
;* - modem status interrupt
;* - receive data available interrupt
;* - transmit hardware empty interrupt
;*
;* The module also contains Timer Tick handler routines to service
;* the COM ports' Read and Write Timeout processing requirements.
;*
;* NOTES:
;* DEPENDENCIES: ABIOS MUST BE ABSENT
;* PATCH LABEL: 0
;*
;* ENTRY POINTS: ComInt1, ComInt2, Ticker
;*
;* INTERNAL REFERENCES:
;* ProcRun - run a blocked thread
;* LinkRP - add the request packet to the end of the request queue
;* UnLinkHeadRP - pull the next available request from a request queue
;* ReadQueue - move data from our Recieve Queue to user's Read buffer
;* WriteQueue - move data from user's Write buffer to our Transmit Queue
;* StartNextWRP - pull the next Write request packet and make it current
;* CheckTX - enable or disable transmit interrupts as required
;* TxFlowDetect - scan Receive Queue for XON/XOFF chars & act accordingly
;* DisableRemoteTX - disable the remote transmitter
;*
;* EXTERNAL REFERENCES:
;* DevHlp_ABIOSCall - call the ABIOS Interrupt Entry Point with:
;* Modem Status Request Block
;* Combined Receive/Transmit Request Block
;* Default Interrupt Handler Request Block
;* DevHlp_EOI - signal End of Interrupt
;*
;*********************** END OF SPECIFICATIONS **********************
; SCCSID = @(#)atintrpt.asm 6.12 92/03/03
PAGE 80,132
.286p
TITLE com01.sys - Asynchronous Communication Device Driver
NAME com01
; Bryan Diehl
; David Gilman
;*** atintrpt.asm - Interrupt Handlers
;
; ComInt - Interrupt entry point
; LxInt - Line status error interrupt (processed in RxInt)
; RxInt - Receive data interrupt
; TxInt - Transmitter empty interrupt
; MxInt - Modem status interrupt
; Ticker - Main Timer tick handler for timeout processing
; WriteTick - Write timeout processing
; ReadTick - Read timeout processing
;
; Modification History
;
; BD 01/18/87 Re-written to conform to MS standard for
; style, clarity and efficiency.
; New design for read and write.
; Uses timer tick for timeout processing.
;
; BD 04/09/87 Restructure main interrupt so multiple
; nested interrupts are not generated.
; A single nested interrupt is ok.
; JGT 05/10/88 Fix TERI event detection in MxInt (per MS)
; YN 05/25/89 MVDM Support - @VDM
; ACW 04/16/91 @PVW Added perfview counters/timers
; JAG 09/14/93 @67790 Rockwell chipset based PCMCIA modems fail
; RAC 12/16/93 76699 Make Perfview optionally assembled
; RDW 03/14/94 80677 VDM not getting RI or TERI Signals correctly
; WDM 04/21/94 82548 - pvwxport.inc now included in atcom.inc
; JAG 12/01/94 101711- SLIP and 16450s not working see bugbug code
;
.xlist
include devhlp.inc
include devsym.inc
include basemaca.inc
include realmac.inc
include osmaca.inc
include error.inc
include protmode.inc
include atcom.inc
include ateisa.inc
include iodelay.inc
include devhlpP.inc ; 76711
.list
;;; new macro for doing EOIs Replaced by new DevEOI Removed By 76711
;; Removed By 76711
;;DevEOI MACRO ByteIRQ Removed By 76711
;; local eoi1, eoi2 Removed By 76711
;; push ax Removed By 76711
;; pushf Removed By 76711
;; mov al,ByteIRQ Removed By 76711
;; shr al,4 Removed By 76711
;; mov al,20h Removed By 76711
;; jnz eoi2 Removed By 76711
;; cli Removed By 76711
;; jnc eoi1 Removed By 76711
;; out 0a0h,al Removed By 76711
;;eoi1: out 020h,al Removed By 76711
;;eoi2: popf Removed By 76711
;; pop ax Removed By 76711
;; ENDM Removed By 76711
EXTRN Com1:WORD
EXTRN Com2:WORD
EXTRN Com3:WORD
EXTRN Com4:WORD
EXTRN GAS_Switch:WORD
EXTRN DevHlp:DWORD
EXTRN Flags:BYTE
EXTRN Ready:WORD
extrn CheckTX:near
extrn ProcRun:near
extrn ReadQueue:near
extrn ReadQueueByte:near
extrn SetAlert:near
extrn StartNextWRP:near
extrn UnLinkHeadRP:near
extrn WriteQueue:near
extrn WriteQueueByte:near
EXTRN VCOMAddress:FAR
EXTRN ShrdIRQ1:BYTE
EXTRN ShrdIRQ2:BYTE
EXTRN ShrdIRQ3:BYTE
EXTRN ShrdIRQ4:BYTE
DSEG SEGMENT
; interrupt service table based on interrupt id register
; MxInt is called directly from ComIntx, never through SrvTbl
; LxInt is called directly from RxInt, never through SrvTbl
SrvTab LABEL WORD
DW OFFSET CSEG:BadInt ; invalid interrupt value
DW OFFSET CSEG:TxInt ; Tx holding reg. empty interrupt
DW OFFSET CSEG:RxInt ; Rx data available interrupt
DW OFFSET CSEG:BadInt ; invalid interrupt value
.errnz II_MX
.errnz II_TX-2
.errnz II_RX-4
.errnz II_LX-6
bad_int DW 0
IntID DB 0
DSEG ENDS
CSEG SEGMENT
;********************** START OF SPECIFICATIONS ********************
;*
;* SUBROUTINE NAME: ComInt1 / ComInt2
;*
;* DESCRIPTIVE NAME: Interrupt Handlers for COM1 and COM2
;*
;*
;* FUNCTION:
;* The interrupts are prioritized in the following order:
;* 1. line status interrupt
;* 2. read data available interrupt
;* 3. transmit buffer empty interrupt
;* 4. modem service interrupt
;*
;* This routine continues to service until all interrupts from the
;* 16450 serial controler have been satisfied.
;* This is required because in a edge triggered environment all
;* interrupting conditions must be cleared before returning from the
;* interrupt. Otherwise, no more interrupts would ever be generated.
;*
;* On entry, the 'Data Moved' flag is cleared. This is set when
;* data is moved in TxInt or at the end of ComInt. If this flag
;* is set, we delay moving receive data until the next interrupt.
;* This avoids doing two PhysToVirts on one interrupt.
;*
;* When a request is completed, the request is put on the 'Ready'
;* list. It doesn't get ProcRun'ed until after the EOI.
;* This is to minimize our interrupt path length before the EOI.
;*
;* NOTE interrupt handlers do NOT need to save registers
;*
;* ENTRY ds = device driver data segment (set up by kernel)
;* interrupts disabled
;*
;* EXIT none
;*
;* USES none
;*
;* INTERNAL REFERENCES:
;* ProcRun - run a blocked thread
;* LinkRP - add the request packet to the end of the request queue
;* UnLinkHeadRP - pull the next available request from a request queue
;* ReadQueue - move data from our Recieve Queue to user's Read buffer
;* WriteQueue - move data from user's Write buffer to our Transmit Queue
;* StartNextWRP - pull the next Write request packet and make it current
;* CheckTX - enable or disable transmit interrupts as required
;* TxFlowDetect - scan Receive Queue for XON/XOFF chars & act accordingly
;* DisableRemoteTX - disable the remote transmitter
;*
;* EXTERNAL REFERENCES:
;* DevHlp_ABIOSCall - call the ABIOS Interrupt Entry Point with:
;* Modem Status Request Block
;* Combined Receive/Transmit Request Block
;* Default Interrupt Handler Request Block
;* DevHlp_EOI - signal End of Interrupt
;*
;*********************** END OF SPECIFICATIONS **********************
Procedure ComInt,FAR
ASSUME cs:CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
cint5: or si,si
ljz cint000 ; ComInfo pointer is null
test [si].ci_int_sharing,INT_SHARING ; Int. sharing supported?
jz cint6 ; N: continue on
mov dx,[si].ci_port ; Y: read the port
add dx,R_INTID ; point to interrupt ID reg.
in al,dx ; (al) = interrupt id
mov IntID, al ; Save Interupt ID
test al,II_NONE ; any interrupts pending?
jz cint6 ; Y: process the int.
stc ; N: indicate not our int.
ret ; and return to int. mgr.
cint6:
SaveReg <si> ; save si on stack frame
mov bp,sp ; (bp) -> stack frame
; [bp]-2 -> si
inc [si].ci_depth ; inc nested interrupt counter
; cannot do a check until the depth flag has been inc'ed or
; ComError will jump to the exit point on an error!
ChkComInfoPtr ; saves flags
; zero flag still set from inc above
.errnz D_BAD
ljz cint0 ; too many nested interrpts
cmp [si].ci_nopens,0 ; make sure port is open
lje cint00 ; port not open yet, disable chip and EOI
cint10: ChkComInfoPtr
cli ; make sure interrupts are disabled
; In order to correctly handle the 'Input Sensitivity to DSR' we have to
; process Modem Status interrupts before Receive interrupts. This allows
; us to handle this mode correctly when DSR changes and we recieve data.
mov dx,[si].ci_port
add dx,R_MODMS ; (dx) -> modem status reg
in al,dx ; (al) = modem status
test al,MS_DCTS OR MS_DDSR OR MS_TERI OR MS_DDCD
jz cint20 ; no MSR changes (interrupt)
call MxInt ; process modem status interrupt
cint20:
; BUGBUG - START OF TO RE-ENABLE TX INTERRUPT
; if TX interrupt is enabled, then disable and re-enable
; to force TX interrupt
; Workaround for a hardware in the 16450 and 16550 chips:
; TX interrupt pending (and highest priority)
; start reading IIR (interrupt identification register)
; reading IIR for TX interrupt clears the TX interrupt
; RX data comes in while still in read cycle
; IIR changes to RX interrupt
; we process the RX interrupt properly, but will never
; get another TX interrupt because it has been cleared.
mov dx,[si].ci_port
add dx,R_INTEN ; (dx) -> interrupt enable reg
in al,dx ; (al) = interrupt enable
test al,IE_TX
jz cint25 ; TX interrupts not enabled
; NOTE: If we're sharing this interrupt line, then we ALWAYS
; want to turn the TX int. on at the chip, to cover up for
; the fact that on entry, we read the Interrupt ID register,
; which cleared any pending TX int. Turning the TX int. back
; on at the chip will restore the correct status of the Interrupt
; ID register.
; test [si].ci_int_sharing,INT_SHARING ; Int. sharing supported?
; jnz cint24 ; Y: ALWAYS re-enable TX int.
; NOTE: don't move this test above the "mov dx," above!
;--- test [si].ci_flagx,FX_16450 ; Western Digital 16550AF ?
;--- jz cint25 ; 8250 or 16550A
; PCMCIA modems don't have this and don't like the fix
; so lets just skip the hack.
test [si].ci_flagx1,FX1_PCMCIA_MODEM ; Is this a PCMCIA modem?
jz cint24 ; N: Do Re-enable
test [si].ci_int_sharing,INT_SHARING; Int. sharing supported?
jz cint25 ; N: go read IIR - haven't read
mov al,IntID ; We read it once already
jmp short cint26 ; Go ISR
cint24:
and al,NOT IE_TX ; disable TX interrupts first
out dx,al
push ax
DevIODelay ax
pop ax
or al,IE_TX ; re-enable TX interrupts
out dx,al
; BUGBUG - END OF TO RE-ENABLE TX INTERRUPT
cint25: add dx,R_INTID-R_INTEN ; (dx) -> interrupt id reg
in al,dx ; (al) = interrupt id
cint26: test al,II_NONE
jnz cint30 ; no interrupts need servicing
mov bl,al ; (bl) = interrupt id
and bx,II_MASK ; (bx) = index into int service table
.errnz II_MX
; cmp bl,II_MX
je cint10 ; MX, process above
call SrvTab[bx] ; service the Interrupt..
sti ; allow higher priority interrupts
; this CANNOT cause a nested interrupt
; because we haven't done an EOI yet
jmp SHORT cint10 ; until all interrupts serviced
;* cint30 - done servicing the actual interrupt(s)
; check for Read request completion or data movement
;
cint30:
; see if the current read request can be completed.
cmp [si].ci_r_rp._hi,0
lje cint60 ; no current read request
mov cx,[si].ci_qin.ioq_count; (cx) = number of bytes in queue
cmp cx,[si].ci_r_to_move
jae cint35 ; enough to complete request
mov al,[si].ci_dcb_flags3
and al,F3_READ_TO_MASK ; (al) = read timeout mode
; BUGBUG - no wait mode
; 'no wait' mode can get here if there were queued read requests
; and then 'no wait' mode was set.
; Each queued request will remain blocked until the first interrupt
; of any type (rx, tx, mx).
; We could complete the current read request and flush all other read
; requests when 'no wait' mode is specified in Set DCB.
cmp al,F3_READ_TO_NW
je cint35 ; no wait mode
cmp al,F3_READ_TO_WFS
jne cint40 ; not wait for something mode
jcxz cint40 ; wait for something mode, but no data
cint35: ; enough to finish request (done, no wait or wait for something)
les di,[si].ci_r_rp ; (es:di) -> request packet
ASSUME es:NOTHING
ChkRPPtr
ChkRPType CMDINPUT
test es:[di].PktStatus,STDON
jnz cint60 ; already marked done
or es:[di].PktStatus,STDON ; mark request done
; (so we don't run it twice)
ProcReady ; put request on 'ready' list
jmp SHORT cint60
; may have enough data to move up to user buffer
; make mark higher for real mode hopeing for it to get moved in prot mode
cint40: cmp cx,RX_MOVE_PROT ; (cx) = # of bytes in qin from above
jb cint60 ; below prot mode mark, don't move
test [si].ci_flagx,FX_DATA_MOVED
jnz cint60 ; data already moved on this interrupt
; set here and in TxInt
cint50: or [si].ci_flagx,FX_DATA_MOVED ; mark data moved
les di,[si].ci_r_rp ; (es:di) -> request packet
ASSUME es:NOTHING
ChkRPPtr
ChkRPType CMDINPUT
; have to move data to user space
sti ; allow interrupts while moving data
mov cx,[si].ci_r_to_move ; set up count
call ReadQueue ; move data to user space
; updates ci_r_to_move
jmp cint10 ; may have more interrupts now
;* cint60 - done servicing the actual interrupt and Read data
; do post-EOI processing only if not a nested interrupt
cint60:
cli ; no interrupts
DevEOI <byte ptr [si].ci_irq>,DevHlp ; Add 76711
cmp [si].ci_depth,D_NEST
je cintnestx ; nested interrupt
; not a nested interrupt, do post processing
cint80:
sti ; Start of allow NESTED INTERRUPTS (after EOI and STI)
and [si].ci_flagx,NOT FX_INT_NESTED ; clear nested flag
; NOTE: a nested interrupt can come in after the sti above and
; before clearing the nested flag; this is OK because we are
; about to do the post-EOI processing anyway. This reduces
; the number of times we go through the post EOI stuff.
; ProcRun requests on the ready list
; this could be done at timer tick time
SaveReg <si>
mov si,OFFSET Ready ; (ds:si) -> Ready list
cint90: call UnLinkHeadRP ; (es:di) -> runnable request packet
jc cint95 ; no more to run
call ProcRun
jmp SHORT cint90 ; try to run another
cint95: RestoreReg <si> ; (ds:si) -> cominfo
ChkComInfoPtr
cli ; no interrupts while we check for nested interrupt
; End of allow NESTED INTERRUPTS
test [si].ci_flagx,FX_INT_NESTED
jnz cint80 ; nested interrupt occured
cint99:
; exiting first level interrupt
and [si].ci_flagx,NOT FX_DATA_MOVED ; clear data moved flag
cintx: mov sp,bp ; restore stack frame
RestoreReg <si> ; (ds:si) -> ComInfo
ChkComInfoPtr
cintxx: dec [si].ci_depth ; dec interrupt depth
.errnz D_BAD
clc ; clear carry to show it was our interrupt
ret
cintnestx:
or [si].ci_flagx,FX_INT_NESTED ; flag nested interrupt occured
jmp SHORT cintx ; done
;* cinterr - exit point for internal error at interrupt time
;
; isuue EOI and return
; Interrupt level has already been released (UnSetIRQ) and
; 16450 interrupt disabled in ShutdownPort,
; but we still need to issue the EOI for this interrupt.
;
; ENTRY (ds) -> DD Data Seg
Entry cinterr,,,nocheck
mov sp,bp ; restore stack frame
pop si ; (ds:si) -> ComInfo
ChkComInfoPtr
DevEOI <byte ptr [si].ci_irq>,DevHlp ; Add 76711
; can't get nested ints because 16450 chip interrupts are disabled
jmp SHORT cintxx
cint0: ComErr <ComInt: too many nested interrupts>
;* cint00 - interrupt during first open or init, disable chip and EOI
cint00: sti
mov dx,[si].ci_port ; (dx) -> port
add dx,R_INTEN ; (dx) -> interrupt enable register
xor ax,ax ; (ax) = 0
out dx,al ; disable interrupts from 16450 chip
DevEOI <byte ptr [si].ci_irq>,DevHlp ; Add 76711
; can't get nested ints because 16450 chip interrupts are disabled
jmp cintx
;* cint000 - interrupt during driver shut down
cint000:
sti
stc ; set carry - not my interrupt
ret ; return carry to interrupt manager which
; will issue EOI for me
EndProc ComInt
;** BadInt - invalid interrupt handler
;
Procedure BadInt,NEAR
ASSUME cs:CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
inc bad_int
cmp bad_int,BAD_MAX
jl finish_badint_proc
;--- Reset IER --------------------------------
mov dx,[si].ci_port
add dx,R_INTEN ; (dx) -> interrupt enable reg
in al,dx ; (al) = interrupt enable
push ax
and al,NOT IE_TX ; disable TX interrupts first
and al,NOT IE_RX ; disable RX interrupts first
and al,NOT IE_MX ; disable MX interrupts first
and al,NOT IE_LX ; disable LX interrupts first
out dx,al
DevIODelay ax
pop ax
out dx,al
;----------------------------------------------
test [si].ci_badmax,IGNORE_ERROR
jz bad_shutdown
finish_badint_proc:
clc ; clear carry to show it was our interrupt
ret
bad_shutdown:
test al, IE_TX
jz try_RX
and al, NOT IE_TX
jmp SHORT fix_it
try_RX:
test al, IE_RX
jz try_LX
and al, NOT IE_RX
jmp SHORT fix_it
try_LX:
test al, IE_LX
jz try_MX
and al, NOT IE_LX
jmp SHORT fix_it
try_MX:
test al, IE_LX
jz fix_it
and al, NOT IE_LX
jmp SHORT fix_it
fix_it:
push ax
DevIODelay ax
pop ax
out dx,ax
cmp bad_int,BAD_MAX+5
jl gods_mercy
ComErr <ComInt : invalid interrupt (presumably LxInt)>
pop ax
gods_mercy:
clc ; clear carry to show it was our interrupt
ret
EndProc BadInt
;** LxInt - line status interrupt (highest priority)
;
; Overrun, parity, framing, or break error.
; Read line status register and save in shadow.
; Mark errors in comerr and event.
;
; ENTRY (ds:si) -> ComInfo
; (dx) -> interrupt id register (R_INTID)
;
; EXIT (al) = LSR error bits only (overrun, parity and frameing)
;
; USES ax dx
Procedure LxInt,NEAR
ASSUME cs:CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
ret
EndProc LxInt
;** RxInt - Rx Data Available Interrupt (second priority)
;
; ENTRY (ds:si) -> ComInfo
; (dx) -> interrupt id register (R_INTID)
;
; EXIT none
;
; USES ax bx cx dx
;
; NOTE Hardware Differences on Overrun Error
;
; 8250 and 16450 (and 16550x in 16450 mode):
; overrun data has over-written valid data in RX HW.
; err char needs to be INSERTED into SW queue BEFORE RX data.
;
; 16550A in FIFO mode:
; overrun data has NOT over-written valid data in RX HW FIFO.
; err char needs to be APPENDED to SW queue AFTER RX data.
;
; Pseudo Code:
;
; oflag = 0 ; overrun shift flag (16 bit)
;
; forever {
; top:
; call LxInt ; read LSR and set error bits
;
; ah = lsrshadow
; lsrshadow &= NOT error bits ; turn off error bits in lsrshadow
;
; if (no RX data available)
; goto done ; no more RX data to process
;
; al = RX data & mask
;
; Note: DSR_OK cannot change through iterations of this loop
; because it changes in MxInt which is a lower priority interrupt.
;
; if (!DSR_OK) ; IN_DSR on AND DSR low
; goto top ; skip this data and errors
;
; if (Overrun Error && Error_Char_Processing) {
; if (FIFO_ON || FIFO_APO)
; oflag |= 8000 ; error AFTER 16th char in FIFO
; else
; oflag |= 0001 ; error BEFORE 1st char in buf
; }
;
; if (Break Interrupt) {
; if (Break_Char_Processing)
; al = break_character
; goto q_data ; go queue the break char
; else
; goto skip_data
; }
;
; if (Parity or Framing Error) {
; if (Error_Char_Processing)
; al = error_character
; goto q_data ; don't check for NULL/XON/XOFF
; }
;
; if (RX == NULL && NULL_stripping)
; goto skip_data
;
; if (OUT_XO) { ; output xoff/xon mode
; if (RX == XOFF)
; hsflag |= XOFF_RECIEVED ; set XOFF received
; else if (RX == XON)
; hsflag &= !XOFF_RECIEVED ; clear XOFF received
; else
; goto q_data ; not xoff/xon, go queue data
;
; call CheckTX ; decide if we can TX now
; goto skip_data ; DON'T queue the xoff/xon char
; }
;
; q_data:
; if (oflag & 1 && FIFO_OFF) {
; oflag &= !1
; call WriteQueueByte(error_character) ; no FIFO, INSERT err char
; }
; call WriteQueueByte(al) ; write data
;
; skip_data:
; oflag >>= 1 ; shift overrun flag
; if (carry)
; call WriteQueueByte(error_character) ; FIFO, APPEND err char
; }
; done:
Procedure RxInt,NEAR
ASSUME cs:CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
mov bad_int,0 ; reset interrupt count
xor cx,cx ; cx = overrun flags (16 bit shifting)
rxi_top:
ChkComInfoPtr
; since LxInt is disabled we must process all line status errors now!
cli ; disable interrupts
ReadLSR ; (al) = LSR
rxi_lxint:
; @VDM change begin
mov [si].ci_vdm_LastLSR,al ; lastLSR = error bits of LSR
test [si].ci_vdm_flag,VDM_Flag_InUse ; if this port is in use by VDM
jz lxi20
; get only the error status bits
cmp [si].ci_qin.ioq_count,QI_SIZE-2 ;@@ is RcvQ full now?
jb no_soft_overrun ;@@ no, so go on
or ax,CE_SW_OVERRUN ;@@ yes, so flag soft overrun
ifdef PERFVIEW
pvw_SW_Overrun ;@PVW increment perfview cntr
endif
no_soft_overrun:
mov bx,[si].ci_qin.ioq_in ; Get the offset of Rcv Head
sub bx,[si].ci_qin.ioq_base ; bx = offset of status
mov [si+bx].ci_qstat,al ; save error LSR for curr char
; @VDM change end
lxi20:
IFDEF LXDEBUG
; test al,LS_OERR OR LS_PERR OR LS_FERR
; jz lxi40 ; no errors
; ComErr <LxInt : line status error (al = lsr)>
lxi40:
ENDIF
test al,LS_BI ; break detect?
jz lxi50 ; not break detect interrupt
or [si].ci_event,EV_BREAK ; show break in event word
.errnz LS_OERR-CE_HW_OVERRUN ; must be the same bits
.errnz LS_PERR-CE_RX_PARITY
.errnz LS_FERR-CE_FRAME
lxi50:
and ax,CE_HW_OVERRUN OR CE_RX_PARITY OR CE_FRAME ; mask error bits
jz rxi05 ; no errors
test ax,CE_HW_OVERRUN
jz lxi51
ifdef PERFVIEW
pvw_HW_Overrun ;@PVW increment perfview cntr
endif
lxi51:
or [si].ci_comerr,ax ; combine error bits with prev. errors
or [si].ci_event,EV_ERR ; show line status error
; use lsrshadow because LxInt read LSR clearing the error bits.
rxi05:
mov ah,[si].ci_lsrshadow ; (ah) = LSR shadow
; clear the line status data ready and error bits in the shadow
and [si].ci_lsrshadow,NOT (LS_DR OR LS_OERR OR LS_PERR OR LS_FERR OR LS_BI)
test ah,LS_DR
; ljz rxix ; no more data available
jnz rxi06 ; no more data available
ret ; save time
rxi06:
mov dx,[si].ci_port
.errnz R_DATA
; add dx,R_DATA ; (dx) -> data I/O Reg.
in al,dx ; (al) = character from HW
and al,[si].ci_cmask ; clear unwanted bits
sti ; enable interrupts
test [si].ci_Flagx1,FX1_FLUSH_RX_IP ;;MF flushing RX queue
ljnz rxix ;;MF yes, drop the data and leave
;* Input Sensitivity to DSR Processing
test [si].ci_flagx,FX_IN_DSR_OK
ljz rxi_top ; DSR is down, ignore all input
; loop back and read all input
test ah,LS_OERR OR LS_PERR OR LS_FERR OR LS_BI
jz rxi40 ; not overrun, parity, framing or break error
;* Overrun Error Processing
test ah,LS_OERR
jz rxi20 ; not overrun error
test [si].ci_dcb_flags2,F2_ERR_CHAR
jz rxi20 ; error character not enabled
mov dx,0001h ; dx = 1; assume NO FIFO
test [si].ci_dcb_flags3,F3_FIFO_HW_ON
jz rxi10 ; FIFO HW not on
mov dx,8000h ; FIFO HW on, error AFTER 16th char
rxi10: or cx,dx ; turn on correct error bit
;* Break Interrupt Processing
rxi20: test ah,LS_BI
jz rxi30 ; not break interrupt
test [si].ci_dcb_flags2,F2_BRK_CHAR
ljz rxi56 ; break character not enabled
mov al,[si].ci_dcb_BrkChar ; al = break char
jmp rxi_q ; go queue break char
;* Parity and Framing Error Processing
rxi30: test ah,LS_PERR OR LS_FERR
jz rxi40 ; not parity or framing error
; parity or framing error
test [si].ci_dcb_flags2,F2_ERR_CHAR
ljz rxi_q ; error replace not active,
; let the character through,
; but DON'T check for NULL/XON/XOFF
mov al,[si].ci_dcb_ErrChar ; al = error char
jmp rxi_q ; go queue the error char
; but DON'T check for NULL/XON/XOFF
;* Valid Character With NO Parity Or Framing Errors
; we have a good character, check it for NULL/XON/XOFF
;* NULL Strip Processing
rxi40: or al,al
jnz rxi45 ; not a null character
test [si].ci_dcb_flags2,F2_NULL_STRIP
ljnz rxi_skip ; strip the null character
;* XON/XOFF Processing
; if output XON/XOFF is enabled and char is XON or XOFF,
; set/clear the XOFF_received flag
; call CheckTx to enable/disable Tx interrupts
; drop the character
rxi45: test [si].ci_vdm_flag,VDM_Flag_InUse ; if this port is in use by VDM
jnz rxi46
test [si].ci_dcb_flags2,F2_OUT_XO
jz rxi_q ; output XON/XOFF not enabled
jmp rxi49
rxi46: pushf
cli
cmp al,XOFFequ ; Is it a XOff character?
jne vdmNextChar_1 ; no, reset state to normal
cmp [si].ci_vdm_Rx_State,3 ; are we already in state 3?
je vdmNextChar ; yes - no work to do
mov [si].ci_vdm_Rx_State,2 ; set rcv state to 2
; (Xoff from device not sent to app)
or [si].ci_Flagx1,FX_XO_FOUND ; show we found a ctrl char
jmp SHORT vdmNextChar ; no, test the next character
vdmNextChar_1:
mov [si].ci_vdm_Rx_State,1 ; set rcv state to normal
mov [si].ci_vdm_Tx_Count,0 ; " " " " "
vdmNextChar:
cmp [si].ci_vdm_Tx_State,3 ; VDM are we in state 3?
jne vdmnextchar1 ; VDM no, do next character stuff
inc [si].ci_vdm_Rx_Count ; VDM inc received char count
cmp [si].ci_vdm_Rx_Count,VDM_Max_Rx_Count ; VDM is it max?
jne vdmnextchar1 ; VDM no, do next character stuff
mov [si].ci_vdm_Rx_Count,0 ; VDM 0 count
mov [si].ci_vdm_Tx_State,1 ; VDM reset to normal state
vdmnextchar1:
test [si].ci_Flagx1,FX_XO_FOUND ; if ctrl char found
jz vdmtxflx ; nope, so exit
call CheckTX ; go and turn tx off
and [si].ci_Flagx1,NOT FX_XO_FOUND ; clear ctrl char found flag
vdmtxflx: ;
popf ; INT restore
jmp SHORT rxi_q
rxi49: cmp al,[si].ci_dcb_XoffChar
jne rxi50 ; not an XOFF, go check XON
or [si].ci_hsflag,HS_XOFF_RECEIVED
jmp SHORT rxi55 ; go call CheckTx
rxi50: cmp al,[si].ci_dcb_XonChar
jne rxi_q ; not an XON
and [si].ci_hsflag,NOT HS_XOFF_RECEIVED ; show XOFF NOT received
rxi55: call CheckTX ; may enable Tx Interrupt
rxi56: jmp SHORT rxi_skip ; skip queueing the xoff/xon
;* Queue Data - check for overrun and queue data
rxi_q:
test cx,1
jz rxi_qq ; no overrun error on this byte
test [si].ci_dcb_flags3,F3_FIFO_HW_ON
jnz rxi_qq ; FIFO HW on, append err char
and cx,NOT 1 ; turn off the error bit
xchg al,ah ; ah = RX data
mov al,[si].ci_dcb_ErrChar ; al = error char
call WriteQueueByte ; queue the error char
xchg al,ah ; al = RX data
; cli
; INT_Notify ;@VDM Macro to see if we need to
; ;@VDM notify the VDM of RX, TX or MS
; ;@VDM interrupts
; sti
rxi_qq:
call WriteQueueByte ; queue the received character
cli
INT_Notify ;@VDM Macro to see if we need to
sti ;@VDM notify the VDM of RX, TX or MS
;@VDM interrupts
rxi_skip:
shr cx,1
jnc rxi_loop ; no overrun error on this byte
mov al,[si].ci_dcb_ErrChar ; al = error char
call WriteQueueByte ; queue the error char
cli
INT_Notify ;@VDM Macro to see if we need to
sti ;@VDM notify the VDM of RX, TX or MS
;@VDM interrupts
rxi_loop:
cli
ReadLSR ; (al) = LSR
test al,LS_DR
jz rxix ; no more data available
jmp rxi_lxint ; loop back to top
rxix:
ret
EndProc RxInt
;** TxInt - Tx Holding Register Empty Interrupt (third priority)
;
; ENTRY (ds:si) -> ComInfo
; dx = interrupt id register port (R_INTID)
;
; EXIT none
;
; USES ax bx cx dx
;
; Pseudo Code:
;
; if (8250 && tx not empty)
; return
;
; count = 1 ; assume only TX 1 char
; if (flags3.TX_16)
; count = 16 ; TX 16 chars
;
; do {
; if (hsflag & (XOFF_pending | XON_pending | TX_immediate_pending)) {
; if (hsflag & XOFF_pending) {
; hsflag &= !XOFF_pending
; hsflag |= XOFF_sent
; al = XOFF_char
; }
; else if (hsflag & XON_pending) {
; hsflag &= !(XON_pending | XOFF_sent)
; al = XON_char
; }
; else if (hsflag & TX_immediate_pending) {
; hsflag &= !TX_immediate_pending
; al = TX_immediate_char
; }
; write (al) to port
; call CheckTX
; if (carry)
; goto done ; no more to TX, done
; goto continue
; }
;
; if (no current request packet)
; internal error
;
; al = ReadQueueByte ; read next byte of data to TX
; if (got data from queue) {
; write (al) to port
; w_to = w_to_start ; reset write timeout
; }
;
; if (w_to_move == 0) { ; no data left from user buffer
; if (qcount == 0) { ; no data in q either
; put request on ready list ; done with req, try next one
; clear current request pointer
; call StartNextWRP ; start next req (calls CheckTX)
; if (carry)
; goto done ; no more req OR cant TX, done
; } else
; goto continue ; data left in queue
; }
; if (qcount <= TX_MOVE_PROT) { ; queue below low water mark
; if (readmode && qcount > TX_MOVE_REAL)
; goto continue
; flag data moved
; call WriteQueue(w_to_move) ; to get the next chunk of data
; }
; continue:
; } while (--count)
; done:
Procedure TxInt,NEAR
ASSUME cs:CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
; BUGBUG - START OF TO IGNORE SPURIOUS TX INTERRUPTS
; Workaround for a hardware in the 8250 chip:
; if TX interrupt is enabled when the transmiter holding
; register is NOT empty, a TX interrupt is generated anyway.
; We have to ignore the spurious TX interrupt.
; Another transmit interrupt will be generated when the
; transmitter holding register actually does empty.
txi00:
txi05:
test [si].ci_flagx,FX_16450 OR FX_16550A
jnz txi10 ; 16450 or FX_16550A
ReadLSR ; (al) = line status register (uses dx)
test al,LS_THRE
ljz txix ; transmitter not empty, can't be tx int
; BUGBUG - END OF TO IGNORE SPURIOUS TX INTERRUPTS
txi10: sti ; enable RX ints on other port
mov cx,1 ; cx = tx count = 1
test [si].ci_dcb_flags3,F3_TX_16
jz txitop
mov cx,16 ; cx = tx count = 16 (FIFO on)
txitop:
test [si].ci_Flagx1,FX1_FLUSH_TX_IP ;;MF flushing TX queue
ljnz txix ;;MF yes, drop interrupt and leave
mov ah,[si].ci_hsflag ; get handshake flag
test ah,HS_XON_PENDING OR HS_XOFF_PENDING OR HS_TX_IMMED
IFDEF RPTSTRICT
Debug = 1
ENDIF
ljnz txixo ; XON/XOFF/TX_IMMED pending, go process
cmp [si].ci_w_rp._hi,0
jnz txi50 ; current request
test [si].ci_vdm_flag,VDM_Flag_InUse
jnz txi50 ;@VDM it is OK It's a VDM
inc bad_int ;it is not OK, increment mark
cmp bad_int,BAD_MAX ;it is maximum, go to hell
je txie1 ;@VDM internal error
call CheckTX ;still have a hope turn off tx int
ret
txie1:
mov dx,[si].ci_port
add dx,R_INTEN ; (dx) -> interrupt enable reg
in al,dx ; (al) = interrupt enable
test al,IE_TX
jz txie2
and al,NOT IE_TX ; disable TX interrupts first
out dx,al
ret
txie2:
ComErr <TxInt : no current request packet>
ret
txi50: ; read a char from the queue and send it to the HW
mov bad_int,0 ; reset interrupt count
call ReadQueueByte ; get next byte from queue
jc txi70 ; no data in queue
mov dx,[si].ci_port
out dx,al ; send data byte
cli
INT_Notify ;@VDM Macro to see if we need to
;@VDM notify the VDM of RX, TX or MS
;@VDM interrupts
sti
mov bx,[si].ci_w_to_start ; get start value for timeout
mov [si].ci_w_to,bx
txi70: cmp [si].ci_w_to_move,0
jne txi90 ; data still to move, request not done
cmp [si].ci_qout.ioq_count,0
jne txicont ; data still in queue, request not done
cmp [si].ci_w_rp._hi,0
je txi85 ; no current request packet
txi80: ; request is done
les di,[si].ci_w_rp ; (es:di) -> request packet
ASSUME es:NOTHING
ChkRPPtr
ChkRPType CMDOUTPUT
ProcReady ; put request on ready list (run later)
mov [si].ci_w_rp._hi,0 ; no longer current
txi85:
call CheckTX ;;MF ; disable tx ints if needed
;;mf call StartNextWRP ; start the next request (calls CheckTX)
;;mf jc txix ; no more requests OR not ready to TX
jmp txix ;;mf ; no more requests
txi90:
mov bx,[si].ci_qout.ioq_count
cmp bx,TX_MOVE_PROT
ja txicont ; not down to prot mode mark
; hit low water mark, move more data
txi95: or [si].ci_flagx,FX_DATA_MOVED ; mark data moved
SaveReg <cx>
les di,[si].ci_w_rp ; (es:di) -> request packet
ASSUME es:NOTHING
ChkRPPtr
ChkRPType CMDOUTPUT
mov cx,[si].ci_w_to_move ; set up count
call WriteQueue ; move data into queue
RestoreReg <cx>
txicont:
;IFNDEF RPTSTRICT
; loop txitop ; transmit up to cx characters
;ELSE
dec cx
jz txix
jmp txitop ; transmit up to cx characters
;ENDIF
;* handle XOFF/XON/TX_IMMED here
txixo:
mov bad_int,0 ; reset interrupt count
test ah,HS_XOFF_PENDING
jz txixo2 ; not XOFF, must be XON or TX_IMMED
; XOFF pending
and ah,NOT HS_XOFF_PENDING ; XOFF no longer pending
or ah,HS_XOFF_SENT ; show XOFF sent
mov [si].ci_hsflag,ah ; save updated handshake flag
mov al,[si].ci_dcb_xoffchar ; get XOff char
jmp SHORT txixo4 ; go output the character.
txixo2: ; XON or TX_IMMED pending
test ah,HS_XON_PENDING
jz txixo3 ; not XON, must be TX_IMMED
; XON pending
and [si].ci_hsflag,NOT (HS_XON_PENDING OR HS_XOFF_SENT)
mov al,[si].ci_dcb_xonchar ; get XON char
jmp SHORT txixo4 ; go output the character.
txixo3: ; TX_IMMED pending
and [si].ci_hsflag,NOT HS_TX_IMMED ; clear xmit immediate flag
mov al,[si].ci_tximm ; get char to xmit
txixo4: mov dx,[si].ci_port
out dx,al ; send XON, XOFF, or TxImm char
call CheckTX ; check if we can still TX
jc txix ; not ready to TX, done
jmp SHORT txicont
txix:
pushf
cli
test [si].ci_vdm_flag,VDM_Flag_InUse
jz txi89
; VDM using this COM port
mov ax,[si].ci_qout.ioq_count
cmp ax,0
jne txi89
test [si].ci_vdm_flag,VDM_Flag_Blocked_IOCTL
jz txi81
; run IOCTL thread that is blocked
push es
push di
push bx
push ax
les di,[si].ci_vdm_Blocked_IOCTL; (es:di) -> request packet
call ProcRun ; run it
and [si].ci_vdm_flag,NOT VDM_Flag_Blocked_IOCTL
pop ax
pop bx
pop di
pop es
txi81:
cmp [si].ci_vdm_Tx_State,2 ; if TX_State == 2
jne txi89
; TX_STATE == 2
; cmp RX buffer,empty
push ax
mov ax,[si].ci_qin.ioq_count
cmp ax,0
pop ax
je txi82
; RX buffer not empty
mov [si].ci_vdm_Tx_State,3
mov [si].ci_vdm_Rx_count,0
jmp short txi89
txi82: ; RX buffer empty
mov [si].ci_vdm_Tx_State,1
mov [si].ci_vdm_Rx_count,0
txi89:
popf
ret ; leave
EndProc TxInt
;** MxInt - Modem Status Interrupt (lowest priority)
;
; ENTRY (ds:si) -> ComInfo
; (al) = modem status register
;
; EXIT none
;
; USES ax dx
Procedure MxInt,HYBRID
ASSUME cs:CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
mov bad_int,0 ; reset interrupt count
ChkComInfoPtr
; mov [si].ci_vdm_LastMSR,al ; RDW 80677
IFDEF MSR_DEBUG
; Save all MSR values in a circular buffer for debugging
DSEG SEGMENT
PUBLIC MSR_buf,MSR_ptr
MSR_BUF_SIZE EQU 1024 ; size of MSR_buf
MSR_ptr DW OFFSET DSEG:MSR_buf ; pointer into MSR_buf
MSR_buf DB MSR_BUF_SIZE dup (0) ; buffer for MSR values
DSEG ENDS
push bx
mov bx,MSR_ptr ; (bx) -> MSR_buf
cmp bx,OFFSET MSR_buf + MSR_BUF_SIZE
jb mxi10 ; not at end of buffer
mov bx,OFFSET MSR_buf ; at end of buffer, wrap to beginning
mxi10: mov [bx],al ; save msr value in table
inc bx ; (bx) -> next MSR_buf value
mov MSR_ptr,bx
pop bx
ENDIF
; check DSR for input sensitivity to DSR
; character is good if:
; input sensitivity to DSR is NOT active OR
; DSR was high before OR is high now
.errnz MS_DSR - 00100000b
.errnz FX_IN_DSR_OK - 00100000b
.errnz F1_IN_DSR_SENSE - 01000000b
mov dl,[si].ci_dcb_flags1
not dl ; (dl) = NOT flags1
shr dl,1
or dl,[si].ci_msrshadow ; (dl) = NOT flags1 OR old MSR
or dl,al ; (dl) = NOT flags1 OR old OR new MSR
and dl,FX_IN_DSR_OK ; (dl) = DSR ok
and [si].ci_flagx,NOT FX_IN_DSR_OK
or [si].ci_flagx,dl
; save the modem staus register in the shadow.
mov [si].ci_msrshadow,al ; save MSR data for others
; modem status positions (before shifting)
.errnz MS_DCTS-00000001b
.errnz MS_DDSR-00000010b
.errnz MS_TERI-00000100b
.errnz MS_DDCD-00001000b
; event mask positions (after shifting)
.errnz EV_CTS-000001000b
.errnz EV_DSR-000010000b
.errnz EV_DCD-000100000b
.errnz EV_Ring-100000000b ; 9 bits!
; create the event mask from the modem status
; y = carrier detect
; t = tailing edge ring indicator
; d = data set ready
; c = clear to send
; 7 6 5 4 3 2 1 0 7 6 5 4 3 2 1 0
mov ah,al ; . . . . y t d c . . . . y t d c
shr ax,2 ; . . . . . . y t d c . . . . y t
ror ah,1 ; t . . . . . . y d c . . . . y t
shr ax,3 ; . . . t . . . . . . y d c . . .
shr ah,4 ; . . . . . . . t . . y d c . . .
and ax,EV_CTS OR EV_DSR OR EV_DCD OR EV_Ring
or [si].ci_event,ax
; So we can us same MxInt routine for standard and enhanced ports
call CheckTX
INT_Notify ;@VDM Macro to see if we need to
;@VDM notify the VDM of RX, TX or MS
;@VDM interrupts
mxx: ret
EndProc MxInt
;** Ticker - timeout routine
;
; Call timeout routines for read and write on COM1 and COM2.
;
; NOTE timer tick handlers DO need to save registers
;
; ENTRY ds = device driver data segment (set up by kernel)
;
; EXIT none
;
; USES none
Procedure SwapTicker,FAR
ASSUME cs:CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
pushf
pusha
SaveReg <es,ds>
mov si,Com1 ; (ds:si) -> ComInfo structure
or si,si
jz tic1 ; no com1 port
cmp [si].ci_nopens,0
je tic1
test [si].ci_flagx,FX_RTS_DROP_PENDING
jz tic0 ; RTS drop not pending
ReadLSR ; (al) = LSR
and al,LS_THRE OR LS_TSRE
cmp al,LS_THRE OR LS_TSRE
jne tic0 ; THR or TSR are not empty
and [si].ci_flagx,NOT FX_RTS_DROP_PENDING
; clear flag
add dx,R_MODMC-R_LINES ; (dx) -> modem control reg.
min al,dx ; (al) = MCR
and al,NOT MC_RTS ; turn RTS off
out dx,al
tic0: call ReadTick
call WriteTick
tic1: mov si,Com2 ; (ds:si) -> ComInfo structure
or si,si
jz tic3 ; no com2 port
cmp [si].ci_nopens,0
je tic3
test [si].ci_flagx,FX_RTS_DROP_PENDING
jz tic2 ; RTS drop not pending
ReadLSR ; (al) = LSR
and al,LS_THRE OR LS_TSRE
cmp al,LS_THRE OR LS_TSRE
jne tic2 ; THR or TSR are not empty
and [si].ci_flagx,NOT FX_RTS_DROP_PENDING
; clear flag
add dx,R_MODMC-R_LINES ; (dx) -> modem control reg.
min al,dx ; (al) = MCR
and al,NOT MC_RTS ; turn RTS off
out dx,al
tic2: call ReadTick
call WriteTick
tic3: mov si,Com3 ; (ds:si) -> ComInfo structure
or si,si
jz tic5 ; no com3 port
cmp [si].ci_nopens,0
jz tic5
test [si].ci_flagx,FX_RTS_DROP_PENDING
jz tic4 ; RTS drop not pending
ReadLSR ; (al) = LSR
and al,LS_THRE OR LS_TSRE
cmp al,LS_THRE OR LS_TSRE
jne tic4 ; THR or TSR are not empty
and [si].ci_flagx,NOT FX_RTS_DROP_PENDING
; clear flag
add dx,R_MODMC-R_LINES ; (dx) -> modem control reg.
min al,dx ; (al) = MCR
and al,NOT MC_RTS ; turn RTS off
out dx,al
tic4: call ReadTick
call WriteTick
tic5: mov si,Com4 ; (ds:si) -> ComInfo structure
or si,si
jz ticx ; no com4 port
cmp [si].ci_nopens,0
je ticx
test [si].ci_flagx,FX_RTS_DROP_PENDING
jz tic6 ; RTS drop not pending
ReadLSR ; (al) = LSR
and al,LS_THRE OR LS_TSRE
cmp al,LS_THRE OR LS_TSRE
jne tic6 ; THR or TSR are not empty
and [si].ci_flagx,NOT FX_RTS_DROP_PENDING
; clear flag
add dx,R_MODMC-R_LINES ; (dx) -> modem control reg.
min al,dx ; (al) = MCR
and al,NOT MC_RTS ; turn RTS off
out dx,al
tic6: call ReadTick
call WriteTick
ticx: RestoreReg <ds,es>
popa
popf
ret
EndProc SwapTicker
;** WriteTick - see if a write request timed out
;
; If there is a current write request, and infinite timeout
; is not on, decrement the timeout counter.
; If counter goes to zero, calculate the number of characters
; already sent to the hardware, complete the request, and
; start the next write request.
;
; ENTRY (ds:si) -> ComInfo structure
;
; EXIT
;
; USES ax dx di es
Procedure WriteTick,NEAR
ASSUME cs:CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
ChkComInfoPtr
test [si].ci_Flagx1,FX1_FLUSH_TX_IP ;;MF
jnz wtkx ;;MF
cli
cmp [si].ci_w_rp._hi,0
je wtkx ; no current write request
test [si].ci_dcb_flags3,F3_W_INF_TO
jnz wtkx ; infinite time
dec [si].ci_w_to ; record tick
jnz wtkx ; no time out
les di,[si].ci_w_rp ; (es:si) -> request packet
ASSUME es:NOTHING
ChkRPPtr
ChkRPType CMDOUTPUT
mov ax,[si].ci_qout.ioq_count
add ax,[si].ci_w_to_move ; ax = number not written
sub es:[di].IOcount,ax ; number of bytes actually written
FlushQueue ci_qout
mov [si].ci_w_rp._hi,0 ; no longer current
; Time to Run any requests on ready list, start the next write
; request, and disable tx if needed.
sti
; Standard port
call ProcRun
cmp GAS_Switch,0
je skip_alert
call SetAlert ; set up any SNA alerts
skip_alert:
;;mf call StartNextWRP
call CheckTX ;;MF ; disable TX ints if needed
jmp SHORT wtkx
wtkx: sti
ret
EndProc WriteTick
;** ReadTick - see if a read request timed out
;
; If there is a current read request, decrement the timeout counter.
; If counter goes to zero, ProcRun the request.
; When the thread wakes up, it attempts to complete the request
; from the data available in the input queue
; and starts the next request.
;
; ENTRY (ds:si) -> ComInfo structure
;
; EXIT
;
; USES ax bx di es
Procedure ReadTick,NEAR
ASSUME cs:CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
ChkComInfoPtr
test [si].ci_Flagx1,FX1_FLUSH_RX_IP ;;MF
jnz rtkx ;;MF
cli
cmp [si].ci_r_rp._hi,0
je rtkx ; no current read request
dec [si].ci_r_to ; record tick
jnz rtkx ; no time out
les di,[si].ci_r_rp ; (es:di) -> request packet
ASSUME es:NOTHING
ChkRPPtr
ChkRPType CMDINPUT
sti
call ProcRun
rtkx: sti
ret
EndProc ReadTick
;********************** START OF SPECIFICATIONS *********************
;*
;* SUBROUTINE NAME: TellVCOMxx
;*
;* DESCRIPTIVE NAME: PCOM to VCOM Interrupt Notification Routine
;*
;* STATUS: RELEASE 2 LEVEL 0
;*
;* FUNCTION: Tells VCOM when an interrupt needs to be reflected to the
;* DOS app running in a VDM.
;*
;* NOTES:
;*
;* DEPENDENCIES: ABIOS MUST BE PRESENT
;*
;* ENTRY POINTS: TellVCOMMs, TellVCOMRx, TellVCOMTx
;*
;* LINKAGE: NEAR
;*
;* INPUT: DS:SI --> ComInfo data area for this port
;* BX = MSR to send to VDM(for TellVCOMMs)
;* ci_vdm_LastLSR = LSR to send to VDM(for TellVCOMRx)
;*
;* OUTPUT: NONE
;*
;* EXIT-NORMAL: NONE
;*
;* EXIT_ERROR: NONE
;*
;* EFFECTS:
;*
;* INTERNAL REFERENCES:
;*
;* EXTERNAL REFERENCES: NONE
;*
;*********************** END OF SPECIFICATIONS ***********************
Procedure TellVCOMxx,near
TellVCOMRx: ; tell VCOM about RX interrupt
mov ah,4
mov bl,[si].ci_vdm_LastLSR
Jmp short TellVCOM
TellVCOMTx: ; tell VCOM about TX interrupt
mov ah,2
Jmp short TellVCOM
TellVCOMMs: ; tell VCOM about Modem Status interrupt
mov ah,0
mov [si].ci_VDM_LastMSR,bl
and [si].ci_VDM_LastMSR, NOT MS_TERI ; RDW 80677 - Tell VCOM when
; RI (TERI) is present
TellVCOM:
mov dl, [si].ci_port_number
.386
call FWORD PTR [VCOMAddress]
.286
RET ; to Caller
EndProc TellVCOMxx
;********************** START OF SPECIFICATIONS *********************
;*
;* SUBROUTINE NAME: Rx_Notify
;*
;* DESCRIPTIVE NAME: Check to see if VCOM should be notified about an
;* Rx interrupt
;*
;* STATUS: RELEASE 2 LEVEL 0
;*
;* FUNCTION:
;*
;* NOTES:
;*
;* DEPENDENCIES: ABIOS MUST BE PRESENT
;*
;* ENTRY POINTS: Rx_Notify
;*
;* LINKAGE: NEAR
;*
;* INPUT: DS:SI --> ComInfo data area for this port
;* ci_LastLSR = LSR to send to VDM(for TellVCOMRx)
;*
;* OUTPUT: NONE
;*
;* EXIT-NORMAL: NONE
;*
;* EXIT_ERROR: NONE
;*
;* EFFECTS:
;*
;* INTERNAL REFERENCES:
;* TellVcomRx
;*
;* EXTERNAL REFERENCES: NONE
;*
;*********************** END OF SPECIFICATIONS ***********************
Procedure Rx_Notify,near
; if the notifiy flag is on
test [si].ci_vdm_flag,VDM_Flag_notify_the_VCOM_RX
jz rxn90
cmp [si].ci_vdm_Tx_State,1 ; if we are in TX state 1
jne rxn90
; if there is data in the rx queue
mov ax,[si].ci_qin.ioq_count ; ax = size of input queue
cmp ax,0
jz rxn90
; set the notify flag off
and [si].ci_vdm_flag,NOT VDM_Flag_notify_the_VCOM_RX
call TellVCOMRx ; notify VCOM
rxn90:
ret
EndProc Rx_Notify
;********************** START OF SPECIFICATIONS *********************
;*
;* SUBROUTINE NAME: Tx_Notify
;*
;* DESCRIPTIVE NAME: Check to see if VCOM should be notified about a
;* Tx interrupt
;*
;* STATUS: RELEASE 2 LEVEL 0
;*
;* FUNCTION:
;*
;* NOTES:
;*
;* DEPENDENCIES: ABIOS MUST BE PRESENT
;*
;* ENTRY POINTS: Tx_Notify
;*
;* LINKAGE: NEAR
;*
;* INPUT: DS:SI --> ComInfo data area for this port
;*
;* OUTPUT: NONE
;*
;* EXIT-NORMAL: NONE
;*
;* EXIT_ERROR: NONE
;*
;* EFFECTS:
;*
;* INTERNAL REFERENCES:
;* TellVcomTx
;*
;* EXTERNAL REFERENCES: NONE
;*
;*********************** END OF SPECIFICATIONS ***********************
Procedure Tx_Notify,near
; if the notifiy flag is on
test [si].ci_vdm_flag,VDM_Flag_notify_the_VCOM_TX
jz txn90 ; no goto end
cmp [si].ci_vdm_Rx_State,3 ; if we are in RX state 3
je txn10 ; yes do processing
cmp [si].ci_vdm_Rx_State,1 ; if we are in RX state 1
jne txn90 ; no goto end
; if there is data in the tx queue
mov ax,[si].ci_qout.ioq_count ; ax = number of char in
; output queue
cmp ax,0
je txn90 ; no goto end
txn10:
; set the notify flag off
and [si].ci_vdm_flag,NOT VDM_Flag_notify_the_VCOM_TX
call TellVCOMTx ; notify VCOM
txn90:
ret
EndProc Tx_Notify
;********************** START OF SPECIFICATIONS *********************
;*
;* SUBROUTINE NAME: Ms_Notify
;*
;* DESCRIPTIVE NAME: Check to see if VCOM should be notified about a
;* Ms interrupt
;*
;* STATUS: RELEASE 2 LEVEL 0
;*
;* FUNCTION:
;*
;* NOTES:
;*
;* DEPENDENCIES: ABIOS MUST BE PRESENT
;*
;* ENTRY POINTS: Ms_Notify
;*
;* LINKAGE: NEAR
;*
;* INPUT: DS:SI --> ComInfo data area for this port
;*
;* OUTPUT: NONE
;*
;* EXIT-NORMAL: NONE
;*
;* EXIT_ERROR: NONE
;*
;* EFFECTS:
;*
;* INTERNAL REFERENCES:
;* TellVcomMs
;*
;* EXTERNAL REFERENCES: NONE
;*
;*********************** END OF SPECIFICATIONS ***********************
Procedure Ms_Notify,near
; Bl = ComInfo.msrshadow
mov bl,[si].ci_msrshadow
; NOTE we are only interested in CTS, DSR, RI and DCD
and bl,MS_CTS+MS_DSR+MS_RI+MS_DCD+MS_TERI ;AA Fix added MS_TERI
; IF (Bl != ComInfo.VDM_lastMSR)
mov bh,[si].ci_vdm_LastMSR
cmp bl,bh
; THEN
je msn90
; IF (ComInfo.Rx_Queue empty)
push bx
mov ax,[si].ci_qin.ioq_count ; ax = size of input queue
pop bx
cmp ax,0
; THEN
jne msn10
; call TellVCOMMs (Temp_MSR)
call TellVCOMMs
jmp short msn90
; ELSE
msn10:
; Bl.CTS = ComInfo.VDM_lastMSR.CTS
; Bl.DSR = ComInfo.VDM_lastMSR.DSR
and bh,MS_CTS+MS_DSR
and bl,NOT (MS_CTS+MS_DSR)
or bl,bh
; IF (Bl != ComInfo.VDM_lastMSR)
cmp bl,[si].ci_vdm_LastMSR
; THEN
je msn90
; call TellVCOMMs
call TellVCOMMs
msn90:
ret
EndProc Ms_Notify
CSEG ENDS
RSEG SEGMENT
ASSUME cs:RSEG
Procedure ComInt2,FAR
setDS DSEG
mov si,Com2 ; pointer to com2 info structure
jmp ComInt
Entry ComInt1,,,nocheck
setDS DSEG
mov si,Com1 ; pointer to com1 info structure
jmp ComInt
Entry ComInt3,,,nocheck
setDS DSEG
mov si,Com3 ; pointer to com3 info structure
jmp ComInt
Entry ComInt4,,,nocheck
setDS DSEG
mov si,Com4 ; pointer to com4 info structure
jmp ComInt
EndProc ComInt2
Procedure SComInt1,FAR
setDS DSEG
lea si, ShrdIRQ1 ; info. for this IRQ line
jmp short SComInt
Entry SComInt2,,,nocheck
setDS DSEG
lea si, ShrdIRQ2 ; info. for this IRQ line
jmp short SComInt
Entry SComInt3,,,nocheck
setDS DSEG
lea si, ShrdIRQ3 ; info. for this IRQ line
jmp short SComInt
Entry SComInt4,,,nocheck
setDS DSEG
lea si, ShrdIRQ4 ; info. for this IRQ line
;;;;; jmp SComInt ; fall into SComInt
SComInt:
mov si, [si].si_firstCOM ; first entry in the chain
sci10:
push si ; save our spot in the chain
push cs ; fake a far call
call [si].ci_isr ; call an interrupt service routine
pop si ; get back our spot in the chain
jc sci20 ; it claimed the interrupt, so exit
ret ; CY is clear, indicating our interrupt
sci20:
mov si, [si].ci_next_COM ; get next entry in the chain
or si, si ; end of the chain (null)?
jnz sci10 ; N: process next COM port in chain
stc ; indicate not our interrupt
ret
EndProc SComInt1
Procedure Ticker,FAR
setDS DSEG
jmp SwapTicker
EndProc Ticker
RSEG ENDS
END