intermediate i/o buffer must be physically contiguous for DMA
[unix-history] / usr / src / sys / tahoe / vba / ik.c
CommitLineData
7ea0073c 1/* ik.c 1.5 86/12/23 */
6fcffbdd
SL
2
3#include "ik.h"
4#if NIK > 0
5/*
6 * PS300/IKON DR-11W Device Driver.
7 */
8#include "param.h"
9#include "buf.h"
10#include "cmap.h"
11#include "conf.h"
12#include "dir.h"
13#include "dkstat.h"
14#include "map.h"
15#include "systm.h"
16#include "user.h"
17#include "vmmac.h"
18#include "proc.h"
19#include "uio.h"
20#include "kernel.h"
e1111228 21#include "syslog.h"
6fcffbdd
SL
22
23#include "../tahoe/mtpr.h"
24#include "../tahoe/pte.h"
25
26#include "../tahoevba/vbavar.h"
27#include "../tahoevba/ikreg.h"
28#include "../tahoevba/psreg.h"
29#include "../tahoevba/psproto.h"
30
93d65f53
SL
31int ikprobe(), ikattach(), iktimer();
32struct vba_device *ikinfo[NIK];
33long ikstd[] = { 0 };
34struct vba_driver ikdriver = { ikprobe, 0, ikattach, 0, ikstd, "ik", ikinfo };
6fcffbdd 35
93d65f53 36#define splik() spl4()
6fcffbdd
SL
37/*
38 * Devices are organized in pairs with the odd valued
39 * device being used for ``diagnostic'' purposes. That
40 * is diagnostic devices don't get auto-attach'd and
41 * detach'd on open-close.
42 */
93d65f53
SL
43#define IKUNIT(dev) (minor(dev) >> 1)
44#define IKDIAG(dev) (minor(dev) & 01) /* is a diagnostic unit */
45
46struct ik_softc {
47 uid_t is_uid; /* uid of open processes */
48 u_short is_timeout; /* current timeout (seconds) */
49 u_short is_error; /* internal error codes */
50 u_short is_flags;
51#define IKF_ATTACHED 0x1 /* unit is attached (not used yet) */
52 union {
53 u_short w[2];
54 u_long l;
55 } is_nameaddr; /* address of last symbol lookup */
7ea0073c 56 caddr_t is_buf[PS_MAXDMA];/* i/o buffer XXX */
6fcffbdd
SL
57} ik_softc[NIK];
58
93d65f53
SL
59struct buf iktab[NIK]; /* unit command queue headers */
60struct buf rikbuf[NIK]; /* buffers for read/write operations */
61struct buf cikbuf[NIK]; /* buffers for control operations */
6fcffbdd
SL
62
63/* buf overlay definitions */
93d65f53 64#define b_command b_resid
6fcffbdd 65
93d65f53
SL
66int ikdiotimo = PS_DIOTIMO; /* dio polling timeout */
67int iktimeout = PS_TIMEOUT; /* attention/dma timeout (in hz) */
6fcffbdd
SL
68
69ikprobe(reg, vi)
93d65f53 70 caddr_t reg;
6fcffbdd
SL
71 struct vba_device *vi;
72{
93d65f53 73 register int br, cvec; /* r12, r11 */
6fcffbdd
SL
74 register struct ikdevice *ik;
75
9d61b7ff
SL
76#ifdef lint
77 br = 0; cvec = br; br = cvec;
78 ikintr(0);
79#endif
93d65f53
SL
80 if (badaddr(reg, 2))
81 return (0);
6fcffbdd
SL
82 ik = (struct ikdevice *)reg;
83 ik->ik_vec = --vi->ui_hd->vh_lastiv;
93d65f53 84 /*
7ea0073c
SL
85 * Use extended non-privileged address modifier
86 * to avoid address overlap with 24-bit devices.
93d65f53
SL
87 */
88 ik->ik_mod = 0xf1; /* address modifier */
89 /*
90 * Try and reset the PS300. Since this
91 * won't work if it's powered off, we
92 * can't use sucess/failure to decide
93 * if the device is present.
94 */
6fcffbdd 95 br = 0;
93d65f53
SL
96 (void) psreset(ik, IKCSR_IENA);
97 if (br == 0) /* XXX */
6fcffbdd 98 br = 0x18, cvec = ik->ik_vec; /* XXX */
93d65f53 99 return (sizeof (struct ikdevice));
6fcffbdd
SL
100}
101
102/*
103 * Perform a ``hard'' reset.
104 */
105psreset(ik, iena)
93d65f53 106 register struct ikdevice *ik;
6fcffbdd
SL
107{
108
93d65f53
SL
109 ik->ik_csr = IKCSR_MCLR|iena;
110 DELAY(10000);
111 ik->ik_csr = IKCSR_FNC3|iena;
112 if (!iena)
113 return (dioread(ik) == PS_RESET);
114 return (1);
6fcffbdd
SL
115}
116
117ikattach(vi)
93d65f53 118 struct vba_device *vi;
6fcffbdd 119{
6fcffbdd 120
93d65f53 121 ik_softc[vi->ui_unit].is_uid = -1;
6fcffbdd
SL
122}
123
124/*
125 * Open a PS300 and attach. We allow multiple
126 * processes with the same uid to share a unit.
127 */
128/*ARGSUSED*/
129ikopen(dev, flag)
93d65f53
SL
130 dev_t dev;
131 int flag;
6fcffbdd 132{
93d65f53
SL
133 register int unit = IKUNIT(dev);
134 register struct ik_softc *sc;
135 struct vba_device *vi;
136 struct ikdevice *ik;
137 int reset;
138
139 if (unit >= NIK || (vi = ikinfo[unit]) == 0 || vi->ui_alive == 0)
140 return (ENXIO);
141 sc = &ik_softc[unit];
9d61b7ff 142 if (sc->is_uid != (uid_t)-1 && sc->is_uid != u.u_uid)
93d65f53 143 return (EBUSY);
9d61b7ff 144 if (sc->is_uid == (uid_t)-1) {
93d65f53 145 sc->is_timeout = 0;
9d61b7ff 146 timeout(iktimer, (caddr_t)unit, hz);
93d65f53
SL
147 /*
148 * Perform PS300 attach for first process.
149 */
150 if (!IKDIAG(dev)) {
151 reset = 0;
152 again:
153 if (ikcommand(dev, PS_ATTACH, 1)) {
154 /*
155 * If attach fails, perform a hard
156 * reset once, then retry the command.
157 */
158 ik = (struct ikdevice *)ikinfo[unit]->ui_addr;
159 if (!reset++ && psreset(ik, 0))
160 goto again;
9d61b7ff 161 untimeout(iktimer, (caddr_t)unit);
93d65f53
SL
162 return (EIO);
163 }
164 }
165 sc->is_uid = u.u_uid;
166 }
167 return (0);
6fcffbdd
SL
168}
169
170/*ARGSUSED*/
171ikclose(dev, flag)
93d65f53
SL
172 dev_t dev;
173 int flag;
6fcffbdd 174{
93d65f53 175 int unit = IKUNIT(dev);
6fcffbdd
SL
176 register struct ik_softc *sc = &ik_softc[unit];
177
93d65f53
SL
178 if (!IKDIAG(dev))
179 (void) ikcommand(dev, PS_DETACH, 1); /* auto detach */
180 sc->is_uid = -1;
9d61b7ff 181 untimeout(iktimer, (caddr_t)unit);
6fcffbdd
SL
182}
183
184ikread(dev, uio)
93d65f53
SL
185 dev_t dev;
186 struct uio *uio;
6fcffbdd
SL
187{
188
93d65f53 189 return (ikrw(dev, uio, B_READ));
6fcffbdd
SL
190}
191
192ikwrite(dev, uio)
93d65f53
SL
193 dev_t dev;
194 struct uio *uio;
6fcffbdd
SL
195{
196
93d65f53 197 return (ikrw(dev, uio, B_WRITE));
6fcffbdd
SL
198}
199
200/*
201 * Take read/write request and perform physical i/o
202 * transaction with PS300. This involves constructing
203 * a physical i/o request vector based on the uio
204 * vector, performing the dma, and, finally, moving
205 * the data to it's final destination (because of CCI
206 * VERSAbus bogosities).
207 */
208ikrw(dev, uio, rw)
93d65f53
SL
209 dev_t dev;
210 register struct uio *uio;
211 int rw;
6fcffbdd 212{
93d65f53
SL
213 int error, unit = IKUNIT(dev), s, wrcmd;
214 register struct buf *bp;
215 register struct iovec *iov;
216 register struct psalist *ap;
217 struct ik_softc *sc = &ik_softc[unit];
218
219 if (unit >= NIK)
220 return (ENXIO);
221 bp = &rikbuf[unit];
222 error = 0, iov = uio->uio_iov, wrcmd = PS_WRPHY;
223 for (; !error && uio->uio_iovcnt; iov++, uio->uio_iovcnt--) {
224 /*
225 * Hack way to set PS300 address w/o doing an lseek
226 * and specify write physical w/ refresh synchronization.
227 */
228 if (iov->iov_len == 0) {
229 if ((int)iov->iov_base&PSIO_SYNC)
230 wrcmd = PS_WRPHY_SYNC;
231 uio->uio_offset = (int)iov->iov_base & ~PSIO_SYNC;
232 continue;
233 }
234 if (iov->iov_len > PS_MAXDMA) {
235 sc->is_error = PSERROR_INVALBC, error = EINVAL;
236 continue;
237 }
238 if ((int)uio->uio_offset&01) {
239 sc->is_error = PSERROR_BADADDR, error = EINVAL;
240 continue;
241 }
242 s = splbio();
243 while (bp->b_flags&B_BUSY) {
244 bp->b_flags |= B_WANTED;
245 sleep((caddr_t)bp, PRIBIO+1);
246 }
247 splx(s);
248 bp->b_flags = B_BUSY | rw;
249 /*
250 * Construct address descriptor in buffer.
251 */
252 ap = (struct psalist *)sc->is_buf;
253 ap->nblocks = 1;
254 /* work-around dr300 word swapping */
255 ap->addr[0] = uio->uio_offset & 0xffff;
256 ap->addr[1] = uio->uio_offset >> 16;
257 ap->wc = (iov->iov_len + 1) >> 1;
258 if (rw == B_WRITE) {
259 error = copyin(iov->iov_base, (caddr_t)&ap[1],
9d61b7ff 260 (unsigned)iov->iov_len);
93d65f53
SL
261 if (!error)
262 error = ikcommand(dev, wrcmd,
263 iov->iov_len + sizeof (*ap));
264 } else {
265 caddr_t cp;
266 int len;
267
268 error = ikcommand(dev, PS_RDPHY, sizeof (*ap));
269 cp = (caddr_t)&ap[1], len = iov->iov_len;
270 for (; len > 0; len -= NBPG, cp += NBPG)
271 mtpr(P1DC, cp);
272 if (!error)
273 error = copyout((caddr_t)&ap[1], iov->iov_base,
9d61b7ff 274 (unsigned)iov->iov_len);
93d65f53
SL
275 }
276 (void) splbio();
277 if (bp->b_flags&B_WANTED)
278 wakeup((caddr_t)bp);
279 splx(s);
280 uio->uio_resid -= iov->iov_len;
281 uio->uio_offset += iov->iov_len;
282 bp->b_flags &= ~(B_BUSY|B_WANTED);
283 }
284 return (error);
6fcffbdd
SL
285}
286
287/*
288 * Perform a PS300 command.
289 */
290ikcommand(dev, com, count)
93d65f53
SL
291 dev_t dev;
292 int com, count;
6fcffbdd 293{
93d65f53
SL
294 register struct buf *bp;
295 register int s;
296
297 bp = &cikbuf[IKUNIT(dev)];
298 s = splik();
299 while (bp->b_flags&B_BUSY) {
300 if (bp->b_flags&B_DONE)
301 break;
302 bp->b_flags |= B_WANTED;
303 sleep((caddr_t)bp, PRIBIO);
304 }
305 bp->b_flags = B_BUSY|B_READ;
306 splx(s);
307 bp->b_dev = dev;
308 bp->b_command = com;
309 bp->b_bcount = count;
310 ikstrategy(bp);
311 biowait(bp);
312 if (bp->b_flags&B_WANTED)
313 wakeup((caddr_t)bp);
314 bp->b_flags &= B_ERROR;
315 return (geterror(bp));
6fcffbdd
SL
316}
317
318/*
319 * Physio strategy routine
320 */
321ikstrategy(bp)
93d65f53 322 register struct buf *bp;
6fcffbdd 323{
93d65f53
SL
324 register struct buf *dp;
325
326 /*
327 * Put request at end of controller queue.
328 */
329 dp = &iktab[IKUNIT(bp->b_dev)];
330 bp->av_forw = NULL;
331 (void) splik();
332 if (dp->b_actf != NULL) {
333 dp->b_actl->av_forw = bp;
334 dp->b_actl = bp;
335 } else
336 dp->b_actf = dp->b_actl = bp;
337 if (!dp->b_active)
338 ikstart(dp);
339 (void) spl0();
6fcffbdd
SL
340}
341
342/*
343 * Start the next command on the controller's queue.
344 */
345ikstart(dp)
93d65f53 346 register struct buf *dp;
6fcffbdd 347{
93d65f53
SL
348 register struct buf *bp;
349 register struct ikdevice *ik;
350 register struct ik_softc *sc;
93d65f53
SL
351 u_short bc, csr;
352 u_int addr;
353 int unit;
6fcffbdd
SL
354
355loop:
93d65f53
SL
356 /*
357 * Pull a request off the controller queue
358 */
359 if ((bp = dp->b_actf) == NULL) {
360 dp->b_active = 0;
361 return;
362 }
363 /*
364 * Mark controller busy and process this request.
365 */
366 dp->b_active = 1;
367 unit = IKUNIT(bp->b_dev);
368 sc = &ik_softc[unit];
369 ik = (struct ikdevice *)ikinfo[unit]->ui_addr;
9d61b7ff 370 switch ((int)bp->b_command) {
93d65f53
SL
371
372 case PS_ATTACH: /* logical unit attach */
373 case PS_DETACH: /* logical unit detach */
374 case PS_LOOKUP: /* name lookup */
375 case PS_RDPHY: /* physical i/o read */
376 case PS_WRPHY: /* physical i/o write */
377 case PS_WRPHY_SYNC: /* physical i/o write w/ sync */
378 /*
379 * Handshake command and, optionally,
380 * byte count and byte swap flag.
381 */
9d61b7ff 382 if (sc->is_error = diowrite(ik, (u_short)bp->b_command))
93d65f53
SL
383 goto bad;
384 if (bp->b_command < PS_DETACH) {
9d61b7ff 385 if (sc->is_error = diowrite(ik, (u_short)bp->b_bcount))
93d65f53 386 goto bad;
9d61b7ff 387 if (sc->is_error = diowrite(ik, (u_short)0 /* !swab */))
93d65f53
SL
388 goto bad;
389 }
390 /*
391 * Set timeout and wait for an attention interrupt.
392 */
393 sc->is_timeout = iktimeout;
394 return;
395
396 case PS_DMAOUT: /* dma data host->PS300 */
397 bc = bp->b_bcount;
398 csr = IKCSR_CYCLE;
399 break;
400
401 case PS_DMAIN: /* dma data PS300->host */
402 bc = bp->b_bcount;
403 csr = IKCSR_CYCLE|IKCSR_FNC1;
404 break;
405
406 default:
407 log(LOG_ERR, "ik%d: bad cmd %x\n", unit, bp->b_command);
408 sc->is_error = PSERROR_BADCMD;
409 goto bad;
410 }
411 /* initiate dma transfer */
9d61b7ff 412 addr = vtoph((struct proc *)0, (unsigned)sc->is_buf);
93d65f53
SL
413 ik->ik_bahi = addr >> 17;
414 ik->ik_balo = (addr >> 1) & 0xffff;
415 ik->ik_wc = ((bc + 1) >> 1) - 1; /* round & convert */
416 ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF;
417 sc->is_timeout = iktimeout;
418 ik->ik_csr = IKCSR_IENA|IKCSR_GO|csr;
419 return;
6fcffbdd 420bad:
93d65f53
SL
421 bp->b_flags |= B_ERROR;
422 dp->b_actf = bp->av_forw; /* remove from queue */
423 biodone(bp);
424 goto loop;
6fcffbdd
SL
425}
426
427#define FETCHWORD(i) { \
93d65f53
SL
428 v = dioread(ik); \
429 if (v == -1) { \
430 sc->is_error = PSERROR_NAMETIMO; \
431 goto bad; \
432 } \
433 sc->is_nameaddr.w[i] = v; \
6fcffbdd
SL
434}
435
436/*
437 * Process a device interrupt.
438 */
439ikintr(ikon)
93d65f53 440 int ikon;
6fcffbdd 441{
93d65f53
SL
442 register struct ikdevice *ik;
443 register struct buf *bp, *dp;
444 struct ik_softc *sc;
445 register u_short data;
9d61b7ff 446 int v;
93d65f53
SL
447
448 /* should go by controller, but for now... */
449 if (ikinfo[ikon] == 0)
450 return;
451 ik = (struct ikdevice *)ikinfo[ikon]->ui_addr;
452 /*
453 * Discard all non-attention interrupts. The
454 * interrupts we're throwing away should all be
455 * associated with DMA completion.
456 */
457 data = ik->ik_data;
458 if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) != IKCSR_ATTF) {
459 ik->ik_pulse = IKPULSE_RATTF|IKPULSE_RDMAF|IKPULSE_SIENA;
460 return;
461 }
462 /*
463 * Fetch attention code immediately.
464 */
465 ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1;
466 ik->ik_pulse = IKPULSE_FNC2;
467 /*
468 * Get device and block structures, and a pointer
469 * to the vba_device for the device. We receive an
470 * unsolicited interrupt whenever the PS300 is power
471 * cycled (so ignore it in that case).
472 */
473 dp = &iktab[ikon];
474 if ((bp = dp->b_actf) == NULL) {
475 if (PS_CODE(data) != PS_RESET) /* power failure */
476 log(LOG_WARNING, "ik%d: spurious interrupt, code %x\n",
477 ikon, data);
478 goto enable;
479 }
480 sc = &ik_softc[IKUNIT(bp->b_dev)];
481 sc->is_timeout = 0; /* disable timer */
482 switch (PS_CODE(data)) {
483
484 case PS_LOOKUP: /* name lookup */
485 if (data == PS_LOOKUP) { /* dma name */
486 bp->b_command = PS_DMAOUT;
487 goto opcont;
488 }
489 if (data == PS_DMAOK(PS_LOOKUP)) {
490 /* reenable interrupt and wait for address */
491 sc->is_timeout = iktimeout;
492 goto enable;
493 }
494 /*
495 * Address should be present, extract it one
496 * word at a time from the PS300 (yech).
497 */
498 if (data != PS_ADROK(PS_LOOKUP))
499 goto bad;
500 FETCHWORD(0);
501 FETCHWORD(1);
502 goto opdone;
503
504 case PS_WRPHY_SYNC: /* physical i/o write w/ sync */
505 if (data == PS_WRPHY_SYNC) { /* start dma transfer */
506 bp->b_command = PS_DMAOUT;
507 goto opcont;
508 }
509 if (data != PS_DMAOK(PS_WRPHY_SYNC))
510 goto bad;
511 goto opdone;
512
513 case PS_WRPHY: /* physical i/o write */
514 if (data == PS_WRPHY) { /* start dma transfer */
515 bp->b_command = PS_DMAOUT;
516 goto opcont;
517 }
518 if (data != PS_DMAOK(PS_WRPHY))
519 goto bad;
520 goto opdone;
521
522 case PS_ATTACH: /* attach unit */
523 case PS_DETACH: /* detach unit */
524 case PS_ABORT: /* abort code from ps300 */
525 if (data != bp->b_command)
526 goto bad;
527 goto opdone;
528
529 case PS_RDPHY: /* physical i/o read */
530 if (data == PS_RDPHY) { /* dma address list */
531 bp->b_command = PS_DMAOUT;
532 goto opcont;
533 }
534 if (data == PS_ADROK(PS_RDPHY)) {
535 /* collect read byte count and start dma */
536 bp->b_bcount = dioread(ik);
537 if (bp->b_bcount == -1)
538 goto bad;
539 bp->b_command = PS_DMAIN;
540 goto opcont;
541 }
542 if (data == PS_DMAOK(PS_RDPHY))
543 goto opdone;
544 goto bad;
545 }
6fcffbdd 546bad:
93d65f53
SL
547 sc->is_error = data;
548 bp->b_flags |= B_ERROR;
6fcffbdd 549opdone:
93d65f53
SL
550 dp->b_actf = bp->av_forw; /* remove from queue */
551 biodone(bp);
6fcffbdd 552opcont:
93d65f53 553 ikstart(dp);
6fcffbdd 554enable:
93d65f53 555 ik->ik_pulse = IKPULSE_SIENA; /* explicitly reenable */
6fcffbdd
SL
556}
557
558/*
559 * Watchdog timer.
560 */
561iktimer(unit)
93d65f53 562 int unit;
6fcffbdd 563{
93d65f53
SL
564 register struct ik_softc *sc = &ik_softc[unit];
565
566 if (sc->is_timeout && --sc->is_timeout == 0) {
567 register struct buf *dp, *bp;
568 int s;
569
570 log(LOG_ERR, "ik%d: timeout\n", unit);
571 s = splik();
572 /* should abort current command */
573 dp = &iktab[unit];
574 if (bp = dp->b_actf) {
575 sc->is_error = PSERROR_CMDTIMO;
576 bp->b_flags |= B_ERROR;
577 dp->b_actf = bp->av_forw; /* remove from queue */
578 biodone(bp);
579 ikstart(dp);
580 }
581 splx(s);
582 }
9d61b7ff 583 timeout(iktimer, (caddr_t)unit, hz);
6fcffbdd
SL
584}
585
586/*
587 * Handshake read from DR300.
588 */
589dioread(ik)
93d65f53 590 register struct ikdevice *ik;
6fcffbdd 591{
9d61b7ff 592 register int t;
93d65f53
SL
593 u_short data;
594
9d61b7ff 595 for (t = ikdiotimo; t > 0; t--)
93d65f53
SL
596 if ((ik->ik_csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF) {
597 data = ik->ik_data;
598 ik->ik_csr = IKCSR_RATTF|IKCSR_RDMAF|IKCSR_FNC1;
599 ik->ik_pulse = IKPULSE_FNC2;
600 return (data);
601 }
602 return (-1);
6fcffbdd
SL
603}
604
605/*
606 * Handshake write to DR300.
607 *
608 * Interrupts are enabled before completing the work
609 * so the caller should either be at splik or be
610 * prepared to take the interrupt immediately.
611 */
612diowrite(ik, v)
93d65f53
SL
613 register struct ikdevice *ik;
614 u_short v;
6fcffbdd 615{
9d61b7ff 616 register int t;
93d65f53 617 register u_short csr;
6fcffbdd
SL
618
619top:
93d65f53
SL
620 /*
621 * Deposit data and generate dr300 attention
622 */
623 ik->ik_data = v;
624 ik->ik_csr = IKCSR_RDMAF|IKCSR_RATTF;
625 ik->ik_pulse = IKPULSE_FNC2;
9d61b7ff 626 for (t = ikdiotimo; t > 0; t--) {
93d65f53
SL
627 csr = ik->ik_csr;
628#define IKCSR_DONE (IKCSR_STATA|IKCSR_STATC)
629 if ((csr&IKCSR_DONE) == IKCSR_DONE) {
630 /*
631 * Done, complete handshake by notifying dr300.
632 */
633 ik->ik_csr = IKCSR_IENA; /* ~IKCSR_FNC1 */
634 ik->ik_pulse = IKPULSE_FNC2;
635 return (0);
636 }
637 /* beware of potential deadlock with dioread */
638 if ((csr&(IKCSR_ATTF|IKCSR_STATC)) == IKCSR_ATTF)
639 goto top;
640 }
641 ik->ik_csr = IKCSR_IENA;
642 return (PSERROR_DIOTIMO);
6fcffbdd
SL
643}
644
645/*ARGSUSED*/
646ikioctl(dev, cmd, data, flag)
93d65f53
SL
647 dev_t dev;
648 int cmd;
649 caddr_t data;
650 int flag;
6fcffbdd 651{
93d65f53
SL
652 int error = 0, unit = IKUNIT(dev), s;
653 register struct ik_softc *sc = &ik_softc[unit];
654
655 switch (cmd) {
656
657 case PSIOGETERROR: /* get error code for last operation */
658 *(int *)data = sc->is_error;
659 break;
660
661 case PSIOLOOKUP: { /* PS300 name lookup */
662 register struct pslookup *lp = (struct pslookup *)data;
663 register struct buf *bp;
664
665 if (lp->pl_len > PS_MAXNAMELEN)
666 return (EINVAL);
667 bp = &rikbuf[unit];
668 s = splbio();
669 while (bp->b_flags&B_BUSY) {
670 bp->b_flags |= B_WANTED;
671 sleep((caddr_t)bp, PRIBIO+1);
672 }
673 splx(s);
674 bp->b_flags = B_BUSY | B_WRITE;
9d61b7ff 675 error = copyin(lp->pl_name, sc->is_buf, (unsigned)lp->pl_len);
93d65f53
SL
676 if (error == 0) {
677 if (lp->pl_len&1)
678 sc->is_buf[lp->pl_len] = '\0';
679 error = ikcommand(dev, PS_LOOKUP, lp->pl_len);
680 }
681 s = splbio();
682 if (bp->b_flags&B_WANTED)
683 wakeup((caddr_t)bp);
684 splx(s);
685 bp->b_flags &= ~(B_BUSY|B_WANTED);
686 lp->pl_addr = sc->is_nameaddr.l;
687 break;
688 }
689 default:
690 return (ENOTTY);
691 }
692 return (error);
6fcffbdd
SL
693}
694#endif