home *** CD-ROM | disk | FTP | other *** search
Text File | 1987-09-14 | 85.3 KB | 1,983 lines |
- * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
- *
- * THIS FILE CONTAINS EXCERPTS FROM THE APPLETALK SOURCES,
- * VERSION 39, AUGUST 1985, AS MODIFIED BY DARTMOUTH COLLEGE
- * TO PRODUCE THE ASYNC APPLETALK DRIVER (.BPP) VERSION 1.2
- * (ASYNC APPLETALK INSTALLER VERSION 2.1) OF MAY 1987.
- *
- * THESE EXCERPTS CONTAIN INFORMATION OF TWO TYPES:
- * 1) CODE WRITTEN ENTIRELY AT DARTMOUTH COLLEGE;
- * 2) CODE WHICH IS FUNDAMENTALLY SIMILAR TO THE
- * PRELIMINARY APPLETALK SOFTWARE DISTRIBUTED
- * WITHOUT RESTRICTION AT THE APPLEBUS DEVELOPER'S
- * CONFERENCE IN CUPERTINO, CA IN MAY, 1984.
- *
- * PORTIONS OF THIS CODE ARE COPYRIGHT OF THE TRUSTEES OF
- * DARTMOUTH COLLEGE OR APPLE COMPUTER INC.
- *
- * THESE CODE SEGMENTS ARE PROVIDED FOR INFORMATION ONLY. NO
- * GUARANTEE OF CORRECT OPERATION IS PROVIDED.
- *
- * FOR MORE INFORMATION ABOUT THIS CODE, CONTACT:
- *
- * Rich Brown
- * Manager of Special Projects
- * Dartmouth College
- * Kiewit Computer Center
- * Hanover, NH 03755
- * 603/646-3648
- *
- * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
-
- ***** file ALAPDEFS.A *****
-
- ; AALAPdefs.a contains all the special definitions which were not
- ; needed for .MPP .
- ;
- ; .BPP et al should now use unmodified versions of:
- ; {AIncludes}atalkequ.a
- ; lapdefs.a
- ; vardefs.a
- ;
- ; Created 31 Mar 87 reb
- ;
- ; AALAP constant defs
- ;
- MaxLAPFrmLen EQU 586+13+3+2 ; DDP data + DDP hdr + LAP hdr + CRC
- FrameChar EQU $A5 ; the Framing Char
- qFrmChar EQU -91 ; for moveq instructions
- DLE EQU $10
- Xoff EQU $13
- Xon EQU $11
-
- lapIM EQU $86 ; I aM
- lapUR EQU $87 ; yoU aRe (sorry for these names...)
- qlapIM EQU -122
- qlapUR EQU -121
-
- noansalrt EQU -15998
- portncalrt EQU -15997
-
- ; Added constant return value for AALAP --
- noAnswer EQU -95 ; same as excessCollsns in real AtalkEqu
-
- AAOfst EQU 10000 ; 0 or 10000 (for final version)
-
- ;+ MPP (Status calls to NBP, DDP and AALAP)
-
- GetStats EQU 400 ; (ABLAP) get the statistics
- GetMyName EQU AAOfst+255 ; get the name of the ATalk driver
- (AALAP)
- GetChar EQU AAOfst+254 ; get the most recently received char
- (AALAP)
- GetLAPStatus EQU AAOfst+253 ; return AALAP status (AALAP)
-
- ;+ MPP (Control calls to NBP, DDP, and AALAP)
-
- FirstAPP EQU AAOfst+237 ; First APP control call
- DoWarnings EQU AAOfst+237 ; Put up the specified alerts
- (AALAP)
- PutChar EQU AAOfst+238 ; Loop 'til TBMT, then output the char
- (AALAP)
- ReInitAALAP EQU AAOfst+239 ; ReInitialize the AALAP variables & SCC
- (AALAP)
- GetNNNN EQU AAOfst+240 ; Do NNNN using SysNetNum and sysLAPAddr
- (AALAP)
- SetBaud EQU AAOfst+241 ; Set the baud rate of the SCC
- (AALAP)
- LastAPP EQU AAOfst+241
- EJECT
- ;
- ; LAP variables
- ;
- WDSPtr EQU MPPVarsEnd ; (4) WDS pointer saved here on writes
- LAPWrtRtn EQU WDSptr+4 ; (4) return adrs of LAPWrite caller
- SaveA45 EQU LAPWrtRtn+4 ; (8) A4 and A5 saved here on interrupt
- SaveDskRtn EQU SaveA45+8 ; (4) DskRtnAdr saved here for
- PollProc
- SavePS EQU SaveDskRtn+4 ; (4) in AALAP, the real PollProc's
- address
- SaveBIn EQU SavePS+4 ; (4) .BIN DCE saved here (for close)
- SaveBOut EQU SaveBIn+4 ; (4) .BOUT DCE saved here (for close)
- SaveVects EQU SaveBOut+4 ; (16) SCC interrupt vectors saved
- here
- SaveRegs EQU SaveVects+16 ; (20) Registers saved here across
- PollProc
-
- ;
- ; Variables for Lisa/Mac hardware differences
- ;
- VAVBufA EQU SaveRegs+20 ; Pointer to VIA or a $FF word
- STLth EQU 6 ; Size of STData area
- VSTData EQU VAVBufA+4 ; Data string to SCC after send
- VDisTxRTS EQU VSTData+1 ; This is the DisTxRTS byte
- EndOrigStuff EQU VSTData+STLth ;
-
- ;
- ; AALAP varibles
- ;
- tWDSptr EQU EndOrigStuff+2 ; (4) WDS ptr of frame being tx
- qWDSptr EQU tWDSptr+4 ; (4) WDS of a queued DevMgr frame
- LastXmit EQU qWDSptr+4 ; (4) Ticks at time of last char sent
- LastRcv EQU LastXmit+4 ; (4) Ticks at time of last good
- received frame
- LAPStash EQU LastRcv+4 ; (4) Pointer to next received char's
- place
- LAPFetch EQU LAPStash+4 ; (4) Pointer to next char to xmit
- LAPInBuf EQU LapFetch+4 ; (4) Pointer to the LAP input buffer
- IMURwds EQU LAPInBUf+4 ; (8) WDS for IM or UR frames
- BusyBuf EQU IMURwds+8 ; (16) Holds up to 16 chars rcvd while
- doingRead
- BusyStash EQU BusyBuf+16 ; (4) pointer to next space in BusyBuf
- BusyFetch EQU BusyStash+4 ; (4) pointer to next char to remove
- IMURbuf EQU BusyFetch+4 ; (8) Holds IM or UR (starting at odd
- adrs)
- InputCRC EQU IMURBuf+8 ; (2) CRC for the receiver
- OutputCRC EQU InputCRC+2 ; (2) CRC for the transmit side
- RcvdLen EQU OutputCRC+2 ; (2) Number of chars received
- TxCount EQU RcvdLen+2 ; (2) Number of char's transmitted
- CRCBuf EQU TxCount+2 ; (2) Two bytes for the CRC for
- xmission
- RandomSeed EQU CRCBuf+2 ; (2) Seed for random number generator
- LastRxCh EQU RandomSeed+2 ; (2) Lsbyte is last rcvd char, else
- $FFFF
- AALAPbaud EQU LastRxCh+2 ; (2) Current baud rate of the LAP
- SentChar EQU AALAPbaud+2 ; (1) True if TxNextCh sent a char
- nFrmChr EQU SentChar+1 ; (1) True if we must send a FrameChar
- nCRC EQU nFrmChr+1 ; (1) True if we must send the CRC
- EscIn EQU nCRC+1 ; (1) Escaping flag for the receiver
- EscOut EQU EscIn+1 ; (1) Transmitter is sending an escaped
- char
- RcvdXoff EQU EscOut+1 ; (1) We received Xoff
- AALAPup EQU RcvdXoff+1 ; (1) true if we've handshook IM & UR
- AALAPstuck EQU AALAPup+1 ; (1) true if we have NNNN conflict
- InpState EQU AALAPstuck+1 ; (1) 0 = idle; <> 0 = in a frame
- stillBusy EQU InpState+1 ; (1) true if still processing a read
- nXon EQU stillBusy+1 ; (1) true if we sent Xoff
- SendingIMUR EQU nXon+1 ; (1) true if sending AALAP control frame
-
- _AssumeEq (InpState+1),stillBusy ; tst.w InpState(A4) in
- _AssumeEq (InpState**$FFFFFFFE),InpState ; myPollProc fails otherwise
-
- IF debug THEN ; doing statistics
- XmitCount EQU SendingIMUR+1
- XOFFTOcount EQU XmitCount+4
- OVRcount EQU XOFFTOcount+4
- RcvIntCount EQU OVRcount+4
- XOFFcount EQU RcvIntCount+4
- XONcount EQU XOFFcount+4
- LongFrame EQU XONcount+4
- ShortFrame EQU LongFrame+4
- FrmCount EQU ShortFrame+4
- NoHandCnt EQU FrmCount+4
- CRCCount EQU NoHandCnt+4
- LenErrCnt EQU CRCCount+4
- BadDDP EQU LenErrCnt+4
- PPCount EQU BadDDP+4
- PPXoffCnt EQU PPCount+4
- DeferXmit EQU PPXoffCnt+4
- ABVarsEnd EQU DeferXmit+4
- ELSE
- ABVarsEnd EQU SendingIMUR+1 ; end of AALAP variables
- ENDIF
-
-
- ***** file MPP.A *****
-
- ... section removed ...
-
- ;___________________________________________________________________________
- ;
- ; SCCConfig - set up the SCC for AppleBus
- ;___________________________________________________________________________
-
- SCCConfig LEA OpenTbl,A0 ; A0 -> (common) open table
- CMP.B #$FF,MacTypeByte ; Mac or Lisa?
- BNE.S @10 ; Branch if Mac - configure it
- BSR ToSCC ; Configure SCC to major settings
- LEA LOpenTbl,A0 ; A0 -> Lisa open table
- @10 BRA ToSCC ; Configure SCC and return
-
- ... section removed ...
-
- ToSCC MOVE.L SCCWr,A3 ; Point to SCC port B write registers
- IF PortA THEN
- ADDQ #ACtl,A3 ; Add in port A offset
- ENDIF
- @10 MOVE (A0)+,D0 ; Get next register number / control
- word
- BEQ.S CloseRTS ; Zero is terminator
- MOVE.B D0,(A3) ; Put out register number
- ROR #8,D0 ; Pickup control word
- MOVE.B D0,(A3) ; Set to SCC
- BRA.S @10 ; And keep going
-
- ... section removed ...
-
- ;_______________________
- ;
- ; Initialization tables
- ;_______________________
-
- ;
- ; SCC Initialization table - common between Mac and Lisa
- ; Entry format: .BYTE control-value, control-reg-number
- ; Taken from the Zilog SCC Application note, 00-2957-02
-
- OpenTbl DC.B ResetOurPort,9 ; ($40 or $80) Reset port
- DC.B $44,4 ; x16 clock, 1 stop, no parity
- DC.B $0,2 ; Interrupt vector = $00
- DC.B $C0,3 ; Rx is 8 bits, disable Rx
- DC.B $E2,5 ; Tx is 8 bits, Disable Tx; DTR, RTS
- on
- DC.B $0,6 ; No address
- DC.B $0,7 ; No Flag character
- DC.B $0,10 ; NRZ
- DC.B $56,11 ; Tx & Rx clock from BRG
- DC.B $2,14 ; BRG source = PCLK, BRG off
- ; enables
- DC.B $3,14 ; BRG on
- DC.B $C1,3 ; Rx on
- DC.B $EA,5 ; Tx on
- ; Interrupt controls
- DC.B MouseInts,15 ; enable DCD ints (for mouse)
- DC.B $10,0 ; reset external ints
- DC.B $10,0 ; reset external ints (twice)
- DC.B $13,1 ; Tx, Rx, Ext int enable
- DC.B MIE,9 ; Master Interrupt Enable
- DC.W 0 ; *** End of table ***
-
- IF RAM THEN ; Only need Lisa table if RAM-based
- ;
- ; SCC initialization table for Lisa
- ; Port A uses PCLK (@4.0 MHz TTL) to drive BRG; Port B uses 3.6864 MHz Xtal
- ;
- IF PortA THEN ; configuration for Port A
- LOpenTbl DC.B $00,14 ; turn off BRG
- DC.B $6A,5 ; enable TX, RTS; DTR low
- DC.B $56,11 ; TTL clock, tx and rx use BRG
- DC.B $02,14 ; Use PCLK to feed BRG, BRG off
- DC.B $03,14 ; BRG on
- DC.W 0
- ELSE ; configuration for PortB
- LOpenTbl DC.B $00,14 ; turn off BRG
- DC.B $6A,5 ; enable TX, RTS; DTR low
- DC.B $D6,11 ; Crystal clock, tx and rx use BRG
- DC.B $00,14 ; Use crystal to feed BRG, BRG off
- DC.B $01,14 ; BRG on
- DC.W 0
- ENDIF
-
- ;
- ; Mac initialization data (first is the post-transmitting SCC string)
- ;
- MacInitData DC.B 5,MDisTxRTS ; ($60) Turn off drivers
- DC.B 14,ResetClks ; ($41) Reset missing clocks flag
- DC.B 3,EnbRxSlv ; ($DD) Enable receiver
- DC.W $2100 ; SR to enable SCC interrupts
- DC.B AbortDelay,0 ; Delay to send out abort bits (3.2B)
- IF RAM THEN
- ;
- ; Lisa initialization data
- ;
- LisaInitData DC.B 5,LDisTxRTS ; ($E2) Turn off drivers
- DC.B 14,ResetClks ; ($41) Reset missing clocks flag
- DC.B 3,EnbRxSlv ; ($DD) Enable receiver
- DC.W $2500 ; SR to enable SCC interrupts
- DC.B 34,0 ; Just delay this much on Lisa (3.2B)
- ENDIF
-
- ***** file LAP.A *****
-
- ;_______________________________________________________________________
- ;
- ; LAP.TEXT - the LAP part of AALAP
- ;
- ; April-August, 1984
- ; Alan Oppenheimer and Larry Kenyon
- ;
- ; Rich Brown, Dartmouth College
- ; May 1987
- ;
- ; Version 1.2a6 Created qWDSptr to point at queued WDS 21 May 87 reb
- ; Version 1.2a5 Always check that TBMT is true before sending 19 May 87 reb
- ; Version 1.2a4 TintHnd, VBLHnd, RintHnd now call TxNextCh; only TintHnd
- ; clears interrupts (as it should be) 14 May 87 reb
- ; Version 1.2a3 Prefetching warning dialogs doesn't work; backed out 10 May 87 reb
- ; Version 1.2a2 tWDSptr now determines whether we're sending a frame;
- ; DoWarn now doesn't read the resource file 8 May 87 reb
- ; Version 1.2a1 Removed queueing from LAPWrite. LAPWrite no longer
- ; allocates memory, so it won't fail if called from
- ; interrupt handling. 19 Apr 87 reb
- ; Version 1.1b2 Changed noAnswer to -95 (so it can be handled like excessCollsns)
- ; LAPWrite returns noAnswer if AALAP not up; (30 Mar 87)
- ; GetNNNN returns noAnswer or PortNotCF;
- ; Changed LAPWrite to return ddpLenErr if too long
- ; Version 1.1b1 Fixed PollProc to be more agressive about sucking chars
- ; from the SCC; added -1 SendChar value (sends Break);
- ; fix Initcursor bug in Dowarn 16 & 30 Dec 86 reb
- ; Version 1.1a1 Output an Xoff if called by PollProc during an input message
- ; 3 Nov 86 reb
- ; Version 1.0b2 Changed to set up SCC properly for Lisa 15 Oct 86
- ; (still has intermittent hangups, tho -- not diagnosed)
- ; Version 1.0b1 Changed last_valid_frame timer to 30 seconds; always send
- ; UR, even after un-matchable IM address
- ; Version 1.0a3 Fixed Status return buffer bug; SetBaud now takes actual
- ; baud rate; added GetLAPStatus call; copy entire message
- ; Version 1.0A2 Added alerts for NoAnswer, PortNotCf (17 Jul 86 reb)
- ; Version 4.2 Int handlers now do IUS etc. more carefully (4 Jul 86)
- ; Version 4.1 Now escapes either parity Xon and Xoff (21 Apr 86)
- ; Version 4.0 First cut at AALAP (26 Oct-14 Dec 85)
- ... section removed ...
- ;
- ; COPYRIGHT (C) 1984 APPLE COMPUTER
- ;_______________________________________________________________________
-
- ... section removed ...
-
- ;___________________________________________________________________________
- ;
- ; MReInit - Control call to reinit AALAP and the SCC
- ;___________________________________________________________________________
-
- MReInit bsr.s AALAPWarm ; Warm start ourselves
- BRA AbusExit ; and return
- ;___________________________________________________________________________
- ;
- ; AALAPCold -- cold start for AALAP; called only once
- ;___________________________________________________________________________
-
- AALAPCold
- ;
- ; Allocate the input buffer (This should be alloc above BufPtr, not sysheap)
- ;
- move.l #maxLAPFrmLen,D0 ; get an AALAP input buffer
- _newptr ,SYS ; from the system heap
- bne.s WarmRTS ; exit if bad
- move.l A0,LAPInBuf(a2) ; otherwise save its pointer
- ;
- ; Clear out LAP variables
- ;
- clr.l WDSPtr(a2)
- clr.l tWDSptr(A2)
- clr.l LAPWrtRtn(A2)
- clr.w SysNetNum(a2)
- clr.b SysLAPAddr(a2)
- clr.l SavePS(A2)
- sf AALAPup(a2)
- sf AALAPstuck(a2)
- ;
- ; Setup SCC for AALAP
- ;
- BSR SCCConfig ; Configure the SCC for Async
- AppleTalk
- move #9600,D0 ; and set up for 9600 baud
- bsr Set_Baud ;
- ;
- ; Reset all the LAP variables which don't irrevocably change the
- ; state of the driver. This routine can be called any time, only
- ; killing the current message(s) in progress.
- ;
- AALAPWarm move.l Ticks,D0
- move.l D0,LastXmit(a2)
- move.l D0,LastRcv(a2)
- lea BusyBuf(a2),A0
- move.l A0,BusyStash(a2)
- move.l A0,BusyFetch(a2)
- move.w #$FFFF,LastRxCh(a2)
- clr.l tWDSptr(A2)
- clr.l qWDSptr(A2)
- clr.w TxCount(a2)
- sf RcvdXoff(a2)
- sf InpState(a2)
- sf EscIn(a2)
- sf SendingIMUR(A2)
- sf stillBusy(a2)
- sf nFrmChr(a2)
- sf nCRC(a2)
- sf nXon(A2)
- WarmRTS rts
-
- EJECT
- ;___________________________________________________________________________
- ;
- ; Status - handle driver status request
- ;___________________________________________________________________________
- _SUBR ; no one better call this...
- Status MOVE.L MPPVars,A2 ; A2 -> our variables
- MOVEQ #StatusErr,D0 ; Assume a status error
- lea CSParam(A0),A1 ; point at the CSParam buffer
- move.w CSCode(A0),D1 ; and get the CScode
-
- IF Stats THEN
- CMP.W #GetStats,D1 ; Clear stats command?
- BNE.S @1 ; check for "What's my Name?" if not
- move.w CSParam(A0),A1 ; CSParam contains a pointer to buffer
- MOVE SR,-(SP)
- MOVE #SCCLockout,SR ; exclude interrupts to keep stats
- clean
- ADD #StatsStart,A2 ; point to stats we keep
- MOVEQ #(StatsLgCnt-1),D0
- MOVEQ #0,D1 ; zero for faster clearing
- @0 MOVE.L (A2),(A1)+ ; return current value
- MOVE.L D1,(A2)+ ; then zero count
- DBRA D0,@0
- MOVE (SP)+,SR
- bra.s AbusExit
- ENDIF
-
- @1 cmp.w #GetMyName,D1 ; is this a "what's my name" call?
- bne.s @2 ; go if not
- Move.l MPP+18,(A1)+ ; move Pascal string from front of driver
- move.b MPP+22,(A1) ; to beginning the buffer (5 chars)
- bra.s @4 ; and exit with good status
-
- @2 cmp.w #GetChar,D1 ; is this a "get last char" call?
- bne.s @3 ; go if not
- move.w LastRxCh(a2),(A1) ; copy the character (word)
- move.w #$FFFF,LastRxCh(a2) ; and flag the character
- bra.s @4
-
- @3 cmp.w #GetLAPStatus,D1 ; is this a "get LAP status" call?
- bne.s AbusExit ; go if not
- move.b AALAPup(A2),(A1)+ ; AALAPup?
- move.b AALAPstuck(A2),(A1)+;AALAPstuck?
- move.w AALAPbaud(A2),(A1) ; What's the baud rate?
- @4 clr.l D0 ; return good status
-
- AbusExit MOVE.L MPPDCE,A1 ; Make sure A1 has DCE address
- AbusExA1 MOVE.L JIODone,-(SP) ; This is how we exit (Prime, Control,
- Status)
- AbusRTS RTS
- SUBEND 'MYSTATUS' ; this marks the AbusExit
-
- Prime BCLR #DrvrActive,DCtlFlags+1(A1) ; *** V2.0C Fix Mac ROM bug
- ***
- RTS ; *** V2.0C Fix Mac ROM bug
- ***
- EJECT
- ;_____________________________________________________________________
- ;
- ; MGetNNNN -- Do the NNNN, using the current values of SysLAPAddr and
- ; SysNetNum. Return bad status if it didn't work.
- ;
- ; On entry: A2 -> BPP variables
- ; On exit: D0 = noErr (0) if we succeeded,
- ; PortNotCF (-98) or
- ; noAnswer (-95) if not
- ;____________________________________________________________________
-
- MGetNNNN bsr.s Get_NNNN ; Use them just as they are
- bra.s AbusExit ; return from the control calls
-
- tries EQU -2 ; counter for the tries
- endtime EQU -6 ; end time
-
- Get_NNNN _SUBR 6
- move.w Ticks+2,RandomSeed(a2) ; randomize things
- move.b SysLAPAddr(a2),D0 ; Node number in D0
- move SysNetNum(a2),D1 ; Net number in D1
- sf AALAPup(a2) ; we're not up yet
- sf AALAPstuck(a2) ; and we're not in trouble either
- move #4,tries(a6) ; tries counter (4 tries)
- @10 move.l Ticks,D2
- add.l #30,D2 ; set endtime to the current time+30
- move.l D2,endtime(a6) ; remember the ending time
- moveq #qlapIM,D2 ; get the lap type
- move.w SysNetNum(a2),D1 ; get the Net number
- move.b SysLAPAddr(a2),D0 ; and the node number
- bsr SendIMUR ; and send it
- @20 clr D0 ; good status if things are OK
- tst.b AALAPup(a2) ; did the magic work?
- bne.s NNNNexit ; go if so
- tst.b AALAPstuck(a2) ; is there an irreconcilable difference?
- bne.s NNNNstuck
- move.l endtime(a6),D2
- cmp.l Ticks,D2 ; otherwise, check the timer
- bpl.s @20 ; loop if not timed out
- sub #1,tries(a6) ; decr the counter
- bgt.s @10 ; loop if non-zero
- moveq #noAnswer,D0 ; They don't want to talk
- bra.s NNNNexit
-
- NNNNstuck moveq #PortNotCF,D0 ; They talk but say bad things
-
- NNNNexit tst.w D0 ; set CC
- _Subend 'GETNNNN ' ; and return
- EJECT
- ;___________________________________________________________________________
- ;
- ; MPutChar -- Kill output and send the char pointed to in the control call
- ;
- ; Entry: A0 -> IOQelement
- ; Exit: Return status is 0000 if noErr,
- ; BadIO if timed out waiting for TBMT
- ;___________________________________________________________________________
-
- SendBrk equ $12 ; Sends Break (w/RTS) when sent to WR5
-
- MPutChar bsr.s Put_Char
- bra AbusExit ; and exit
-
- Put_Char _SUBR
- move.w CSParam(a0),D0 ; get the character (in an integer)
- bmi.s @10 ; if it's 0..255,
- bsr SendChar ; output the character
- bra.s @20 ; and quit
-
- @10 lea BreakTbl,A0 ;
- move.b #SendBrk,(A0) ; set the break bit in WR5
- bsr ToScc ;
- move.l #10,A0 ; wait 10 ticks
- _delay
- move #$EA,D0 ; Enable Tx, DTR, RTS
- CMPI.B #$FF,MacTypeByte ; Mac or Lisa?
- BNE.S @15 ; Branch if Mac (PortA & PortB are same)
- move #$6A,D0 ; Lisa doesn't assert DTR
- @15lea BreakTbl,A0
- move.b D0,(A0) ; and turn the Break off
- bsr ToSCC
- clr D0
-
- @20 SUBEND 'MPUTCHAR'
-
- breaktbl dc.b 0,5 ; THIS WON'T MAKE ROMMABLE CODE
- dc.w 0000
- ;_____________________________________________________________________
- ;
- ; MSetBaud -- send the (integer) value in the CSParamblk to SCC as its Baud
- Rate
- ; Entry: A0 -> IOQelement
- ; Exit: noErr if aok
- ; -1 if requesting 19,200 baud on a Lisa, port A (cannot be done)
- ;_____________________________________________________________________
- ; THIS WON'T MAKE ROMMABLE CODE!
- BaudConsts DC.B 2,14 ; turn off BRG (so it doesn't count for
- a while)
- lsBaudVal DC.B 0,12 ; LSByte of BRG
- msBaudVal DC.B 0,13 ; MSByte of BRG
- BaudSrc DC.B 0,14 ; turn it on again, with proper baud
- source
- DC.W 0000 ; end of constant string
-
- BaudTable DC.W 1200,94,102 ; 1200 baud, Mac&LisaB , LisaA BRG
- constants
- DC.W 2400,46,50 ; 2400 baud
- DC.W 4800,22,24 ; 4800 baud
- DC.W 9600,10,11 ; 9600 baud
- DC.W 19200,4,-1 ; 19200 baud (but not for Lisa Port
- A...)
- BaudTblEnd DC.W -1 ; sentinel
-
- MSetBaud move CSParam(a0),D0 ; get the (integer) baud rate
- bsr.s Set_Baud
- bra AbusExit
-
- Set_Baud _SUBR ; D0 contains the actual desired baud
- rate
- move.w D0,AALAPbaud(A2) ; save the current baud rate
- lea BaudTable,A0 ; point at the table
- @10 cmp.w (a0),D0 ; does it match?
- beq.s @30 ; go if so
- addq.l #6,A0
- tst.w (A0) ; are we done?
- bpl.s @10 ; loop if we didn't hit the sentinel
- moveq #-1,D0 ;
- bra.s @50 ; and bail out
-
- @30 moveq #3,D1 ; set up for Mac port A/B (PCLK/BRG on)
- CMPI.B #$FF,MacTypeByte ; Mac or Lisa?
- BNE.S @40 ; Branch if Mac (PortA & PortB are
- same)
- IF PortA THEN ; Lisa ports A/B differ; Macs don't
- addq.l #2,A0 ; bump to Lisa PortA column
- ELSE
- moveq #1,D1 ; Lisa portB works from Xtal, not PCLK
- ENDIF
- @40 move.w 2(a0),D0 ; get value BRG (-1 if 19,200 on Lisa)
- bmi.s @50 ; exit if negative
-
- ; D0 now contains the value for the BRG
- lea BaudConsts,a0 ; point at the constants
- move.b d0,lsBaudVal-BaudConsts(a0) ; save the LSByte of the BRG
- ror #8,d0
- move.b d0,msBaudVal-BaudConsts(a0) ; and the MSByte of the BRG
- move.b d1,BaudSrc-BaudConsts(a0) ; and the source for BRG
- bsr toSCC ; and output it
- clr d0
- @50 _SUBEND 'MSETBAUD'
- EJECT
- ;___________________________________________________
- ;
- ; MWriteLAP - write out a LAP packet
- ;
- ; Call:
- ; A0 -> IO queue element
- ; A1 -> WDS. First entry must start as follows:
- ; +-----------------+
- ; | Destination addr|
- ; +-----------------+
- ; | | [ for source addr ]
- ; +-----------------+
- ; | LAP type code |
- ; +-----------------+
- ; : :
- ; A2 -> local variables
- ;
- ; Return:
- ; D0 = error code
- ;
- ; NOTE: for MPP, first two data bytes must be length
- ;____________________________________________________
-
- MWriteLAP MOVE.L 2(A1),A0 ; A0 -> first WDS entry
- MOVEQ #LAPProtErr,D0 ; Assume an error (2.3F)
- TST.B LAPType(A0) ; Make sure protocol is a valid one
- ble.s MWRLAPex ; Return error if not
- MOVE.B LAPDstAdr(A0),D2 ; D2 = destination address
- bsr.s LAPWrite ; Write out the packet
- MWRLAPex bra AbusExit
- EJECT
- ;___________________________________________________________________________
- ;
- ; LAPWrite - send a packet out an Async port. Called both by MWriteLAP
- ; and DDPWrite.
- ;
- ; Call:
- ; A1 -> WDS (first entry must start as in MWriteLAP above)
- ; A2 -> local variables
- ; D2 = LAP destination address
- ;
- ; Return:
- ; D0 = noErr or the error code
- ; Uses D1-D3,A0,A1,A3
- ;
- ; Save the WDS passed in
- ; If AALAP isn't up, return noAnswer
- ; Next, check the length of the frame for <= 603 bytes; return error if bad
- ; If we're currently sending a frame:
- ; if it's an IM/UR, simply return (WDS will be sent when done)
- ; if it's not, then stop (somehow we got two frames to send from DevMgr)
- ; If interrupts are on
- ; Update PollProc pointer if it needs it
- ; Check that the AALAP is still working, sending IM/UR if necessary.
- ; Start sending the frame
- ;
- ; This code relies on the Device Manager for queuing. Here's how it works:
- ;
- ; General Rule #1: All operations initiated by the device manager
- ; ultimately return to the DevMgr through jIOdone.
- ;
- ; General Rule #2: All async operations which cannot complete immediately
- ; return thru a RTS. When the operation does complete, the (interrupt)
- ; routine can go thru jIOdone.
- ;
- ; Specific AppleTalk Rule #1: All callers of LAPWrite have bra AbusExit
- ; code right after the call to LAPWrite. This eventually jumps to jIOdone.
- ;
- ; Specific AppleTalk Rule #2: Since they've taken care of the details,
- ; LAPWrite only has to remember two things: If we finish, we can return
- ; to our original caller (by jumping thru LAPWrtRtn to go to the device
- ; manager); If we don't finish, we should return to the caller's caller
- ; (which called the device manager in the first place). Whew!
- ;___________________________________________________________________________
-
- LAPWrite move.l (SP)+,LAPWrtRtn(A2) ; save the caller's adrs
- move.l A1,WDSptr(A2) ; and the frame we're asked to send
-
- move.w #noAnswer,D0
- tst.b AALAPup(a2) ; is the AALAP up?
- beq LAPWexit ; exit if bad
- ;
- ; Next compute the length of the WDS -- exit if it's bad
- ;
- move.l A1,A0 ; get the WDS pointer
-
- clr.l D2 ; D2 = number of data bytes in frame
- clr.l D1 ; D1 = number of segments in WDS
- cmp.w #2,(a0) ; is first segment too short?
- ble.s LAPWexit ; go if it is
- @20 tst.w (a0) ; is WDS length = 0?
- beq.s @30 ; go if so
- add.w (a0),d2 ; add in this length
- addq #1,d1 ; incr the segment counter
- addq.l #6,A0 ; bump the WDS pointer
- bra.s @20
-
- ; D2 is the length of the message we've been asked to send
- ; D1 is the number of segments we've been presented with
- ; (A1 still has WDSptr)
-
- @30 moveq #LAPProtErr,D0
- tst.l d1 ; is D1 (number of segments) < 1?
- ble.s LAPWexit ; go if so (error)
- moveq #ddpLenErr,D0
- cmp.w #603,D2 ; is the length > 603 (3 LAP + 600
- data)
- bgt.s LAPWexit ; go if it's bad
- ;
- ; we can try to send WDS in A1 -- are we currently sending a frame?
- ;
- tst.l tWDSptr(a2) ; are we presently sending a frame?
- beq.s @40 ; go if not
- tst.b SendingIMUR(A2) ; is it an IM or UR?
- beq.s @35 ; go if not
- tst.l qWDSptr(A2) ; is one already queued?
- bne.s @35 ; go if so (stop)
- move.l A1,qWDSptr(A2) ; save the (queued) WDS pointer
- _statcount DeferXmit
- rts
- @35 pea AALAP2in1 ; point at the string
- DC.W $ABFF ; and trap 'em (in lieu of $A9FF)
-
- ;
- ; WDS in A1 is OK to send now: if interrupts enabled,
- ; update PollProc and check time since last good frame
- ;
- @40 move SR,D0
- and #$70,D0 ; is the interrupt mask <> 0?
- bne.s SendWDSptr ; just send it
- ;
- ; Update our local PollProc pointer
- ;
- move SR,-(A7) ; save the state
- move #SCCLockout,SR ; turn off interrupts
- lea myPollProc,A1 ; A1 -> our PollProc
- move.l PollProc,D0 ; get the current PollProc address
- cmp.l D0,A1 ; have we already updated it?
- beq.s @50 ; go if we have
- move.l D0,SavePS(A2) ; else update our saved copy
- move.l A1,PollProc ; and point the real PollProc at us
- @50 move (A7)+,SR ; and re-enable
- ;
- ; check for (Ticks - LastRcv) > 1800 - see if they're still there
- ;
- move.l Ticks,D0 ; have we received a frame recently?
- sub.l LastRcv(a2),D0
- cmp.l #1800,D0 ; (ticks - LastRcv) > 1800 (30 sec)?
- bmi.s SendWDSptr ; go if not (send it)
- bsr Get_NNNN ; do the IM/UR stuff
- beq.s SendWDSptr ; go if it worked
- move.w D0,-(SP) ; otherwise, save the status
- bsr DoWarn ; else, warn them
- move.w (SP)+,D0 ; and return bad status
- ;
- ; Come here if we need to return immediately (status is in D0)
- ;
- LAPWexit move.l LAPWrtRtn(A2),A0 ; this'll get 'em to IOdone
- jmp (A0) ; sooner or later
-
- AALAP2in1 dc.b 24
- dc.b 'AALAP - TWO MSGS AT ONCE'
- align 2
- EJECT
- ;____________________________________________________________________
- ;
- ; SendFrame -- Starts off transmission of a frame
- ;
- ; A0 points to the WDS of the frame to send
- ;
- ; SendFrame sets all the pointers, etc. and then sends the FrameChar
- ; ($A5). The Transmit Interrupt Handler ships all the remaining bytes
- ; as they are needed.
- ;
- ;____________________________________________________________________
-
- SendWDSptr move.l WDSptr(A2),A0 ; get the WDS to send
- SendFrame move.w (a0)+,D0 ; D0 = the length of the 1st segment
- move.l (a0)+,a1 ; a1 -> the first byte of 1st segment
- move.l a0,tWDSPtr(a2) ; and save the pointer to rest of WDS
- subq #2,D0 ; Finagle the length and address
- move D0,TxCount(a2) ; of the segment (AALAP doesn't
- addq.l #2,A1 ; send dest and source node)
- move.l a1,LAPFetch(a2) ;
- st nCRC(a2) ; we'll need to send a CRC
- st nFrmChr(a2) ; and a closing FrameChar
- sf EscOut(a2) ; clear the Escape flag
- clr OutputCRC(a2) ; and the CRC
- moveq #qFrmChar,D0 ; load a FrameChar
- bra.s SendSCC ; and kick off the frame
- EJECT
- ;____________________________________________________________________
- ;
- ; LAPSend -- send the next byte in the LAP frame
- ;
- ; This routine checks to see if we're flow-controlled, if not, it
- ; gets the next char, accumulates the CRC, generates DLE's as
- ; required, and calls the routine to place the byte in the SCC.
- ;
- ; It works from LAPFetch(a2), and advances it (and decrements TxCount)
- ; as necessary.
- ;
- ; If we sent a char, then we set SentChar(A2) to true
- ;____________________________________________________________________
-
- LAPSend tst.b RcvdXoff(a2) ; are we flow controlled?
- bne.s LAPSendRTS ; go if so
-
- move TxCount(a2),D3 ; get the remaining length
- ble.s LAPBadCount ; go if zero or negative
- cmp.w #maxLAPFrmLen,D3 ; check its length
- bgt.s LAPBadCount ; go if too big
-
- move.l Ticks,LastXmit(a2) ; remember when we last sent a char
- subq #1,D3 ; decr the count
- move.l LAPFetch(a2),a0 ;
- move.b (a0)+,D0 ; and fetch the character, bumping the ptr
-
- tst.b EscOut(a2) ; are we escaping this char?
- bne.s @15 ; go if yes -- it's already in CRC
- lea OutputCRC(a2),a3 ; point at the output CRC Accumulator
- bsr NextCRC ; accumulate the un-processed char
-
- cmp.b #DLE,D0 ; test for DLE, Xon, Xoff, FrameChar
- beq.s @10 ; go if it's a special one
- cmp.b #FrameChar,D0
- beq.s @10
- move.b D0,D1
- and.b #$7F,D1 ; is it a XON or XOFF (either parity)?
- cmp.b #Xoff,D1
- beq.s @10
- cmp.b #Xon,D1
- bne.s @20 ; go if it's just a normal character
-
- @10 st EscOut(a2) ; remember that we're escaping
- moveq #DLE,D0 ; data to send is a DLE
- bra.s SendSCC ; (and don't update the pointer/len)
-
- @15 eor #$40,D0 ; come here if we're escaping this char
- @20 move.l a0,LAPFetch(a2) ; update the pointer
- move D3,TxCount(a2) ; and the remaining length
- sf EscOut(a2) ;
- ; ; D0 has the next char to send
- ; bra.s SendSCC ; and send the character
- ;
- ; SendSCC -- sends D0 to the SCC Write Data Register
- ; Assumes that SCC is ready (TBMT is true)
- ; Returns D0 = 0
- ; uses A1
- ;
- SendSCC st SentChar(A2) ; remember we sent a char
- move.l SCCWr,a1 ; point at the SCC Write Control
- IF PortA THEN
- addq.l #ACtl,a1 ; add in the offset for Port A
- ENDIF
- move.b D0,SCCData(a1) ; output the character
- moveq #0,D0 ; clear the return status
- LAPSendRTS rts ; and return
- LAPBadCount pea BadCntStr
- DC.W $ABFF ; Trap 'em (not $A9FF)
- rts
- BadCntStr DC.B 10
- DC.B 'Bad length'
- align 2
- EJECT
- ;____________________________________________________________________
- ;
- ; SendChar -- Synchronously wait for TBMT and send another character
- ; Use Ticks to watch for 1/2 sec timeout, so we don't hang forever
- ;
- ; Entry: D0 = char to send
- ; Exit: D0 = 0000 if OK
- ; D0 = BadTBMT if we timed out (-3110)
- ; A0,A1,D2 changed
- ;____________________________________________________________________
-
- SendChar _SUBR
- move Ticks,D2 ; fail-safe counter
- add.l #30,D2 ; bump by 1/2 second
- @10 bsr.s TestTBMT ; look to see if we can send it
- bne.s @20 ; go if we can
- cmp.l Ticks,D2 ; did we time out?
- bpl.s @10 ; go if not
- move #-3110,D0 ; BadTBMT return code
- bra.s @40
-
- @20 bsr.s SendSCC ; else send it
-
- @40 _SUBEND 'SENDCHAR'
- ;
- ; Check state of TBMT - sets CCR to state of TBMT
- ; Uses A0
- ;
- TestTBMT movem.l SCCRd,A0 ; point at the SCC
- IF PortA THEN
- addq.l #Actl,A0
- ENDIF
- btst #TxEmptyBit,(a0) ; is the TBMT set?
- rts ; return
- EJECT
- ;____________________________________________________________________
- ;
- ; TIntHnd -- this code catches the Tx Buffer Empty interrupts from
- ; the SCC and tries to send another character. If it could not
- ; send a character, it clears the Tx Pending bit, so that the SCC
- ; will not interrupt again. Finally (in any case) it also resets
- ; the highest interrupt under service (IUS) in the SCC to clear
- ; the interrupt before returning.
- ;
- ; On entry, A0/A1 point to the SCC control read/write registers.
- ; Like a normal interrupt handler, it must preserve D4-D7 and A4-A7
- ;____________________________________________________________________
-
- TIntHnd move.l MPPVars,a2 ; point at the MPP Variables
- _statcount XmitCount ;
-
- sf SentChar(A2) ;
- bsr.s TxNextCh ; try to send another char
-
- tst.b SentChar(A2) ; did we?
- bne.s TintIUS ; go if so
- move.l SCCWr,A1 ; otherwise reset TxPend
- IF PortA THEN
- addq.l #Actl,A1
- ENDIF
- move.b #$28,(A1)
- TIntIUS bra DoIUS ; and reset the highest IUS
-
- ;___________________________________________________________________________
- ;
- ; TxNextCh -- try to send (in this order)
- ; the next character of the segment, or
- ; the next segment, or
- ; the CRC, or
- ; the trailing FrameChar.
- ;
- ; If a complete frame which was initiated by the device manager has
- ; been sent, we should jump thru IODone (asking the DevMgr for more
- ; to do). Otherwise, (it was an IM or UR) we look to see if there
- ; is a frame from the DevMgr queued (in WDSptr). If so, we start
- ; sending it, otherwise, we simply RTS.
- ;___________________________________________________________________________
-
- TxNextCh move.l tWDSPtr(a2),D0 ; D0 -> WDS in progress
- beq.s TxNextRTS ; if nil, just exit (no message)
- tst.w TxCount(A2) ; is there more of the segment to send
- bne LAPSend ; if so, send next character
-
- @5 move.l D0,A0 ; otherwise, point at the WDS
- tst (a0) ; check the next length
- beq.s @10 ; go if it's zero (end of the frame)
- move (a0)+,TxCount(a2) ; otherwise, update TxCount and
- move.l (a0)+,LAPFetch(a2) ; and LAPFetch
- move.l a0,tWDSptr(a2) ; and update the tWDSPtr
- bra LAPSend ; and send it off
- ;
- ; Now send the CRC
- ;
- @10 tst.b nCRC(a2) ; do we need to send a CRC?
- beq.s @20 ; go if not
- sf nCRC(a2) ; don't need one now
- move outputCRC(a2),D0 ; get the two CRC bytes
- ror.w #8,D0 ; swap them
- lea CRCBuf(a2),a0 ; point at the CRC Tx Buffer
- move D0,(a0) ; save the CRC bytes
- move.l a0,LAPFetch(a2) ; and save the fetch pointer
- move #2,TxCount(a2) ; save the length, too
- bra LAPSend ; and send them off
- ;
- ; We've sent the CRC, now send the closing FrameChar
- ;
- @20 tst.b nFrmChr(a2) ; do we need to send a FrameChar?
- beq.s @30 ; go if not
- sf nFrmChr(a2) ;
- moveq #qFrmChar,D0 ; get $A5
- bra SendSCC ; send it and exit
- ;
- ; We've sent a full frame, now clean up
- ;
- @30 clr.w TxCount(a2) ; clear the TxCount
- clr.l tWDSPtr(a2) ; clear the tWDSptr (no longer sending)
- ;
- ; Now decide whether to return, wakeup the Dev. Mgr, or start a queued frame
- ;
- tst.b SendingIMUR(A2) ; were we sending an IM or UR?
- beq.s NotIMUR ; go if not
- sf SendingIMUR(A2) ; well, we're not anymore
- move.l qWDSptr(A2),D0 ; is there a queued frame?
- beq.s TxNextRTS ; go if not
- move.l D0,A0
- bra SendFrame ; otherwise, start sending it
- TxNextRTS rts ; otherwise, return (RTS)
- ;
- ; We weren't sending IM/UR so we must have finished a msg from the
- ; device mgr. Therefore, we should return to the Device Manager.
- ;
- NotIMUR clr.l qWDSptr(A2) ; clear out the WDS
- moveq #0,D0 ; good return status
- bra LAPWexit ; and go thru LAPWrtRtn to IOdone
- EJECT
- ;___________________________________________________________________________
- ;
- ; RandomWord - generate a random number
- ;
- ; Call:
- ; RandomSeed(A2) = seed
- ;
- ; Return:
- ; D0 = random number (CCR set to it)
- ;___________________________________________________________________________
-
- RandomWord MOVE RandomSeed(A2),D0 ; D0 = current seed
- MULU #773,D0 ; Times 773
- ADDQ #1,D0 ; Plus 1
- MOVE D0,-(SP) ; Save high byte on stack
- LSL #8,D0 ; Put low byte into high byte
- MOVE.B (SP)+,D0 ; And high byte into low byte
- MOVE D0,RandomSeed(A2) ; Set back in seed
- RTS
- EJECT
- ;________________________________________________________________________
- ;
- ; VBL handler - come here every VBLtimer ticks. Used to check for long
- ; output puases; if we stop for > 1 second, we expermientally send
- ; the next character.
- ; A0 -> VBL queue element
- ;________________________________________________________________________
-
- VBLHnd MOVE #VBLtimer,VBLCount(A0) ; Better re-init VBL count
- MOVE.L MPPVars,A2 ; A2 -> local variables
- ;
- ; Have we sent an Xoff (did we set nXon)? If so, try to send an Xon
- ;
- tst.b nXon(A2) ; do we need an Xon?
- beq.s @20 ; go if not
- bsr TestTBMT ; try to send it to the SCC
- beq.s VBLHndRTS ; quit if we couldn't send it
- moveq #Xon,D0
- bsr SendSCC ; send an Xon
- sf nXon(A2) ; and clear the flag
- bra.s VBLHndRTS ; and quit
- ;
- ; Check for long pause during transmit
- ;
- @20 tst.l tWDSptr(A2) ; do we have anything to send?
- beq.s VBLHndRTS ; return if not
- move.l Ticks,D0
- sub.l LastXmit(a2),D0 ; if (ticks - LastXmit) > 60 then
- cmp #60,D0 ; let's try to send another char
- bmi.s VBLHndRTS
- bsr TestTBMT ; is TBMT set (can we send another char?)
- beq.s VBLHndRTS ; go if not
- sf RcvdXoff(a2) ;
- _statcount XOFFTOcount
- MOVE #SCCLockout,SR ; exclude SCC interrupts (VIA priority < SCC)
- bsr TxNextCh ; otherwise, do another character
- VBLHndRTS rts ; this'll restore SR et al
- eject
- ;___________________________________________________________________________
- ;
- ; myPollProc -- AALAP PollProc addendum (predendum?):
- ;
- ; The AALAP needs a bit of a PollProc, since it will lose characters
- ; whenever the disk spins. Of course, all good Macintosh programmers
- ; know that the Printer Port (PortB) isn't polled by the disk driver
- ; since there's just not enough horsepower to go around.
- ;
- ; The PollProc is called by the disk driver to poll PortA. We
- ; execute a snippet of code before the real PollProc, and send an
- ; Xoff to the other end if we're receiving or processing a message
- ; while the disk is spinning. Then we transfer to the real PollProc.
- ;
- ; This routine preserves all regs except the SR. It does this by
- ; reserving a longword on the stack, and then stuffing the SavePS
- ; value in it. If it's zero, then there wasn't a PollProc, and we
- ; pop that value off the stack and return to the disk driver. If
- ; that value wasn't zero, then the real PollProc's address will be
- ; on the top of the stack, and we go there. The disk driver's return
- ; address will be left on the stack, allowing the PollProc to return
- ; normally.
- ;
- ; InpState and stillBusy must both be in the same word. The
- ; tst.w InpState(A2) below fails otherwise.
- ;___________________________________________________________________________
-
- myPollProc subq #4,A7 ; save space for a return adrs
- move.l A2,-(SP) ; and save A2
- move.l MPPVars,A2 ; point at the MPP locals
- tst.b nXon(A2) ; have we already sent an Xoff?
- bne.s myPPexit ; go if so
- tst.w InpState(A2) ; are we receiving or processing a message?
- beq.s myPPexit ; go if not
-
- movem.l A0/A1/D0,-(SP) ; save regs
- @10 bsr StashSCCch ; grab a char from the SCC, save it
- bne.s @10 ; loop 'til it's empty
- statcount PPCount
- bsr TestTBMT ; is it OK to send the Xoff?
- beq.s @30 ; go if not
- moveq #Xoff,D0
- bsr SendSCC ; send Xoff
- st nXon(A2) ; and remember we need Xon
- statcount PPXoffCnt
- @30 movem.l (SP)+,A0/A1/D0 ; restore the regs
-
- myPPexit move.l SavePS(A2),4(SP) ; move address onto stack (sets CC)
- movea.l (SP)+,A2 ; restore A2
- bne.s @20 ; go if PollProc adrs <> 0 (use it)
- addq.l #4,SP ; else pop the (nil) adrs
- @20 rts ; and go there
-
- EJECT
- ;___________________________________________________________________________
- ;
- ; ExtIntHnd -- catch the External or Status Interrupts from the SCC
- ;
- ; Checks for mouse interrupt, passes control if it is one, else resets
- ; the external/status SCC interrupts.
- ;___________________________________________________________________________
-
- ExtIntHnd btst #DCDbit,D1 ; did the DCD bit change (mouse moved)
- beq.s @10 ; go if not
- move.l MouseVector,A3 ; else, point at the mouse handler
- jmp (A3) ; and go there
-
- @10 move.b #$10,(a1) ; reset ext interrupts
- move.b #$10,(a1) ; (twice)
- move.b #ResetIUS,(a1) ; Reset Highest IUS in SCC (to WR0)
- rts
- EJECT
- ;___________________________________________________________________________
- ;
- ; RIntHnd - SCC receive interrupt handler
- ;
- ; Called: A0 -> SCC control read register
- ; A1 -> SCC control write register
- ;
- ; This code is structured differently from the ABLAP code, since
- ; the arrival rate of the chars is so much slower for AALAP. Normal
- ; ABLAP routines call ReadPacket and ReadRest to get pieces or the rest
- ; of the frame as they arrive in real time. With AALAP, the character
- ; arrival rate is so slow that we copy the entire frame into an
- ; interrupt-time buffer.
- ;
- ; When we receive a good frame, we then pass control to the appropriate
- ; protocol handler, which then makes calls on ReadPacket and ReadRest to
- ; dole out the characters as necessary.
- ;
- ; Like all Mac interrupt handlers, it must preserve D4-D7 and A4-A7.
- ; and return with a RTS instruction.
- ;
- ; Since the default DDP socket listener is quite slow (3-4 msec to process
- ; a newly received message) we set up a buffer to contain characters
- ; which arrive during the time the socket listener is in control. We
- ; set a flag (stillBusy) to indicate that we're still busy, and save the
- ; chars in BusyBuf.
- ;_________________________________________________________________________
-
- SpIntHnd
- RIntHnd move.l MPPVars,A2 ; A2 -> driver variables
- _statcount RcvIntCount ; remember the number of Rcv
- interrupts
-
- RIntHnd10 bsr NextChar ; handle next char (from BusyBuf or
- SCC)
- beq RIntRTS ; quit if no data
-
- and #$00FF,D0 ; use only eight bits
- move.w D0,LastRxCh(a2) ; remember the char
- ;
- ; Check for flow control from other side
- ;
- @15 move.b D0,D1 ; check for either parity Xon/Xoff
- and.b #$7F,D1
- cmp.b #Xoff,D1 ; is it a control-S?
- bne.s @20 ; go if not
- _statcount XOFFcount ; count it
- st rcvdXoff(a2) ; and remember we received Xoff
- bra.s RIntHnd10 ; loop for another char
-
- @20 cmp.b #Xon,D1 ; or is it a control-Q?
- bne.s @30 ; go if not
- _statcount XONcount
- sf rcvdXoff(a2)
- bsr TestTBMT ; is the tx empty?
- beq.s RIntHnd10 ; loop if not
- bsr TxNextCh ; otherwise, start up Tx side again
- bra.s RIntHnd10 ; loop for another char
- ;
- ; Watch out for framing characters
- ;
- @30 cmp.b #FrameChar,D0 ; is it a framing character?
- beq.s GotFrmCh ; go if so
- tst.b InpState(a2) ; are we in a frame?
- beq.s RintHnd10 ; loop for another char
- EJECT
- ;
- ; Maybe this is a data char -- check the frame length
- ;
- cmp #MaxLAPFrmLen,rcvdlen(a2) ; is the frame too long?
- bls.s @50 ; go if it's OK
- _statcount LongFrame ; remember the long frame
- sf InpState(a2) ; go idle
- bra.s RIntHnd10 ; loop for another char
- ;
- ; We have a real char -- un-escape it
- ;
- @50 cmp.b #DLE,D0 ; is it a DLE?
- bne.s @90 ; go if not
- st EscIn(a2) ; remember we've seen an escape
- bra.s RIntHnd10
- ;
- ; This is a data char -- complete any escaping, accumulate the CRC
- ;
- @90 tst.b EscIn(a2) ; should we escape it?
- beq.s @100 ; go if not
- eor #$40,D0 ; xor with $40
- sf EscIn(a2) ; and clear the escape flag
-
- ; now we've got a good char
- @100 lea inputCRC(a2),a3 ; point at the CRC accumulator
- bsr NextCRC ; update the CRC accum using byte in
- D0
- move.l LAPStash(a2),a0 ; point at the next free char in
- buffer
- move.b D0,(a0)+ ; save the char in the buffer, bump the
- pointer
- addq #1,rcvdlen(a2) ; increment the bytes-read counter
- cmp #3,rcvdlen(a2) ; have we read in exactly three chars?
- bne.s @110 ; go if not
- move.l LAPInBuf(a2),a0 ; otherwise point at the LAPInBuf
- @110 move.l a0,LAPStash(a2) ; and update the pointer
- bra RIntHnd10 ; loop for another char
-
- RIntRTS bra DoIUS ; reset Highest IUS and return
-
- ;
- ; We've discovered a FrameChar -- check if we're done or just starting
- ;
- GotFrmCh tst.b InpState(a2) ; are we in a frame?
- beq.s FrmStart ; go if not (we will be)
-
- FrmEnd cmp #2,rcvdlen(a2) ; found closing char
- bhi.s CheckCRC ; go if frame is long enough
- _statcount ShortFrame ; else, flag that we got a short frame
- ; and fall into FrameStrt
- ;
- ; We're in a frame now!
- ;
- FrmStart lea toRHA(a2),a3 ; a3 -> RHA (holds 1st 5 bytes)
- move.b sysLAPAddr(a2),(a3)+ ; copy the node number
- move.b sysABridge(a2),(a3)+ ; and the bridge address
- move.l a3,LAPStash(a2) ; remember where next byte goes
- st InpState(a2) ; change the InpState to in_msg
- sf EscIn(a2) ; and we're not escaping data
- clr InputCRC(a2) ; no CRC yet
- clr rcvdlen(a2) ; no data, either
- bra.s RIntRTS
- EJECT
- ;
- ; We received a complete frame -- check the CRC
- ;
- CheckCRC
- sf InpState(a2) ; we're not in a frame now
- tst InputCRC(a2) ; is the CRC zero?
- beq.s LAPDemux ; go if it is OK
- _statcount CRCCount ; save the statistic
- bra.s RIntRTS ; and exit
- ;
- ; Come here on receipt of a good frame. We've cleared the InpState
- ; to indicate we're out of a frame.
- ;
-
- LAPDemux _statcount FrmCount ; log another good frame
- move.l Ticks,LastRcv(a2) ; remember this frame's arrival time
- lea 2+toRHA(a2),a3 ; a3 -> LAP type byte
- MOVE.B (A3)+,D0 ; Get the LAPtype, bump pointer
- tst.b D0
- BMI LAPIn ; If minus, it's a LAP packet
-
- ;
- ; Got a data packet - look for a protocol handler
- ;
- tst.b AALAPup(a2) ; but first, is the AALAP up?
- beq.s @60 ; go if it's not up
- MOVEQ #(LAPTblSz-1),D2 ; D2 = index into active protocols list
- @30 CMP.B Protocols(A2,D2),D0 ; Match?
- DBEQ D2,@30 ; (If none, D2 is negative - 3.1F)
- LSL.W #2,D2 ; Make D2 a longword index into Handlers
- ;
- ; Got a protocol handler -- Compute the desired length of the message in D1
- ;
- move.b (a3)+,D1 ; Get MSByte of the length into D1
- and #3,D1 ; mask for two lsbits
- LSL #8,D1 ; Move to proper position
- MOVE.B (a3)+,D1 ; D1 = total length
- move rcvdlen(a2),D0 ; D0 = total chars received (DDP + LAP
- + CRC)
- subq #3,D0 ; disregard LAP type and CRC
- cmp D1,D0 ; are they equal?
- beq.s @40 ; go if so
- _statcount LenErrCnt ; save the stats
- bra RIntRTS ; and exit
-
- @40 SUBQ #2,D1 ; Subtract 2 for length bytes
- move d1,RcvdLen(a2) ; and remember the number of unread chars
- EJECT
- ;___________________________________________________________________________
- ;
- ; At this point, Handlers(A2,D2) points to the address of the protocol
- ; handler for this packet's protocol (or D2 is negative if there is
- ; none -- 3.1F). JMP to it with the following:
- ;
- ; A0,A1 = SCC read/write addressses
- ; A2 = ptr to driver locals
- ; A3 = ptr into the RHA (first 5 bytes loaded)
- ; A4 will be the address of our read packet routine
- ; A5 will be saved for handler's usage (until packet's all in or error)
- ; D1 = length of packet still left to read (from header)
- ;
- ; The protocol handler must obey the following conventions:
- ;
- ; 1) It must preserve, across the call, A0-A2, A4 and D1
- ; 2) A6 and D4-D7 must be saved and restored if used.
- ; 3) It must JSR to the routine at (A4) or 2(A4) with registers as defined
- ; there, for the purpose of reading more of the packet and eventually
- ; resetting the SCC for the next interrupt.
- ;___________________________________________________________________________
-
- TST D2 ; Is there a protocol handler? (3.1F)
- BMI.S @60 ; Branch if not
- bsr DoIUS ; reset Highest IUS
- MOVEM.L A4/A5,SaveA45(A2) ; Save A4 and A5 (may be free time now)
- move.l LAPInBuf(a2),a4 ; point at the next char of the msg
- move.l A4,LAPStash(a2) ; (we can snatch A4 for a few instrs)
- MOVE.L Handlers(A2,D2),A5 ; A5 -> protocol handler
- LEA ReadPacket,A4 ; A4 -> ReadPacket
- st stillBusy(a2) ; remember we're processing a frame
- move.w VSCCEnable(A2),SR ; re-enable so we can catch more chars (!)
-
- JSR (A5) ; Call the protocol handler
-
- move.l MPPVars,A2 ; point at our variables
- cmpa.l SaveA45(A2),A4 ; paranoia land -- make sure they've left
- bne.s @45 ; things as they should be
- cmpa.l (SaveA45+4)(A2),A5
- beq.s @50
- @45 pea BadA4A5
- DC.W $ABFF ; print the text (in lieu of $A9FF)
- @50 sf stillBusy(A2) ; and now we're not in a frame
- rts ; exit the interrupt handler
- ;
- ; No handler, just log the error
- ;
- @60 _StatCount NoHandCnt ; Count packets without a handler
- bra RIntRTS ; and exit
- BadA4A5 DC.B 17 ; debugging only
- DC.B 'AALAP - Bad A4/A5'
- align 2
- EJECT
- ;______________________________________________________________________
- ;
- ; NextChar -- Handle the next char
- ;
- ; This routine does two things: If we're awaiting a full message, then
- ; it gets the next character. That char may have arrived from the SCC,
- ; or it may be a char left in the BusyBuf. (Chars in the BusyBuf take
- ; precedence.)
- ;
- ; If we're still processing the previous message (stillBusy set true),
- ; then all characters which arrive will be placed in BusyBuf, and the
- ; associated pointers updated. (Note: myPollProc also inserts data
- ; into the BusyBuf, but it doesn't set stillBusy.)
- ;
- ; Uses A0,A1,D0
- ; Assumes A2 -> MPPVars
- ;
- ; Returns Z if no character
- ; NZ if char present (char is in 8 lsbits of D0)
- ;______________________________________________________________________
-
- NextChar _SUBR
- tst.b stillBusy(A2) ; are we still processing the prev.
- frame?
- bne.s @30 ; go if we are
-
- bsr.s GetBusyChar ; else, look for a char from BusyBuf
- bne.s @50 ; quit if we got one
- bsr.s GetSCCchar ; else check the SCC
- bra.s @50 ; and quit
-
- @30 bsr.s StashSCCch ; stash a char from SCC into BusyBuf
- bne.s @30 ; go back and look for more
-
- @50 _SUBEND 'NEXTCHAR'
- _assumeEq BusyStash,BusyBuf+16 ; otherwise cmpa.l A0,A1 (above)
- fails
-
- GetBusyChar _SUBR ; get a char from the BusyBuf
- move.l BusyFetch(A2),D0 ; get the fetch pointer
- cmp.l BusyStash(A2),D0 ; is it the same as the stash pointer
- bne.s @10 ; go if not (more chars to do)
- lea BusyBuf(a2),a0 ; point at the busy buffer
- move.l a0,BusyStash(A2) ; and save it in the BusyStash
- move.l a0,BusyFetch(A2) ; and BusyFetch
- moveq #0,D0 ; clear the CC
- bra.s @20
- @10 move.l D0,A0 ; there's still more to take
- move.b (A0)+,D0 ; get the byte
- move.l A0,BusyFetch(A2) ; update the pointer
- or.w #$100,D0 ; make CC <> Z (must preserve 8
- lsbits)
- @20 _SUBEND 'GETBUSYC'
- EJECT
- ;______________________________________________________________________
- ;
- ; GetSCCchar and StashSCCch both are called by RintHnd and myPollProc
- ; BOTH ROUTINES MAY ONLY USE A0, A1, AND D0!!!!! (A2 will -> MPPVars)
- ;
- ; GetSCCchar looks at RCA on the proper channel, and returns the char
- ; in D0 if there was one (with CC set <> Z); else it returns CC = Z.
- ;______________________________________________________________________
- GetSCCchar movem.l SCCRd,A0/A1 ; forces A0/A1 to point at SCC
- IF PortA THEN
- addq.l #Actl,A0
- addq.l #Actl,A1
- ENDIF
- btst #RCAbit,(A0) ; is there a char?
- beq.s @20 ; go if not
- move.b #1,(a1) ; point at the error bits from RR1
- nop
- move.b (a0),D0 ; get them (Overrun,Framing) in D0
- and #$70,D0 ; any error bits?
- beq.s @10 ; go if not
- move.b #ResetErr,(a1) ; else send Error Reset to WR0
- nop
- move.b #1,(a1) ; point at WR1
- nop
- move.b #$13,(a1) ; and set up for int on all rx chars
- nop
- _statcount OVRcount ; count 'em
- @10 move.b SCCData(a0),D0 ; and get the data (EVEN IF ERROR!)
- or.w #$100,D0 ; set the SR (to NZ -- there's a char)
- @20 rts
- ;
- ; StashSCCch -- take a char from SCC, save in BusyBuf if there's space
- ; Return Z if no char or no space; NZ otherwise
- ;
- StashSCCch bsr.s GetSCCchar ; look for a char in the SCC
- beq.s @50 ; go if none
- lea BusyStash(a2),A1 ; point at the BusyStash pointer
- move.l (a1),A0 ; and get it
- cmpa.l A0,A1 ; will this be too many chars?
- beq.s @50 ; yes, simply exit (and ignore the char)
- move.b D0,(a0)+ ; save the char, and bump the pointer
- move.l A0,BusyStash(A2) ; and update the pointer
- or.w #$100,D0 ; set the CC <> Z ('cause we took one )
- @50 rts ; and return
- EJECT
- ;______________________________________________________________________
- ;
- ; DoIUS -- reset Highest IUS
- ;______________________________________________________________________
-
- DoIUS _SUBR
- move.l SCCWr,A1 ; point at the SCC write regs
- IF PortA THEN
- addq.l #Actl,A1
- ENDIF
- move.b #ResetIUS,(a1) ; Reset Highest IUS in SCC (to WR0)
- _SUBEND 'DOIUS '
- EJECT
- ;______________________________________________________________________
- ;
- ; LAPIn - it's a LAP control packet.
- ;
- ; D0 = LAP type
- ; A3 -> remainder of the frame
- ; Note: for IM/UR frames, the net number (2 bytes) is at (a3),
- ; but the node number (1 byte) is the first byte in LAPInBuf
- ;______________________________________________________________________
- ;
- ; Check for IM
- ;
- LAPIn move (a3),D1 ; D1 = Net number (a3 sb even)
- move.l LAPInBuf(a2),A0 ; point at first char in input buf
- move.b (a0),D2 ; D2 = node number
- cmp.b #lapIM,D0 ; is it an IM?
- bne.s @60 ; go if not
- move D2,D0 ; D0 = node number
- sf RcvdXoff(A2) ; so we can start sending
- bsr.s CheckIM ; figure out the net and node to send
- bsr.s SendIMUR ; send 'em
- bra.s @80
- ;
- ; Check for UR
- ;
- @60 cmp.b #lapUR,D0 ; is it a UR?
- bne.s @80 ; go if not
- move D2,D0 ; D0 = Node number (D1 = Net number)
- bsr.s CheckUR ; check these values, return <> 0 if OK
- sne AALAPup(a2) ; if non-zero, then we're up
- @80 rts ; and return
-
- _AssumeEq lapENQ,$81 ; (1)
- _AssumeEq lapRTS,lapENQ+3 ; (2)
- _AssumeEq lapCTS,lapRTS+1 ; (3)
- EJECT
- ;__________________________________________________________________________
- ;
- ; CheckIM -- check the received IM frame, compute UR response
- ;
- ; Entry: D0 = their node number
- ; D1 = their network number
- ; Exit: D0,D1 = node, net number for the UR
- ; D2 = qlapUR
- ; Changes A0,A1,A3, D0-D3
- ;__________________________________________________________________________
-
- CheckIM move.l #0,A0 ; return nil sometimes
- move.w SysNetNum(a2),D2 ; D2 = our Net number
- beq.s @10 ; go if so -- check the node numbers
- move D2,D1 ; else, use our net number
- @10 move.b SysLAPAddr(a2),D3 ; D3 = our node number
- @15 tst.b D0 ; while (theirnode <> 0)
- beq.s @18 ; & (theirnode <> mynode)
- cmp.b D3,D0 ; have we both chosen the same value?
- bne.s @20 ; go if not -- return their value
- @18 bsr RandomWord ; choose a random value
- and #$7F,D0 ; mask to 7 bits
- bra.s @15 ; loop to insure they're different
- @20 move.b D0,sysABridge(a2) ; remember their node number
- moveq #qlapUR,D2 ; D2 = LAP type
- rts
-
- EJECT
- ;__________________________________________________________________________
- ;
- ; CheckUR -- check the received UR frame
- ;
- ; Entry: D0 = node number
- ; D1 = network number
- ; Exit: D0 = 0 if net/node didn't match
- ; <> 0 if they matched right off
- ;
- ;__________________________________________________________________________
-
- CheckUR SUBR
- cmp SysNetNum(a2),D1 ; Network numbers match?
- bne.s @10 ; go if not
- cmp.b SysLAPAddr(a2),D0 ; Node number match?
- bne.s @10 ; go if not
- moveq #-1,D0 ; make D0 non-zero (it's OK)
- bra.s CkURRTS ; and exit
- @10 tst SysNetNum(a2) ; is our network number 0000?
- bne.s @50 ; go if not (we cannot resolve this)
- move D1,SysNetNum(a2) ; save their Net/Node suggestions
- move.b D0,SysLAPAddr(a2)
- bra.s @60
-
- @50 st AALAPstuck(a2) ; we're really bad off -- NNNN conflict
- @60 clr D0 ; we didn't match
-
- CkURRTS _SUBEND 'CHECKUR '
- EJECT
- ;_____________________________________________________________________
- ;
- ; SendIMUR - This routine fills and sends an IM or UR frame. This is
- ; a bit dicey, since a UR may be required as a result of receiving
- ; an IM. Since it's difficult to abort a frame already in progress,
- ; we finesse the problem by not sending the IM/UR frame. Here's why
- ; it works:
- ;
- ; A UR response is only necessary in two cases:
- ; a) we're trying to bring the link up, and the other guy said "IM";
- ; b) he hasn't heard from us, and he wants to make sure we're here.
- ;
- ; For a), we shouldn't be talking, but he'll ask again anyway;
- ; for b), the IM is trying to force us to send a good frame.
- ; If the frame in transit makes it, OK. If not, he'll
- ; still ask again.
- ;
- ; Entry: A0 -> master pointer of this hdlblk
- ; A2 -> MPPVars
- ; D0 = node number
- ; D1 = Net number
- ; D2 = LAP type
- ; Exit: A0,A1,A3,D0-D3 changed
- ;_____________________________________________________________________
-
- SendIMUR _SUBR
- tst.l tWDSptr(A2) ; are we sending?
- bne.s SndIMUR1 ; yes, just return
- lea IMURbuf+1(A2),A1 ; A1 points at IMURbuf (odd adrs)
- move.b D2,2(a1) ; save the LAPtype (IM or UR)
- move.w D1,3(a1) ; and the Net number
- move.b D0,5(a1) ; and the Node number
-
- lea IMURwds(A2),A0 ; A0 points at the WDS
- move.w #6,(A0) ; save the length
- move.l A1,2(A0) ; and the pointer to the data
- clr.w 6(A0) ;
-
- st SendingIMUR(A2) ; remember this!
- bsr SendFrame ; and send it
- SndIMUR1 _SUBEND 'SENDIMUR'
- EJECT
- ;___________________________________________________________________________
- ;
- ; ReadPacket - read in the specified number of bytes into the specified
- ; buffer. It is an error to request more bytes than have been received.
- ;
- ; ReadRest - read in the rest of the packet, putting the specified number
- ; of bytes into the specified buffer. Error if packet longer than buffer.
- ;
- ; Call:
- ; A0,A1,A2 = SCC read and write addresses and local variables
- ; A3 -> buffer to read into
- ; A4 -> start of ReadPacket
- ; D3 = byte count to read (word)
- ;
- ; Return:
- ; D0 changed
- ; D1 number of chars still unread (ReadPacket); modified (ReadRest)
- ; D2 saved
- ; D3 = 0 if exact number of bytes requested were read
- ; > 0 indicates number of bytes requested but not read
- ; (packet smaller than requested maximum)
- ; < 0 indicates number of extra bytes read but not returned
- ; (packet larger than requested maximum)
- ; A0,A1 preserved by ReadPacket, modified by ReadRest
- ; A3 -> one past where last character went
- ; A4,A5 saved (until packet's all in or error)
- ;
- ; NOTE: CRC bytes not included in counts
- ;___________________________________________________________________________
-
- ReadPacket BRA.S DoRP ; Need this for two entry points
-
- ReadRest movem.l a0/a1/D2,-(sp) ; save some regs
- move RcvdLen(a2),D1 ; get the number of remaining chars in D1
- move D1,D0 ; we expect to copy D1 bytes
- move #0,-(sp) ; and expect good return status
- sub D1,D3 ; compute (D3 - D1)
- bpl.s @1 ; go if we should copy D1 bytes (it fits)
- add D3,D0 ; otherwise, copy D3 bytes (d1 + (d3-d1))
- move #-1,(sp) ; and set error return status
- @1 movem.l SaveA45(a2),a4/a5 ; restore A4 and A5
- bra.s DoCopy ; and go to the common code
-
- DoRP movem.l a0/a1/D2,-(sp) ; push some regs
- move RcvdLen(a2),D1 ; get the number of remaining chars in D1
- move D1,D0 ; assume we'll copy them all
- move #-1,-(sp) ; and that there's an error
- sub D3,D1 ; update D1 (remaining bytes in buf)
- bmi.s DoCopy ; go if it's negative (error)
- move D3,D0 ; we'll read what they asked for (D3)
- clr (sp) ; and remember that it's exactly right
- clr D3 ;
-
- DoCopy move.l LAPStash(A2),a0 ; point at the source data
- ext.l D0 ; belt and suspenders (D0 = actual length)
- add.l D0,LAPStash(A2) ; and update the LAPStash value
- sub D0,RcvdLen(a2) ; and the num chars remaining
- move.l A3,A1 ; point at the dest buffer
- lea 0(A3,D0),A3 ; update the return pointer
- _BlockMove ; Do It
- move RcvdLen(a2),D1 ; return number of unread chars
- move (sp)+,d0 ; get the return status back
- movem.l (sp)+,a0/a1/D2 ; get the other registers
- tst D0 ; set the CCR
- rts
- EJECT
- ;___________________________________________________________________________
- ;
- ; NextCRC -- compute a CRC on the word pointed at by A3 and the char in D0
- ;
- ; This routine computes a CRC-16 on a stream of bytes. It uses a
- ; table lookup scheme to implement a x^16 + x^15 + x^2 + 1 polynomial.
- ; The interested reader is referred to McNamara's Technical Aspects
- ; of Data Communications, second edition, pps 110-122 for an obliquely
- ; related discussion.
- ;
- ; This routine takes the storage short cut of looking up two four-bit
- ; values in a 16-entry table instead of one eight-bit value in a 256
- ; word table. This saves a considerable amount of space (32 bytes vs.
- ; 512 bytes for the table).
- ;
- ; One pass thru this routine (one character) is about 262 cycles, or
- ; 33.45 usec on a Mac. This is a data rate of ~29,900 char/sec,
- ; or plenty fast to keep up with a 9600 baud link.
- ;
- ; Entry: A3 -> CRC accumulator
- ; D0 LSbyte is the data char (already masked to 8 bits)
- ;
- ; Exit: D1,D2 changed
- ; Other regs unchanged
- ;____________________________________________________________________________
-
- NextCRC _SUBR 0 ; for macsbug
- move (a3),D2 ; D2 is the temp accumulator
- move D0,D1 ; make a copy of the input character
- ; first work on the least significant nibble
- eor D2,D1 ; xor the accumulator with the data char
- and #$0F,D1 ; to get an index into the CRCTable
- add D1,D1 ; to make a word index
- lsr #4,D2 ; shift the CRC right four bits
- move CRCTable(D1),D1
- eor D1,D2 ; and mask it with the approp. table entry
- move D0,D1
- lsr #4,D1 ; shift the data char right four bits
- ; and do it again for the high nibble
- eor D2,D1 ; xor the accumulator with the data char
- and #$0F,D1 ; to get an index into the CRCTable
- add D1,D1 ; to make a word index
- lsr #4,D2 ; shift the CRC right four bits
- move CRCTable(D1),D1 ; and mask it with the approp. table entry
- eor D1,D2
- move D2,(a3) ; remember this CRC for next time
- _SUBEND 'NEXTCRC '
-
- CRCTable DC.W $0000,$CC01,$D801,$1400
- DC.W $F001,$3C00,$2800,$E401
- DC.W $A001,$6C00,$7800,$B401
- DC.W $5000,$9C01,$8801,$4400
- EJECT
- ;
- * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
- * * * * * * * ****
- ;___________________________________________________________________________
- ;
- ; MDoWarn -- Control call to put up a warning
- ;
- ; Entry: A0 -> IOQelement
- ;___________________________________________________________________________
-
- MDoWarn move CSParam(a0),D0 ; get the error code into D0
- bsr.s DoWarn ; warn 'em and return status in D0
- bra AbusExit ; and exit
-
- ; Put up alerts
- ;____________________________________________________________________
- ;
- ; DoWarn -- Warn the user... Give a beep, and display a dialog;
- ; wait for their choice, then try the NNNN one more time.
- ; If they choose "Use new address" from Mismatch dialog,
- ; set SysLAPaddr and SysNetNum to zero before exiting.
- ;
- ; Entry: D0 = PortNotCf
- ; noAnswer
- ; Exit: D0 = -4001 (user clicked OK/Try again)
- ; -4002 (user clicked Use New)
- ; -193 (ResFNotFound)
- ;____________________________________________________________________
-
- resfile EQU -2 ; res file number
- dlgwindow EQU -6 ; dialog window handle
- warning EQU -8 ; error number/return status
- MyCurMap EQU -10 ; save the current res file
-
- DoWarn _SUBR 10 ; Warn the user about troubles
-
- move.w D0,warning(A6) ; remember the warning
- move.w CurMap,MyCurMap(A6) ; and the current res file
- InitCursor ; make it an arrow again
-
- ; Open our resource file.
-
- subq.l #2,sp ; make space for result
- pea fileName ; point to file name
- OpenResFile
- move.w (SP)+,resfile(A6) ; save the resfile number
- cmp.w #-1,resfile(a6) ; check for failure
- bne.s @3 ; branch if ok
- move.w #60,-(A7) ; else beep (long)
- SysBeep
- move.w #ResFNotFound,D0 ; return bad status
- bra.s @20 ; and quit
-
- ; beep at 'em
- @3
- move.w #6,-(A7) ; 1/10 second beep
- _SysBeep
-
- ; choose a dialog to display
- move.w #PortNCalrt,D0
- cmp.w #PortNotCf,warning(a6) ; which warning?
- beq.s @5
- move.w #Noansalrt,D0 ; noAnswer dialog
-
- ; now display the dialog
- @5
- subq.l #4,sp ; space for result of _GetNewDialog
- move.w D0,-(sp) ; dialog resource ID
- clr.l -(sp) ; dialog record in heap
- move.l #-1,-(sp) ; in front of other windows
- _GetNewDialog
- move.l (SP)+,dlgwindow(A6) ; save the dialog's handle
-
- ; Now do the dialog stuff
-
- subq.l #2,sp ; result on stack
- clr.l -(sp) ; normal filterproc
- pea 4(sp) ; point to result space
- _ModalDialog ; Do it
-
- ; discard dialog
-
- move.l dlgWindow(a6),-(sp) ; point to dialog
- _DisposDialog
-
- ; What did they hit?
-
- move.w (sp)+,d0 ; get the button's item #
- cmp.w #1,D0 ; (Try Again or OK (=1)) or Use New?
- beq.s @10 ; go if not "Use New"
- clr.b SysLAPAddr(a2) ; otherwise, Use New
- clr.w SysNetNum(a2) ; and reset net and node adrs
-
- @10 neg.l D0 ; item will be 1 or 2; return -4001
- sub.l #4000,D0 ; or -4002 as the status
- move.w D0,warning(A6) ; save it
-
- ; discard resource file
-
- move.w resfile(A6),D0 ; get the refnum
- cmp.w MyCurMap(A6),D0 ; was it the current resource file
- beq.s @15 ; go if so (someone else opened it)
- move.w D0,-(sp) ; else, push it
- CloseResFile ; and close it
- @15 move.w warning(A6),D0 ; get the status from the NNNN
-
- @20 ; D0 is result code for this routine
- _SUBEND 'DOWARN ' ; and exit
-
- FileName DC.B 15
- DC.B 'Async AppleTalk'
- DC.B 'V1.2a6'
- ALIGN 2
-
- ; ****** end of lap.a
-
-
-
-
-
-
-
-
-
-
- Listing 2
-
- CRC Calculations
-
- This file contains a CRC calculation in Pascal. It was used with
- preliminary versions of Async AppleTalk, and computes the same
- function as the code in the M68000 listing.
-
- The NextCRC algorithm simulates the feedback shift register which
- normally implements a CRC calculation. NextCRC takes each four-
- bit nibble of the input char and uses a table (crctbl) to select
- a mask which is exclusive-or'd with the current CRC accumulator.
- }
-
- { pseudo-CONST -- put this in the initialization code of your program
-
- crctbl[00] := $0000; crctbl[01] := $CC01;
- crctbl[02] := $D801; crctbl[03] := $1400;
- crctbl[04] := $F001; crctbl[05] := $3C00;
- crctbl[06] := $2800; crctbl[07] := $E401;
- crctbl[08] := $A001; crctbl[09] := $6C00;
- crctbl[10] := $7800; crctbl[11] := $B401;
- crctbl[12] := $5000; crctbl[13] := $9C01;
- crctbl[14] := $8801; crctbl[15] := $4400;
- }
-
- VAR crctbl : array [0..15] of integer;
-
- function NextCRC (crc : integer; c : QDbyte) : integer;
-
- VAR
- j : integer;
-
- BEGIN
- j := crctbl[ band(bxor(crc,c),$000F) ];
- crc := bxor(bsr(crc,4),j);
- c := bsr(c,4);
- j := crctbl[ band(bxor(crc,c),$000F) ];
- crc := bxor(bsr(crc,4),j);
- nextcrc := crc;
- END; { NextCRC }
-
- function crc16 (p : qdptr; len : integer) : integer;
- VAR
- i,j : integer; { sixteen bits wide }
- c : qdbyte; { an eight bit value }
- crc : integer; { the CRC accumulator }
-
- BEGIN
- crc := 0;
- for i := 1 to len do begin
- c := p^;
- p := pointer(ord(p) + 1);
- crc := NextCRC(crc,c);
- end;
- crc16 := crc;
- END; { crc16 }
-
-
-
-
-
- Listing 3
-
- ;
- ; _AssumeEq Arg1, Arg2 -- macro to generate a compile-time error if two
- ; arguments are unequal.
- ;
- ; To optimize code size, we will be making various assumptions,
- ; mainly as to offset values. This macro is a way of formalizing
- ; those assumptions within the code.
- ;
-
- BLANKS ON
- STRING ASIS
-
- MACRO
- _AssumeEq
- IF &Eval(&Syslst[1]) <> &Eval(&Syslst[2]) THEN
- _ERR ; Invalid statement - will cause error
- ENDIF
- ENDM
- ;
- ; _StatCount Arg1 -- increment a statistics count if stat keeping is enabled
- ;
- ; Assumes A2 points to the driver variables
- ;
-
- MACRO
- _StatCount
- IF debug THEN
- ADDQ.L #1,&Syslst[1](A2); Update the count
- ELSE
- .* nop ; commented out
- ENDIF
- ENDM
-
- ;
- ; _Subr -- assembles a "Link A6,#???"
- ; works for _SUBR <no param> and _SUBR ###
- ;
- MACRO
- _Subr &size
- IF &size = '' THEN
- Link A6,#0
- ELSE
- Link A6,#(-&size)
- ENDIF
- ENDM
-
- ;
- ; _Subend NAME,$xx -- Subroutine epilog
- ; If debugging, put in Unlk and the name
- ;
- MACRO
- _Subend &name
- Unlk A6 ; unlink the stack frame
- rts ; and return
- DC.B &name ; the name
- ALIGN 2
- ENDM
-
-