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