[comp.protocols.tcp-ip.ibmpc] PC-NFS and pktd.sys problems

palowoda@fiver.UUCP (Bob Palowoda) (07/02/90)

From article <2115@east.East.Sun.COM>, by geoff@hinode.East.Sun.COM (Geoff Arnold @ Sun BOS - R.H. coast near the top):

> There was a problem with one version of the pktd.sys driver which I
> posted to Clarkson, and I've recently posted a new copy - I haven't had
> a chance to see if Russ has put it up yet.  The new one is part of the
> "PC-NFS compatibility kit" which includes both Packet and NDIS
> drivers.

 I checked on the Clarkson bbs and found no archive with 'pktd.sys' in
it. I do have the one that came accross the net some time ago marked
1.0 (files date are march 28) but I beleive this is the one with the
bug that John Breeden is talking about. It's there an archive that
I can access other than ftp that has this update your talking about?
Or maybe you can just post the pktd.asm. I'm under the impression that
there was only one change in the find_driver or setup.

---Bob


-- 
Bob Palowoda   palowoda@fiver              |   *Home of Fiver BBS*
Home {sun}!ys2!fiver!palowoda              | 415-623-8809 1200/2400
     {pacbell}!indetech!fiver!palowoda     |     An XBBS System                
Work {sun,pyramid,decwrl}!megatest!palowoda| 415-623-8806 1200/2400/19.2k TB+

jbreeden@netcom.UUCP (John Breeden) (07/02/90)

In article <1066@fiver.UUCP> palowoda@fiver.UUCP (Bob Palowoda) writes:
>1.0 (files date are march 28) but I beleive this is the one with the
>bug that John Breeden is talking about. It's there an archive that
>I can access other than ftp that has this update your talking about?
>Or maybe you can just post the pktd.asm. I'm under the impression that
>there was only one change in the find_driver or setup.

This is my fixed pktd.asm, all I did was fix the driver_info call. I've used
this with both PC-NFS V2.0 & 2.1 on AT&T STarlan10 boards.


