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