Merge branch 'vendor/LIBARCHIVE'
[dragonfly.git] / sys / platform / pc32 / isa / ipl.s
1 /*-
2  * Copyright (c) 1989, 1990 William F. Jolitz.
3  * Copyright (c) 1990 The Regents of the University of California.
4  * All rights reserved.
5  *
6  * This code is derived from software contributed to Berkeley by
7  * William Jolitz.
8  *
9  * Redistribution and use in source and binary forms, with or without
10  * modification, are permitted provided that the following conditions
11  * are met:
12  * 1. Redistributions of source code must retain the above copyright
13  *    notice, this list of conditions and the following disclaimer.
14  * 2. Redistributions in binary form must reproduce the above copyright
15  *    notice, this list of conditions and the following disclaimer in the
16  *    documentation and/or other materials provided with the distribution.
17  * 3. All advertising materials mentioning features or use of this software
18  *    must display the following acknowledgement:
19  *      This product includes software developed by the University of
20  *      California, Berkeley and its contributors.
21  * 4. Neither the name of the University nor the names of its contributors
22  *    may be used to endorse or promote products derived from this software
23  *    without specific prior written permission.
24  *
25  * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
26  * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
27  * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
28  * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
29  * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
30  * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
31  * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
32  * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
33  * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
34  * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
35  * SUCH DAMAGE.
36  *
37  *      @(#)ipl.s
38  *
39  * $FreeBSD: src/sys/i386/isa/ipl.s,v 1.32.2.3 2002/05/16 16:03:56 bde Exp $
40  * $DragonFly: src/sys/platform/pc32/isa/ipl.s,v 1.28 2007/01/22 19:37:04 corecode Exp $
41  */
42
43 #include "use_npx.h"
44
45 #include <machine/asmacros.h>
46 #include <machine/segments.h>
47 #include <machine/ipl.h>
48 #include <machine/lock.h>
49 #include <machine/psl.h>
50 #include <machine/trap.h>
51  
52 #include "assym.s"
53
54 /*
55  * AT/386
56  * Vector interrupt control section
57  *
58  *  ipending    - Pending interrupts (set when a masked interrupt occurs)
59  *  spending    - Pending software interrupts
60  */
61         .data
62         ALIGN_DATA
63
64         .globl          fastunpend_count
65 fastunpend_count:       .long   0
66
67         .text
68         SUPERALIGN_TEXT
69
70         /*
71          * GENERAL NOTES
72          *
73          *      - fast interrupts are always called with a critical section
74          *        held
75          *
76          *      - we release our critical section when scheduling interrupt
77          *        or softinterrupt threads in order so they can preempt
78          *        (unless we are called manually from a critical section, in
79          *        which case there will still be a critical section and
80          *        they won't preempt anyway).
81          *
82          *      - TD_NEST_COUNT prevents splz from nesting too deeply within
83          *        itself.  It is *not* actually an interrupt nesting count.
84          *        PCPU(intr_nesting_level) is an interrupt nesting count.
85          *
86          *      - We have to be careful in regards to local interrupts
87          *        occuring simultaniously with our doreti and splz 
88          *        processing.
89          */
90
91         /*
92          * DORETI
93          *
94          * Handle return from interrupts, traps and syscalls.  This function
95          * checks the cpl for unmasked pending interrupts (fast, normal, or
96          * soft) and schedules them if appropriate, then irets.
97          *
98          * If we are in a critical section we cannot run any pending ints
99          * nor can be play with mp_lock.
100          *
101          * NOTE: Since SPLs no longer exist, all callers of this function
102          * push $0 for the CPL.  HOWEVER, we *STILL* use the cpl mask within
103          * this function to mark fast interrupts which could not be dispatched
104          * do to the unavailability of the BGL.
105          */
106         SUPERALIGN_TEXT
107         .globl  doreti
108         .type   doreti,@function
109 doreti:
110         FAKE_MCOUNT(bintr)              /* init "from" bintr -> doreti */
111         popl    %eax                    /* cpl to restore XXX */
112         movl    $0,%eax                 /* irq mask unavailable due to BGL */
113         movl    PCPU(curthread),%ebx
114         cli                             /* interlock with TDPRI_CRIT */
115         cmpl    $0,PCPU(reqflags)       /* short cut if nothing to do */
116         je      5f
117         cmpl    $TDPRI_CRIT,TD_PRI(%ebx) /* can't unpend if in critical sec */
118         jge     5f
119         addl    $TDPRI_CRIT,TD_PRI(%ebx) /* force all ints to pending */
120 doreti_next:
121         sti                             /* allow new interrupts */
122         movl    %eax,%ecx               /* irq mask unavailable due to BGL */
123         notl    %ecx
124         cli                             /* disallow YYY remove */
125 #ifdef SMP
126         testl   $RQF_IPIQ,PCPU(reqflags)
127         jnz     doreti_ipiq
128         testl   $RQF_TIMER,PCPU(reqflags)
129         jnz     doreti_timer
130 #endif
131         testl   PCPU(fpending),%ecx     /* check for an unmasked fast int */
132         jnz     doreti_fast
133
134         testl   PCPU(ipending),%ecx     /* check for an unmasked slow int */
135         jnz     doreti_intr
136
137         movl    PCPU(spending),%ecx     /* check for a pending software int */
138         cmpl    $0,%ecx
139         jnz     doreti_soft
140
141         testl   $RQF_AST_MASK,PCPU(reqflags) /* any pending ASTs? */
142         jz      2f
143         testl   $PSL_VM,TF_EFLAGS(%esp)
144         jz      1f
145         cmpl    $1,in_vm86call          /* YYY make per 'cpu'? */
146         jnz     doreti_ast
147 1:
148         /* ASTs are only applicable when returning to userland */
149         testb   $SEL_RPL_MASK,TF_CS(%esp)
150         jnz     doreti_ast
151 2:
152         /*
153          * Nothing left to do, finish up.  Interrupts are still disabled.
154          * %eax contains the mask of IRQ's that are not available due to
155          * BGL requirements.  We can only clear RQF_INTPEND if *ALL* pending
156          * interrupts have been processed.
157          */
158         subl    $TDPRI_CRIT,TD_PRI(%ebx)        /* interlocked with cli */
159         testl   %eax,%eax
160         jnz     5f
161         andl    $~RQF_INTPEND,PCPU(reqflags)
162 5:
163         MEXITCOUNT
164
165         /*
166          * Restore the segment registers.  Since segment register values
167          * can be set from user mode, this can result in a kernel mode
168          * exception.  The trap code will revector to the *_fault code
169          * which then sets up a T_PROTFLT signal.  If the signal is
170          * sent to userland, sendsig() will automatically clean up all
171          * the segment registers to avoid a loop.
172          */
173         .globl  doreti_popl_gs
174         .globl  doreti_popl_fs
175         .globl  doreti_popl_es
176         .globl  doreti_popl_ds
177         .globl  doreti_iret
178         .globl  doreti_syscall_ret
179 doreti_syscall_ret:
180 doreti_popl_gs:
181         popl    %gs
182 doreti_popl_fs:
183         popl    %fs
184 doreti_popl_es:
185         popl    %es
186 doreti_popl_ds:
187         popl    %ds
188         popal
189         addl    $3*4,%esp       /* xflags, trap, err */
190 doreti_iret:
191         iret
192
193         ALIGN_TEXT
194         .globl  doreti_iret_fault
195 doreti_iret_fault:
196         subl    $3*4,%esp       /* xflags, trap, err */
197         pushal
198         pushl   %ds
199         .globl  doreti_popl_ds_fault
200 doreti_popl_ds_fault:
201         pushl   %es
202         .globl  doreti_popl_es_fault
203 doreti_popl_es_fault:
204         pushl   %fs
205         .globl  doreti_popl_fs_fault
206 doreti_popl_fs_fault:
207         pushl   %gs
208         .globl  doreti_popl_gs_fault
209 doreti_popl_gs_fault:
210         movl    $0,TF_ERR(%esp) /* XXX should be the error code */
211         movl    $T_PROTFLT,TF_TRAPNO(%esp)
212         jmp     alltraps_with_regs_pushed
213
214         /*
215          * FAST interrupt pending.  NOTE: stack context holds frame structure
216          * for fast interrupt procedure, do not do random pushes or pops!
217          */
218         ALIGN_TEXT
219 doreti_fast:
220         andl    PCPU(fpending),%ecx     /* only check fast ints */
221         bsfl    %ecx, %ecx              /* locate the next dispatchable int */
222         btrl    %ecx, PCPU(fpending)    /* is it really still pending? */
223         jnc     doreti_next
224         pushl   %eax                    /* save IRQ mask unavailable for BGL */
225                                         /* NOTE: is also CPL in frame */
226 #if 0
227 #ifdef SMP
228         pushl   %ecx                    /* save ecx */
229         call    try_mplock
230         popl    %ecx
231         testl   %eax,%eax
232         jz      1f
233         /* MP lock successful */
234 #endif
235 #endif
236         incl    PCPU(intr_nesting_level)
237         call    dofastunpend            /* unpend fast intr %ecx */
238         decl    PCPU(intr_nesting_level)
239 #if 0
240 #ifdef SMP
241         call    rel_mplock
242 #endif
243 #endif
244         popl    %eax
245         jmp     doreti_next
246 1:
247         btsl    %ecx, PCPU(fpending)    /* oops, couldn't get the MP lock */
248         popl    %eax                    /* add to temp. cpl mask to ignore */
249         orl     PCPU(fpending),%eax
250         jmp     doreti_next
251
252         /*
253          *  INTR interrupt pending
254          *
255          *  Temporarily back-out our critical section to allow an interrupt
256          *  preempt us when we schedule it.  Bump intr_nesting_level to
257          *  prevent the switch code from recursing via splz too deeply.
258          */
259         ALIGN_TEXT
260 doreti_intr:
261         andl    PCPU(ipending),%ecx     /* only check normal ints */
262         bsfl    %ecx, %ecx              /* locate the next dispatchable int */
263         btrl    %ecx, PCPU(ipending)    /* is it really still pending? */
264         jnc     doreti_next
265         pushl   %eax
266         pushl   %ecx
267         incl    TD_NEST_COUNT(%ebx)     /* prevent doreti/splz nesting */
268         subl    $TDPRI_CRIT,TD_PRI(%ebx) /* so we can preempt */
269         call    sched_ithd              /* YYY must pull in imasks */
270         addl    $TDPRI_CRIT,TD_PRI(%ebx)
271         decl    TD_NEST_COUNT(%ebx)
272         addl    $4,%esp
273         popl    %eax
274         jmp     doreti_next
275
276         /*
277          *  SOFT interrupt pending
278          *
279          *  Temporarily back-out our critical section to allow an interrupt
280          *  preempt us when we schedule it.  Bump intr_nesting_level to
281          *  prevent the switch code from recursing via splz too deeply.
282          */
283         ALIGN_TEXT
284 doreti_soft:
285         bsfl    %ecx,%ecx               /* locate the next pending softint */
286         btrl    %ecx,PCPU(spending)     /* make sure its still pending */
287         jnc     doreti_next
288         addl    $FIRST_SOFTINT,%ecx     /* actual intr number */
289         pushl   %eax
290         pushl   %ecx
291         incl    TD_NEST_COUNT(%ebx)     /* prevent doreti/splz nesting */
292         subl    $TDPRI_CRIT,TD_PRI(%ebx) /* so we can preempt */
293         call    sched_ithd              /* YYY must pull in imasks */
294         addl    $TDPRI_CRIT,TD_PRI(%ebx)
295         decl    TD_NEST_COUNT(%ebx)
296         addl    $4,%esp
297         popl    %eax
298         jmp     doreti_next
299
300         /*
301          * AST pending.  We clear RQF_AST_SIGNAL automatically, the others
302          * are cleared by the trap as they are processed.
303          *
304          * Temporarily back-out our critical section because trap() can be
305          * a long-winded call, and we want to be more syscall-like.  
306          *
307          * YYY theoretically we can call lwkt_switch directly if all we need
308          * to do is a reschedule.
309          */
310 doreti_ast:
311         andl    $~(RQF_AST_SIGNAL|RQF_AST_UPCALL),PCPU(reqflags)
312         sti
313         movl    %eax,%esi               /* save cpl (can't use stack) */
314         movl    $T_ASTFLT,TF_TRAPNO(%esp)
315         pushl   %esp                    /* pass frame by reference */
316         subl    $TDPRI_CRIT,TD_PRI(%ebx)
317         call    trap
318         addl    $TDPRI_CRIT,TD_PRI(%ebx)
319         addl    $4,%esp
320         movl    %esi,%eax               /* restore cpl for loop */
321         jmp     doreti_next
322
323 #ifdef SMP
324         /*
325          * IPIQ message pending.  We clear RQF_IPIQ automatically.
326          */
327 doreti_ipiq:
328         movl    %eax,%esi               /* save cpl (can't use stack) */
329         incl    PCPU(intr_nesting_level)
330         andl    $~RQF_IPIQ,PCPU(reqflags)
331         subl    $8,%esp                 /* add dummy vec and ppl */
332         pushl   %esp                    /* pass frame by reference */
333         call    lwkt_process_ipiq_frame
334         addl    $12,%esp
335         decl    PCPU(intr_nesting_level)
336         movl    %esi,%eax               /* restore cpl for loop */
337         jmp     doreti_next
338
339 doreti_timer:
340         movl    %eax,%esi               /* save cpl (can't use stack) */
341         incl    PCPU(intr_nesting_level)
342         andl    $~RQF_TIMER,PCPU(reqflags)
343         subl    $8,%esp                 /* add dummy vec and ppl */
344         pushl   %esp                    /* pass frame by reference */
345         call    lapic_timer_process_frame
346         addl    $12,%esp
347         decl    PCPU(intr_nesting_level)
348         movl    %esi,%eax               /* restore cpl for loop */
349         jmp     doreti_next
350
351 #endif
352
353         /*
354          * SPLZ() a C callable procedure to dispatch any unmasked pending
355          *        interrupts regardless of critical section nesting.  ASTs
356          *        are not dispatched.
357          *
358          *        Use %eax to track those IRQs that could not be processed
359          *        due to BGL requirements.
360          */
361         SUPERALIGN_TEXT
362
363 ENTRY(splz)
364         pushfl
365         pushl   %ebx
366         movl    PCPU(curthread),%ebx
367         addl    $TDPRI_CRIT,TD_PRI(%ebx)
368         movl    $0,%eax
369
370 splz_next:
371         cli
372         movl    %eax,%ecx               /* ecx = ~CPL */
373         notl    %ecx
374 #ifdef SMP
375         testl   $RQF_IPIQ,PCPU(reqflags)
376         jnz     splz_ipiq
377         testl   $RQF_TIMER,PCPU(reqflags)
378         jnz     splz_timer
379 #endif
380         testl   PCPU(fpending),%ecx     /* check for an unmasked fast int */
381         jnz     splz_fast
382
383         testl   PCPU(ipending),%ecx
384         jnz     splz_intr
385
386         movl    PCPU(spending),%ecx
387         cmpl    $0,%ecx
388         jnz     splz_soft
389
390         subl    $TDPRI_CRIT,TD_PRI(%ebx)
391
392         /*
393          * Nothing left to do, finish up.  Interrupts are still disabled.
394          * If our mask of IRQs we couldn't process due to BGL requirements
395          * is 0 then there are no pending interrupt sources left and we
396          * can clear RQF_INTPEND.
397          */
398         testl   %eax,%eax
399         jnz     5f
400         andl    $~RQF_INTPEND,PCPU(reqflags)
401 5:
402         popl    %ebx
403         popfl
404         ret
405
406         /*
407          * FAST interrupt pending
408          */
409         ALIGN_TEXT
410 splz_fast:
411         andl    PCPU(fpending),%ecx     /* only check fast ints */
412         bsfl    %ecx, %ecx              /* locate the next dispatchable int */
413         btrl    %ecx, PCPU(fpending)    /* is it really still pending? */
414         jnc     splz_next
415         pushl   %eax
416 #if 0
417 #ifdef SMP
418         pushl   %ecx
419         call    try_mplock
420         popl    %ecx
421         testl   %eax,%eax
422         jz      1f
423 #endif
424 #endif
425         incl    PCPU(intr_nesting_level)
426         call    dofastunpend            /* unpend fast intr %ecx */
427         decl    PCPU(intr_nesting_level)
428 #if 0
429 #ifdef SMP
430         call    rel_mplock
431 #endif
432 #endif
433         popl    %eax
434         jmp     splz_next
435 1:
436         btsl    %ecx, PCPU(fpending)    /* oops, couldn't get the MP lock */
437         popl    %eax
438         orl     PCPU(fpending),%eax
439         jmp     splz_next
440
441         /*
442          *  INTR interrupt pending
443          *
444          *  Temporarily back-out our critical section to allow the interrupt
445          *  preempt us.
446          */
447         ALIGN_TEXT
448 splz_intr:
449         andl    PCPU(ipending),%ecx     /* only check normal ints */
450         bsfl    %ecx, %ecx              /* locate the next dispatchable int */
451         btrl    %ecx, PCPU(ipending)    /* is it really still pending? */
452         jnc     splz_next
453         sti
454         pushl   %eax
455         pushl   %ecx
456         subl    $TDPRI_CRIT,TD_PRI(%ebx)
457         incl    TD_NEST_COUNT(%ebx)     /* prevent doreti/splz nesting */
458         call    sched_ithd              /* YYY must pull in imasks */
459         addl    $TDPRI_CRIT,TD_PRI(%ebx)
460         decl    TD_NEST_COUNT(%ebx)     /* prevent doreti/splz nesting */
461         addl    $4,%esp
462         popl    %eax
463         jmp     splz_next
464
465         /*
466          *  SOFT interrupt pending
467          *
468          *  Temporarily back-out our critical section to allow the interrupt
469          *  preempt us.
470          */
471         ALIGN_TEXT
472 splz_soft:
473         bsfl    %ecx,%ecx               /* locate the next pending softint */
474         btrl    %ecx,PCPU(spending)     /* make sure its still pending */
475         jnc     splz_next
476         addl    $FIRST_SOFTINT,%ecx     /* actual intr number */
477         sti
478         pushl   %eax
479         pushl   %ecx
480         subl    $TDPRI_CRIT,TD_PRI(%ebx)
481         incl    TD_NEST_COUNT(%ebx)     /* prevent doreti/splz nesting */
482         call    sched_ithd              /* YYY must pull in imasks */
483         addl    $TDPRI_CRIT,TD_PRI(%ebx)
484         decl    TD_NEST_COUNT(%ebx)     /* prevent doreti/splz nesting */
485         addl    $4,%esp
486         popl    %eax
487         jmp     splz_next
488
489 #ifdef SMP
490 splz_ipiq:
491         andl    $~RQF_IPIQ,PCPU(reqflags)
492         pushl   %eax
493         call    lwkt_process_ipiq
494         popl    %eax
495         jmp     splz_next
496
497 splz_timer:
498         andl    $~RQF_TIMER,PCPU(reqflags)
499         pushl   %eax
500         call    lapic_timer_process
501         popl    %eax
502         jmp     splz_next
503 #endif
504
505         /*
506          * dofastunpend(%ecx:intr)
507          *
508          * A FAST interrupt previously made pending can now be run,
509          * execute it by pushing a dummy interrupt frame and 
510          * calling ithread_fast_handler to execute or schedule it.
511          * 
512          * ithread_fast_handler() returns 0 if it wants us to unmask
513          * further interrupts.
514          */
515 #define PUSH_DUMMY                                                      \
516         pushfl ;                /* phys int frame / flags */            \
517         pushl   %cs ;           /* phys int frame / cs */               \
518         pushl   12(%esp) ;      /* original caller eip */               \
519         pushl   $0 ;            /* dummy error code */                  \
520         pushl   $0 ;            /* dummy trap type */                   \
521         pushl   $0 ;            /* dummy xflags */                      \
522         subl    $13*4,%esp ;    /* pushal + 4 seg regs (dummy) + CPL */ \
523
524 #define POP_DUMMY                                                       \
525         addl    $19*4,%esp ;                                            \
526
527 dofastunpend:
528         pushl   %ebp                    /* frame for backtrace */
529         movl    %esp,%ebp
530         PUSH_DUMMY
531         pushl   %ecx                    /* last part of intrframe = intr */
532         incl    fastunpend_count
533         pushl   %esp                    /* pass frame by reference */
534         call    ithread_fast_handler    /* returns 0 to unmask */
535         addl    $4,%esp                 /* remove pointer, now intr on top */
536         cmpl    $0,%eax
537         jnz     1f
538         movl    MachIntrABI + MACHINTR_INTREN, %eax
539         call    *%eax                   /* MachIntrABI.intren(intr) */
540 1:
541         addl    $4,%esp
542         POP_DUMMY
543         popl    %ebp
544         ret
545