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