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 *
844534Sbostic * %sccs.include.redist.c%
934506Skarels *
10*49755Smarc * @(#)mp.c 7.17 (Berkeley) 05/16/91
1134506Skarels */
1232633Ssam
1332633Ssam #include "mp.h"
1432633Ssam #if NMP > 0
1532633Ssam /*
1632633Ssam * Multi Protocol Communications Controller (MPCC).
1732633Ssam * Asynchronous Terminal Protocol Support.
1832633Ssam */
1945798Sbostic #include "sys/param.h"
2045798Sbostic #include "sys/ioctl.h"
2145798Sbostic #include "sys/tty.h"
2245798Sbostic #include "sys/user.h"
2345798Sbostic #include "sys/map.h"
2445798Sbostic #include "sys/buf.h"
2545798Sbostic #include "sys/conf.h"
2645798Sbostic #include "sys/file.h"
2745798Sbostic #include "sys/errno.h"
2845798Sbostic #include "sys/syslog.h"
2945798Sbostic #include "sys/vmmac.h"
3045798Sbostic #include "sys/kernel.h"
3145798Sbostic #include "sys/clist.h"
3232633Ssam
3345798Sbostic #include "../include/pte.h"
3445798Sbostic #include "../include/mtpr.h"
3534506Skarels
3645798Sbostic #include "../vba/vbavar.h"
3745798Sbostic #include "../vba/mpreg.h"
3832633Ssam
3932633Ssam #define MPCHUNK 16
4032633Ssam #define MPPORT(n) ((n) & 0xf)
4132633Ssam #define MPUNIT(n) ((n) >> 4)
4232633Ssam
4332633Ssam /*
4432633Ssam * Driver information for auto-configuration stuff.
4532633Ssam */
4632633Ssam int mpprobe(), mpattach(), mpintr();
4732633Ssam struct vba_device *mpinfo[NMP];
4832633Ssam long mpstd[] = { 0 };
4932633Ssam struct vba_driver mpdriver =
5032633Ssam { mpprobe, 0, mpattach, 0, mpstd, "mp", mpinfo };
5132633Ssam
5232633Ssam int mpstart();
5337607Smarc int mpparam();
5437607Smarc struct mpevent *mpparam2();
5532633Ssam struct mpevent *mp_getevent();
5632633Ssam
5732633Ssam /*
5832633Ssam * The following structure is needed to deal with mpcc's convoluted
5932633Ssam * method for locating it's mblok structures (hold your stomach).
6032633Ssam * When an mpcc is reset at boot time it searches host memory
6132633Ssam * looking for a string that says ``ThIs Is MpCc''. The mpcc
6232633Ssam * then reads the structure to locate the pointer to it's mblok
6332633Ssam * structure (you can wretch now).
6432633Ssam */
6532633Ssam struct mpbogus {
6632633Ssam char s[12]; /* `ThIs Is MpCc'' */
6732633Ssam u_char status;
6832633Ssam u_char unused;
6932633Ssam u_short magic;
7032633Ssam struct mblok *mb;
7132633Ssam struct mblok *mbloks[NMP]; /* can support at most 16 mpcc's */
7232633Ssam } mpbogus = { 'T','h','I','s',' ','I','s',' ','M','p','C','c' };
7332633Ssam
7432633Ssam /*
7532633Ssam * Software state per unit.
7632633Ssam */
7732633Ssam struct mpsoftc {
7832633Ssam u_int ms_ivec; /* interrupt vector */
7932633Ssam u_int ms_softCAR; /* software carrier for async */
8032633Ssam struct mblok *ms_mb; /* mpcc status area */
8132633Ssam struct vb_buf ms_buf; /* vba resources for ms_mb */
8232633Ssam struct hxmtl ms_hxl[MPMAXPORT];/* host transmit list */
8332633Ssam struct asyncparam ms_async[MPMAXPORT][MPINSET];/* async structs */
8432633Ssam char ms_cbuf[MPMAXPORT][MPOUTSET][CBSIZE];/* input character buffers */
8532633Ssam } mp_softc[NMP];
8632633Ssam
8737607Smarc struct speedtab
8837607Smarc mpspeedtab[] = {
8937607Smarc 9600, M9600, /* baud rate = 9600 */
9037607Smarc 4800, M4800, /* baud rate = 4800 */
9137607Smarc 2400, M2400, /* baud rate = 2400 */
9237607Smarc 1800, M1800, /* baud rate = 1800 */
9337607Smarc 1200, M1200, /* baud rate = 1200 */
9437607Smarc 600, M600, /* baud rate = 600 */
9537607Smarc 300, M300, /* baud rate = 300 */
9637607Smarc 200, M200, /* baud rate = 200 */
9737607Smarc 150, M150, /* baud rate = 150 */
9837607Smarc 134, M134_5, /* baud rate = 134.5 */
9937607Smarc 110, M110, /* baud rate = 110 */
10037607Smarc 75, M75, /* baud rate = 75 */
10137607Smarc 50, M50, /* baud rate = 50 */
10237607Smarc 0, M0, /* baud rate = 0 */
10337607Smarc 2000, M2000, /* baud rate = 2000 */
10437607Smarc 3600, M3600, /* baud rate = 3600 */
10537607Smarc 7200, M7200, /* baud rate = 7200 */
10637607Smarc 19200, M19200, /* baud rate = 19,200 */
10737607Smarc 24000, M24000, /* baud rate = 24,000 */
10837607Smarc 28400, M28400, /* baud rate = 28,400 */
10937607Smarc 37800, M37800, /* baud rate = 37,800 */
11037607Smarc 40300, M40300, /* baud rate = 40,300 */
11137607Smarc 48000, M48000, /* baud rate = 48,000 */
11237607Smarc 52000, M52000, /* baud rate = 52,000 */
11337607Smarc 56800, M56800, /* baud rate = 56,800 */
11437607Smarc EXTA, MEXTA, /* baud rate = Ext A */
11537607Smarc EXTB, MEXTB, /* baud rate = Ext B */
11637607Smarc -1, -1,
11737607Smarc };
11837607Smarc
11932633Ssam struct tty mp_tty[NMP*MPCHUNK];
12032633Ssam #ifndef lint
12132633Ssam int nmp = NMP*MPCHUNK;
12232633Ssam #endif
12332633Ssam
12432633Ssam int ttrstrt();
12532633Ssam
mpprobe(reg,vi)12632633Ssam mpprobe(reg, vi)
12732633Ssam caddr_t reg;
12832633Ssam struct vba_device *vi;
12932633Ssam {
13032633Ssam register int br, cvec;
13132633Ssam register struct mpsoftc *ms;
13232633Ssam
13332633Ssam #ifdef lint
13432633Ssam br = 0; cvec = br; br = cvec;
13532633Ssam mpintr(0);
13634506Skarels mpdlintr(0);
13732633Ssam #endif
13832633Ssam if (badaddr(reg, 2))
13932633Ssam return (0);
14032633Ssam ms = &mp_softc[vi->ui_unit];
14132633Ssam /*
14232633Ssam * Allocate page tables and mblok
14332633Ssam * structure (mblok in non-cached memory).
14432633Ssam */
14532633Ssam if (vbainit(&ms->ms_buf, sizeof (struct mblok), VB_32BIT) == 0) {
14632633Ssam printf("mp%d: vbainit failed\n", vi->ui_unit);
14732633Ssam return (0);
14832633Ssam }
14932633Ssam ms->ms_mb = (struct mblok *)ms->ms_buf.vb_rawbuf;
15032633Ssam ms->ms_ivec = MPINTRBASE + 2*vi->ui_unit; /* XXX */
15132633Ssam br = 0x14, cvec = ms->ms_ivec; /* XXX */
15234287Skarels return (sizeof (*reg));
15332633Ssam }
15432633Ssam
mpattach(vi)15532633Ssam mpattach(vi)
15632633Ssam register struct vba_device *vi;
15732633Ssam {
15832633Ssam register struct mpsoftc *ms = &mp_softc[vi->ui_unit];
15932633Ssam
16032633Ssam ms->ms_softCAR = vi->ui_flags;
16132633Ssam /*
16232633Ssam * Setup pointer to mblok, initialize bogus
16332633Ssam * status block used by mpcc to locate the pointer
16432633Ssam * and then poke the mpcc to get it to search host
16532633Ssam * memory to find mblok pointer.
16632633Ssam */
16732633Ssam mpbogus.mbloks[vi->ui_unit] = (struct mblok *)ms->ms_buf.vb_physbuf;
16832633Ssam *(short *)vi->ui_addr = 0x100; /* magic */
16932633Ssam }
17032633Ssam
17132633Ssam /*
17232633Ssam * Open an mpcc port.
17332633Ssam */
17434506Skarels /* ARGSUSED */
mpopen(dev,mode)17532633Ssam mpopen(dev, mode)
17632633Ssam dev_t dev;
17732633Ssam {
17832633Ssam register struct tty *tp;
17932633Ssam register struct mpsoftc *ms;
18032633Ssam int error, s, port, unit, mpu;
18132633Ssam struct vba_device *vi;
18232633Ssam struct mpport *mp;
18332633Ssam struct mpevent *ev;
18432633Ssam
18532633Ssam unit = minor(dev);
18632633Ssam mpu = MPUNIT(unit);
18732633Ssam if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0)
18832633Ssam return (ENXIO);
18932633Ssam tp = &mp_tty[unit];
19032633Ssam if (tp->t_state & TS_XCLUDE && u.u_uid != 0)
19132633Ssam return (EBUSY);
19232633Ssam ms = &mp_softc[mpu];
19332633Ssam port = MPPORT(unit);
19432633Ssam if (ms->ms_mb->mb_proto[port] != MPPROTO_ASYNC ||
19532633Ssam ms->ms_mb->mb_status != MP_OPOPEN)
19632633Ssam return (ENXIO);
19732633Ssam mp = &ms->ms_mb->mb_port[port]; /* host mpcc struct */
19832633Ssam s = spl8();
19935935Sbostic /*
20035935Sbostic * serialize open and close events
20135935Sbostic */
20237607Smarc while ((mp->mp_flags & MP_PROGRESS) || ((tp->t_state & TS_WOPEN) &&
20340734Skarels !(mode&O_NONBLOCK) && !(tp->t_cflag&CLOCAL)))
20440734Skarels if (error = tsleep((caddr_t)&tp->t_canq, TTIPRI | PCATCH,
20540734Skarels ttopen, 0)) {
20640734Skarels splx(s);
20740734Skarels return (error);
20840734Skarels }
20935935Sbostic restart:
21032633Ssam tp->t_state |= TS_WOPEN;
21132633Ssam tp->t_addr = (caddr_t)ms;
21232633Ssam tp->t_oproc = mpstart;
21337607Smarc tp->t_param = mpparam;
21432633Ssam tp->t_dev = dev;
21534978Sbostic if ((tp->t_state & TS_ISOPEN) == 0) {
21634978Sbostic ttychars(tp);
21734978Sbostic if (tp->t_ispeed == 0) {
21840734Skarels tp->t_ispeed = TTYDEF_SPEED;
21940734Skarels tp->t_ospeed = TTYDEF_SPEED;
22040734Skarels tp->t_iflag = TTYDEF_IFLAG;
22140734Skarels tp->t_oflag = TTYDEF_OFLAG;
22240734Skarels tp->t_lflag = TTYDEF_LFLAG;
22340734Skarels tp->t_cflag = TTYDEF_CFLAG;
22434978Sbostic }
22534978Sbostic /*
22634978Sbostic * Initialize port state: init MPCC interface
22734978Sbostic * structures for port and setup modem control.
22834978Sbostic */
22934978Sbostic error = mpportinit(ms, mp, port);
23034978Sbostic if (error)
23134978Sbostic goto bad;
23237607Smarc ev = mpparam2(tp, &tp->t_termios);
23334978Sbostic if (ev == 0) {
23434978Sbostic error = ENOBUFS;
23534978Sbostic goto bad;
23634978Sbostic }
23735935Sbostic mp->mp_flags |= MP_PROGRESS;
23834978Sbostic mpcmd(ev, EVCMD_OPEN, 0, ms->ms_mb, port);
23935935Sbostic /*
24035935Sbostic * wait for port to start
24135935Sbostic */
24235935Sbostic while (mp->mp_proto != MPPROTO_ASYNC)
24340734Skarels if (error = tsleep((caddr_t)&tp->t_canq,
24440734Skarels TTIPRI | PCATCH, ttopen, 0))
24540734Skarels goto bad;
24637607Smarc ttsetwater(tp);
24735935Sbostic mp->mp_flags &= ~MP_PROGRESS;
24832633Ssam }
24940734Skarels while ((mode&O_NONBLOCK) == 0 && (tp->t_cflag&CLOCAL) == 0 &&
25040734Skarels (tp->t_state & TS_CARR_ON) == 0) {
25144397Smarc if (error = ttysleep(tp, (caddr_t)&tp->t_rawq, TTIPRI | PCATCH,
25244397Smarc ttopen, 0))
25340734Skarels goto bad;
25435935Sbostic /*
25535935Sbostic * a mpclose() might have disabled port. if so restart
25635935Sbostic */
25735935Sbostic if (mp->mp_proto != MPPROTO_ASYNC)
25835935Sbostic goto restart;
25935935Sbostic tp->t_state |= TS_WOPEN;
26035935Sbostic }
26132633Ssam error = (*linesw[tp->t_line].l_open)(dev,tp);
26232633Ssam done:
26332633Ssam splx(s);
26435935Sbostic /*
26535935Sbostic * wakeup those processes waiting for the open to complete
26635935Sbostic */
26732633Ssam wakeup((caddr_t)&tp->t_canq);
26832633Ssam return (error);
26932633Ssam bad:
27032633Ssam tp->t_state &= ~TS_WOPEN;
27132633Ssam goto done;
27232633Ssam }
27332633Ssam
27432633Ssam /*
27532633Ssam * Close an mpcc port.
27632633Ssam */
27734506Skarels /* ARGSUSED */
mpclose(dev,flag)27834506Skarels mpclose(dev, flag)
27932633Ssam dev_t dev;
28032633Ssam {
28132633Ssam register struct tty *tp;
28232633Ssam register struct mpport *mp;
28332633Ssam register struct mpevent *ev;
28440734Skarels int s, port, unit, error = 0;
28532633Ssam struct mblok *mb;
28632633Ssam
28732633Ssam unit = minor(dev);
28832633Ssam tp = &mp_tty[unit];
28932633Ssam port = MPPORT(unit);
29032633Ssam mb = mp_softc[MPUNIT(unit)].ms_mb;
29132633Ssam mp = &mb->mb_port[port];
29232633Ssam s = spl8();
29335935Sbostic if (mp->mp_flags & MP_PROGRESS) {
29432633Ssam if (mp->mp_flags & MP_REMBSY) {
29532633Ssam mp->mp_flags &= ~MP_REMBSY;
29632633Ssam splx(s);
29732633Ssam return (0);
29832633Ssam }
29932633Ssam while (mp->mp_flags & MP_PROGRESS)
30040734Skarels if (error = tsleep((caddr_t)&tp->t_canq,
30140734Skarels TTIPRI | PCATCH, ttclos, 0)) {
30240734Skarels splx(s);
30340734Skarels return (error);
30440734Skarels }
30532633Ssam }
30632633Ssam mp->mp_flags |= MP_PROGRESS;
307*49755Smarc (*linesw[tp->t_line].l_close)(tp, flag);
30835935Sbostic ev = mp_getevent(mp, unit, 1);
30932633Ssam if (ev == 0) {
31034977Sbostic error = ENOBUFS;
31134977Sbostic mp->mp_flags &= ~MP_PROGRESS;
31234977Sbostic goto out;
31332633Ssam }
31434977Sbostic if (tp->t_state & TS_HUPCLS || (tp->t_state & TS_ISOPEN) == 0)
31534977Sbostic mpmodem(unit, MMOD_OFF);
31634977Sbostic else
31734977Sbostic mpmodem(unit, MMOD_ON);
31832633Ssam mpcmd(ev, EVCMD_CLOSE, 0, mb, port);
31940734Skarels error = ttyclose(tp);
32032633Ssam out:
32132633Ssam if (mp->mp_flags & MP_REMBSY)
32232633Ssam mpclean(mb, port);
32335935Sbostic else
32440734Skarels while (mp->mp_flags & MP_PROGRESS && error == 0)
32540734Skarels error = tsleep((caddr_t)&tp->t_canq, TTIPRI | PCATCH,
32640734Skarels ttclos, 0);
32732633Ssam splx(s);
32832633Ssam return (error);
32932633Ssam }
33032633Ssam
33132633Ssam /*
33232633Ssam * Read from an mpcc port.
33332633Ssam */
mpread(dev,uio,flag)33437607Smarc mpread(dev, uio, flag)
33532633Ssam dev_t dev;
33632633Ssam struct uio *uio;
33732633Ssam {
33832633Ssam struct tty *tp;
33932633Ssam
34032633Ssam tp = &mp_tty[minor(dev)];
34137607Smarc return ((*linesw[tp->t_line].l_read)(tp, uio, flag));
34232633Ssam }
34332633Ssam
34432633Ssam /*
34532633Ssam * Write to an mpcc port.
34632633Ssam */
mpwrite(dev,uio,flag)34737607Smarc mpwrite(dev, uio, flag)
34832633Ssam dev_t dev;
34932633Ssam struct uio *uio;
35032633Ssam {
35132633Ssam struct tty *tp;
35232633Ssam
35332633Ssam tp = &mp_tty[minor(dev)];
35437607Smarc return ((*linesw[tp->t_line].l_write)(tp, uio, flag));
35532633Ssam }
35632633Ssam
35732633Ssam /*
35832633Ssam * Ioctl for a mpcc port
35932633Ssam */
mpioctl(dev,cmd,data,flag)36032633Ssam mpioctl(dev, cmd, data, flag)
36132633Ssam dev_t dev;
36232633Ssam caddr_t data;
36332633Ssam {
36432633Ssam register struct tty *tp;
36532633Ssam register struct mpsoftc *ms;
36637607Smarc register struct mpport *mp;
36732633Ssam register struct mpevent *ev;
36832633Ssam int s, port, error, unit;
36932633Ssam struct mblok *mb;
37032633Ssam
37132633Ssam unit = minor(dev);
37232633Ssam tp = &mp_tty[unit];
37332633Ssam ms = &mp_softc[MPUNIT(unit)];
37432633Ssam mb = ms->ms_mb;
37535935Sbostic port = MPPORT(unit);
37635935Sbostic mp = &mb->mb_port[port];
37735935Sbostic if (mp->mp_proto != MPPROTO_ASYNC)
37835935Sbostic return(ENXIO);
37932633Ssam error = (*linesw[tp->t_line].l_ioctl)(tp, cmd, data, flag);
38032633Ssam if (error >= 0)
38132633Ssam return (error);
38232633Ssam error = ttioctl(tp, cmd, data, flag);
38337607Smarc if (error >= 0)
38432633Ssam return (error);
38532633Ssam switch (cmd) {
38632633Ssam case TIOCSBRK: /* send break */
38732633Ssam case TIOCCBRK: /* clear break */
38832633Ssam s = spl8();
38935935Sbostic while (mp->mp_flags & MP_IOCTL) {
39040734Skarels if (error = tsleep((caddr_t)&tp->t_canq,
39140734Skarels TTIPRI | PCATCH, ttyout, 0)) {
39240734Skarels splx(s);
39340734Skarels return (error);
39440734Skarels }
39535935Sbostic if (mp->mp_proto != MPPROTO_ASYNC) {
39635935Sbostic splx(s);
39740734Skarels return (ENXIO);
39835935Sbostic }
39935935Sbostic }
40035935Sbostic ev = mp_getevent(mp, unit, 0);
40135935Sbostic if (ev) {
40235935Sbostic mp->mp_flags |= MP_IOCTL;
40332633Ssam mpcmd(ev, EVCMD_IOCTL,
40435935Sbostic (cmd == TIOCSBRK ? A_BRKON : A_BRKOFF), mb, port);
40535935Sbostic } else
40632633Ssam error = ENOBUFS;
40732633Ssam splx(s);
40832633Ssam break;
40932633Ssam case TIOCSDTR: /* set dtr control line */
41032633Ssam break;
41132633Ssam case TIOCCDTR: /* clear dtr control line */
41232633Ssam break;
41332633Ssam default:
41432633Ssam error = ENOTTY;
41532633Ssam break;
41632633Ssam }
41732633Ssam return (error);
41832633Ssam }
41932633Ssam
42037607Smarc mpparam(tp, t)
42137607Smarc struct tty *tp;
42237607Smarc struct termios *t;
42337607Smarc {
42437607Smarc register struct mpevent *ev;
42537607Smarc int unit = minor(tp->t_dev);
42637607Smarc struct mpsoftc *ms = &mp_softc[MPUNIT(unit)];
42737607Smarc struct mblok *mb = ms->ms_mb;
42837607Smarc
42937607Smarc ev = mpparam2(tp, t);
43037607Smarc if (ev == 0)
43137607Smarc return (ENOBUFS);
43237607Smarc mpcmd(ev, EVCMD_IOCTL, A_CHGALL, mb, MPPORT(unit));
43337607Smarc return (0);
43437607Smarc }
43537607Smarc
43632633Ssam struct mpevent *
mpparam2(tp,t)43737607Smarc mpparam2(tp, t)
43837607Smarc register struct tty *tp;
43937607Smarc struct termios *t;
44032633Ssam {
44132633Ssam register struct mpevent *ev;
44232633Ssam register struct mpport *mp;
44337607Smarc int unit = minor(tp->t_dev);
44432633Ssam struct mblok *mb;
44532633Ssam struct mpsoftc *ms;
44632633Ssam register struct asyncparam *asp;
44737607Smarc int port, speedcode;
44832633Ssam
44932633Ssam ms = &mp_softc[MPUNIT(unit)];
45032633Ssam mb = ms->ms_mb;
45132633Ssam port = MPPORT(unit);
45232633Ssam mp = &mb->mb_port[port];
45335935Sbostic ev = mp_getevent(mp, unit, 0); /* XXX */
45437607Smarc speedcode = ttspeedtab(t->c_ospeed, mpspeedtab);
45537607Smarc if (ev == 0 || speedcode < 0) {
45637607Smarc printf("mp mpunit %d port %d param2 failed ev: %x speed %d, wanted %d\n",
45737607Smarc MPUNIT(unit), port, ev, speedcode, t->c_ospeed);
45837607Smarc return (0); /* XXX */
45937607Smarc }
46032633Ssam /* YUCK */
46132633Ssam asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1];
46237607Smarc asp->ap_xon = t->c_cc[VSTART];
46337607Smarc asp->ap_xoff = t->c_cc[VSTOP];
46437607Smarc if (!(t->c_iflag&IXON) || (asp->ap_xon == _POSIX_VDISABLE) ||
46537607Smarc (asp->ap_xoff == _POSIX_VDISABLE))
46634796Sbostic asp->ap_xena = MPA_DIS;
46734796Sbostic else
46834796Sbostic asp->ap_xena = MPA_ENA;
46937607Smarc asp->ap_xany = ((t->c_iflag & IXANY) ? MPA_ENA : MPA_DIS);
47032633Ssam #ifdef notnow
47137607Smarc if (t->t_cflag&CSIZE) == CS8) {
47232633Ssam #endif
47332633Ssam asp->ap_data = MPCHAR_8;
47432633Ssam asp->ap_parity = MPPAR_NONE;
47532633Ssam #ifdef notnow
47632633Ssam } else {
47732633Ssam asp->ap_data = MPCHAR_7;
47837607Smarc if ((t->c_flags & (EVENP|ODDP)) == ODDP) /* XXX */
47932633Ssam asp->ap_parity = MPPAR_ODD;
48032633Ssam else
48132633Ssam asp->ap_parity = MPPAR_EVEN;
48232633Ssam }
48332633Ssam #endif
48435935Sbostic asp->ap_loop = MPA_DIS; /* disable loopback */
48535935Sbostic asp->ap_rtimer = A_RCVTIM; /* default receive timer */
48637607Smarc if (t->c_ospeed == B110)
48732633Ssam asp->ap_stop = MPSTOP_2;
48832633Ssam else
48932633Ssam asp->ap_stop = MPSTOP_1;
49037607Smarc if (t->c_ospeed == 0) {
49135935Sbostic tp->t_state |= TS_HUPCLS;
49235935Sbostic setm(&asp->ap_modem, 0, DROP);
49335935Sbostic seti(&asp->ap_intena, A_DCD);
49435935Sbostic return (ev);
49535935Sbostic }
49637607Smarc if (t->c_ospeed == EXTA || t->c_ospeed == EXTB)
49732633Ssam asp->ap_baud = M19200;
49832633Ssam else
49937607Smarc asp->ap_baud = speedcode;
50037607Smarc if (1 || ms->ms_softCAR & (1<<port)) /* XXX HARDWIRE FOR NOW */
50132633Ssam setm(&asp->ap_modem, A_DTR, ASSERT);
50232633Ssam else
50332633Ssam setm(&asp->ap_modem, A_DTR, AUTO);
50432633Ssam seti(&asp->ap_intena, A_DCD);
50537607Smarc return(ev);
50632633Ssam }
50732633Ssam
mpstart(tp)50832633Ssam mpstart(tp)
50932633Ssam register struct tty *tp;
51032633Ssam {
51132633Ssam register struct mpevent *ev;
51232633Ssam register struct mpport *mp;
51332633Ssam struct mblok *mb;
51432633Ssam struct mpsoftc *ms;
51532633Ssam int port, unit, xcnt, n, s, i;
51632633Ssam struct hxmtl *hxp;
51732633Ssam struct clist outq;
51832633Ssam
51932633Ssam s = spl8();
52032633Ssam unit = minor(tp->t_dev);
52132633Ssam ms = &mp_softc[MPUNIT(unit)];
52232633Ssam mb = ms->ms_mb;
52332633Ssam port = MPPORT(unit);
52432633Ssam mp = &mb->mb_port[port];
52532633Ssam hxp = &ms->ms_hxl[port];
52632633Ssam xcnt = 0;
52732633Ssam outq = tp->t_outq;
52832633Ssam for (i = 0; i < MPXMIT; i++) {
52932633Ssam if (tp->t_state & (TS_TIMEOUT|TS_BUSY|TS_TTSTOP))
53032633Ssam break;
53137607Smarc if (outq.c_cc <= tp->t_lowat) {
53232633Ssam if (tp->t_state & TS_ASLEEP) {
53332633Ssam tp->t_state &= ~TS_ASLEEP;
53432633Ssam wakeup((caddr_t)&tp->t_outq);
53532633Ssam }
53632633Ssam if (tp->t_wsel) {
53732633Ssam selwakeup(tp->t_wsel, tp->t_state & TS_WCOLL);
53832633Ssam tp->t_wsel = 0;
53932633Ssam tp->t_state &= ~TS_WCOLL;
54032633Ssam }
54132633Ssam }
54232633Ssam if (outq.c_cc == 0)
54332633Ssam break;
54432633Ssam /*
54532633Ssam * If we're not currently busy outputting,
54632633Ssam * and there is data to be output, set up
54732633Ssam * port transmit structure to send to mpcc.
54832633Ssam */
54937607Smarc if (1) /* || tp->t_flags & (RAW|LITOUT)) XXX FIX */
55032633Ssam n = ndqb(&outq, 0);
55132633Ssam else {
55232633Ssam n = ndqb(&outq, 0200);
55332633Ssam if (n == 0) {
55435935Sbostic if (xcnt > 0)
55535935Sbostic break;
55632633Ssam n = getc(&outq);
55732633Ssam timeout(ttrstrt, (caddr_t)tp, (n&0177)+6);
55832633Ssam tp->t_state |= TS_TIMEOUT;
55932633Ssam break;
56032633Ssam }
56132633Ssam }
56234506Skarels hxp->dblock[i] = (caddr_t)kvtophys(outq.c_cf);
56332633Ssam hxp->size[i] = n;
56432633Ssam xcnt++; /* count of xmts to send */
56532633Ssam ndadvance(&outq, n);
56632633Ssam }
56732633Ssam /*
56832633Ssam * If data to send, poke mpcc.
56932633Ssam */
57032633Ssam if (xcnt) {
57135935Sbostic ev = mp_getevent(mp, unit, 0);
57232633Ssam if (ev == 0) {
57332633Ssam tp->t_state &= ~(TS_BUSY|TS_TIMEOUT);
57432633Ssam } else {
57532633Ssam tp->t_state |= TS_BUSY;
57632633Ssam ev->ev_count = xcnt;
57732633Ssam mpcmd(ev, EVCMD_WRITE, 0, mb, MPPORT(unit));
57832633Ssam }
57932633Ssam }
58032633Ssam splx(s);
58132633Ssam }
58232633Ssam
58332633Ssam /*
58432633Ssam * Advance cc bytes from q but don't free memory.
58532633Ssam */
ndadvance(q,cc)58632633Ssam ndadvance(q, cc)
58732633Ssam register struct clist *q;
58832633Ssam register cc;
58932633Ssam {
59032633Ssam register struct cblock *bp;
59132633Ssam char *end;
59232633Ssam int rem, s;
59332633Ssam
59432633Ssam s = spltty();
59532633Ssam if (q->c_cc <= 0)
59632633Ssam goto out;
59732633Ssam while (cc>0 && q->c_cc) {
59832633Ssam bp = (struct cblock *)((int)q->c_cf & ~CROUND);
59932633Ssam if ((int)bp == (((int)q->c_cl-1) & ~CROUND)) {
60032633Ssam end = q->c_cl;
60132633Ssam } else {
60232633Ssam end = (char *)((int)bp + sizeof (struct cblock));
60332633Ssam }
60432633Ssam rem = end - q->c_cf;
60532633Ssam if (cc >= rem) {
60632633Ssam cc -= rem;
60732633Ssam q->c_cc -= rem;
60832633Ssam q->c_cf = bp->c_next->c_info;
60932633Ssam } else {
61032633Ssam q->c_cc -= cc;
61132633Ssam q->c_cf += cc;
61232633Ssam break;
61332633Ssam }
61432633Ssam }
61532633Ssam if (q->c_cc <= 0) {
61632633Ssam q->c_cf = q->c_cl = NULL;
61732633Ssam q->c_cc = 0;
61832633Ssam }
61932633Ssam out:
62032633Ssam splx(s);
62132633Ssam }
62232633Ssam
62332633Ssam /*
62432633Ssam * Stop output on a line, e.g. for ^S/^Q or output flush.
62532633Ssam */
62634506Skarels /* ARGSUSED */
mpstop(tp,rw)62732633Ssam mpstop(tp, rw)
62832633Ssam register struct tty *tp;
62932633Ssam int rw;
63032633Ssam {
63135935Sbostic register struct mpport *mp;
63235935Sbostic register struct mpevent *ev;
63335935Sbostic int unit = minor(tp->t_dev);
63435935Sbostic int port;
63535935Sbostic struct mblok *mb;
63634506Skarels int s;
63732633Ssam
63832633Ssam s = spl8();
63932633Ssam if (tp->t_state & TS_BUSY) {
64035935Sbostic if ((tp->t_state & TS_TTSTOP) == 0) {
64132633Ssam tp->t_state |= TS_FLUSH;
64235935Sbostic port = MPPORT(unit);
64335935Sbostic mb = mp_softc[MPUNIT(unit)].ms_mb;
64435935Sbostic mp = &mb->mb_port[port];
64535935Sbostic ev = mp_getevent(mp, unit, 0);
64635935Sbostic if (ev == 0) {
64735935Sbostic splx(s);
64835935Sbostic return;
64935935Sbostic }
65035935Sbostic mpcmd(ev, EVCMD_WRITE, A_FLUSH, mb, port);
65135935Sbostic }
65232633Ssam }
65332633Ssam splx(s);
65432633Ssam }
65532633Ssam
65632633Ssam /*
65732633Ssam * Initialize an async port's MPCC state.
65832633Ssam */
mpportinit(ms,mp,port)65932633Ssam mpportinit(ms, mp, port)
66032633Ssam register struct mpsoftc *ms;
66132633Ssam register struct mpport *mp;
66232633Ssam int port;
66332633Ssam {
66432633Ssam register struct mpevent *ev;
66532633Ssam register int i;
66632633Ssam caddr_t ptr;
66732633Ssam
66832633Ssam mp->mp_on = mp->mp_off = 0;
66932633Ssam mp->mp_nextrcv = 0;
67032633Ssam mp->mp_flags = 0;
67132633Ssam ev = &mp->mp_recvq[0];
67232633Ssam for (i = 0; ev < &mp->mp_recvq[MPINSET]; ev++, i++) {
67332633Ssam ev->ev_status = EVSTATUS_FREE;
67432633Ssam ev->ev_cmd = 0;
67532633Ssam ev->ev_opts = 0;
67632633Ssam ev->ev_error = 0;
67732633Ssam ev->ev_flags = 0;
67832633Ssam ev->ev_count = 0;
67934506Skarels ev->ev_un.hxl = (struct hxmtl *) kvtophys(&ms->ms_hxl[port]);
68034506Skarels ev->ev_params = (caddr_t) kvtophys(&ms->ms_async[port][i]);
68132633Ssam }
68232633Ssam ev = &mp->mp_sendq[0];
68332633Ssam for (i = 0; ev < &mp->mp_sendq[MPOUTSET]; ev++, i++) {
68432633Ssam /* init so that L2 can't send any events */
68532633Ssam /* to host until open has completed */
68632633Ssam ev->ev_status = EVSTATUS_FREE;
68732633Ssam ev->ev_cmd = 0;
68835935Sbostic ev->ev_opts = 0;
68932633Ssam ev->ev_error = 0;
69032633Ssam ev->ev_flags = 0;
69132633Ssam ev->ev_count = 0;
69232633Ssam ptr = (caddr_t) &ms->ms_cbuf[port][i][0];
69334506Skarels ev->ev_un.rcvblk = (u_char *)kvtophys(ptr);
69434506Skarels ev->ev_params = (caddr_t) kvtophys(ptr);
69532633Ssam }
69632633Ssam return (0);
69732633Ssam }
69832633Ssam
69932633Ssam /*
70032633Ssam * Send an event to an mpcc.
70132633Ssam */
mpcmd(ev,cmd,flags,mb,port)70232633Ssam mpcmd(ev, cmd, flags, mb, port)
70332633Ssam register struct mpevent *ev;
70432633Ssam struct mblok *mb;
70532633Ssam {
70632633Ssam int s;
70732633Ssam
70832633Ssam s = spl8();
70932633Ssam /* move host values to inbound entry */
71032633Ssam ev->ev_cmd = cmd;
71132633Ssam ev->ev_opts = flags;
71232633Ssam /* show event ready for mpcc */
71332633Ssam ev->ev_status = EVSTATUS_GO;
71432633Ssam mpintmpcc(mb, port);
71532633Ssam splx(s);
71632633Ssam }
71732633Ssam
71832633Ssam /*
71932633Ssam * Return the next available event entry for the indicated port.
72032633Ssam */
72132633Ssam struct mpevent *
mp_getevent(mp,unit,cls_req)72235935Sbostic mp_getevent(mp, unit, cls_req)
72332633Ssam register struct mpport *mp;
72432633Ssam int unit;
72535935Sbostic int cls_req;
72632633Ssam {
72732633Ssam register struct mpevent *ev;
72832633Ssam int i, s;
72932633Ssam
73032633Ssam s = spl8();
73132633Ssam ev = &mp->mp_recvq[mp->mp_on];
73232633Ssam if (ev->ev_status != EVSTATUS_FREE)
73332633Ssam goto bad;
73432633Ssam /*
73532633Ssam * If not a close request, verify one extra
73632633Ssam * event is available for closing the port.
73732633Ssam */
73835935Sbostic if (!cls_req) {
73932633Ssam if ((i = mp->mp_on + 1) >= MPINSET)
74032633Ssam i = 0;
74132633Ssam if (mp->mp_recvq[i].ev_status != EVSTATUS_FREE)
74232633Ssam goto bad;
74332633Ssam }
74432633Ssam /* init inbound fields marking this entry as busy */
74535935Sbostic ev->ev_cmd = 0;
74635935Sbostic ev->ev_opts = 0;
74732633Ssam ev->ev_error = 0;
74832633Ssam ev->ev_flags = 0;
74932633Ssam ev->ev_count = 0;
75032633Ssam ev->ev_status = EVSTATUS_BUSY;
75132633Ssam /* adjust pointer to next available inbound entry */
75232633Ssam adjptr(mp->mp_on, MPINSET);
75332633Ssam splx(s);
75432633Ssam return (ev);
75532633Ssam bad:
75632633Ssam splx(s);
75735935Sbostic log(LOG_ERR, "mp%d: port%d, out of events\n",
75835935Sbostic MPUNIT(unit), MPPORT(unit));
75932633Ssam return ((struct mpevent *)0);
76032633Ssam }
76132633Ssam
mpmodem(unit,flag)76232633Ssam mpmodem(unit, flag)
76332633Ssam int unit, flag;
76432633Ssam {
76532633Ssam struct mpsoftc *ms = &mp_softc[MPUNIT(unit)];
76632633Ssam int port = MPPORT(unit);
76732633Ssam register struct mpport *mp;
76832633Ssam register struct asyncparam *asp;
76932633Ssam
77032633Ssam mp = &ms->ms_mb->mb_port[port];
77132633Ssam asp = &ms->ms_async[port][mp->mp_on?mp->mp_on-1:MPINSET-1];
77232633Ssam if (flag == MMOD_ON) {
77337607Smarc if (1 || ms->ms_softCAR & (1 << port))/* XXX HARDWIRE FOR NOW */
77432633Ssam setm(&asp->ap_modem, A_DTR, ASSERT);
77532633Ssam else
77632633Ssam setm(&asp->ap_modem, A_DTR, AUTO);
77732633Ssam seti(&asp->ap_intena, A_DCD);
77832633Ssam } else {
77932633Ssam setm(&asp->ap_modem, 0, DROP);
78032633Ssam seti(&asp->ap_intena, 0);
78132633Ssam }
78232633Ssam }
78332633Ssam
78432633Ssam /*
78532633Ssam * Set up the modem control structure according to mask.
78632633Ssam * Each set bit in the mask means assert the corresponding
78732633Ssam * modem control line, otherwise, it will be dropped.
78832633Ssam * RTS is special since it can either be asserted, dropped
78932633Ssam * or put in auto mode for auto modem control.
79032633Ssam */
79132633Ssam static
setm(mc,mask,rts)79232633Ssam setm(mc, mask, rts)
79332633Ssam register struct mdmctl *mc;
79432633Ssam register int mask;
79532633Ssam {
79632633Ssam
79732633Ssam mc->mc_rngdsr = (mask & A_RNGDSR) ? ASSERT : DROP;
79832633Ssam mc->mc_rate = (mask & A_RATE) ? ASSERT : DROP;
79932633Ssam mc->mc_dcd = (mask & A_DCD) ? ASSERT : DROP;
80032633Ssam mc->mc_sectx = (mask & A_SECTX) ? ASSERT : DROP;
80132633Ssam mc->mc_cts = (mask & A_CTS) ? ASSERT : DROP;
80232633Ssam mc->mc_secrx = (mask & A_SECRX) ? ASSERT : DROP;
80332633Ssam mc->mc_dtr = (mask & A_DTR) ? ASSERT : DROP;
80432633Ssam mc->mc_rts = rts;
80532633Ssam }
80632633Ssam
80732633Ssam /*
80832633Ssam * Set up the status change enable field from mask.
80932633Ssam * When a signal is enabled in this structure and
81032633Ssam * and a change in state on a corresponding modem
81132633Ssam * control line occurs, a status change event will
81232633Ssam * be delivered to the host.
81332633Ssam */
81432633Ssam static
seti(mc,mask)81532633Ssam seti(mc, mask)
81632633Ssam register struct mdmctl *mc;
81732633Ssam register int mask;
81832633Ssam {
81932633Ssam
82032633Ssam mc->mc_rngdsr = (mask & A_RNGDSR) ? MDM_ON : MDM_OFF;
82132633Ssam mc->mc_rate = (mask & A_RATE) ? MDM_ON : MDM_OFF;
82232633Ssam mc->mc_dcd = (mask & A_DCD) ? MDM_ON : MDM_OFF;
82332633Ssam mc->mc_sectx = (mask & A_SECTX) ? MDM_ON : MDM_OFF;
82432633Ssam mc->mc_cts = (mask & A_CTS) ? MDM_ON : MDM_OFF;
82532633Ssam mc->mc_secrx = (mask & A_SECRX) ? MDM_ON : MDM_OFF;
82632633Ssam mc->mc_dtr = (mask & A_DTR) ? MDM_ON : MDM_OFF;
82732633Ssam mc->mc_rts = (mask & A_RTS) ? MDM_ON : MDM_OFF;
82832633Ssam }
82932633Ssam
83032633Ssam mpcleanport(mb, port)
83132633Ssam struct mblok *mb;
83232633Ssam int port;
83332633Ssam {
83432633Ssam register struct mpport *mp;
83532633Ssam register struct tty *tp;
83632633Ssam
83732633Ssam mp = &mb->mb_port[port];
83832633Ssam if (mp->mp_proto == MPPROTO_ASYNC) {
83932633Ssam mp->mp_flags = MP_REMBSY;
84034506Skarels /* signal loss of carrier and close */
84132633Ssam tp = &mp_tty[mb->mb_unit*MPCHUNK+port];
84232633Ssam ttyflush(tp, FREAD|FWRITE);
84334506Skarels (void) (*linesw[tp->t_line].l_modem)(tp, 0);
84432633Ssam }
84532633Ssam }
84632633Ssam
mpclean(mb,port)84732633Ssam mpclean(mb, port)
84832633Ssam register struct mblok *mb;
84932633Ssam int port;
85032633Ssam {
85132633Ssam register struct mpport *mp;
85232633Ssam register struct mpevent *ev;
85332633Ssam register int i;
85434506Skarels u_char list[2];
85532633Ssam int unit;
85632633Ssam
85732633Ssam mp = &mb->mb_port[port];
85832633Ssam unit = mb->mb_unit;
85932633Ssam for (i = mp->mp_off; i != mp->mp_on; i = (i+1 % MPINSET)) {
86032633Ssam ev = &mp->mp_recvq[i];
86132633Ssam ev->ev_error = ENXIO;
86232633Ssam ev->ev_status = EVSTATUS_DONE;
86332633Ssam }
86432633Ssam list[0] = port, list[1] = MPPORT_EOL;
86532633Ssam mpxintr(unit, list);
86632633Ssam mprintr(unit, list);
86732633Ssam /* Clear async for port */
86832633Ssam mp->mp_proto = MPPROTO_UNUSED;
86932633Ssam mp->mp_flags = 0;
87032633Ssam mp->mp_on = 0;
87132633Ssam mp->mp_off = 0;
87232633Ssam mp->mp_nextrcv = 0;
87332633Ssam
87432633Ssam mp_tty[unit*MPCHUNK + port].t_state = 0;
87532633Ssam for (ev = &mp->mp_sendq[0]; ev < &mp->mp_sendq[MPOUTSET]; ev++) {
87632633Ssam ev->ev_status = EVSTATUS_FREE;
87732633Ssam ev->ev_cmd = 0;
87832633Ssam ev->ev_error = 0;
87932633Ssam ev->ev_un.rcvblk = 0;
88032633Ssam ev->ev_params = 0;
88132633Ssam }
88232633Ssam for (ev = &mp->mp_recvq[0]; ev < &mp->mp_recvq[MPINSET]; ev++) {
88332633Ssam ev->ev_status = EVSTATUS_FREE;
88432633Ssam ev->ev_cmd = 0;
88532633Ssam ev->ev_error = 0;
88632633Ssam ev->ev_params = 0;
88732633Ssam }
88832633Ssam }
88932633Ssam
89032633Ssam /*
89132633Ssam * MPCC interrupt handler.
89232633Ssam */
mpintr(mpcc)89332633Ssam mpintr(mpcc)
89432633Ssam int mpcc;
89532633Ssam {
89632633Ssam register struct mblok *mb;
89732633Ssam register struct his *his;
89832633Ssam
89932633Ssam mb = mp_softc[mpcc].ms_mb;
90032633Ssam if (mb == 0) {
90132633Ssam printf("mp%d: stray interrupt\n", mpcc);
90232633Ssam return;
90332633Ssam }
90432633Ssam his = &mb->mb_hostint;
90532633Ssam his->semaphore &= ~MPSEMA_AVAILABLE;
90632633Ssam /*
90732633Ssam * Check for events to be processed.
90832633Ssam */
90932633Ssam if (his->proto[MPPROTO_ASYNC].outbdone[0] != MPPORT_EOL)
91032633Ssam mprintr(mpcc, his->proto[MPPROTO_ASYNC].outbdone);
91132633Ssam if (his->proto[MPPROTO_ASYNC].inbdone[0] != MPPORT_EOL)
91232633Ssam mpxintr(mpcc, his->proto[MPPROTO_ASYNC].inbdone);
91332633Ssam if (mb->mb_harderr || mb->mb_softerr)
91432633Ssam mperror(mb, mpcc);
91532633Ssam his->semaphore |= MPSEMA_AVAILABLE;
91632633Ssam }
91732633Ssam
91832633Ssam /*
91932633Ssam * Handler for processing completion of transmitted events.
92032633Ssam */
mpxintr(unit,list)92132633Ssam mpxintr(unit, list)
92234506Skarels register u_char *list;
92332633Ssam {
92432633Ssam register struct mpport *mp;
92532633Ssam register struct mpevent *ev;
92632633Ssam register struct mblok *mb;
92732633Ssam register struct tty *tp;
92832633Ssam register struct asyncparam *ap;
92932633Ssam struct mpsoftc *ms;
93032633Ssam int port, i, j;
93135935Sbostic # define nextevent(mp) &mp->mp_recvq[mp->mp_off]
93232633Ssam
93332633Ssam ms = &mp_softc[unit];
93432633Ssam mb = mp_softc[unit].ms_mb;
93532633Ssam for (j = 0; j < MPMAXPORT && ((port = *list++) != MPPORT_EOL); j++) {
93632633Ssam /*
93732633Ssam * Process each completed entry in the inbound queue.
93832633Ssam */
93932633Ssam mp = &mb->mb_port[port];
94032633Ssam tp = &mp_tty[unit*MPCHUNK + port];
94132633Ssam ev = nextevent(mp);
94235935Sbostic for (; ev->ev_status & EVSTATUS_DONE; ev = nextevent(mp)) {
94332633Ssam /* YUCK */
94432633Ssam ap = &ms->ms_async[port][mp->mp_off];
94534506Skarels mppurge((caddr_t)ap, (int)sizeof (*ap));
94632633Ssam switch (ev->ev_cmd) {
94732633Ssam case EVCMD_OPEN:
94832633Ssam /*
94932633Ssam * Open completion, start all reads and
95032633Ssam * assert modem status information.
95132633Ssam */
95232633Ssam for (i = 0; i < MPOUTSET; i++)
95332633Ssam mp->mp_sendq[i].ev_status = EVSTATUS_GO;
95432633Ssam (*linesw[tp->t_line].l_modem)
95532633Ssam (tp, ap->ap_modem.mc_dcd == ASSERT);
95635935Sbostic mp_freein(ev);
95735935Sbostic adjptr(mp->mp_off, MPINSET);
95835935Sbostic mp->mp_proto = MPPROTO_ASYNC; /* XXX */
95935935Sbostic wakeup((caddr_t)&tp->t_canq);
96032633Ssam break;
96132633Ssam case EVCMD_CLOSE:
96232633Ssam /*
96332633Ssam * Close completion, flush all pending
96432633Ssam * transmissions, free resources, and
96532633Ssam * cleanup mpcc port state.
96632633Ssam */
96732633Ssam for (i = 0; i < MPOUTSET; i++) {
96832633Ssam mp->mp_sendq[i].ev_status =
96932633Ssam EVSTATUS_FREE;
97032633Ssam mp->mp_sendq[i].ev_un.rcvblk = 0;
97132633Ssam mp->mp_sendq[i].ev_params = 0;
97232633Ssam }
97335935Sbostic mp_freein(ev);
97435935Sbostic adjptr(mp->mp_off, MPINSET);
97535935Sbostic tp->t_state &= ~(TS_CARR_ON|TS_BUSY|TS_FLUSH);
97632633Ssam mp->mp_on = mp->mp_off = mp->mp_nextrcv = 0;
97732633Ssam mp->mp_flags &= ~MP_PROGRESS;
97832633Ssam mp->mp_proto = MPPROTO_UNUSED;
97935055Skarels wakeup((caddr_t)&tp->t_canq);
98035935Sbostic break;
98132633Ssam case EVCMD_IOCTL:
98235935Sbostic mp_freein(ev);
98335935Sbostic adjptr(mp->mp_off, MPINSET);
98435935Sbostic mp->mp_flags &= ~MP_IOCTL;
98535935Sbostic wakeup((caddr_t)&tp->t_canq);
98632633Ssam break;
98732633Ssam case EVCMD_WRITE:
98832633Ssam /*
98932633Ssam * Transmission completed, update tty
99032633Ssam * state and restart output.
99132633Ssam */
99235935Sbostic if (ev->ev_opts != A_FLUSH) {
99335935Sbostic tp->t_state &= ~TS_BUSY;
99435935Sbostic if (tp->t_state & TS_FLUSH)
99535935Sbostic tp->t_state &= ~TS_FLUSH;
99635935Sbostic else {
99735935Sbostic register int cc = 0, n;
99835935Sbostic struct hxmtl *hxp;
99932633Ssam
100035935Sbostic hxp = &ms->ms_hxl[port];
100135935Sbostic for (n=0;n < ev->ev_count; n++)
100235935Sbostic cc += hxp->size[n];
100335935Sbostic ndflush(&tp->t_outq, cc);
100435935Sbostic }
100532633Ssam }
100632633Ssam switch (ev->ev_error) {
100732633Ssam case A_SIZERR: /*# error in xmt data size */
100832633Ssam mplog(unit, port, A_XSIZE, 0);
100932633Ssam break;
101032633Ssam case A_NXBERR: /*# no more xmt evt buffers */
101132633Ssam mplog(unit, port, A_NOXBUF, 0);
101232633Ssam break;
101332633Ssam }
101435935Sbostic mp_freein(ev);
101535935Sbostic adjptr(mp->mp_off, MPINSET);
101632633Ssam mpstart(tp);
101732633Ssam break;
101832633Ssam default:
101934506Skarels mplog(unit, port, A_INVCMD, (int)ev->ev_cmd);
102035935Sbostic mp_freein(ev);
102135935Sbostic adjptr(mp->mp_off, MPINSET);
102232633Ssam break;
102332633Ssam }
102432633Ssam }
102532633Ssam }
102635935Sbostic #undef nextevent
102732633Ssam }
102832633Ssam
mp_freein(ev)102935935Sbostic mp_freein(ev)
103035935Sbostic register struct mpevent *ev;
103135935Sbostic {
103235935Sbostic /* re-init all values in this entry */
103335935Sbostic ev->ev_cmd = 0;
103435935Sbostic ev->ev_opts = 0;
103535935Sbostic ev->ev_error = 0;
103635935Sbostic ev->ev_flags = 0;
103735935Sbostic ev->ev_count = 0;
103835935Sbostic /* show this entry is available for use */
103935935Sbostic ev->ev_status = EVSTATUS_FREE;
104035935Sbostic }
104135935Sbostic
104232633Ssam /*
104332633Ssam * Handler for processing received events.
104432633Ssam */
mprintr(unit,list)104532633Ssam mprintr(unit, list)
104634506Skarels u_char *list;
104732633Ssam {
104832633Ssam register struct tty *tp;
104932633Ssam register struct mpport *mp;
105032633Ssam register struct mpevent *ev;
105132633Ssam struct mblok *mb;
105232633Ssam register int cc;
105332633Ssam register char *cp;
105432633Ssam struct mpsoftc *ms;
105532633Ssam caddr_t ptr;
105632633Ssam char *rcverr;
105732633Ssam int port, i;
105832633Ssam
105932633Ssam ms = &mp_softc[unit];
106032633Ssam mb = mp_softc[unit].ms_mb;
106132633Ssam for (i = 0; i < MPMAXPORT && (port = *list++) != MPPORT_EOL; i++) {
106232633Ssam tp = &mp_tty[unit*MPCHUNK + port];
106332633Ssam mp = &mb->mb_port[port];
106432633Ssam ev = &mp->mp_sendq[mp->mp_nextrcv];
106532633Ssam while (ev->ev_status & EVSTATUS_DONE) {
106635935Sbostic switch(ev->ev_cmd) {
106735935Sbostic case EVCMD_STATUS:
106832633Ssam /*
106932633Ssam * Status change, look for carrier changes.
107032633Ssam */
107135935Sbostic switch(ev->ev_opts) {
107235935Sbostic case DCDASRT:
107335935Sbostic (*linesw[tp->t_line].l_modem)(tp, 1);
107435935Sbostic wakeup((caddr_t)&tp->t_canq);
107535935Sbostic break;
107635935Sbostic case DCDDROP:
107735935Sbostic (*linesw[tp->t_line].l_modem)(tp, 0);
107835935Sbostic wakeup((caddr_t)&tp->t_canq);
107935935Sbostic break;
108035935Sbostic case NORBUF:
108135935Sbostic case NOEBUF:
108232633Ssam mplog(unit, port,
108335935Sbostic "out of receive events", 0);
108435935Sbostic break;
108535935Sbostic default:
108635935Sbostic mplog(unit, port,
108732633Ssam "unexpect status command",
108834506Skarels (int)ev->ev_opts);
108935935Sbostic break;
109035935Sbostic }
109135935Sbostic break;
109235935Sbostic case EVCMD_READ:
109332633Ssam /*
109435935Sbostic * Process received data.
109535935Sbostic */
109635935Sbostic if ((tp->t_state & TS_ISOPEN) == 0) {
109735935Sbostic wakeup((caddr_t)&tp->t_rawq);
109835935Sbostic break;
109935935Sbostic }
110035935Sbostic if ((cc = ev->ev_count) == 0)
110135935Sbostic break;
110235935Sbostic cp = ms->ms_cbuf[port][mp->mp_nextrcv];
110335935Sbostic mppurge(cp, CBSIZE);
110435935Sbostic while (cc-- > 0) {
110535935Sbostic /*
110635935Sbostic * A null character is inserted,
110735935Sbostic * potentially when a break or framing
110835935Sbostic * error occurs. If we're not in raw
110935935Sbostic * mode, substitute the interrupt
111035935Sbostic * character.
111135935Sbostic */
111237607Smarc /*** XXX - FIXUP ***/
111335935Sbostic if (*cp == 0 &&
111435935Sbostic (ev->ev_error == BRKASRT ||
111535935Sbostic ev->ev_error == FRAMERR))
111635935Sbostic if ((tp->t_flags&RAW) == 0)
111737607Smarc ;
111837607Smarc /* XXX was break */
111935935Sbostic (*linesw[tp->t_line].l_rint)(*cp++, tp);
112035935Sbostic }
112135935Sbostic /* setup for next read */
112235935Sbostic ptr = (caddr_t)&mp_softc[unit].ms_cbuf[port][mp->mp_nextrcv][0];
112335935Sbostic ev->ev_un.rcvblk = (u_char *)kvtophys(ptr);
112435935Sbostic ev->ev_params = (caddr_t) kvtophys(ptr);
112535935Sbostic switch(ev->ev_error) {
112635935Sbostic case RCVDTA:
112735935Sbostic /* Normal (good) rcv data do not
112835935Sbostic * report the following they are
112935935Sbostic * "normal" errors
113035935Sbostic */
113135935Sbostic case FRAMERR:
113235935Sbostic /* frame error */
113335935Sbostic case BRKASRT:
113435935Sbostic /* Break condition */
113535935Sbostic case PARERR:
113635935Sbostic /* parity error */
113735935Sbostic rcverr = (char *)0;
113835935Sbostic break;
113935935Sbostic case OVRNERR:
114035935Sbostic /* Overrun error */
114135935Sbostic rcverr = "overrun error";
114235935Sbostic break;
114335935Sbostic case OVFERR:
114435935Sbostic /* Overflow error */
114535935Sbostic rcverr = "overflow error";
114635935Sbostic break;
114735935Sbostic default:
114835935Sbostic rcverr = "undefined rcv error";
114935935Sbostic break;
115035935Sbostic }
115135935Sbostic if (rcverr != (char *)0)
115235935Sbostic mplog(unit, port, rcverr,
115335935Sbostic (int)ev->ev_error);
115432633Ssam break;
115535935Sbostic default:
115635935Sbostic mplog(unit, port, "unexpected command",
115735935Sbostic (int)ev->ev_cmd);
115832633Ssam break;
115932633Ssam }
116032633Ssam ev->ev_cmd = 0;
116132633Ssam ev->ev_opts = 0;
116232633Ssam ev->ev_error = 0;
116332633Ssam ev->ev_flags = 0;
116435935Sbostic ev->ev_count = 0;
116532633Ssam ev->ev_status = EVSTATUS_GO; /* start next read */
116632633Ssam adjptr(mp->mp_nextrcv, MPOUTSET);
116732633Ssam ev = &mp->mp_sendq[mp->mp_nextrcv];
116832633Ssam }
116932633Ssam }
117032633Ssam }
117132633Ssam
117232633Ssam /*
117332633Ssam * Log an mpcc diagnostic.
117432633Ssam */
mplog(unit,port,cp,flags)117532633Ssam mplog(unit, port, cp, flags)
117632633Ssam char *cp;
117732633Ssam {
117832633Ssam
117932633Ssam if (flags)
118032633Ssam log(LOG_ERR, "mp%d: port%d, %s (%d)\n",
118132633Ssam unit, port, cp, flags);
118232633Ssam else
118332633Ssam log(LOG_ERR, "mp%d: port%d, %s\n", unit, port, cp);
118432633Ssam }
118532633Ssam
118632633Ssam int MPHOSTINT = 1;
118732633Ssam
mptimeint(mb)118832633Ssam mptimeint(mb)
118932633Ssam register struct mblok *mb;
119032633Ssam {
119132633Ssam
119232633Ssam mb->mb_mpintcnt = 0;
119332633Ssam mb->mb_mpintclk = (caddr_t)0;
119432633Ssam *(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2;
119532633Ssam }
119632633Ssam
119732633Ssam /*
119832633Ssam * Interupt mpcc
119932633Ssam */
mpintmpcc(mb,port)120032633Ssam mpintmpcc(mb, port)
120132633Ssam register struct mblok *mb;
120232633Ssam {
120332633Ssam
120432633Ssam mb->mb_intr[port] |= MPSEMA_WORK;
120532633Ssam if (++mb->mb_mpintcnt == MPHOSTINT) {
120632633Ssam mb->mb_mpintcnt = 0;
120732633Ssam *(u_short *)mpinfo[mb->mb_unit]->ui_addr = 2;
120832633Ssam if (mb->mb_mpintclk) {
120934506Skarels untimeout(mptimeint, (caddr_t)mb);
121032633Ssam mb->mb_mpintclk = 0;
121132633Ssam }
121232633Ssam } else {
121332633Ssam if (mb->mb_mpintclk == 0) {
121434506Skarels timeout(mptimeint, (caddr_t)mb, 4);
121532633Ssam mb->mb_mpintclk = (caddr_t)1;
121632633Ssam }
121732633Ssam }
121832633Ssam }
121932633Ssam
122032633Ssam static char *mpherrmsg[] = {
122132633Ssam "",
122232633Ssam "Bus error", /* MPBUSERR */
122332633Ssam "Address error", /* ADDRERR */
122432633Ssam "Undefined ecc interrupt", /* UNDECC */
122532633Ssam "Undefined interrupt", /* UNDINT */
122632633Ssam "Power failure occurred", /* PWRFL */
122732633Ssam "Stray transmit done interrupt", /* NOXENTRY */
122832633Ssam "Two fast timers on one port", /* TWOFTMRS */
122932633Ssam "Interrupt queue full", /* INTQFULL */
123032633Ssam "Interrupt queue ack error", /* INTQERR */
123132633Ssam "Uncorrectable dma parity error", /* CBPERR */
123232633Ssam "32 port ACAP failed power up", /* ACPDEAD */
123332633Ssam };
123432633Ssam #define NHERRS (sizeof (mpherrmsg) / sizeof (mpherrmsg[0]))
123532633Ssam
mperror(mb,unit)123632633Ssam mperror(mb, unit)
123732633Ssam register struct mblok *mb;
123832633Ssam int unit;
123932633Ssam {
124032633Ssam register char *cp;
124132633Ssam register int i;
124232633Ssam
124332633Ssam if (mb->mb_softerr) {
124432633Ssam switch (mb->mb_softerr) {
124532633Ssam case DMAPERR: /* dma parity error */
124632633Ssam cp = "dma parity error";
124732633Ssam break;
124832633Ssam case ECCERR:
124932633Ssam cp = "local memory ecc error";
125032633Ssam break;
125132633Ssam default:
125232633Ssam cp = "unknown error";
125332633Ssam break;
125432633Ssam }
125532633Ssam log(LOG_ERR, "mp%d: soft error, %s", unit, cp);
125632633Ssam mb->mb_softerr = 0;
125732633Ssam }
125832633Ssam if (mb->mb_harderr) {
125932633Ssam if (mb->mb_harderr < NHERRS)
126032633Ssam cp = mpherrmsg[mb->mb_harderr];
126132633Ssam else
126232633Ssam cp = "unknown error";
126332633Ssam log(LOG_ERR, "mp%d: hard error, %s", unit, cp);
126432633Ssam if (mb->mb_status == MP_OPOPEN) {
126532633Ssam for (i = 0; i < MPMAXPORT; i++) {
126632633Ssam mpcleanport(mb, i);
126732633Ssam mb->mb_proto[i] = MPPROTO_UNUSED;
126832633Ssam }
126932633Ssam }
127032633Ssam mb->mb_harderr = 0;
127132633Ssam mb->mb_status = 0;
127232633Ssam }
127332633Ssam }
127432633Ssam
mppurge(addr,cc)127532633Ssam mppurge(addr, cc)
127632633Ssam register caddr_t addr;
127732633Ssam register int cc;
127832633Ssam {
127932633Ssam
128032633Ssam for (; cc >= 0; addr += NBPG, cc -= NBPG)
128132633Ssam mtpr(P1DC, addr);
128232633Ssam }
128332633Ssam
128432633Ssam /*
128532633Ssam * MPCC Download Pseudo-device.
128632633Ssam */
128732633Ssam char mpdlbuf[MPDLBUFSIZE];
128832633Ssam int mpdlbusy; /* interlock on download buffer */
128932633Ssam int mpdlerr;
129032633Ssam
mpdlopen(dev)129132633Ssam mpdlopen(dev)
129232633Ssam dev_t dev;
129332633Ssam {
129432633Ssam int unit, mpu;
129532633Ssam struct vba_device *vi;
129632633Ssam
129732633Ssam unit = minor(dev);
129832633Ssam mpu = MPUNIT(unit);
129932633Ssam if (mpu >= NMP || (vi = mpinfo[mpu]) == 0 || vi->ui_alive == 0)
130032633Ssam return (ENODEV);
130132633Ssam return (0);
130232633Ssam }
130332633Ssam
mpdlwrite(dev,uio)130432633Ssam mpdlwrite(dev, uio)
130532633Ssam dev_t dev;
130632633Ssam struct uio *uio;
130732633Ssam {
130832633Ssam register struct mpsoftc *ms = &mp_softc[MPUNIT(minor(dev))];
130932633Ssam register struct mpdl *dl;
131032633Ssam int error;
131132633Ssam
131232633Ssam if (ms->ms_mb == 0 || ms->ms_mb->mb_status != MP_DLOPEN)
131332633Ssam return (EFAULT);
131432633Ssam dl = &ms->ms_mb->mb_dl;
131532633Ssam dl->mpdl_count = uio->uio_iov->iov_len;
131634506Skarels dl->mpdl_data = (caddr_t) kvtophys(mpdlbuf);
131737751Smckusick if (error = uiomove(mpdlbuf, (int)dl->mpdl_count, uio))
131832633Ssam return (error);
131932633Ssam uio->uio_resid -= dl->mpdl_count; /* set up return from write */
132032633Ssam dl->mpdl_cmd = MPDLCMD_NORMAL;
132132633Ssam error = mpdlwait(dl);
132232633Ssam return (error);
132332633Ssam }
132432633Ssam
mpdlclose(dev)132532633Ssam mpdlclose(dev)
132632633Ssam dev_t dev;
132732633Ssam {
132832633Ssam register struct mblok *mb = mp_softc[MPUNIT(minor(dev))].ms_mb;
132932633Ssam
133032633Ssam if (mb == 0 || mb->mb_status != MP_DLDONE) {
133132633Ssam mpbogus.status = 0;
133232633Ssam if (mpbogus.mb == mpbogus.mbloks[MPUNIT(minor(dev))])
133332633Ssam mpdlbusy--;
133432633Ssam return (EEXIST);
133532633Ssam }
133632633Ssam mb->mb_status = MP_OPOPEN;
133732633Ssam mpbogus.status = 0;
133832633Ssam /* set to dead, for board handshake */
133932633Ssam mb->mb_hostint.imok = MPIMOK_DEAD;
134032633Ssam return (0);
134132633Ssam }
134232633Ssam
134334506Skarels /* ARGSUSED */
mpdlioctl(dev,cmd,data,flag)134432633Ssam mpdlioctl(dev, cmd, data, flag)
134532633Ssam dev_t dev;
134632633Ssam caddr_t data;
134732633Ssam {
134832633Ssam register struct mblok *mb;
134932633Ssam register struct mpdl *dl;
135040734Skarels int unit, error = 0, s, i;
135132633Ssam
135232633Ssam mb = mp_softc[unit=MPUNIT(minor(dev))].ms_mb;
135332633Ssam if (mb == 0)
135440734Skarels return (EEXIST);
135532633Ssam dl = &mb->mb_dl;
135632633Ssam error = 0;
135732633Ssam switch (cmd) {
135832633Ssam case MPIOPORTMAP:
135932633Ssam bcopy(data, (caddr_t)mb->mb_proto, sizeof (mb->mb_proto));
136032633Ssam break;
136132633Ssam case MPIOHILO:
136232633Ssam bcopy(data, (caddr_t)&mb->mb_hiport, 2*(sizeof(mb->mb_hiport)));
136332633Ssam break;
136432633Ssam case MPIOENDDL:
136532633Ssam dl->mpdl_count = 0;
136632633Ssam dl->mpdl_data = 0;
136732633Ssam dl->mpdl_cmd = MPIOENDDL&IOCPARM_MASK;
136832633Ssam error = mpdlwait(dl);
136932633Ssam mpccinit(unit);
137032633Ssam mb->mb_status = MP_DLDONE;
137132633Ssam mpdlbusy--;
137232633Ssam break;
137332633Ssam case MPIOENDCODE:
137432633Ssam dl->mpdl_count = 0;
137532633Ssam dl->mpdl_data = 0;
137632633Ssam dl->mpdl_cmd = MPIOENDCODE&IOCPARM_MASK;
137732633Ssam error = mpdlwait(dl);
137832633Ssam break;
137932633Ssam case MPIOASYNCNF:
138032633Ssam bcopy(data, mpdlbuf, sizeof (struct abdcf));
138134506Skarels dl->mpdl_data = (caddr_t) kvtophys(mpdlbuf);
138232633Ssam dl->mpdl_count = sizeof (struct abdcf);
138332633Ssam dl->mpdl_cmd = MPIOASYNCNF&IOCPARM_MASK;
138432633Ssam error = mpdlwait(dl);
138532633Ssam break;
138632633Ssam case MPIOSTARTDL:
138740734Skarels s = spl8();
138832633Ssam while (mpdlbusy)
138940734Skarels if (error = tsleep((caddr_t)&mpdlbusy,
139040734Skarels (PZERO+1) | PCATCH, devioc, 0))
139140734Skarels break;
139240734Skarels splx(s);
139340734Skarels if (error)
139440734Skarels break;
139532633Ssam mpdlbusy++;
139632633Ssam /* initialize the downloading interface */
139732633Ssam mpbogus.magic = MPMAGIC;
139832633Ssam mpbogus.mb = mpbogus.mbloks[unit];
139932633Ssam mpbogus.status = 1;
140032633Ssam dl->mpdl_status = EVSTATUS_FREE;
140132633Ssam dl->mpdl_count = 0;
140232633Ssam dl->mpdl_cmd = 0;
140332633Ssam dl->mpdl_data = (char *) 0;
140432633Ssam mpdlerr = 0;
140532633Ssam mb->mb_magic = MPMAGIC;
140632633Ssam mb->mb_ivec = mp_softc[unit].ms_ivec+1; /* download vector */
140732633Ssam mb->mb_status = MP_DLPEND;
140832633Ssam mb->mb_diagswitch[0] = 'A';
140932633Ssam mb->mb_diagswitch[1] = 'P';
141032633Ssam s = spl8();
141132633Ssam *(u_short *)mpinfo[unit]->ui_addr = 2;
141240734Skarels error = tsleep((caddr_t)&mb->mb_status, (PZERO+1) | PCATCH,
141340734Skarels devio, 30*hz);
141432633Ssam splx(s);
141540734Skarels if (error == EWOULDBLOCK)
141632633Ssam error = ETIMEDOUT;
141740734Skarels if (error)
141832633Ssam mpbogus.status = 0;
141934506Skarels bzero((caddr_t)mb->mb_port, sizeof (mb->mb_port));
142032633Ssam break;
142132633Ssam case MPIORESETBOARD:
142232633Ssam s = spl8();
142332633Ssam if (mb->mb_imokclk)
142432633Ssam mb->mb_imokclk = 0;
142532633Ssam *(u_short *)mpinfo[unit]->ui_addr = 0x100;
142632633Ssam if (mb->mb_status == MP_DLOPEN || mb->mb_status == MP_DLDONE) {
142732633Ssam mpdlerr = MP_DLERROR;
142832633Ssam dl->mpdl_status = EVSTATUS_FREE;
142932633Ssam wakeup((caddr_t)&dl->mpdl_status);
143032633Ssam mpbogus.status = 0;
143132633Ssam }
143232633Ssam for (i = 0; i < MPMAXPORT; i++) {
143332633Ssam if (mb->mb_harderr || mb->mb_softerr)
143432633Ssam mperror(mb, i);
143532633Ssam mpcleanport(mb, i);
143632633Ssam mb->mb_proto[i] = MPPROTO_UNUSED;
143732633Ssam }
143832633Ssam mb->mb_status = 0;
143932633Ssam splx(s);
144032633Ssam break;
144132633Ssam default:
144232633Ssam error = EINVAL;
144332633Ssam break;
144432633Ssam }
144532633Ssam return (error);
144632633Ssam }
144732633Ssam
mpccinit(unit)144832633Ssam mpccinit(unit)
144932633Ssam int unit;
145032633Ssam {
145132633Ssam register struct mblok *mb = mp_softc[unit].ms_mb;
145232633Ssam register struct his *his;
145332633Ssam register int i, j;
145432633Ssam
145532633Ssam mb->mb_status = MP_DLDONE;
145632633Ssam mb->mb_ivec = mp_softc[unit].ms_ivec;
145732633Ssam mb->mb_magic = MPMAGIC;
145832633Ssam /* Init host interface structure */
145932633Ssam his = &mb->mb_hostint;
146032633Ssam his->semaphore = MPSEMA_AVAILABLE;
146132633Ssam for (i = 0; i < NMPPROTO; i++)
146232633Ssam for (j = 0; j < MPMAXPORT; j++) {
146332633Ssam his->proto[i].inbdone[j] = MPPORT_EOL;
146432633Ssam his->proto[i].outbdone[j] = MPPORT_EOL;
146532633Ssam }
146632633Ssam mb->mb_unit = unit;
146732633Ssam }
146832633Ssam
mpdlintr(mpcc)146932633Ssam mpdlintr(mpcc)
147032633Ssam int mpcc;
147132633Ssam {
147232633Ssam register struct mblok *mb;
147332633Ssam register struct mpdl *dl;
147432633Ssam
147532633Ssam mb = mp_softc[mpcc].ms_mb;
147632633Ssam if (mb == 0) {
147732633Ssam printf("mp%d: stray download interrupt\n", mpcc);
147832633Ssam return;
147932633Ssam }
148032633Ssam dl = &mb->mb_dl;
148132633Ssam switch (mb->mb_status) {
148232633Ssam case MP_DLOPEN:
148332633Ssam if (dl->mpdl_status != EVSTATUS_DONE)
148432633Ssam mpdlerr = MP_DLERROR;
148532633Ssam dl->mpdl_status = EVSTATUS_FREE;
148632633Ssam wakeup((caddr_t)&dl->mpdl_status);
148732633Ssam return;
148832633Ssam case MP_DLPEND:
148932633Ssam mb->mb_status = MP_DLOPEN;
149034506Skarels wakeup((caddr_t)&mb->mb_status);
149132633Ssam /* fall thru... */
149232633Ssam case MP_DLTIME:
149332633Ssam return;
149432633Ssam case MP_OPOPEN:
149532633Ssam if (mb->mb_imokclk)
149632633Ssam mb->mb_imokclk = 0;
149732633Ssam mb->mb_nointcnt = 0; /* reset no interrupt count */
149832633Ssam mb->mb_hostint.imok = MPIMOK_DEAD;
149932633Ssam mb->mb_imokclk = (caddr_t)1;
150032633Ssam break;
150132633Ssam default:
150232633Ssam log(LOG_ERR, "mp%d: mpdlintr, status %x\n",
150332633Ssam mpcc, mb->mb_status);
150432633Ssam break;
150532633Ssam }
150632633Ssam }
150732633Ssam
150832633Ssam /*
150932633Ssam * Wait for a transfer to complete or a timeout to occur.
151032633Ssam */
mpdlwait(dl)151132633Ssam mpdlwait(dl)
151232633Ssam register struct mpdl *dl;
151332633Ssam {
151432633Ssam int s, error = 0;
151532633Ssam
151632633Ssam s = spl8();
151732633Ssam dl->mpdl_status = EVSTATUS_GO;
151832633Ssam while (dl->mpdl_status != EVSTATUS_FREE) {
151940734Skarels error = tsleep((caddr_t)&dl->mpdl_status, (PZERO+1) | PCATCH,
152040734Skarels devout, 0);
152132633Ssam if (mpdlerr == MP_DLERROR)
152232633Ssam error = EIO;
152340734Skarels if (error)
152440734Skarels break;
152532633Ssam }
152632633Ssam splx(s);
152732633Ssam return (error);
152832633Ssam }
152932633Ssam #endif
1530