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