home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
The Best of Mecomp Multimedia 1
/
Mecomp-CD.iso
/
amiga
/
tools
/
misc
/
cnetdevice
/
src
/
cnetdevice.asm
next >
Wrap
Assembly Source File
|
1997-06-02
|
47KB
|
1,574 lines
;---------------------------------------------------------------------------
; CNet CN40BC PCMCIA ethernet card driver for A1200
;---------------------------------------------------------------------------
;
; HISTORY:
;
; 10-4-97 v0.1 - Created by Bruce Abbott (bhabbott@inhb.co.nz)
; *** First Aminet Release ***
;
; 29-4-97 v0.2 - Implemented CMD_ONLINE/OFFLINE/FLUSH (for Miami).
;
; - Enabled interrupts during RemoteWrite (no more serial
; port overruns!).
;
; 6-5-97 v0.3 - Added a flag so that we won't try to ReleaseCard()
; unless there was a successful OwnCard()!
;
; 2-6-97 v0.4 - CMD_CONFIGINTERFACE now overrides the default hardware
; address (for Maimi).
;
; - Device now goes offline if the PCMCIA card is removed.
;
; - CMD_ONEVENT implemented.
;
; - Loosened hardware address verification to accept the
; Accton EN2216.
;
; - Unrolled loops to improve data transfer speed. Now
; about 20% faster on an unexpanded A600.
;
; - Hack to fix problem with missed interrupts. Now we
; clear the Gayle interrupt bits instead of letting
; card.resource do it for us.
; *** Second Aminet Release ***
;
;
output devs:networks/cnet.device
include amiga.i ; commodore includes (WB1.3)
include pcmcia.i ; card.resource etc.
include sanaii.i ; the essential network stuff
include cnet.i ; hardware specific stuff
VERSION = 0
REVISION = 4
; 1uS delay before nic register access
; May not be required with slower CPU.
delay MACRO
tst.b $bfe001 ; at least 1uS, even on fast machines
ENDM
;===========================================================================
Section 0,CODE
start_exe:
moveq #-1,D0 ; it's a device, not an application!
rts
romtag:
dc.w RTC_MATCHWORD ; RT_MATCHWORD
dc.l romtag ; RT_MATCHTAG
dc.l Endcode ; RT_ENDSKIP
dc.b RTF_AUTOINIT ; RT_FLAGS
dc.b VERSION ; RT_VERSION
dc.b NT_DEVICE ; RT_TYPE
dc.b 0 ; RT_PRI
dc.l DeviceName ; RT_NAME
dc.l IDString ; RT_IDSTRING
dc.l Init ; RT_INIT
Init:
dc.l dd_extsize ; data space size
dc.l funcTable ; pointer to function initializers
dc.l dataTable ; pointer to data initializers
dc.l initRoutine ; routine to run at startup
funcTable:
dc.w -1
dc.w Open_Device-funcTable
dc.w Close_Device-funcTable
dc.w _DevExpunge-funcTable
dc.w _Null-funcTable
dc.w _DevBeginIO-funcTable
dc.w _DevAbortIO-funcTable
dc.w -1
dataTable:
INITBYTE LN_TYPE,NT_DEVICE
INITLONG LN_NAME,DeviceName
INITBYTE LIB_FLAGS,LIBF_SUMUSED!LIBF_CHANGED
INITWORD LIB_VERSION,VERSION
INITWORD LIB_REVISION,REVISION
INITLONG LIB_IDSTRING,idString
dc.w 0
;=======================================================
; initRoutine
;=======================================================
;
; Called after device has been allocated.
; This routine is single threaded
;
; input: a0 = seglist
; d0 = device
;
initRoutine:
movem.l d1-d7/a0-a5,-(A7)
move.l d0,a5
move.l a0,dd_SegList(a5) ; seglist for expunge
move.l 4,execbase ; local copy of execbase
move.l a5,d0
movem.l (A7)+,d1-d7/a0-a5
rts
_Null:
moveq #0,d0
rts
;=================================================================
; Open Device
;=================================================================
;
; error = Open_Device(device, ioreq, unitnum, flags)
; d0 a6 a1 d0 d1
;
Open_Device:
movem.l D2-D4/A2-A4/A6,-(A7)
move.l A6,A3 ; a3 = device
move.l A1,A4 ; a4 = ioreq
move.l D0,D4 ; d4 = unit
move.l a3,a1
bsr init_device ; init device data structures
move.l a3,a0
move.l a4,a1
move.l d4,d0
bsr Open_Unit ; open unit
move.l d0,io_unit(a4)
beq.s .error
move.l A3,A1
bsr init_card ; init PCMCIA card
tst.l D0
bne.s .error
move.l a3,a1
bsr init_nic ; init Network Interface Controller
tst.l d0
beq.s .ok
.error:
move.l dd_cardres(a3),d1
beq.s .nocard
move.l d1,a6
bclr #DDB_OWNED,dd_flags(a3)
beq.s .nocard
lea dd_cardhandle(a3),a1
moveq #CARDF_REMOVEHANDLE,d0
jsr _LVOReleaseCard(a6) ; release card if error
.nocard:
moveq #IOERR_OPENFAIL,d0
move.b d0,io_error(a4)
move.l d0,io_device(a4)
bra.s .done
.ok:
bset #DDB_ONLINE,dd_flags(a3) ; ready to accept packets
moveq #0,d0
move.b d0,io_error(a4) ; complete the ioreq
move.b #NT_REPLYMSG,ln_type(a4)
addq.w #1,lib_OpenCnt(a3) ; opened successfully
.done:
movem.l (A7)+,D2-D4/A2-A4/A6
rts
;===============================================================
; unit=Open Unit(device, ioreq, unitnum)
; d0 a0 a1 d0
;===============================================================
;
; Get the caller's buffer copy callback vectors
;
; NOTE: we only keep the vectors from the current caller
;
Open_Unit:
movem.l D2-D4/A2-A5,-(A7)
move.l A0,A4 ; A4 = device
move.l A1,A5 ; A5 = ioreq
tst.l D0 ; only unit 0 is supported
bne .error
move.l ios2_buffermanagement(A5),D0 ; tag list supplied?
beq .ok
moveq #0,D2 ; d2 = number of required tags found
move.l D0,A0 ; a0 = tag list
.next_tag:
move.l (A0)+,D0 ; d0 = tag number
beq .got_tags ; end of tag list?
move.l (A0)+,D1 ; d1 = tag value
cmp.l #S2_COPYFROMBUFF,D0
beq.s .from ; tag_copyfrombuf ?
cmp.l #S2_COPYTOBUFF,D0
bne.s .next_tag ; tag_copytobuf ?
.to:
move.l D1,dd_copytobuf(a4) ; store function
addq.w #1,D2 ; got the tag
bra .next_tag
.from:
move.l D1,dd_copyfrombuf(a4) ; store function
addq.w #1,D2 ; got the tag
bra .next_tag
.got_tags:
subq.w #2,D2 ; got both tags ?
beq.s .ok
.error:
moveq #0,d0 ; return error
bra.s .done
.ok:
moveq #1,d0 ; return OK
.done:
movem.l (A7)+,D2-D4/A2-A5
rts
;============================================================
; Expunge Device
;============================================================
;
; called when system wants us to close down
;
_DevExpunge:
tst.w lib_opencnt(a6)
bne.s .done
bset #LIBB_DELEXP,lib_flags(a6)
.done:
moveq #0,d0
rts
;============================================================
; Close Device
;============================================================
;
; Seglist = CloseDevice(device)
; d0 a6
;
Close_Device:
move.w lib_OpenCnt(a6),d0
beq.s .done ; already closed ?
subq.w #1,d0
move.w d0,lib_OpenCnt(a6)
.done:
moveq #0,d0
rts
;===============================================================
; Dev_BeginIO
;===============================================================
; the entry point for all device commands
;
_DevBeginIO:
move.b #NT_MESSAGE,ln_type(A1) ; make sure type is message
moveq #0,d0
move.w io_command(A1),D0 ; get command number
cmp.w #S2_END,D0
bhs.s .error ; valid command?
lsl.w #2,D0
move.l cmds(PC,D0.w),D0 ; get command vector
bne.s .ok
.error:
move.b #IOERR_NOCMD,io_error(A1)
bra TermIO ; return invalid command
.ok:
clr.b io_error(A1) ; no errors yet
move.l D0,A0
jmp (A0) ; jump to command
; command vector array ( those marked '*' are commonly used by AmiTCP )
cmds:
dc.l 0 ; 0
dc.l 0 ; 1
dc.l devcmd_read ; 2 = cmd_read *
dc.l devcmd_write ; 3 = cmd_write *
dc.l 0 ; 4
dc.l 0 ; 5
dc.l 0 ; 6
dc.l 0 ; 7
dc.l devcmd_flush ; 8 = cmd_flush
dc.l devcmd_devicequery ; 9 = S2_DEVICEQUERY *
dc.l devcmd_getstationaddress ; 10= S2_GETSTATIONADDRESS *
dc.l devcmd_configinterface ; 11= S2_CONFIGINTERFACE *
dc.l 0 ; 12
dc.l 0 ; 13
dc.l 0 ; 14= S2_ADDMULTICASTADDRESS
dc.l 0 ; 15= S2_DELMULTICASTADDRESS
dc.l 0 ; 16= S2_MULTICAST
dc.l devcmd_broadcast ; 17= S2_BROADCAST *
dc.l devcmd_tracktype ; 18= S2_TRACKTYPE *
dc.l 0 ; 19= S2_UNTRACKTYPE
dc.l 0 ; 20= S2_GETTYPESTATS
dc.l 0 ; 21= S2_GETSPECIALSTATS
dc.l 0 ; 22= S2_GETGLOBALSTATS
dc.l devcmd_onevent ; 23= S2_ONEVENT
dc.l 0 ; 24= S2_READORPHAN
dc.l devcmd_online ; 25= S2_ONLINE
dc.l devcmd_offline ; 26= S2_OFFLINE
;====================================================================
; Abort_IO
;====================================================================
;
; try to cancel a pending ioreq
;
_DevAbortIO:
movem.l A2/A6,-(A7)
move.l A1,A2
moveq #-1,D0 ; assume failure
cmp.b #NT_MESSAGE,ln_type(A2) ; only cancel queued ioreq's
bne.s .done
move.l execbase(PC),A6
jsr _LVODisable(A6)
move.l A2,A1
jsr _LVORemove(A6) ; remove ioreq from list
move.b #IOERR_ABORTED,io_error(A2)
move.l A2,A1
jsr _LVOReplyMsg(A6) ; reply to originator's message
jsr _LVOEnable(A6)
moveq #0,D0 ; aborted OK
.done:
movem.l (A7)+,A2/A6
rts
;===========================================================
; termio(ioreq)
; a1
;===========================================================
;
; return completed ioreq to sender.
;
TermIO:
movem.l A2/A6,-(A7)
move.l A1,A2
move.b io_error(a1),d0 ; completed OK ?
beq.s .noerr
moveq #0,d1
move.w io_command(a2),d1
move.l io_device(A2),A0
moveq #S2EVENT_ERROR,D0
bsr DoEvent ; create error event
.noerr:
move.b #NT_REPLYMSG,ln_type(A2)
btst #IOB_QUICK,io_flags(A2)
bne.s .quick ; does sender need a reply ?
move.l A2,A1
move.l execbase(PC),A6
jsr _LVOReplyMsg(A6) ; not quick, so send reply
.quick
.done:
movem.l (A7)+,A2/A6
rts
;====================================================
; CMD_READ
;====================================================
;
devcmd_read:
movem.l A2/A3/A6,-(A7)
move.l A1,A2 ; A2 = ioreq
move.l io_device(A2),A3
btst #DDB_CONFIGURED,dd_flags(A3) ; configured ?
bne.s .configured
move.b #S2ERR_BAD_STATE,io_error(A2)
moveq #S2WERR_NOT_CONFIGURED,D0
move.l D0,ios2_WireError(A2) ; error, device is not configured
bra.s .error
.configured:
bclr #IOB_QUICK,io_flags(A2) ; must be queued
move.l execbase(PC),A6
jsr _LVODisable(A6)
lea dd_readlist(A3),A0
move.l A2,A1
jsr _LVOAddTail(A6) ; add ioreq to read queue
jsr _LVOEnable(A6)
bra.s .done
.error:
move.l A2,A1
bsr TermIO ; terminate with error
.done:
movem.l (A7)+,A2/A3/A6
rts
;======================================================
; CMD_WRITE
;======================================================
;
devcmd_write:
movem.l A2/A3/A6,-(A7)
move.l A1,A2 ; A2 = ioreq
move.l io_device(A2),A3
btst #DDB_CONFIGURED,dd_flags(A3) ; configured ?
bne.s .configured
move.b #S2ERR_BAD_STATE,io_error(A2)
moveq #S2WERR_NOT_CONFIGURED,D0
move.l D0,ios2_WireError(A2) ; error, not configured
bra .error
.configured:
btst #SANA2IOB_RAW,io_flags(A2) ; raw packets ?
beq.s .cooked
move.l ios2_DataLength(A2),D1
cmp.l #RAWPKT_SIZE,D1
bls.s .goodlen ; check packet size
bra.s .toobig
.cooked:
move.l ios2_DataLength(A2),D1
cmp.l #ETHERPKT_SIZE,D1
bls.s .goodlen
.toobig:
move.b #S2ERR_MTU_EXCEEDED,io_error(A2) ; oops! packet too big
clr.l ios2_WireError(A2)
bra .error
.goodlen:
bclr #IOB_QUICK,io_flags(A2) ; must be queued
move.l execbase(PC),A6
jsr _LVODisable(A6)
lea dd_writelist(A3),A0
move.l A2,A1
jsr _LVOAddTail(A6) ; add ioreq to write queue
jsr _LVOEnable(A6)
lea dd_txint(A3),A1
jsr _LVOCause(A6) ; start tx
bra.s .done
.error:
move.l A2,A1
bsr TermIO ; terminate with error
.done:
movem.l (A7)+,A2/A3/A6
rts
;==============================================
; CMD_FLUSH
;==============================================
;
devcmd_flush:
movem.l A1/A2/A6,-(A7)
move.l io_device(A1),A2
move.l execbase(PC),A6
jsr _LVODisable(A6)
bra.s .flushreads
.readloop:
move.l D0,A1
move.b #IOERR_ABORTED,io_error(A1)
jsr _LVOReplyMsg(A6) ; abort all Read requests
.flushreads:
lea dd_readlist(A2),A0
jsr _LVORemHead(A6)
tst.l D0
bne.s .readloop
bra.s .flushwrites
.writeloop:
move.l D0,A1
move.b #IOERR_ABORTED,io_error(A1)
jsr _LVOReplyMsg(A6) ; abort all Write requests
.flushwrites:
lea dd_writelist(A2),A0
jsr _LVORemHead(A6)
tst.l D0
bne.s .writeloop
bra.s .flushevents
.eventloop:
move.l D0,A1 ; abort all Event requests
move.b #IOERR_ABORTED,io_error(A1)
jsr _LVOReplyMsg(A6)
.flushevents:
lea dd_eventlist(A2),A0
jsr _LVORemHead(A6)
tst.l D0
bne.s .eventloop
jsr _LVOEnable(A6)
movem.l (A7)+,A1/A2/A6
bra TermIO
;==============================================
; CMD_ONLINE
;==============================================
;
; Try to put device online
;
devcmd_online:
movem.l a1/a2,-(a7)
move.l io_device(a1),a2
btst #DDB_CONFIGURED,dd_flags(a2) ; won't go online unless configured!
beq.s .error
bset #DDB_ONLINE,dd_flags(a2)
bne.s .done ; already online ?
move.l ioaddr(pc),a0
move.b dd_rcr(a2),nic_rcr(a0) ; set receiver to normal mode
moveq #S2EVENT_ONLINE,D0
bsr DoEvent ; create ONLINE event
bra.s .done
.error:
move.b #S2ERR_OUTOFSERVICE,io_error(a1)
moveq #S2WERR_UNIT_OFFLINE,d0
move.l d0,ios2_wireerror(a1)
.done:
movem.l (a7)+,a1/a2
bra TermIO
;==============================================
; CMD_OFFLINE
;==============================================
;
; take device offline
;
devcmd_offline
move.l a1,-(a7)
move.l io_device(a1),a0
bclr #DDB_ONLINE,dd_flags(a0)
beq.s .done ; already offline ?
move.l ioaddr(pc),a0
move.b #DSRC_MON,nic_rcr(a0) ; set receiver to monitor mode
moveq #S2EVENT_OFFLINE,D0
bsr DoEvent ; create OFFLINE event
.done:
move.l (a7)+,a1
bra TermIO
;==============================================
; CMD_ONEVENT
;==============================================
;
; queue up event requests
;
devcmd_onevent:
movem.l a1/a6,-(a7)
move.l io_device(a1),a0
bclr #IOB_QUICK,io_flags(a1) ; must be queued
move.l execbase(PC),A6
jsr _LVODisable(A6)
lea dd_eventlist(A0),A0
jsr _LVOAddTail(A6) ; add ioreq to event queue
jsr _LVOEnable(A6)
movem.l (a7)+,a1/a6
bra TermIO
;==============================================
; CMD_DEVICEQUERY
;==============================================
;
devcmd_devicequery:
move.l A1,-(A7)
move.l ios2_statdata(A1),A0 ; a0 = caller's buffer
move.l (A0),D1 ; D1 = buffer size
move.l size_supplied(pc),D0
cmp.l D0,D1 ; enough space to store info?
bhs.s .get
clr.l S2DQ_SIZESUPPLIED(A0) ; nope!
bra.s .done
.get:
lea S2DQ_SIZESUPPLIED(A0),A1
lea size_supplied(pc),A0
subq.l #4,D0 ; skip bytes_available
bra.s .copy
.copyloop:
move.b (A0)+,(A1)+ ; copy info to caller's buffer
.copy:
dbf D0,.copyloop
.done:
move.l (A7)+,A1
bra TermIO
;==============================================
; CMD_GETSTATIONADDRESS
;==============================================
;
devcmd_getstationaddress:
move.l A1,-(A7)
move.l io_device(A1),A0
lea dd_stationaddress(A0),A0
move.l A0,D1
lea ios2_srcaddr(A1),A1
move.w #ETHER_ADDR_SIZE-1,D0
.copysrc:
move.b (A0)+,(A1)+ ; source address = station address
dbf d0,.copysrc
move.l (A7),A1
lea ios2_dstaddr(A1),A1
move.w #ETHER_ADDR_SIZE-1,D0
move.l D1,A0
.copydst:
moveq #0,d1
move.b (A0)+,d1
move.b d1,(A1)+ ; dest address = station address
dbf d0,.copydst
move.l (A7)+,A1
bra TermIO
;==============================================
; CMD_CONFIGINTERFACE
;==============================================
;
; NOTE: a default station address has already
; been set by init_nic
;
devcmd_configinterface:
movem.l a1/a6,-(sp)
move.l io_device(A1),A0
move.l ios2_srcaddr(a1),d0
ble .done ; check for valid address
move.l d0,dd_stationaddress(a0)
move.w ios2_srcaddr+4(a1),dd_stationaddress+4(a0)
move.l execbase(pc),a6
jsr _LVODisable(a6)
move.l ioaddr(pc),a1
move.b nic_cr(a1),d1 ; remember current command
delay
move.b #DSCM_NODMA|DSCM_PG1,nic_cr(a1) ; select bank 1
delay
move.b dd_stationaddress+0(a0),nic_par0(a1)
delay
move.b dd_stationaddress+1(a0),nic_par1(a1)
delay
move.b dd_stationaddress+2(a0),nic_par2(a1)
delay ; set station address
move.b dd_stationaddress+3(a0),nic_par3(a1)
delay
move.b dd_stationaddress+4(a0),nic_par4(a1)
delay
move.b dd_stationaddress+5(a0),nic_par5(a1)
delay
move.b d1,nic_cr(a1) ; restore command
jsr _LVOEnable(a6)
bset #DDB_CONFIGURED,dd_flags(a0) ; now configured
.done:
movem.l (sp)+,a1/a6
bra TermIO
;==============================================
; CMD_BROADCAST
;==============================================
;
devcmd_broadcast:
move.w #ETHER_ADDR_SIZE-1,D0
moveq #0,d1
.loop:
move.b #255,ios2_dstaddr(a1,d1.w) ; dest address = BROADCAST
addq.w #1,d1
dbf d0,.loop
.doit:
bra devcmd_write
;============================================
; CMD_TRACKTYPE
;============================================
;
; This function adds a packet type to the
; list of those that are being tracked.
;
devcmd_tracktype:
bra TermIO ; but we won't actually track anything
;=========================================
; doevent(device, event)
; a0 d0
;=========================================
;
; called when an 'important' event occurs
;
DoEvent:
movem.l D2/A2/A6,-(A7)
move.l D0,D2
move.l dd_eventlist(A0),A2 ; get first ioreq
move.l execbase(PC),A6
jsr _LVODisable(A6) ; exclusive access to list required
bra.s .start
.loop:
move.l ios2_wireerror(A2),D0
and.l D2,D0 ; should this ioreq be completed?
beq.s .next
move.l D0,ios2_wireerror(A2) ; clear the event
move.l A2,A1
jsr _LVORemove(A6) ; remove ioreq from list
move.l A2,A1
bsr TermIO ; return ioreq to owner
.next:
move.l (A2),A2 ; next ioreq
.start:
tst.l (A2) ; last ioreq ?
bne.s .loop
.done:
jsr _LVOEnable(A6) ; other tasks now allowed to access list
movem.l (A7)+,D2/A2/A6
rts
;======================
; delay approx 1.5mS
;======================
;
delay1500:
move.l D0,-(A7)
move.w #1500,D0
.loop:
tst.b $bfe001 ; wait 1uS
dbf D0,.loop
move.l (A7)+,D0
rts
;==================================================================
; RemoteRead(buffer, nicbuffer, length)
; a1 d0.w d1.w
;==================================================================
;
; Get a copy of data stored in the network card's onboard RAM.
;
; buffer = Amiga RAM
;
; nicbuffer = 16 bit address in card memory
;
RemoteRead:
move.l ioaddr(pc),a0
addq.w #1,D1 ; bump up count to even value
bclr #0,d1
swap d1
delay
move.b nic_cr(a0),d1 ; save old command
swap d1
delay
move.b #DSCM_NODMA|DSCM_START,nic_cr(A0) ; select bank 0
delay
move.b D1,nic_rbcr0(A0) ; set count.lo
ror.w #8,D1
delay
move.b D1,nic_rbcr1(A0) ; set count.hi
delay
move.b D0,nic_rsar0(A0) ; set address.lo
ror.w #8,D0
delay
move.b D0,nic_rsar1(A0) ; set address.hi
delay
move.b #DSCM_RREAD|DSCM_START,nic_cr(A0) ; request Remote Read
ror.w #8,D1
move.w #1600,d0
sub.w d1,d0 ; calculate jump address for required
lea nic_data(a0),a0 ; number of 'move.w' opcodes
jmp .dmaread(pc,d0)
.dmaread:
rept 1600/2
move.w (A0),(A1)+ ; read data words from nic
endr
move.l ioaddr(pc),a0
move.b #DSIS_RDC,nic_isr(A0) ; Remote DMA Complete
swap d1
delay
move.b d1,nic_cr(a0) ; restore old command
rts
;=================================================================
; RemoteWrite( buffer, nicbuffer, count )
; a1 d0.w d1.w
;=================================================================
;
; Puts data into the network card's onboard RAM
;
; buffer = Amiga memory
;
; nicbuffer = 16 bit address in card RAM
;
;
RemoteWrite:
addq.w #1,D1
bclr #0,D1 ; bump up count to even value
move.l ioaddr(pc),a0
swap d1
delay
move.b nic_cr(a0),d1 ; save old command
swap d1
delay
move.b #DSIS_RDC,nic_isr(A0) ; remote DMA complete
delay
move.b #DSCM_NODMA|DSCM_START,nic_cr(A0) ; select bank 0
delay
move.b D0,nic_rsar0(A0) ; set address.lo
lsr.w #8,D0
delay
move.b D0,nic_rsar1(A0) ; set address.hi
delay
move.b D1,nic_rbcr0(A0) ; set count.lo
ror.w #8,D1
delay
move.b D1,nic_rbcr1(A0) ; set count.hi
delay
move.b #DSCM_START|DSCM_RWRITE,nic_cr(A0) ; request remote write
ror.w #8,D1
move.w #1600,d0
sub.w d1,d0
lea nic_data(a0),a0
jmp .dmaread(pc,d0)
.dmaread:
rept 1600/2
move.w (A1)+,(A0)
endr
move.l ioaddr(pc),a0
move.w #30000,D0 ; set timeout
.check:
delay
move.b nic_isr(A0),d1 ; wait for remote DMA complete
and.b #DSIS_RDC,d1
bne.s .OK
dbf D0,.check
moveq #1,D0 ; timed out error
bra.s .done
.ok:
moveq #0,D0 ; OK
.done:
delay
move.b #DSIS_RDC,nic_isr(a0) ; Remote DMA complete
swap d1
delay
move.b d1,nic_cr(a0) ; restore old command
rts
;=========================================================
; reset_nic()
;=========================================================
;
reset_nic:
move.l ioaddr(pc),a0
delay
move.b nic_rst(A0),D0 ; start reset pulse
delay
move.b D0,nic_rst(A0) ; end reset pulse
delay
move.b #DSCM_NODMA|DSCM_STOP,nic_cr(A0) ; stop controller
bsr delay1500 ; wait 1.5mS
move.b #$ff,nic_isr(A0) ; clear all nic ints
rts
;========================================================================
; init_nic(device)
; a1
;========================================================================
;
; set up the network card for online operation
;
; Here we also get the hardware station address from the nic's ROM. The
; CNet card sometimes doesn't read its ROM correctly, so in this case we
; use a fixed address instead.
;
init_nic:
movem.l D2/A4-A6,-(A7)
move.l A1,A5 ; a5 = device data
move.l execbase(PC),A6
jsr _LVODisable(A6) ; ignore ints while setting up
btst #DDB_NICUP,dd_flags(a5)
bne .ok ; already initialised ?
move.b #DSDC_WTS|DSDC_FT1|DSDC_BMS,dd_dcr(A5) ; Word Xfer, FIFO, Burst
move.b #DSRC_AB,dd_rcr(A5) ; accept broadcast packets
move.b #INTMASK,dd_imr(A5) ; accept useful interrupts
move.l ioaddr(pc),d0
beq .bad ; valid I/O Address ?
move.l D0,A4 ; A4 = CNet card I/O address
bsr reset_nic ; reset the controller
delay
move.b nic_cr(A4),D0 ; get command
cmp.b #DSCM_NODMA|DSCM_STOP,d0
bne .error ; is it correct ?
delay
move.b dd_dcr(A5),nic_dcr(A4) ; set data configuration register
delay
move.b #0,nic_rbcr0(A4) ; clear remote byte count
delay
move.b #0,nic_rbcr1(A4) ; ''
delay
move.b #DSRC_MON,nic_rcr(A4) ; set rx to monitor mode
delay
move.b #DSTC_LB0,nic_tcr(A4) ; set tx to loopback mode 1
delay
move.b #(RBUFEND/256)-1,nic_bnry(A4) ; set boundary page
delay
move.b #RBUF/256,nic_pstart(A4) ; set start of rx ring buffer
delay
move.b #RBUFEND/256,nic_pstop(A4) ; set end of rx ring buffer
delay
move.b #$ff,nic_isr(a4) ; clear all interrupts
delay
move.b #0,nic_imr(a4) ; no interrupts allowed
delay
move.b nic_rsr(a4),d0
delay
move.b nic_ncr(a4),d0
delay
move.b nic_cntr0(a4),d0 ; read status registers
delay
move.b nic_cntr1(a4),d0
delay
move.b nic_cntr2(a4),d0
delay
move.b #ETHER_ADDR_SIZE*2,nic_rbcr0(A4) ; byte count low = (words)
delay
move.b #0,nic_rbcr1(A4) ; byte count high = 0
delay
move.b #0,nic_rsar0(A4) ; remote start addr low = 0 (ROM)
delay
move.b #0,nic_rsar1(A4) ; remote start addr high = 0 (ROM)
delay
move.b #DSCM_RREAD,nic_cr(A4) ; start remote read to get
delay ; station address from ROM
lea dd_romstationaddress(a5),A0
move.w #ETHER_ADDR_SIZE-1,D0
.getaddr:
move.b nic_data(A4),(A0)+ ; get ROM station address
dbf D0,.getaddr ; NOTE: 'move.b' as ROM is 8 bit
move.w #30000,d1
.waitloop:
delay
move.b nic_isr(A4),d0
and.b #DSIS_RDC,d0 ; wait for remote DMA complete
dbne d1,.waitloop
tst.w d0
beq .error ; error if timed out
delay
move.b #DSIS_RDC,nic_isr(A4) ; clear remote DMA complete int
lea dd_romstationaddress(a5),a0
btst #7,(a0)
bne.s .badaddr ; good station address ?
move.l 2(a0),d0
beq.s .badaddr
cmp.l #-1,d0
bne.s .gotstation
.badaddr:
lea default_address(pc),a0 ; use known good station address
.gotstation:
lea dd_stationaddress(a5),a1
moveq #ETHER_ADDR_SIZE-1,d0
.copyaddr:
move.b (a0)+,(a1)+ ; copy address to device data
dbf d0,.copyaddr
delay
move.b #DSCM_NODMA|DSCM_PG1|DSCM_STOP,nic_cr(A4) ; select bank 1
delay
move.b dd_stationaddress+0(a5),nic_par0(a4)
delay
move.b dd_stationaddress+1(a5),nic_par1(a4)
delay
move.b dd_stationaddress+2(a5),nic_par2(a4)
delay ; set station address
move.b dd_stationaddress+3(a5),nic_par3(a4)
delay
move.b dd_stationaddress+4(a5),nic_par4(a4)
delay
move.b dd_stationaddress+5(a5),nic_par5(a4)
delay
move.b #RBUF/256,nic_curr(A4) ; set current page for rx
move.b #DSCM_NODMA|DSCM_START,d0
delay
move.b d0,nic_cr(A4) ; start controller
delay
cmp.b nic_cr(A4),D0
bne .error ; command accepted ?
delay
move.b dd_rcr(A5),nic_rcr(A4) ; normal rx mode
delay
move.b #0,nic_tcr(A4) ; loopback mode off
delay
move.b #TBUF/256,nic_tpsr(a4) ; init tx start page
delay
move.b #$ff,nic_isr(A4) ; clear all interrupts
delay
move.b dd_imr(A5),nic_imr(A4) ; enable nic interrupts
.ok:
bset #DDB_NICUP,dd_flags(a5) ; nic is initialised
moveq #0,D0
bra.s .done ; return OK
.error:
bsr reset_nic ; reset nic after malfunction
.bad:
moveq #-1,D0 ; return error
.done:
jsr _LVOEnable(A6) ; allow interrupt processing
movem.l (A7)+,D2/A4-A6
rts
;========================================================
; txintcode(device)
; a1
;========================================================
;
; send packets to network card. packets will be put
; into the card's onboard 16 bit ram, and then
; transmitted to the wire.
;
txintcode:
movem.l D4-D7/A2-A4/A6,-(A7)
move.l A1,A4 ; a4 = device
.next:
btst #DDB_TX,dd_flags(a4) ; quit if tx in progress (status int
bne .done ; will restart us when tx complete)
.getreq:
lea dd_writelist(A4),A0
move.l execbase(pc),a6 ; remove top ioreq
jsr _LVORemHead(A6)
tst.l D0 ; any ioreqs to process?
beq .done
move.l D0,A3 ; A3 = ioreq
lea txbuffer,A1 ; A1 = our internal packet buffer
btst #SANA2IOB_RAW,io_flags(A3) ; raw packets?
beq.s .notraw
move.l ios2_datalength(A3),D6 ; raw packet is full length
bra.s .send
.notraw:
lea ios2_dstaddr(A3),A0
moveq #ETHER_ADDR_SIZE-1,D0
.copy1:
move.b (A0)+,(A1)+ ; insert dest stationaddr into packet
dbra D0,.copy1
lea dd_stationaddress(A4),A0
moveq #ETHER_ADDR_SIZE-1,D0
.copy2:
move.b (A0)+,(A1)+ ; insert src address into packet
dbra D0,.copy2
move.l ios2_packettype(A3),D0 ; insert packettype into packet
move.w D0,(A1)+
moveq #ether_data,D6
add.l ios2_datalength(A3),D6 ; d6 = length of header + data
.send:
move.l dd_copyfrombuf(a4),a2
move.l a1,a0
move.l ios2_data(A3),A1
move.l ios2_datalength(A3),D0
jsr (a2) ; call copyfrombuf
moveq #ETHER_MIN_LEN,D0
cmp.l D0,D6
bge.s .min ; d6 adjusted to legal packet size
move.l D0,D6
.min:
move.l D6,D1
move.w #TBUF,d0
lea txbuffer,A1
bsr RemoteWrite ; put packet into nic tx buffer
tst.l D0
bne.s .termio
move.l execbase(PC),A6 ; disable interrupts during tx setup
jsr _LVODisable(A6)
bset #DDB_TX,dd_flags(A4) ; set our "buffer full" flag
move.l ioaddr(pc),a0 ; a0 = nic
delay
move.b D6,nic_tbcr0(A0) ; set tx byte count lo
ror.w #8,D6
delay
move.b D6,nic_tbcr1(A0) ; set tx byte count hi
delay
move.b #DSCM_NODMA|DSCM_TRANS|DSCM_START,nic_cr(A0) ; start tx
move.l execbase(PC),A6
jsr _LVOEnable(A6) ; enable interrupts
.termio:
move.l A3,A1
bsr TermIO ; finish IOrequest
bra .next ; process next ioreq
.done:
movem.l (A7)+,D4-D7/A2-A4/A6
moveq #0,d0
rts
;============================================================
; rxintcode(device)
; a1
;============================================================
;
; service rx interrupts
;
rxintcode:
movem.l D6/D7/A3-A6,-(A7)
move.l A1,A3 ; a3 = device
move.l ioaddr(pc),A4 ; a4 = nic registers
move.l execbase(PC),A6
.nextpage:
jsr _LVODisable(A6)
delay
move.b #DSCM_NODMA|DSCM_PG1|DSCM_START,nic_cr(A4) ; select bank 1
moveq #0,D7
move.b nic_curr(A4),D7 ; d7 = current page
delay
move.b #DSCM_NODMA|DSCM_START,nic_cr(A4) ; select bank 0
jsr _LVOEnable(A6)
moveq #0,D6
delay
move.b nic_bnry(A4),D6
addq.w #1,D6 ; d6 = next page (boundary+1)
cmp.w #RBUFEND/256,D6
blo.s .nowrap ; end of buffer mem ?
moveq #RBUF/256,D6 ; wrap around to start
.nowrap:
cmp.w D6,D7 ; current page = next page ?
beq .done ; if so then nothing to get
move.w D6,D0
asl.w #8,D0 ; d0 = 16 bit page address
lea rx_header(pc),A1 ; a1 = buffer
moveq #20,D1 ; 20 bytes to get
bsr RemoteRead ; get packet header
move.b rx_header+prhdr_status(pc),d0
and.b #DSRS_RPC,d0 ; complete packet received ?
bne.s .goodpacket
addq.l #1,dd_errors(a3) ; another packet error
bra.s .next
.goodpacket:
move.l A3,A0
move.w D6,D0
lea rx_header(pc),A1
bsr readpacket ; read whole packet into ioreqs
.next:
moveq #0,D0
move.b rx_header+prhdr_nxtpg(pc),D0 ; get next page number
move.w D0,D7
subq.w #1,D0 ; nxtpage-1 = new boundary
cmp.w #RBUF/256,D0
bge.s .boundary ; wrap if before 1st page
moveq #(RBUFEND/256)-1,D0
.boundary:
delay
move.b D0,nic_bnry(A4) ; set new boundary
bra .nextpage ; back for more
.done:
delay
move.b #DSCM_NODMA|DSCM_START,nic_cr(A4) ; select bank 0
jsr _LVODisable(A6)
delay
move.b nic_rsr(a4),d0 ; read rx status
delay
move.b nic_cntr0(A4),D0
delay
move.b nic_cntr1(A4),D0 ; read counters
delay
move.b nic_cntr2(A4),D0
or.b #DSIM_OVWE|DSIM_RXEE|DSIM_PRXE,dd_imr(A3)
move.b dd_imr(a3),nic_imr(a4) ; allow rx interrupts
jsr _LVOEnable(A6)
movem.l (A7)+,D6/D7/A3-A6
moveq #0,D0
rts
;==============================================================
; readpacket( device, pkthdr, page )
; a0 a1 d0.w
;==============================================================
;
; get packet from network card and feed it to next ioreq
;
; Inputs:
;
; pkthdr = packet header info extracted from nic
;
; page = 256 byte page in nic RAM that holds packet
;
;
readpacket:
movem.l D3-D7/A2-A6,-(A7)
move.l D0,D7 ; D7 = page
move.l A0,A5 ; A5 = device
move.l A1,A4 ; a4 = header
moveq #0,D6
move.b prhdr_sz1(A4),D6
lsl.w #8,D6 ; D6 = packet data length
move.b prhdr_sz0(A4),D6
sub.w #prhdr_sizeof+ether_data,D6 ; D6 = length of user data
moveq #0,D3
move.w prhdr_sizeof+ether_type(A4),D3 ; d3 = type
move.l dd_readlist(A5),A3 ; a3 = first ioreq
bra.s .getreq ; find a suitable ioreq
.checkreq:
cmp.l ios2_packettype(A3),D3 ; does it want our packet ?
beq.s .gotreq
.nextreq:
move.l D1,A3 ; a3 = next ioreq in list
.getreq:
move.l (A3),D1 ; end of list ?
bne.s .checkreq
bra .done
.gotreq:
move.l A3,A1
move.l execbase(PC),A6
jsr _LVORemove(A6) ; remove ioreq from list
lea ios2_dstaddr(A3),A0
moveq #ETHER_ADDR_SIZE-1,D0
.dst:
move.b (A4)+,(A0)+ ; extract the dest address
dbf D0,.dst
lea ios2_srcaddr(A3),A0
moveq #ETHER_ADDR_SIZE-1,D0
.src:
move.b (A4)+,(A0)+ ; extract the src address
dbf D0,.src
move.w D7,D5
asl.w #8,D5 ; address=page*256
add.w #prhdr_sizeof+ether_data,D5 ; skip pageheader and etherheader
btst #SANA2IOB_RAW,io_flags(A3)
beq.s .getpacket ; is etherheader wanted ?
moveq #ether_data,D0
add.l D0,D6 ; add header length for raw packet
sub.w D0,D5 ; backup nic address to include header
.getpacket:
lea rxbuffer,A1
move.w D5,D0
move.w D6,D1
bsr RemoteRead ; get packet from network card's RAM
move.l dd_copytobuf(a5),a2
move.l ios2_data(A3),A0
lea rxbuffer,A1
move.l D6,ios2_datalength(A3) ; set data length in ioreq
move.l d6,d0
jsr (a2) ; call copytobuf
move.l A3,A1
bsr TermIO ; IO finished
.done:
movem.l (A7)+,D3-D7/A2-A6
rts
;======================================================================
; init_card(device)
; a1
;======================================================================
;
; Initialise PCMCIA card
;
init_card:
movem.l A3-A6,-(A7)
move.l A1,A3 ; a3 = device
btst #DDB_OWNED,dd_flags(a3) ; port already set up ?
bne .owned
lea cardname(pc),a1
move.l execbase(pc),a6
jsr _LVOOpenResource(a6) ; open credit card resource
move.l d0,dd_cardres(a3)
beq .error
move.l d0,a6
jsr _LVOGetCardMap(a6)
move.l d0,dd_cmm(a3) ; remember Card Memory Map
lea dd_cardhandle(a3),a1
lea dd_cardremoved(a3),a0 ; init interrupt for card removed
move.l a3,is_data(a0)
move.l #card_removed_code,is_code(a0)
move.l a0,cah_CardRemoved(a1)
lea dd_cardinserted(a3),a0 ; init interrupt for card inserted
move.l a3,is_data(a0)
move.l #card_inserted_code,is_code(a0)
move.l a0,cah_CardInserted(a1)
lea dd_cardstatus(a3),a0 ; init interrupt for status change
move.l a3,is_data(a0)
move.l #status_int_code,is_code(a0)
move.l a0,cah_CardStatus(a1)
lea devicename(pc),a0
move.l a0,ln_name(a1)
move.b #20,ln_pri(a1) ; high priority for I/O card
move.b #CARDF_IFAVAILABLE,cah_cardflags(a1)
jsr _LVOOwnCard(a6) ; own card (sets up interrupt vectors)
tst.l d0
bne .error
bset #DDB_OWNED,dd_flags(a3) ; card is now owned by us
lea dd_cardhandle(a3),a1
move.l #CARDF_DISABLE_WP|CARDF_ENABLE_DIGAUDIO,d1
jsr _LVOCardMiscControl(a6) ; enable card I/O functions
bset #DDB_CARDIN,dd_flags(a3) ; card is inserted
.owned:
btst #DDB_CARDIN,dd_flags(a3) ; is card is inserted ?
beq.s .error
move.l dd_cmm(a3),d0
beq.s .error ; valid card memory map ?
move.l d0,a1
move.l cmm_AttributeMemory(a1),a0
move.b #IOat300,Config_Register(a0) ; set Card Configuration Register
move.l cmm_IOMemory(a1),d0
add.l #IOBase,d0
move.l d0,ioaddr ; calculate I/O base address
bra.s .ok
.error:
moveq #-1,d0 ; could not get card, return error
bra.s .done
.ok:
moveq #0,D0 ; card is active, return OK
.done:
movem.l (A7)+,A3-A6
rts
;=================================================================
; initialise device data structures
;=================================================================
;
; init_device(device)
; a1
;
init_device:
move.l A3,-(A7)
move.l A1,A3
bset #DDB_DEVINIT,dd_flags(A3) ; already initialised ?
bne .done
lea dd_readlist(A3),A0
move.l A0,mlh_tailpred(A0)
lea mlh_tail(A0),A1 ; New MinList for read queue
clr.l (A1)
move.l A1,(A0)
lea dd_writelist(A3),A0
move.l A0,mlh_tailpred(A0) ; New MinList for write queue
lea mlh_tail(A0),A1
clr.l (A1)
move.l A1,(A0)
lea dd_eventlist(A3),A0 ; New MinList for event queue
move.l A0,mlh_tailpred(A0)
lea mlh_tail(A0),A1
clr.l (A1)
move.l A1,(A0)
move.b #NT_INTERRUPT,dd_rxint+ln_type(a3)
move.b #16,dd_rxint+ln_pri(a3)
lea rxintname(pc),a0
move.l a0,dd_rxint+ln_name(a3) ; set up rx swi
lea rxintcode(pc),a0
move.l a0,dd_rxint+is_code(a3)
move.l a3,dd_rxint+is_data(a3)
move.b #NT_INTERRUPT,dd_txint+ln_type(a3)
move.b #0,dd_txint+ln_pri(a3)
lea txintname(pc),a0
move.l a0,dd_txint+ln_name(a3) ; set up tx swi
lea txintcode(pc),a0
move.l a0,dd_txint+is_code(a3)
move.l a3,dd_txint+is_data(a3)
.done:
move.l (A7)+,A3
rts
;============================================================
; PCMCIA status change interrupt
;============================================================
;
; Occurs whenever a PCMCIA status line changes
;
; eg. when the network card activates it's interrupt line
;
;
; entry: d0 = status change(s)
; a1 = device
;
; exit: d0 must be preserved!
;
status_int_code:
movem.l D2-D6/A2-A4,-(A7)
move.l D0,D6 ; d6 = status changes
move.l A1,A4 ; a4 = device
btst #DDB_ONLINE,dd_flags(a4) ; is device online ?
beq .done
move.l ioaddr(pc),a3 ; a3 = nic I/O address
delay
move.b nic_cr(a3),d5 ; save old command
delay
move.b #0,nic_imr(a3) ; prevent nic interrupts
bra .checkint
; interrupt service loop (D3 = interrupt status)
.intloop:
btst #DSIB_ROVRN,d3
beq .no_overflow
; receiver ring buffer overflowed (eek!)
addq.l #1,dd_overflows(a4)
delay
move.b #0,nic_rbcr0(a3)
delay
move.b #0,nic_rbcr1(a3) ; reset remote byte count
delay
move.b #DSTC_LB0,nic_tcr(a3)
delay ; monitor mode
move.b #DSRC_MON,nic_rcr(a3)
delay
move.b #DSCM_NODMA|DSCM_START,nic_cr(a3) ; try to restart controller
delay
move.b #DSRC_AB,nic_rcr(a3)
delay ; normal rx mode
move.b #0,nic_tcr(a3)
.no_overflow:
btst #DSIB_RXE,d3
beq.s .norxerr
addq.l #1,dd_errors(a4)
delay
move.b nic_rsr(a3),d0 ; read rx status
delay
move.b nic_cntr0(A3),D0
delay
move.b nic_cntr1(A3),D0 ; read counters
delay
move.b nic_cntr2(A3),D0
bra.s .rx
.norxerr:
btst #DSIB_RX,d3
beq.s .no_rx
; new packet(s) arrived in receive ring buffer
.rx:
and.b #~(DSIM_OVWE|DSIM_RXEE|DSIM_PRXE),dd_imr(A4) ; ignore rx ints
lea dd_rxint(A4),A1
move.l execbase(PC),A6
jsr _LVOCause(A6) ; to copy packet(s) into waiting ioreqs
.no_rx:
btst #DSIB_TXE,d3
bne.s .tx
btst #DSIB_TX,d3
beq .no_tx
; a packet has just been transmitted
.tx:
moveq #0,d0
delay
move.b nic_ncr(A3),d0 ; read collision count
add.l d0,dd_collisions(a4)
bclr #DDB_TX,dd_flags(A4) ; buffer now free
lea dd_txint(A4),A1
move.l execbase(PC),A6
jsr _LVOCause(A6) ; to transmit next packet
.no_tx:
btst #DSIB_CTRS,d3 ; counter overflow ?
bne.s .counter
bra.s .checkint ; all ints processed
; counter overflow
.counter:
delay
move.b nic_cntr0(A3),D0
delay
move.b nic_cntr1(A3),D0 ; read counters
delay
move.b nic_cntr2(A3),D0
.checkint:
delay
move.b nic_isr(a3),D3 ; D3 = nic interrupt status
delay
move.b d3,nic_isr(a3) ; clear current interrupt bit(s)
and.b dd_imr(a4),d3
bne .intloop ; any valid interrupts ?
.end:
delay
move.b d5,nic_cr(a3) ; restore old command
eor.b #$2c,d6
or.b #$c0,d6
move.b d6,$da9000 ; clear PCMCIA status change bits
delay
move.b dd_imr(a4),nic_imr(a3) ; enable nic interrupts
moveq #0,d0 ; don't clear status bits coz we did
.done:
movem.l (A7)+,D2-D6/A2-A4
rts
;============================================================
; PCMCIA Card Inserted interrupt
;============================================================
;
; Occurs whenever a PCMCIA card is plugged in
;
card_inserted_code:
bset #DDB_CARDIN,dd_flags(a1) ; card is inserted
rts
;============================================================
; PCMCIA Card Removed interrupt
;============================================================
;
; Occurs whenever a PCMCIA card is unplugged
;
card_removed_code:
bclr #DDB_CARDIN,dd_flags(a1) ; card removed
bclr #DDB_ONLINE,dd_flags(a1) ; device not online
bclr #DDB_CONFIGURED,dd_flags(a1) ; hardware address not configured
bclr #DDB_NICUP,dd_flags(a1) ; nic not initialised
rts
rxintname:
dc.b "cnet.device rxint",0
txintname:
dc.b "cnet.device txint",0
cardname:
dc.b "card.resource",0
DeviceName:
dc.b "cnet.device",0
IDString:
dc.b "$VER: cnet.device "
dc.b (VERSION+"0"),".",(REVISION+"0")," "
dc.b __DATE
dc.b " by Bruce Abbott (bhabbott@inhb.co.nz)",10,0
even
; devicequery block
size_supplied:
dc.l S2DQ_SIZE ; bytes supplied (size of this block)
dc.l 0 ; this is type 0
dc.l 0 ; this document is level 0
dc.w ETHER_ADDR_SIZE*8 ; address size in bits
dc.l ETHERPKT_SIZE ; maximum packet data size
dc.l 10000000 ; line rate (10 Megabits/sec)
dc.l S2WIRETYPE_ETHERNET ; what the wire is
; default station address to use if the card won't give it to us.
default_address:
dc.b $00,$80,$ad,$a2,$31,$a7 ; replace this with your card's address!
;--------------------------------------------------------
; Global data
;--------------------------------------------------------
execbase dc.l 0 ; local copy of execbase
ioaddr dc.l 0 ; address of nic I/O registers
rx_header:
ds.b 20 ; received packet header
Endcode:
section buffers,bss
rxbuffer:
ds.b 1600 ; received packet buffer
txbuffer:
ds.b 1600 ; transmit packet buffer