home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Power-Programmierung
/
CD1.mdf
/
lan
/
drivrs30
/
wd8003e.asm
< prev
next >
Wrap
Assembly Source File
|
1989-06-08
|
25KB
|
767 lines
version equ 2
include defs.asm
; PC/FTP Packet Driver source, conforming to version 1.05 of the spec
; Updated to version 1.08 Feb. 17, 1989 by Russell Nelson.
; Robert C Clements, K1BC, August 19, 1988
; Portions (C) Copyright 1988 Robert C Clements
; This program is free software; you can redistribute it and/or modify
; it under the terms of the GNU General Public License as published by
; the Free Software Foundation, version 1.
;
; This program is distributed in the hope that it will be useful,
; but WITHOUT ANY WARRANTY; without even the implied warranty of
; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
; GNU General Public License for more details.
;
; You should have received a copy of the GNU General Public License
; along with this program; if not, write to the Free Software
; Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
code segment byte public
assume cs:code, ds:code
HT equ 09h
CR equ 0dh
LF equ 0ah
;
; Packet Driver Error numbers
BAD_HANDLE equ 1 ;invalid handle number
NO_CLASS equ 2 ;no interfaces of specified class found
NO_TYPE equ 3 ;no interfaces of specified type found
NO_NUMBER equ 4 ;no interfaces of specified number found
BAD_TYPE equ 5 ;bad packet type specified
NO_MULTICAST equ 6 ;this interface does not support
CANT_TERMINATE equ 7 ;this packet driver cannot terminate
BAD_MODE equ 8 ;an invalid receiver mode was specified
NO_SPACE equ 9 ;operation failed because of insufficient
TYPE_INUSE equ 10 ;the type had previously been accessed,
BAD_COMMAND equ 11 ;the command was out of range, or not
CANT_SEND equ 12 ;the packet couldn't be sent (usually
; Stuff specific to the Western Digital WD003E Ethernet controller board
; C version by Bob Clements, K1BC, May 1988 for the KA9Q TCP/IP package
; Symbol prefix "EW" is for Ethernet, Western-digital card
; The EW registers - First, the board registers */
EW_CMD equ 000h ; Board's command register
EW_SAPROM equ 008h ; Window on station addr prom
; The EW registers - Next, the DS8390 chip registers */
; There are two (really 3) pages of registers in the chip. You select
; which page you want, then address them at offsets 10-1F from base.
; The chip command register (EW_CCMD) appears in both pages.
EW_CCMD equ 010h ; Chip's command register
; Page 0
EW0_STARTPG equ 011h ; Starting page of ring bfr
EW0_STOPPG equ 012h ; Ending page +1 of ring bfr
EW0_BOUNDARY equ 013h ; Boundary page of ring bfr
EW0_TSR equ 014h ; Transmit status reg
EW0_TPSR equ 014h ; Transmit starting page
EW0_TCNTLO equ 015h ; Low byte of tx byte count
EW0_TCNTHI equ 016h ; High byte of tx byte count
EW0_ISR equ 017h ; Interrupt status reg
EW0_RCNTLO equ 01ah ; Remote byte count reg
EW0_RCNTHI equ 01bh ; Remote byte count reg
EW0_RXCR equ 01ch ; RX control reg
EW0_TXCR equ 01dh ; TX control reg
EW0_COUNTER0 equ 01dh ; Rcv alignment error counter
EW0_DCFG equ 01eh ; Data configuration reg
EW0_COUNTER1 equ 01eh ; Rcv CRC error counter
EW0_IMR equ 01fh ; Interrupt mask reg
EW0_COUNTER2 equ 01fh ; Rcv missed frame error counter
; Page 1
EW1_PHYS equ 011h ; This board's physical enet addr
EW1_CURPAG equ 017h ; Current memory page
EW1_MULT equ 018h ; Desired multicast addr
; Board commands in EW_CMD
EW_RESET equ 080h ; Reset the board
EW_MEMEN equ 040h ; Enable the shared memory
EW_MEM_MASK equ 03fh ; B18-B13 of address of the shared memory
; Chip commands in EW_CCMD
EWC_STOP equ 001h ; Stop the chip
EWC_START equ 002h ; Start the chip
EWC_TRANS equ 004h ; Transmit a frame
EWC_NODMA equ 020h ; No remote DMA used on this card
EWC_PAGE0 equ 000h ; Select page 0 of chip registers
EWC_PAGE1 equ 040h ; Select page 1 of chip registers
; Commands for RX control reg
EWRXCR_MON equ 020h ; Monitor mode
EWRXCR_BCST equ 004h ; Accept broadcasts
; Commands for TX control reg
EWTXCR_LOOP equ 002h ; Set loopback mode
; Bits in EW0_DCFG - Data config register
EWDCFG_BM8 equ 048h ; Set burst mode, 8 deep FIFO
; Bits in EW0_ISR - Interrupt status register
EWISR_RX equ 001h ; Receiver, no error
EWISR_TX equ 002h ; Transmitter, no error
EWISR_RX_ERR equ 004h ; Receiver, with error
EWISR_TX_ERR equ 008h ; Transmitter, with error
EWISR_OVER equ 010h ; Receiver overwrote the ring
EWISR_COUNTERS equ 020h ; Counters need emptying
EWISR_RESET equ 080h ; Reset completed
EWISR_ALL equ 03fh ; Interrupts we will enable
; Bits in received packet status byte and EW0_RSR
EWPS_RXOK equ 001h ; Received a good packet
; Bits in TX status reg
EWTSR_COLL equ 004h ; Collided at least once
EWTSR_COLL16 equ 008h ; Collided 16 times and was dropped
EWTSR_FU equ 020h ; TX FIFO Underrun
; Shared memory management parameters
XMIT_MTU equ 600h ; Largest packet we have room for.
SM_TSTART_PG equ 0 ; First page of TX buffer
SM_RSTART_PG equ 6 ; Starting page of ring
SM_RSTOP_PG equ 32 ; Last page +1 of ring
SM_BASE equ 0C400h ; Default para where shared memory starts
; Real value set at attach time.
; Description of header of each packet in receive area of shared memory
EW_RBUF_STAT equ 0 ; Received frame status
EW_RBUF_NXT_PG equ 1 ; Page after this frame
EW_RBUF_SIZE_LO equ 2 ; Length of this frame
EW_RBUF_SIZE_HI equ 3 ; Length of this frame
EW_RBUF_NHDR equ 4 ; Length of above header area
; End of WD8003E parameter definitions
; The following three values may be overridden from the command line.
; If they are omitted from the command line, these defaults are used.
public int_no, io_addr, mem_base
int_no db 2,0,0,0 ; Interrupt level
io_addr dw 0280h,0 ; I/O address for card (jumpers)
mem_base dw 0c400h,0 ; Shared memory addr (software)
public driver_class, driver_type, driver_name
driver_class db 1 ;from the packet spec
driver_type db 14 ;from the packet spec
driver_name db 'WD8003E',0 ;name of the driver.
; send_pkt: - The Transmit Frame routine
public send_pkt
send_pkt:
;enter with ds:si -> packet, cx = packet length.
;exit with nc if ok, or else cy if error, dh set to error number.
assume ds:nothing
loadport ; Point at chip command register
setport EW_CCMD ; ..
tx_wait:
mov bx, 8000h ; Avoid infinite loop
in al, dx ; Get chip command state
test al,EWC_TRANS ; Is transmitter still running?
jz tx_idle ; Go if free
dec bx ; Count the timeout
jnz tx_wait ; Fall thru if TX is stuck
; Should count these error timeouts
; Maybe need to add recovery logic here
tx_idle:
cmp cx,XMIT_MTU ; Is this packet too large?
ja send_pkt_toobig
cmp cx, RUNT ; Is the frame long enough?
jnb tx_oklen ; Go if OK
mov cx, RUNT ; Stretch frame to minimum allowed
tx_oklen:
push cx ; Hold count for later
; Now compute destination of move in es:di
mov ax, mem_base ; Compute base of transmit buffer
; add ax, SM_TSTART_PG*16 ; The right page in mem (currently zero)
mov es, ax ; Paragraph of the TX buffer
xor di, di ; Fill starting at beginning of paragraph
call movemem
pop cx ; Get back count to give to board
loadport ; Base of I/O regs
setport EW0_TCNTLO ; Low byte of TX count
mov al, cl ; Get the count
out dx, al ; Tell card the count
setport EW0_TCNTHI ; High byte of TX count
mov al, ch ; Get the count
out dx, al ; Tell card the count
setport EW0_TPSR ; Transmit Page Start Register
mov al, SM_TSTART_PG
out dx, al ; Start the transmitter
setport EW_CCMD ; Chip command reg
mov al, EWC_TRANS+EWC_NODMA
out dx, al ; Start the transmitter
clc
ret ; End of transmit-start routine
send_pkt_toobig:
mov dh,NO_SPACE
stc
ret
movemem:
;does the same thing as "rep movsb", only 50% faster.
;moves words instead of bytes, and handles the case of both addresses odd
;efficiently. There is no way to handle one address odd efficiently.
;This routine always aligns the source address in the hopes that the
;destination address will also get aligned. This is from Phil Karn's
;code from ec.c, a part of his NET package. I bummed a few instructions
;out.
jcxz movemem_cnte ; If zero, we're done already.
test si,1 ; Does source start on odd byte?
jz movemem_adre ; Go if not
movsb ; Yes, move the first byte
dec cx ; Count that byte
movemem_adre:
shr cx,1 ; convert to word count
rep movsw ; Move the bulk as words
jnc movemem_cnte ; Go if the count was even
movsb ; Move leftover last byte
movemem_cnte:
ret
public get_address
get_address:
;get the address of the interface.
;enter with es:di -> place to get the address, cx = size of address buffer.
;exit with nc, cx = actual size of address, or cy if buffer not big enough.
assume ds:code
cmp cx, EADDR_LEN ; Caller wants a reasonable length?
jb get_addr_x ; No, fail.
mov cx, EADDR_LEN ; Yes. Set count for loop
loadport ; Base of device
setport EW_SAPROM ; Where the address prom is
cld ; Make sure string mode is right
get_addr_loop:
in al, dx ; Get a byte of address
stosb ; Feed it to caller
inc dx ; Next byte at next I/O port
loop get_addr_loop ; Loop over six bytes
mov cx, EADDR_LEN ; Tell caller how many bytes we fed him
clc ; Carry off says success
ret
get_addr_x:
stc ; Tell caller our addr is too big for him
ret
public set_address
set_address:
assume ds:nothing
;enter with ds:si -> Ethernet address, CX = length of address.
;exit with nc if okay, or cy, dh=error if any errors.
;
cmp cx,EADDR_LEN ;ensure that their address is okay.
je set_address_4
mov dh,BAD_ADDRESS
stc
jmp short set_address_done
set_address_4:
loadport
setport EW1_PHYS
set_address_1:
lodsb
out dx,al
inc dx
loop set_address_1
set_address_okay:
clc
set_address_done:
push cs
pop ds
assume ds:code
ret
public reset_interface
reset_interface:
assume ds:code
loadport ; Base of I/O regs
setport EW_CCMD ; Chip command reg
mov al, EWC_STOP+EWC_NODMA
out dx, al ; Stop the DS8390
setport EW0_ISR ; Interrupt status reg
mov al, 0ffh ; Clear all pending interrupts
out dx, al ; ..
setport EW0_IMR ; Interrupt mask reg
xor al, al ; Turn off all enables
out dx, al ; ..
ret
;called when we want to determine what to do with a received packet.
;enter with cx = packet length, es:di -> packet type.
;It returns with es:di = 0 if don't want this type or if no buffer available.
extrn recv_find: near
;called after we have copied the packet into the buffer.
;enter with ds:si ->the packet, cx = length of the packet.
extrn recv_copy: near
extrn count_in_err: near
extrn count_out_err: near
public recv
recv:
;called from the recv isr. All registers have been saved, and ds=cs.
;Actually, not just receive, but all interrupts come here.
;Upon exit, the interrupt will be acknowledged.
assume ds:code
check_isr: ; Was there an interrupt from this card?
loadport ; Point at interrupt status register
setport EW0_ISR ; ..
in al, dx ; Get pending interrupts
and al, EWISR_ALL ; Any?
jnz isr_test_overrun
jmp interrupt_done ; Go if none
; First, a messy procedure for handling the case where the rcvr
; over-runs its ring buffer. This is spec'ed by National for the chip.
isr_test_overrun:
test al,EWISR_OVER ; Was there an overrun?
jnz recv_overrun ; Go if so.
jmp recv_no_overrun ; Go if not.
recv_overrun:
setport EW_CCMD ; Stop the card
mov al, EWC_STOP+EWC_NODMA
out dx, al ; Write "stop" to command register
; Remove one frame from the ring
setport EW0_BOUNDARY ; Find end of this frame
in al, dx ; Get memory page number
inc al ; Page plus 1
cmp al, SM_RSTOP_PG ; Wrapped around ring?
jnz rcv_ovr_nwrap ; Go if not
mov al, SM_RSTART_PG ; Yes, wrap the page pointer
rcv_ovr_nwrap:
xor ah, ah ; Convert page to segment
mov cl, 4
mov bl, al ; Page number as arg to rcv_frm
shl ax, cl ; ..
add ax, mem_base ; Page in this memory
mov es, ax ; Segment pointer to the frame header
push es ; Hold this frame pointer for later
mov al, es:[EW_RBUF_STAT] ; Get the buffer status byte
test al,EWPS_RXOK ; Is this frame any good?
jz rcv_ovr_ng ; Skip if not
call rcv_frm ; Yes, go accept it
rcv_ovr_ng:
pop es ; Back to start of this frame
mov al, es:[EW_RBUF_NXT_PG] ; Get pointer to next frame
dec al ; Back up one page
cmp al, SM_RSTART_PG ; Did it wrap?
jge rcv_ovr_nwr2
mov al, SM_RSTOP_PG-1 ; Yes, back to end of ring
rcv_ovr_nwr2:
loadport ; Point at boundary reg
setport EW0_BOUNDARY ; ..
out dx, al ; Set the boundary
setport EW0_RCNTLO ; Point at byte count regs
xor al, al ; Clear them
out dx, al ; ..
setport EW0_RCNTHI
out dx, al
setport EW0_ISR ; Point at status reg
mov cx, 8000h ; Timeout counter
rcv_ovr_rst_loop:
in al, dx ; Is it finished resetting?
test al,EWISR_RESET ; ..
jnz rcv_ovr_rst ; Go if so
dec cx ; Loop til reset, or til timeout
jnz rcv_ovr_rst_loop
rcv_ovr_rst:
loadport ; Point at Transmit control reg
setport EW0_TXCR ; ..
mov al, EWTXCR_LOOP ; Put transmitter in loopback mode
out dx, al ; ..
setport EW_CCMD ; Point at Chip command reg
mov al, EWC_START+EWC_NODMA
out dx, al ; Start the chip running again
setport EW0_TXCR ; Back to TX control reg
xor al, al ; Clear the loopback bit
out dx, al ; ..
setport EW0_ISR ; Point at Interrupt status register
mov al, EWISR_OVER ; Clear the overrun interrupt bit
out dx, al ; ..
call count_in_err ; Count the anomaly
jmp check_isr ; Done with the overrun case
recv_no_overrun:
; Handle receive flags, normal and with error (but not overrun).
test al,EWISR_RX+EWISR_RX_ERR ; Frame received without overrun?
jnz recv_frame ; Go if so.
jmp recv_no_frame ; Go if not.
recv_frame:
loadport ; Point at Chip's Command Reg
setport EW_CCMD ; ..
mov al, EWC_NODMA+EWC_PAGE1
out dx, al ; Switch to page 1 registers
setport EW1_CURPAG ;Get current page of rcv ring
in al, dx ; ..
mov ah, al ; Hold current page in AH
setport EW_CCMD ; Back to page zero registers
mov al, EWC_NODMA+EWC_PAGE0
out dx, al ; Switch back to page 0 registers
setport EW0_BOUNDARY ;Get boundary page
in al, dx ; ..
inc al ; Step boundary from last used page
cmp al, SM_RSTOP_PG ; Wrap if needed
jne rx_nwrap3 ; Go if not
mov al, SM_RSTART_PG ; Wrap to first RX page
rx_nwrap3:
cmp al, ah ; Read all the frames?
je recv_frame_break ; Finished them all
mov bl, al ; Page number as arg to rcv_frm
xor ah, ah ; Make segment pointer to this frame
mov cl, 4 ; 16 * pages = paragraphs
shl ax, cl ; ..
add ax, mem_base ; That far into shared memory
mov es, ax ; Segment part of pointer
push es ; Hold on to this pointer for later
mov al, es:[EW_RBUF_STAT] ; Get the buffer status byte
test al,EWPS_RXOK ; Good frame?
jz recv_no_rcv
call rcv_frm ; Yes, go accept it
recv_no_rcv:
pop es ; Back to base of frame
mov al, es:[EW_RBUF_NXT_PG] ; Start of next frame
dec al ; Make previous page for new boundary
cmp al, SM_RSTART_PG ; Wrap around the bottom?
jge rcv_nwrap4
mov al, SM_RSTOP_PG-1 ; Yes
rcv_nwrap4:
loadport ; Point at the Boundary Reg again
setport EW0_BOUNDARY ; ..
out dx, al ; Set new boundary
jmp recv_frame ; See if any more frames
recv_frame_break:
loadport ; Point at Interrupt Status Reg
setport EW0_ISR ; ..
mov al, EWISR_RX+EWISR_RX_ERR+EWISR_OVER
out dx, al ; Clear those requests
jmp check_isr ; See if any other interrupts pending
recv_no_frame: ; Handle transmit flags.
test al,EWISR_TX+EWISR_TX_ERR ; Frame transmitted?
jnz isr_tx ; Go if so.
jmp isr_no_tx ; Go if not.
isr_tx:
mov ah, al ; Hold interrupt status bits
loadport ; Point at Transmit Status Reg
setport EW0_TSR ; ..
in al, dx ; ..
test ah,EWISR_TX ; Non-error TX?
jz isr_tx_err ; No, do TX error completion
test al,EWTSR_COLL16 ; Jammed for 16 transmit tries?
jz isr_tx_njam ; Go if not
call count_out_err ; Yes, count those
isr_tx_njam:
setport EW0_ISR ; Clear the TX complete flag
mov al, EWISR_TX ; ..
out dx, al ; ..
jmp isr_tx_done
isr_tx_err:
test al,EWTSR_FU ; FIFO Underrun?
jz isr_txerr_nfu
call count_out_err ; Yes, count those
isr_txerr_nfu:
loadport ; Clear the TX error completion flag
setport EW0_ISR ; ..
mov al, EWISR_TX_ERR ; ..
out dx, al ; ..
isr_tx_done:
; If TX queue and/or TX shared memory ring buffer were being
; used, logic to step through them would go here. However,
; in this version, we just clear the flags for background to notice.
jmp check_isr ; See if any other interrupts on
isr_no_tx:
; Now check to see if any counters are getting full
test al,EWISR_COUNTERS ; Interrupt to handle counters?
jnz isr_stat ; Go if so.
jmp isr_no_stat ; Go if not.
isr_stat:
; We have to read the counters to clear them and to clear the interrupt.
; The structure of the PC/FTP driver system doesn't give us
; anything useful to do with the data, though.
loadport ; Point at first counter
setport EW0_COUNTER0 ; ..
in al, dx ; Read the count, ignore it.
setport EW0_COUNTER1
in al, dx ; Read the count, ignore it.
setport EW0_COUNTER2
in al, dx ; Read the count, ignore it.
setport EW0_ISR ; Clear the statistics completion flag
mov al, EWISR_COUNTERS ; ..
out dx, al ; ..
isr_no_stat:
jmp check_isr ; Anything else to do?
interrupt_done:
ret
; Do the work of copying out a receive frame.
; Called with bl/ the page number of the frame header in shared memory/
; Also, es/ the paragraph number of that page.
rcv_frm:
; Old version checked size, memory space, queue length here. Now done
; in higher level code.
; Set cx to length of this frame.
mov ch, es:[EW_RBUF_SIZE_HI] ; Extract size of frame
mov cl, es:[EW_RBUF_SIZE_LO] ; Extract size of frame
sub cx, EW_RBUF_NHDR ; Less the header stuff
; Set es:di to point to Ethernet type field. es is already at base of
; page where this frame starts. Set di after the header and two addresses.
mov di, EW_RBUF_NHDR+EADDR_LEN+EADDR_LEN
push bx ; Save page number in bl
push cx ; Save frame size
push es
mov ax, cs ; Set ds = code
mov ds, ax
assume ds:code
call recv_find ; See if type and size are wanted
pop ds ; RX page pointer in ds now
assume ds:nothing
pop cx
pop bx
cld ; Copies below are forward, please
mov ax, es ; Did recv_find give us a null pointer?
or ax, di ; ..
je rcv_no_copy ; If null, don't copy the data
push cx ; We will want the count and pointer
push es ; to hand to client after copying,
push di ; so save them at this point
;; if ( (((size + 255 + EW_RBUF_NHDR) >> 8) + pg) > SM_RSTOP_PG){
mov ax, cx ; Length of frame
add ax, EW_RBUF_NHDR+255 ; Including the overhead bytes, rounded up
add ah, bl ; Compute page with last byte of data in ah
cmp ah, SM_RSTOP_PG ; Over the top of the ring?
jg rcopy_wrap ; Yes, move in two pieces
mov si, EW_RBUF_NHDR ; One piece, starts here in first page (in ds)
jmp rcopy_one_piece ; Go move it
rcopy_wrap:
;; Copy in two pieces due to buffer wraparound. */
;; n = ((SM_RSTOP_PG - pg) << 8) - EW_RBUF_NHDR; /* To top of mem */
mov ah, SM_RSTOP_PG ; Compute length of first part
sub ah, bl ; as all of the pages up to wrap point
xor al, al ; 16-bit count
sub ax, EW_RBUF_NHDR ; Less the four overhead bytes
sub cx, ax ; Move the rest in second part
push cx ; Save count of second part
mov cx, ax ; Count for first move
mov si, EW_RBUF_NHDR ; ds:si points at first byte to move
shr cx, 1 ; All above are even numbers, do words.
rep movsw ; Move first part of frame
mov ax, mem_base ; Paragraph of base of shared memory
mov ds, ax ; ..
mov si, SM_RSTART_PG*256 ; Offset to start of first receive page
pop cx ; Bytes left to move
rcopy_one_piece:
call movemem
pop si ; Recover pointer to destination
pop ds ; Tell client it's his source
pop cx ; And it's this long
assume ds:nothing
call recv_copy ; Give it to him
rcv_no_copy:
push cs ; Put ds back in code space
pop ds ; ..
assume ds:code
ret ; That's it for rcv_frm
;any code after this will not be kept after initialization.
end_resident label byte
public usage_msg
usage_msg db "usage: WD8003E <packet_int_no> <int_level> <io_addr> <mem_base>",CR,LF,'$'
public copyright_msg
copyright_msg db "Packet driver for Western Digital WD8003E, version ",'0'+majver,".",'0'+version,CR,LF
db "Portions Copyright 1988, Robert C. Clements, K1BC",CR,LF,'$'
no_board_msg:
db "WD8003E apparently not present at this address.",CR,LF,'$'
int_no_name db "Interrupt number ",'$'
io_addr_name db "I/O port ",'$'
mem_base_name db "Memory address ",'$'
extrn set_recv_isr: near
;enter with si -> argument string, di -> word to store.
;if there is no number, don't change the number.
extrn get_number: near
public parse_args
parse_args:
mov di,offset int_no
mov bx,offset int_no_name
call get_number
mov di,offset io_addr
mov bx,offset io_addr_name
call get_number
mov di,offset mem_base
mov bx,offset mem_base_name
call get_number
ret
bad_cksum:
mov dx,offset no_board_msg
mov ah,9
int 21h
stc
ret
public etopen
etopen: ; Initialize interface
loadport ; First, pulse the board reset
setport EW_CMD
mov al, EW_RESET
out dx, al ; Turn on board reset bit
xor al, al
out dx, al ; Turn off board reset bit
setport EW_CCMD ; DS8390 chip's command register
mov al, EWC_NODMA+EWC_PAGE0
out dx, al ; Switch to page zero
setport EW0_ISR ; Clear all interrupt flags
mov al, 0ffh ; ..
out dx, al ; ..
; Copy our Ethernet address from PROM into the DS8390
; (No provision in driver spec for setting a false address.)
setport EW_CCMD ; Chip command register
mov al, EWC_NODMA+EWC_PAGE1
out dx, al ; Switch to page one for writing eaddr
mov cl, EADDR_LEN ; Loop for six bytes
xor ch, ch ; Clear the index of bytes
xor bx, bx ; Clear the addr ROM checksum
cpy_adr_loop:
loadport ; Base of registers
setport EW_SAPROM ; Prom address
add dl, ch ; Plus which byte this is
in al, dx ; Get a byte of address
add bl,al ; Compute the checksum
add dl, EW1_PHYS-EW_SAPROM ; Point at reg in chip
out dx, al ; Copy that byte
inc ch ; Step the index
dec cl ; Count bytes
jnz cpy_adr_loop ; Loop for six
loadport ; Get last two bytes into cksum
setport EW_SAPROM+EADDR_LEN
in al, dx ; Get seventh byte
add bl, al ; Add it in
inc dx ; Step to eighth byte
in al, dx ; Get last byte
add bl, al ; Final checksum
cmp bl, 0ffh ; Correct?
jnz bad_cksum ; No, board is not happy
; Clear the multicast filter enables, we don't want any of them.
mov cl, 8 ; Eight bytes of multicast filter
xor al, al ; Zeros for filter
loadport ; Base of multicast filter locations
setport EW1_MULT ; ..
clr_mcast_l:
out dx, al ; Clear a byte
inc dl ; Step to next one
dec cl ; Count 8 filter locs
jnz clr_mcast_l ; ..
loadport ; Base of I/O regs
setport EW_CCMD ; Chip command register
mov al, EWC_NODMA+EWC_PAGE0
out dx, al ; Back to page zero
setport EW0_DCFG ; Configure the fifo organization
mov al, EWDCFG_BM8 ; Fifo threshold = 8 bytes
out dx, al
setport EW0_RCNTLO ; Clear the byte count registers
xor al, al ; ..
out dx, al
setport EW0_RCNTHI
out dx, al ; Clear high byte, too
setport EW0_RXCR ; Set receiver to monitor mode
mov al, EWRXCR_MON
out dx, al
setport EW0_TXCR ; Set transmitter mode to normal
xor al, al
out dx, al
; Turn on the shared memory block
setport EW_CMD ; Point at board command register
mov ax, mem_base ; Find where shared memory will be mapped
mov al, ah ; Shift to right location
sar al, 1 ; in the map control word
and al, EW_MEM_MASK ; Just these bits
or al, EW_MEMEN ; Command to turn on map
out dx, al ; Create that memory
; Set up control of shared memory, buffer ring, etc.
setport EW0_STARTPG ; Set receiver's first buffer page
mov al, SM_RSTART_PG
out dx, al
setport EW0_STOPPG ; and receiver's last buffer page + 1
mov al, SM_RSTOP_PG
out dx, al
setport EW0_BOUNDARY ; Set initial "last page we have emptied"
mov al, SM_RSTART_PG
out dx, al
setport EW_CCMD ; Switch to page one registers
mov al, EWC_NODMA+EWC_PAGE1
out dx, al
setport EW1_CURPAG ; Set current shared page for RX to work on
mov al, SM_RSTART_PG+1
out dx, al
setport EW_CCMD ; Switch back to page zero registers
mov al, EWC_NODMA+EWC_PAGE0
out dx, al
setport EW0_IMR ; Clear all interrupt enable flags
xor al, al
out dx, al
setport EW0_ISR ; Clear all interrupt assertion flags
mov al, 0ffh ; again for safety before making the
out dx, al ; interrupt be enabled
call set_recv_isr ; Put ourselves in interrupt chain
loadport
setport EW_CCMD ; Now start the DS8390
mov al, EWC_START+EWC_NODMA
out dx, al ; interrupt be enabled
setport EW0_RXCR ; Tell it to accept broadcasts
mov al, EWRXCR_BCST
out dx, al
setport EW0_IMR ; Tell card it can cause these interrupts
mov al, EWISR_ALL
out dx, al
mov dx,offset end_resident
clc
ret
code ends
end