1/*	$NetBSD: siop.c,v 1.1 2010/10/14 06:58:22 kiyohara Exp $	*/
2/*
3 * Copyright (c) 2010 KIYOHARA Takashi
4 * All rights reserved.
5 *
6 * Redistribution and use in source and binary forms, with or without
7 * modification, are permitted provided that the following conditions
8 * are met:
9 * 1. Redistributions of source code must retain the above copyright
10 *    notice, this list of conditions and the following disclaimer.
11 * 2. Redistributions in binary form must reproduce the above copyright
12 *    notice, this list of conditions and the following disclaimer in the
13 *    documentation and/or other materials provided with the distribution.
14 *
15 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
16 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
17 * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
18 * DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT,
19 * INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES
20 * (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR
21 * SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
23 * STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
24 * ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
25 * POSSIBILITY OF SUCH DAMAGE.
26 */
27
28#include <lib/libsa/stand.h>
29#include <lib/libkern/libkern.h>
30
31#include <dev/microcode/siop/siop.out>
32
33#include "boot.h"
34#include "sdvar.h"
35
36#define ALLOC(T, A)	\
37		(T *)(((uint32_t)alloc(sizeof(T) + (A)) + (A)) & ~((A) - 1))
38#define VTOPHYS(va)	(uint32_t)(va)
39#define DEVTOV(pa)	(uint32_t)(pa)
40#define wbinv(adr, siz)	_wbinv(VTOPHYS(adr), (uint32_t)(siz))
41#define inv(adr, siz)	_inv(VTOPHYS(adr), (uint32_t)(siz))
42
43/* 53c810 supports little endian */
44#define htoc32(x)	htole32(x)
45#define ctoh32(x)	le32toh(x)
46
47static void siop_pci_reset(int);
48
49static void siop_setuptables(struct siop_adapter *, struct siop_xfer *,
50			     struct scsi_xfer *);
51static void siop_ma(struct siop_adapter *, struct scsi_xfer *);
52static void siop_sdp(struct siop_adapter *, struct siop_xfer *,
53		     struct scsi_xfer *, int);
54static void siop_update_resid(struct siop_adapter *, struct siop_xfer *,
55			      struct scsi_xfer *, int);
56
57static int siop_intr(struct siop_adapter *);
58static void siop_scsicmd_end(struct siop_adapter *, struct scsi_xfer *);
59static int siop_scsi_request(struct siop_adapter *, struct scsi_xfer *);
60static void siop_start(struct siop_adapter *, struct scsi_xfer *);
61static void siop_xfer_setup(struct siop_xfer *, void *);
62
63static int siop_add_reselsw(struct siop_adapter *, int, int);
64static void siop_update_scntl3(struct siop_adapter *, int, int);
65
66static int _scsi_inquire(struct siop_adapter *, int, int, int, char *);
67static void scsi_request_sense(struct siop_adapter *, struct scsi_xfer *);
68static int scsi_interpret_sense(struct siop_adapter *, struct scsi_xfer *);
69static int scsi_probe(struct siop_adapter *);
70
71static struct siop_adapter adapt;
72
73
74static void
75siop_pci_reset(int addr)
76{
77	int dmode, ctest5;
78	const int maxburst = 4;			/* 53c810 */
79
80	dmode = readb(addr + SIOP_DMODE);
81
82	ctest5 = readb(addr + SIOP_CTEST5);
83	writeb(addr + SIOP_CTEST4, readb(addr + SIOP_CTEST4) & ~CTEST4_BDIS);
84	ctest5 &= ~CTEST5_BBCK;
85	ctest5 |= (maxburst - 1) & CTEST5_BBCK;
86	writeb(addr + SIOP_CTEST5, ctest5);
87
88	dmode |= DMODE_ERL;
89	dmode &= ~DMODE_BL_MASK;
90	dmode |= ((maxburst - 1) << DMODE_BL_SHIFT) & DMODE_BL_MASK;
91	writeb(addr + SIOP_DMODE, dmode);
92}
93
94
95static void
96siop_setuptables(struct siop_adapter *adp, struct siop_xfer *xfer,
97		 struct scsi_xfer *xs)
98{
99	int msgoffset = 1;
100
101	xfer->siop_tables.id =
102	    htoc32((adp->clock_div << 24) | (xs->target << 16));
103	memset(xfer->siop_tables.msg_out, 0, sizeof(xfer->siop_tables.msg_out));
104	/* request sense doesn't disconnect */
105	if (xs->cmd->opcode == SCSI_REQUEST_SENSE)
106		xfer->siop_tables.msg_out[0] = MSG_IDENTIFY(xs->lun, 0);
107	else
108		xfer->siop_tables.msg_out[0] = MSG_IDENTIFY(xs->lun, 1);
109
110	xfer->siop_tables.t_msgout.count = htoc32(msgoffset);
111	xfer->siop_tables.status =
112	    htoc32(SCSI_SIOP_NOSTATUS); /* set invalid status */
113
114	xfer->siop_tables.cmd.count = htoc32(xs->cmdlen);
115	xfer->siop_tables.cmd.addr = htoc32(local_to_PCI((u_long)xs->cmd));
116	if (xs->datalen != 0) {
117		xfer->siop_tables.data[0].count = htoc32(xs->datalen);
118		xfer->siop_tables.data[0].addr =
119		    htoc32(local_to_PCI((u_long)xs->data));
120	}
121}
122
123static void
124siop_ma(struct siop_adapter *adp, struct scsi_xfer *xs)
125{
126	int offset, dbc;
127
128	/*
129	 * compute how much of the current table didn't get handled when
130	 * a phase mismatch occurs
131	 */
132	if (xs->datalen == 0)
133	    return; /* no valid data transfer */
134
135	offset = readb(adp->addr + SIOP_SCRATCHA + 1);
136	if (offset >= SIOP_NSG) {
137		printf("bad offset in siop_sdp (%d)\n", offset);
138		return;
139	}
140	dbc = readl(adp->addr + SIOP_DBC) & 0x00ffffff;
141	xs->resid = dbc;
142}
143
144static void
145siop_sdp(struct siop_adapter *adp, struct siop_xfer *xfer, struct scsi_xfer *xs,
146	 int offset)
147{
148
149	if (xs->datalen == 0)
150	    return; /* no data pointers to save */
151
152	/*
153	 * offset == SIOP_NSG may be a valid condition if we get a Save data
154	 * pointer when the xfer is done. Just ignore the Save data pointer
155	 * in this case
156	 */
157	if (offset == SIOP_NSG)
158		return;
159	/*
160	 * Save data pointer. We do this by adjusting the tables to point
161	 * at the begginning of the data not yet transfered.
162	 * offset points to the first table with untransfered data.
163	 */
164
165	/*
166	 * before doing that we decrease resid from the ammount of data which
167	 * has been transfered.
168	 */
169	siop_update_resid(adp, xfer, xs, offset);
170
171#if 0
172	/*
173	 * First let see if we have a resid from a phase mismatch. If so,
174	 * we have to adjst the table at offset to remove transfered data.
175	 */
176	if (siop_cmd->flags & CMDFL_RESID) {
177		scr_table_t *table;
178
179		siop_cmd->flags &= ~CMDFL_RESID;
180		table = &xfer->siop_tables.data[offset];
181		/* "cut" already transfered data from this table */
182		table->addr =
183		    htoc32(ctoh32(table->addr) + ctoh32(table->count) -
184							siop_cmd->resid);
185		table->count = htoc32(siop_cmd->resid);
186	}
187#endif
188
189	/*
190	 * now we can remove entries which have been transfered.
191	 * We just move the entries with data left at the beggining of the
192	 * tables
193	 */
194	memmove(xfer->siop_tables.data, &xfer->siop_tables.data[offset],
195	    (SIOP_NSG - offset) * sizeof(scr_table_t));
196}
197
198static void
199siop_update_resid(struct siop_adapter *adp, struct siop_xfer *xfer,
200		  struct scsi_xfer *xs, int offset)
201{
202	int i;
203
204	if (xs->datalen == 0)
205	    return; /* no data to transfer */
206
207	/*
208	 * update resid. First account for the table entries which have
209	 * been fully completed.
210	 */
211	for (i = 0; i < offset; i++)
212		xs->resid -= ctoh32(xfer->siop_tables.data[i].count);
213#if 0
214	/*
215	 * if CMDFL_RESID is set, the last table (pointed by offset) is a
216	 * partial transfers. If not, offset points to the entry folloing
217	 * the last full transfer.
218	 */
219	if (siop_cmd->flags & CMDFL_RESID) {
220		scr_table_t *table = &xfer->siop_tables.data[offset];
221
222		xs->resid -= ctoh32(table->count) - xs->resid;
223	}
224#endif
225}
226
227
228#define CALL_SCRIPT(ent)	writel(adp->addr + SIOP_DSP, scriptaddr + ent);
229
230static int
231siop_intr(struct siop_adapter *adp)
232{
233	struct siop_xfer *siop_xfer = NULL;
234	struct scsi_xfer *xs = NULL;
235	u_long scriptaddr = local_to_PCI((u_long)adp->script);
236	int offset, target, lun, tag, restart = 0, need_reset = 0;
237	uint32_t dsa, irqcode;
238	uint16_t sist;
239	uint8_t dstat, sstat1, istat;
240
241	istat = readb(adp->addr + SIOP_ISTAT);
242	if ((istat & (ISTAT_INTF | ISTAT_DIP | ISTAT_SIP)) == 0)
243		return 0;
244	if (istat & ISTAT_INTF) {
245		printf("INTRF\n");
246		writeb(adp->addr + SIOP_ISTAT, ISTAT_INTF);
247	}
248	if ((istat & (ISTAT_DIP | ISTAT_SIP | ISTAT_ABRT)) ==
249	    (ISTAT_DIP | ISTAT_ABRT))
250		/* clear abort */
251		writeb(adp->addr + SIOP_ISTAT, 0);
252	/* use DSA to find the current siop_cmd */
253	dsa = readl(adp->addr + SIOP_DSA);
254	if (dsa >= local_to_PCI((u_long)adp->xfer) &&
255	    dsa < local_to_PCI((u_long)adp->xfer) + SIOP_TABLE_SIZE) {
256		dsa -= local_to_PCI((u_long)adp->xfer);
257		siop_xfer = adp->xfer;
258		_inv((u_long)siop_xfer, sizeof(*siop_xfer));
259
260		xs = adp->xs;
261	}
262
263	if (istat & ISTAT_DIP)
264		dstat = readb(adp->addr + SIOP_DSTAT);
265	if (istat & ISTAT_SIP) {
266		if (istat & ISTAT_DIP)
267			delay(10);
268		/*
269		 * Can't read sist0 & sist1 independently, or we have to
270		 * insert delay
271		 */
272		sist = readw(adp->addr + SIOP_SIST0);
273		sstat1 = readb(adp->addr + SIOP_SSTAT1);
274
275		if ((sist & SIST0_MA) && need_reset == 0) {
276			if (siop_xfer) {
277				int scratcha0;
278
279				dstat = readb(adp->addr + SIOP_DSTAT);
280				/*
281				 * first restore DSA, in case we were in a S/G
282				 * operation.
283				 */
284				writel(adp->addr + SIOP_DSA,
285				    local_to_PCI((u_long)siop_xfer));
286				scratcha0 = readb(adp->addr + SIOP_SCRATCHA);
287				switch (sstat1 & SSTAT1_PHASE_MASK) {
288				case SSTAT1_PHASE_STATUS:
289				/*
290				 * previous phase may be aborted for any reason
291				 * ( for example, the target has less data to
292				 * transfer than requested). Compute resid and
293				 * just go to status, the command should
294				 * terminate.
295				 */
296					if (scratcha0 & A_flag_data)
297						siop_ma(adp, xs);
298					else if ((dstat & DSTAT_DFE) == 0)
299printf("PHASE STATUS: siop_clearfifo...\n");
300//						siop_clearfifo(adp);
301					CALL_SCRIPT(Ent_status);
302					return 1;
303				case SSTAT1_PHASE_MSGIN:
304				/*
305				 * target may be ready to disconnect
306				 * Compute resid which would be used later
307				 * if a save data pointer is needed.
308				 */
309					if (scratcha0 & A_flag_data)
310						siop_ma(adp, xs);
311					else if ((dstat & DSTAT_DFE) == 0)
312printf("PHASE MSGIN: siop_clearfifo...\n");
313//						siop_clearfifo(adp);
314					writeb(adp->addr + SIOP_SCRATCHA,
315					    scratcha0 & ~A_flag_data);
316					CALL_SCRIPT(Ent_msgin);
317					return 1;
318				}
319				printf("unexpected phase mismatch %d\n",
320				    sstat1 & SSTAT1_PHASE_MASK);
321			} else
322				printf("phase mismatch without command\n");
323			need_reset = 1;
324		}
325		if (sist & (SIST1_STO << 8)) {
326			/* selection time out, assume there's no device here */
327			if (siop_xfer) {
328				xs->error = XS_SELTIMEOUT;
329				goto end;
330			} else
331				printf("selection timeout without command\n");
332		}
333
334		/* Else it's an unhandled exception (for now). */
335		printf("unhandled scsi interrupt,"
336		    " sist=0x%x sstat1=0x%x DSA=0x%x DSP=0x%lx\n",
337		    sist, sstat1, dsa,
338		    readl(adp->addr + SIOP_DSP) - scriptaddr);
339		if (siop_xfer) {
340			xs->error = XS_SELTIMEOUT;
341			goto end;
342		}
343		need_reset = 1;
344	}
345	if (need_reset) {
346reset:
347		printf("XXXXX: fatal error, need reset the bus...\n");
348		return 1;
349	}
350
351//scintr:
352	if ((istat & ISTAT_DIP) && (dstat & DSTAT_SIR)) { /* script interrupt */
353		irqcode = readl(adp->addr + SIOP_DSPS);
354		/*
355		 * no command, or an inactive command is only valid for a
356		 * reselect interrupt
357		 */
358		if ((irqcode & 0x80) == 0) {
359			if (siop_xfer == NULL) {
360				printf(
361				    "script interrupt 0x%x with invalid DSA\n",
362				    irqcode);
363				goto reset;
364			}
365		}
366		switch(irqcode) {
367		case A_int_err:
368			printf("error, DSP=0x%lx\n",
369			    readl(adp->addr + SIOP_DSP) - scriptaddr);
370			if (xs) {
371				xs->error = XS_SELTIMEOUT;
372				goto end;
373			} else {
374				goto reset;
375			}
376		case A_int_reseltarg:
377			printf("reselect with invalid target\n");
378			goto reset;
379		case A_int_resellun:
380			target = readb(adp->addr + SIOP_SCRATCHA) & 0xf;
381			lun = readb(adp->addr + SIOP_SCRATCHA + 1);
382			tag = readb(adp->addr + SIOP_SCRATCHA + 2);
383			if (target != adp->xs->target ||
384			    lun != adp->xs->lun ||
385			    tag != 0) {
386				printf("unknwon resellun:"
387				    " target %d lun %d tag %d\n",
388				    target, lun, tag);
389				goto reset;
390			}
391			siop_xfer = adp->xfer;
392			dsa = local_to_PCI((u_long)siop_xfer);
393			writel(adp->addr + SIOP_DSP,
394			    dsa + sizeof(struct siop_common_xfer) +
395			    Ent_ldsa_reload_dsa);
396			_wbinv((u_long)siop_xfer, sizeof(*siop_xfer));
397			return 1;
398		case A_int_reseltag:
399			printf("reselect with invalid tag\n");
400			goto reset;
401		case A_int_disc:
402			offset = readb(adp->addr + SIOP_SCRATCHA + 1);
403			siop_sdp(adp, siop_xfer, xs, offset);
404#if 0
405			/* we start again with no offset */
406			siop_cmd->saved_offset = SIOP_NOOFFSET;
407#endif
408			_wbinv((u_long)siop_xfer, sizeof(*siop_xfer));
409			CALL_SCRIPT(Ent_script_sched);
410			return 1;
411		case A_int_resfail:
412			printf("reselect failed\n");
413			return  1;
414		case A_int_done:
415			if (xs == NULL) {
416				printf("done without command, DSA=0x%lx\n",
417				    local_to_PCI((u_long)adp->xfer));
418				return 1;
419			}
420			/* update resid.  */
421			offset = readb(adp->addr + SIOP_SCRATCHA + 1);
422#if 0
423			/*
424			 * if we got a disconnect between the last data phase
425			 * and the status phase, offset will be 0. In this
426			 * case, siop_cmd->saved_offset will have the proper
427			 * value if it got updated by the controller
428			 */
429			if (offset == 0 &&
430			    siop_cmd->saved_offset != SIOP_NOOFFSET)
431				offset = siop_cmd->saved_offset;
432#endif
433			siop_update_resid(adp, siop_xfer, xs, offset);
434			goto end;
435		default:
436			printf("unknown irqcode %x\n", irqcode);
437			if (xs) {
438				xs->error = XS_SELTIMEOUT;
439				goto end;
440			}
441			goto reset;
442		}
443		return 1;
444	}
445	/* We just should't get there */
446	panic("siop_intr: I shouldn't be there !");
447
448	return 1;
449
450end:
451	/*
452	 * restart the script now if command completed properly
453	 * Otherwise wait for siop_scsicmd_end(), we may need to cleanup the
454	 * queue
455	 */
456	xs->status = ctoh32(siop_xfer->siop_tables.status);
457	if (xs->status == SCSI_OK)
458		writel(adp->addr + SIOP_DSP, scriptaddr + Ent_script_sched);
459	else
460		restart = 1;
461	siop_scsicmd_end(adp, xs);
462	if (restart)
463		writel(adp->addr + SIOP_DSP, scriptaddr + Ent_script_sched);
464
465	return 1;
466}
467
468static void
469siop_scsicmd_end(struct siop_adapter *adp, struct scsi_xfer *xs)
470{
471
472	switch(xs->status) {
473	case SCSI_OK:
474		xs->error = XS_NOERROR;
475		break;
476	case SCSI_BUSY:
477	case SCSI_CHECK:
478	case SCSI_QUEUE_FULL:
479		xs->error = XS_BUSY;
480		break;
481	case SCSI_SIOP_NOCHECK:
482		/*
483		 * don't check status, xs->error is already valid
484		 */
485		break;
486	case SCSI_SIOP_NOSTATUS:
487		/*
488		 * the status byte was not updated, cmd was
489		 * aborted
490		 */
491		xs->error = XS_SELTIMEOUT;
492		break;
493	default:
494		printf("invalid status code %d\n", xs->status);
495		xs->error = XS_DRIVER_STUFFUP;
496	}
497	_inv((u_long)xs->cmd, xs->cmdlen);
498	if (xs->datalen != 0)
499		_inv((u_long)xs->data, xs->datalen);
500	xs->xs_status = XS_STS_DONE;
501}
502
503static int
504siop_scsi_request(struct siop_adapter *adp, struct scsi_xfer *xs)
505{
506	void *xfer = adp->xfer;
507	int timo, error;
508
509	if (adp->sel_t != xs->target) {
510		const int free_lo = __arraycount(siop_script);
511		int i;
512		void *scriptaddr = (void *)local_to_PCI((u_long)adp->script);
513
514		if (adp->sel_t != -1)
515			adp->script[Ent_resel_targ0 / 4 + adp->sel_t * 2] =
516			    htoc32(0x800c00ff);
517
518		for (i = 0; i < __arraycount(lun_switch); i++)
519			adp->script[free_lo + i] = htoc32(lun_switch[i]);
520		adp->script[free_lo + E_abs_lunsw_return_Used[0]] =
521		    htoc32(scriptaddr + Ent_lunsw_return);
522
523		siop_add_reselsw(adp, xs->target, free_lo);
524
525		adp->sel_t = xs->target;
526	}
527
528restart:
529
530	siop_setuptables(adp, xfer, xs);
531
532	/* load the DMA maps */
533	if (xs->datalen != 0)
534		_inv((u_long)xs->data, xs->datalen);
535	_wbinv((u_long)xs->cmd, xs->cmdlen);
536
537	_wbinv((u_long)xfer, sizeof(struct siop_xfer));
538	siop_start(adp, xs);
539
540	adp->xs = xs;
541	timo = 0;
542	while (!(xs->xs_status & XS_STS_DONE)) {
543		delay(1000);
544		siop_intr(adp);
545
546		if (timo++ > 3000) {		/* XXXX: 3sec */
547			printf("%s: timeout\n", __func__);
548			return ETIMEDOUT;
549		}
550	}
551
552	if (xs->error != XS_NOERROR) {
553		if (xs->error == XS_BUSY || xs->status == SCSI_CHECK)
554			scsi_request_sense(adp, xs);
555
556		switch (xs->error) {
557		case XS_SENSE:
558		case XS_SHORTSENSE:
559			error = scsi_interpret_sense(adp, xs);
560			break;
561		case XS_RESOURCE_SHORTAGE:
562			printf("adapter resource shortage\n");
563
564			/* FALLTHROUGH */
565		case XS_BUSY:
566			error = EBUSY;
567			break;
568		case XS_REQUEUE:
569			printf("XXXX: requeue...\n");
570			error = ERESTART;
571			break;
572		case XS_SELTIMEOUT:
573		case XS_TIMEOUT:
574			error = EIO;
575			break;
576		case XS_RESET:
577			error = EIO;
578			break;
579		case XS_DRIVER_STUFFUP:
580			printf("generic HBA error\n");
581			error = EIO;
582			break;
583		default:
584			printf("invalid return code from adapter: %d\n",
585			    xs->error);
586			error = EIO;
587			break;
588		}
589		if (error == ERESTART) {
590			xs->error = XS_NOERROR;
591			xs->status = SCSI_OK;
592			xs->xs_status &= ~XS_STS_DONE;
593			goto restart;
594		}
595		return error;
596	}
597	return 0;
598}
599
600static void
601siop_start(struct siop_adapter *adp, struct scsi_xfer *xs)
602{
603	struct siop_xfer *siop_xfer = adp->xfer;
604	uint32_t dsa, *script = adp->script;
605	int target, lun, slot;
606	void *scriptaddr = (void *)local_to_PCI((u_long)script);
607	const int siop_common_xfer_size = sizeof(struct siop_common_xfer);
608
609	/*
610	 * The queue management here is a bit tricky: the script always looks
611	 * at the slot from first to last, so if we always use the first
612	 * free slot commands can stay at the tail of the queue ~forever.
613	 * The algorithm used here is to restart from the head when we know
614	 * that the queue is empty, and only add commands after the last one.
615	 * When we're at the end of the queue wait for the script to clear it.
616	 * The best thing to do here would be to implement a circular queue,
617	 * but using only 53c720 features this can be "interesting".
618	 * A mid-way solution could be to implement 2 queues and swap orders.
619	 */
620	slot = adp->currschedslot;
621	/*
622	 * If the instruction is 0x80000000 (JUMP foo, IF FALSE) the slot is
623	 * free. As this is the last used slot, all previous slots are free,
624	 * we can restart from 0.
625	 */
626	if (ctoh32(script[(Ent_script_sched_slot0 / 4) + slot * 2]) ==
627	    0x80000000) {
628		slot = adp->currschedslot = 0;
629	} else {
630		slot++;
631	}
632	target = xs->target;
633	lun = xs->lun;
634	/*
635	 * find a free scheduler slot and load it.
636	 */
637#define SIOP_NSLOTS	0x40
638	for (; slot < SIOP_NSLOTS; slot++) {
639		/*
640		 * If cmd if 0x80000000 the slot is free
641		 */
642		if (ctoh32(script[(Ent_script_sched_slot0 / 4) + slot * 2]) ==
643		    0x80000000)
644			break;
645	}
646	if (slot == SIOP_NSLOTS) {
647		/*
648		 * no more free slot, no need to continue. freeze the queue
649		 * and requeue this command.
650		 */
651		printf("no mode free slot\n");
652		return;
653	}
654
655	/* patch scripts with DSA addr */
656	dsa = local_to_PCI((u_long)siop_xfer);
657
658	/* CMD script: MOVE MEMORY addr */
659	siop_xfer->resel[E_ldsa_abs_slot_Used[0]] =
660	    htoc32(scriptaddr + Ent_script_sched_slot0 + slot * 8);
661	_wbinv((u_long)siop_xfer, sizeof(*siop_xfer));
662	/* scheduler slot: JUMP ldsa_select */
663	script[(Ent_script_sched_slot0 / 4) + slot * 2 + 1] =
664	    htoc32(dsa + siop_common_xfer_size + Ent_ldsa_select);
665	/*
666	 * Change JUMP cmd so that this slot will be handled
667	 */
668	script[(Ent_script_sched_slot0 / 4) + slot * 2] = htoc32(0x80080000);
669	adp->currschedslot = slot;
670
671	/* make sure SCRIPT processor will read valid data */
672	_wbinv((u_long)script, SIOP_SCRIPT_SIZE);
673	/* Signal script it has some work to do */
674	writeb(adp->addr + SIOP_ISTAT, ISTAT_SIGP);
675	/* and wait for IRQ */
676}
677
678static void
679siop_xfer_setup(struct siop_xfer *xfer, void *scriptaddr)
680{
681	const int off_msg_in = offsetof(struct siop_common_xfer, msg_in);
682	const int off_status = offsetof(struct siop_common_xfer, status);
683	uint32_t dsa, *scr;
684	int i;
685
686	memset(xfer, 0, sizeof(*xfer));
687	dsa = local_to_PCI((u_long)xfer);
688	xfer->siop_tables.t_msgout.count = htoc32(1);
689	xfer->siop_tables.t_msgout.addr = htoc32(dsa);
690	xfer->siop_tables.t_msgin.count = htoc32(1);
691	xfer->siop_tables.t_msgin.addr = htoc32(dsa + off_msg_in);
692	xfer->siop_tables.t_extmsgin.count = htoc32(2);
693	xfer->siop_tables.t_extmsgin.addr = htoc32(dsa + off_msg_in + 1);
694	xfer->siop_tables.t_extmsgdata.addr = htoc32(dsa + off_msg_in + 3);
695	xfer->siop_tables.t_status.count = htoc32(1);
696	xfer->siop_tables.t_status.addr = htoc32(dsa + off_status);
697
698	/* The select/reselect script */
699	scr = xfer->resel;
700	for (i = 0; i < __arraycount(load_dsa); i++)
701		scr[i] = htoc32(load_dsa[i]);
702
703	/*
704	 * 0x78000000 is a 'move data8 to reg'. data8 is the second
705	 * octet, reg offset is the third.
706	 */
707	scr[Ent_rdsa0 / 4] = htoc32(0x78100000 | ((dsa & 0x000000ff) <<  8));
708	scr[Ent_rdsa1 / 4] = htoc32(0x78110000 | ( dsa & 0x0000ff00       ));
709	scr[Ent_rdsa2 / 4] = htoc32(0x78120000 | ((dsa & 0x00ff0000) >>  8));
710	scr[Ent_rdsa3 / 4] = htoc32(0x78130000 | ((dsa & 0xff000000) >> 16));
711	scr[E_ldsa_abs_reselected_Used[0]] =
712	    htoc32(scriptaddr + Ent_reselected);
713	scr[E_ldsa_abs_reselect_Used[0]] = htoc32(scriptaddr + Ent_reselect);
714	scr[E_ldsa_abs_selected_Used[0]] = htoc32(scriptaddr + Ent_selected);
715	scr[E_ldsa_abs_data_Used[0]] =
716	    htoc32(dsa + sizeof(struct siop_common_xfer) + Ent_ldsa_data);
717	/* JUMP foo, IF FALSE - used by MOVE MEMORY to clear the slot */
718	scr[Ent_ldsa_data / 4] = htoc32(0x80000000);
719}
720
721static int
722siop_add_reselsw(struct siop_adapter *adp, int target, int lunsw_off)
723{
724	uint32_t *script = adp->script;
725	int reseloff;
726	void *scriptaddr = (void *)local_to_PCI((u_long)adp->script);
727
728	/*
729	 * add an entry to resel switch
730	 */
731	reseloff = Ent_resel_targ0 / 4 + target * 2;
732	if ((ctoh32(script[reseloff]) & 0xff) != 0xff) {
733		/* it's not free */
734		printf("siop: resel switch full\n");
735		return EBUSY;
736	}
737
738	/* JUMP abs_foo, IF target | 0x80; */
739	script[reseloff + 0] = htoc32(0x800c0080 | target);
740	script[reseloff + 1] =
741	    htoc32(scriptaddr + lunsw_off * 4 + Ent_lun_switch_entry);
742
743	siop_update_scntl3(adp, target, lunsw_off);
744	return 0;
745}
746
747static void
748siop_update_scntl3(struct siop_adapter *adp, int target, int lunsw_off)
749{
750	uint32_t *script = adp->script;
751
752	/* MOVE target->id >> 24 TO SCNTL3 */
753	script[lunsw_off + (Ent_restore_scntl3 / 4)] =
754	    htoc32(0x78030000 | ((adp->clock_div >> 16) & 0x0000ff00));
755	/* MOVE target->id >> 8 TO SXFER */
756	script[lunsw_off + (Ent_restore_scntl3 / 4) + 2] =
757	    htoc32(0x78050000 | (0x000000000 & 0x0000ff00));
758	_wbinv((u_long)script, SIOP_SCRIPT_SIZE);
759}
760
761
762/*
763 * SCSI functions
764 */
765
766static int
767_scsi_inquire(struct siop_adapter *adp, int t, int l, int buflen, char *buf)
768{
769	struct scsipi_inquiry *cmd = (struct scsipi_inquiry *)adp->cmd;
770	struct scsipi_inquiry_data *inqbuf =
771	    (struct scsipi_inquiry_data *)adp->data;
772	struct scsi_xfer xs;
773	int error;
774
775	memset(cmd, 0, sizeof(*cmd));
776	cmd->opcode = INQUIRY;
777	cmd->length = SCSIPI_INQUIRY_LENGTH_SCSI2;
778	memset(inqbuf, 0, sizeof(*inqbuf));
779
780	memset(&xs, 0, sizeof(xs));
781	xs.target = t;
782	xs.lun = l;
783	xs.cmdlen = sizeof(*cmd);
784	xs.cmd = (void *)cmd;
785	xs.datalen = SCSIPI_INQUIRY_LENGTH_SCSI2;
786	xs.data = (void *)inqbuf;
787
788	xs.error = XS_NOERROR;
789	xs.resid = xs.datalen;
790	xs.status = SCSI_OK;
791
792	error = siop_scsi_request(adp, &xs);
793	if (error != 0)
794		return error;
795
796	memcpy(buf, inqbuf, buflen);
797	return 0;
798}
799
800static void
801scsi_request_sense(struct siop_adapter *adp, struct scsi_xfer *xs)
802{
803	struct scsi_request_sense *cmd = adp->sense;
804	struct scsi_sense_data *data = (struct scsi_sense_data *)adp->data;
805	struct scsi_xfer sense;
806	int error;
807
808	memset(cmd, 0, sizeof(struct scsi_request_sense));
809	cmd->opcode = SCSI_REQUEST_SENSE;
810	cmd->length = sizeof(struct scsi_sense_data);
811	memset(data, 0, sizeof(struct scsi_sense_data));
812
813	memset(&sense, 0, sizeof(sense));
814	sense.target = xs->target;
815	sense.lun = xs->lun;
816	sense.cmdlen = sizeof(struct scsi_request_sense);
817	sense.cmd = (void *)cmd;
818	sense.datalen = sizeof(struct scsi_sense_data);
819	sense.data = (void *)data;
820
821	sense.error = XS_NOERROR;
822	sense.resid = sense.datalen;
823	sense.status = SCSI_OK;
824
825	error = siop_scsi_request(adp, &sense);
826	switch (error) {
827	case 0:
828		/* we have a valid sense */
829		xs->error = XS_SENSE;
830		return;
831	case EINTR:
832		/* REQUEST_SENSE interrupted by bus reset. */
833		xs->error = XS_RESET;
834		return;
835	case EIO:
836		 /* request sense coudn't be performed */
837		/*
838		 * XXX this isn't quite right but we don't have anything
839		 * better for now
840		 */
841		xs->error = XS_DRIVER_STUFFUP;
842		return;
843	default:
844		 /* Notify that request sense failed. */
845		xs->error = XS_DRIVER_STUFFUP;
846		printf("request sense failed with error %d\n", error);
847		return;
848	}
849}
850
851/*
852 * scsi_interpret_sense:
853 *
854 *	Look at the returned sense and act on the error, determining
855 *	the unix error number to pass back.  (0 = report no error)
856 *
857 *	NOTE: If we return ERESTART, we are expected to haved
858 *	thawed the device!
859 *
860 *	THIS IS THE DEFAULT ERROR HANDLER FOR SCSI DEVICES.
861 */
862static int
863scsi_interpret_sense(struct siop_adapter *adp, struct scsi_xfer *xs)
864{
865	struct scsi_sense_data *sense;
866	u_int8_t key;
867	int error;
868	uint32_t info;
869	static const char *error_mes[] = {
870		"soft error (corrected)",
871		"not ready", "medium error",
872		"non-media hardware failure", "illegal request",
873		"unit attention", "readonly device",
874		"no data found", "vendor unique",
875		"copy aborted", "command aborted",
876		"search returned equal", "volume overflow",
877		"verify miscompare", "unknown error key"
878	};
879
880	sense = (struct scsi_sense_data *)xs->data;
881
882	/* otherwise use the default */
883	switch (SSD_RCODE(sense->response_code)) {
884
885		/*
886		 * Old SCSI-1 and SASI devices respond with
887		 * codes other than 70.
888		 */
889	case 0x00:		/* no error (command completed OK) */
890		return 0;
891	case 0x04:		/* drive not ready after it was selected */
892		if (adp->sd->sc_flags & FLAGS_REMOVABLE)
893			adp->sd->sc_flags &= ~FLAGS_MEDIA_LOADED;
894		/* XXX - display some sort of error here? */
895		return EIO;
896	case 0x20:		/* invalid command */
897		return EINVAL;
898	case 0x25:		/* invalid LUN (Adaptec ACB-4000) */
899		return EACCES;
900
901		/*
902		 * If it's code 70, use the extended stuff and
903		 * interpret the key
904		 */
905	case 0x71:		/* delayed error */
906		key = SSD_SENSE_KEY(sense->flags);
907		printf(" DEFERRED ERROR, key = 0x%x\n", key);
908		/* FALLTHROUGH */
909	case 0x70:
910		if ((sense->response_code & SSD_RCODE_VALID) != 0)
911			info = _4btol(sense->info);
912		else
913			info = 0;
914		key = SSD_SENSE_KEY(sense->flags);
915
916		switch (key) {
917		case SKEY_NO_SENSE:
918		case SKEY_RECOVERED_ERROR:
919			if (xs->resid == xs->datalen && xs->datalen) {
920				/*
921				 * Why is this here?
922				 */
923				xs->resid = 0;	/* not short read */
924			}
925		case SKEY_EQUAL:
926			error = 0;
927			break;
928		case SKEY_NOT_READY:
929			if (adp->sd->sc_flags & FLAGS_REMOVABLE)
930				adp->sd->sc_flags &= ~FLAGS_MEDIA_LOADED;
931			if (sense->asc == 0x3A) {
932				error = ENODEV; /* Medium not present */
933			} else
934				error = EIO;
935			break;
936		case SKEY_ILLEGAL_REQUEST:
937			error = EINVAL;
938			break;
939		case SKEY_UNIT_ATTENTION:
940			if (sense->asc == 0x29 &&
941			    sense->ascq == 0x00) {
942				/* device or bus reset */
943				return ERESTART;
944			}
945			if (adp->sd->sc_flags & FLAGS_REMOVABLE)
946				adp->sd->sc_flags &= ~FLAGS_MEDIA_LOADED;
947			if (!(adp->sd->sc_flags & FLAGS_REMOVABLE))
948				return ERESTART;
949			error = EIO;
950			break;
951		case SKEY_DATA_PROTECT:
952			error = EROFS;
953			break;
954		case SKEY_BLANK_CHECK:
955			error = 0;
956			break;
957		case SKEY_ABORTED_COMMAND:
958			break;
959		case SKEY_VOLUME_OVERFLOW:
960			error = ENOSPC;
961			break;
962		default:
963			error = EIO;
964			break;
965		}
966
967		/* Print brief(er) sense information */
968		printf("%s", error_mes[key - 1]);
969		if ((sense->response_code & SSD_RCODE_VALID) != 0) {
970			switch (key) {
971			case SKEY_NOT_READY:
972			case SKEY_ILLEGAL_REQUEST:
973			case SKEY_UNIT_ATTENTION:
974			case SKEY_DATA_PROTECT:
975				break;
976			case SKEY_BLANK_CHECK:
977				printf(", requested size: %d (decimal)",
978				    info);
979				break;
980			case SKEY_ABORTED_COMMAND:
981				printf(", cmd 0x%x, info 0x%x",
982				    xs->cmd->opcode, info);
983				break;
984			default:
985				printf(", info = %d (decimal)", info);
986			}
987		}
988		if (sense->extra_len != 0) {
989			int n;
990			printf(", data =");
991			for (n = 0; n < sense->extra_len; n++)
992				printf(" %x", sense->csi[n]);
993		}
994		printf("\n");
995		return error;
996
997	/*
998	 * Some other code, just report it
999	 */
1000	default:
1001		printf("Sense Error Code 0x%x",
1002			SSD_RCODE(sense->response_code));
1003		if ((sense->response_code & SSD_RCODE_VALID) != 0) {
1004			struct scsi_sense_data_unextended *usense =
1005			    (struct scsi_sense_data_unextended *)sense;
1006			printf(" at block no. %d (decimal)",
1007			    _3btol(usense->block));
1008		}
1009		printf("\n");
1010		return EIO;
1011	}
1012}
1013
1014static int
1015scsi_probe(struct siop_adapter *adp)
1016{
1017	struct scsipi_inquiry_data *inqbuf;
1018	int found, t, l;
1019	uint8_t device;
1020	char buf[SCSIPI_INQUIRY_LENGTH_SCSI2],
1021	    product[sizeof(inqbuf->product) + 1];
1022
1023	found = 0;
1024	for (t = 0; t < 8; t++) {
1025		if (t == adp->id)
1026			continue;
1027		for (l = 0; l < 8; l++) {
1028			if (_scsi_inquire(adp, t, l, sizeof(buf), buf) != 0)
1029				continue;
1030
1031			inqbuf = (struct scsipi_inquiry_data *)buf;
1032			device = inqbuf->device & SID_TYPE;
1033			if (device == T_NODEVICE)
1034				continue;
1035			if (device != T_DIRECT &&
1036			    device != T_OPTICAL &&
1037			    device != T_SIMPLE_DIRECT)
1038				continue;
1039
1040			memset(product, 0, sizeof(product));
1041			strncpy(product, inqbuf->product, sizeof(product) - 1);
1042			printf("/dev/disk/scsi/0/%d/%d: <%s>\n", t, l, product);
1043			found++;
1044		}
1045	}
1046	return found;
1047}
1048
1049int
1050scsi_inquire(struct sd_softc *sd, int buflen, void *buf)
1051{
1052	struct siop_adapter *adp;
1053	int error;
1054
1055	if (sd->sc_bus != 0)
1056		return ENOTSUP;
1057	if (adapt.addr == 0)
1058		return ENOENT;
1059	adp = &adapt;
1060
1061	adp->sd = sd;
1062	error = _scsi_inquire(adp, sd->sc_target, sd->sc_lun, buflen, buf);
1063	adp->sd = NULL;
1064
1065	return error;
1066}
1067
1068/*
1069 * scsi_mode_sense
1070 *	get a sense page from a device
1071 */
1072
1073int
1074scsi_mode_sense(struct sd_softc *sd, int byte2, int page,
1075		  struct scsi_mode_parameter_header_6 *data, int len)
1076{
1077	struct scsi_mode_sense_6 cmd;
1078
1079	memset(&cmd, 0, sizeof(cmd));
1080	cmd.opcode = SCSI_MODE_SENSE_6;
1081	cmd.byte2 = byte2;
1082	cmd.page = page;
1083	cmd.length = len & 0xff;
1084
1085	return scsi_command(sd, (void *)&cmd, sizeof(cmd), (void *)data, len);
1086}
1087
1088int
1089scsi_command(struct sd_softc *sd, void *cmd, int cmdlen, void *data,
1090	     int datalen)
1091{
1092	struct siop_adapter *adp;
1093	struct scsi_xfer xs;
1094	int error;
1095
1096	if (sd->sc_bus != 0)
1097		return ENOTSUP;
1098	if (adapt.addr == 0)
1099		return ENOENT;
1100	adp = &adapt;
1101
1102	memcpy(adp->cmd, cmd, cmdlen);
1103	adp->sd = sd;
1104
1105	memset(&xs, 0, sizeof(xs));
1106	xs.target = sd->sc_target;
1107	xs.lun = sd->sc_lun;
1108	xs.cmdlen = cmdlen;
1109	xs.cmd = adp->cmd;
1110	xs.datalen = datalen;
1111	xs.data = adp->data;
1112
1113	xs.error = XS_NOERROR;
1114	xs.resid = datalen;
1115	xs.status = SCSI_OK;
1116
1117	error = siop_scsi_request(adp, &xs);
1118	adp->sd = NULL;
1119	if (error != 0)
1120		return error;
1121
1122	if (datalen > 0)
1123		memcpy(data, adp->data, datalen);
1124	return 0;
1125}
1126
1127/*
1128 * Initialize the device.
1129 */
1130int
1131siop_init(int bus, int dev, int func)
1132{
1133	struct siop_adapter tmp;
1134	struct siop_xfer *xfer;
1135	struct scsipi_generic *cmd;
1136	struct scsi_request_sense *sense;
1137	uint32_t reg;
1138	u_long addr;
1139	uint32_t *script;
1140	int slot, id, i;
1141	void *scriptaddr;
1142	u_char *data;
1143	const int clock_div = 3;		/* 53c810 */
1144
1145	slot = PCISlotnum(bus, dev, func);
1146	if (slot == -1)
1147		return ENOENT;
1148
1149	addr = PCIAddress(slot, 1, PCI_MAPREG_TYPE_MEM);
1150	if (addr == 0xffffffff)
1151		return EINVAL;
1152	enablePCI(slot, 0, 1, 1);
1153
1154	script = ALLOC(uint32_t, SIOP_SCRIPT_SIZE);
1155	if (script == NULL)
1156		return ENOMEM;
1157	scriptaddr = (void *)local_to_PCI((u_long)script);
1158	cmd = ALLOC(struct scsipi_generic, SIOP_SCSI_COMMAND_SIZE);
1159	if (cmd == NULL)
1160		return ENOMEM;
1161	sense = ALLOC(struct scsi_request_sense, SIOP_SCSI_COMMAND_SIZE);
1162	if (sense == NULL)
1163		return ENOMEM;
1164	data = ALLOC(u_char, SIOP_SCSI_DATA_SIZE);
1165	if (data == NULL)
1166		return ENOMEM;
1167	xfer = ALLOC(struct siop_xfer, sizeof(struct siop_xfer));
1168	if (xfer == NULL)
1169		return ENOMEM;
1170	siop_xfer_setup(xfer, scriptaddr);
1171
1172	id = readb(addr + SIOP_SCID) & SCID_ENCID_MASK;
1173
1174	/* reset bus */
1175	reg = readb(addr + SIOP_SCNTL1);
1176	writeb(addr + SIOP_SCNTL1, reg | SCNTL1_RST);
1177	delay(100);
1178	writeb(addr + SIOP_SCNTL1, reg);
1179
1180	/* reset the chip */
1181	writeb(addr + SIOP_ISTAT, ISTAT_SRST);
1182	delay(1000);
1183	writeb(addr + SIOP_ISTAT, 0);
1184
1185	/* init registers */
1186	writeb(addr + SIOP_SCNTL0, SCNTL0_ARB_MASK | SCNTL0_EPC | SCNTL0_AAP);
1187	writeb(addr + SIOP_SCNTL1, 0);
1188	writeb(addr + SIOP_SCNTL3, clock_div);
1189	writeb(addr + SIOP_SXFER, 0);
1190	writeb(addr + SIOP_DIEN, 0xff);
1191	writeb(addr + SIOP_SIEN0, 0xff & ~(SIEN0_CMP | SIEN0_SEL | SIEN0_RSL));
1192	writeb(addr + SIOP_SIEN1, 0xff & ~(SIEN1_HTH | SIEN1_GEN));
1193	writeb(addr + SIOP_STEST2, 0);
1194	writeb(addr + SIOP_STEST3, STEST3_TE);
1195	writeb(addr + SIOP_STIME0, (0xb << STIME0_SEL_SHIFT));
1196	writeb(addr + SIOP_SCID, id | SCID_RRE);
1197	writeb(addr + SIOP_RESPID0, 1 << id);
1198	writeb(addr + SIOP_DCNTL, DCNTL_COM);
1199
1200	/* BeBox uses PCIC */
1201	writeb(addr + SIOP_STEST1, STEST1_SCLK);
1202
1203	siop_pci_reset(addr);
1204
1205	/* copy and patch the script */
1206	for (i = 0; i < __arraycount(siop_script); i++)
1207		script[i] = htoc32(siop_script[i]);
1208	for (i = 0; i < __arraycount(E_abs_msgin_Used); i++)
1209		script[E_abs_msgin_Used[i]] =
1210		    htoc32(scriptaddr + Ent_msgin_space);
1211
1212	/* start script */
1213	_wbinv((u_long)script, SIOP_SCRIPT_SIZE);
1214	writel(addr + SIOP_DSP, (int)scriptaddr + Ent_reselect);
1215
1216	memset(&tmp, 0, sizeof(tmp));
1217	tmp.id = id;
1218	tmp.clock_div = clock_div;
1219	tmp.addr = addr;
1220	tmp.script = script;
1221	tmp.xfer = xfer;
1222	tmp.cmd = cmd;
1223	tmp.sense = sense;
1224	tmp.data = data;
1225	tmp.currschedslot = 0;
1226	tmp.sel_t = -1;
1227
1228	if (scsi_probe(&tmp) == 0)
1229		return ENXIO;
1230	adapt = tmp;
1231	return 0;
1232}
1233