134506Skarels /* 234506Skarels * Copyright (c) 1988 Regents of the University of California. 334506Skarels * All rights reserved. 434506Skarels * 535055Skarels * This code is derived from software contributed to Berkeley by 635055Skarels * Computer Consoles Inc. 735055Skarels * 834506Skarels * Redistribution and use in source and binary forms are permitted 934866Sbostic * provided that the above copyright notice and this paragraph are 1034866Sbostic * duplicated in all such forms and that any documentation, 1134866Sbostic * advertising materials, and other materials related to such 1234866Sbostic * distribution and use acknowledge that the software was developed 1334866Sbostic * by the University of California, Berkeley. The name of the 1434866Sbostic * University may not be used to endorse or promote products derived 1534866Sbostic * from this software without specific prior written permission. 1634866Sbostic * THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY EXPRESS OR 1734866Sbostic * IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED 1834866Sbostic * WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE. 1934506Skarels * 20*35935Sbostic * @(#)mp.c 7.7 (Berkeley) 10/19/88 2134506Skarels */ 2232633Ssam 2332633Ssam #include "mp.h" 2432633Ssam #if NMP > 0 2532633Ssam /* 2632633Ssam * Multi Protocol Communications Controller (MPCC). 2732633Ssam * Asynchronous Terminal Protocol Support. 2832633Ssam */ 2932633Ssam #include "param.h" 3032633Ssam #include "ioctl.h" 3132633Ssam #include "tty.h" 3232633Ssam #include "dir.h" 3332633Ssam #include "user.h" 3432633Ssam #include "map.h" 3532633Ssam #include "buf.h" 3632633Ssam #include "conf.h" 3732633Ssam #include "file.h" 3832633Ssam #include "uio.h" 3932633Ssam #include "errno.h" 4032633Ssam #include "syslog.h" 4132633Ssam #include "vmmac.h" 4232633Ssam #include "kernel.h" 4332633Ssam #include "clist.h" 4432633Ssam 4534506Skarels #include "../machine/pte.h" 4634506Skarels #include "../machine/mtpr.h" 4734506Skarels 4832633Ssam #include "../tahoevba/vbavar.h" 4932633Ssam #include "../tahoevba/mpreg.h" 5032633Ssam 5132633Ssam #define MPCHUNK 16 5232633Ssam #define MPPORT(n) ((n) & 0xf) 5332633Ssam #define MPUNIT(n) ((n) >> 4) 5432633Ssam 5532633Ssam /* 5632633Ssam * Driver information for auto-configuration stuff. 5732633Ssam */ 5832633Ssam int mpprobe(), mpattach(), mpintr(); 5932633Ssam struct vba_device *mpinfo[NMP]; 6032633Ssam long mpstd[] = { 0 }; 6132633Ssam struct vba_driver mpdriver = 6232633Ssam { mpprobe, 0, mpattach, 0, mpstd, "mp", mpinfo }; 6332633Ssam 6432633Ssam int mpstart(); 6532633Ssam struct mpevent *mpparam(); 6632633Ssam struct mpevent *mp_getevent(); 6732633Ssam 6832633Ssam /* 6932633Ssam * The following structure is needed to deal with mpcc's convoluted 7032633Ssam * method for locating it's mblok structures (hold your stomach). 7132633Ssam * When an mpcc is reset at boot time it searches host memory 7232633Ssam * looking for a string that says ``ThIs Is MpCc''. The mpcc 7332633Ssam * then reads the structure to locate the pointer to it's mblok 7432633Ssam * structure (you can wretch now). 7532633Ssam */ 7632633Ssam struct mpbogus { 7732633Ssam char s[12]; /* `ThIs Is MpCc'' */ 7832633Ssam u_char status; 7932633Ssam u_char unused; 8032633Ssam u_short magic; 8132633Ssam struct mblok *mb; 8232633Ssam struct mblok *mbloks[NMP]; /* can support at most 16 mpcc's */ 8332633Ssam } mpbogus = { 'T','h','I','s',' ','I','s',' ','M','p','C','c' }; 8432633Ssam 8532633Ssam /* 8632633Ssam * Software state per unit. 8732633Ssam */ 8832633Ssam struct mpsoftc { 8932633Ssam u_int ms_ivec; /* interrupt vector */ 9032633Ssam u_int ms_softCAR; /* software carrier for async */ 9132633Ssam struct mblok *ms_mb; /* mpcc status area */ 9232633Ssam struct vb_buf ms_buf; /* vba resources for ms_mb */ 9332633Ssam struct hxmtl ms_hxl[MPMAXPORT];/* host transmit list */ 9432633Ssam struct asyncparam ms_async[MPMAXPORT][MPINSET];/* async structs */ 9532633Ssam char ms_cbuf[MPMAXPORT][MPOUTSET][CBSIZE];/* input character buffers */ 9632633Ssam } mp_softc[NMP]; 9732633Ssam 9832633Ssam struct tty mp_tty[NMP*MPCHUNK]; 9932633Ssam #ifndef lint 10032633Ssam int nmp = NMP*MPCHUNK; 10132633Ssam #endif 10232633Ssam 10332633Ssam int ttrstrt(); 10432633Ssam 10532633Ssam mpprobe(reg, vi) 10632633Ssam caddr_t reg; 10732633Ssam struct vba_device *vi; 10832633Ssam { 10932633Ssam register int br, cvec; 11032633Ssam register struct mpsoftc *ms; 11132633Ssam 11232633Ssam #ifdef lint 11332633Ssam br = 0; cvec = br; br = cvec; 11432633Ssam mpintr(0); 11534506Skarels mpdlintr(0); 11632633Ssam #endif 11732633Ssam if (badaddr(reg, 2)) 11832633Ssam return (0); 11932633Ssam ms = &mp_softc[vi->ui_unit]; 12032633Ssam /* 12132633Ssam * Allocate page tables and mblok 12232633Ssam * structure (mblok in non-cached memory). 12332633Ssam */ 12432633Ssam if (vbainit(&ms->ms_buf, sizeof (struct mblok), VB_32BIT) == 0) { 12532633Ssam printf("mp%d: vbainit failed\n", vi->ui_unit); 12632633Ssam return (0); 12732633Ssam } 12832633Ssam ms->ms_mb = (struct mblok *)ms->ms_buf.vb_rawbuf; 12932633Ssam ms->ms_ivec = MPINTRBASE + 2*vi->ui_unit; /* XXX */ 13032633Ssam br = 0x14, cvec = ms->ms_ivec; /* XXX */ 13134287Skarels return (sizeof (*reg)); 13232633Ssam } 13332633Ssam 13432633Ssam mpattach(vi) 13532633Ssam register struct vba_device *vi; 13632633Ssam { 13732633Ssam register struct mpsoftc *ms = &mp_softc[vi->ui_unit]; 13832633Ssam 13932633Ssam ms->ms_softCAR = vi->ui_flags; 14032633Ssam /* 14132633Ssam * Setup pointer to mblok, initialize bogus 14232633Ssam * status block used by mpcc to locate the pointer 14332633Ssam * and then poke the mpcc to get it to search host 14432633Ssam * memory to find mblok pointer. 14532633Ssam */ 14632633Ssam mpbogus.mbloks[vi->ui_unit] = (struct mblok *)ms->ms_buf.vb_physbuf; 14732633Ssam *(short *)vi->ui_addr = 0x100; /* magic */ 14832633Ssam } 14932633Ssam 15032633Ssam /* 15132633Ssam * Open an mpcc port. 15232633Ssam */ 15334506Skarels /* ARGSUSED */ 15432633Ssam mpopen(dev, mode) 15532633Ssam dev_t dev; 15632633Ssam { 15732633Ssam register struct tty *tp; 15832633Ssam register struct mpsoftc *ms; 15932633Ssam int error, s, port, unit, mpu; 16032633Ssam struct vba_device *vi; 16132633Ssam struct mpport *mp; 16232633Ssam struct mpevent *ev; 16332633Ssam 16432633Ssam unit = minor(dev); 16532633Ssam mpu = MPUNIT(unit); 16632633Ssam if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0) 16732633Ssam return (ENXIO); 16832633Ssam tp = &mp_tty[unit]; 16932633Ssam if (tp->t_state & TS_XCLUDE && u.u_uid != 0) 17032633Ssam return (EBUSY); 17132633Ssam ms = &mp_softc[mpu]; 17232633Ssam port = MPPORT(unit); 17332633Ssam if (ms->ms_mb->mb_proto[port] != MPPROTO_ASYNC || 17432633Ssam ms->ms_mb->mb_status != MP_OPOPEN) 17532633Ssam return (ENXIO); 17632633Ssam mp = &ms->ms_mb->mb_port[port]; /* host mpcc struct */ 17732633Ssam s = spl8(); 178*35935Sbostic /* 179*35935Sbostic * serialize open and close events 180*35935Sbostic */ 181*35935Sbostic while ((mp->mp_flags & MP_PROGRESS) || (tp->t_state & TS_WOPEN)) 18232633Ssam sleep((caddr_t)&tp->t_canq, TTIPRI); 183*35935Sbostic restart: 18432633Ssam tp->t_state |= TS_WOPEN; 18532633Ssam tp->t_addr = (caddr_t)ms; 18632633Ssam tp->t_oproc = mpstart; 18732633Ssam tp->t_dev = dev; 18834978Sbostic if ((tp->t_state & TS_ISOPEN) == 0) { 18934978Sbostic ttychars(tp); 19034978Sbostic if (tp->t_ispeed == 0) { 19134978Sbostic tp->t_ispeed = B9600; 19234978Sbostic tp->t_ospeed = B9600; 19334978Sbostic tp->t_flags = ODDP|EVENP|ECHO; 19434978Sbostic } 19534978Sbostic /* 19634978Sbostic * Initialize port state: init MPCC interface 19734978Sbostic * structures for port and setup modem control. 19834978Sbostic */ 19934978Sbostic error = mpportinit(ms, mp, port); 20034978Sbostic if (error) 20134978Sbostic goto bad; 20234978Sbostic ev = mpparam(unit); 20334978Sbostic if (ev == 0) { 20434978Sbostic error = ENOBUFS; 20534978Sbostic goto bad; 20634978Sbostic } 207*35935Sbostic mp->mp_flags |= MP_PROGRESS; 20834978Sbostic mpcmd(ev, EVCMD_OPEN, 0, ms->ms_mb, port); 209*35935Sbostic /* 210*35935Sbostic * wait for port to start 211*35935Sbostic */ 212*35935Sbostic while (mp->mp_proto != MPPROTO_ASYNC) 213*35935Sbostic sleep((caddr_t)&tp->t_canq, TTIPRI); 214*35935Sbostic mp->mp_flags &= ~MP_PROGRESS; 21532633Ssam } 216*35935Sbostic while ((tp->t_state & TS_CARR_ON) == 0) { 21732633Ssam sleep((caddr_t)&tp->t_rawq, TTIPRI); 218*35935Sbostic /* 219*35935Sbostic * a mpclose() might have disabled port. if so restart 220*35935Sbostic */ 221*35935Sbostic if (mp->mp_proto != MPPROTO_ASYNC) 222*35935Sbostic goto restart; 223*35935Sbostic tp->t_state |= TS_WOPEN; 224*35935Sbostic } 22532633Ssam error = (*linesw[tp->t_line].l_open)(dev,tp); 22632633Ssam done: 22732633Ssam splx(s); 228*35935Sbostic /* 229*35935Sbostic * wakeup those processes waiting for the open to complete 230*35935Sbostic */ 23132633Ssam wakeup((caddr_t)&tp->t_canq); 23232633Ssam return (error); 23332633Ssam bad: 23432633Ssam tp->t_state &= ~TS_WOPEN; 23532633Ssam goto done; 23632633Ssam } 23732633Ssam 23832633Ssam /* 23932633Ssam * Close an mpcc port. 24032633Ssam */ 24134506Skarels /* ARGSUSED */ 24234506Skarels mpclose(dev, flag) 24332633Ssam dev_t dev; 24432633Ssam { 24532633Ssam register struct tty *tp; 24632633Ssam register struct mpport *mp; 24732633Ssam register struct mpevent *ev; 24832633Ssam int s, port, unit, error; 24932633Ssam struct mblok *mb; 25032633Ssam 25132633Ssam unit = minor(dev); 25232633Ssam tp = &mp_tty[unit]; 25332633Ssam port = MPPORT(unit); 25432633Ssam mb = mp_softc[MPUNIT(unit)].ms_mb; 25532633Ssam mp = &mb->mb_port[port]; 25632633Ssam s = spl8(); 257*35935Sbostic if (mp->mp_flags & MP_PROGRESS) { 25832633Ssam if (mp->mp_flags & MP_REMBSY) { 25932633Ssam mp->mp_flags &= ~MP_REMBSY; 26032633Ssam splx(s); 26132633Ssam return (0); 26232633Ssam } 26332633Ssam while (mp->mp_flags & MP_PROGRESS) 264*35935Sbostic sleep((caddr_t)&tp->t_canq, TTIPRI); 26532633Ssam } 26632633Ssam error = 0; 26732633Ssam mp->mp_flags |= MP_PROGRESS; 26832633Ssam (*linesw[tp->t_line].l_close)(tp); 269*35935Sbostic ev = mp_getevent(mp, unit, 1); 27032633Ssam if (ev == 0) { 27134977Sbostic error = ENOBUFS; 27234977Sbostic mp->mp_flags &= ~MP_PROGRESS; 27334977Sbostic goto out; 27432633Ssam } 27534977Sbostic if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0) 27634977Sbostic mpmodem(unit, MMOD_OFF); 27734977Sbostic else 27834977Sbostic mpmodem(unit, MMOD_ON); 27932633Ssam mpcmd(ev, EVCMD_CLOSE, 0, mb, port); 28034977Sbostic ttyclose(tp); 28132633Ssam out: 28232633Ssam if (mp->mp_flags & MP_REMBSY) 28332633Ssam mpclean(mb, port); 284*35935Sbostic else 285*35935Sbostic while (mp->mp_flags & MP_PROGRESS) 286*35935Sbostic sleep((caddr_t)&tp->t_canq,TTIPRI); 28732633Ssam splx(s); 28832633Ssam return (error); 28932633Ssam } 29032633Ssam 29132633Ssam /* 29232633Ssam * Read from an mpcc port. 29332633Ssam */ 29432633Ssam mpread(dev, uio) 29532633Ssam dev_t dev; 29632633Ssam struct uio *uio; 29732633Ssam { 29832633Ssam struct tty *tp; 29932633Ssam 30032633Ssam tp = &mp_tty[minor(dev)]; 30132633Ssam return ((*linesw[tp->t_line].l_read)(tp, uio)); 30232633Ssam } 30332633Ssam 30432633Ssam /* 30532633Ssam * Write to an mpcc port. 30632633Ssam */ 30732633Ssam mpwrite(dev, uio) 30832633Ssam dev_t dev; 30932633Ssam struct uio *uio; 31032633Ssam { 31132633Ssam struct tty *tp; 31232633Ssam 31332633Ssam tp = &mp_tty[minor(dev)]; 31432633Ssam return ((*linesw[tp->t_line].l_write)(tp, uio)); 31532633Ssam } 31632633Ssam 31732633Ssam /* 31832633Ssam * Ioctl for a mpcc port 31932633Ssam */ 32032633Ssam mpioctl(dev, cmd, data, flag) 32132633Ssam dev_t dev; 32232633Ssam caddr_t data; 32332633Ssam { 32432633Ssam register struct tty *tp; 32532633Ssam register struct mpsoftc *ms; 32632633Ssam register struct mpevent *ev; 32732633Ssam register struct mpport *mp; 32832633Ssam int s, port, error, unit; 32932633Ssam struct mblok *mb; 33032633Ssam 33132633Ssam unit = minor(dev); 33232633Ssam tp = &mp_tty[unit]; 33332633Ssam ms = &mp_softc[MPUNIT(unit)]; 33432633Ssam mb = ms->ms_mb; 335*35935Sbostic port = MPPORT(unit); 336*35935Sbostic mp = &mb->mb_port[port]; 337*35935Sbostic if (mp->mp_proto != MPPROTO_ASYNC) 338*35935Sbostic return(ENXIO); 33932633Ssam error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag); 34032633Ssam if (error >= 0) 34132633Ssam return (error); 34232633Ssam error = ttioctl(tp, cmd, data, flag); 34332633Ssam if (error >= 0) { 34432633Ssam if (cmd == TIOCSETP || cmd == TIOCSETN || cmd == TIOCLBIS || 34534796Sbostic cmd == TIOCLBIC || cmd == TIOCLSET || cmd == TIOCSETC) { 346*35935Sbostic s = spl8(); 347*35935Sbostic while (mp->mp_flags & MP_IOCTL) { 348*35935Sbostic sleep((caddr_t)&tp->t_canq, TTIPRI); 349*35935Sbostic if (mp->mp_proto != MPPROTO_ASYNC) { 350*35935Sbostic mp->mp_flags &= ~MP_IOCTL; 351*35935Sbostic splx(s); 352*35935Sbostic return(ENXIO); 353*35935Sbostic } 354*35935Sbostic } 35532633Ssam ev = mpparam(unit); 35632633Ssam if (ev == 0) 35732633Ssam error = ENOBUFS; 358*35935Sbostic else { 359*35935Sbostic mp->mp_flags |= MP_IOCTL; 360*35935Sbostic mpcmd(ev, EVCMD_IOCTL, A_CHGALL, mb, port); 361*35935Sbostic } 362*35935Sbostic splx(s); 36332633Ssam } 36432633Ssam return (error); 36532633Ssam } 36632633Ssam switch (cmd) { 36732633Ssam case TIOCSBRK: /* send break */ 36832633Ssam case TIOCCBRK: /* clear break */ 36932633Ssam s = spl8(); 370*35935Sbostic while (mp->mp_flags & MP_IOCTL) { 371*35935Sbostic sleep((caddr_t)&tp->t_canq, TTIPRI); 372*35935Sbostic if (mp->mp_proto != MPPROTO_ASYNC) { 373*35935Sbostic mp->mp_flags &= ~MP_IOCTL; 374*35935Sbostic splx(s); 375*35935Sbostic return(ENXIO); 376*35935Sbostic } 377*35935Sbostic } 378*35935Sbostic ev = mp_getevent(mp, unit, 0); 379*35935Sbostic if (ev) { 380*35935Sbostic mp->mp_flags |= MP_IOCTL; 38132633Ssam mpcmd(ev, EVCMD_IOCTL, 382*35935Sbostic (cmd == TIOCSBRK ? A_BRKON : A_BRKOFF), mb, port); 383*35935Sbostic } else 38432633Ssam error = ENOBUFS; 38532633Ssam splx(s); 38632633Ssam break; 38732633Ssam case TIOCSDTR: /* set dtr control line */ 38832633Ssam break; 38932633Ssam case TIOCCDTR: /* clear dtr control line */ 39032633Ssam break; 39132633Ssam default: 39232633Ssam error = ENOTTY; 39332633Ssam break; 39432633Ssam } 39532633Ssam return (error); 39632633Ssam } 39732633Ssam 39832633Ssam struct mpevent * 39932633Ssam mpparam(unit) 40032633Ssam int unit; 40132633Ssam { 40232633Ssam register struct mpevent *ev; 40332633Ssam register struct mpport *mp; 40432633Ssam register struct tty *tp; 40532633Ssam struct mblok *mb; 40632633Ssam struct mpsoftc *ms; 40732633Ssam register struct asyncparam *asp; 40832633Ssam int port; 40932633Ssam 41032633Ssam ms = &mp_softc[MPUNIT(unit)]; 41132633Ssam mb = ms->ms_mb; 41232633Ssam port = MPPORT(unit); 41332633Ssam mp = &mb->mb_port[port]; 414*35935Sbostic ev = mp_getevent(mp, unit, 0); /* XXX */ 41532633Ssam if (ev == 0) 41632633Ssam return (ev); 41732633Ssam tp = &mp_tty[unit]; 41832633Ssam /* YUCK */ 41932633Ssam asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1]; 42034796Sbostic asp->ap_xon = (u_char)tp->t_startc; 42134796Sbostic asp->ap_xoff = (u_char)tp->t_stopc; 42234796Sbostic if ((tp->t_flags & RAW) || (tp->t_stopc == -1) || (tp->t_startc == -1)) 42334796Sbostic asp->ap_xena = MPA_DIS; 42434796Sbostic else 42534796Sbostic asp->ap_xena = MPA_ENA; 42633995Sbostic asp->ap_xany = ((tp->t_flags & DECCTQ) ? MPA_DIS : MPA_ENA); 42732633Ssam #ifdef notnow 42832633Ssam if (tp->t_flags & (RAW|LITOUT|PASS8)) { 42932633Ssam #endif 43032633Ssam asp->ap_data = MPCHAR_8; 43132633Ssam asp->ap_parity = MPPAR_NONE; 43232633Ssam #ifdef notnow 43332633Ssam } else { 43432633Ssam asp->ap_data = MPCHAR_7; 43532633Ssam if ((tp->t_flags & (EVENP|ODDP)) == ODDP) 43632633Ssam asp->ap_parity = MPPAR_ODD; 43732633Ssam else 43832633Ssam asp->ap_parity = MPPAR_EVEN; 43932633Ssam } 44032633Ssam #endif 441*35935Sbostic asp->ap_loop = MPA_DIS; /* disable loopback */ 442*35935Sbostic asp->ap_rtimer = A_RCVTIM; /* default receive timer */ 44332633Ssam if (tp->t_ospeed == B110) 44432633Ssam asp->ap_stop = MPSTOP_2; 44532633Ssam else 44632633Ssam asp->ap_stop = MPSTOP_1; 447*35935Sbostic if (tp->t_ospeed == 0) { 448*35935Sbostic tp->t_state |= TS_HUPCLS; 449*35935Sbostic setm(&asp->ap_modem, 0, DROP); 450*35935Sbostic seti(&asp->ap_intena, A_DCD); 451*35935Sbostic return (ev); 452*35935Sbostic } 45332633Ssam if (tp->t_ospeed == EXTA || tp->t_ospeed == EXTB) 45432633Ssam asp->ap_baud = M19200; 45532633Ssam else 45632633Ssam asp->ap_baud = tp->t_ospeed; 45732633Ssam if (ms->ms_softCAR & (1<<port)) 45832633Ssam setm(&asp->ap_modem, A_DTR, ASSERT); 45932633Ssam else 46032633Ssam setm(&asp->ap_modem, A_DTR, AUTO); 46132633Ssam seti(&asp->ap_intena, A_DCD); 46232633Ssam return (ev); 46332633Ssam } 46432633Ssam 46532633Ssam mpstart(tp) 46632633Ssam register struct tty *tp; 46732633Ssam { 46832633Ssam register struct mpevent *ev; 46932633Ssam register struct mpport *mp; 47032633Ssam struct mblok *mb; 47132633Ssam struct mpsoftc *ms; 47232633Ssam int port, unit, xcnt, n, s, i; 47332633Ssam struct hxmtl *hxp; 47432633Ssam struct clist outq; 47532633Ssam 47632633Ssam s = spl8(); 47732633Ssam unit = minor(tp->t_dev); 47832633Ssam ms = &mp_softc[MPUNIT(unit)]; 47932633Ssam mb = ms->ms_mb; 48032633Ssam port = MPPORT(unit); 48132633Ssam mp = &mb->mb_port[port]; 48232633Ssam hxp = &ms->ms_hxl[port]; 48332633Ssam xcnt = 0; 48432633Ssam outq = tp->t_outq; 48532633Ssam for (i = 0; i < MPXMIT; i++) { 48632633Ssam if (tp->t_state & (TS_TIMEOUT|TS_BUSY|TS_TTSTOP)) 48732633Ssam break; 48832633Ssam if (outq.c_cc <= TTLOWAT(tp)) { 48932633Ssam if (tp->t_state & TS_ASLEEP) { 49032633Ssam tp->t_state &= ~TS_ASLEEP; 49132633Ssam wakeup((caddr_t)&tp->t_outq); 49232633Ssam } 49332633Ssam if (tp->t_wsel) { 49432633Ssam selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL); 49532633Ssam tp->t_wsel = 0; 49632633Ssam tp->t_state &= ~TS_WCOLL; 49732633Ssam } 49832633Ssam } 49932633Ssam if (outq.c_cc == 0) 50032633Ssam break; 50132633Ssam /* 50232633Ssam * If we're not currently busy outputting, 50332633Ssam * and there is data to be output, set up 50432633Ssam * port transmit structure to send to mpcc. 50532633Ssam */ 50632633Ssam if (tp->t_flags & (RAW|LITOUT)) 50732633Ssam n = ndqb(&outq, 0); 50832633Ssam else { 50932633Ssam n = ndqb(&outq, 0200); 51032633Ssam if (n == 0) { 511*35935Sbostic if (xcnt > 0) 512*35935Sbostic break; 51332633Ssam n = getc(&outq); 51432633Ssam timeout(ttrstrt, (caddr_t)tp, (n&0177)+6); 51532633Ssam tp->t_state |= TS_TIMEOUT; 51632633Ssam break; 51732633Ssam } 51832633Ssam } 51934506Skarels hxp->dblock[i] = (caddr_t)kvtophys(outq.c_cf); 52032633Ssam hxp->size[i] = n; 52132633Ssam xcnt++; /* count of xmts to send */ 52232633Ssam ndadvance(&outq, n); 52332633Ssam } 52432633Ssam /* 52532633Ssam * If data to send, poke mpcc. 52632633Ssam */ 52732633Ssam if (xcnt) { 528*35935Sbostic ev = mp_getevent(mp, unit, 0); 52932633Ssam if (ev == 0) { 53032633Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT); 53132633Ssam } else { 53232633Ssam tp->t_state |= TS_BUSY; 53332633Ssam ev->ev_count = xcnt; 53432633Ssam mpcmd(ev, EVCMD_WRITE, 0, mb, MPPORT(unit)); 53532633Ssam } 53632633Ssam } 53732633Ssam splx(s); 53832633Ssam } 53932633Ssam 54032633Ssam /* 54132633Ssam * Advance cc bytes from q but don't free memory. 54232633Ssam */ 54332633Ssam ndadvance(q, cc) 54432633Ssam register struct clist *q; 54532633Ssam register cc; 54632633Ssam { 54732633Ssam register struct cblock *bp; 54832633Ssam char *end; 54932633Ssam int rem, s; 55032633Ssam 55132633Ssam s = spltty(); 55232633Ssam if (q->c_cc <= 0) 55332633Ssam goto out; 55432633Ssam while (cc>0 && q->c_cc) { 55532633Ssam bp = (struct cblock *)((int)q->c_cf & ~CROUND); 55632633Ssam if ((int)bp == (((int)q->c_cl-1) & ~CROUND)) { 55732633Ssam end = q->c_cl; 55832633Ssam } else { 55932633Ssam end = (char *)((int)bp + sizeof (struct cblock)); 56032633Ssam } 56132633Ssam rem = end - q->c_cf; 56232633Ssam if (cc >= rem) { 56332633Ssam cc -= rem; 56432633Ssam q->c_cc -= rem; 56532633Ssam q->c_cf = bp->c_next->c_info; 56632633Ssam } else { 56732633Ssam q->c_cc -= cc; 56832633Ssam q->c_cf += cc; 56932633Ssam break; 57032633Ssam } 57132633Ssam } 57232633Ssam if (q->c_cc <= 0) { 57332633Ssam q->c_cf = q->c_cl = NULL; 57432633Ssam q->c_cc = 0; 57532633Ssam } 57632633Ssam out: 57732633Ssam splx(s); 57832633Ssam } 57932633Ssam 58032633Ssam /* 58132633Ssam * Stop output on a line, e.g. for ^S/^Q or output flush. 58232633Ssam */ 58334506Skarels /* ARGSUSED */ 58432633Ssam mpstop(tp, rw) 58532633Ssam register struct tty *tp; 58632633Ssam int rw; 58732633Ssam { 588*35935Sbostic register struct mpport *mp; 589*35935Sbostic register struct mpevent *ev; 590*35935Sbostic int unit = minor(tp->t_dev); 591*35935Sbostic int port; 592*35935Sbostic struct mblok *mb; 59334506Skarels int s; 59432633Ssam 59532633Ssam s = spl8(); 59632633Ssam if (tp->t_state & TS_BUSY) { 597*35935Sbostic if ((tp->t_state & TS_TTSTOP) == 0) { 59832633Ssam tp->t_state |= TS_FLUSH; 599*35935Sbostic port = MPPORT(unit); 600*35935Sbostic mb = mp_softc[MPUNIT(unit)].ms_mb; 601*35935Sbostic mp = &mb->mb_port[port]; 602*35935Sbostic ev = mp_getevent(mp, unit, 0); 603*35935Sbostic if (ev == 0) { 604*35935Sbostic splx(s); 605*35935Sbostic return; 606*35935Sbostic } 607*35935Sbostic mpcmd(ev, EVCMD_WRITE, A_FLUSH, mb, port); 608*35935Sbostic } 60932633Ssam } 61032633Ssam splx(s); 61132633Ssam } 61232633Ssam 61332633Ssam /* 61432633Ssam * Initialize an async port's MPCC state. 61532633Ssam */ 61632633Ssam mpportinit(ms, mp, port) 61732633Ssam register struct mpsoftc *ms; 61832633Ssam register struct mpport *mp; 61932633Ssam int port; 62032633Ssam { 62132633Ssam register struct mpevent *ev; 62232633Ssam register int i; 62332633Ssam caddr_t ptr; 62432633Ssam 62532633Ssam mp->mp_on = mp->mp_off = 0; 62632633Ssam mp->mp_nextrcv = 0; 62732633Ssam mp->mp_flags = 0; 62832633Ssam ev = &mp->mp_recvq[0]; 62932633Ssam for (i = 0; ev < &mp->mp_recvq[MPINSET]; ev++, i++) { 63032633Ssam ev->ev_status = EVSTATUS_FREE; 63132633Ssam ev->ev_cmd = 0; 63232633Ssam ev->ev_opts = 0; 63332633Ssam ev->ev_error = 0; 63432633Ssam ev->ev_flags = 0; 63532633Ssam ev->ev_count = 0; 63634506Skarels ev->ev_un.hxl = (struct hxmtl *) kvtophys(&ms->ms_hxl[port]); 63734506Skarels ev->ev_params = (caddr_t) kvtophys(&ms->ms_async[port][i]); 63832633Ssam } 63932633Ssam ev = &mp->mp_sendq[0]; 64032633Ssam for (i = 0; ev < &mp->mp_sendq[MPOUTSET]; ev++, i++) { 64132633Ssam /* init so that L2 can't send any events */ 64232633Ssam /* to host until open has completed */ 64332633Ssam ev->ev_status = EVSTATUS_FREE; 64432633Ssam ev->ev_cmd = 0; 645*35935Sbostic ev->ev_opts = 0; 64632633Ssam ev->ev_error = 0; 64732633Ssam ev->ev_flags = 0; 64832633Ssam ev->ev_count = 0; 64932633Ssam ptr = (caddr_t) &ms->ms_cbuf[port][i][0]; 65034506Skarels ev->ev_un.rcvblk = (u_char *)kvtophys(ptr); 65134506Skarels ev->ev_params = (caddr_t) kvtophys(ptr); 65232633Ssam } 65332633Ssam return (0); 65432633Ssam } 65532633Ssam 65632633Ssam /* 65732633Ssam * Send an event to an mpcc. 65832633Ssam */ 65932633Ssam mpcmd(ev, cmd, flags, mb, port) 66032633Ssam register struct mpevent *ev; 66132633Ssam struct mblok *mb; 66232633Ssam { 66332633Ssam int s; 66432633Ssam 66532633Ssam s = spl8(); 66632633Ssam /* move host values to inbound entry */ 66732633Ssam ev->ev_cmd = cmd; 66832633Ssam ev->ev_opts = flags; 66932633Ssam /* show event ready for mpcc */ 67032633Ssam ev->ev_status = EVSTATUS_GO; 67132633Ssam mpintmpcc(mb, port); 67232633Ssam splx(s); 67332633Ssam } 67432633Ssam 67532633Ssam /* 67632633Ssam * Return the next available event entry for the indicated port. 67732633Ssam */ 67832633Ssam struct mpevent * 679*35935Sbostic mp_getevent(mp, unit, cls_req) 68032633Ssam register struct mpport *mp; 68132633Ssam int unit; 682*35935Sbostic int cls_req; 68332633Ssam { 68432633Ssam register struct mpevent *ev; 68532633Ssam int i, s; 68632633Ssam 68732633Ssam s = spl8(); 68832633Ssam ev = &mp->mp_recvq[mp->mp_on]; 68932633Ssam if (ev->ev_status != EVSTATUS_FREE) 69032633Ssam goto bad; 69132633Ssam /* 69232633Ssam * If not a close request, verify one extra 69332633Ssam * event is available for closing the port. 69432633Ssam */ 695*35935Sbostic if (!cls_req) { 69632633Ssam if ((i = mp->mp_on + 1) >= MPINSET) 69732633Ssam i = 0; 69832633Ssam if (mp->mp_recvq[i].ev_status != EVSTATUS_FREE) 69932633Ssam goto bad; 70032633Ssam } 70132633Ssam /* init inbound fields marking this entry as busy */ 702*35935Sbostic ev->ev_cmd = 0; 703*35935Sbostic ev->ev_opts = 0; 70432633Ssam ev->ev_error = 0; 70532633Ssam ev->ev_flags = 0; 70632633Ssam ev->ev_count = 0; 70732633Ssam ev->ev_status = EVSTATUS_BUSY; 70832633Ssam /* adjust pointer to next available inbound entry */ 70932633Ssam adjptr(mp->mp_on, MPINSET); 71032633Ssam splx(s); 71132633Ssam return (ev); 71232633Ssam bad: 71332633Ssam splx(s); 714*35935Sbostic log(LOG_ERR, "mp%d: port%d, out of events\n", 715*35935Sbostic MPUNIT(unit), MPPORT(unit)); 71632633Ssam return ((struct mpevent *)0); 71732633Ssam } 71832633Ssam 71932633Ssam mpmodem(unit, flag) 72032633Ssam int unit, flag; 72132633Ssam { 72232633Ssam struct mpsoftc *ms = &mp_softc[MPUNIT(unit)]; 72332633Ssam int port = MPPORT(unit); 72432633Ssam register struct mpport *mp; 72532633Ssam register struct asyncparam *asp; 72632633Ssam 72732633Ssam mp = &ms->ms_mb->mb_port[port]; 72832633Ssam asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1]; 72932633Ssam if (flag == MMOD_ON) { 73032633Ssam if (ms->ms_softCAR & (1 << port)) 73132633Ssam setm(&asp->ap_modem, A_DTR, ASSERT); 73232633Ssam else 73332633Ssam setm(&asp->ap_modem, A_DTR, AUTO); 73432633Ssam seti(&asp->ap_intena, A_DCD); 73532633Ssam } else { 73632633Ssam setm(&asp->ap_modem, 0, DROP); 73732633Ssam seti(&asp->ap_intena, 0); 73832633Ssam } 73932633Ssam } 74032633Ssam 74132633Ssam /* 74232633Ssam * Set up the modem control structure according to mask. 74332633Ssam * Each set bit in the mask means assert the corresponding 74432633Ssam * modem control line, otherwise, it will be dropped. 74532633Ssam * RTS is special since it can either be asserted, dropped 74632633Ssam * or put in auto mode for auto modem control. 74732633Ssam */ 74832633Ssam static 74932633Ssam setm(mc, mask, rts) 75032633Ssam register struct mdmctl *mc; 75132633Ssam register int mask; 75232633Ssam { 75332633Ssam 75432633Ssam mc->mc_rngdsr = (mask & A_RNGDSR) ? ASSERT : DROP; 75532633Ssam mc->mc_rate = (mask & A_RATE) ? ASSERT : DROP; 75632633Ssam mc->mc_dcd = (mask & A_DCD) ? ASSERT : DROP; 75732633Ssam mc->mc_sectx = (mask & A_SECTX) ? ASSERT : DROP; 75832633Ssam mc->mc_cts = (mask & A_CTS) ? ASSERT : DROP; 75932633Ssam mc->mc_secrx = (mask & A_SECRX) ? ASSERT : DROP; 76032633Ssam mc->mc_dtr = (mask & A_DTR) ? ASSERT : DROP; 76132633Ssam mc->mc_rts = rts; 76232633Ssam } 76332633Ssam 76432633Ssam /* 76532633Ssam * Set up the status change enable field from mask. 76632633Ssam * When a signal is enabled in this structure and 76732633Ssam * and a change in state on a corresponding modem 76832633Ssam * control line occurs, a status change event will 76932633Ssam * be delivered to the host. 77032633Ssam */ 77132633Ssam static 77232633Ssam seti(mc, mask) 77332633Ssam register struct mdmctl *mc; 77432633Ssam register int mask; 77532633Ssam { 77632633Ssam 77732633Ssam mc->mc_rngdsr = (mask & A_RNGDSR) ? MDM_ON : MDM_OFF; 77832633Ssam mc->mc_rate = (mask & A_RATE) ? MDM_ON : MDM_OFF; 77932633Ssam mc->mc_dcd = (mask & A_DCD) ? MDM_ON : MDM_OFF; 78032633Ssam mc->mc_sectx = (mask & A_SECTX) ? MDM_ON : MDM_OFF; 78132633Ssam mc->mc_cts = (mask & A_CTS) ? MDM_ON : MDM_OFF; 78232633Ssam mc->mc_secrx = (mask & A_SECRX) ? MDM_ON : MDM_OFF; 78332633Ssam mc->mc_dtr = (mask & A_DTR) ? MDM_ON : MDM_OFF; 78432633Ssam mc->mc_rts = (mask & A_RTS) ? MDM_ON : MDM_OFF; 78532633Ssam } 78632633Ssam 78732633Ssam mpcleanport(mb, port) 78832633Ssam struct mblok *mb; 78932633Ssam int port; 79032633Ssam { 79132633Ssam register struct mpport *mp; 79232633Ssam register struct tty *tp; 79332633Ssam 79432633Ssam mp = &mb->mb_port[port]; 79532633Ssam if (mp->mp_proto == MPPROTO_ASYNC) { 79632633Ssam mp->mp_flags = MP_REMBSY; 79734506Skarels /* signal loss of carrier and close */ 79832633Ssam tp = &mp_tty[mb->mb_unit*MPCHUNK+port]; 79932633Ssam ttyflush(tp, FREAD|FWRITE); 80034506Skarels (void) (*linesw[tp->t_line].l_modem)(tp, 0); 80132633Ssam } 80232633Ssam } 80332633Ssam 80432633Ssam mpclean(mb, port) 80532633Ssam register struct mblok *mb; 80632633Ssam int port; 80732633Ssam { 80832633Ssam register struct mpport *mp; 80932633Ssam register struct mpevent *ev; 81032633Ssam register int i; 81134506Skarels u_char list[2]; 81232633Ssam int unit; 81332633Ssam 81432633Ssam mp = &mb->mb_port[port]; 81532633Ssam unit = mb->mb_unit; 81632633Ssam for (i = mp->mp_off; i != mp->mp_on; i = (i+1 % MPINSET)) { 81732633Ssam ev = &mp->mp_recvq[i]; 81832633Ssam ev->ev_error = ENXIO; 81932633Ssam ev->ev_status = EVSTATUS_DONE; 82032633Ssam } 82132633Ssam list[0] = port, list[1] = MPPORT_EOL; 82232633Ssam mpxintr(unit, list); 82332633Ssam mprintr(unit, list); 82432633Ssam /* Clear async for port */ 82532633Ssam mp->mp_proto = MPPROTO_UNUSED; 82632633Ssam mp->mp_flags = 0; 82732633Ssam mp->mp_on = 0; 82832633Ssam mp->mp_off = 0; 82932633Ssam mp->mp_nextrcv = 0; 83032633Ssam 83132633Ssam mp_tty[unit*MPCHUNK + port].t_state = 0; 83232633Ssam for (ev = &mp->mp_sendq[0]; ev < &mp->mp_sendq[MPOUTSET]; ev++) { 83332633Ssam ev->ev_status = EVSTATUS_FREE; 83432633Ssam ev->ev_cmd = 0; 83532633Ssam ev->ev_error = 0; 83632633Ssam ev->ev_un.rcvblk = 0; 83732633Ssam ev->ev_params = 0; 83832633Ssam } 83932633Ssam for (ev = &mp->mp_recvq[0]; ev < &mp->mp_recvq[MPINSET]; ev++) { 84032633Ssam ev->ev_status = EVSTATUS_FREE; 84132633Ssam ev->ev_cmd = 0; 84232633Ssam ev->ev_error = 0; 84332633Ssam ev->ev_params = 0; 84432633Ssam } 84532633Ssam } 84632633Ssam 84732633Ssam /* 84832633Ssam * MPCC interrupt handler. 84932633Ssam */ 85032633Ssam mpintr(mpcc) 85132633Ssam int mpcc; 85232633Ssam { 85332633Ssam register struct mblok *mb; 85432633Ssam register struct his *his; 85532633Ssam 85632633Ssam mb = mp_softc[mpcc].ms_mb; 85732633Ssam if (mb == 0) { 85832633Ssam printf("mp%d: stray interrupt\n", mpcc); 85932633Ssam return; 86032633Ssam } 86132633Ssam his = &mb->mb_hostint; 86232633Ssam his->semaphore &= ~MPSEMA_AVAILABLE; 86332633Ssam /* 86432633Ssam * Check for events to be processed. 86532633Ssam */ 86632633Ssam if (his->proto[MPPROTO_ASYNC].outbdone[0] != MPPORT_EOL) 86732633Ssam mprintr(mpcc, his->proto[MPPROTO_ASYNC].outbdone); 86832633Ssam if (his->proto[MPPROTO_ASYNC].inbdone[0] != MPPORT_EOL) 86932633Ssam mpxintr(mpcc, his->proto[MPPROTO_ASYNC].inbdone); 87032633Ssam if (mb->mb_harderr || mb->mb_softerr) 87132633Ssam mperror(mb, mpcc); 87232633Ssam his->semaphore |= MPSEMA_AVAILABLE; 87332633Ssam } 87432633Ssam 87532633Ssam /* 87632633Ssam * Handler for processing completion of transmitted events. 87732633Ssam */ 87832633Ssam mpxintr(unit, list) 87934506Skarels register u_char *list; 88032633Ssam { 88132633Ssam register struct mpport *mp; 88232633Ssam register struct mpevent *ev; 88332633Ssam register struct mblok *mb; 88432633Ssam register struct tty *tp; 88532633Ssam register struct asyncparam *ap; 88632633Ssam struct mpsoftc *ms; 88732633Ssam int port, i, j; 888*35935Sbostic # define nextevent(mp) &mp->mp_recvq[mp->mp_off] 88932633Ssam 89032633Ssam ms = &mp_softc[unit]; 89132633Ssam mb = mp_softc[unit].ms_mb; 89232633Ssam for (j = 0; j < MPMAXPORT && ((port = *list++) != MPPORT_EOL); j++) { 89332633Ssam /* 89432633Ssam * Process each completed entry in the inbound queue. 89532633Ssam */ 89632633Ssam mp = &mb->mb_port[port]; 89732633Ssam tp = &mp_tty[unit*MPCHUNK + port]; 89832633Ssam ev = nextevent(mp); 899*35935Sbostic for (; ev->ev_status & EVSTATUS_DONE; ev = nextevent(mp)) { 90032633Ssam /* YUCK */ 90132633Ssam ap = &ms->ms_async[port][mp->mp_off]; 90234506Skarels mppurge((caddr_t)ap, (int)sizeof (*ap)); 90332633Ssam switch (ev->ev_cmd) { 90432633Ssam case EVCMD_OPEN: 90532633Ssam /* 90632633Ssam * Open completion, start all reads and 90732633Ssam * assert modem status information. 90832633Ssam */ 90932633Ssam for (i = 0; i < MPOUTSET; i++) 91032633Ssam mp->mp_sendq[i].ev_status = EVSTATUS_GO; 91132633Ssam (*linesw[tp->t_line].l_modem) 91232633Ssam (tp, ap->ap_modem.mc_dcd == ASSERT); 913*35935Sbostic mp_freein(ev); 914*35935Sbostic adjptr(mp->mp_off, MPINSET); 915*35935Sbostic mp->mp_proto = MPPROTO_ASYNC; /* XXX */ 916*35935Sbostic wakeup((caddr_t)&tp->t_canq); 91732633Ssam break; 91832633Ssam case EVCMD_CLOSE: 91932633Ssam /* 92032633Ssam * Close completion, flush all pending 92132633Ssam * transmissions, free resources, and 92232633Ssam * cleanup mpcc port state. 92332633Ssam */ 92432633Ssam for (i = 0; i < MPOUTSET; i++) { 92532633Ssam mp->mp_sendq[i].ev_status = 92632633Ssam EVSTATUS_FREE; 92732633Ssam mp->mp_sendq[i].ev_un.rcvblk = 0; 92832633Ssam mp->mp_sendq[i].ev_params = 0; 92932633Ssam } 930*35935Sbostic mp_freein(ev); 931*35935Sbostic adjptr(mp->mp_off, MPINSET); 932*35935Sbostic tp->t_state &= ~(TS_CARR_ON|TS_BUSY|TS_FLUSH); 93332633Ssam mp->mp_on = mp->mp_off = mp->mp_nextrcv = 0; 93432633Ssam mp->mp_flags &= ~MP_PROGRESS; 93532633Ssam mp->mp_proto = MPPROTO_UNUSED; 93635055Skarels wakeup((caddr_t)&tp->t_canq); 937*35935Sbostic break; 93832633Ssam case EVCMD_IOCTL: 939*35935Sbostic mp_freein(ev); 940*35935Sbostic adjptr(mp->mp_off, MPINSET); 941*35935Sbostic mp->mp_flags &= ~MP_IOCTL; 942*35935Sbostic wakeup((caddr_t)&tp->t_canq); 94332633Ssam break; 94432633Ssam case EVCMD_WRITE: 94532633Ssam /* 94632633Ssam * Transmission completed, update tty 94732633Ssam * state and restart output. 94832633Ssam */ 949*35935Sbostic if (ev->ev_opts != A_FLUSH) { 950*35935Sbostic tp->t_state &= ~TS_BUSY; 951*35935Sbostic if (tp->t_state & TS_FLUSH) 952*35935Sbostic tp->t_state &= ~TS_FLUSH; 953*35935Sbostic else { 954*35935Sbostic register int cc = 0, n; 955*35935Sbostic struct hxmtl *hxp; 95632633Ssam 957*35935Sbostic hxp = &ms->ms_hxl[port]; 958*35935Sbostic for (n=0;n < ev->ev_count; n++) 959*35935Sbostic cc += hxp->size[n]; 960*35935Sbostic ndflush(&tp->t_outq, cc); 961*35935Sbostic } 96232633Ssam } 96332633Ssam switch (ev->ev_error) { 96432633Ssam case A_SIZERR: /*# error in xmt data size */ 96532633Ssam mplog(unit, port, A_XSIZE, 0); 96632633Ssam break; 96732633Ssam case A_NXBERR: /*# no more xmt evt buffers */ 96832633Ssam mplog(unit, port, A_NOXBUF, 0); 96932633Ssam break; 97032633Ssam } 971*35935Sbostic mp_freein(ev); 972*35935Sbostic adjptr(mp->mp_off, MPINSET); 97332633Ssam mpstart(tp); 97432633Ssam break; 97532633Ssam default: 97634506Skarels mplog(unit, port, A_INVCMD, (int)ev->ev_cmd); 977*35935Sbostic mp_freein(ev); 978*35935Sbostic adjptr(mp->mp_off, MPINSET); 97932633Ssam break; 98032633Ssam } 98132633Ssam } 98232633Ssam } 983*35935Sbostic #undef nextevent 98432633Ssam } 98532633Ssam 986*35935Sbostic mp_freein(ev) 987*35935Sbostic register struct mpevent *ev; 988*35935Sbostic { 989*35935Sbostic /* re-init all values in this entry */ 990*35935Sbostic ev->ev_cmd = 0; 991*35935Sbostic ev->ev_opts = 0; 992*35935Sbostic ev->ev_error = 0; 993*35935Sbostic ev->ev_flags = 0; 994*35935Sbostic ev->ev_count = 0; 995*35935Sbostic /* show this entry is available for use */ 996*35935Sbostic ev->ev_status = EVSTATUS_FREE; 997*35935Sbostic } 998*35935Sbostic 99932633Ssam /* 100032633Ssam * Handler for processing received events. 100132633Ssam */ 100232633Ssam mprintr(unit, list) 100334506Skarels u_char *list; 100432633Ssam { 100532633Ssam register struct tty *tp; 100632633Ssam register struct mpport *mp; 100732633Ssam register struct mpevent *ev; 100832633Ssam struct mblok *mb; 100932633Ssam register int cc; 101032633Ssam register char *cp; 101132633Ssam struct mpsoftc *ms; 101232633Ssam caddr_t ptr; 101332633Ssam char *rcverr; 101432633Ssam int port, i; 101532633Ssam 101632633Ssam ms = &mp_softc[unit]; 101732633Ssam mb = mp_softc[unit].ms_mb; 101832633Ssam for (i = 0; i < MPMAXPORT && (port = *list++) != MPPORT_EOL; i++) { 101932633Ssam tp = &mp_tty[unit*MPCHUNK + port]; 102032633Ssam mp = &mb->mb_port[port]; 102132633Ssam ev = &mp->mp_sendq[mp->mp_nextrcv]; 102232633Ssam while (ev->ev_status & EVSTATUS_DONE) { 1023*35935Sbostic switch(ev->ev_cmd) { 1024*35935Sbostic case EVCMD_STATUS: 102532633Ssam /* 102632633Ssam * Status change, look for carrier changes. 102732633Ssam */ 1028*35935Sbostic switch(ev->ev_opts) { 1029*35935Sbostic case DCDASRT: 1030*35935Sbostic (*linesw[tp->t_line].l_modem)(tp, 1); 1031*35935Sbostic wakeup((caddr_t)&tp->t_canq); 1032*35935Sbostic break; 1033*35935Sbostic case DCDDROP: 1034*35935Sbostic (*linesw[tp->t_line].l_modem)(tp, 0); 1035*35935Sbostic wakeup((caddr_t)&tp->t_canq); 1036*35935Sbostic break; 1037*35935Sbostic case NORBUF: 1038*35935Sbostic case NOEBUF: 103932633Ssam mplog(unit, port, 1040*35935Sbostic "out of receive events", 0); 1041*35935Sbostic break; 1042*35935Sbostic default: 1043*35935Sbostic mplog(unit, port, 104432633Ssam "unexpect status command", 104534506Skarels (int)ev->ev_opts); 1046*35935Sbostic break; 1047*35935Sbostic } 1048*35935Sbostic break; 1049*35935Sbostic case EVCMD_READ: 105032633Ssam /* 1051*35935Sbostic * Process received data. 1052*35935Sbostic */ 1053*35935Sbostic if ((tp->t_state & TS_ISOPEN) == 0) { 1054*35935Sbostic wakeup((caddr_t)&tp->t_rawq); 1055*35935Sbostic break; 1056*35935Sbostic } 1057*35935Sbostic if ((cc = ev->ev_count) == 0) 1058*35935Sbostic break; 1059*35935Sbostic cp = ms->ms_cbuf[port][mp->mp_nextrcv]; 1060*35935Sbostic mppurge(cp, CBSIZE); 1061*35935Sbostic while (cc-- > 0) { 1062*35935Sbostic /* 1063*35935Sbostic * A null character is inserted, 1064*35935Sbostic * potentially when a break or framing 1065*35935Sbostic * error occurs. If we're not in raw 1066*35935Sbostic * mode, substitute the interrupt 1067*35935Sbostic * character. 1068*35935Sbostic */ 1069*35935Sbostic if (*cp == 0 && 1070*35935Sbostic (ev->ev_error == BRKASRT || 1071*35935Sbostic ev->ev_error == FRAMERR)) 1072*35935Sbostic if ((tp->t_flags&RAW) == 0) 1073*35935Sbostic *cp = tp->t_intrc; 1074*35935Sbostic (*linesw[tp->t_line].l_rint)(*cp++, tp); 1075*35935Sbostic } 1076*35935Sbostic /* setup for next read */ 1077*35935Sbostic ptr = (caddr_t)&mp_softc[unit].ms_cbuf[port][mp->mp_nextrcv][0]; 1078*35935Sbostic ev->ev_un.rcvblk = (u_char *)kvtophys(ptr); 1079*35935Sbostic ev->ev_params = (caddr_t) kvtophys(ptr); 1080*35935Sbostic switch(ev->ev_error) { 1081*35935Sbostic case RCVDTA: 1082*35935Sbostic /* Normal (good) rcv data do not 1083*35935Sbostic * report the following they are 1084*35935Sbostic * "normal" errors 1085*35935Sbostic */ 1086*35935Sbostic case FRAMERR: 1087*35935Sbostic /* frame error */ 1088*35935Sbostic case BRKASRT: 1089*35935Sbostic /* Break condition */ 1090*35935Sbostic case PARERR: 1091*35935Sbostic /* parity error */ 1092*35935Sbostic rcverr = (char *)0; 1093*35935Sbostic break; 1094*35935Sbostic case OVRNERR: 1095*35935Sbostic /* Overrun error */ 1096*35935Sbostic rcverr = "overrun error"; 1097*35935Sbostic break; 1098*35935Sbostic case OVFERR: 1099*35935Sbostic /* Overflow error */ 1100*35935Sbostic rcverr = "overflow error"; 1101*35935Sbostic break; 1102*35935Sbostic default: 1103*35935Sbostic rcverr = "undefined rcv error"; 1104*35935Sbostic break; 1105*35935Sbostic } 1106*35935Sbostic if (rcverr != (char *)0) 1107*35935Sbostic mplog(unit, port, rcverr, 1108*35935Sbostic (int)ev->ev_error); 110932633Ssam break; 1110*35935Sbostic default: 1111*35935Sbostic mplog(unit, port, "unexpected command", 1112*35935Sbostic (int)ev->ev_cmd); 111332633Ssam break; 111432633Ssam } 111532633Ssam ev->ev_cmd = 0; 111632633Ssam ev->ev_opts = 0; 111732633Ssam ev->ev_error = 0; 111832633Ssam ev->ev_flags = 0; 1119*35935Sbostic ev->ev_count = 0; 112032633Ssam ev->ev_status = EVSTATUS_GO; /* start next read */ 112132633Ssam adjptr(mp->mp_nextrcv, MPOUTSET); 112232633Ssam ev = &mp->mp_sendq[mp->mp_nextrcv]; 112332633Ssam } 112432633Ssam } 112532633Ssam } 112632633Ssam 112732633Ssam /* 112832633Ssam * Log an mpcc diagnostic. 112932633Ssam */ 113032633Ssam mplog(unit, port, cp, flags) 113132633Ssam char *cp; 113232633Ssam { 113332633Ssam 113432633Ssam if (flags) 113532633Ssam log(LOG_ERR, "mp%d: port%d, %s (%d)\n", 113632633Ssam unit, port, cp, flags); 113732633Ssam else 113832633Ssam log(LOG_ERR, "mp%d: port%d, %s\n", unit, port, cp); 113932633Ssam } 114032633Ssam 114132633Ssam int MPHOSTINT = 1; 114232633Ssam 114332633Ssam mptimeint(mb) 114432633Ssam register struct mblok *mb; 114532633Ssam { 114632633Ssam 114732633Ssam mb->mb_mpintcnt = 0; 114832633Ssam mb->mb_mpintclk = (caddr_t)0; 114932633Ssam *(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2; 115032633Ssam } 115132633Ssam 115232633Ssam /* 115332633Ssam * Interupt mpcc 115432633Ssam */ 115532633Ssam mpintmpcc(mb, port) 115632633Ssam register struct mblok *mb; 115732633Ssam { 115832633Ssam 115932633Ssam mb->mb_intr[port] |= MPSEMA_WORK; 116032633Ssam if (++mb->mb_mpintcnt == MPHOSTINT) { 116132633Ssam mb->mb_mpintcnt = 0; 116232633Ssam *(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2; 116332633Ssam if (mb->mb_mpintclk) { 116434506Skarels untimeout(mptimeint, (caddr_t)mb); 116532633Ssam mb->mb_mpintclk = 0; 116632633Ssam } 116732633Ssam } else { 116832633Ssam if (mb->mb_mpintclk == 0) { 116934506Skarels timeout(mptimeint, (caddr_t)mb, 4); 117032633Ssam mb->mb_mpintclk = (caddr_t)1; 117132633Ssam } 117232633Ssam } 117332633Ssam } 117432633Ssam 117532633Ssam static char *mpherrmsg[] = { 117632633Ssam "", 117732633Ssam "Bus error", /* MPBUSERR */ 117832633Ssam "Address error", /* ADDRERR */ 117932633Ssam "Undefined ecc interrupt", /* UNDECC */ 118032633Ssam "Undefined interrupt", /* UNDINT */ 118132633Ssam "Power failure occurred", /* PWRFL */ 118232633Ssam "Stray transmit done interrupt", /* NOXENTRY */ 118332633Ssam "Two fast timers on one port", /* TWOFTMRS */ 118432633Ssam "Interrupt queue full", /* INTQFULL */ 118532633Ssam "Interrupt queue ack error", /* INTQERR */ 118632633Ssam "Uncorrectable dma parity error", /* CBPERR */ 118732633Ssam "32 port ACAP failed power up", /* ACPDEAD */ 118832633Ssam }; 118932633Ssam #define NHERRS (sizeof (mpherrmsg) / sizeof (mpherrmsg[0])) 119032633Ssam 119132633Ssam mperror(mb, unit) 119232633Ssam register struct mblok *mb; 119332633Ssam int unit; 119432633Ssam { 119532633Ssam register char *cp; 119632633Ssam register int i; 119732633Ssam 119832633Ssam if (mb->mb_softerr) { 119932633Ssam switch (mb->mb_softerr) { 120032633Ssam case DMAPERR: /* dma parity error */ 120132633Ssam cp = "dma parity error"; 120232633Ssam break; 120332633Ssam case ECCERR: 120432633Ssam cp = "local memory ecc error"; 120532633Ssam break; 120632633Ssam default: 120732633Ssam cp = "unknown error"; 120832633Ssam break; 120932633Ssam } 121032633Ssam log(LOG_ERR, "mp%d: soft error, %s", unit, cp); 121132633Ssam mb->mb_softerr = 0; 121232633Ssam } 121332633Ssam if (mb->mb_harderr) { 121432633Ssam if (mb->mb_harderr < NHERRS) 121532633Ssam cp = mpherrmsg[mb->mb_harderr]; 121632633Ssam else 121732633Ssam cp = "unknown error"; 121832633Ssam log(LOG_ERR, "mp%d: hard error, %s", unit, cp); 121932633Ssam if (mb->mb_status == MP_OPOPEN) { 122032633Ssam for (i = 0; i < MPMAXPORT; i++) { 122132633Ssam mpcleanport(mb, i); 122232633Ssam mb->mb_proto[i] = MPPROTO_UNUSED; 122332633Ssam } 122432633Ssam } 122532633Ssam mb->mb_harderr = 0; 122632633Ssam mb->mb_status = 0; 122732633Ssam } 122832633Ssam } 122932633Ssam 123032633Ssam mppurge(addr, cc) 123132633Ssam register caddr_t addr; 123232633Ssam register int cc; 123332633Ssam { 123432633Ssam 123532633Ssam for (; cc >= 0; addr += NBPG, cc -= NBPG) 123632633Ssam mtpr(P1DC, addr); 123732633Ssam } 123832633Ssam 123932633Ssam /* 124032633Ssam * MPCC Download Pseudo-device. 124132633Ssam */ 124232633Ssam char mpdlbuf[MPDLBUFSIZE]; 124332633Ssam int mpdlbusy; /* interlock on download buffer */ 124432633Ssam int mpdlerr; 124532633Ssam 124632633Ssam mpdlopen(dev) 124732633Ssam dev_t dev; 124832633Ssam { 124932633Ssam int unit, mpu; 125032633Ssam struct vba_device *vi; 125132633Ssam 125232633Ssam unit = minor(dev); 125332633Ssam mpu = MPUNIT(unit); 125432633Ssam if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0) 125532633Ssam return (ENODEV); 125632633Ssam return (0); 125732633Ssam } 125832633Ssam 125932633Ssam mpdlwrite(dev, uio) 126032633Ssam dev_t dev; 126132633Ssam struct uio *uio; 126232633Ssam { 126332633Ssam register struct mpsoftc *ms = &mp_softc[MPUNIT(minor(dev))]; 126432633Ssam register struct mpdl *dl; 126532633Ssam int error; 126632633Ssam 126732633Ssam if (ms->ms_mb == 0 || ms->ms_mb->mb_status != MP_DLOPEN) 126832633Ssam return (EFAULT); 126932633Ssam dl = &ms->ms_mb->mb_dl; 127032633Ssam dl->mpdl_count = uio->uio_iov->iov_len; 127134506Skarels dl->mpdl_data = (caddr_t) kvtophys(mpdlbuf); 127234506Skarels if (error = uiomove(mpdlbuf, (int)dl->mpdl_count, UIO_WRITE, uio)) 127332633Ssam return (error); 127432633Ssam uio->uio_resid -= dl->mpdl_count; /* set up return from write */ 127532633Ssam dl->mpdl_cmd = MPDLCMD_NORMAL; 127632633Ssam error = mpdlwait(dl); 127732633Ssam return (error); 127832633Ssam } 127932633Ssam 128032633Ssam mpdlclose(dev) 128132633Ssam dev_t dev; 128232633Ssam { 128332633Ssam register struct mblok *mb = mp_softc[MPUNIT(minor(dev))].ms_mb; 128432633Ssam 128532633Ssam if (mb == 0 || mb->mb_status != MP_DLDONE) { 128632633Ssam mpbogus.status = 0; 128732633Ssam if (mpbogus.mb == mpbogus.mbloks[MPUNIT(minor(dev))]) 128832633Ssam mpdlbusy--; 128932633Ssam return (EEXIST); 129032633Ssam } 129132633Ssam mb->mb_status = MP_OPOPEN; 129232633Ssam mpbogus.status = 0; 129332633Ssam /* set to dead, for board handshake */ 129432633Ssam mb->mb_hostint.imok = MPIMOK_DEAD; 129532633Ssam return (0); 129632633Ssam } 129732633Ssam 129832633Ssam int mpdltimeout(); 129932633Ssam 130034506Skarels /* ARGSUSED */ 130132633Ssam mpdlioctl(dev, cmd, data, flag) 130232633Ssam dev_t dev; 130332633Ssam caddr_t data; 130432633Ssam { 130532633Ssam register struct mblok *mb; 130632633Ssam register struct mpdl *dl; 130734506Skarels int unit, error, s, i; 130832633Ssam 130932633Ssam mb = mp_softc[unit=MPUNIT(minor(dev))].ms_mb; 131032633Ssam if (mb == 0) 131132633Ssam return (EEXIST); 131232633Ssam dl = &mb->mb_dl; 131332633Ssam error = 0; 131432633Ssam switch (cmd) { 131532633Ssam case MPIOPORTMAP: 131632633Ssam bcopy(data, (caddr_t)mb->mb_proto, sizeof (mb->mb_proto)); 131732633Ssam break; 131832633Ssam case MPIOHILO: 131932633Ssam bcopy(data, (caddr_t)&mb->mb_hiport, 2*(sizeof(mb->mb_hiport))); 132032633Ssam break; 132132633Ssam case MPIOENDDL: 132232633Ssam dl->mpdl_count = 0; 132332633Ssam dl->mpdl_data = 0; 132432633Ssam dl->mpdl_cmd = MPIOENDDL&IOCPARM_MASK; 132532633Ssam error = mpdlwait(dl); 132632633Ssam mpccinit(unit); 132732633Ssam mb->mb_status = MP_DLDONE; 132832633Ssam mpdlbusy--; 132932633Ssam break; 133032633Ssam case MPIOENDCODE: 133132633Ssam dl->mpdl_count = 0; 133232633Ssam dl->mpdl_data = 0; 133332633Ssam dl->mpdl_cmd = MPIOENDCODE&IOCPARM_MASK; 133432633Ssam error = mpdlwait(dl); 133532633Ssam break; 133632633Ssam case MPIOASYNCNF: 133732633Ssam bcopy(data, mpdlbuf, sizeof (struct abdcf)); 133834506Skarels dl->mpdl_data = (caddr_t) kvtophys(mpdlbuf); 133932633Ssam dl->mpdl_count = sizeof (struct abdcf); 134032633Ssam dl->mpdl_cmd = MPIOASYNCNF&IOCPARM_MASK; 134132633Ssam error = mpdlwait(dl); 134232633Ssam break; 134332633Ssam case MPIOSTARTDL: 134432633Ssam while (mpdlbusy) 134532633Ssam sleep((caddr_t)&mpdlbusy, PZERO+1); 134632633Ssam mpdlbusy++; 134732633Ssam /* initialize the downloading interface */ 134832633Ssam mpbogus.magic = MPMAGIC; 134932633Ssam mpbogus.mb = mpbogus.mbloks[unit]; 135032633Ssam mpbogus.status = 1; 135132633Ssam dl->mpdl_status = EVSTATUS_FREE; 135232633Ssam dl->mpdl_count = 0; 135332633Ssam dl->mpdl_cmd = 0; 135432633Ssam dl->mpdl_data = (char *) 0; 135532633Ssam mpdlerr = 0; 135632633Ssam mb->mb_magic = MPMAGIC; 135732633Ssam mb->mb_ivec = mp_softc[unit].ms_ivec+1; /* download vector */ 135832633Ssam mb->mb_status = MP_DLPEND; 135932633Ssam mb->mb_diagswitch[0] = 'A'; 136032633Ssam mb->mb_diagswitch[1] = 'P'; 136132633Ssam s = spl8(); 136232633Ssam *(u_short *)mpinfo[unit]->ui_addr = 2; 136334506Skarels timeout(mpdltimeout, (caddr_t)mb, 30*hz); 136432633Ssam sleep((caddr_t)&mb->mb_status, PZERO+1); 136532633Ssam splx(s); 136632633Ssam if (mb->mb_status == MP_DLOPEN) { 136734506Skarels untimeout(mpdltimeout, (caddr_t)mb); 136832633Ssam } else if (mb->mb_status == MP_DLTIME) { 136932633Ssam mpbogus.status = 0; 137032633Ssam error = ETIMEDOUT; 137132633Ssam } else { 137232633Ssam mpbogus.status = 0; 137332633Ssam error = ENXIO; 137432633Ssam log(LOG_ERR, "mp%d: start download: unknown status %x", 137532633Ssam unit, mb->mb_status); 137632633Ssam } 137734506Skarels bzero((caddr_t)mb->mb_port, sizeof (mb->mb_port)); 137832633Ssam break; 137932633Ssam case MPIORESETBOARD: 138032633Ssam s = spl8(); 138132633Ssam if (mb->mb_imokclk) 138232633Ssam mb->mb_imokclk = 0; 138332633Ssam *(u_short *)mpinfo[unit]->ui_addr = 0x100; 138432633Ssam if (mb->mb_status == MP_DLOPEN || mb->mb_status == MP_DLDONE) { 138532633Ssam mpdlerr = MP_DLERROR; 138632633Ssam dl->mpdl_status = EVSTATUS_FREE; 138732633Ssam wakeup((caddr_t)&dl->mpdl_status); 138832633Ssam mpbogus.status = 0; 138932633Ssam } 139032633Ssam for (i = 0; i < MPMAXPORT; i++) { 139132633Ssam if (mb->mb_harderr || mb->mb_softerr) 139232633Ssam mperror(mb, i); 139332633Ssam mpcleanport(mb, i); 139432633Ssam mb->mb_proto[i] = MPPROTO_UNUSED; 139532633Ssam } 139632633Ssam mb->mb_status = 0; 139732633Ssam splx(s); 139832633Ssam break; 139932633Ssam default: 140032633Ssam error = EINVAL; 140132633Ssam break; 140232633Ssam } 140332633Ssam return (error); 140432633Ssam } 140532633Ssam 140632633Ssam mpccinit(unit) 140732633Ssam int unit; 140832633Ssam { 140932633Ssam register struct mblok *mb = mp_softc[unit].ms_mb; 141032633Ssam register struct his *his; 141132633Ssam register int i, j; 141232633Ssam 141332633Ssam mb->mb_status = MP_DLDONE; 141432633Ssam mb->mb_ivec = mp_softc[unit].ms_ivec; 141532633Ssam mb->mb_magic = MPMAGIC; 141632633Ssam /* Init host interface structure */ 141732633Ssam his = &mb->mb_hostint; 141832633Ssam his->semaphore = MPSEMA_AVAILABLE; 141932633Ssam for (i = 0; i < NMPPROTO; i++) 142032633Ssam for (j = 0; j < MPMAXPORT; j++) { 142132633Ssam his->proto[i].inbdone[j] = MPPORT_EOL; 142232633Ssam his->proto[i].outbdone[j] = MPPORT_EOL; 142332633Ssam } 142432633Ssam mb->mb_unit = unit; 142532633Ssam } 142632633Ssam 142732633Ssam mpdlintr(mpcc) 142832633Ssam int mpcc; 142932633Ssam { 143032633Ssam register struct mblok *mb; 143132633Ssam register struct mpdl *dl; 143232633Ssam 143332633Ssam mb = mp_softc[mpcc].ms_mb; 143432633Ssam if (mb == 0) { 143532633Ssam printf("mp%d: stray download interrupt\n", mpcc); 143632633Ssam return; 143732633Ssam } 143832633Ssam dl = &mb->mb_dl; 143932633Ssam switch (mb->mb_status) { 144032633Ssam case MP_DLOPEN: 144132633Ssam if (dl->mpdl_status != EVSTATUS_DONE) 144232633Ssam mpdlerr = MP_DLERROR; 144332633Ssam dl->mpdl_status = EVSTATUS_FREE; 144432633Ssam wakeup((caddr_t)&dl->mpdl_status); 144532633Ssam return; 144632633Ssam case MP_DLPEND: 144732633Ssam mb->mb_status = MP_DLOPEN; 144834506Skarels wakeup((caddr_t)&mb->mb_status); 144932633Ssam /* fall thru... */ 145032633Ssam case MP_DLTIME: 145132633Ssam return; 145232633Ssam case MP_OPOPEN: 145332633Ssam if (mb->mb_imokclk) 145432633Ssam mb->mb_imokclk = 0; 145532633Ssam mb->mb_nointcnt = 0; /* reset no interrupt count */ 145632633Ssam mb->mb_hostint.imok = MPIMOK_DEAD; 145732633Ssam mb->mb_imokclk = (caddr_t)1; 145832633Ssam break; 145932633Ssam default: 146032633Ssam log(LOG_ERR, "mp%d: mpdlintr, status %x\n", 146132633Ssam mpcc, mb->mb_status); 146232633Ssam break; 146332633Ssam } 146432633Ssam } 146532633Ssam 146632633Ssam mpdltimeout(mp) 146732633Ssam struct mblok *mp; 146832633Ssam { 146932633Ssam 147032633Ssam mp->mb_status = MP_DLTIME; 147132633Ssam wakeup((caddr_t)&mp->mb_status); 147232633Ssam } 147332633Ssam 147432633Ssam /* 147532633Ssam * Wait for a transfer to complete or a timeout to occur. 147632633Ssam */ 147732633Ssam mpdlwait(dl) 147832633Ssam register struct mpdl *dl; 147932633Ssam { 148032633Ssam int s, error = 0; 148132633Ssam 148232633Ssam s = spl8(); 148332633Ssam dl->mpdl_status = EVSTATUS_GO; 148432633Ssam while (dl->mpdl_status != EVSTATUS_FREE) { 148532633Ssam sleep((caddr_t)&dl->mpdl_status, PZERO+1); 148632633Ssam if (mpdlerr == MP_DLERROR) 148732633Ssam error = EIO; 148832633Ssam } 148932633Ssam splx(s); 149032633Ssam return (error); 149132633Ssam } 149232633Ssam #endif 1493