fd_asm.s revision 457:d8f2995c64aa
1/*
2 * CDDL HEADER START
3 *
4 * The contents of this file are subject to the terms of the
5 * Common Development and Distribution License, Version 1.0 only
6 * (the "License").  You may not use this file except in compliance
7 * with the License.
8 *
9 * You can obtain a copy of the license at usr/src/OPENSOLARIS.LICENSE
10 * or http://www.opensolaris.org/os/licensing.
11 * See the License for the specific language governing permissions
12 * and limitations under the License.
13 *
14 * When distributing Covered Code, include this CDDL HEADER in each
15 * file and include the License file at usr/src/OPENSOLARIS.LICENSE.
16 * If applicable, add the following below this CDDL HEADER, with the
17 * fields enclosed by brackets "[]" replaced with your own identifying
18 * information: Portions Copyright [yyyy] [name of copyright owner]
19 *
20 * CDDL HEADER END
21 */
22/*
23 * Copyright 2005 Sun Microsystems, Inc.  All rights reserved.
24 * Use is subject to license terms.
25 */
26
27#ident	"%Z%%M%	%I%	%E% SMI"
28
29/*
30 * This file contains no entry points which can be called directly from
31 * C and hence is of no interest to lint. However, we want to avoid the
32 * dreaded "Empty translation unit"  warning.
33 */
34
35#if defined(lint)
36#include <sys/types.h>
37
38/*ARGSUSED*/
39u_int
40fd_intr(caddr_t arg)
41{
42	return (0);
43}
44
45#else	/* lint */
46
47#include <sys/asm_linkage.h>
48#include <sys/fdreg.h>
49#include <sys/fdvar.h>
50#include "fd_assym.h"
51
52/*
53 * Since this is part of a Sparc "generic" module, it may be loaded during
54 * reconfigure time on systems that do not support the fast interrupt
55 * handler.  On these machines the symbol "impl_setintreg_on" will be
56 * undefined but we don't want to cause error messages when we load.
57 */
58	.weak	impl_setintreg_on
59	.type	impl_setintreg_on, #function
60	.weak	fd_softintr_cookie
61	.type	fd_softintr_cookie, #object
62
63#define	Tmp2	%l4	/* temp register prior to dispatch to right opmode */
64#define	Reg	%l4	/* pointer to the chip's registers */
65#define	Fdc	%l3	/* pointer to fdctlr structure */
66#define	Adr	%l5	/* data address pointer */
67#define	Len	%l6	/* data length counter */
68#define	Tmp	%l7	/* general scratch */
69#define	TRIGGER	0x33
70	ENTRY(fd_intr)		! fd standard interrupt handler
71	save	%sp, -SA(MINFRAME), %sp
72	!
73	! Traverse the list of controllers until we find the first
74	! controller expecting an interrupt. Unfortunately, the
75	! 82072 floppy controller really doesn't have a way to tell
76	! you that it is interrupting.
77	!
78	set	fdctlrs, Fdc		! load list of controllers
79	ldn	[Fdc], Fdc		! get the first in the list...
801:	tst	Fdc			! do we have any more to check
81	bz	.panic			! Nothing to service. Panic
82	nop
83
843:	ldub	[Fdc + FD_OPMODE], Tmp2	! load opmode into Tmp2
85	and	Tmp2, 0x3, Tmp2		! opmode must be 1, 2, or 3
86	tst	Tmp2			! non-zero?
87	bnz	.mutex_enter		! yes!
88	nop
89	ldn	[Fdc + FD_NEXT], Tmp	! Try next ctlr...
90	tst	Tmp
91	bnz,a	1b
92	mov	Tmp, Fdc
93					! no more controllers
94	mov	0x2, Tmp2		! must be spurious or "ready" int
95.mutex_enter:
96	!
97	! grab high level mutex for this controller
98	!
99	sethi	%hi(asm_mutex_spin_enter), %l7
100	jmpl	%l7 + %lo(asm_mutex_spin_enter), %l7
101	add	Fdc, FD_HILOCK, %l6
102	!
103	! dispatch to correct handler
104	!
105	cmp	Tmp2, 3			!case 3: results ?
106	be,a	.opmode3		! yes...
107	ldn	[Fdc + FD_REG], Reg	! load pointer to h/w registers
108	cmp	Tmp2, 2			!case 2: seek/recalibrate ?
109	be	.opmode2		! yes..
110	ldn	[Fdc + FD_REG], Reg	! load pointer to h/w registers
111	!
112	! opmode 1:
113	! read/write/format data-xfer case - they have a result phase
114	!
115.opmode1:
116	ld	[Fdc + FD_RLEN], Len
117	!
118	! XXX- test for null raddr
119	!
120	ldn	[Fdc + FD_RADDR], Adr
121
122	!
123	! while the fifo ready bit set, then data/status available
124	!
1251:	ldub	[Reg], Tmp		! get csr
126	andcc	Tmp, RQM, %g0		!
127	be	4f			! branch if bit clear
128	andcc	Tmp, NDM, %g0		! NDM set means data
129	be	7f			! if not set, it is status time
130	andcc	Tmp, DIO, %g0		! check for input vs. output data
131	be	2f			!
132	sub	Len, 0x1, Len		! predecrement length...
133	ldub	[Reg + 0x1], Tmp	! DIO set, *addr = *fifo
134	b	3f			!
135	stb	Tmp, [Adr]		!
1362:	ldsb	[Adr], Tmp		! *fifo = *addr
137	stb	Tmp, [Reg + 0x1]	!
1383:	tst	Len			! if (len == 0) send TC
139	bne	1b			! branch if not....
140	add	Adr, 0x1, Adr		!
141	b	6f			!
142	.empty				!
143	!
144	! save updated len, addr
145	!
1464:	st	Len, [Fdc + FD_RLEN]
147	b	.out			! not done yet, return
148	stn	Adr, [Fdc + FD_RADDR]
149	!
150	! END OF TRANSFER - if read/write, toggle the TC
151	! bit in AUXIO_REG then save status and set state = 3.
152	!
1535:
154	!
155	! Stash len and addr before they get lost
156	!
157	st	Len, [Fdc + FD_RLEN]
1586:	stn	Adr, [Fdc + FD_RADDR]
159	!
160	! Begin TC delay...
161	! Old comment:
162	!	five nops provide 100ns of delay at 10MIPS to ensure
163	!	TC is wide enough at slowest possible floppy clock
164	!	(500ns @ 250Kbps).
165	!
166	! I gather this mean that we have to give 100ns delay for TC.
167	!
168	! At 100 Mips, that would be 1 * 10 (10) nops.
169	!
170
171	ldn	[Fdc + FD_AUXIOVA], Adr
172	ldub	[Fdc + FD_AUXIODATA], Tmp2
173	ldub	[Adr], Tmp
174	or	Tmp, Tmp2, Tmp
175	stb	Tmp, [Adr]
176	nop; nop; nop; nop; nop; nop; nop; nop; nop; nop	! 10 nops
177	!
178	! End TC delay...now clear the TC bit
179	!
180	ldub	[Fdc + FD_AUXIODATA2], Tmp2
181	andn	Tmp, Tmp2, Tmp
182	stb	Tmp, [Adr]
183
184	!
185	! set opmode to 3 to indicate going into status mode
186	!
187	mov	3, Tmp
188	b	.out
189	stb	Tmp, [Fdc + FD_OPMODE]
190	!
191	! error status state: save old pointers, go direct to result snarfing
192	!
1937:	st	Len, [Fdc + FD_RLEN]
194	stn	Adr, [Fdc + FD_RADDR]
195	mov	0x3, Tmp
196	b	.opmode3
197	stb	Tmp, [Fdc + FD_OPMODE]
198	!
199	! opmode 2:
200	! recalibrate/seek - no result phase, must do sense interrupt status.
201	!
202.opmode2:
203	ldub	[Reg], Tmp			! Tmp = *csr
2041:	andcc	Tmp, CB, %g0			! is CB set?
205	bne	1b				! yes, keep waiting
206	ldub	[Reg], Tmp			!! Tmp = *csr
207	!
208	! wait!!! should we check rqm first???  ABSOLUTELY YES!!!!
209	!
2101:	andcc	Tmp, RQM, %g0		!
211	be,a	1b			! branch if bit clear
212	ldub	[Reg], Tmp		! busy wait until RQM set
213	mov	SNSISTAT, Tmp		! cmd for SENSE_INTERRUPT_STATUS
214	stb	Tmp, [Reg + 0x1]
215	!
216	! NOTE: we ignore DIO here, assume it is set before RQM!
217	!
218	ldub	[Reg], Tmp			! busy wait until RQM set
2191:	andcc	Tmp, RQM, Tmp
220	be,a	1b				! branch if bit clear
221	ldub	[Reg], Tmp			! busy wait until RQM set
222	!
223	! fdc->c_csb.csb_rslt[0] = *fifo;
224	!
225	ldub	[Reg + 0x1], Tmp
226	stb	Tmp, [Fdc + FD_RSLT]
227	ldub	[Reg], Tmp			! busy wait until RQM set
2281:	andcc	Tmp, RQM, Tmp
229	be,a	1b				! branch if bit clear
230	ldub	[Reg], Tmp			! busy wait until RQM set
231	!
232	! fdc->c_csb.csb_rslt[1] = *fifo;
233	!
234	ldub	[Reg + 0x1], Tmp
235	b	.notify
236	stb	Tmp, [Fdc + FD_RSLT + 1]
237	!
238	! case 3: result mode
239	! We are in result mode make sure all status bytes are read out
240	!
241	! We have to have *both* RQM and DIO set.
242	!
243.opmode3:
244	add	Fdc, FD_RSLT, Adr		! load address of csb->csb_rslt
245	add	Adr, 10, Len			! put an upper bound on it..
246	ldub	[Reg], Tmp			!
2471:	andcc	Tmp, CB, %g0			! is CB set?
248	be	.notify				! no, jump around, must be done
249	andcc	Tmp, RQM, %g0			! check for RQM in delay slot
250	be,a	1b				! No RQM, go back
251	ldub	[Reg], Tmp			! and load control reg in delay
252	andcc	Tmp, DIO, %g0			! DIO set?
253	be,a	1b				! No DIO, go back
254	ldub	[Reg], Tmp			! and load control reg in delay
255	!
256	! CB && DIO && RQM all true.
257	! Time to get a byte.
258	!
259	ldub	[Reg + 0x1], Tmp		! *fifo into Tmp
260	cmp	Adr, Len			! already at our limit?
261	bge,a	1b				! Yes, go back..
262	ldub	[Reg], Tmp			! and load control reg in delay
263	stb	Tmp, [Adr]			! store new byte
264	add	Adr, 1, Adr			! increment address
265	b	1b				! and pop back to the top
266	ldub	[Reg], Tmp			! and load control reg in delay
267
268	!
269	! schedule 2nd stage interrupt
270	!
271.notify:
272	!
273	! if fast traps are enabled, use the platform dependent
274	! impl_setintreg_on function.
275	!
276	ldub    [Fdc + FD_FASTTRAP], Tmp
277	tst     Tmp
278	bnz	.fast
279	nop
280
281	!
282	! fast traps are not in use.  Do not schedule the soft interrupt
283	! at this time.  Wait to trigger it at the end of the handler
284	! when the mutexes have been released
285	!
286	mov   	TRIGGER, Tmp2
287	b	.out
288	nop
289
290	!
291	! fast traps are enabled.  Schedule the soft interrupt.
292	! impl_setintreg uses %l4-%l7
293	!
294.fast:	sethi   %hi(fd_softintr_cookie), %l6
295	sethi	%hi(impl_setintreg_on), %l7
296	jmpl	%l7 + %lo(impl_setintreg_on), %l7
297	ld      [%l6 + %lo(fd_softintr_cookie)], %l6
298	!
299	! set new opmode to 4
300	!
301	mov	0x4, Tmp
302	stb	Tmp, [Fdc + FD_OPMODE]
303
304	!
305	! and fall through to exit
306	!
307.out:
308	!
309	! update high level interrupt counter...
310	!
311	ldn	[Fdc + FD_HIINTCT], Adr
312	tst	Adr
313	be,a	1f
314	nop
315	ld	[Adr], Tmp
316	inc	Tmp
317	st	Tmp, [Adr]
3181:
319	!
320	! Release mutex
321	!
322	sethi	%hi(asm_mutex_spin_exit), %l7
323	jmpl	%l7 + %lo(asm_mutex_spin_exit), %l7
324	add	Fdc, FD_HILOCK, %l6
325
326	!
327	! schedule the soft interrupt if needed
328	!
329	cmp	Tmp2, TRIGGER
330	bne	.end
331	nop
332
333   	!
334	! set new opmode to 4
335        !
336	mov     0x4, Tmp
337        stb     Tmp, [Fdc + FD_OPMODE]
338
339	! invoke ddi_trigger_softintr.  load
340	! softid parameter in the delay slot
341	!
342	call	ddi_trigger_softintr
343	ldn	[Fdc + FD_SOFTID], %o0
344
345.end:	mov	1, %i0
346	ret
347	restore
348	SET_SIZE(fd_intr)
349
350.panic:
351        ! invoke a kernel panic
352        sethi   %hi(panic_msg), %o1
353        ldn    [%o1 + %lo(panic_msg)], %o1
354        mov     3, %o0
355        call    cmn_err
356	nop
357
358
359#endif  /* lint */
360