1*34287Skarels /* mp.c 1.5 88/05/14 */ 232633Ssam 332633Ssam #include "mp.h" 432633Ssam #if NMP > 0 532633Ssam /* 632633Ssam * Multi Protocol Communications Controller (MPCC). 732633Ssam * Asynchronous Terminal Protocol Support. 832633Ssam */ 932633Ssam #include "../machine/pte.h" 1032633Ssam #include "../machine/mtpr.h" 1132633Ssam 1232633Ssam #include "param.h" 1332633Ssam #include "ioctl.h" 1432633Ssam #include "tty.h" 1532633Ssam #include "dir.h" 1632633Ssam #include "user.h" 1732633Ssam #include "map.h" 1832633Ssam #include "buf.h" 1932633Ssam #include "conf.h" 2032633Ssam #include "file.h" 2132633Ssam #include "uio.h" 2232633Ssam #include "errno.h" 2332633Ssam #include "syslog.h" 2432633Ssam #include "vmmac.h" 2532633Ssam #include "kernel.h" 2632633Ssam #include "clist.h" 2732633Ssam 2832633Ssam #include "../tahoevba/vbavar.h" 2932633Ssam #include "../tahoevba/mpreg.h" 3032633Ssam 3132633Ssam #define MPCHUNK 16 3232633Ssam #define MPPORT(n) ((n) & 0xf) 3332633Ssam #define MPUNIT(n) ((n) >> 4) 3432633Ssam 3532633Ssam /* 3632633Ssam * Driver information for auto-configuration stuff. 3732633Ssam */ 3832633Ssam int mpprobe(), mpattach(), mpintr(); 3932633Ssam struct vba_device *mpinfo[NMP]; 4032633Ssam long mpstd[] = { 0 }; 4132633Ssam struct vba_driver mpdriver = 4232633Ssam { mpprobe, 0, mpattach, 0, mpstd, "mp", mpinfo }; 4332633Ssam 4432633Ssam int mpstart(); 4532633Ssam struct mpevent *mpparam(); 4632633Ssam struct mpevent *mp_getevent(); 4732633Ssam 4832633Ssam /* 4932633Ssam * The following structure is needed to deal with mpcc's convoluted 5032633Ssam * method for locating it's mblok structures (hold your stomach). 5132633Ssam * When an mpcc is reset at boot time it searches host memory 5232633Ssam * looking for a string that says ``ThIs Is MpCc''. The mpcc 5332633Ssam * then reads the structure to locate the pointer to it's mblok 5432633Ssam * structure (you can wretch now). 5532633Ssam */ 5632633Ssam struct mpbogus { 5732633Ssam char s[12]; /* `ThIs Is MpCc'' */ 5832633Ssam u_char status; 5932633Ssam u_char unused; 6032633Ssam u_short magic; 6132633Ssam struct mblok *mb; 6232633Ssam struct mblok *mbloks[NMP]; /* can support at most 16 mpcc's */ 6332633Ssam } mpbogus = { 'T','h','I','s',' ','I','s',' ','M','p','C','c' }; 6432633Ssam 6532633Ssam /* 6632633Ssam * Software state per unit. 6732633Ssam */ 6832633Ssam struct mpsoftc { 6932633Ssam u_int ms_ivec; /* interrupt vector */ 7032633Ssam u_int ms_softCAR; /* software carrier for async */ 7132633Ssam struct mblok *ms_mb; /* mpcc status area */ 7232633Ssam struct vb_buf ms_buf; /* vba resources for ms_mb */ 7332633Ssam struct hxmtl ms_hxl[MPMAXPORT];/* host transmit list */ 7432633Ssam struct asyncparam ms_async[MPMAXPORT][MPINSET];/* async structs */ 7532633Ssam char ms_cbuf[MPMAXPORT][MPOUTSET][CBSIZE];/* input character buffers */ 7632633Ssam } mp_softc[NMP]; 7732633Ssam 7832633Ssam struct tty mp_tty[NMP*MPCHUNK]; 7932633Ssam #ifndef lint 8032633Ssam int nmp = NMP*MPCHUNK; 8132633Ssam #endif 8232633Ssam 8332633Ssam int ttrstrt(); 8432633Ssam 8532633Ssam mpprobe(reg, vi) 8632633Ssam caddr_t reg; 8732633Ssam struct vba_device *vi; 8832633Ssam { 8932633Ssam register int br, cvec; 9032633Ssam register struct mpsoftc *ms; 9132633Ssam 9232633Ssam #ifdef lint 9332633Ssam br = 0; cvec = br; br = cvec; 9432633Ssam mpintr(0); 9532633Ssam #endif 9632633Ssam if (badaddr(reg, 2)) 9732633Ssam return (0); 9832633Ssam ms = &mp_softc[vi->ui_unit]; 9932633Ssam /* 10032633Ssam * Allocate page tables and mblok 10132633Ssam * structure (mblok in non-cached memory). 10232633Ssam */ 10332633Ssam if (vbainit(&ms->ms_buf, sizeof (struct mblok), VB_32BIT) == 0) { 10432633Ssam printf("mp%d: vbainit failed\n", vi->ui_unit); 10532633Ssam return (0); 10632633Ssam } 10732633Ssam ms->ms_mb = (struct mblok *)ms->ms_buf.vb_rawbuf; 10832633Ssam ms->ms_ivec = MPINTRBASE + 2*vi->ui_unit; /* XXX */ 10932633Ssam br = 0x14, cvec = ms->ms_ivec; /* XXX */ 110*34287Skarels return (sizeof (*reg)); 11132633Ssam } 11232633Ssam 11332633Ssam mpattach(vi) 11432633Ssam register struct vba_device *vi; 11532633Ssam { 11632633Ssam register struct mpsoftc *ms = &mp_softc[vi->ui_unit]; 11732633Ssam 11832633Ssam ms->ms_softCAR = vi->ui_flags; 11932633Ssam /* 12032633Ssam * Setup pointer to mblok, initialize bogus 12132633Ssam * status block used by mpcc to locate the pointer 12232633Ssam * and then poke the mpcc to get it to search host 12332633Ssam * memory to find mblok pointer. 12432633Ssam */ 12532633Ssam mpbogus.mbloks[vi->ui_unit] = (struct mblok *)ms->ms_buf.vb_physbuf; 12632633Ssam *(short *)vi->ui_addr = 0x100; /* magic */ 12732633Ssam } 12832633Ssam 12932633Ssam /* 13032633Ssam * Open an mpcc port. 13132633Ssam */ 13232633Ssam mpopen(dev, mode) 13332633Ssam dev_t dev; 13432633Ssam { 13532633Ssam register struct tty *tp; 13632633Ssam register struct mpsoftc *ms; 13732633Ssam int error, s, port, unit, mpu; 13832633Ssam struct vba_device *vi; 13932633Ssam struct mpport *mp; 14032633Ssam struct mpevent *ev; 14132633Ssam 14232633Ssam unit = minor(dev); 14332633Ssam mpu = MPUNIT(unit); 14432633Ssam if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0) 14532633Ssam return (ENXIO); 14632633Ssam tp = &mp_tty[unit]; 14732633Ssam if (tp->t_state & TS_XCLUDE && u.u_uid != 0) 14832633Ssam return (EBUSY); 14932633Ssam ms = &mp_softc[mpu]; 15032633Ssam port = MPPORT(unit); 15132633Ssam if (ms->ms_mb->mb_proto[port] != MPPROTO_ASYNC || 15232633Ssam ms->ms_mb->mb_status != MP_OPOPEN) 15332633Ssam return (ENXIO); 15432633Ssam mp = &ms->ms_mb->mb_port[port]; /* host mpcc struct */ 15532633Ssam s = spl8(); 15632633Ssam while (mp->mp_flags & MP_PROGRESS) 15732633Ssam sleep((caddr_t)&tp->t_canq, TTIPRI); 15832633Ssam while (tp->t_state & TS_WOPEN) 15932633Ssam sleep((caddr_t)&tp->t_canq, TTIPRI); 16032633Ssam if (tp->t_state & TS_ISOPEN) { 16132633Ssam splx(s); 16232633Ssam return (0); 16332633Ssam } 16432633Ssam tp->t_state |= TS_WOPEN; 16532633Ssam tp->t_addr = (caddr_t)ms; 16632633Ssam tp->t_oproc = mpstart; 16732633Ssam tp->t_dev = dev; 16832633Ssam ttychars(tp); 16932633Ssam if (tp->t_ispeed == 0) { 17032633Ssam tp->t_ispeed = B9600; 17132633Ssam tp->t_ospeed = B9600; 17232633Ssam tp->t_flags |= ODDP|EVENP|ECHO; 17332633Ssam } 17432633Ssam /* 17532633Ssam * Initialize port state: init MPCC interface 17632633Ssam * structures for port and setup modem control. 17732633Ssam */ 17832633Ssam mp->mp_proto = MPPROTO_ASYNC; /* XXX */ 17932633Ssam error = mpportinit(ms, mp, port); 18032633Ssam if (error) 18132633Ssam goto bad; 18232633Ssam ev = mpparam(unit); 18332633Ssam if (ev == 0) { 18432633Ssam error = ENOBUFS; 18532633Ssam goto bad; 18632633Ssam } 18732633Ssam mpcmd(ev, EVCMD_OPEN, 0, ms->ms_mb, port); 18832633Ssam while ((tp->t_state & TS_CARR_ON) == 0) 18932633Ssam sleep((caddr_t)&tp->t_rawq, TTIPRI); 19032633Ssam error = mpmodem(unit, MMOD_ON); 19132633Ssam if (error) 19232633Ssam goto bad; 19332633Ssam while ((tp->t_state & TS_CARR_ON) == 0) 19432633Ssam sleep((caddr_t)&tp->t_rawq, TTIPRI); 19532633Ssam error = (*linesw[tp->t_line].l_open)(dev,tp); 19632633Ssam done: 19732633Ssam splx(s); 19832633Ssam /* wakeup anyone waiting for open to complete */ 19932633Ssam wakeup((caddr_t)&tp->t_canq); 20032633Ssam 20132633Ssam return (error); 20232633Ssam bad: 20332633Ssam tp->t_state &= ~TS_WOPEN; 20432633Ssam goto done; 20532633Ssam } 20632633Ssam 20732633Ssam /* 20832633Ssam * Close an mpcc port. 20932633Ssam */ 21032633Ssam mpclose(dev) 21132633Ssam dev_t dev; 21232633Ssam { 21332633Ssam register struct tty *tp; 21432633Ssam register struct mpport *mp; 21532633Ssam register struct mpevent *ev; 21632633Ssam int s, port, unit, error; 21732633Ssam struct mblok *mb; 21832633Ssam 21932633Ssam unit = minor(dev); 22032633Ssam tp = &mp_tty[unit]; 22132633Ssam port = MPPORT(unit); 22232633Ssam mb = mp_softc[MPUNIT(unit)].ms_mb; 22332633Ssam mp = &mb->mb_port[port]; 22432633Ssam s = spl8(); 22532633Ssam if (mp->mp_flags & MP_PROGRESS) { /* close in progress */ 22632633Ssam if (mp->mp_flags & MP_REMBSY) { 22732633Ssam mp->mp_flags &= ~MP_REMBSY; 22832633Ssam splx(s); 22932633Ssam return (0); 23032633Ssam } 23132633Ssam while (mp->mp_flags & MP_PROGRESS) 23232633Ssam sleep((caddr_t)&tp->t_canq,TTIPRI); 23332633Ssam } 23432633Ssam error = 0; 23532633Ssam mp->mp_flags |= MP_PROGRESS; 23632633Ssam (*linesw[tp->t_line].l_close)(tp); 23732633Ssam if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0) 23832633Ssam if (error = mpmodem(unit, MMOD_OFF)) { 23932633Ssam mp->mp_flags &= ~MP_PROGRESS; 24032633Ssam goto out; 24132633Ssam } 24232633Ssam while (tp->t_state & TS_FLUSH) /* ??? */ 24332633Ssam sleep((caddr_t)&tp->t_state, TTOPRI); /* ??? */ 24432633Ssam ttyclose(tp); 24532633Ssam ev = mp_getevent(mp, unit); 24632633Ssam if (ev == 0) { 24732633Ssam error = ENOBUFS; 24832633Ssam goto out; 24932633Ssam } 25032633Ssam mpcmd(ev, EVCMD_CLOSE, 0, mb, port); 25132633Ssam out: 25232633Ssam if (mp->mp_flags & MP_REMBSY) 25332633Ssam mpclean(mb, port); 25432633Ssam splx(s); 25532633Ssam return (error); 25632633Ssam } 25732633Ssam 25832633Ssam /* 25932633Ssam * Read from an mpcc port. 26032633Ssam */ 26132633Ssam mpread(dev, uio) 26232633Ssam dev_t dev; 26332633Ssam struct uio *uio; 26432633Ssam { 26532633Ssam struct tty *tp; 26632633Ssam 26732633Ssam tp = &mp_tty[minor(dev)]; 26832633Ssam return ((*linesw[tp->t_line].l_read)(tp, uio)); 26932633Ssam } 27032633Ssam 27132633Ssam /* 27232633Ssam * Write to an mpcc port. 27332633Ssam */ 27432633Ssam mpwrite(dev, uio) 27532633Ssam dev_t dev; 27632633Ssam struct uio *uio; 27732633Ssam { 27832633Ssam struct tty *tp; 27932633Ssam 28032633Ssam tp = &mp_tty[minor(dev)]; 28132633Ssam return ((*linesw[tp->t_line].l_write)(tp, uio)); 28232633Ssam } 28332633Ssam 28432633Ssam /* 28532633Ssam * Ioctl for a mpcc port 28632633Ssam */ 28732633Ssam mpioctl(dev, cmd, data, flag) 28832633Ssam dev_t dev; 28932633Ssam caddr_t data; 29032633Ssam { 29132633Ssam register struct tty *tp; 29232633Ssam register struct mpsoftc *ms; 29332633Ssam register struct mpevent *ev; 29432633Ssam register struct mpport *mp; 29532633Ssam int s, port, error, unit; 29632633Ssam struct mblok *mb; 29732633Ssam 29832633Ssam unit = minor(dev); 29932633Ssam tp = &mp_tty[unit]; 30032633Ssam ms = &mp_softc[MPUNIT(unit)]; 30132633Ssam mb = ms->ms_mb; 30232633Ssam error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag); 30332633Ssam if (error >= 0) 30432633Ssam return (error); 30532633Ssam error = ttioctl(tp, cmd, data, flag); 30632633Ssam if (error >= 0) { 30732633Ssam if (cmd == TIOCSETP || cmd == TIOCSETN || cmd == TIOCLBIS || 30832633Ssam cmd == TIOCLBIC || cmd == TIOCLSET) { 30932633Ssam ev = mpparam(unit); 31032633Ssam if (ev == 0) 31132633Ssam error = ENOBUFS; 31232633Ssam else 31332633Ssam mpcmd(ev, EVCMD_IOCTL, A_CHGALL, mb, 31432633Ssam MPPORT(unit)); 31532633Ssam } 31632633Ssam return (error); 31732633Ssam } 31832633Ssam switch (cmd) { 31932633Ssam case TIOCSBRK: /* send break */ 32032633Ssam case TIOCCBRK: /* clear break */ 32132633Ssam port = MPPORT(unit); 32232633Ssam mp = &mb->mb_port[port]; 32332633Ssam s = spl8(); 32432633Ssam ev = mp_getevent(mp, unit); 32532633Ssam if (ev) 32632633Ssam mpcmd(ev, EVCMD_IOCTL, 32732633Ssam (cmd == TIOCSBRK ? A_BRKON : A_BRKOFF), 32832633Ssam mb, port); 32932633Ssam else 33032633Ssam error = ENOBUFS; 33132633Ssam splx(s); 33232633Ssam break; 33332633Ssam case TIOCSDTR: /* set dtr control line */ 33432633Ssam break; 33532633Ssam case TIOCCDTR: /* clear dtr control line */ 33632633Ssam break; 33732633Ssam default: 33832633Ssam error = ENOTTY; 33932633Ssam break; 34032633Ssam } 34132633Ssam return (error); 34232633Ssam } 34332633Ssam 34432633Ssam struct mpevent * 34532633Ssam mpparam(unit) 34632633Ssam int unit; 34732633Ssam { 34832633Ssam register struct mpevent *ev; 34932633Ssam register struct mpport *mp; 35032633Ssam register struct tty *tp; 35132633Ssam struct mblok *mb; 35232633Ssam struct mpsoftc *ms; 35332633Ssam register struct asyncparam *asp; 35432633Ssam int port; 35532633Ssam 35632633Ssam ms = &mp_softc[MPUNIT(unit)]; 35732633Ssam mb = ms->ms_mb; 35832633Ssam port = MPPORT(unit); 35932633Ssam mp = &mb->mb_port[port]; 36032633Ssam ev = mp_getevent(mp, unit); /* XXX */ 36132633Ssam if (ev == 0) 36232633Ssam return (ev); 36332633Ssam tp = &mp_tty[unit]; 36432633Ssam /* YUCK */ 36532633Ssam asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1]; 36632633Ssam asp->ap_xon = tp->t_startc; 36732633Ssam asp->ap_xoff = tp->t_stopc; 36833995Sbostic asp->ap_xena = ((tp->t_flags & RAW) ? MPA_DIS : MPA_ENA); 36933995Sbostic asp->ap_xany = ((tp->t_flags & DECCTQ) ? MPA_DIS : MPA_ENA); 37032633Ssam #ifdef notnow 37132633Ssam if (tp->t_flags & (RAW|LITOUT|PASS8)) { 37232633Ssam #endif 37332633Ssam asp->ap_data = MPCHAR_8; 37432633Ssam asp->ap_parity = MPPAR_NONE; 37532633Ssam #ifdef notnow 37632633Ssam } else { 37732633Ssam asp->ap_data = MPCHAR_7; 37832633Ssam if ((tp->t_flags & (EVENP|ODDP)) == ODDP) 37932633Ssam asp->ap_parity = MPPAR_ODD; 38032633Ssam else 38132633Ssam asp->ap_parity = MPPAR_EVEN; 38232633Ssam } 38332633Ssam #endif 38432633Ssam if (tp->t_ospeed == B110) 38532633Ssam asp->ap_stop = MPSTOP_2; 38632633Ssam else 38732633Ssam asp->ap_stop = MPSTOP_1; 38832633Ssam if (tp->t_ospeed == EXTA || tp->t_ospeed == EXTB) 38932633Ssam asp->ap_baud = M19200; 39032633Ssam else 39132633Ssam asp->ap_baud = tp->t_ospeed; 39232633Ssam asp->ap_loop = MPA_DIS; /* disable loopback */ 39332633Ssam asp->ap_rtimer = A_RCVTIM; /* default receive timer */ 39432633Ssam if (ms->ms_softCAR & (1<<port)) 39532633Ssam setm(&asp->ap_modem, A_DTR, ASSERT); 39632633Ssam else 39732633Ssam setm(&asp->ap_modem, A_DTR, AUTO); 39832633Ssam seti(&asp->ap_intena, A_DCD); 39932633Ssam return (ev); 40032633Ssam } 40132633Ssam 40232633Ssam mpstart(tp) 40332633Ssam register struct tty *tp; 40432633Ssam { 40532633Ssam register struct mpevent *ev; 40632633Ssam register struct mpport *mp; 40732633Ssam struct mblok *mb; 40832633Ssam struct mpsoftc *ms; 40932633Ssam int port, unit, xcnt, n, s, i; 41032633Ssam struct hxmtl *hxp; 41132633Ssam struct clist outq; 41232633Ssam 41332633Ssam s = spl8(); 41432633Ssam unit = minor(tp->t_dev); 41532633Ssam ms = &mp_softc[MPUNIT(unit)]; 41632633Ssam mb = ms->ms_mb; 41732633Ssam port = MPPORT(unit); 41832633Ssam mp = &mb->mb_port[port]; 41932633Ssam hxp = &ms->ms_hxl[port]; 42032633Ssam xcnt = 0; 42132633Ssam outq = tp->t_outq; 42232633Ssam for (i = 0; i < MPXMIT; i++) { 42332633Ssam if (tp->t_state & (TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) 42432633Ssam break; 42532633Ssam if (outq.c_cc <= TTLOWAT(tp)) { 42632633Ssam if (tp->t_state & TS_ASLEEP) { 42732633Ssam tp->t_state &= ~TS_ASLEEP; 42832633Ssam wakeup((caddr_t)&tp->t_outq); 42932633Ssam } 43032633Ssam if (tp->t_wsel) { 43132633Ssam selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL); 43232633Ssam tp->t_wsel = 0; 43332633Ssam tp->t_state &= ~TS_WCOLL; 43432633Ssam } 43532633Ssam } 43632633Ssam if (outq.c_cc == 0) 43732633Ssam break; 43832633Ssam /* 43932633Ssam * If we're not currently busy outputting, 44032633Ssam * and there is data to be output, set up 44132633Ssam * port transmit structure to send to mpcc. 44232633Ssam */ 44332633Ssam if (tp->t_flags & (RAW|LITOUT)) 44432633Ssam n = ndqb(&outq, 0); 44532633Ssam else { 44632633Ssam n = ndqb(&outq, 0200); 44732633Ssam if (n == 0) { 44832633Ssam n = getc(&outq); 44932633Ssam timeout(ttrstrt, (caddr_t)tp, (n&0177)+6); 45032633Ssam tp->t_state |= TS_TIMEOUT; 45132633Ssam break; 45232633Ssam } 45332633Ssam } 45432633Ssam hxp->dblock[i] = (caddr_t)vtoph(0, (int)outq.c_cf); 45532633Ssam hxp->size[i] = n; 45632633Ssam xcnt++; /* count of xmts to send */ 45732633Ssam ndadvance(&outq, n); 45832633Ssam } 45932633Ssam /* 46032633Ssam * If data to send, poke mpcc. 46132633Ssam */ 46232633Ssam if (xcnt) { 46332633Ssam ev = mp_getevent(mp, unit); 46432633Ssam if (ev == 0) { 46532633Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT); 46632633Ssam } else { 46732633Ssam tp->t_state |= TS_BUSY; 46832633Ssam ev->ev_count = xcnt; 46932633Ssam mpcmd(ev, EVCMD_WRITE, 0, mb, MPPORT(unit)); 47032633Ssam } 47132633Ssam } 47232633Ssam splx(s); 47332633Ssam } 47432633Ssam 47532633Ssam /* 47632633Ssam * Advance cc bytes from q but don't free memory. 47732633Ssam */ 47832633Ssam ndadvance(q, cc) 47932633Ssam register struct clist *q; 48032633Ssam register cc; 48132633Ssam { 48232633Ssam register struct cblock *bp; 48332633Ssam char *end; 48432633Ssam int rem, s; 48532633Ssam 48632633Ssam s = spltty(); 48732633Ssam if (q->c_cc <= 0) 48832633Ssam goto out; 48932633Ssam while (cc>0 && q->c_cc) { 49032633Ssam bp = (struct cblock *)((int)q->c_cf & ~CROUND); 49132633Ssam if ((int)bp == (((int)q->c_cl-1) & ~CROUND)) { 49232633Ssam end = q->c_cl; 49332633Ssam } else { 49432633Ssam end = (char *)((int)bp + sizeof (struct cblock)); 49532633Ssam } 49632633Ssam rem = end - q->c_cf; 49732633Ssam if (cc >= rem) { 49832633Ssam cc -= rem; 49932633Ssam q->c_cc -= rem; 50032633Ssam q->c_cf = bp->c_next->c_info; 50132633Ssam } else { 50232633Ssam q->c_cc -= cc; 50332633Ssam q->c_cf += cc; 50432633Ssam break; 50532633Ssam } 50632633Ssam } 50732633Ssam if (q->c_cc <= 0) { 50832633Ssam q->c_cf = q->c_cl = NULL; 50932633Ssam q->c_cc = 0; 51032633Ssam } 51132633Ssam out: 51232633Ssam splx(s); 51332633Ssam } 51432633Ssam 51532633Ssam /* 51632633Ssam * Stop output on a line, e.g. for ^S/^Q or output flush. 51732633Ssam */ 51832633Ssam mpstop(tp, rw) 51932633Ssam register struct tty *tp; 52032633Ssam int rw; 52132633Ssam { 52232633Ssam int s, port; 52332633Ssam struct mpevent *ev; 52432633Ssam struct mblok *mb; 52532633Ssam 52632633Ssam s = spl8(); 52732633Ssam /* XXX: DISABLE TRANSMITTER */ 52832633Ssam if (tp->t_state & TS_BUSY) { 52932633Ssam if ((tp->t_state & TS_TTSTOP) == 0) 53032633Ssam tp->t_state |= TS_FLUSH; 53132633Ssam } 53232633Ssam splx(s); 53332633Ssam } 53432633Ssam 53532633Ssam /* 53632633Ssam * Initialize an async port's MPCC state. 53732633Ssam */ 53832633Ssam mpportinit(ms, mp, port) 53932633Ssam register struct mpsoftc *ms; 54032633Ssam register struct mpport *mp; 54132633Ssam int port; 54232633Ssam { 54332633Ssam register struct mpevent *ev; 54432633Ssam register int i; 54532633Ssam caddr_t ptr; 54632633Ssam 54732633Ssam mp->mp_on = mp->mp_off = 0; 54832633Ssam mp->mp_nextrcv = 0; 54932633Ssam mp->mp_flags = 0; 55032633Ssam ev = &mp->mp_recvq[0]; 55132633Ssam for (i = 0; ev < &mp->mp_recvq[MPINSET]; ev++, i++) { 55232633Ssam ev->ev_status = EVSTATUS_FREE; 55332633Ssam ev->ev_cmd = 0; 55432633Ssam ev->ev_opts = 0; 55532633Ssam ev->ev_error = 0; 55632633Ssam ev->ev_flags = 0; 55732633Ssam ev->ev_count = 0; 55832633Ssam ev->ev_un.hxl = (struct hxmtl *) vtoph(0, &ms->ms_hxl[port]); 55932633Ssam ev->ev_params = (caddr_t) vtoph(0, &ms->ms_async[port][i]); 56032633Ssam } 56132633Ssam ev = &mp->mp_sendq[0]; 56232633Ssam for (i = 0; ev < &mp->mp_sendq[MPOUTSET]; ev++, i++) { 56332633Ssam /* init so that L2 can't send any events */ 56432633Ssam /* to host until open has completed */ 56532633Ssam ev->ev_status = EVSTATUS_FREE; 56632633Ssam ev->ev_cmd = 0; 56732633Ssam ev->ev_error = 0; 56832633Ssam ev->ev_flags = 0; 56932633Ssam ev->ev_count = 0; 57032633Ssam ptr = (caddr_t) &ms->ms_cbuf[port][i][0]; 57132633Ssam ev->ev_un.rcvblk = (u_char *)vtoph(0, ptr); 57232633Ssam ev->ev_params = (caddr_t) vtoph(0, ptr); 57332633Ssam } 57432633Ssam return (0); 57532633Ssam } 57632633Ssam 57732633Ssam /* 57832633Ssam * Send an event to an mpcc. 57932633Ssam */ 58032633Ssam mpcmd(ev, cmd, flags, mb, port) 58132633Ssam register struct mpevent *ev; 58232633Ssam struct mblok *mb; 58332633Ssam { 58432633Ssam int s; 58532633Ssam 58632633Ssam s = spl8(); 58732633Ssam /* move host values to inbound entry */ 58832633Ssam ev->ev_cmd = cmd; 58932633Ssam ev->ev_opts = flags; 59032633Ssam /* show event ready for mpcc */ 59132633Ssam ev->ev_status = EVSTATUS_GO; 59232633Ssam mpintmpcc(mb, port); 59332633Ssam splx(s); 59432633Ssam } 59532633Ssam 59632633Ssam /* 59732633Ssam * Return the next available event entry for the indicated port. 59832633Ssam */ 59932633Ssam struct mpevent * 60032633Ssam mp_getevent(mp, unit) 60132633Ssam register struct mpport *mp; 60232633Ssam int unit; 60332633Ssam { 60432633Ssam register struct mpevent *ev; 60532633Ssam int i, s; 60632633Ssam 60732633Ssam s = spl8(); 60832633Ssam ev = &mp->mp_recvq[mp->mp_on]; 60932633Ssam if (ev->ev_status != EVSTATUS_FREE) 61032633Ssam goto bad; 61132633Ssam /* 61232633Ssam * If not a close request, verify one extra 61332633Ssam * event is available for closing the port. 61432633Ssam */ 61532633Ssam if ((mp->mp_flags && MP_PROGRESS) == 0) { 61632633Ssam if ((i = mp->mp_on + 1) >= MPINSET) 61732633Ssam i = 0; 61832633Ssam if (mp->mp_recvq[i].ev_status != EVSTATUS_FREE) 61932633Ssam goto bad; 62032633Ssam } 62132633Ssam /* init inbound fields marking this entry as busy */ 62232633Ssam ev->ev_error = 0; 62332633Ssam ev->ev_flags = 0; 62432633Ssam ev->ev_count = 0; 62532633Ssam ev->ev_status = EVSTATUS_BUSY; 62632633Ssam /* adjust pointer to next available inbound entry */ 62732633Ssam adjptr(mp->mp_on, MPINSET); 62832633Ssam splx(s); 62932633Ssam return (ev); 63032633Ssam bad: 63132633Ssam splx(s); 63232633Ssam log(LOG_ERR, "mp%d: port%d, out of events", MPUNIT(unit), MPPORT(unit)); 63332633Ssam return ((struct mpevent *)0); 63432633Ssam } 63532633Ssam 63632633Ssam mpmodem(unit, flag) 63732633Ssam int unit, flag; 63832633Ssam { 63932633Ssam struct mpsoftc *ms = &mp_softc[MPUNIT(unit)]; 64032633Ssam int port = MPPORT(unit); 64132633Ssam register struct mpport *mp; 64232633Ssam register struct mpevent *ev; 64332633Ssam register struct asyncparam *asp; 64432633Ssam 64532633Ssam mp = &ms->ms_mb->mb_port[port]; 64632633Ssam ev = mp_getevent(mp, unit); 64732633Ssam if (ev == 0) 64832633Ssam return (ENOBUFS); 64932633Ssam /* YUCK */ 65032633Ssam asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1]; 65132633Ssam if (flag == MMOD_ON) { 65232633Ssam if (ms->ms_softCAR & (1 << port)) 65332633Ssam setm(&asp->ap_modem, A_DTR, ASSERT); 65432633Ssam else 65532633Ssam setm(&asp->ap_modem, A_DTR, AUTO); 65632633Ssam seti(&asp->ap_intena, A_DCD); 65732633Ssam } else { 65832633Ssam setm(&asp->ap_modem, 0, DROP); 65932633Ssam seti(&asp->ap_intena, 0); 66032633Ssam } 66132633Ssam mpcmd(ev, EVCMD_IOCTL, A_MDMCHG, ms->ms_mb, port); 66232633Ssam return (0); 66332633Ssam } 66432633Ssam 66532633Ssam /* 66632633Ssam * Set up the modem control structure according to mask. 66732633Ssam * Each set bit in the mask means assert the corresponding 66832633Ssam * modem control line, otherwise, it will be dropped. 66932633Ssam * RTS is special since it can either be asserted, dropped 67032633Ssam * or put in auto mode for auto modem control. 67132633Ssam */ 67232633Ssam static 67332633Ssam setm(mc, mask, rts) 67432633Ssam register struct mdmctl *mc; 67532633Ssam register int mask; 67632633Ssam { 67732633Ssam 67832633Ssam mc->mc_rngdsr = (mask & A_RNGDSR) ? ASSERT : DROP; 67932633Ssam mc->mc_rate = (mask & A_RATE) ? ASSERT : DROP; 68032633Ssam mc->mc_dcd = (mask & A_DCD) ? ASSERT : DROP; 68132633Ssam mc->mc_sectx = (mask & A_SECTX) ? ASSERT : DROP; 68232633Ssam mc->mc_cts = (mask & A_CTS) ? ASSERT : DROP; 68332633Ssam mc->mc_secrx = (mask & A_SECRX) ? ASSERT : DROP; 68432633Ssam mc->mc_dtr = (mask & A_DTR) ? ASSERT : DROP; 68532633Ssam mc->mc_rts = rts; 68632633Ssam } 68732633Ssam 68832633Ssam /* 68932633Ssam * Set up the status change enable field from mask. 69032633Ssam * When a signal is enabled in this structure and 69132633Ssam * and a change in state on a corresponding modem 69232633Ssam * control line occurs, a status change event will 69332633Ssam * be delivered to the host. 69432633Ssam */ 69532633Ssam static 69632633Ssam seti(mc, mask) 69732633Ssam register struct mdmctl *mc; 69832633Ssam register int mask; 69932633Ssam { 70032633Ssam 70132633Ssam mc->mc_rngdsr = (mask & A_RNGDSR) ? MDM_ON : MDM_OFF; 70232633Ssam mc->mc_rate = (mask & A_RATE) ? MDM_ON : MDM_OFF; 70332633Ssam mc->mc_dcd = (mask & A_DCD) ? MDM_ON : MDM_OFF; 70432633Ssam mc->mc_sectx = (mask & A_SECTX) ? MDM_ON : MDM_OFF; 70532633Ssam mc->mc_cts = (mask & A_CTS) ? MDM_ON : MDM_OFF; 70632633Ssam mc->mc_secrx = (mask & A_SECRX) ? MDM_ON : MDM_OFF; 70732633Ssam mc->mc_dtr = (mask & A_DTR) ? MDM_ON : MDM_OFF; 70832633Ssam mc->mc_rts = (mask & A_RTS) ? MDM_ON : MDM_OFF; 70932633Ssam } 71032633Ssam 71132633Ssam mpcleanport(mb, port) 71232633Ssam struct mblok *mb; 71332633Ssam int port; 71432633Ssam { 71532633Ssam register struct mpport *mp; 71632633Ssam register struct tty *tp; 71732633Ssam 71832633Ssam mp = &mb->mb_port[port]; 71932633Ssam if (mp->mp_proto == MPPROTO_ASYNC) { 72032633Ssam mp->mp_flags = MP_REMBSY; 72132633Ssam /* flush I/O queues and send hangup signals */ 72232633Ssam tp = &mp_tty[mb->mb_unit*MPCHUNK+port]; 72332633Ssam tp->t_state &= ~TS_CARR_ON; 72432633Ssam ttyflush(tp, FREAD|FWRITE); 72532633Ssam gsignal(tp->t_pgrp, SIGHUP); 72632633Ssam gsignal(tp->t_pgrp, SIGKILL); 72732633Ssam mpclose(tp->t_dev, 0); 72832633Ssam } 72932633Ssam } 73032633Ssam 73132633Ssam mpclean(mb, port) 73232633Ssam register struct mblok *mb; 73332633Ssam int port; 73432633Ssam { 73532633Ssam register struct mpport *mp; 73632633Ssam register struct mpevent *ev; 73732633Ssam register int i; 73832633Ssam char list[2], *cp; 73932633Ssam int unit; 74032633Ssam 74132633Ssam mp = &mb->mb_port[port]; 74232633Ssam unit = mb->mb_unit; 74332633Ssam for (i = mp->mp_off; i != mp->mp_on; i = (i+1 % MPINSET)) { 74432633Ssam ev = &mp->mp_recvq[i]; 74532633Ssam ev->ev_error = ENXIO; 74632633Ssam ev->ev_status = EVSTATUS_DONE; 74732633Ssam } 74832633Ssam list[0] = port, list[1] = MPPORT_EOL; 74932633Ssam mpxintr(unit, list); 75032633Ssam mprintr(unit, list); 75132633Ssam /* Clear async for port */ 75232633Ssam mp->mp_proto = MPPROTO_UNUSED; 75332633Ssam mp->mp_flags = 0; 75432633Ssam mp->mp_on = 0; 75532633Ssam mp->mp_off = 0; 75632633Ssam mp->mp_nextrcv = 0; 75732633Ssam 75832633Ssam mp_tty[unit*MPCHUNK + port].t_state = 0; 75932633Ssam for (ev = &mp->mp_sendq[0]; ev < &mp->mp_sendq[MPOUTSET]; ev++) { 76032633Ssam ev->ev_status = EVSTATUS_FREE; 76132633Ssam ev->ev_cmd = 0; 76232633Ssam ev->ev_error = 0; 76332633Ssam ev->ev_un.rcvblk = 0; 76432633Ssam ev->ev_params = 0; 76532633Ssam } 76632633Ssam for (ev = &mp->mp_recvq[0]; ev < &mp->mp_recvq[MPINSET]; ev++) { 76732633Ssam ev->ev_status = EVSTATUS_FREE; 76832633Ssam ev->ev_cmd = 0; 76932633Ssam ev->ev_error = 0; 77032633Ssam ev->ev_params = 0; 77132633Ssam } 77232633Ssam } 77332633Ssam 77432633Ssam /* 77532633Ssam * MPCC interrupt handler. 77632633Ssam */ 77732633Ssam mpintr(mpcc) 77832633Ssam int mpcc; 77932633Ssam { 78032633Ssam register struct mblok *mb; 78132633Ssam register struct his *his; 78232633Ssam register int i; 78332633Ssam 78432633Ssam mb = mp_softc[mpcc].ms_mb; 78532633Ssam if (mb == 0) { 78632633Ssam printf("mp%d: stray interrupt\n", mpcc); 78732633Ssam return; 78832633Ssam } 78932633Ssam his = &mb->mb_hostint; 79032633Ssam his->semaphore &= ~MPSEMA_AVAILABLE; 79132633Ssam /* 79232633Ssam * Check for events to be processed. 79332633Ssam */ 79432633Ssam if (his->proto[MPPROTO_ASYNC].outbdone[0] != MPPORT_EOL) 79532633Ssam mprintr(mpcc, his->proto[MPPROTO_ASYNC].outbdone); 79632633Ssam if (his->proto[MPPROTO_ASYNC].inbdone[0] != MPPORT_EOL) 79732633Ssam mpxintr(mpcc, his->proto[MPPROTO_ASYNC].inbdone); 79832633Ssam if (mb->mb_harderr || mb->mb_softerr) 79932633Ssam mperror(mb, mpcc); 80032633Ssam his->semaphore |= MPSEMA_AVAILABLE; 80132633Ssam } 80232633Ssam 80332633Ssam /* 80432633Ssam * Handler for processing completion of transmitted events. 80532633Ssam */ 80632633Ssam mpxintr(unit, list) 80732633Ssam register char *list; 80832633Ssam { 80932633Ssam register struct mpport *mp; 81032633Ssam register struct mpevent *ev; 81132633Ssam register struct mblok *mb; 81232633Ssam register struct tty *tp; 81332633Ssam register struct asyncparam *ap; 81432633Ssam struct mpsoftc *ms; 81532633Ssam int port, i, j; 81632633Ssam 81732633Ssam ms = &mp_softc[unit]; 81832633Ssam mb = mp_softc[unit].ms_mb; 81932633Ssam for (j = 0; j < MPMAXPORT && ((port = *list++) != MPPORT_EOL); j++) { 82032633Ssam /* 82132633Ssam * Process each completed entry in the inbound queue. 82232633Ssam */ 82332633Ssam mp = &mb->mb_port[port]; 82432633Ssam tp = &mp_tty[unit*MPCHUNK + port]; 82532633Ssam #define nextevent(mp) &mp->mp_recvq[mp->mp_off] 82632633Ssam ev = nextevent(mp); 82732633Ssam for(; ev->ev_status & EVSTATUS_DONE; ev = nextevent(mp)) { 82832633Ssam /* YUCK */ 82932633Ssam ap = &ms->ms_async[port][mp->mp_off]; 83032633Ssam mppurge(ap, sizeof (*ap)); 83132633Ssam switch (ev->ev_cmd) { 83232633Ssam case EVCMD_OPEN: 83332633Ssam /* 83432633Ssam * Open completion, start all reads and 83532633Ssam * assert modem status information. 83632633Ssam */ 83732633Ssam for (i = 0; i < MPOUTSET; i++) 83832633Ssam mp->mp_sendq[i].ev_status = EVSTATUS_GO; 83932633Ssam (*linesw[tp->t_line].l_modem) 84032633Ssam (tp, ap->ap_modem.mc_dcd == ASSERT); 84132633Ssam break; 84232633Ssam case EVCMD_CLOSE: 84332633Ssam /* 84432633Ssam * Close completion, flush all pending 84532633Ssam * transmissions, free resources, and 84632633Ssam * cleanup mpcc port state. 84732633Ssam */ 84832633Ssam for (i = 0; i < MPOUTSET; i++) { 84932633Ssam mp->mp_sendq[i].ev_status = 85032633Ssam EVSTATUS_FREE; 85132633Ssam mp->mp_sendq[i].ev_un.rcvblk = 0; 85232633Ssam mp->mp_sendq[i].ev_params = 0; 85332633Ssam } 85432633Ssam tp->t_state &= ~TS_CARR_ON; 85532633Ssam mp->mp_on = mp->mp_off = mp->mp_nextrcv = 0; 85632633Ssam mp->mp_flags &= ~MP_PROGRESS; 85732633Ssam mp->mp_proto = MPPROTO_UNUSED; 85832633Ssam wakeup((caddr_t)&tp->t_canq); /* ??? */ 85932633Ssam goto done; 86032633Ssam case EVCMD_IOCTL: 86132633Ssam /* 86232633Ssam * Nothing to do, just pitch. 86332633Ssam */ 86432633Ssam break; 86532633Ssam case EVCMD_WRITE: 86632633Ssam /* 86732633Ssam * Transmission completed, update tty 86832633Ssam * state and restart output. 86932633Ssam */ 87032633Ssam tp->t_state &= ~TS_BUSY; 87132633Ssam if (tp->t_state & TS_FLUSH) { 87232633Ssam tp->t_state &= ~TS_FLUSH; 87332633Ssam wakeup((caddr_t)&tp->t_state); 87432633Ssam } else { 87532633Ssam register int cc = 0, i; 87632633Ssam struct hxmtl *hxp; 87732633Ssam 87832633Ssam hxp = &ms->ms_hxl[port]; 87932633Ssam for(i = 0; i < ev->ev_count; i++) 88032633Ssam cc += hxp->size[i]; 88132633Ssam ndflush(&tp->t_outq, cc); 88232633Ssam } 88332633Ssam switch (ev->ev_error) { 88432633Ssam case A_SIZERR: /*# error in xmt data size */ 88532633Ssam mplog(unit, port, A_XSIZE, 0); 88632633Ssam break; 88732633Ssam case A_NXBERR: /*# no more xmt evt buffers */ 88832633Ssam mplog(unit, port, A_NOXBUF, 0); 88932633Ssam break; 89032633Ssam } 89132633Ssam mpstart(tp); 89232633Ssam break; 89332633Ssam default: 89432633Ssam mplog(unit, port, A_INVCMD, ev->ev_cmd); 89532633Ssam break; 89632633Ssam } 89732633Ssam /* re-init all values in this entry */ 89832633Ssam ev->ev_cmd = 0; 89932633Ssam ev->ev_opts = 0; 90032633Ssam ev->ev_error = 0; 90132633Ssam ev->ev_flags = 0; 90232633Ssam ev->ev_count = 0; 90332633Ssam /* show this entry is available for use */ 90432633Ssam ev->ev_status = EVSTATUS_FREE; 90532633Ssam adjptr(mp->mp_off, MPINSET); 90632633Ssam #undef nextevent 90732633Ssam } 90832633Ssam done: 90932633Ssam ; 91032633Ssam } 91132633Ssam } 91232633Ssam 91332633Ssam /* 91432633Ssam * Handler for processing received events. 91532633Ssam */ 91632633Ssam mprintr(unit, list) 91732633Ssam char *list; 91832633Ssam { 91932633Ssam register struct tty *tp; 92032633Ssam register struct mpport *mp; 92132633Ssam register struct mpevent *ev; 92232633Ssam struct mblok *mb; 92332633Ssam register int cc; 92432633Ssam register char *cp; 92532633Ssam struct mpsoftc *ms; 92632633Ssam caddr_t ptr; 92732633Ssam char *rcverr; 92832633Ssam int port, i; 92932633Ssam 93032633Ssam ms = &mp_softc[unit]; 93132633Ssam mb = mp_softc[unit].ms_mb; 93232633Ssam for (i = 0; i < MPMAXPORT && (port = *list++) != MPPORT_EOL; i++) { 93332633Ssam tp = &mp_tty[unit*MPCHUNK + port]; 93432633Ssam mp = &mb->mb_port[port]; 93532633Ssam ev = &mp->mp_sendq[mp->mp_nextrcv]; 93632633Ssam while (ev->ev_status & EVSTATUS_DONE) { 93732633Ssam if (ev->ev_cmd != EVCMD_READ && 93832633Ssam ev->ev_cmd != EVCMD_STATUS) { 93932633Ssam mplog(unit, port, "unexpected command", 94032633Ssam ev->ev_cmd); 94132633Ssam goto next; 94232633Ssam } 94332633Ssam if (ev->ev_cmd == EVCMD_STATUS) { 94432633Ssam /* 94532633Ssam * Status change, look for carrier changes. 94632633Ssam */ 94732633Ssam if (ev->ev_opts == DCDASRT || 94832633Ssam ev->ev_opts == DCDDROP) 94932633Ssam (*linesw[tp->t_line].l_modem) 95032633Ssam (tp, ev->ev_opts == DCDASRT); 95132633Ssam else 95232633Ssam mplog(unit, port, 95332633Ssam "unexpect status command", 95432633Ssam ev->ev_opts); 95532633Ssam goto next; 95632633Ssam } 95732633Ssam /* 95832633Ssam * Process received data. 95932633Ssam */ 96032633Ssam if ((tp->t_state & (TS_ISOPEN|TS_WOPEN)) == 0) 96132633Ssam goto next; 96232633Ssam cc = ev->ev_count; 96332633Ssam if (cc == 0) 96432633Ssam goto next; 96532633Ssam /* YUCK */ 96632633Ssam cp = ms->ms_cbuf[port][mp->mp_nextrcv]; 96732633Ssam mppurge(cp, CBSIZE); 96832633Ssam while (cc-- > 0) { 96932633Ssam /* 97032633Ssam * A null character is inserted, potentially 97132633Ssam * when a break or framing error occurs. If 97232633Ssam * we're not in raw mode, substitute the 97332633Ssam * interrupt character. 97432633Ssam */ 97532633Ssam if (*cp == 0 && 97632633Ssam (ev->ev_error == BRKASRT || 97732633Ssam ev->ev_error == FRAMERR)) 97832633Ssam if ((tp->t_flags&RAW) == 0) 97932633Ssam *cp = tp->t_intrc; 98032633Ssam (*linesw[tp->t_line].l_rint)(*cp++, tp); 98132633Ssam } 98232633Ssam /* setup for next read */ 98332633Ssam ptr = (caddr_t)&mp_softc[unit].ms_cbuf[port][mp->mp_nextrcv][0]; 98432633Ssam ev->ev_un.rcvblk = (u_char *)vtoph(0, ptr); 98532633Ssam ev->ev_params = (caddr_t) vtoph(0, ptr); 98633673Sbostic switch(ev->ev_error) { 98733673Sbostic case RCVDTA: /* Normal (good) rcv data */ 98833673Sbostic /* do not report the following */ 98933673Sbostic /* they are "normal" errors */ 99033673Sbostic case FRAMERR: /* frame error */ 99133673Sbostic case BRKASRT: /* Break condition */ 99232633Ssam case PARERR: /* parity error */ 99333673Sbostic rcverr = (char *)0; 99432633Ssam break; 99532633Ssam case OVRNERR: /* Overrun error */ 99632633Ssam rcverr = "overrun error"; 99732633Ssam break; 99832633Ssam case OVFERR: /* Overflow error */ 99932633Ssam rcverr = "overflow error"; 100032633Ssam break; 100132633Ssam default: 100232633Ssam rcverr = "undefined rcv error"; 100332633Ssam } 100432633Ssam if (rcverr != (char *)0) 100532633Ssam mplog(unit, port, rcverr, ev->ev_error); 100632633Ssam next: 100732633Ssam ev->ev_cmd = 0; 100832633Ssam ev->ev_opts = 0; 100932633Ssam ev->ev_error = 0; 101032633Ssam ev->ev_flags = 0; 101132633Ssam ev->ev_status = EVSTATUS_GO; /* start next read */ 101232633Ssam adjptr(mp->mp_nextrcv, MPOUTSET); 101332633Ssam ev = &mp->mp_sendq[mp->mp_nextrcv]; 101432633Ssam } 101532633Ssam } 101632633Ssam } 101732633Ssam 101832633Ssam /* 101932633Ssam * Log an mpcc diagnostic. 102032633Ssam */ 102132633Ssam mplog(unit, port, cp, flags) 102232633Ssam char *cp; 102332633Ssam { 102432633Ssam 102532633Ssam if (flags) 102632633Ssam log(LOG_ERR, "mp%d: port%d, %s (%d)\n", 102732633Ssam unit, port, cp, flags); 102832633Ssam else 102932633Ssam log(LOG_ERR, "mp%d: port%d, %s\n", unit, port, cp); 103032633Ssam } 103132633Ssam 103232633Ssam int MPHOSTINT = 1; 103332633Ssam 103432633Ssam mptimeint(mb) 103532633Ssam register struct mblok *mb; 103632633Ssam { 103732633Ssam 103832633Ssam mb->mb_mpintcnt = 0; 103932633Ssam mb->mb_mpintclk = (caddr_t)0; 104032633Ssam *(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2; 104132633Ssam } 104232633Ssam 104332633Ssam /* 104432633Ssam * Interupt mpcc 104532633Ssam */ 104632633Ssam mpintmpcc(mb, port) 104732633Ssam register struct mblok *mb; 104832633Ssam u_short port; 104932633Ssam { 105032633Ssam 105132633Ssam mb->mb_intr[port] |= MPSEMA_WORK; 105232633Ssam if (++mb->mb_mpintcnt == MPHOSTINT) { 105332633Ssam mb->mb_mpintcnt = 0; 105432633Ssam *(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2; 105532633Ssam if (mb->mb_mpintclk) { 105632633Ssam untimeout(mptimeint, mb); 105732633Ssam mb->mb_mpintclk = 0; 105832633Ssam } 105932633Ssam } else { 106032633Ssam if (mb->mb_mpintclk == 0) { 106132633Ssam timeout(mptimeint, mb, 4); 106232633Ssam mb->mb_mpintclk = (caddr_t)1; 106332633Ssam } 106432633Ssam } 106532633Ssam } 106632633Ssam 106732633Ssam static char *mpherrmsg[] = { 106832633Ssam "", 106932633Ssam "Bus error", /* MPBUSERR */ 107032633Ssam "Address error", /* ADDRERR */ 107132633Ssam "Undefined ecc interrupt", /* UNDECC */ 107232633Ssam "Undefined interrupt", /* UNDINT */ 107332633Ssam "Power failure occurred", /* PWRFL */ 107432633Ssam "Stray transmit done interrupt", /* NOXENTRY */ 107532633Ssam "Two fast timers on one port", /* TWOFTMRS */ 107632633Ssam "Interrupt queue full", /* INTQFULL */ 107732633Ssam "Interrupt queue ack error", /* INTQERR */ 107832633Ssam "Uncorrectable dma parity error", /* CBPERR */ 107932633Ssam "32 port ACAP failed power up", /* ACPDEAD */ 108032633Ssam }; 108132633Ssam #define NHERRS (sizeof (mpherrmsg) / sizeof (mpherrmsg[0])) 108232633Ssam 108332633Ssam mperror(mb, unit) 108432633Ssam register struct mblok *mb; 108532633Ssam int unit; 108632633Ssam { 108732633Ssam register char *cp; 108832633Ssam register int i; 108932633Ssam 109032633Ssam if (mb->mb_softerr) { 109132633Ssam switch (mb->mb_softerr) { 109232633Ssam case DMAPERR: /* dma parity error */ 109332633Ssam cp = "dma parity error"; 109432633Ssam break; 109532633Ssam case ECCERR: 109632633Ssam cp = "local memory ecc error"; 109732633Ssam break; 109832633Ssam default: 109932633Ssam cp = "unknown error"; 110032633Ssam break; 110132633Ssam } 110232633Ssam log(LOG_ERR, "mp%d: soft error, %s", unit, cp); 110332633Ssam mb->mb_softerr = 0; 110432633Ssam } 110532633Ssam if (mb->mb_harderr) { 110632633Ssam if (mb->mb_harderr < NHERRS) 110732633Ssam cp = mpherrmsg[mb->mb_harderr]; 110832633Ssam else 110932633Ssam cp = "unknown error"; 111032633Ssam log(LOG_ERR, "mp%d: hard error, %s", unit, cp); 111132633Ssam if (mb->mb_status == MP_OPOPEN) { 111232633Ssam for (i = 0; i < MPMAXPORT; i++) { 111332633Ssam mpcleanport(mb, i); 111432633Ssam mb->mb_proto[i] = MPPROTO_UNUSED; 111532633Ssam } 111632633Ssam } 111732633Ssam mb->mb_harderr = 0; 111832633Ssam mb->mb_status = 0; 111932633Ssam } 112032633Ssam } 112132633Ssam 112232633Ssam mppurge(addr, cc) 112332633Ssam register caddr_t addr; 112432633Ssam register int cc; 112532633Ssam { 112632633Ssam 112732633Ssam for (; cc >= 0; addr += NBPG, cc -= NBPG) 112832633Ssam mtpr(P1DC, addr); 112932633Ssam } 113032633Ssam 113132633Ssam /* 113232633Ssam * MPCC Download Pseudo-device. 113332633Ssam */ 113432633Ssam char mpdlbuf[MPDLBUFSIZE]; 113532633Ssam int mpdlbusy; /* interlock on download buffer */ 113632633Ssam int mpdlerr; 113732633Ssam 113832633Ssam mpdlopen(dev) 113932633Ssam dev_t dev; 114032633Ssam { 114132633Ssam int unit, mpu; 114232633Ssam struct vba_device *vi; 114332633Ssam 114432633Ssam unit = minor(dev); 114532633Ssam mpu = MPUNIT(unit); 114632633Ssam if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0) 114732633Ssam return (ENODEV); 114832633Ssam return (0); 114932633Ssam } 115032633Ssam 115132633Ssam mpdlwrite(dev, uio) 115232633Ssam dev_t dev; 115332633Ssam struct uio *uio; 115432633Ssam { 115532633Ssam register struct mpsoftc *ms = &mp_softc[MPUNIT(minor(dev))]; 115632633Ssam register struct mpdl *dl; 115732633Ssam int error; 115832633Ssam 115932633Ssam if (ms->ms_mb == 0 || ms->ms_mb->mb_status != MP_DLOPEN) 116032633Ssam return (EFAULT); 116132633Ssam dl = &ms->ms_mb->mb_dl; 116232633Ssam dl->mpdl_count = uio->uio_iov->iov_len; 116332633Ssam dl->mpdl_data = (caddr_t) vtoph((struct proc *)0, mpdlbuf); 116432633Ssam if (error = uiomove(mpdlbuf, dl->mpdl_count, UIO_WRITE, uio)) 116532633Ssam return (error); 116632633Ssam uio->uio_resid -= dl->mpdl_count; /* set up return from write */ 116732633Ssam dl->mpdl_cmd = MPDLCMD_NORMAL; 116832633Ssam error = mpdlwait(dl); 116932633Ssam return (error); 117032633Ssam } 117132633Ssam 117232633Ssam mpdlclose(dev) 117332633Ssam dev_t dev; 117432633Ssam { 117532633Ssam register struct mblok *mb = mp_softc[MPUNIT(minor(dev))].ms_mb; 117632633Ssam int ret = 0; 117732633Ssam 117832633Ssam if (mb == 0 || mb->mb_status != MP_DLDONE) { 117932633Ssam mpbogus.status = 0; 118032633Ssam if (mpbogus.mb == mpbogus.mbloks[MPUNIT(minor(dev))]) 118132633Ssam mpdlbusy--; 118232633Ssam return (EEXIST); 118332633Ssam } 118432633Ssam mb->mb_status = MP_OPOPEN; 118532633Ssam mpbogus.status = 0; 118632633Ssam /* set to dead, for board handshake */ 118732633Ssam mb->mb_hostint.imok = MPIMOK_DEAD; 118832633Ssam return (0); 118932633Ssam } 119032633Ssam 119132681Skarels mpreset(dev) 119232681Skarels dev_t dev; 119332681Skarels { 119432681Skarels /* XXX */ 119532681Skarels } 119632681Skarels 119732633Ssam int mpdltimeout(); 119832633Ssam 119932633Ssam mpdlioctl(dev, cmd, data, flag) 120032633Ssam dev_t dev; 120132633Ssam caddr_t data; 120232633Ssam { 120332633Ssam register struct mblok *mb; 120432633Ssam register struct mpdl *dl; 120532633Ssam int unit, error, s, i, j; 120632633Ssam 120732633Ssam mb = mp_softc[unit=MPUNIT(minor(dev))].ms_mb; 120832633Ssam if (mb == 0) 120932633Ssam return (EEXIST); 121032633Ssam dl = &mb->mb_dl; 121132633Ssam error = 0; 121232633Ssam switch (cmd) { 121332633Ssam case MPIOPORTMAP: 121432633Ssam bcopy(data, (caddr_t)mb->mb_proto, sizeof (mb->mb_proto)); 121532633Ssam break; 121632633Ssam case MPIOHILO: 121732633Ssam bcopy(data, (caddr_t)&mb->mb_hiport, 2*(sizeof(mb->mb_hiport))); 121832633Ssam break; 121932633Ssam case MPIOENDDL: 122032633Ssam dl->mpdl_count = 0; 122132633Ssam dl->mpdl_data = 0; 122232633Ssam dl->mpdl_cmd = MPIOENDDL&IOCPARM_MASK; 122332633Ssam error = mpdlwait(dl); 122432633Ssam mpccinit(unit); 122532633Ssam mb->mb_status = MP_DLDONE; 122632633Ssam mpdlbusy--; 122732633Ssam break; 122832633Ssam case MPIOENDCODE: 122932633Ssam dl->mpdl_count = 0; 123032633Ssam dl->mpdl_data = 0; 123132633Ssam dl->mpdl_cmd = MPIOENDCODE&IOCPARM_MASK; 123232633Ssam error = mpdlwait(dl); 123332633Ssam break; 123432633Ssam case MPIOASYNCNF: 123532633Ssam bcopy(data, mpdlbuf, sizeof (struct abdcf)); 123632633Ssam dl->mpdl_data = (caddr_t) vtoph((struct proc *)0, mpdlbuf); 123732633Ssam dl->mpdl_count = sizeof (struct abdcf); 123832633Ssam dl->mpdl_cmd = MPIOASYNCNF&IOCPARM_MASK; 123932633Ssam error = mpdlwait(dl); 124032633Ssam break; 124132633Ssam case MPIOSTARTDL: 124232633Ssam while (mpdlbusy) 124332633Ssam sleep((caddr_t)&mpdlbusy, PZERO+1); 124432633Ssam mpdlbusy++; 124532633Ssam /* initialize the downloading interface */ 124632633Ssam mpbogus.magic = MPMAGIC; 124732633Ssam mpbogus.mb = mpbogus.mbloks[unit]; 124832633Ssam mpbogus.status = 1; 124932633Ssam dl->mpdl_status = EVSTATUS_FREE; 125032633Ssam dl->mpdl_count = 0; 125132633Ssam dl->mpdl_cmd = 0; 125232633Ssam dl->mpdl_data = (char *) 0; 125332633Ssam mpdlerr = 0; 125432633Ssam mb->mb_magic = MPMAGIC; 125532633Ssam mb->mb_ivec = mp_softc[unit].ms_ivec+1; /* download vector */ 125632633Ssam mb->mb_status = MP_DLPEND; 125732633Ssam mb->mb_diagswitch[0] = 'A'; 125832633Ssam mb->mb_diagswitch[1] = 'P'; 125932633Ssam s = spl8(); 126032633Ssam *(u_short *)mpinfo[unit]->ui_addr = 2; 126132633Ssam timeout(mpdltimeout, mb, 30*hz); /* approx 15 seconds */ 126232633Ssam sleep((caddr_t)&mb->mb_status, PZERO+1); 126332633Ssam splx(s); 126432633Ssam if (mb->mb_status == MP_DLOPEN) { 126532633Ssam untimeout(mpdltimeout, mb); 126632633Ssam } else if (mb->mb_status == MP_DLTIME) { 126732633Ssam mpbogus.status = 0; 126832633Ssam error = ETIMEDOUT; 126932633Ssam } else { 127032633Ssam mpbogus.status = 0; 127132633Ssam error = ENXIO; 127232633Ssam log(LOG_ERR, "mp%d: start download: unknown status %x", 127332633Ssam unit, mb->mb_status); 127432633Ssam } 127532633Ssam bzero(mb->mb_port, sizeof (mb->mb_port)); 127632633Ssam break; 127732633Ssam case MPIORESETBOARD: 127832633Ssam s = spl8(); 127932633Ssam if (mb->mb_imokclk) 128032633Ssam mb->mb_imokclk = 0; 128132633Ssam *(u_short *)mpinfo[unit]->ui_addr = 0x100; 128232633Ssam if (mb->mb_status == MP_DLOPEN || mb->mb_status == MP_DLDONE) { 128332633Ssam mpdlerr = MP_DLERROR; 128432633Ssam dl->mpdl_status = EVSTATUS_FREE; 128532633Ssam wakeup((caddr_t)&dl->mpdl_status); 128632633Ssam mpbogus.status = 0; 128732633Ssam } 128832633Ssam for (i = 0; i < MPMAXPORT; i++) { 128932633Ssam if (mb->mb_harderr || mb->mb_softerr) 129032633Ssam mperror(mb, i); 129132633Ssam mpcleanport(mb, i); 129232633Ssam mb->mb_proto[i] = MPPROTO_UNUSED; 129332633Ssam } 129432633Ssam mb->mb_status = 0; 129532633Ssam splx(s); 129632633Ssam break; 129732633Ssam default: 129832633Ssam error = EINVAL; 129932633Ssam break; 130032633Ssam } 130132633Ssam return (error); 130232633Ssam } 130332633Ssam 130432633Ssam mpccinit(unit) 130532633Ssam int unit; 130632633Ssam { 130732633Ssam register struct mblok *mb = mp_softc[unit].ms_mb; 130832633Ssam register struct his *his; 130932633Ssam register int i, j; 131032633Ssam 131132633Ssam mb->mb_status = MP_DLDONE; 131232633Ssam mb->mb_ivec = mp_softc[unit].ms_ivec; 131332633Ssam mb->mb_magic = MPMAGIC; 131432633Ssam /* Init host interface structure */ 131532633Ssam his = &mb->mb_hostint; 131632633Ssam his->semaphore = MPSEMA_AVAILABLE; 131732633Ssam for (i = 0; i < NMPPROTO; i++) 131832633Ssam for (j = 0; j < MPMAXPORT; j++) { 131932633Ssam his->proto[i].inbdone[j] = MPPORT_EOL; 132032633Ssam his->proto[i].outbdone[j] = MPPORT_EOL; 132132633Ssam } 132232633Ssam mb->mb_unit = unit; 132332633Ssam } 132432633Ssam 132532633Ssam mpdlintr(mpcc) 132632633Ssam int mpcc; 132732633Ssam { 132832633Ssam register struct mblok *mb; 132932633Ssam register struct mpdl *dl; 133032633Ssam 133132633Ssam mb = mp_softc[mpcc].ms_mb; 133232633Ssam if (mb == 0) { 133332633Ssam printf("mp%d: stray download interrupt\n", mpcc); 133432633Ssam return; 133532633Ssam } 133632633Ssam dl = &mb->mb_dl; 133732633Ssam switch (mb->mb_status) { 133832633Ssam case MP_DLOPEN: 133932633Ssam if (dl->mpdl_status != EVSTATUS_DONE) 134032633Ssam mpdlerr = MP_DLERROR; 134132633Ssam dl->mpdl_status = EVSTATUS_FREE; 134232633Ssam wakeup((caddr_t)&dl->mpdl_status); 134332633Ssam return; 134432633Ssam case MP_DLPEND: 134532633Ssam mb->mb_status = MP_DLOPEN; 134632633Ssam wakeup(&mb->mb_status); 134732633Ssam /* fall thru... */ 134832633Ssam case MP_DLTIME: 134932633Ssam return; 135032633Ssam case MP_OPOPEN: 135132633Ssam if (mb->mb_imokclk) 135232633Ssam mb->mb_imokclk = 0; 135332633Ssam mb->mb_nointcnt = 0; /* reset no interrupt count */ 135432633Ssam mb->mb_hostint.imok = MPIMOK_DEAD; 135532633Ssam mb->mb_imokclk = (caddr_t)1; 135632633Ssam break; 135732633Ssam default: 135832633Ssam log(LOG_ERR, "mp%d: mpdlintr, status %x\n", 135932633Ssam mpcc, mb->mb_status); 136032633Ssam break; 136132633Ssam } 136232633Ssam } 136332633Ssam 136432633Ssam mpdltimeout(mp) 136532633Ssam struct mblok *mp; 136632633Ssam { 136732633Ssam 136832633Ssam mp->mb_status = MP_DLTIME; 136932633Ssam wakeup((caddr_t)&mp->mb_status); 137032633Ssam } 137132633Ssam 137232633Ssam /* 137332633Ssam * Wait for a transfer to complete or a timeout to occur. 137432633Ssam */ 137532633Ssam mpdlwait(dl) 137632633Ssam register struct mpdl *dl; 137732633Ssam { 137832633Ssam int s, error = 0; 137932633Ssam 138032633Ssam s = spl8(); 138132633Ssam dl->mpdl_status = EVSTATUS_GO; 138232633Ssam while (dl->mpdl_status != EVSTATUS_FREE) { 138332633Ssam sleep((caddr_t)&dl->mpdl_status, PZERO+1); 138432633Ssam if (mpdlerr == MP_DLERROR) 138532633Ssam error = EIO; 138632633Ssam } 138732633Ssam splx(s); 138832633Ssam return (error); 138932633Ssam } 139032633Ssam #endif 1391