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