Setting up repository
[linux-libre-firmware.git] / ath9k_htc / sboot / magpie_1_1 / sboot / athos / src / xtos / int-lowpri-dispatcher.S
1 // Level-one interrupt dispatcher (user vectored handler)
2
3 // Copyright (c) 1999-2010 Tensilica Inc.
4 //
5 // Permission is hereby granted, free of charge, to any person obtaining
6 // a copy of this software and associated documentation files (the
7 // "Software"), to deal in the Software without restriction, including
8 // without limitation the rights to use, copy, modify, merge, publish,
9 // distribute, sublicense, and/or sell copies of the Software, and to
10 // permit persons to whom the Software is furnished to do so, subject to
11 // the following conditions:
12 //
13 // The above copyright notice and this permission notice shall be included
14 // in all copies or substantial portions of the Software.
15 //
16 // THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
17 // EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
18 // MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
19 // IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
20 // CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
21 // TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
22 // SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
23
24 #include <xtensa/coreasm.h>
25 #include <xtensa/config/specreg.h>
26 #include "xtos-internal.h"
27 #include "interrupt-pri.h"
28
29 #if XCHAL_HAVE_EXCEPTIONS && XCHAL_HAVE_INTERRUPTS
30
31
32         /*
33          *  Macros to slightly reduce the number of #if statements in the code:
34          */
35
36 /*  This is set (for #if only) if there is only ONE interrupt configured at level one:  */
37 # define XTOS_SINGLE_INT        defined(XCHAL_INTLEVEL1_NUM)
38
39 /*  Simplify the #if's around saving and restoring of SAR ('#' is a comment char):  */
40 # if ((XTOS_SUBPRI_ORDER == XTOS_SPO_ZERO_LO) || (XTOS_INT_FAIRNESS && XTOS_SUBPRI)) && !XTOS_SINGLE_INT
41 #  define NEEDSAR               /* need SAR saved early w/ints locked */
42 #  define LATESAR       #       /* need SAR saved late w/ints unlocked */
43 # else
44 #  define NEEDSAR       #       /* need SAR saved early w/ints locked */
45 #  define LATESAR               /* need SAR saved late w/ints unlocked */
46 # endif
47
48 /*  Simplify the #if's around fairness-specific code ('#' is a comment char):  */
49 # if XTOS_INT_FAIRNESS
50 #  define IFFAIR                /* for code enabled only for fairness */
51 #  define NOFAIR        #       /* for code enabled only without fairness */
52 # else
53 #  define IFFAIR        #       /* for code enabled only for fairness */
54 #  define NOFAIR                /* for code enabled only without fairness */
55 # endif
56
57
58         //  NOTE:  something equivalent to the following vector is executed
59         //  before entering this handler (see user-vector.S).
60 //_UserExceptionVector:
61 //      addi    a1, a1, -ESF_TOTALSIZE  // allocate exception stack frame, etc.
62 //      s32i    a2, a1, UEXC_a2
63 //      s32i    a3, a1, UEXC_a3
64 //      movi    a3, _xtos_exc_handler_table
65 //      rsr     a2, EXCCAUSE
66 //      addx4   a2, a2, a3
67 //      l32i    a2, a2, 0
68 //      s32i    a4, a1, UEXC_a4
69 //      jx      a2              // jump to cause-specific handler
70
71         .global _need_user_vector_      // pull-in real user vector (tiny LSP)
72
73         .text
74         .align  4
75         .global _xtos_l1int_handler
76 _xtos_l1int_handler:
77         //  HERE:  a2, a3, a4 have been saved to exception stack frame allocated with a1 (sp).
78
79         s32i    a5, a1, UEXC_a5         // a5 will get clobbered by ENTRY after pseudo-CALL4
80                                         //   (a4..a15 spilled as needed; save if modified)
81
82 # if XCHAL_HAVE_XEA2
83
84         //  Set PS fields:
85         //      EXCM     = 0
86         //      WOE      = __XTENSA_CALL0_ABI__ ? 0 : 1
87         //      UM       = 1
88         //      INTLEVEL = EXCM_LEVEL
89         //      CALLINC  = __XTENSA_CALL0_ABI__ ? 0 : 1
90         //      OWB      = 0  (actual value is a don't care)
91
92 #  ifdef __XTENSA_CALL0_ABI__
93         movi    a2, PS_UM|PS_INTLEVEL(XCHAL_EXCM_LEVEL)
94 #  else
95         movi    a2, PS_UM|PS_INTLEVEL(XCHAL_EXCM_LEVEL)|PS_WOE|PS_CALLINC(1)    // CALL4 emulation
96 #  endif
97         rsr     a3, EPC_1
98         xsr     a2, PS
99
100 #  ifdef __XTENSA_WINDOWED_ABI__
101         //  HERE:  window overflows enabled, but NOT SAFE because we're not quite
102         //      in a valid windowed context (haven't restored a1 yet);
103         //      so don't cause any (by accessing only a0..a3) until we've saved critical state
104         //      and restored a1 (note: critical state already saved in a2 and a3):
105         //  NOTE:  saved EPC1 before causing any overflows, because overflows corrupt EPC1.
106 #  endif
107
108         s32i    a3, a1, UEXC_pc
109         s32i    a2, a1, UEXC_ps
110
111 # else /*if XEA1:*/
112
113         //  Would need to save & clear LCOUNT only with protection.  None here.
114         //  No need to save EXCVADDR or EXCCAUSE for low-priority interrupts.
115 #  if 1
116         rsr     a2, INTERRUPT                   // read INTERRUPT while PS.INTLEVEL is 1 and INTENABLE is intact
117         rsilft  a3, 1, XTOS_LOCKLEVEL           // lockout
118         s32i    a2, a1, UEXC_vpri               // save for interrupt computation
119         rsr     a2, INTENABLE
120         movi    a3, XTOS_UNLOCKABLE_MASK        // mask out level one, and high levels covered by XTOS_LOCKLEVEL if any,
121                                                 //  so we can run at PS.INTLEVEL=0 while manipulating INTENABLE
122         s32i    a2, a1, UEXC_sar                // save old INTENABLE, to handle the spurious interrupt case
123         and     a3, a2, a3                      // mask out selected interrupts
124         wsr     a3, INTENABLE                   // disable all interrupts up to and including XTOS_LOCKLEVEL
125 #  else
126         //  Using this alternate code requires extensive changes elsewhere;
127         //  its only advantage is potentially lowered latency of interrupts
128         //  of priority levels 2 thru XTOS_LOCKLEVEL:
129         movi    a2, _xtos_intstruct             // address of interrupt management globals
130         rsilft  a3, 1, XTOS_LOCKLEVEL           // lockout
131         l32i    a3, a2, XTOS_VPRI_ENABLED_OFS   // read previous _xtos_vpri_enabled
132         //interlock
133         s32i    a3, a1, UEXC_vpri               // save previous vpri
134         movi    a3, ~XCHAL_EXCM_MASK            // mask out all low-priority interrupts
135                                                 //  so we can run at PS.INTLEVEL=0 while ESF allocation not reflected in SP
136         //interlock
137         s32i    a3, a2, XTOS_VPRI_ENABLED_OFS   // set new _xtos_vpri_enabled (mask all low-priority interrupts)
138         l32i    a2, a2, XTOS_ENABLED_OFS        // read _xtos_enabled
139         //interlock
140         and     a3, a2, a3                      // mask out selected interrupts
141         wsr     a3, INTENABLE                   // disable all low-priority interrupts
142 #  endif
143         movi    a3, PS_WOE|PS_CALLINC(1)|PS_UM  // WOE=1, UM=1, INTLEVEL=0, CALLINC=1 (call4 emul), OWB=(dontcare)=0
144
145         //  NOTE:  could use XSR here if targeting T1040 or T1050 hardware (requiring slight sequence adjustment as for XEA2):
146         rsr     a2, PS
147         rsync   //NOT-ISA-DEFINED               // wait for WSR to INTENABLE to complete before clearing PS.INTLEVEL
148         wsr     a3, PS                          // PS.INTLEVEL=0, effective INTLEVEL (via INTENABLE) is XTOS_LOCKLEVEL (NOTA: LOWPRI_LEVELS)
149
150         //  HERE:  window overflows enabled, but NOT SAFE because we're not quite
151         //      in a valid windowed context (haven't restored a1 yet...);
152         //      so don't cause any (keep to a0..a3) until we've saved critical state and restored a1:
153
154         //  NOTE:  MUST SAVE EPC1 before causing any overflows, because overflows corrupt EPC1.
155         rsr     a3, EPC_1
156         s32i    a2, a1, UEXC_ps
157         s32i    a3, a1, UEXC_pc
158
159 # endif /* XEA1 */
160
161
162 # ifdef __XTENSA_CALL0_ABI__
163
164         s32i    a0, a1, UEXC_a0         // save the rest of the registers
165         s32i    a6, a1, UEXC_a6
166         s32i    a7, a1, UEXC_a7
167         s32i    a8, a1, UEXC_a8
168         s32i    a9, a1, UEXC_a9
169         s32i    a10, a1, UEXC_a10
170         s32i    a11, a1, UEXC_a11
171         s32i    a12, a1, UEXC_a12
172         s32i    a13, a1, UEXC_a13
173         s32i    a14, a1, UEXC_a14
174         s32i    a15, a1, UEXC_a15
175 #  if XTOS_DEBUG_PC
176         // TODO: setup return PC for call traceback through interrupt dispatch
177 #  endif
178
179         rsync                           // wait for WSR to PS to complete
180
181 # else  /* ! __XTENSA_CALL0_ABI__ */
182
183 #  if XTOS_CNEST
184         l32i    a2, a1, ESF_TOTALSIZE-20        // save nested-C-func call-chain ptr
185 #  endif
186         addi    a1, a1, ESF_TOTALSIZE   // restore sp (dealloc ESF) for sane stack again
187         rsync                           // wait for WSR to PS to complete
188
189         /*  HERE:  we can SAFELY get window overflows.
190          *
191          *  From here, registers a4..a15 automatically get spilled if needed.
192          *  They become a0..a11 after the ENTRY instruction.
193          *  Currently, we don't check whether or not these registers
194          *  get spilled, so we must save and restore any that we
195          *  modify.  We've already saved a4 and a5
196          *  which we modify as part of the pseudo-CALL.
197          *
198          *  IMPLEMENTATION NOTE:
199          *
200          *      The pseudo-CALL below effectively saves registers a2..a3
201          *      so that they are available again after the corresponding
202          *      RETW when returning from the exception handling.  We
203          *      could choose to put something like EPC1 or PS in
204          *      there, so they're available more quickly when
205          *      restoring.  HOWEVER, exception handlers may wish to
206          *      change such values, or anything on the exception stack
207          *      frame, and expect these to be restored as modified.
208          *
209          *      NOTA: future: figure out what's the best thing to put
210          *      in a2 and a3.  (candidate: a4 and a5 below; but what
211          *      if exception handler manipulates ARs, as in a syscall
212          *      handler.... oh well)
213          *
214          *
215          *  Now do the pseudo-CALL.
216          *  Make it look as if the code that got the exception made a
217          *  CALL4 to the exception handling code.  (We call
218          *  this the "pseudo-CALL".)
219          *
220          *  This pseudo-CALL is important and done this way:
221          *
222          *      1. There are only three ways to safely update the stack pointer
223          *         in the windowed ABI, such that window exceptions work correctly:
224          *         (a) spill all live windows to stack then switch to a new stack
225          *             (or, save the entire address register file and window
226          *              registers, which is likely even more expensive)
227          *         (b) use MOVSP (or equivalent)
228          *         (c) use ENTRY/RETW
229          *         Doing (a) is excessively expensive, and doing (b) here requires
230          *         copying 16 bytes back and forth which is also time-consuming;
231          *         whereas (c) is very efficient, so that's what we do here.
232          *
233          *      2. Normally we cannot do a pseudo-CALL8 or CALL12 here.
234          *         According to the
235          *         windowed ABI, a function must allocate enough space
236          *         for the largest call that it makes.  However, the
237          *         pseudo-CALL is executed in the context of the
238          *         function that happened to be executing at the time
239          *         the interrupt was taken, and that function might or
240          *         might not have allocated enough stack space for a
241          *         CALL8 or a CALL12.  If we try doing a pseudo-CALL8
242          *         or -CALL12 here, we corrupt the stack if the
243          *         interrupted function happened to not have allocated
244          *         space for such a call.
245          *
246          *      3. We set the return PC, but it's not strictly
247          *         necessary for proper operation.  It does make
248          *         debugging, ie. stack tracebacks, much nicer if it
249          *         can point to the interrupted code (not always
250          *         possible, eg. if interrupted code is in a different
251          *         GB than the interrupt handling code, which is
252          *         unlikely in a system without protection where
253          *         interrupt handlers and general application code are
254          *         typically linked together).
255          *
256          *  IMPORTANT:  Interrupts must stay disabled while doing the pseudo-CALL,
257          *  or at least until after the ENTRY instruction, because SP has been
258          *  restored to its original value that does not reflect the exception
259          *  stack frame's allocation.  An interrupt taken here would
260          *  corrupt the exception stack frame (ie. allocate another over it).
261          *  (High priority interrupts can remain enabled, they save and restore
262          *  all of their state and use their own stack or save area.)
263          *  For the same reason, we mustn't get any exceptions in this code
264          *  (other than window exceptions where noted) until ENTRY is done.
265          */
266
267         //  HERE:  may get a single window overflow (caused by the following instruction).
268
269 #  if XTOS_DEBUG_PC
270         movi    a4, 0xC0000000          // [for debug] for return PC computation below
271         or      a3, a4, a3              // [for debug] set upper two bits of return PC
272         addx2   a4, a4, a3              // [for debug] clear upper bit
273 #  else
274         movi    a4, 0                   // entry cannot cause overflow, cause it here
275 #  endif
276
277         .global _LevelOneInterrupt
278 _LevelOneInterrupt:                     // this label makes tracebacks through interrupts look nicer
279
280         _entry  a1, ESF_TOTALSIZE       // as if after a CALL4 (PS.CALLINC set to 1 above)
281
282         /*
283          *  The above ENTRY instruction does a number of things:
284          *
285          *      1. Because we're emulating CALL4, the ENTRY rotates windows
286          *         forward by 4 registers (as per 'ROTW +1'), so that
287          *         a4-a15 became a0-a11.  So now: a0-a11 are part of
288          *         the interrupted context to be preserved.  a0-a1
289          *         were already saved above when they were a4-a5.
290          *         a12-a15 are free to use as they're NOT part of the
291          *         interrupted context.  We don't need to save/restore
292          *         them, and they will get spilled if needed.
293          *
294          *      2. Updates SP (new a1), allocating the exception stack
295          *         frame in the new window, preserving the old a1 in
296          *         the previous window.
297          *
298          *      3. The underscore prefix prevents the assembler from
299          *         automatically aligning the ENTRY instruction on a
300          *         4-byte boundary, which could create a fatal gap in
301          *         the instruction stream.
302          *
303          *  At this point, ie. before we re-enable interrupts, we know the caller is
304          *  always live so we can safely modify a1 without using MOVSP (we can use MOVSP
305          *  but it will never cause an ALLOCA or underflow exception here).
306          *  So this is a good point to modify the stack pointer if we want eg. to
307          *  switch to an interrupt stack (if we do, we need to save the current SP
308          *  because certain things have been saved to that exception stack frame).
309          *  We couldn't do this easily before ENTRY, where the caller wasn't
310          *  necessarily live.
311          */
312
313 #  if 0 /*... non-nested interrupt ...*/
314         mov     ...some address register..., a1         // save ptr to original ESF
315         movi    a1, _interrupt_stack                    // switch stack
316 #  endif
317
318 # endif /* __XTENSA_CALL0_ABI__ */
319
320         /*
321          *  Now we can enable interrupts of higher virtual priority than the one(s)
322          *  being dispatched/processed here.  This may entail some software prioritization,
323          *  if so configured.
324          *  (Pseudo-CALL is complete, and SP reflects allocation of exception stack frame
325          *  or switch to new stack.)
326          */
327
328 # if XCHAL_HAVE_XEA2
329         rsilft  a15, XCHAL_EXCM_LEVEL, 1        // INTERRUPT reg *must* be read at PS.INTLEVEL<=1
330                                                 // (otherwise it might get higher pri ints)
331 #  define CUR_INTLEVEL  1
332 # else
333 #  define CUR_INTLEVEL  0
334 # endif
335         /*  At this point, PS.INTLEVEL is:  0 if XEA1, 1 if XEA2  (per CUR_INTLEVEL)  */
336
337
338         /*****************  Dispatch low-priority interrupts to service  *****************/
339
340         /* HERE: We may get up to 3 window overflows on the following instruction.
341          *
342          *    The worst case is 3 overflows, two 4-register overflows and one
343          *    12-register overflow.
344          */
345
346
347 # if XTOS_VIRTUAL_INTENABLE
348         /*
349          *  The INTENABLE register is virtualized, because it serves two purposes:
350          *  controlling which interrupts are active (eg. enabled once a handler
351          *  is registered) as reflected in _xtos_enabled, and what is the current
352          *  effective interrupt level as reflected in _xtos_vpri_enabled.
353          *
354          *  The INTENABLE register always contains (_xtos_enabled & _xtos_vpri_enabled).
355          *  NOTE:  It is important that INTENABLE, _xtos_enabled and _xtos_vpri_enabled
356          *  only be modified when interrupts at XTOS_LOCK_LEVEL and below are disabled,
357          *  that they never be modified by interrupts at levels above XTOS_LOCK_LEVEL,
358          *  and that they be consistent and never modified when the current interrupt
359          *  level is below XTOS_LOCK_LEVEL.
360          *
361          *  NOTE:  Reading the INTERRUPT register *must* be done at PS.INTLEVEL <= 1
362          *  otherwise we might incorrectly see higher priority interrupts.
363          */
364
365
366         movi    a14, _xtos_intstruct            // address of interrupt management globals
367 #  if XCHAL_HAVE_XEA1
368         l32i    a15, a1, UEXC_vpri              // read saved INTERRUPT register value
369         l32i    a13, a14, XTOS_VPRI_ENABLED_OFS // read previous _xtos_vpri_enabled
370         l32i    a12, a14, XTOS_ENABLED_OFS      // read _xtos_enabled
371         and     a15, a15, a13                   // don't handle ints already being handled
372 #  else
373         rsr     a15, INTERRUPT                  // interrupts pending
374         rsr     a12, INTENABLE                  // interrupts enabled (already should equal _xtos_enabled & _xtos_vpri_enabled)
375         l32i    a13, a14, XTOS_VPRI_ENABLED_OFS // read previous _xtos_vpri_enabled
376 #  endif
377         and     a15, a15, a12                   // a15 = INTERRUPT & (interrupts we can consider processing)
378 NEEDSAR rsr     a12, SAR
379         s32i    a13, a1, UEXC_vpri              // save previous vpri
380
381         _beqz   a15, spurious_int               // no interrupt to handle (spurious interrupt)
382 NEEDSAR s32i    a12, a1, UEXC_sar               // note: in XEA1, UEXC_sar must be set *after* beqz above
383
384 IFFAIR  s32i    a2, a1, UEXC_exccause           // save a2 (interrupted code's a6)
385 IFFAIR  movi    a2, -1                          // initial fairness mask
386
387 .L1_loop0:
388         //  a15 = non-zero mask of interrupt bits to consider handling
389
390 #  if XTOS_SUBPRI_ORDER == XTOS_SPO_ZERO_HI && !XTOS_INT_FAIRNESS && !XTOS_SUBPRI_GROUPS
391         //  Special case that can be handled a bit more efficiently:
392
393         neg     a12, a15                        // find lsbit in a15 ...
394         and     a12, a12, a15                   // ...
395         //  a12 = single bit corresponding to interrupt to be processed (highest pri pending+enabled).
396
397         //  Compute a13 = new virtual priority based on this selected highest priority interrupt:
398         movi    a15, ~XCHAL_LOWPRI_MASK         // mask of all low-priority interrupts
399         addi    a13, a12, -1                    // mask of interrupts enabled at this new priority
400         or      a13, a13, a15                   // also leave medium- and high-priority interrupts enabled
401
402 #  else /* special case */
403
404         //  Entry:
405         //      a12 = (undefined)
406         //      a13 = (undefined)
407         //      a14 = &_xtos_intstruct  --or--  interrupt table adjusted base
408         //      a15 = non-zero mask of interrupt bits to consider handling
409         //  Exit:
410         //      a12 = index
411         //      a13 = (clobbered)
412         //      a14 = (preserved)
413         //      a15 = single bit corresponding to index
414         //
415         indexmask_int   a12, a15, a14, a13
416
417         //  a12 = index of highest priority pending+enabled interrupt, to be processed.
418         //  a15 = (1 << a12), ie. bit corresponding to interrupt to be processed.
419 IFFAIR  xor     a2, a2, a15             // update fairness mask - mask out this interrupt until recycling mask
420         movi    a13, _xtos_interrupt_table - IFNSA( (32-XCHAL_NUM_INTERRUPTS)*XIE_SIZE, 0 )
421         wsr     a15, INTCLEAR           // clear interrupt (if software or external edge-triggered or write-error)
422         addx8   a12, a12, a13           // a12 = address in interrupt table for given interrupt number
423
424 .L1_loop1:
425         //  a12 now contains pointer to interrupt table entry for interrupt to be processed
426         l32i    a13, a12, XIE_VPRIMASK  // a13 = new vpri (mask of interrupts enabled at this interrupt's priority)
427 #  endif /* !special case */
428
429         //  a13 = new virtual priority based on the selected highest priority interrupt
430
431         rsilft  a15, 1*XCHAL_HAVE_XEA2, XTOS_LOCKLEVEL  // lockout
432
433         //  Now do the equivalent of:   prev = _xtos_set_vpri( a13 );
434
435         l32i    a15, a14, XTOS_ENABLED_OFS      // a15 = _xtos_enabled
436         s32i    a13, a14, XTOS_VPRI_ENABLED_OFS // update new _xtos_vpri_enabled
437         and     a15, a15, a13                   // a15 = _xtos_enabled & _xtos_vpri_enabled
438         //NOTE: Here, do:  a15 &= ~_xtos_pending  if XTOS_VIRTUAL_INTERRUPT is set.
439         wsr     a15, INTENABLE
440         //interlock
441         //interlock
442         rsync   // NOTA - not ISA defined       // wait for INTENABLE write to complete before we set PS.INTLEVEL to zero
443
444
445         //  Okay, we've updated INTENABLE to reflect the new virtual priority (vpri)
446         //  according to the highest priority pending+enabled (low-priority) interrupt.
447
448         //  IMPLEMENTATION NOTE - Before we unlock (enable interrupts), we could
449         //  switch stacks here, now that we have enough free registers through the unlock.
450
451         //  Now we can enable interrupts via PS.INTLEVEL.  (Already done for XEA1.)
452
453         rsil    a15, 0                          // unlock
454 #  undef CUR_INTLEVEL
455 #  define CUR_INTLEVEL  0
456
457         //  HERE:  interrupts are enabled again (those interrupts of
458         //      higher virtual priority than the one we're currently processing).
459
460         //  HERE:
461         //      a12 = pointer to interrupt entry in table, or
462         //              mask of interrupt bit to process (special case only)
463         //      a13, a15 = available for use
464         //      a14 = available for use if virtual INTENABLE, else is pointer to interrupt table
465
466 #  if XTOS_SUBPRI_ORDER == XTOS_SPO_ZERO_HI && !XTOS_INT_FAIRNESS && !XTOS_SUBPRI_GROUPS
467         /*  In this special case, we moved as much as possible where interrupts are enabled again:  */
468         //  a12 is bit corresponding to interrupt, convert to ptr to interrupt table entry...
469         movi            a14, _xtos_interrupt_table - IFNSA( (32-XCHAL_NUM_INTERRUPTS)*XIE_SIZE, 0 )
470         wsr             a12, INTCLEAR   // clear interrupt (if software or external edge-triggered or write-error)
471 //IFFAIR        xor     a2, a2, a12     // update fairness mask - mask out this interrupt until recycling mask
472         msindex_int     a15, a12        // a15 = index of msbit set in a12 (a12 clobbered)
473         addx8           a12, a15, a14   // a12 = address in interrupt table for given interrupt number
474 #  endif /* special case */
475
476
477
478 # elif XTOS_SINGLE_INT
479         /*
480          *  Only one interrupt is configured to map to this vector.
481          *  This simplifies the code considerably -- no checking and resolving of INTERRUPT
482          *  register required.  Just call the handler and exit.
483          *
484          *  (With INTENABLE register virtualization, the simplification is
485          *   not as great, and not implemented separately above.)
486          */
487
488
489 #  define XTOS_SINGLE_INT_NUM   XCHAL_INTLEVEL1_NUM
490 #  define XTOS_SINGLE_INT_MASK  XCHAL_INTLEVEL1_MASK
491 #  define XTOS_SINGLE_INT_CLEAR ((XTOS_SINGLE_INT_MASK & XCHAL_INTCLEARABLE_MASK) != 0)
492 #  if XTOS_SINGLE_INT_CLEAR
493         movi    a13, XCHAL_LOWPRI_MASK          // bit to clear in INTERRUPT register
494 #  endif
495         //  Get pointer to interrupt table entry for this vector's only interrupt:
496         movi    a12, _xtos_interrupt_table + MAPINT(XTOS_SINGLE_INT_NUM)*XIE_SIZE
497 #  if XTOS_SINGLE_INT_CLEAR
498         wsr     a13, INTCLEAR                   // clear interrupt pending bit (if software or external-edge-triggered or write-error)
499 #  endif
500
501
502
503 # else /* ie. if !XTOS_VIRTUAL_INTENABLE && !XTOS_SINGLE_INT */
504         /*
505          *  Here, the INTENABLE register is NOT virtualized.  There are no _xtos_enabled
506          *  or _xtos_vpri_enabled global variables to track.  INTENABLE simply controls
507          *  which interrupts are active (eg. enabled once a handler is registered).
508          *
509          *  NOTE:  To ensure its coherency, it is still important to only modify the
510          *  INTENABLE register when interrupts at XTOS_LOCK_LEVEL and below are disabled,
511          *  that it never be modified by interrupts at levels above XTOS_LOCK_LEVEL,
512          *  and that it never be modified when the current interrupt level is below
513          *  XTOS_LOCK_LEVEL.  This is because modifications to INTENABLE generally
514          *  require an RSR/modify/WSR sequence to modify only selected bits.
515          *
516          *  NOTE:  Reading the INTERRUPT register *must* be done at PS.INTLEVEL <= 1
517          *  otherwise we might incorrectly see higher priority interrupts.
518          *
519          *  This option implies XEA2, because XEA1 always requires INTENABLE virtualization.
520          *  This option also implies SUBPRI is zero (no interrupt sub-prioritization in software).
521          */
522
523
524         rsr     a15, INTERRUPT                  // interrupts pending
525         rsr     a13, INTENABLE                  // interrupts enabled (directly; no virtualization)
526         movi    a14, _xtos_interrupt_table - IFNSA( (32-XCHAL_NUM_INTERRUPTS)*XIE_SIZE, 0 )
527 NEEDSAR rsr     a12, SAR
528         and     a15, a15, a13                   // a15 = INTERRUPT & INTENABLE
529
530         _beqz   a15, spurious_int               // no interrupt to handle (spurious interrupt)
531 NEEDSAR s32i    a12, a1, UEXC_sar
532
533 IFFAIR  s32i    a2, a1, UEXC_exccause           // save a2 (interrupted code's a6)
534 IFFAIR  movi    a2, -1                          // initial fairness mask
535
536 .L1_loop0:
537         //  Entry:
538         //      a12 = (undefined)
539         //      a13 = (undefined)
540         //      a14 = interrupt table adjusted base (not used here)
541         //      a15 = non-zero mask of interrupt bits to consider handling
542         //  Exit:
543         //      a12 = index
544         //      a13 = (clobbered)
545         //      a14 = (preserved)
546         //      a15 = single bit corresponding to index
547         //
548         indexmask_int   a12, a15, a14_UNUSED, a13
549
550         //  a12 = index of highest priority pending+enabled interrupt, to be processed.
551         //  a15 = (1 << a12), ie. bit corresponding to interrupt to be processed.
552 IFFAIR  xor     a2, a2, a15             // update fairness mask - mask out this interrupt until recycling mask
553         wsr     a15, INTCLEAR           // clear interrupt (if software or external edge-triggered or write-error)
554
555         addx8   a12, a12, a14           // a12 = address in interrupt table for given interrupt number
556
557 .L1_loop1:
558         //  a12 now contains pointer to interrupt table entry for interrupt to be processed
559
560         //  HERE:
561         //      a12 = pointer to interrupt entry in table
562         //      a13, a15 = available for use
563         //      a14 = available for use if virtual INTENABLE, else is pointer to interrupt table
564
565
566 # endif /* !XTOS_VIRTUAL_INTENABLE && !XTOS_SINGLE_INT */
567         /*  At this point, PS.INTLEVEL is:  1 if XEA2 and (XTOS_SINGLE_INT || !XTOS_VIRTUAL_INTENABLE), 0 otherwise  */
568
569         //  HERE:  a12 = pointer to interrupt entry in table
570
571         // (Possible enhancement: do at higher-level, to avoid doing it all the time? !?!?!?)
572         save_loops_mac16        a1, a13, a15    // save LOOP & MAC16 regs, if configured
573
574 LATESAR rsr     a15, SAR
575
576 # if 0
577         /* ... alternate code to allow context-switching would go here ... */
578 # else
579         l32i    a13, a12, XIE_HANDLER   // a13 = address of interrupt handler
580 LATESAR s32i    a15, a1, UEXC_sar
581 # endif
582
583 # ifdef __XTENSA_CALL0_ABI__
584         l32i    a2, a12, XIE_ARG        // first arg
585         mov     a3, a1                  // second arg, exception stack frame
586         callx0  a13                     // call interrupt handler
587 # else
588         mov     a15, a1                 // second arg, exception stack frame
589         l32i    a14, a12, XIE_ARG       // first argument passed to interrupt handler (relayed by context-dispatcher, if non-nested)
590         callx12 a13                     // execute interrupt handler, directly or via context-dispatcher (clobbers a12-a15)
591 # endif
592
593         // (Possible enhancement: do at higher-level, to avoid doing it all the time? !?!?!?)
594         restore_loops_mac16     a1, a13, a14, a15       // restore LOOP & MAC16 regs, if configured
595
596 LATESAR l32i    a12, a1, UEXC_sar
597
598
599 # if XTOS_VIRTUAL_INTENABLE
600         /*  Here, INTENABLE register is virtualized.  */
601
602         movi    a14, _xtos_intstruct            // address of interrupt management globals
603 LATESAR wsr     a12, SAR
604 #  if XCHAL_HAVE_XEA1
605         movi    a12, XTOS_UNLOCKABLE_MASK       // mask out levels covered by XTOS_LOCKLEVEL
606                                                 //  so we can run at PS.INTLEVEL=0 (for the RETW below)
607                                                 //  while manipulating virtual INTENABLE
608 #  endif
609         rsr     a15, INTERRUPT
610         rsil    a13, XTOS_LOCKLEVEL
611         l32i    a13, a14, XTOS_ENABLED_OFS      // a13 = _xtos_enabled
612 #  if XCHAL_HAVE_XEA1
613         and     a12, a12, a13                   // compute new INTENABLE
614         wsr     a12, INTENABLE                  // mask out at XTOS_LOCKLEVEL via INTENABLE
615 #  endif
616         l32i    a12, a1, UEXC_vpri              // read saved vpri
617         //interlock
618         and     a13, a13, a12                   // a13 = old-vpri & _xtos_enabled (INTENABLE value to restore)
619         and     a15, a15, a13                   // what's pending among what we can handle?
620
621
622         //  a15 now contains the remaining pending+enabled interrupts.
623         //  NOTE:  we MUST NOT consider interrupts potentially already being handled
624         //  by another interrupt handler that we pre-empted.
625         //  So we masked with saved vpri, ie. the set of interrupts enabled when we entered
626         //  this handler, ie. the set of interrupts that can pre-empt the previous context.
627 NOFAIR  _bnez   a15, .L1_loop0                  // more interrupt(s) to handle
628 IFFAIR  _bnez   a15, preloop                    // more interrupt(s) to handle
629 IFFAIR  l32i    a2, a1, UEXC_exccause           // restore a2 (interrupted code's a6)
630
631
632         //  NOTE:
633         //  Register allocation is why we didn't restore *HERE* the loop regs, MAC16, SAR, etc.
634         //  (at least part of the reason)
635         //  We only have one registers (a15), however with 7-stage pipe, three registers
636         //  are required to avoid interlocks.  We could get 2 more registers at 1 cycle each [now only one?],
637         //  but it isn't obvious whether paying these extra cycles are worth it...
638
639         //  Restore vpri as it was before we handled the interrupt(s):
640         s32i    a12, a14, XTOS_VPRI_ENABLED_OFS // restore _xtos_vpri_enabled
641 NEEDSAR l32i    a12, a1, UEXC_sar
642 #  if XCHAL_HAVE_XEA1
643         s32i    a13, a1, UEXC_sar               // save new INTENABLE value across RETW
644 #  else
645         wsr     a13, INTENABLE                  // update INTENABLE per original vpri
646
647         //  NOTE:  leave locked, disabling only the low- and medium-priority interrupts
648         rsilft  a13, XTOS_LOCKLEVEL, XCHAL_EXCM_LEVEL   // lockout
649 #   undef CUR_INTLEVEL
650 #   define CUR_INTLEVEL XCHAL_EXCM_LEVEL
651 #  endif
652
653 # elif XTOS_SINGLE_INT
654
655 #  undef NEEDSAR
656 #  define NEEDSAR
657
658 # else /* ie.  if !XTOS_VIRTUAL_INTENABLE && !XTOS_SINGLE_INT */
659         /*  Here, INTENABLE register is NOT virtualized (implies XEA2).  */
660
661         rsr     a15, INTERRUPT                  // interrupts pending
662         rsr     a13, INTENABLE                  // interrupts enabled (directly; no virtualization)
663         movi    a14, _xtos_interrupt_table - IFNSA( (32-XCHAL_NUM_INTERRUPTS)*XIE_SIZE, 0 )
664 LATESAR wsr     a12, SAR
665         and     a15, a15, a13                   // a15 = INTERRUPT & INTENABLE
666
667         //  a15 now contains the remaining pending+enabled interrupts.
668         //  NOTE:  we MUST NOT consider interrupts potentially already being handled
669         //  by another interrupt handler that we pre-empted.
670         //  So we masked with saved vpri, ie. the set of interrupts enabled when we entered
671         //  this handler, ie. the set of interrupts that can pre-empt the previous context.
672 NOFAIR  _bnez   a15, .L1_loop0                  // more interrupt(s) to handle
673 IFFAIR  _bnez   a15, preloop                    // more interrupt(s) to handle
674 IFFAIR  l32i    a2, a1, UEXC_exccause           // restore a2 (interrupted code's a6)
675
676
677         //  NOTE:
678         //  Register allocation is why we didn't restore *HERE* the loop regs, MAC16, SAR, etc.
679         //  (at least part of the reason)
680         //  We only have one registers (a15), however with 7-stage pipe, three registers
681         //  are required to avoid interlocks.  We could get 2 more registers at 1 cycle each [now only one?],
682         //  but it isn't obvious whether paying these extra cycles are worth it...
683
684 NEEDSAR l32i    a12, a1, UEXC_sar
685 # endif /* !XTOS_VIRTUAL_INTENABLE && !XTOS_SINGLE_INT */
686
687
688         /***************************/
689
690         //  Now exit the handler.
691
692         /*
693          *  Leave interrupts disabled while returning from the pseudo-CALL setup above,
694          *  for the same reason they were disabled while doing the pseudo-CALL:
695          *  this sequence restores SP such that it doesn't reflect the allocation
696          *  of the exception stack frame, which is still needed to return from
697          *  the exception.
698          */
699
700 spurious_int:
701
702         movi    a0, _xtos_return_from_exc
703 # ifdef __XTENSA_CALL0_ABI__
704 NEEDSAR wsr     a12, SAR
705         jx      a0
706 # else /* ! __XTENSA_CALL0_ABI__ */
707         //  Now return from the pseudo-CALL from the interrupted code, to rotate
708         //  our windows back...
709
710         movi    a13, 0xC0000000
711 NEEDSAR wsr     a12, SAR
712         or      a0, a0, a13             // set upper two bits
713         addx2   a0, a13, a0             // clear upper bit
714
715 #  if XCHAL_HAVE_XEA2
716         //  Disable ints during unalloc'ed live stack after RETW below.
717         rsil    a13, XCHAL_EXCM_LEVEL   // might come here via spurious_int, so always rsil
718 #  endif
719
720         retw
721 # endif /* __XTENSA_CALL0_ABI__ */
722
723
724
725 # if XTOS_INT_FAIRNESS
726 preloop:
727         //  Lowering priority or recycling fairness-mask bits ...
728         //  a14 = &_xtos_intstruct *or* interrupt table ptr
729         //  a15 = non-zero mask of interrupt bits to consider handling
730
731 #  if !XTOS_SUBPRI
732         and     a13, a15, a2            // a13 = interrupt bits to consider handling, masked for fairness
733         movi    a12, -1                 // (new fairness mask, all one's)
734         moveqz  a2, a12, a13            // recycle fairness mask if all bits to consider are masked by fairness, and leave a15 intact
735         movnez  a15, a13, a13           // otherwise set a15 = a13, ie. mask out bits for fairness (a15 is still non-zero)
736         j       .L1_loop0
737 #  else /* XTOS_SUBPRI */
738         //  NOTE:  In this case, with SUBPRI, XTOS_VIRTUAL_INTENABLE is always set.
739         //  So:  a14 = &_xtos_intstruct
740
741         //  Compute a13 = index of highest priority interrupt in a15 (a13 is reversed if NSA present)
742         //  (a14, a15 preserved; a12 is a temporary):
743         index_int       a13, a15, a14, a12
744
745         //  a12 = (available)
746         //  a13 = index
747         //  a14 = &_xtos_intstruct
748         //  a15 = mask of candidates
749         movi    a12, _xtos_interrupt_table - IFNSA( (32-XCHAL_NUM_INTERRUPTS)*XIE_SIZE, 0 )
750         //slot
751         addx8   a12, a13, a12           // a12 = address in interrupt table for given interrupt number
752         l32i    a14, a12, XIE_LEVELMASK // a14 = mask of all interrupts at selected interrupt's level
753         and     a15, a15, a2            // mask out for fairness
754         and     a15, a15, a14           // only consider interrupts at highest pending level
755         movi    a14, _xtos_intstruct    // needed at loop0, and below
756         _bnez   a15, .L1_loop0          // interrupts are allowed by current fairness mask, redo indexing with proper mask (a15, a14 = ...)
757
758         //  a12 = ptr to interrupt entry
759         //  a13 = index
760         //  a14 = &_xtos_intstruct
761         //  a15 = (available)
762
763         //  Compute bitmask of interrupt to be processed...
764 #   if XCHAL_HAVE_NSA
765         movi    a15, 0x80000000
766         ssr     a13
767         srl     a13, a15
768 #   else
769         movi    a15, 1
770         ssl     a13
771         sll     a13, a15
772 #   endif
773         //  a13 = single bit set corresponding to interrupt to be processed...
774         l32i    a15, a12, XIE_LEVELMASK // a15 = mask of all interrupts at selected interrupt's level
775         wsr     a13, INTCLEAR           // clear interrupt (if software or external edge-triggered or write-error)
776         or      a2, a2, a15             // recycle fairness mask for selected interrupt level
777         xor     a2, a2, a13             // update fairness mask - mask out this interrupt until recycling mask
778         j       .L1_loop1               // handle selected interrupt (a12 = interrupt entry, a14 = &_xtos_intstruct)
779
780 #  endif /* XTOS_SUBPRI */
781 # endif /* XTOS_INT_FAIRNESS */
782
783         /* FIXME: what about _LevelOneInterrupt ? */
784         .size   _xtos_l1int_handler, . - _xtos_l1int_handler
785
786 #endif /* XCHAL_HAVE_EXCEPTIONS && XCHAL_HAVE_INTERRUPTS */
787