;       @(#)pktd.asm.u	1.5    2/7/90
;
; Copyright (c) 1989, 1990 by Sun Microsystems, Inc.
;

title Sun Packet Driver Interface Driver
page ,132

;
;	The following driver is derived from two sources:
;	(1) Version 1.08 of the Packet Driver Specification,
;	    developed at FTP Software Inc.
;	(2) The PC-NFS Link Level Driver Kit.
;
;	In addition, Karl Auerbach (karl@asylum.sf.ca.us) contributed
;	a couple of fixes; his mods are marked "***KAA". Thanks, Karl.
;
;	This version includes the fixes suggested by many users to allow
;	PC-NFS to co-exist with Netware using the New York code. Thanks
;	to Russ Nelson at Clarkson and James Van Bokkelen at FTP for
;	their help.
;
;	This material is provided "as is." It is NOT a supported
;	Sun product, and has not been tested against more than
;	a handful of packet drivers. Please send any comments,
;	fixes, etc. to me (geoff@east.sun.com).
;
;		Geoff Arnold
;
;       Fixed DRIVER_INFO call (line 251) - John Breeden - April 1990

_OPERATING_STATISTICS equ 1

cseg	segment para public 'code'
	assume	cs:cseg
	assume	ds:nothing
	assume	es:nothing


include pktdd.asm
include pktd.mac
include ..\include\protocol.inc
include ..\include\log.inc
include ..\include\select.inc

;
;	EXTRNS
;
extrn	demux:near
extrn	upcall:near

;	PUBLICS
;

public	select_table_pointer	       ; new name for universal demux routine

public	log_seg
public	log_base
public	ethsend

;	variables which live in cseg
;

;
; Pointer to select table - used by demux.asm
;
select_table_pointer dw 2 dup (0)	; address of select table



; the following are the segment & offset for the log table
log_seg 	dw	?
log_base	dw	?
; The log routine follows:
	logproc
;............................................................
; see the pop_f macro in pktd.mac for why this is here
iretins:
	iret

;	initialize the ethernet interface and driver
;	es:di contains address of select table
ethinit proc far
	push	es
	push	ds			; save old ds and set to cs
	push	cs
	pop	ds
	mov	select_table_pointer,di ; save the table address away
	mov	select_table_pointer+2,es
	mov	es:sel_largest[di], largest_packet	; ret size of buffer
;
;	get log info
;
	mov	ax, es:sel_logtab_s[di]
	mov	log_seg, ax
	mov	ax, es:sel_logtab_o[di]
	mov	log_base, ax
;
; (we can now use the log macro)
;
	push	es
	call	setup
	pop	es
	push	cs
	pop	ds
	lea	di,sel_ethaddr[di]	;point to ether address entry
	mov	si, offset pd_addr
	movsw
	movsw
	movsw
ethinitdone:
	sub	ax,ax
	pop	ds
	pop	es
	sti
	ret
ethinit endp

ethsend proc	far
	call	sender
	ret
ethsend endp



;--  The packet driver code looks like this:
;--
;--  setup() {
;--	 if(state==UP)
;--	     return; /* state starts out as DOWN */
;--	 if(find_driver() == FALSE)
;--	     return;
;--	 stuff = call_driver(DRIVER_INFO);
;--	 handle = call_driver(ACCESS_TYPE, IP_TYPE, 2, receiver);
;--	 handle = call_driver(ACCESS_TYPE, ARP_TYPE, 2, receiver);
;--	 handle = call_driver(ACCESS_TYPE, RARP_TYPE, 2, receiver);
;--	 call_driver(GET_ADDRESS, handle, &my_link_addr, &my_link_addr_len);
;--	 state = UP;
;--  }
;--
;--  find_driver() {
;--	 vecptr = PTR(0, 0x60*4); /* point into vectors */
;--	 for(vector = 0x60; vector <= 0x80; vector++) {
;--	     driverptr = *vecptr; /* deref ptr to dword ptr */
;--	     if (strcmp(*(driverptr+3), "PKT DRVR") == 0)
;--		 return(TRUE);
;--	     vecptr += 4; /* step to next vector */
;--	 }
;--	 return(FALSE);
;--  }
;--
;--  call_driver(func,args) {
;--	 load args into registers;
;--	 set AH = func;
;--	 soft int to vector; /* ?far call to driverptr with ints off? */
;--  }
;--
;--  sender() {
;--	 if(multiple fragments) {
;--	     marshal fragments into sendbuf;
;--	     call_driver(SEND_PKT, sendbuf);
;--	 } else {
;--	     call_driver(SEND_PKT, caller_buf);
;--	 }
;--  }
;--
;--  receiver(ax) {
;--	 if(ax == 0) {	     /* first call for a packet */
;--	     set es:di to pint at rcvbuf; cx = sizeof(rcvbuf);
;--	 } else {	     /* data copied - test and demux */
;--	     demux_and_upcall(rcvbuf);
;--	 }
;--  }
;------ The descriptions above are replicated before each routine


DRIVER_INFO	equ	1
ACCESS_TYPE	equ	2
SEND_PKT	equ	4
GET_ADDRESS	equ	6

buflen	    equ     1518
pd_sig	    db	    'PKT DRVR',0
pd_sig_len  equ     $-pd_sig
pd_int	    db	    0
pd_setup    db	    0
pd_class    db	    0
pd_num      db	    0
pd_type     dw      0
pd_alen     dw	    6
pd_addr     db	    6 dup (0)
pd_handle   dw	    0
pd_rbuf     db	    buflen dup (?)
pd_sbuf     db	    buflen dup (?)
pd_rlen     dw	    0
;
ip_type     db      8,0
arp_type    db      8,6
rarp_type   db      80h,35h
;

pd_stklev   dw	    0
pd_stack    db	    256 dup ('x')
pd_stktop   dw	    0
; Save the SI returned by demux() in the following locations ***KAA
si_save	    dw	    0					    ;***KAA

;--
;--  call_driver(func,args) {
;--	 load args into registers;
;--	 set AH = func;
;--	 soft int to vector; /* ?far call to driverptr with ints off? */
;--  }
public call_driver
call_driver proc    near
	int	0
	ret
call_driver endp

pd_patch    equ     call_driver+1


;--
;--  setup() {
;--	 if(state==UP)
;--	     return; /* state starts out as DOWN */
;--	 if(find_driver() == FALSE)
;--	     return;
;--	 stuff = call_driver(DRIVER_INFO);
;--	 handle = call_driver(ACCESS_TYPE, IP_TYPE, 2, receiver);
;--	 handle = call_driver(ACCESS_TYPE, ARP_TYPE, 2, receiver);
;--	 handle = call_driver(ACCESS_TYPE, RARP_TYPE, 2, receiver);
;;--	 call_driver(GET_ADDRESS, handle, &my_link_addr, &my_link_addr_len);
;--	 state = UP;
;--  }
public setup
setup	    proc    near
	    push    ax
	    push    bx
	    push    cx
	    push    dx
	    push    es
	    push    di
	    push    si
	    cmp     pd_setup, 0
	    jne     se_900
	    inc     pd_setup
	    call    find_driver
	    jc	    se_900
	    mov     ah, DRIVER_INFO
	    mov	    al, 0ffh		; fix - set this reg for call
	    call    call_driver
	    push    cs
	    pop     ds		    ; deliberately ignoring the name
	    jc	    se_900
	    mov     pd_class, ch
            mov     pd_num, cl
            mov     pd_type, dx
;
            mov     si, offset ip_type
            call    register_type
            jc      se_900
            mov     si, offset arp_type
            call    register_type
            jc      se_900
            mov     si, offset rarp_type
            call    register_type
            jc      se_900

	    mov     bx, pd_handle
	    mov     ah, GET_ADDRESS
	    push    cs
	    pop     es
	    mov     di, offset pd_addr
	    mov     cx, pd_alen
	    call    call_driver
	    jc	    se_900
	    mov     pd_alen, cx
se_900:
	    pop     si
	    pop     di
	    pop     es
	    pop     dx
	    pop     cx
	    pop     bx
	    pop     ax
	    ret
setup	    endp

;
; register_type, entered with ds:si pointing at the packet type code
;
public register_type
register_type proc near
	    mov     ah, ACCESS_TYPE
	    mov     al, pd_class
	    mov     bx, pd_type
	    mov     dl, pd_num
	    mov     cx, 2		; 2 bytes of filter
	    push    cs
	    pop     es
	    mov     di, offset receiver
	    call    call_driver
	    jc	    rt_900
	    mov     pd_handle, ax
            ret
rt_900:	
;		int 3
		ret
register_type endp

;--
;--  find_driver() {
;--	 vecptr = PTR(0, 0x60*4); /* point into vectors */
;--	 for(vector = 0x60; vector <= 0x80; vector++) {
;--	     driverptr = *vecptr; /* deref ptr to dword ptr */
;--	     if (strcmp(*(driverptr+3), "PKT DRVR") == 0)
;--		 return(TRUE);
;--	     vecptr += 4; /* step to next vector */
;--	 }
;--	 return(FALSE);
;--  }
public find_driver
find_driver proc    near
	    mov     bx, 60h*4
	    mov     dx, 60h
	    xor     ax, ax
	    cld
fd_010:
	    mov     es, ax
	    les     di, es:[bx] 	; get vector in ES:BX
	    lea     di, 3[di]		; point at signature
	    mov     si, offset pd_sig
	    mov     cx, pd_sig_len
	    repe    cmpsb
	    je	    fd_100		; found it
	    add     bx, 4
	    inc     dx
	    cmp     dx, 80h
	    jle     fd_010
	    stc
	    ret
fd_100:
	    mov     pd_int, dl
	    mov     byte ptr cs:pd_patch, dl
	    clc
	    ret
find_driver endp


;--
;--  sender() {
;--	 if(multiple fragments) {
;--	     marshal fragments into sendbuf;
;--	     call_driver(SEND_PKT, sendbuf);
;--	 } else {
;--	     call_driver(SEND_PKT, caller_buf);
;--	 }
;--  }
public sender
sender	    proc    near
	    log     _LOG_ETH_XMIT
	    push    bx
	    push    cx
	    push    dx
	    push    si
	    push    ds
	    push    es
	    mov     ah, SEND_PKT
	    add     di, 2		    ; step over status
	    mov     cx, word ptr es:[di]
	    lds     si, dword ptr es:[di+2]
	    add     di, 6
	    cmp     word ptr es:[di], 0     ; any more?
	    jne     send_010		    ; if so, go do multiple...
	    call    call_driver
	    jmp     send_090
send_010:
;  we must copy the data into a local buffer first
	    push    es
	    push    di
	    mov     dx, cx		    ; save count
	    push    cs
	    pop     es
	    mov     di, offset pd_sbuf
	    call    copydata
	    pop     si
	    pop     ds
	    mov     cx, word ptr [si]
	    lds     si, dword ptr [si+2]
	    add     dx, cx
	    call    copydata
	    push    cs
	    pop     ds
	    mov     si, offset pd_sbuf
	    mov     cx, dx
	    call    call_driver
send_090:
	    pop     es
	    pop     ds
	    pop     si
	    pop     dx
	    pop     cx
	    pop     bx
	    sub     ax, ax	    ; no error
	    ret
sender	    endp

public copydata
copydata    proc    near
	    inc     cx		    ; if odd (illegal?) ...
	    shr     cx, 1	    ; ... round up (otherwise inc is benign)
	    rep     movsw
	    ret
copydata    endp

;--
;--  receiver(ax) {
;--	 if(ax == 0) {	     /* first call for a packet */
;--	     set es:di to pint at rcvbuf; cx = sizeof(rcvbuf);
;--	 } else {	     /* data copied - test and demux */
;--	     demux_and_upcall(rcvbuf);
;--	 }
;--  }
public receiver
receiver    proc    far
	cmp	ax, 0
	jne	rcv_010
	push	cs
	pop	es
	mov	di, offset pd_rbuf
	mov	cs:pd_rlen, cx
	ret
rcv_010:
;	we first switch to our stack. we can trash ax/bx/dx, per spec
	pushf
	pop	dx
	cli
	cmp	cs:pd_stklev, 0
	jne	rcv_015
	inc	cs:pd_stklev
	mov	ax, ss
	mov	bx, sp
	push	cs
	pop	ss
	mov	sp, offset pd_stktop
	push	ax
	push	bx
rcv_015:
	push	dx		    ; saved flags
	popf

	push	ds		    ; general save

	push	ds		    ; save...
	push	si		    ; ... over ...
	push	cx		    ;	 ... demux

	push	ds
	pop	es

	push	si
	pop	di

	mov	cx,64	            ; Limit demux's view (why ???) ***KAA
	call	demux		    ; and remember to preserve BX cookie
	mov	si_save,si	    ; It is necessary to save the SI returned
				    ; from demux and pass it to upcall ***KAA

	pop	ax		    ; original len
	pop	si
	pop	ds

	jc	rcv_800 	    ; carry from demux call
	log	_LOG_ETH_RCV
	cmp	ax, cx
	jge	rcv_200
	mov	cx, ax
rcv_200:
	call	copydata
	mov	si,si_save	    ;***KAA
	call	upcall
	jmp	rcv_900
rcv_800:
	log	_LOG_ETH_DROPPED
rcv_900:
	pop	ds
	pushf
	pop	dx		; save those flags
	cli
	dec	cs:pd_stklev
	jne	rcv_990
	pop	bx
	pop	ax
	mov	ss, ax
	mov	sp, bx
rcv_990:
	push	dx		; the flags, the flags....
	popf
	ret
receiver    endp

cseg	ends
end	begin