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