home *** CD-ROM | disk | FTP | other *** search
- version equ 0
-
- ; Packet driver to simulate Ethernet on Novell IPX protocol.
- ;
- ; Paul Kranenburg
- ; Department of Computer Science
- ; University of Leiden
- ; Niels Bohrweg 1
- ; PO Box 9512
- ; 2300 RA Leiden
- ; The Netherlands
- ;
- ;
- ; File: ipxpkt.asm
- ;
- ; Compile with: tasm /ml (preserve case)
- ;
- ;
- ; General description:
- ;
- ; Take destination from the Ethernet packet and feed it to IPX
- ; in the Event Control Block Immediate Address field.
- ;
- ; IPX packets are 576 bytes at most, 30 are needed for the IPX header
- ; leaving 546 bytes of user data. Another 4 bytes are used to describe
- ; fragments.
- ; If NO_OF_SND_BUFS is set to 1, this yields an MTU for this driver of 528.
- ; (546 - 4 - sizeof(Ether header)[=14]).
- ;
- ; If NO_OF_SND_BUFS is set to 3, the Ethernet packet is broken into at most
- ; 3 fragments. These are tagged with a Fragment id and shipped.
- ;
- ; On reception, fragments are kept on a linked list ordered by fragment number
- ; and keyed by source node address and fragment id.
- ; An IPX event is scheduled to allow for timeout of pending reassembly queues.
- ;
- ; If all fragments are reassembled, the client is called to provide a buffer for
- ; the packet.
- ;
- ; [ To save on buffer space, the driver could conceivably do with some minimum
- ; number of buffers and call recv_find as soon as a fragment arrives, copy
- ; the contents, and only call recv_copy when all fragments have arrived. However,
- ; I don't think there is a way to notify the client in case a fragment gets lost.]
- ;
- ; In this code, the number of receive buffers (NO_OF_RCV_BUFS) has been set
- ; to 6 (a wild guess).
- ; This driver has yet to be tested in a gateway under heavy load. One probably
- ; needs more buffers in this case.
- ;
- ; Buffer space for the receive buffers is allocated after the "end_resident"
- ; label. There is a potential problem here: we start listening for packets
- ; using these buffers while still in the initialisation code, which is overlaid
- ; by the receive buffers. This is why interrupts are turned off wherever possible.
- ;
- ;
- ;
-
-
- include defs.asm
-
- MAX_IPX_LEN = 576 ; Maximum packet size that can be
- ; shipped through IPX
- IP_socket = 08061h ; Socket allocated (by me) for
- ; Blue book Ether on IPX
-
- PEP = 4 ; Packet Exchange Packet (ipx_type)
-
- ipx_header struc
- ipx_chksum dw ? ; Checksum, network byte order
- ipx_len dw ? ; Packet length, "
- ipx_prot db ? ; Transport protocol
- ipx_type db ? ; Packet type
- ipx_destnet db 4 dup(?) ; Destination network
- ipx_destnode db 6 dup(?) ; Destination node
- ipx_destsock dw ? ; Destination socket
- ipx_srcnet db 4 dup(?) ; Source network
- ipx_srcnode db 6 dup(?) ; Source node
- ipx_srcsock dw ? ; Source socket
- ipx_header ends
-
-
- frag_dscr struc
- frag_addr dd ? ; Fragment address
- frag_size dw ? ; Fragment size
- frag_dscr ends
-
- ecb struc
- ecb_link dd ? ;
- ecb_esr dd ? ; Event Service Routine
- ecb_inuse db ? ; In Use field
- ecb_cmplt db ? ; Completion Code
- ecb_sock dw ? ; Socket Number
- ecb_ipxwork db 4 dup (?) ; IPX reserved workspace
- ecb_drvwork db 12 dup (?) ; Driver reserved workspace
- ecb_ia db 6 dup (?) ; Immediate Address
- ecb_fragcnt dw ? ; Fragment count
- ;ecb_dscr = $ ; Start of Fragment descriptor list
- ecb ends
-
- aes_ecb struc
- aes_link dd ? ;
- aes_esr dd ? ; Event Service Routine
- aes_inuse db ? ; In Use field
- aes_work db 5 dup (?) ; Driver reserved workspace
- aes_ecb ends
-
-
- ether_frag struc
- ef_fragno db ? ; This fragment number
- ef_fragtot db ? ; Total number of fragments comprising the packet
- ef_fragid dw ? ; Fragment Id
- ether_frag ends
-
- ifdef ??Version
- queue_entry struc
- q_aes aes_ecb <> ; AES structure, used for reassembly timeouts
- q_count db 0 ; Number of fragments currently queued here
- q_node db 6 dup(?) ; Source node
- q_fragid dw ? ; Fragment Id
- q_len dw ? ; Total length of user data queued here
- q_ecb dd ? ; Ecb pointer to fragment
- queue_entry ends
- else
- queue_entry struc
- q_aes db (size aes_ecb) dup(?); AES structure, used for reassembly timeouts
- q_count db 0 ; Number of fragments currently queued here
- q_node db 6 dup(?) ; Source node
- q_fragid dw ? ; Fragment Id
- q_len dw ? ; Total length of user data queued here
- q_ecb dd ? ; Ecb pointer to fragment
- queue_entry ends
- endif
-
- ifdef ??Version
- u_buf struc
- u_ecb ecb <>
- u_ipx_frag frag_dscr <>
- u_frag_frag frag_dscr <>
- u_data_frag frag_dscr <>
- u_ipx ipx_header <>
- u_ether_frag ether_frag <>
- ;u_data LABEL BYTE
- u_buf ends
- else
- u_buf struc
- u_ecb db (size ecb) dup(?)
- u_ipx_frag db (size frag_dscr) dup(?)
- u_frag_frag db (size frag_dscr) dup(?)
- u_data_frag db (size frag_dscr) dup(?)
- u_ipx db (size ipx_header) dup(?)
- u_ether_frag db (size ether_frag) dup(?)
- ;u_data LABEL BYTE
- u_buf ends
- endif
-
- MAX_PAYLOAD = MAX_IPX_LEN - SIZE ipx_header - SIZE ether_frag
-
- print$ macro string
- ;---------------------------------------;
- ; sends $ terminated string to screen ;
- ;---------------------------------------;
- push dx
- mov ah,9
- mov dx,offset &string& ; print $ terminated string
- int 21h
- pop dx
- endm
-
- ; ipx function numbers
- OPEN_SOCKET = 0
- CLOSE_SOCKET = 1
- SEND_PACKET = 3
- LISTEN = 4
- SCHEDULE_EVENT = 5
- CANCEL_EVENT = 6
- SCHEDULE_SPECIAL_EVENT = 7
- GET_NODE_ADDRESS = 9
- RELINQUISH = 0Ah
-
- call_ipx macro opcode,reg1,reg2,reg3,reg4,reg5,reg6,reg7,reg8
- irp N, <reg1,reg2,reg3,reg4,reg5,reg6,reg7,reg8>
- ifnb <N>
- push N
- endif
- endm
- mov bx, opcode
- ;better be save here and use Code segment explicitly
- call cs:IPXentry
- irp N, <reg8,reg7,reg6,reg5,reg4,reg3,reg2,reg1>
- ifnb <N>
- pop N
- endif
- endm
- endm
-
-
- code segment byte public
- assume cs:code, ds:code
-
- IPXentry dd ?
- FragmentID dw ?
-
- NO_OF_FRAGMENTS = 3
- NO_OF_RCV_BUFS = 6
- NO_OF_SND_BUFS = 3
- NO_OF_QUEUES = NO_OF_RCV_BUFS ; ????
-
- reass_queues queue_entry NO_OF_QUEUES dup(<>)
-
- rcv_bufs u_buf NO_OF_RCV_BUFS dup(<>)
- snd_bufs u_buf NO_OF_SND_BUFS dup(<>)
-
- ;-------------------------------------------------------------------------------
- ;
- ; local functions
- ;
- ; A NOTE on style:
- ;
- ; the functions below seem to liberally load and reload pointers into
- ; a register pair involving the ds segment register.
- ; In fact, ds almost always contains the code segment as "assumed" above.
- ; Also, the distinction between pointers to ecb's and ubuf's / queue's is not made
- ; most of the time. This alright as long as the ecb structures remain the first
- ; ones declared in u_buf and queue.
- ; Need to work out a consistent register usage some day...
- ;
-
- find_queue proc near
- ;
- ; Find/allocate a queue-entry where an ether fragment can be stored.
- ; On entry: es:di -> source node address.
- ; dx == fragment Id.
- ; Out: si == 0 if no queue entry available,
- ; otherwise: (ds:)si -> allocated queue-entry.
- ; Must be called with interrupts disabled.
-
- push cx
- push bx
- mov cx, NO_OF_QUEUES
- lea si, reass_queues
- mov bx, 0
-
- fq_loop:
- mov al, [si].q_count
- or al, al
- jnz fq_1
- or bx, bx ;
- jne fq_2 ; remember first entry not in use
- mov bx, si ;
- jmp short fq_2
-
- fq_1:
- push cx
- push si
- push di
- add si, q_node
- mov cx, SIZE ipx_srcnode
- cld
- repe cmpsb
- pop di
- pop si
- pop cx
- jne fq_2
- cmp dx, [si].q_fragid
- jne fq_2
- jmp short fq_x
-
- fq_2:
- add si, SIZE queue_entry
- loop fq_loop
-
- mov si, bx
-
- fq_x:
- pop bx
- pop cx
- ret
- find_queue endp
-
- enqueue proc near
- ; Queue an etherpacket fragment on appropriate queue
- ; On entry: es:si -> received ecb.
- ; cx = length of data in this fragment
- ; Out: carry set if no space available.
- ; zero flag set if packet on queue complete.
- ; ds:si -> queue_entry on which fragment was queued.
-
- push si
- push es
- mov ax, 0
- mov es:[si].u_ecb.ecb_link.offs, ax ; clear link-field
- mov es:[si].u_ecb.ecb_link.segm, ax
- mov di, si
- push di
- lea di, es:[si].u_ipx.ipx_srcnode
- mov dx, es:[si].u_ether_frag.ef_fragid
- call find_queue
- pop di
- or si, si
- jnz enq_0
- add sp, 4
- stc
- ret
-
- enq_0:
- mov dl, es:[di].u_ether_frag.ef_fragno
- mov dh, es:[di].u_ether_frag.ef_fragtot
- cmp [si].q_count, 0
- jne enq_3
-
- ;this is the first fragment we receive
- pop [si].q_ecb.segm
- pop [si].q_ecb.offs
- mov [si].q_len, cx
- mov [si].q_count, 1
- cmp dh, 1 ;
- jne enq_1 ; short cut if fragment count == 1.
- ret
-
- ;initialise queue structure a bit more...
- enq_1:
- mov ax, es:[di].u_ether_frag.ef_fragid
- mov [si].q_fragid, ax
-
- ;copy source node address
- push bx
- mov bx, (SIZE ipx_srcnode) - 1
-
- enq_2:
- mov al, es:[di+bx].u_ipx.ipx_srcnode
- mov ds:[si+bx].q_node, al
- sub bx, 1
- jnc enq_2
- pop bx
-
- mov ax, cs
- mov [si].q_aes.aes_esr.segm, ax
- mov [si].q_aes.aes_esr.offs, offset reass_timeout
- mov ax, ds
- mov es, ax
- mov ax, 2 ; two ticks to timeout
- call_ipx SCHEDULE_SPECIAL_EVENT,si,dx
- cmp dh, [si].q_count
- ret
-
- ; add ecb to existing queue, keep list ordered by fragment number.
- enq_3:
- lea ax, [si].q_ecb
- push ax ; put link field address on stack
- push ds
- les di, [si].q_ecb
-
- enq_4:
- mov ax, es
- or ax, di
- jz enq_5
- cmp dl, es:[di].u_ether_frag.ef_fragno
- jb enq_5
- add sp, 4
- ; lea ax, es:[di].u_ecb.ecb_link
- ; push ax
- push di
- push es
- les di, es:[di].u_ecb.ecb_link
- jmp enq_4
-
- ; enter here with two addresses on the stack:
- ; 1) address of ecb to link in
- ; 2) address of link field after which to link
- ; es:di contains the "next" link.
-
- enq_5:
- mov ax, es
- mov bx, di
- pop es
- pop di
- pop es:[di].segm
- pop es:[di].offs
- les di, es:[di]
- mov es:[di].u_ecb.ecb_link.segm, ax
- mov es:[di].u_ecb.ecb_link.offs, bx
- add [si].q_len, cx
- inc [si].q_count
- cmp dh, [si].q_count
- ret
-
- enqueue endp
-
- dequeue proc near
- ; Send reassembled packet to client and reschedule receive buffers.
- ; On entry: ds:si -> queue.
-
- mov cx, [si].q_len
- les di, [si].q_ecb
- les di, es:[di].u_data_frag.frag_addr
- add di, 2 * EADDR_LEN
- push si
- call recv_find
- pop si
- mov ax, es
- or ax, di
- jz deq_2
-
- mov dh, [si].q_count
- mov cx, [si].q_len
- push si ; save our queue address
- push ds
- push di ; save their buffer address
- push es
- push cx
- lds si, ds:[si].q_ecb
- cld
-
- ;all set, es:di -> user buffer, ds:si -> first fragment
- ;??? save count and source pointer for call to recv_copy
-
- deq_1:
- mov cx, ds:[si].u_ipx.ipx_len
- xchg cl, ch
- sub cx, (SIZE ipx_header + SIZE ether_frag)
- push si
- push ds
- lds si, ds:[si].u_data_frag.frag_addr
- rep movsb
- pop ds
- pop si
- lds si, ds:[si].u_ecb.ecb_link
- dec dh
- jnz deq_1
-
- pop cx ; recover packet length and address
- pop ds ; for completion call
- pop si ;
- call recv_copy
-
- pop ds ; recover queue address
- pop si ;
-
- deq_2:
- mov ax, ds
- mov es, ax
- call_ipx CANCEL_EVENT,si
-
- push si
- mov dh, [si].q_count
- les si, ds:[si].q_ecb
-
- deq_3:
- mov bx, es:[si].ecb_link.offs
- mov cx, es:[si].ecb_link.segm
- call listen_proc
- mov si, bx
- mov es, cx
- ; les si, es:[si].u_ecb.ecb_link
- dec dh
- jnz deq_3
- pop si
- mov [si].q_count, 0
- ret
- dequeue endp
-
-
- my_net_address db 4 dup(?) ;contiguous 10 byte addrss-area as IPX wants it
- my_node_address db 6 dup(?)
-
- from_us proc near
- ;
- ; Check if ecb immediate-address is our own.
- ; On entry: es:si -> ecb.
- ; Out: zero flag set if from us.
-
- push ds
- push si
- push di
- push cx
- mov ax, cs
- mov ds, ax
-
- mov di, si
- add di, ecb_ia
- lea si, my_node_address
- mov cx, SIZE my_node_address
-
- cld
- repe cmpsb
-
- pop cx
- pop di
- pop si
- pop ds
- ret
- from_us endp
-
- reass_timeout proc far
- ; Called by AES when reassembly timeout occurs.
- ; On entry: es:si pointer to ecb.
- ;
-
- push ds
- mov ax, cs
- mov ds, ax
- push si
- push es
- mov dh, es:[si].q_count
- les si, es:[si].q_ecb
-
- reass_to_3:
- mov bx, es:[si].ecb_link.offs
- mov cx, es:[si].ecb_link.segm
- call listen_proc
- mov si, bx
- mov es, cx
- dec dh
- jnz reass_to_3
-
- pop es
- pop si
- mov es:[si].q_count, 0
-
- pop ds
- ret
- reass_timeout endp
-
- receiver proc far
- ;
- ; On entry: es:si pointer to ecb.
- ;
-
- push ds
- mov ax, cs
- mov ds, ax
- mov al, es:[si].u_ecb.ecb_cmplt
- or al, al
- jnz receiver_err
-
- cmp es:[si].u_ecb.ecb_fragcnt, NO_OF_FRAGMENTS
- jne receiver_err
-
- call from_us ; IPX seems to receive its own broadcasts
- ;XXX ; maybe the Packet type field in the ipx header
- ; plays a role in this.
- jz receiver_x
-
- mov cx, es:[si].u_ipx.ipx_len
- xchg cl, ch
- sub cx, (SIZE ipx_header + SIZE ether_frag)
- jbe receiver_err
-
- push es ; save ecb address
- push si
- call enqueue
- jnz rec_1
- call dequeue
-
- rec_1:
- pop si ; pop original ecb address
- pop es
- pop ds
- ret
-
- receiver_err:
- call count_in_err
-
- receiver_x:
- call listen_proc ; post listen again
- pop ds
- cli ; must return with interrupts disabled, says Novell.
- ret
- receiver endp
-
- listen_proc proc near
- ;
- ; Post to u_buf for reception.
- ; On entry: es:si -> receive-ecb
- ;
-
- push bx
-
- ;fill in ecb
- mov es:[si].u_ecb.ecb_esr.offs, offset receiver
- mov ax, cs
- mov word ptr es:[si].u_ecb.ecb_esr.segm, ax
- mov es:[si].u_ecb.ecb_sock, IP_socket
- call_ipx LISTEN,es,si,di,dx,cx
-
- pop bx
- ret
-
- listen_proc endp
-
- fill_ipxhdr proc near
- ;
- ; Fill in ipx header from user data
- ; On entry: ds:si -> user data, cx length, es:bx -> ipx header
- ;
-
- push si
- push di
- push cx
- ;
- ; clear ipx structure
- ;
- mov di, bx
- mov al, 0
- mov cx, SIZE ipx_header
- cld
- rep stosb
-
- ; pop cx
- ; push cx
- ; xchg cl, ch
- ; mov es:[bx].ipx_len, cx
-
- mov di, bx
- add di, ipx_destnode
- mov cx, EADDR_LEN
- rep movsb
-
- mov di, bx
- add di, ipx_srcnode
- mov cx, EADDR_LEN
- rep movsb
-
- mov es:[bx].ipx_type, PEP
- mov es:[bx].ipx_destsock, IP_socket
-
- pop cx
- pop di
- pop si
- ret
- fill_ipxhdr endp
-
- route proc near
- ;
- ; Determine where to send the packet
- ; On entry: es:si -> ecb and ipx, setup for destination node
- ;
-
- push ds
- push si
- push di
- push cx
-
- mov di, si
- add di, ecb_ia
- add si, u_ipx + ipx_destnode
- mov ax, es
- mov ds, ax ; ds:si -> ipx_destnode
- mov cx, SIZE ipx_destnode
- cld
- rep movsb
-
- pop cx
- pop di
- pop si
- pop ds
- ret
- route endp
-
- public int_no
- int_no db 0,0,0,0 ;must be four bytes long for get_number.
-
- public driver_class, driver_type, driver_name, driver_function, parameter_list
- driver_class db 1 ;from the packet spec
- driver_type db 1 ;from the packet spec
- driver_name db 'IPX',0 ;name of the driver.
- driver_function db 2
- parameter_list label byte
- db 1 ;major rev of packet driver
- db 9 ;minor rev of packet driver
- db 14 ;length of parameter list
- db EADDR_LEN ;length of MAC-layer address
- if NO_OF_SND_BUFS eq 1
- dw 528 ;MTU, including MAC headers
- else
- dw GIANT ;MTU, including MAC headers
- endif
- dw MAX_MULTICAST * EADDR_LEN ;buffer size of multicast addrs
- dw 0 ;(# of back-to-back MTU rcvs) - 1
- dw 0 ;(# of successive xmits) - 1
- dw 0 ;Interrupt # to hook for post-EOI
- ;processing, 0 == none,
-
- public rcv_modes
- rcv_modes dw 4 ;number of receive modes in our table.
- dw 0,0,0,rcv_mode_3
-
- 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
- push es
- push di
- mov ax, cs
- mov es, ax
-
- ;first, compute number of fragments needed, keep in dx
- mov dx, 0
- mov ax, cx
-
- snd_1:
- inc dx
- sub ax, MAX_PAYLOAD
- jnc snd_1
-
- ;can we handle this amount?
- cmp dx, NO_OF_SND_BUFS
- jbe snd_frags_ok
-
- snd_err:
- call count_out_err
- pop di
- pop es
- mov dh, CANT_SEND
- stc
- ret
-
- snd_frags_ok:
- lea di, snd_bufs
- push cx
- mov cx, dx
- mov bx, 0
- mov al, 0
-
- snd_free_chk:
- or al, es:[di+bx].u_ecb.ecb_inuse
- add bx, SIZE u_buf
- loop snd_free_chk
-
- pop cx
- or al, al
- jnz snd_err
-
- mov dh, dl
- mov dl, 1
- mov bx, 0
- inc FragmentID
- push di
-
- snd_next_frag:
- ;
- ; dh = total number of fragments to send
- ; dl = current fragment
- ; bx = offset into client buffer (ds:si) for this fragment
- ; cx = bytes to go
- ; es:di = address of current fragment's ecb
- ;
-
- ;compute address of associated ipx header
- push bx
- mov bx, di
- add bx, u_ipx
- call fill_ipxhdr
- pop bx
-
- ;fill in ecb
- mov ax, 0
- mov es:[di].u_ecb.ecb_esr.offs, ax
- mov es:[di].u_ecb.ecb_esr.segm, ax
-
- mov es:[di].u_ecb.ecb_sock, IP_socket
-
- mov es:[di].u_ether_frag.ef_fragtot, dh
- mov es:[di].u_ether_frag.ef_fragno, dl
- mov ax, FragmentID
- mov es:[di].u_ether_frag.ef_fragid, ax
-
- mov ax, ds
- mov es:[di].u_data_frag.frag_addr.segm, ax
-
- mov ax, MAX_PAYLOAD
- sub cx, ax
- jnc snd_frag1
- add ax, cx
-
- snd_frag1:
- mov es:[di].u_data_frag.frag_size, ax
- push si
- add si, bx
- mov es:[di].u_data_frag.frag_addr.offs, si
- add bx, ax
-
- mov si, di
- ;
- ; es:si -> ecb to ship
- ;
-
- ;determine next hop, according to the ecb and ipx
-
- call route
-
- call_ipx SEND_PACKET,es,di,dx,cx,bx
- pop si
-
- add di, SIZE u_buf
- inc dl
- cmp dl, dh
- jbe snd_next_frag
-
- pop di
-
- ;simple timeout on sends
- mov cx, 0ffffh
-
- snd_wait:
- sti
- mov bx, 0
- push cx
- mov ch, 0
- mov cl, dh
- mov al, 0
- snd_wait1:
- or al, es:[di+bx].u_ecb.ecb_inuse
- add bx, SIZE u_buf
- loop snd_wait1
- pop cx
-
- or al, al
- jz snd_done
- call_ipx RELINQUISH,es,di,dx,cx
- loop snd_wait
-
- ;arrive here on timeout, cancel IPX sends
- mov ch, 0
- mov cl, dh
- mov si, di
-
- snd_cancel:
- call_ipx CANCEL_EVENT,es,si,cx
- add si, SIZE u_buf
- loop snd_cancel
- jmp snd_err
-
- snd_done:
- mov bx, 0
- mov ch, 0
- mov cl, dh
- mov al, 0
- snd_done1:
- or al, es:[di+bx].u_ecb.ecb_cmplt
- add bx, SIZE u_buf
- loop snd_done1
-
- or al, al
- jz snd_ok
- jmp snd_err
-
- snd_ok:
- pop di
- pop es
- 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, SIZE my_node_address
- jb get_address_error
- push ds
- push es
- mov ax, cs
- mov ds, ax
- mov es, ax
- lea si, my_net_address
- call_ipx GET_NODE_ADDRESS,di,cx
- pop es ;apparently, there is no error code from IPX
- mov si, offset my_node_address
- mov cx, SIZE my_node_address
- cld
- rep movsb
- mov cx, SIZE my_node_address
- clc
- pop ds
- ret
-
- get_address_error:
- stc
- ret
-
- public set_address
- set_address:
- ;enter with ds:si -> Ethernet address, CX = length of address.
- ;exit with nc if okay, or cy, dh=error if any errors.
- assume ds:nothing
- ret
-
-
- rcv_mode_3:
- ;receive mode 3 is the only one we support, so we don't have to do anything.
- ret
-
-
- public set_multicast_list
- set_multicast_list:
- ;enter with es:di ->list of multicast addresses, cx = number of bytes.
- ;return nc if we set all of them, or cy,dh=error if we didn't.
- mov dh,NO_MULTICAST
- stc
- ret
-
-
- public get_multicast_list
- get_multicast_list:
- ;return with nc, es:di ->list of multicast addresses, cx = number of bytes.
- ;return cy, NO_ERROR if we don't remember all of the addresses ourselves.
- ;return cy, NO_MULTICAST if we don't implement multicast.
- mov dh,NO_MULTICAST
- stc
- ret
-
-
- public reset_interface
- reset_interface:
- ;reset the interface.
- assume ds:code
- ret
-
-
- ;called when we want to determine what to do with a received packet.
- ;enter with cx = packet length, es:di -> packet type.
- 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.
- ;Upon exit, the interrupt will be acknowledged.
- assume ds:code
- ret
-
-
- public recv_exiting
- recv_exiting:
- ;called from the recv isr after interrupts have been acknowledged.
- ;Only ds and ax have been saved.
- assume ds:nothing
- ret
-
- public terminate
- terminate:
- ;called when this driver should cease operation.
- assume ds:nothing
-
- ;close socket, outstanding listens should be cancelled automatically
- mov dx, IP_socket
- call_ipx CLOSE_SOCKET
-
- ; mov ax, cs
- ; mov es, ax
- ; mov cx, NO_OF_RCV_BUFS
- ; lea si, rcv_bufs
- ;
- ;terminate_1:
- ; call_ipx CANCEL_EVENT,es,si,cx
- ; add si, SIZE u_buf
- ; loop terminate_1
-
- ret
-
-
- ;any code after this will not be kept after initialization.
- end_resident label byte
-
-
- public usage_msg
- usage_msg db "usage: ipx_pkt <packet_int_no>",CR,LF,'$'
-
- public copyright_msg
- copyright_msg db "Packet driver for a generic device, version ",'0'+version,CR,LF,'$'
- db "Portions Copyright 19xx, J. Random Hacker",CR,LF,'$'
-
- no_ipx_msg db "IPX presence not detected",CR,LF, '$'
- wrong_sock_msg db "IPX has no good socket",CR,LF, '$'
-
- extrn set_recv_isr: near
-
- ;enter with si -> argument string, di -> wword to store.
- ;if there is no number, don't change the number.
- extrn get_number: near
-
- public parse_args
- parse_args:
- ret
-
-
- public etopen
- etopen:
-
- ;first see if IPX is there
- mov ax, 07A00h
- int 2fh
- cmp al, 0ffh
- je ipx_is_here
- print$ no_ipx_msg
- stc
- ret
-
- ipx_is_here:
- mov ax, es
- mov IPXentry.offs, di
- mov IPXentry.segm, ax
-
- ;close socket first, since "head" won't notify us on termination
- mov dx, IP_socket
- call_ipx CLOSE_SOCKET
-
- ;next open socket
- mov al, 0ffh ; stay open until explicitly closed
- mov dx, IP_socket
- call_ipx OPEN_SOCKET
- or al, 0
- jnz wrong_socket
- cmp dx, IP_socket
- je good_socket
-
- ;close socket and exit
- wrong_socket:
- call_ipx CLOSE_SOCKET
- print$ wrong_sock_msg
- stc
- ret
-
- good_socket:
- ;init send buffer fragment list
- mov ax, cs
- mov es, ax
-
- mov cx, NO_OF_SND_BUFS
- lea si, snd_bufs
-
- et_1:
- mov es:[si].u_ecb.ecb_fragcnt, NO_OF_FRAGMENTS
-
- mov bx, si ; bx = offset ipx_header
- add bx, u_ipx
- mov es:[si].u_ipx_frag.frag_addr.offs, bx
- mov es:[si].u_ipx_frag.frag_addr.segm, ax
- mov es:[si].u_ipx_frag.frag_size, SIZE ipx_header
-
- mov bx, si ; bx = offset ether_frag
- add bx, u_ether_frag
- mov es:[si].u_frag_frag.frag_addr.offs, bx
- mov es:[si].u_frag_frag.frag_addr.segm, ax
- mov es:[si].u_frag_frag.frag_size, SIZE ether_frag
-
- mov ax, es
- add si, SIZE u_buf
- loop et_1
-
- ;init receive buffers and start listening
- mov cx, NO_OF_RCV_BUFS
- lea si, rcv_bufs
- lea di, end_resident ; living dangerously...
- cli ; don't know if this helps
-
- et_2:
- mov es:[si].u_ecb.ecb_fragcnt, NO_OF_FRAGMENTS
-
- mov bx, si
- add bx, u_ipx
- mov es:[si].u_ipx_frag.frag_addr.offs, bx
- mov es:[si].u_ipx_frag.frag_addr.segm, ax
- mov es:[si].u_ipx_frag.frag_size, SIZE ipx_header
-
- mov bx, si
- add bx, u_ether_frag
- mov es:[si].u_frag_frag.frag_addr.offs, bx
- mov es:[si].u_frag_frag.frag_addr.segm, ax
- mov es:[si].u_frag_frag.frag_size, SIZE ether_frag
-
- mov es:[si].u_data_frag.frag_addr.offs, di ; di = offset data buffer
- mov es:[si].u_data_frag.frag_addr.segm, ax
- mov es:[si].u_data_frag.frag_size, MAX_PAYLOAD
-
- call listen_proc
- cli ; just to be certain
- mov ax, es
- add si, SIZE u_buf
- add di, MAX_PAYLOAD
- loop et_2
-
- ;if all is okay,
- mov dx,offset end_resident
- add dx, NO_OF_RCV_BUFS * MAX_PAYLOAD
- clc
- ret
-
- ;if we got an error,
- stc
- ret
-
- code ends
-
- end
-