home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
OS/2 Shareware BBS: 10 Tools
/
10-Tools.zip
/
ddkx86v5.zip
/
DDKX86
/
SRC
/
DEV
/
ATCOM
/
ATESP.ASM
< prev
next >
Wrap
Assembly Source File
|
1995-04-14
|
61KB
|
1,702 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 = @(#)atesp.asm 6.3 91/04/22
; ***************************************************************************
; *
; *
; *
; ***************************************************************************
PAGE 80,132
.286p
TITLE com01.sys - Asynchronous Communication Device Driver
NAME com01
;
; Modification History
;
; ACW 04/16/91 @PVW Added perfview counters/timers
; WDM 04/21/94 82548 - pvwxport.inc now included in atcom.inc
;
.286p
.xlist
; 82548 include pvwxport.inc ;@PVW
include ateisa.inc
include devhlp.inc
include atcom.inc
include realmac.inc
include basemaca.inc
include osmaca.inc
include atesp.inc
include atespmac.inc
.list
EXTRNFAR ComError
EXTRNFAR SetBaud
EXTRNFAR CheckLCR
EXTRNFAR SetLineC
EXTRNFAR ComputeHHS
EXTRNFAR ComputeAPO
EXTRNFAR ComputeWTO
EXTRNFAR ComputeRTO
EXTRNFAR EnableRemoteTX
EXTRNFAR MxInt
extrn endESPcode:byte
HSEG SEGMENT
; All ABIOS request blocks must reside in driver's RESIDENT data segment
; (HSEG) because DevHlp_ABIOSCommonEntry requires that DS points to driver's
; RESIDENT data segment.
public alloc_rb,dealloc_rb,disable_rb,tcount_rb,read_write_rb
public alloc_ptr,dealloc_ptr,disable_ptr,tcount_ptr,read_write_ptr
alloc_rb ArbLevelRB <>
alloc_ptr dw alloc_rb
dealloc_rb ArbLevelRB <>
dealloc_ptr dw dealloc_rb
disable_rb ArbLevelRB <>
disable_ptr dw disable_rb
tcount_rb TransCountRB <>
tcount_ptr dw tcount_rb
read_write_rb ReadWriteRB <>
read_write_ptr dw read_write_rb
public get_parms_ptr,read_pos_ptr
get_parms_rb GetParmsRB <>
get_parms_ptr dw get_parms_rb
read_pos_rb ReadPOSRB <>
read_pos_ptr dw read_pos_rb
HSEG ENDS
DSEG SEGMENT
EXTRN DevHlp:DWORD
EXTRN Flags:BYTE
EXTRN Kernel_Type:WORD
ports_using_DMA_lid db 0 ;free DMA LID when this goes to zero
DMA_lid dw 0 ;need this to talk to ABIOS
public FirstESP,SecondESP
; MASM/Link fix start
;FirstESP ESPInfo <>
;SecondESP ESPInfo <>
FirstESP db size ESPInfo dup(-1) ;port1 and port2 should be -1
SecondESP db size ESPInfo dup(-1) ;port1 and port2 should be -1
; MASM/Link fix end
public ESP1,ESP2
ESP1 dw FirstESP
ESP2 dw SecondESP
ESPcodelockh db lhlen dup(0)
ESPdatalockh db lhlen dup(0)
DSEG ENDS
E_CSEG SEGMENT ; code specific to enhanced ports
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
public startESPcode
startESPcode label byte ; before any code in E_CSEG
;** E_LockSegments
;
; Locks segment containg ESP-specific code
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT 'C' clear if lock successful
; 'C' set if lock failed
;
Procedure E_LockSegments,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:DSEG,ss:NOTHING
.386p
SaveReg <es,si>
setES DSEG ; DevHlp is in DSEG
; lock ESP-specific code
; do a virttolin DevHelp (linear address)
mov ax,E_CSEG ; ESP-specific code segment
lea esi,startESPcode
mov dl,DevHlp_VirtToLin
call es:[DevHlp]
mov edi,eax
; do a virttolin DevHelp (lockhandle)
mov ax,DSEG ; lock handle is in DSEG
mov esi,OFFSET ESPcodelockh
mov dl,DevHlp_VirtToLin
call es:[DevHlp]
; do a VMLock DevHelp
mov esi,eax ; get offset to lock handle
mov ebx,edi ; get offset to area to lock
mov edi,-1 ; set to no page list
lea ecx,endESPcode ; size to lock
sub ecx,OFFSET startESPcode ; size to lock
mov eax,16 ; long term lock
mov dl,DevHlp_VMLock
call es:[DevHlp]
jnc lockok
lockerr:stc
jmp SHORT lockx
lockok: SET Flags,F_ESP_CODE_LOCKED
clc
lockx: RestoreReg <si,es>
ret
.286p
EndProc E_LockSegments
;** E_UnLockSegments
;
; Unlocks segment containg ESP-specific code
;
; ENTRY (ds:si) -> ComInfo
;
Procedure E_UnLockSegments,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:DSEG,ss:NOTHING
.386p
; unlock code
push si
; do a virttolin DevHelp (lockhandle)
mov ax,DSEG
mov esi,OFFSET ESPcodelockh
mov dl,DevHlp_VirtToLin
DevHelp
; do a VMUnlock DevHelp using previously saved lock handle
mov esi,eax ; get offset to lock handle
mov dl,DevHlp_VMUnlock
DevHelp
pop si
CLR Flags,F_ESP_CODE_LOCKED
ret
.286p
EndProc E_UnLockSegments
;** JustEnhancedMode
;
; Sends ESP command to switch hw into enhanced mode. Either DMA or
; PIO mode is chosen independently for tx and rx, based on ComInfo.
;
; ENTRY (ds:si) -> ComInfo
;
Procedure JustEnhancedMode,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
xor ah,ah
cmp [si].ci_rx_request,DMA_REQ_DISABLE
je em10
SET ah,ESP_MODE_RX_DMA
jmp SHORT em20
em10: CLR ah,ESP_MODE_RX_DMA
em20: cmp [si].ci_tx_request,DMA_REQ_DISABLE
je em30
SET ah,ESP_MODE_TX_DMA
jmp SHORT em40
em30: CLR ah,ESP_MODE_TX_DMA
em40: or ah,ESP_MODE_ENHANCED
SetMode ah
ret
EndProc JustEnhancedMode
;** JustStandardMode
;
; Sends ESP command to switch hw into standard mode.
;
; ENTRY (ds:si) -> ComInfo
Procedure JustStandardMode,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
SetMode ESP_MODE_S
ret
EndProc JustStandardMode
;** SwtichToEnhanced
;
; Does all that is necessary to switch port from standard to enhanced:
; - sets up UART registers
; - sends ESP setup commands
; - deinstall interrupt handler for UART
; - installs interrupt handler for ESP if necessary
; - send ESP command to put this port in enhanced mode
; - sets up ESP's interrupt mask
; WARNING! The order of the above steps is very important!
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT 'C' clear if no problems
Procedure SwitchToEnhanced,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
push di ; ???????
SET [si].ci_eflags,EF_MODE_ENHANCED
; Go through ESP to set up UART's baud rate, LCR, and MCR.
mov ax,[si].ci_baud
CALLFAR SetBaud ; does SetTriggerLevel, SetRxTimeout
mov al,[si].ci_bytesize
mov ah,[si].ci_parity
mov ch,[si].ci_stopbits
CALLFAR CheckLCR ; calculates LCR, puts it into (al)
CALLFAR SetLineC
mov bx,0
CALLFAR ComputeHHS ; does SetErrorMask, SetFCType
; Just to be safe, better send ALL port setup commands to ESP.
; Must use "gate" mechanism, because other ESP port may be in
; enhanced mode already.
SetFCLevel HIGH(ESP_DEF_FC_LEVEL_OFF), \
LOW(ESP_DEF_FC_LEVEL_OFF), \
HIGH(ESP_DEF_FC_LEVEL_ON), \
LOW(ESP_DEF_FC_LEVEL_ON)
SetFlowOffTimeout ESP_DEF_FLOW_OFF
FlushRxFIFO
FlushTxFIFO
; Always dump UART interrupt handler for this port's (standard) irq.
xor bh,bh
mov bl,[si].ci_irq ; standard irq
mov dl,DevHlp_UnSetIRQ
; Do fancy segment swapping so DevHlp is called with DS set to
; driver's resident data segment.
setES DSEG ; ES = segment for DevHlp ptr
setDS HSEG ; DS = driver's resident data seg
call es:[DevHlp]
setDS DSEG ; restore DS
; Use info in ESPInfo to install ESP interrupt handler only if
; other ESP port hasn't already.
; Proper handler MUST be installed before switching to enhanced mode!
test [di].pi_flagx,PIF_ONE_HAS_IRQ
jnz swen30
SET [di].pi_flagx,PIF_ONE_HAS_IRQ
mov ax,[di].pi_isr ; enhanced port isr
mov bl,[di].pi_irq ; enhanced port irq
xor bh,bh
mov dh,[si].ci_int_sharing ; 0 on ISA, var. on EISA
mov dl,DevHlp_SetIRQ ; devhlp request code
; Do fancy segment swapping so DevHlp is called with DS set to
; driver's resident data segment.
setES DSEG ; ES = segment for DevHlp ptr
setDS HSEG ; DS = driver's resident data seg
call es:[DevHlp]
setDS DSEG ; restore DS
ljc swenx ; error, couldn't get IRQ
swen30:
; ESP interrupt handler is registered -- now we can switch port to
; enhanced mode.
call JustEnhancedMode
; Set this port's bits in ESP's service mask
mov ah,[di].pi_svcmask ; (al) = current svc mask
cmp [si].ci_cmd_offset,0
jne swen40 ; port2
SET ah,ESP_SID_PORT1 ; turn on port1 bits in mask
CLR ah,ESP_SID_TX1 ; Tx enabled (later) by CheckTx
jmp SHORT swen50
swen40: or ah,ESP_SID_PORT2 ; turn on port2 bits in mask
CLR ah,ESP_SID_TX2 ; Tx enabled (later) by CheckTx
swen50: SET ah,ESP_SID_DMAFIN ; turn on DMA fin bit in mask
SET ah,ESP_SID_DMATO ; turn on DMA fin bit in mask
mov [di].pi_svcmask,ah ; save new svc mask
; Disable ALL ints while re-enabling ESP interrupts
cli
ISSUE ESP_CMD_SETSVCMASK,ah
ISSUE ESP_CMD_GDIPS
PREAD ESP_R_STATUS1
sti
clc ; show caller no problems
swenx: pop di ; ????????????
ret
EndProc SwitchToEnhanced
;** SwtichToStandard
;
; Does all that is necessary to switch port from enhanced to standard:
; - disable ESP interrupts for this port
; - deinstall interrupt handler for ESP if last open enhanced port
; - install interrupt handler for UART on this port's standard IRQ
; - send ESP commmand to put this port in standard mode
; - set up UART registers
; WARNING! The order of the above steps is very important!
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT 'C' clear if no problems
Procedure SwitchToStandard,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
push di ; ??????????????
mov di,[si].ci_pinfo
CLR [si].ci_eflags,EF_MODE_ENHANCED
; Send ESP a new service mask to disable enhanced interrupts --
; for this port ONLY.
mov al,[di].pi_svcmask
cmp [si].ci_cmd_offset,0
jne sws5
CLR al,ESP_SID_PORT1
jmp SHORT sws10
sws5: CLR al,ESP_SID_PORT2
sws10: mov [di].pi_svcmask,al ; save new svc mask
SetSvcMask al
; Dump ESP interrupt handler only if other ESP port is NOT using the
; (enhanced) interrupt.
push si
cmp [si].ci_cmd_offset,0
jne sws20
; We're ESP port1, so examine port2 ComInfo
mov si,[di].pi_port2
jmp SHORT sws30
; We're ESP port2, so examine port1 ComInfo
sws20: mov si,[di].pi_port1
sws30:
; (si) -> ComInfo pointer for "other" port on ESP board.
test [si].ci_eflags,EF_MODE_ENHANCED ; other port enhanced?
jz sws35 ; no, release irq
cmp [si].ci_nopens,0 ; other port open?
je sws35 ; no, release irq
jmp SHORT sws40 ; don't release irq
sws35: xor bh,bh
mov bl,[di].pi_irq ; enhanced irq
mov dl,DevHlp_UnSetIRQ
; Do fancy segment swapping so DevHlp is called with DS set to
; driver's resident data segment.
setES DSEG ; ES = segment for DevHlp ptr
setDS HSEG ; DS = driver's resident data seg
call es:[DevHlp]
setDS DSEG ; restore DS
CLR [di].pi_flagx,PIF_ONE_HAS_IRQ
sws40: pop si ; (ds:si) -> original ComInfo
; Use info in ComInfo to install regular UART interrupt handler
; for this port's irq.
; Proper handler MUST be installed before switching to standard mode!
mov ax,[si].ci_isr ; standard port isr
mov bl,[si].ci_irq ; standard port irq
xor bh,bh
mov dh,[si].ci_int_sharing ; 0 on ISA, var. on EISA
mov dl,DevHlp_SetIRQ ; devhlp request code
; Do fancy segment swapping so DevHlp is called with DS set to
; driver's resident data segment.
setES DSEG ; ES = segment for DevHlp ptr
setDS HSEG ; DS = driver's resident data seg
call es:[DevHlp]
setDS DSEG ; restore DS
ljc swsx ; error, couldn't get IRQ
; UART interrupt handler is registered -- now we can switch port to
; standard mode. Once we do this, the UART can begin generating
; interrupts. But wait, the UART registers (baud,LCR,etc.) aren't
; set up properly yet! So make the ISR ignore interrupts temporarily
; by settings ci_nopens to zero.
push [si].ci_nopens
mov [si].ci_nopens,0
SetMode ESP_MODE_S
; Set up UART's baud rate, LCR, and MCR.
mov ax,[si].ci_baud
CALLFAR SetBaud
mov al,[si].ci_bytesize
mov ah,[si].ci_parity
mov ch,[si].ci_stopbits
CALLFAR CheckLCR ; calculates LCR, puts it into (al)
CALLFAR SetLineC
; Set up rest of UART stuff.
mov dx,[si].ci_port ; (dx) -> port base address
add dx,R_LINES ; (dx) -> LSR
min al,dx ; (al) = LSR (clear it)
mov [si].ci_lsrshadow,al ; shadow the contents of LSR
add dx,R_DATA-R_LINES ; (dx) -> data reg
min al,dx ; clear RX buffer
add dx,R_FIFOC-R_DATA ; (dx) -> fifo control reg
test [si].ci_dcb_flags3,F3_FIFO_HW_ON
jz sws50 ; FIFO HW off
mov al,[si].ci_dcb_flags3 ; (al) = flags3
and al,F3_RX_MASK ; (al) = RX trigger level
shl al,1 ; (al) = RX trigger level bits for FIFO
or al,FF_ENABLE OR FF_CLEAR_RX OR FF_CLEAR_TX
mout dx,al ; clear RX and TX FIFOs
sws50:
.errnz R_INTID-R_FIFOC
add dx,R_INTID-R_FIFOC ; (dx) -> int id reg.
min al,dx ; clear int id
mov [si].ci_msrshadow,0 ; zero previous msrshadow
add dx,R_MODMS-R_INTID ; (dx) -> modem status reg.
min al,dx ; clear modem status
CALLFAR MxInt ; update msrshadow
xor bx,bx ; show 0 for previous flags1 and flags2
CALLFAR ComputeHHS ; set up handshake state and
; initialize the MCR
CALLFAR EnableRemoteTX ; we're all set up, tell the remote TXer
cli ; disable processor interrupts before
; enabling 16450 chip interrupts
; Enable Receive Data and nModem Status interrupts.
; TX Holding Register interrupt will be enabled by CheckTx.
mov dx,[si].ci_port ; (dx) -> port
add dx,R_INTEN ; (dx) -> interrupt enable reg
mov al,IE_RX OR IE_MX ; (al) = interrupts to enable
mout dx,al
; Finished with UART set up, so restore ci_nopens and interrupt
; handler will process interrupts once again.
pop [si].ci_nopens ; count the open calls
sti
clc ; show caller no problem
swsx: pop di
ret
EndProc SwitchToStandard
;** E_CheckTX
;
; Enables/disables TxFIFO interrupt for a port
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT 'C' clear if TX disabled
; 'C' set if TX enabled
Procedure E_CheckTX,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
ChkComInfoPtr
mov di,[si].ci_pinfo
cmp [si].ci_w_rp._hi,0
jz ctxoff ; no data enqueued, disable TxFIFO
test [si].ci_hsflag,HS_BREAK_SET
jnz ctxoff
test [si].ci_hsflag,HS_XOFF_RECEIVED
jnz ctxoff ; act like XOFF received, disable TxFIFO
; Enable transmit interrupts
mov al,[di].pi_svcmask
cmp [si].ci_cmd_offset,0
jne ctx25
; Enable TxFIFO for port1
SET al,ESP_SVC_MASK_TX1
jmp SHORT ctx26
ctx25: ; Enable TxFIFO for port2
SET al,ESP_SVC_MASK_TX2
ctx26: clc ; 'C' clear - TX disabled
jmp ctx40
; Disable transmit interrupts
ctxoff: mov al,[di].pi_svcmask
cmp [si].ci_cmd_offset,0
jne ctx35
; Disable TxFIFO for por1
CLR al,ESP_SVC_MASK_TX1
jmp ctx37
ctx35: ; Disable TxFIFO for port2
CLR al,ESP_SVC_MASK_TX2
ctx37: stc
ctx40: pushf ; save C flag for caller
mov [di].pi_svcmask,al
mov dx,[di].pi_address
; Disable ALL ints while re-enabling ESP interrupts
CLI
ctx50: in al,dx
test al,ESP_RDY_CMD1
jz ctx50
add dx,ESP_R_CMD1-ESP_R_RDY
mov al,ESP_CMD_SETSVCMASK
out dx,al
add dx,ESP_R_RDY-ESP_R_CMD1
ctx60: in al,dx
test al,ESP_RDY_CMD2
jz ctx60
add dx,ESP_R_CMD2-ESP_R_RDY
mov al,[di].pi_svcmask
out dx,al
; Issue GetDips to be *SURE* that ESP has processed SetSvcMask before
; we re-enable interrupts
mov dx,[di].pi_address
ctx70: in al,dx
test al,ESP_RDY_CMD1
jz ctx70
add dx,ESP_R_CMD1-ESP_R_RDY
mov al,ESP_CMD_GDIPS
out dx,al
add dx,ESP_R_RDY-ESP_R_CMD1
ctx80: in al,dx
test al,ESP_RDY_STATUS1
jz ctx80
add dx,ESP_R_STATUS1-ESP_R_RDY
in al,dx
STI
ASSUME ds:NOTHING
POPFF ; restore C flag for caller
ret
EndProc E_CheckTX
Procedure E_Init_For_ABIOS_DMA,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
SaveReg <si,ds,es>
; Fill in ABIOS structures now so DMA can be used later.
; First step is to ask for logical ID for DMA device.
inc ports_using_DMA_lid
cmp ports_using_DMA_lid,1 ; Only port using DMA LID?
ljne edma_x ; Yes, don't get LID -- strucs already filled in
mov al,DEVICE_ID_DMA
mov bl,0 ; first avail LID
mov dh,1 ; must be 1 to get DMA device
mov dl,DevHlp_GetLIDEntry
DevHelp ; (ax) = LID
jnc edma_lid
jmp edma_x ; 'C' set tells caller error occurred
edma_lid:
mov DMA_lid,ax
; Got that LID, ask ABIOS for length of DMA request block.
mov cx,ax ; (cx) DMA LID from DevHlp
setDS HSEG ; get_parms_rb is in HSEG
lea si,get_parms_rb
mov [si].lid,ax
mov [si].func,ABIOS_FUNC_RETURNPARMS
mov [si].len,20h ; ABIOS doc says this is fixed at 20h
mov [si].retval,0FFFFh
sub ax,ax
mov WORD PTR [si].res,ax
mov WORD PTR [si].res+2,ax
mov dh,0 ; use Start entry point
mov dl,DevHlp_ABIOSCommonEntry
; Do fancy segment swapping so DevHlp is called with DS set to
; driver's resident data segment.
setES DSEG ; ES = segment for DevHlp ptr
call es:[DevHlp] ; DS = RESIDENT data segment
jnc eop_arbstruc
cmp [si].retval,0
je eop_arbstruc
; Can't use DMA because of problem with ABIOS. Free LID entry and
; return with 'C' set to notify caller of error.
dec es:ports_using_DMA_lid
jnz lid_in_use
mov ax,DMA_lid
mov dl,DevHlp_FreeLIDEntry
call es:[DevHlp]
lid_in_use:
stc ; 'C' set tells caller error occurred
jmp SHORT edma_x
eop_arbstruc:
mov ax,[si].rblen ; (ax) = DMA rb length
; Now that we know the DMA Request Block length, fill in specific
; Request Block strucs for use at interrupt time.
lea si,alloc_rb
mov [si].arblid,cx ; (cx) = LID from DevHlp
mov [si].arblen,ax ; (ax) = DMA rb length from above
mov [si].arbunit,0 ; first unit within LID
mov [si].arbtime,0
lea si,dealloc_rb
mov [si].arblid,cx ; (cx) = LID from DevHlp
mov [si].arblen,ax ; (ax) = DMA rb length from above
mov [si].arbunit,0 ; first unit within LID
mov [si].arbtime,0
lea si,disable_rb
mov [si].arblid,cx ; (cx) = LID from DevHlp
mov [si].arblen,ax ; (ax) = DMA rb length from above
mov [si].arbunit,0 ; first unit within LID
mov [si].arbtime,0
lea si,tcount_rb
mov [si].tclid,cx ; (cx) = LID from DevHlp
mov [si].tclen,ax ; (ax) = DMA rb length from above
mov [si].tcunit,0 ; first unit within LID
lea si,read_write_rb
mov [si].rwlid,cx ; (cx) = LID from DevHlp
mov [si].rwlen,ax ; (ax) = DMA rb length from above
mov [si].rwunit,0 ; first unit within LID
clc
edma_x:
RestoreReg <es,ds,si>
ret
EndProc E_Init_For_ABIOS_DMA
;** E_Open
;
; Must take extra steps to open an enhanced port:
; - initialize ComInfo.eflags
; - send ESP set up commands
; - store physical address of in/out ques for use at interrupt time
; - send ESP SetIRQ command to set up IRQ and DMA channel
; - enable ESP interrupts for this port
; - send command to put this port into enhanced mode
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT 'C' clear if TX disabled
; 'C' set if TX enabled
Procedure E_Open,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
mov [si].ci_rx_request,DMA_REQ_AUTO
mov [si].ci_tx_request,DMA_REQ_AUTO
SET [si].ci_eflags,EF_RX_REQUEST_DEF_DMA
CLR [si].ci_eflags,EF_RX_REQUEST_NOT_PIO
SET [si].ci_eflags,EF_TX_REQUEST_DEF_DMA
CLR [si].ci_eflags,EF_TX_REQUEST_NOT_PIO
SET [si].ci_eflags,EF_LAST_RX_WAS_DMA
SET [si].ci_eflags,EF_LAST_TX_WAS_DMA
; Read LSR and MSR
GetUARTStatus ; (al) = LSR, (ah) = MSR
mov [si].ci_lsrshadow,al
mov [si].ci_msrshadow,ah
xor bx,bx ; show 0 for previous flags1
; and flags2
CALLFAR ComputeHHS ; set up handshake state and
; issue SetFCType and SetErrMask
LocalXon ; spec says "first-level open
; will cause driver to believe
; it has NOT received an XOFF"
SetFCLevel HIGH(ESP_FC_LEVEL_OFF),LOW(ESP_FC_LEVEL_OFF),HIGH(ESP_FC_LEVEL_ON),LOW(ESP_FC_LEVEL_ON)
SetFlowOffTimeout ESP_DEF_FLOW_OFF
FlushRxFIFO
FlushTxFIFO
; Get phys address of in and out queues -- used at int time for DMA
eop10: lea bx,[si].ci_qin_q
SaveReg <si>
mov si,bx ; (ds:si) = virtual address to convert
mov dl,DevHlp_VirtToPhys
call [DevHlp]
RestoreReg <si>
jnc eop20
ComErr <VirtToPhys failed>,CALLFAR
eop20: mov WORD PTR [si].ci_qin.ioq_phys._hi,ax
mov WORD PTR [si].ci_qin.ioq_phys._lo,bx
lea bx,[si].ci_qout_q
SaveReg <si>
mov si,bx ; (ds:si) = virtual address to convert
mov dl,DevHlp_VirtToPhys
call [DevHlp]
RestoreReg <si>
jnc eop30
ComErr <VirtToPhys failed>,CALLFAR
eop30: mov WORD PTR [si].ci_qout.ioq_phys._hi,ax
mov WORD PTR [si].ci_qout.ioq_phys._lo,bx
; FIX THIS: Should ask VDMA if DMA channel available for receive,
; if not don't use DMA. If user didn't specify, do we use 1 or 3?
mov di,[si].ci_pinfo ; Look at ESPInfo
cmp [di].pi_DMA_chan,-1 ; did parameter specify DMA channel?
jne dma_done ; yes
mov [di].pi_DMA_chan,1 ; assume adapter is first ESP, use 1
cmp di,es:ESP1
je dma_done
mov [di].pi_DMA_chan,3 ; adapter is second ESP, use 3
dma_done:
mov al,[di].pi_irq
cmp al,3 ; build irq/dma mask
jne eop40
mov al,2
jmp SHORT eop60
eop40: cmp al,5
jne eop50
mov al,6
jmp SHORT eop60
eop50: cmp al,9
jne eop60
mov al,0
; last case is irq_level=4, but mask for that value is also 4
eop60: SET al,ESP_INT_ENABLE
mov ah,[di].pi_DMA_chan
shl ah,4
or ah,al
SetIRQ ah
; Send ESP a new service mask, with non-zero bits for OUR PORT ONLY.
eop65: cli ; disable processor interrupts before
; enabling ESP interrupts
mov al,[di].pi_svcmask ; (al) = current svc mask
cmp [si].ci_cmd_offset,0
jne eop70 ; port2
SET al,ESP_SID_PORT1 ; turn on port1 bits in mask
CLR al,ESP_SID_TX1 ; Tx enabled (later) by CheckTx
jmp SHORT eop80
eop70: or al,ESP_SID_PORT2 ; turn on port2 bits in mask
CLR al,ESP_SID_TX2 ; Tx enabled (later) by CheckTx
eop80: SET al,ESP_SID_DMAFIN ; turn on DMA fin bit in mask
SET al,ESP_SID_DMATO ; turn on DMA fin bit in mask
mov [di].pi_svcmask,al ; save new svc mask
SetSvcMask al
;issue mode command
xor ah,ah
cmp [si].ci_rx_request,DMA_REQ_DISABLE
je eop90
SET ah,ESP_MODE_RX_DMA
jmp SHORT eop95
eop90: CLR ah,ESP_MODE_RX_DMA
eop95: cmp [si].ci_tx_request,DMA_REQ_DISABLE
je eop100
SET ah,ESP_MODE_TX_DMA
jmp SHORT eop105
eop100: CLR ah,ESP_MODE_TX_DMA
eop105: or ah,ESP_MODE_ENHANCED
SetMode ah
ret
EndProc E_Open
;** E_Close
;
; Must take extra steps to close an enhanced port:
; - disable ESP interrupts for this port
; - deinstall ESP interrupt handler
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT 'C' clear if TX disabled
; 'C' set if TX enabled
Procedure E_Close,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
SaveReg <ds,es>
; Flush ESP's RxFIFO -- he'll flow remote transmitter on if necessary.
FlushRxFIFO
xor ax,ax
SetFCType ah,al ; lower RTS and DTR
; Send ESP a new service mask to ignore interrupts from our port.
mov di,[si].ci_pinfo
mov al,[di].pi_svcmask
cmp [si].ci_cmd_offset,0
jne ec10
CLR al,ESP_SID_PORT1
jmp SHORT ec20
ec10: CLR al,ESP_SID_PORT2
ec20: mov [di].pi_svcmask,al ; save new svc mask
SetSvcMask al
; Don't release IRQ if:
; - interrupt sharing
; - other ESP port is both enhanced and open
test [si].ci_int_sharing, INT_SHARING ; sharing the IRQ?
ljnz ec70 ; yes, don't release irq
SaveReg <si>
mov di,[si].ci_pinfo
cmp [si].ci_cmd_offset,0
jne ec30
; We're ESP port1, so examine port2 ComInfo
cmp [di].pi_port2,0 ; does other port exist?
je ec50 ; no, pop di, pop si and release irq
mov si,[di].pi_port2
jmp SHORT ec40
; We're ESP port2, so examine port1 ComInfo
ec30: cmp [di].pi_port1,0 ; does other port exist?
je ec50 ; no, pop di, pop si and release irq
mov si,[di].pi_port1
; (si) -> ComInfo pointer for "other" port on ESP board.
ec40: test [si].ci_eflags,EF_MODE_ENHANCED ; other port enhanced?
jz ec50 ; no, pop di, pop si and release irq
cmp [si].ci_nopens,0 ; other port open?
je ec50 ; no, pop di, pop si and release irq
; OK, now we know the other ESP port on this board is still using
; the irq, so don't release the irq.
pop si
jmp ec60
; OK, now we know the other ESP port on this board is NOT using
; the irq, so we will release the irq.
ec50: xor bh,bh
mov bl,[di].pi_irq
mov dl,DevHlp_UnSetIRQ
; Do fancy segment swapping so DevHlp is called with DS set to
; driver's resident data segment.
setES DSEG ; ES = segment for DevHlp ptr
setDS HSEG ; DS = driver's resident data seg
call es:[DevHlp]
setDS DSEG ; restore DS
RestoreReg <si>
CLR [di].pi_flagx,PIF_ONE_HAS_IRQ
jnc ec60
ComErr <ComClose : could not release the IRQ>,CALLFAR
; Now that the IRQ is released, the ISR won't run again, so we can
; clear PIF_PECAN_BUSY.
ec60: mov di,[si].ci_pinfo
CLR [di].pi_flagx,PIF_PECAN_BUSY
; If we're the only enhanced port left open, we can free the DMA LID
; entry we've been using to talk to ABIOS.
cmp kernel_type,ABIOS_COM
jne ec70
dec ports_using_DMA_lid
jnz ec70
mov ax,DMA_lid
mov dl,DevHlp_FreeLIDEntry
; Do fancy segment swapping so DevHlp is called with DS set to
; driver's resident data segment.
setES DSEG ; ES = segment for DevHlp ptr
setDS HSEG ; DS = driver's resident data seg
call es:[DevHlp]
ec70:
RestoreReg <es,ds>
ret
EndProc E_Close
;** E_WStat
;
; Answers the question: can the enhanced port transmit?
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT 'C' clear if CAN transmit
; 'C' set if CAN'T transmit
Procedure E_WStat,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
.386
GetErrorStatus ; (al) = error1; (ah) = error2
bt ah,ESP_ERR2_ONLOCAL ; (ah) = error2
; carry set if busy, carry clear if able to transmit
ret
EndProc E_WStat
;** E_RFlush
;
; Sends ESP command to clear receive FIFOs
;
; ENTRY (ds:si) -> ComInfo
;
Procedure E_RFlush,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
; Flush ESP's buffers, and he'll enable remote transmitter.
FlushRxFIFO
ret
EndProc E_RFlush
;** E_HHS - compute hardware handshake signals for enhanced port
;
; E_HHS sets up ESP for appropriate flow control type for this port
;
; May raise or lower DTR or RTS depending on flags1 and flags2
; and the previous values of flags1 and flgas2.
;
; Set hhslines and outhhslines depending on flags1 and flags2.
;
; ENTRY (ds:si) -> ComInfo
; (bl) = previous flags1
; (bh) = previous flags2
;
; EXIT
;
; USES ax bx dx
Procedure E_HHS,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
SaveReg <bx>
; process DTR
and bl,F1_DTR_MASK ; (bl) = old DTR bits
mov ah,[si].ci_dcb_flags1 ; (ah) = flags1
and ah,F1_DTR_MASK ; (ah) = new DTR bits
cmp ah,bl
je ehh20 ; no change to DTR, do RTS
test ah,F1_DTR_FLOW
jnz ehh10 ; DTR is handshake line
; enable/disable DTR
CLR [si].ci_esp_flow1,ESP_FC1_RX_DTR ; ESP does NOT use DTR
test ah,F1_DTR_ENABLE
jz ehh5
SET [si].ci_esp_flow1,ESP_FC1_ON_DTR ; enable DTR
jmp SHORT ehh20 ; finished with DTR, do RTS
ehh5: CLR [si].ci_esp_flow1,ESP_FC1_ON_DTR ; disable DTR
jmp SHORT ehh20 ; finished with DTR, do RTS
; DTR is handshake line
ehh10: SET [si].ci_esp_flow1,ESP_FC1_RX_DTR ; ESP uses DTR
CLR [si].ci_esp_flow1,ESP_FC1_ON_DTR ; ESP does NOT use DTR
; process RTS
ehh20: and bh,F2_RTS_MASK ; (bh) = old RTS bits
mov ah,[si].ci_dcb_flags2 ; (ah) = flags2
and ah,F2_RTS_MASK ; (ah) = new RTS bits
cmp ah,bh
je ehh40 ; no change to RTS, do XOFF
cmp ah,F2_RTS_FLOW
je ehh30 ; RTS is handshake line
; enable/disable RTS
CLR [si].ci_esp_flow1,ESP_FC1_RX_RTS ; ESP does NOT use RTS
; if RTS toggling, turn off RTS for now
cmp ah,F2_RTS_TOGGLE
je ehh25
test ah,F2_RTS_ENABLE
jz ehh25
SET [si].ci_esp_flow1,ESP_FC1_ON_RTS ; enable RTS
jmp SHORT ehh40 ; finished with RTS, do XOFF
ehh25: CLR [si].ci_esp_flow1,ESP_FC1_ON_RTS ; disable RTS
jmp SHORT ehh40 ; finished with RTS, do XOFF
; RTS is handshake line
ehh30: SET [si].ci_esp_flow1,ESP_FC1_RX_RTS; ESP uses RTS
CLR [si].ci_esp_flow1,ESP_FC1_ON_RTS
; process input XON/XOFF
ehh40: RestoreReg <bx> ; (bl) = previous flags1,
; (bh) = previous flags2
SaveReg <bx>
mov bl,bh ; (bl) = (bh) = previous flags2
mov ah,[si].ci_dcb_flags2 ; (ah) = flags2
and ah,F2_IN_XO ; (ah) = new input XON bit
and bh,F2_IN_XO ; (bh) = old input XON bit
cmp ah,bh
je ehh50 ; no change to input XON,
; do output XON
test ah,F2_IN_XO
jz ehh45
SET [si].ci_esp_flow1,ESP_FC1_RX_XO ; ESP uses input XON/XOFF
jmp SHORT ehh50
ehh45: CLR [si].ci_esp_flow1,ESP_FC1_RX_XO ; ESP does NOT use input XON/XOFF
; process output XON/XOFF
ehh50: mov ah,[si].ci_dcb_flags2 ; (ah) = flags2
and ah,F2_OUT_XO ; (ah) = new output XON bit
and bl,F2_OUT_XO ; (bl) = old output XON bit
cmp ah,bl
je ehh60 ; no change to output XON, do CTS
test ah,F2_OUT_XO
jz ehh55
SET [si].ci_esp_flow1,ESP_FC1_TX_XO ; ESP uses output XON/XOFF
jmp SHORT ehh60
ehh55: CLR [si].ci_esp_flow1,ESP_FC1_TX_XO ; ESP does NOT use output XON/XOFF
; process CTS
ehh60: RestoreReg <bx> ; (bl) = previous flags1,
; (bh) = previous flags2
SaveReg <bx>
mov bh,bl ; (bh) = (bl) = previous flags1
mov ah,[si].ci_dcb_flags1 ; (ah) = flags1
and ah,F1_OUT_CTS_FLOW ; (ah) = new CTS bits
and bl,F1_OUT_CTS_FLOW ; (bl) = old CTS bits
cmp ah,bl
je ehh70 ; no change to CTS, do DSR
test ah,F1_OUT_CTS_FLOW
jz ehh65
SET [si].ci_esp_flow2,ESP_FC2_TX_CTS; ESP uses CTS
jmp SHORT ehh70
ehh65: CLR [si].ci_esp_flow2,ESP_FC2_TX_CTS; ESP does not use CTS
; process DSR
ehh70: mov ah,[si].ci_dcb_flags1 ; (ah) = flags1
and ah,F1_OUT_DSR_FLOW ; (ah) = new DSR bits
and bh,F1_OUT_DSR_FLOW ; (bl) = old DSR bits
cmp ah,bh
je ehh80 ; no change DSR
test ah,F1_OUT_DSR_FLOW
jz ehh75
SET [si].ci_esp_flow2,ESP_FC2_TX_DSR; ESP uses DSR
jmp SHORT ehh80
ehh75: CLR [si].ci_esp_flow2,ESP_FC2_TX_DSR; ESP does not use DSR
; Finally ready to tell ESP the proper flow control type
ehh80:
mov ah,[si].ci_esp_flow1
mov al,[si].ci_esp_flow2
SetFCType ah,al
; If XON/XOFF chosen, must tell ESP flow control characters to use
test [si].ci_dcb_flags2,F2_OUT_XO
jnz ehh83 ; using XON/XOFF
test [si].ci_dcb_flags2,F2_IN_XO
jnz ehh83 ; using XON/XOFF
jmp SHORT ehh85 ; not using XON/XOFF
; Set ESP flow control characters. Last 3 ESP parameters are only used
; if xparent flow control is selected, but must send them anyway.
ehh83: mov ah,[si].ci_dcb_XonChar
mov al,[si].ci_dcb_XoffChar
SetFCChar ah,al,DLE,XMASK,PMASK
ehh85: RestoreReg <bx> ; (bl) = previous flags1
; (bh) = previous flags2
SaveReg <bx>
mov bl,bh ; (bl) = (bh) = previous flags1
; process DSR sensitivity and DCD handshaking
xor cx,cx
mov al,[si].ci_dcb_flags1
and al,F1_OUT_DCD_FLOW
and bl,F1_OUT_DCD_FLOW
cmp bl,al
jne ehh100
mov ah,[si].ci_dcb_flags1
and ah,F1_IN_DSR_SENSE
and bh,F1_IN_DSR_SENSE
cmp bh,ah
je ehh130
ehh100: test [si].ci_dcb_flags1,F1_OUT_DCD_FLOW
jz ehh105
mov cl,ESP_ERR1_MSR
jmp SHORT ehh110
ehh105: xor cl,cl
ehh110: SET [si].ci_flagx,FX_IN_DSR_OK ; assume no DSR sensitivity
test [si].ci_dcb_flags1,F1_IN_DSR_SENSE
jz ehh120
SaveReg <cx>
GetUARTStatus ; (al) = LSR; (ah) = MSR
RestoreReg <cx>
SET [si].ci_flagx,FX_IN_DSR_OK
test ah,MS_DSR
jnz ehh115
CLR [si].ci_flagx,FX_IN_DSR_OK
ehh115: mov ch,ESP_ERR1_MSR
jmp SHORT ehh125
ehh120: xor ch,ch
ehh125: or cl,ch
ehh130: or cl,ESP_DEF_ERR1
SetErrorMask cl,ESP_DEF_ERR2
RestoreReg <bx> ; (bl) = previous flags1
; (bh) = previous flags2
ret
EndProc E_HHS
;** E_SetLineC - set line control values for an enhanced port
;
; E_SetLineC sets the byte size, parity and number of stop bits
; according to the value in (al).
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT
;
Procedure E_SetLineC,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
SaveReg <ax>
WriteToUART R_LINEC,al
RestoreReg <ax>
ret
EndProc E_SetLineC
;** E_SetBaud - set the baud rate for an enhanced port
;
; SetBaud verifies that the baud rate is within the valid
; baud range and can be supported within +-.01% (except 110
; baud @ +.026% error, and 2000 baud @ -.69% error)
; Converts the baud rate into the format necesary
; by the hardware and sets the rate.
; Also sends ESP commands to set trigger level and receive timeout value
;
; ENTRY (ds:si) -> ComInfo
; (ax) = baud rate
;
; EXIT if 'C' clear
; ci_baud = baud rate
; divisor latch set in hardware
; else
; invalid baud rate
;
; USES ax bx cx dx flags
Procedure E_SetBaud,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
; Enhanced port: Tell ESP to set baud, trigger level and receive
; timeout.
SaveReg <bx>
ChangeBaud ch,cl ; give ESP divisor, he sets baud
RestoreReg <bx>
mov ax,bx
mov [si].ci_baud,ax
; Also change trigger level when we change baud rates, so that
; RxFIFO trigger happens at least every 0.1 second. If baud rate
; is above 19200, more than 256 characters will come in during 0.1
; second, and ESP suggests a trigger <= 256.
cmp ax,19200
jbe esb55
mov ax,255
jmp SHORT esb70
esb55: mov cl,100 ; 10 bits in a char
; (ax) = baud = dividend; (cl) = 100 = divisor
div cl
; now (al) = quotient = new trigger level
xor ah,ah ; Because we know trigger level is < 256
esb70: mov [si].ci_rx_trigger,ax ; save new trigger level
SetTriggers ah, al, HIGH(ESP_DEF_TRIGGER_TX), LOW(ESP_DEF_TRIGGER_TX)
; Change Receive Char Timeout to about 4 character times. However,
; ESP only allows timeout between 2 msec and 239 msec, so for
; baud < 300 use max timeout and for baud >= 19200 use min timeout.
cmp [si].ci_baud,300
jae esb74
mov al,239
jmp SHORT esb80
esb74: cmp [si].ci_baud,19200
jb esb78
mov al,4
jmp SHORT esb80
esb78: mov ax,40000 ; dividend
xor dx,dx
div [si].ci_baud ; quotient goes into ax
esb80: SetRxTimeout al
CALLFAR ComputeWTO ; re-compute write timeout value
CALLFAR ComputeRTO ; re-compute read timeout value
clc ; valid baud rate
ret
EndProc E_SetBaud
;** E_ShutDownPort - shut down an enhanced com port if it was open
;
; if the port is open
; turn off ESP interrupts from this port
; UnsetIRQ
;
; ENTRY (ds:si) -> ComInfo of port to shut down
;
; EXIT NONE
;
Procedure E_ShutDownPort,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
; Enhanced port: tell ESP to ignore interrupts from our port,
mov bx,[si].ci_pinfo
mov al,[bx].pi_svcmask
cmp [si].ci_cmd_offset,0
jne esd12
CLR al,ESP_SID_PORT1
jmp SHORT esd13
esd12: CLR al,ESP_SID_PORT2
esd13: mov [bx].pi_svcmask,al ; save new svc mask
SetSvcMask al
; Can't release IRQ unless we determine that other ESP port
; is closed.
mov bx,[si].ci_pinfo
mov al,[si].ci_cmd_offset ; are we ESP port1 or port2?
or al,al
jnz esd15
; we're ESP port1, examine port2 ComInfo
cmp [bx].pi_port2,0 ; does other port even exist?
je esstc ; no, release IRQ
SaveReg <si> ; save original ComInfo ptr
mov si,[bx].pi_port2 ; (si) -> ComInfo for port2
cmp [si].ci_nopens,0 ; other ESP port still open?
RestoreReg <si> ; restore original ComInfo ptr
jne esclc ; don't release IRQ
jmp esstc ; release IRQ
; we're ESP port2, examine port1 ComInfo
esd15: cmp [bx].pi_port1,0 ; does other port even exist?
je esstc ; no, release IRQ
SaveReg <si> ; save original ComInfo ptr
mov si,[bx].pi_port1 ; (si) -> ComInfo for port2
cmp [si].ci_nopens,0 ; other ESP port still open?
RestoreReg <si> ; restore original ComInfo ptr
jne esclc ; don't release IRQ
esstc: stc ; tell caller to release IRQ
ret
esclc: clc ; tell caller NOT to release IRQ
ret
EndProc E_ShutDownPort
;** E_SetModemC - set Modem Control register for enhanced port
;
; ENTRY (ds:si) -> ComInfo
; bh = bits to turn off
; bl = bits to turn on
;
; EXIT NONE
Procedure E_SetModemC,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
; (bh) = bits to turn off, (bl) = bits to turn on
mov cl,4
rol bh,cl ; adjust MCR bit position to same as
; ESP flow control bit position
or [si].ci_esp_flow1,bl ; turn ON desired bits.
rol bl,cl ; adjust MCR bit position to same as
; ESP flow control bit position.
and [si].ci_esp_flow1,bh ; turn OFF desired bits.
mov ah,[si].ci_esp_flow1
mov al,[si].ci_esp_flow2
SetFCType ah,al ; Use SetFCType ESP commmand to set MCR
ret
EndProc E_SetModemC
;** E_TxBytes - get bytes available in ESP's transmit FIFO
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT (ax) = bytes available in ESP transmit FIFO
Procedure E_TxBytes,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
GetTxBytes
xchg ah,al ; (ax) = bytes avail in ESP's TxFIFO
ret
EndProc E_TxBytes
;** E_GetMCR - get Modem Control register for enhanced port
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT (al) = MCR
Procedure E_GetMCR,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
ReadFromUART R_MODMC
ret ; (al) = MCR
EndProc E_GetMCR
;** E_GetMSR - get Modem Status register for enhanced port
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT (al) = MSR
Procedure E_GetMSR,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
GetUARTStatus ; (al) = LSR, (ah) = MSR
xchg ah,al ; (al) = MSR
ret
EndProc E_GetMSR
;** E_GetLSR - get Line Status register for enhanced port
;
; ENTRY (ds:si) -> ComInfo
;
; EXIT (al) = LSR
Procedure E_GetLSR,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
GetUARTStatus ; (al) = LSR, (ah) = MSR
ret
EndProc E_GetLSR
;** E_GetLSR - transmit byte immediately from enhanced port
;
; ENTRY (ds:si) -> ComInfo
; (al) = data byte
Procedure E_TxImm,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
; (al) = data byte to transmit immediately
WriteToUART R_DATA,al
ret
EndProc E_TxImm
;** E_Xoff - behave as if XOFF received for enhanced port
;
; ENTRY (ds:si) -> ComInfo
Procedure E_Xoff,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
; Tell ESP to stop transmitting
SaveReg <es,di>
LocalXoff
RestoreReg <di,es>
SET [si].ci_HSFlag,HS_FLOW_OFF_LOCAL
test [si].ci_dcb_flags2,F2_OUT_XO OR F2_IN_XO
jz eoffx
SET [si].ci_HSFlag,HS_XOFF_RECEIVED
eoffx: ret
EndProc E_Xoff
;** E_Xon - behave as if XON received for enhanced port
;
; ENTRY (ds:si) -> ComInfo
Procedure E_Xon,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
; Tell ESP to start transmitting
SaveReg <es,di>
LocalXon
RestoreReg <di,es>
CLR [si].ci_HSFlag,HS_FLOW_OFF_LOCAL
test [si].ci_dcb_flags2,F2_OUT_XO OR F2_IN_XO
jz eonx
CLR [si].ci_HSFlag,HS_XOFF_RECEIVED
eonx: ret
EndProc E_Xon
;** E_BreakOn - start transmitting break for enhanced port
;
; ENTRY (ds:si) -> ComInfo
Procedure E_BreakOn,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
SendBreak 0 ; hold line until Break Off cmd
ret
EndProc E_BreakOn
;** E_BreakOff - stop transmitting break for enhanced port
;
; ENTRY (ds:si) -> ComInfo
Procedure E_BreakOff,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
SendBreak 1 ; 10ms break, then ESP will stop
ret
EndProc E_BreakOff
;** E_EnableRxFIFO - enable RxFIFO interrupts for enhanced port
;
; ENTRY (ds:si) -> ComInfo
Procedure E_EnableRxFIFO,FAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
mov di,[si].ci_pinfo
cmp [si].ci_cmd_offset,0
jne rdq60
SET [di].pi_svcmask,ESP_SID_RX1
jmp SHORT rdq70
rdq60: SET [di].pi_svcmask,ESP_SID_RX2
rdq70:
mov [si].ci_rx_state,RX_STATE_OK
mov dx,[di].pi_address
; Disable ALL ints while re-enabling ESP interrupts
CLI
rdq72: in al,dx
test al,ESP_RDY_CMD1
jz rdq72
add dx,ESP_R_CMD1-ESP_R_RDY
mov al,ESP_CMD_SETSVCMASK
add al,[si].ci_cmd_offset
out dx,al
add dx,ESP_R_RDY-ESP_R_CMD1
rdq73: in al,dx
test al,ESP_RDY_CMD2
jz rdq73
add dx,ESP_R_CMD2-ESP_R_RDY
mov al,[di].pi_svcmask
out dx,al
; Issue GetDips to be *SURE* that ESP has processed SetSvcMask before
; we re-enable interrupts
mov dx,[di].pi_address
rdq74: in al,dx
test al,ESP_RDY_CMD1
jz rdq74
add dx,ESP_R_CMD1-ESP_R_RDY
mov al,ESP_CMD_GDIPS
out dx,al
add dx,ESP_R_RDY-ESP_R_CMD1
rdq76: in al,dx
test al,ESP_RDY_STATUS1
jz rdq76
add dx,ESP_R_STATUS1-ESP_R_RDY
in al,dx
; Re-enable ALL interrupts.
STI
ret
EndProc E_EnableRxFIFO
;** TriggerTX - turn on/off TxFIFO interrupt for enhanced port
;
; ENTRY (ds:si) -> ComInfo
;
; ESP interrupt handler needs NEAR call, but WriteTick (in CSEG) needs FAR call
Procedure TriggerTX,HYBRID
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
mov di,[si].ci_pinfo
mov al,[di].pi_svcmask
; Must keep transmit int enabled if waiting on tx empty -- if not,
; how will we know when tx goes empty?
test [si].ci_flagx,FX_WAITING_TX_EMPTY
jnz ictx5
cmp [si].ci_w_rp._hi,0 ; no request packet
je ictx20
; enable transmit interrupts
ictx5: cmp [si].ci_cmd_offset,0
jne ictx10
; enable TxFIFO for port1
SET al,ESP_SVC_MASK_TX1
jmp SHORT ictx15
; enable TxFIFO for port2
ictx10: SET al,ESP_SVC_MASK_TX2
ictx15: clc ; 'C' clear - TX enabled
jmp SHORT ictx40
ictx20: ; disable transmit interrupts
cmp [si].ci_cmd_offset,0
jne ictx30
; disable TxFIFO for port1
CLR al,ESP_SVC_MASK_TX1
; if TxFIFO int was pending in SID, issuing new service mask will
; clear it, so update sid
; CLR [di].pi_sid,ESP_SID_TX1
jmp SHORT ictx35
; disable TxFIFO for port2
ictx30: CLR al,ESP_SVC_MASK_TX2
; if TxFIFO int was pending in SID, issuing new service mask will
; clear it, so update sid
; CLR [di].pi_sid,ESP_SID_TX2
ictx35: stc ; 'C' set - TX disabled
; Don't issue ESP SetSvcMask command unless "new" one in AL
; differs from "current" one in [di].pi_svcmask
ictx40: cmp al,[di].pi_svcmask
je ttx ; don't issue command
mov [di].pi_svcmask,al ; save new svcmask
pushf ; save carry flag
mov dx,[si].ci_esp_address ; (dx) -> ready reg
ictx50: in al,dx
test al,ESP_RDY_CMD1
jz ictx50
add dx,ESP_R_CMD1-ESP_R_RDY ; (dx) -> cmd1 reg
mov al,ESP_CMD_SETSVCMASK
add al,[si].ci_cmd_offset
out dx,al
add dx,ESP_R_RDY-ESP_R_CMD1 ; (dx) -> ready reg
ictx60: in al,dx
test al,ESP_RDY_CMD2
jz ictx60
add dx,ESP_R_CMD2-ESP_R_RDY ; (dx) -> cmd2 reg
mov al,[di].pi_svcmask ; (al) = new svc mask
out dx,al
popf ; restore carry flag for caller
ttx: ret
EndProc TriggerTX
; ** IssueESPCmd
;
; ENTRY (ds:si) -> ComInfo
; [si].ci_parm_area.cmd_code = command
; [si].ci_parm_area.num_writes = how many parameters to
; write to ESP
; [si].ci_parm_area.writes = array of parameters to write
; [si].ci_parm_area.num_reads = how many status bytes to
; read from ESP
;
; EXIT [si].ci_parm_area.reads = array of status bytes read from ESP
;
; USES ax,bx,cx,dx,si,di
;
; WARNING - IssueESPCmd declared NEAR, so don't call except from E_CSEG!
Procedure IssueESPCmd,NEAR
ASSUME cs:E_CSEG,ds:DSEG,es:NOTHING,ss:NOTHING
CLI
mov dx,[si].ci_esp_address ; (dx) -> ready reg
foo1: in al,dx ; wait for cmd1 ready
test al,ESP_RDY_CMD1
jz foo1
mov al,[si].ci_parm_area.cmd_code
add dx,ESP_R_CMD1-ESP_R_RDY ; (dx) -> cmd1 reg
out dx,al ; out cmd1
mov cl,[si].ci_parm_area.num_writes
or cl,cl ; jump around if no data
jz foo3 ; bytes to send out
xor ch,ch ; set up for loop
xor bx,bx
add dx,ESP_R_RDY-ESP_R_CMD1 ; (dx) -> ready reg
foo2: in al,dx
test al,ESP_RDY_CMD2 ; wait for cmd2 ready
jz foo2
add dx,ESP_R_CMD2-ESP_R_RDY ; (dx) -> cmd2 reg
mov al,[si].ci_parm_area.writes+[bx]
out dx,al ; out next data byte
inc bx
add dx,ESP_R_RDY-ESP_R_CMD2 ; (dx) -> ready reg
loop foo2
foo3: mov cl,[si].ci_parm_area.num_reads
or cl,cl ; jump around if not data
jz foo6 ; bytes to get
mov dx,[si].ci_esp_address
add dx,ESP_R_RDY ; (dx) -> ready reg
foo4: in al,dx
test al,ESP_RDY_STATUS1 ; wait for status1 ready
jz foo4
add dx,ESP_R_STATUS1-ESP_R_RDY ; (dx) -> status1 reg
in al,dx
mov [si].ci_parm_area.reads,al ; store data byte
cmp cl,2 ; get another?
jne foo6
add dx,ESP_R_RDY-ESP_R_STATUS1 ; (dx) -> ready reg
foo5: in al,dx
test al,ESP_RDY_STATUS2 ; wait for status2 ready
jz foo5
add dx,ESP_R_STATUS2-ESP_R_RDY ; (dx) -> status2 reg
in al,dx
mov [si].ci_parm_area.reads+1,al ; store data byte
foo6:
STI
ret
EndProc IssueESPCmd
E_CSEG ENDS
END