source: rtems/c/src/lib/libbsp/sparc/shared/irq_asm.S @ fbda4a8

4.115
Last change on this file since fbda4a8 was fbda4a8, checked in by Sebastian Huber <sebastian.huber@…>, on 07/01/14 at 08:48:28

score: PR2183: Fix context switch on SMP

Fix context switch on SMP for ARM, PowerPC and SPARC.

Atomically test and set the is executing indicator of the heir context
to ensure that at most one processor uses the heir context. Break the
busy wait loop also due to heir updates.

  • Property mode set to 100644
File size: 25.1 KB
RevLine 
[5d69cd3]1/*  cpu_asm.s
2 *
3 *  This file contains the basic algorithms for all assembly code used
4 *  in an specific CPU port of RTEMS.  These algorithms must be implemented
5 *  in assembly language.
6 *
7 *  COPYRIGHT (c) 1989-2011.
8 *  On-Line Applications Research Corporation (OAR).
9 *
[fbda4a8]10 *  Copyright (c) 2014 embedded brains GmbH
11 *
[5d69cd3]12 *  The license and distribution terms for this file may be
13 *  found in the file LICENSE in this distribution or at
[c499856]14 *  http://www.rtems.org/license/LICENSE.
[5d69cd3]15 *
16 *  Ported to ERC32 implementation of the SPARC by On-Line Applications
17 *  Research Corporation (OAR) under contract to the European Space
18 *  Agency (ESA).
19 *
20 *  ERC32 modifications of respective RTEMS file: COPYRIGHT (c) 1995.
21 *  European Space Agency.
22 */
23
24#include <rtems/asm.h>
[f8ad6c6f]25#include <rtems/score/percpu.h>
[8b077ca0]26#include <bspopts.h>
27
[88f6c4fc]28/*
29 *  void _CPU_Context_switch(
30 *    Context_Control  *run,
31 *    Context_Control  *heir
32 *  )
33 *
34 *  This routine performs a normal non-FP context switch.
35 */
36
37        .align 4
38        PUBLIC(_CPU_Context_switch)
39SYM(_CPU_Context_switch):
[b2ec2d15]40        st      %g5, [%o0 + G5_OFFSET]       ! save the global registers
[7c0bd74]41        st      %g7, [%o0 + G7_OFFSET]
[88f6c4fc]42
43        std     %l0, [%o0 + L0_OFFSET]       ! save the local registers
44        std     %l2, [%o0 + L2_OFFSET]
45        std     %l4, [%o0 + L4_OFFSET]
46        std     %l6, [%o0 + L6_OFFSET]
47
48        std     %i0, [%o0 + I0_OFFSET]       ! save the input registers
49        std     %i2, [%o0 + I2_OFFSET]
50        std     %i4, [%o0 + I4_OFFSET]
51        std     %i6, [%o0 + I6_FP_OFFSET]
52
[97cf623d]53        std     %o6, [%o0 + O6_SP_OFFSET]    ! save the output registers
[88f6c4fc]54
[f8ad6c6f]55        ! load the ISR stack nesting prevention flag
[7c0bd74]56        ld      [%g6 + SPARC_PER_CPU_ISR_DISPATCH_DISABLE], %o4
[f8ad6c6f]57        ! save it a bit later so we do not waste a couple of cycles
58
[88f6c4fc]59        rd      %psr, %o2
60        st      %o2, [%o0 + PSR_OFFSET]      ! save status register
61
[f8ad6c6f]62        ! Now actually save ISR stack nesting prevention flag
63        st       %o4, [%o0 + ISR_DISPATCH_DISABLE_STACK_OFFSET]
64
[88f6c4fc]65        /*
66         *  This is entered from _CPU_Context_restore with:
67         *    o1 = context to restore
68         *    o2 = psr
69         */
70
71        PUBLIC(_CPU_Context_restore_heir)
72SYM(_CPU_Context_restore_heir):
73        /*
74         *  Flush all windows with valid contents except the current one.
75         *  In examining the set register windows, one may logically divide
76         *  the windows into sets (some of which may be empty) based on their
77         *  current status:
78         *
79         *    + current (i.e. in use),
80         *    + used (i.e. a restore would not trap)
81         *    + invalid (i.e. 1 in corresponding bit in WIM)
82         *    + unused
83         *
84         *  Either the used or unused set of windows may be empty.
85         *
86         *  NOTE: We assume only one bit is set in the WIM at a time.
87         *
88         *  Given a CWP of 5 and a WIM of 0x1, the registers are divided
89         *  into sets as follows:
90         *
91         *    + 0   - invalid
92         *    + 1-4 - unused
93         *    + 5   - current
94         *    + 6-7 - used
95         *
96         *  In this case, we only would save the used windows -- 6 and 7.
97         *
98         *   Traps are disabled for the same logical period as in a
99         *     flush all windows trap handler.
100         *
101         *    Register Usage while saving the windows:
102         *      g1 = current PSR
103         *      g2 = current wim
104         *      g3 = CWP
105         *      g4 = wim scratch
106         *      g5 = scratch
107         */
108
109        ld      [%o1 + PSR_OFFSET], %g1       ! g1 = saved psr
110
111        and     %o2, SPARC_PSR_CWP_MASK, %g3  ! g3 = CWP
112                                              ! g1 = psr w/o cwp
113        andn    %g1, SPARC_PSR_ET_MASK | SPARC_PSR_CWP_MASK, %g1
114        or      %g1, %g3, %g1                 ! g1 = heirs psr
115        mov     %g1, %psr                     ! restore status register and
116                                              ! **** DISABLE TRAPS ****
117        mov     %wim, %g2                     ! g2 = wim
118        mov     1, %g4
119        sll     %g4, %g3, %g4                 ! g4 = WIM mask for CW invalid
120
121save_frame_loop:
122        sll     %g4, 1, %g5                   ! rotate the "wim" left 1
123        srl     %g4, SPARC_NUMBER_OF_REGISTER_WINDOWS - 1, %g4
124        or      %g4, %g5, %g4                 ! g4 = wim if we do one restore
125
126        /*
127         *  If a restore would not underflow, then continue.
128         */
129
130        andcc   %g4, %g2, %g0                 ! Any windows to flush?
131        bnz     done_flushing                 ! No, then continue
132        nop
133
134        restore                               ! back one window
135
136        /*
137         *  Now save the window just as if we overflowed to it.
138         */
139
140        std     %l0, [%sp + CPU_STACK_FRAME_L0_OFFSET]
141        std     %l2, [%sp + CPU_STACK_FRAME_L2_OFFSET]
142        std     %l4, [%sp + CPU_STACK_FRAME_L4_OFFSET]
143        std     %l6, [%sp + CPU_STACK_FRAME_L6_OFFSET]
144
145        std     %i0, [%sp + CPU_STACK_FRAME_I0_OFFSET]
146        std     %i2, [%sp + CPU_STACK_FRAME_I2_OFFSET]
147        std     %i4, [%sp + CPU_STACK_FRAME_I4_OFFSET]
148        std     %i6, [%sp + CPU_STACK_FRAME_I6_FP_OFFSET]
149
150        ba      save_frame_loop
151        nop
152
153done_flushing:
154
155        add     %g3, 1, %g3                   ! calculate desired WIM
156        and     %g3, SPARC_NUMBER_OF_REGISTER_WINDOWS - 1, %g3
157        mov     1, %g4
158        sll     %g4, %g3, %g4                 ! g4 = new WIM
159        mov     %g4, %wim
160
161        or      %g1, SPARC_PSR_ET_MASK, %g1
162        mov     %g1, %psr                     ! **** ENABLE TRAPS ****
163                                              !   and restore CWP
164        nop
165        nop
166        nop
167
[38b59a6]168#if defined(RTEMS_SMP)
[11b05f1]169        ! The executing context no longer executes on this processor
[fbda4a8]170        st      %g0, [%o0 + SPARC_CONTEXT_CONTROL_IS_EXECUTING_OFFSET]
171
172        ! Try to update the is executing indicator of the heir context
173        mov     1, %g1
174
175try_update_is_executing:
[38b59a6]176
[fbda4a8]177        swap    [%o1 + SPARC_CONTEXT_CONTROL_IS_EXECUTING_OFFSET], %g1
[38b59a6]178        cmp     %g1, 0
[fbda4a8]179        bne     check_is_executing
[38b59a6]180
[fbda4a8]181        ! The next load is in a delay slot, which is all right
[38b59a6]182#endif
183
[b2ec2d15]184        ld      [%o1 + G5_OFFSET], %g5        ! restore the global registers
[7c0bd74]185        ld      [%o1 + G7_OFFSET], %g7
[88f6c4fc]186
187        ! Load thread specific ISR dispatch prevention flag
188        ld      [%o1 + ISR_DISPATCH_DISABLE_STACK_OFFSET], %o2
189        ! Store it to memory later to use the cycles
190
191        ldd     [%o1 + L0_OFFSET], %l0        ! restore the local registers
192        ldd     [%o1 + L2_OFFSET], %l2
193        ldd     [%o1 + L4_OFFSET], %l4
194        ldd     [%o1 + L6_OFFSET], %l6
195
196        ! Now restore thread specific ISR dispatch prevention flag
[7c0bd74]197        st      %o2, [%g6 + SPARC_PER_CPU_ISR_DISPATCH_DISABLE]
[88f6c4fc]198
[20828099]199        ldd     [%o1 + I0_OFFSET], %i0        ! restore the input registers
[88f6c4fc]200        ldd     [%o1 + I2_OFFSET], %i2
201        ldd     [%o1 + I4_OFFSET], %i4
202        ldd     [%o1 + I6_FP_OFFSET], %i6
203
[97cf623d]204        ldd     [%o1 + O6_SP_OFFSET], %o6     ! restore the output registers
[88f6c4fc]205
206        jmp     %o7 + 8                       ! return
207        nop                                   ! delay slot
208
[fbda4a8]209#if defined(RTEMS_SMP)
210check_is_executing:
211
212        ! Check the is executing indicator of the heir context
213        ld      [%o1 + SPARC_CONTEXT_CONTROL_IS_EXECUTING_OFFSET], %g1
214        cmp     %g1, 0
215        beq     try_update_is_executing
216         mov    1, %g1
217
218        ! Check if a thread dispatch is necessary
219        ldub    [%g6 + PER_CPU_DISPATCH_NEEDED], %g1
220        cmp     %g1, 0
221        beq     check_is_executing
222         nop
223
224        ! We have a new heir
225
226        ! Clear the thread dispatch necessary flag
227        stub    %g0, [%g6 + PER_CPU_DISPATCH_NEEDED]
228
229        ! Here we assume a strong memory order, otherwise a memory barrier must
230        ! be inserted here
231
232        ! Read the executing and heir
233        ld      [%g6 + PER_CPU_OFFSET_EXECUTING], %g1
234        ld      [%g6 + PER_CPU_OFFSET_HEIR], %g2
235
236        ! Calculate the heir context pointer
237        sub     %o1, %g1, %g1
238        add     %g1, %g2, %o1
239
240        ! Update the executing
241        st      %g2, [%g6 + PER_CPU_OFFSET_EXECUTING]
242
243        ba      try_update_is_executing
244         mov    1, %g1
245#endif
246
[88f6c4fc]247/*
248 *  void _CPU_Context_restore(
249 *    Context_Control *new_context
250 *  )
251 *
252 *  This routine is generally used only to perform restart self.
253 *
254 *  NOTE: It is unnecessary to reload some registers.
255 */
256        .align 4
257        PUBLIC(_CPU_Context_restore)
258SYM(_CPU_Context_restore):
259        save    %sp, -CPU_MINIMUM_STACK_FRAME_SIZE, %sp
260        rd      %psr, %o2
[38b59a6]261#if defined(RTEMS_SMP)
262        ! On SPARC the restore path needs also a valid executing context on SMP
263        ! to update the is executing indicator.
264        mov     %i0, %o0
265#endif
[88f6c4fc]266        ba      SYM(_CPU_Context_restore_heir)
267        mov     %i0, %o1                      ! in the delay slot
268
[5d69cd3]269/*
270 *  void _ISR_Handler()
271 *
272 *  This routine provides the RTEMS interrupt management.
273 *
274 *  We enter this handler from the 4 instructions in the trap table with
275 *  the following registers assumed to be set as shown:
276 *
277 *    l0 = PSR
278 *    l1 = PC
279 *    l2 = nPC
280 *    l3 = trap type
281 *
282 *  NOTE: By an executive defined convention, trap type is between 0 and 255 if
283 *        it is an asynchonous trap and 256 and 511 if it is synchronous.
284 */
285
286        .align 4
287        PUBLIC(_ISR_Handler)
288SYM(_ISR_Handler):
289        /*
290         *  Fix the return address for synchronous traps.
291         */
292
293        andcc   %l3, SPARC_SYNCHRONOUS_TRAP_BIT_MASK, %g0
294                                      ! Is this a synchronous trap?
295        be,a    win_ovflow            ! No, then skip the adjustment
296        nop                           ! DELAY
297        mov     %l1, %l6              ! save trapped pc for debug info
298        mov     %l2, %l1              ! do not return to the instruction
299        add     %l2, 4, %l2           ! indicated
300
301win_ovflow:
302        /*
303         *  Save the globals this block uses.
304         *
305         *  These registers are not restored from the locals.  Their contents
306         *  are saved directly from the locals into the ISF below.
307         */
308
309        mov     %g4, %l4                 ! save the globals this block uses
310        mov     %g5, %l5
311
312        /*
313         *  When at a "window overflow" trap, (wim == (1 << cwp)).
314         *  If we get here like that, then process a window overflow.
315         */
316
317        rd      %wim, %g4
318        srl     %g4, %l0, %g5            ! g5 = win >> cwp ; shift count and CWP
319                                         !   are LS 5 bits ; how convenient :)
320        cmp     %g5, 1                   ! Is this an invalid window?
321        bne     dont_do_the_window       ! No, then skip all this stuff
322        ! we are using the delay slot
323
324        /*
325         *  The following is same as a 1 position right rotate of WIM
326         */
327
328        srl     %g4, 1, %g5              ! g5 = WIM >> 1
329        sll     %g4, SPARC_NUMBER_OF_REGISTER_WINDOWS-1 , %g4
330                                         ! g4 = WIM << (Number Windows - 1)
331        or      %g4, %g5, %g4            ! g4 = (WIM >> 1) |
332                                         !      (WIM << (Number Windows - 1))
333
334        /*
335         *  At this point:
336         *
337         *    g4 = the new WIM
338         *    g5 is free
339         */
340
341        /*
342         *  Since we are tinkering with the register windows, we need to
343         *  make sure that all the required information is in global registers.
344         */
345
346        save                          ! Save into the window
347        wr      %g4, 0, %wim          ! WIM = new WIM
348        nop                           ! delay slots
349        nop
350        nop
351
352        /*
353         *  Now save the window just as if we overflowed to it.
354         */
355
356        std     %l0, [%sp + CPU_STACK_FRAME_L0_OFFSET]
357        std     %l2, [%sp + CPU_STACK_FRAME_L2_OFFSET]
358        std     %l4, [%sp + CPU_STACK_FRAME_L4_OFFSET]
359        std     %l6, [%sp + CPU_STACK_FRAME_L6_OFFSET]
360
361        std     %i0, [%sp + CPU_STACK_FRAME_I0_OFFSET]
362        std     %i2, [%sp + CPU_STACK_FRAME_I2_OFFSET]
363        std     %i4, [%sp + CPU_STACK_FRAME_I4_OFFSET]
364        std     %i6, [%sp + CPU_STACK_FRAME_I6_FP_OFFSET]
365
366        restore
367        nop
368
369dont_do_the_window:
370        /*
371         *  Global registers %g4 and %g5 are saved directly from %l4 and
372         *  %l5 directly into the ISF below.
373         */
374
375save_isf:
376
377        /*
378         *  Save the state of the interrupted task -- especially the global
379         *  registers -- in the Interrupt Stack Frame.  Note that the ISF
380         *  includes a regular minimum stack frame which will be used if
381         *  needed by register window overflow and underflow handlers.
382         *
383         *  REGISTERS SAME AS AT _ISR_Handler
384         */
385
386        sub     %fp, CONTEXT_CONTROL_INTERRUPT_FRAME_SIZE, %sp
387                                               ! make space for ISF
388
389        std     %l0, [%sp + ISF_PSR_OFFSET]    ! save psr, PC
390        st      %l2, [%sp + ISF_NPC_OFFSET]    ! save nPC
391        st      %g1, [%sp + ISF_G1_OFFSET]     ! save g1
392        std     %g2, [%sp + ISF_G2_OFFSET]     ! save g2, g3
393        std     %l4, [%sp + ISF_G4_OFFSET]     ! save g4, g5 -- see above
[7c0bd74]394        st      %g7, [%sp + ISF_G7_OFFSET]     ! save g7
[5d69cd3]395
396        std     %i0, [%sp + ISF_I0_OFFSET]     ! save i0, i1
397        std     %i2, [%sp + ISF_I2_OFFSET]     ! save i2, i3
398        std     %i4, [%sp + ISF_I4_OFFSET]     ! save i4, i5
399        std     %i6, [%sp + ISF_I6_FP_OFFSET]  ! save i6/fp, i7
400
401        rd      %y, %g1
402        st      %g1, [%sp + ISF_Y_OFFSET]      ! save y
403        st      %l6, [%sp + ISF_TPC_OFFSET]    ! save real trapped pc
404
405        mov     %sp, %o1                       ! 2nd arg to ISR Handler
406
[849bb7a3]407        /*
408         *  Increment ISR nest level and Thread dispatch disable level.
409         *
410         *  Register usage for this section:
411         *
412         *    l6 = _Thread_Dispatch_disable_level value
413         *    l7 = _ISR_Nest_level value
414         *
[7c0bd74]415         *  NOTE: It is assumed that l6 - l7 will be preserved until the ISR
[849bb7a3]416         *        nest and thread dispatch disable levels are unnested.
417         */
418
[7c0bd74]419        ld       [%g6 + PER_CPU_ISR_NEST_LEVEL], %l7
420        ld       [%g6 + PER_CPU_THREAD_DISPATCH_DISABLE_LEVEL], %l6
[849bb7a3]421
422        add      %l7, 1, %l7
[7c0bd74]423        st       %l7, [%g6 + PER_CPU_ISR_NEST_LEVEL]
[849bb7a3]424
[f715433]425        add      %l6, 1, %l6
[7c0bd74]426        st       %l6, [%g6 + PER_CPU_THREAD_DISPATCH_DISABLE_LEVEL]
[f715433]427
[849bb7a3]428        /*
429         *  If ISR nest level was zero (now 1), then switch stack.
430         */
431
432        mov      %sp, %fp
433        subcc    %l7, 1, %l7             ! outermost interrupt handler?
434        bnz      dont_switch_stacks      ! No, then do not switch stacks
435
[de5d6d0]436#if defined( RTEMS_PROFILING )
437         sethi   %hi(SYM(_SPARC_Counter)), %o5
438        ld       [%o5 + %lo(SYM(_SPARC_Counter))], %l4
439        ld       [%l4], %o5
440#else
441         nop
442#endif
443
[7c0bd74]444        ld       [%g6 + PER_CPU_INTERRUPT_STACK_HIGH], %sp
[849bb7a3]445
446dont_switch_stacks:
447        /*
448         *  Make sure we have a place on the stack for the window overflow
449         *  trap handler to write into.  At this point it is safe to
450         *  enable traps again.
451         */
452
453        sub      %sp, CPU_MINIMUM_STACK_FRAME_SIZE, %sp
454
[5d69cd3]455        /*
456         *  Check if we have an external interrupt (trap 0x11 - 0x1f). If so,
457         *  set the PIL in the %psr to mask off interrupts with lower priority.
458         *  The original %psr in %l0 is not modified since it will be restored
459         *  when the interrupt handler returns.
460         */
461
462        mov      %l0, %g5
463        and      %l3, 0x0ff, %g4
464        subcc    %g4, 0x11, %g0
465        bl       dont_fix_pil
466        subcc    %g4, 0x1f, %g0
467        bg       dont_fix_pil
468        sll      %g4, 8, %g4
469        and      %g4, SPARC_PSR_PIL_MASK, %g4
470        andn     %l0, SPARC_PSR_PIL_MASK, %g5
471        ba       pil_fixed
472        or       %g4, %g5, %g5
473dont_fix_pil:
474        or       %g5, SPARC_PSR_PIL_MASK, %g5
475pil_fixed:
476        wr       %g5, SPARC_PSR_ET_MASK, %psr ! **** ENABLE TRAPS ****
477dont_fix_pil2:
478
479        /*
480         *  Vector to user's handler.
481         *
482         *  NOTE: TBR may no longer have vector number in it since
483         *        we just enabled traps.  It is definitely in l3.
484         */
485
486        sethi    %hi(SYM(_ISR_Vector_table)), %g4
[03b7789]487        or       %g4, %lo(SYM(_ISR_Vector_table)), %g4
[5d69cd3]488        and      %l3, 0xFF, %g5         ! remove synchronous trap indicator
489        sll      %g5, 2, %g5            ! g5 = offset into table
490        ld       [%g4 + %g5], %g4       ! g4 = _ISR_Vector_table[ vector ]
491
492
493                                        ! o1 = 2nd arg = address of the ISF
494                                        !   WAS LOADED WHEN ISF WAS SAVED!!!
495        mov      %l3, %o0               ! o0 = 1st arg = vector number
496        call     %g4, 0
[de5d6d0]497#if defined( RTEMS_PROFILING )
498         mov     %o5, %l3               ! save interrupt entry instant
499        cmp      %l7, 0
500        bne      profiling_not_outer_most_exit
501         nop
502        call     SYM(sparc_disable_interrupts), 0
503         nop
504        ld       [%l4], %o2             ! o2 = 3rd arg = interrupt exit instant
505        mov      %l3, %o1               ! o1 = 2nd arg = interrupt entry instant
506        call     SYM(_Profiling_Outer_most_interrupt_entry_and_exit), 0
[7c0bd74]507         mov     %g6, %o0               ! o0 = 1st arg = per-CPU control
[de5d6d0]508profiling_not_outer_most_exit:
509#else
510         nop                            ! delay slot
511#endif
[5d69cd3]512
513        /*
514         *  Redisable traps so we can finish up the interrupt processing.
515         *  This is a VERY conservative place to do this.
516         *
517         *  NOTE: %l0 has the PSR which was in place when we took the trap.
518         */
519
520        mov      %l0, %psr             ! **** DISABLE TRAPS ****
521        nop; nop; nop
522
523        /*
524         *  Decrement ISR nest level and Thread dispatch disable level.
525         *
526         *  Register usage for this section:
527         *
528         *    l6 = _Thread_Dispatch_disable_level value
529         *    l7 = _ISR_Nest_level value
530         */
531
[7c0bd74]532        st       %l7, [%g6 + PER_CPU_ISR_NEST_LEVEL]
[f715433]533
[5d69cd3]534        sub      %l6, 1, %l6
[7c0bd74]535        st       %l6, [%g6 + PER_CPU_THREAD_DISPATCH_DISABLE_LEVEL]
[5d69cd3]536
537        /*
538         *  If dispatching is disabled (includes nested interrupt case),
539         *  then do a "simple" exit.
540         */
541
542        orcc     %l6, %g0, %g0   ! Is dispatching disabled?
543        bnz      simple_return   ! Yes, then do a "simple" exit
[f8ad6c6f]544        nop
[5d69cd3]545
546        ! Are we dispatching from a previous ISR in the interrupted thread?
[7c0bd74]547        ld       [%g6 + SPARC_PER_CPU_ISR_DISPATCH_DISABLE], %l7
[5d69cd3]548        orcc     %l7, %g0, %g0   ! Is this thread already doing an ISR?
549        bnz      simple_return   ! Yes, then do a "simple" exit
[849bb7a3]550        nop
551
[5d69cd3]552
553        /*
554         *  If a context switch is necessary, then do fudge stack to
555         *  return to the interrupt dispatcher.
556         */
557
[7c0bd74]558        ldub     [%g6 + PER_CPU_DISPATCH_NEEDED], %l6
[849bb7a3]559
[f8ad6c6f]560        orcc     %l6, %g0, %g0   ! Is thread switch necessary?
[849bb7a3]561        bz       simple_return   ! no, then do a simple return
562        nop
563
[5d69cd3]564        /*
565         *  Invoke interrupt dispatcher.
566         */
567
568        ! Set ISR dispatch nesting prevention flag
569        mov      1,%l6
[7c0bd74]570        st       %l6, [%g6 + SPARC_PER_CPU_ISR_DISPATCH_DISABLE]
[5d69cd3]571
572        /*
573         *  The following subtract should get us back on the interrupted
574         *  tasks stack and add enough room to invoke the dispatcher.
575         *  When we enable traps, we are mostly back in the context
576         *  of the task and subsequent interrupts can operate normally.
577         */
578
579        sub      %fp, CPU_MINIMUM_STACK_FRAME_SIZE, %sp
580
581        or      %l0, SPARC_PSR_ET_MASK, %l7    ! l7 = PSR with ET=1
582        mov     %l7, %psr                      !  **** ENABLE TRAPS ****
583        nop
584        nop
585        nop
586isr_dispatch:
587        call    SYM(_Thread_Dispatch), 0
588        nop
589
590        /*
591         *  We invoked _Thread_Dispatch in a state similar to the interrupted
592         *  task.  In order to safely be able to tinker with the register
593         *  windows and get the task back to its pre-interrupt state,
594         *  we need to disable interrupts disabled so we can safely tinker
595         *  with the register windowing.  In particular, the CWP in the PSR
596         *  is fragile during this period. (See PR578.)
597         */
598        mov     2,%g1                           ! syscall (disable interrupts)
599        ta      0                               ! syscall (disable interrupts)
600
601        /*
602         *  While we had ISR dispatching disabled in this thread,
603         *  did we miss anything.  If so, then we need to do another
604         *  _Thread_Dispatch before leaving this ISR Dispatch context.
605         */
606
[7c0bd74]607        ldub     [%g6 + PER_CPU_DISPATCH_NEEDED], %l7
[849bb7a3]608
609        orcc     %l7, %g0, %g0    ! Is thread switch necesary?
610        bz       allow_nest_again ! No, then clear out and return
[5d69cd3]611        nop
612
613        ! Yes, then invoke the dispatcher
614dispatchAgain:
615        mov     3,%g1                           ! syscall (enable interrupts)
616        ta      0                               ! syscall (enable interrupts)
617        ba      isr_dispatch
618        nop
619
620allow_nest_again:
621
622        ! Zero out ISR stack nesting prevention flag
[7c0bd74]623        st       %g0, [%g6 + SPARC_PER_CPU_ISR_DISPATCH_DISABLE]
[5d69cd3]624
625        /*
626         *  The CWP in place at this point may be different from
627         *  that which was in effect at the beginning of the ISR if we
628         *  have been context switched between the beginning of this invocation
629         *  of _ISR_Handler and this point.  Thus the CWP and WIM should
630         *  not be changed back to their values at ISR entry time.  Any
631         *  changes to the PSR must preserve the CWP.
632         */
633
634simple_return:
635        ld      [%fp + ISF_Y_OFFSET], %l5      ! restore y
636        wr      %l5, 0, %y
637
638        ldd     [%fp + ISF_PSR_OFFSET], %l0    ! restore psr, PC
639        ld      [%fp + ISF_NPC_OFFSET], %l2    ! restore nPC
640        rd      %psr, %l3
641        and     %l3, SPARC_PSR_CWP_MASK, %l3   ! want "current" CWP
642        andn    %l0, SPARC_PSR_CWP_MASK, %l0   ! want rest from task
643        or      %l3, %l0, %l0                  ! install it later...
644        andn    %l0, SPARC_PSR_ET_MASK, %l0
645
646        /*
647         *  Restore tasks global and out registers
648         */
649
650        mov    %fp, %g1
651
652                                              ! g1 is restored later
653        ldd     [%fp + ISF_G2_OFFSET], %g2    ! restore g2, g3
654        ldd     [%fp + ISF_G4_OFFSET], %g4    ! restore g4, g5
[7c0bd74]655        ld      [%fp + ISF_G7_OFFSET], %g7    ! restore g7
[5d69cd3]656
657        ldd     [%fp + ISF_I0_OFFSET], %i0    ! restore i0, i1
658        ldd     [%fp + ISF_I2_OFFSET], %i2    ! restore i2, i3
659        ldd     [%fp + ISF_I4_OFFSET], %i4    ! restore i4, i5
660        ldd     [%fp + ISF_I6_FP_OFFSET], %i6 ! restore i6/fp, i7
661
662        /*
663         *  Registers:
664         *
665         *   ALL global registers EXCEPT G1 and the input registers have
666         *   already been restored and thuse off limits.
667         *
668         *   The following is the contents of the local registers:
669         *
670         *     l0 = original psr
671         *     l1 = return address (i.e. PC)
672         *     l2 = nPC
673         *     l3 = CWP
674         */
675
676        /*
677         *  if (CWP + 1) is an invalid window then we need to reload it.
678         *
679         *  WARNING: Traps should now be disabled
680         */
681
682        mov     %l0, %psr                  !  **** DISABLE TRAPS ****
683        nop
684        nop
685        nop
686        rd      %wim, %l4
687        add     %l0, 1, %l6                ! l6 = cwp + 1
688        and     %l6, SPARC_PSR_CWP_MASK, %l6 ! do the modulo on it
689        srl     %l4, %l6, %l5              ! l5 = win >> cwp + 1 ; shift count
690                                           !  and CWP are conveniently LS 5 bits
691        cmp     %l5, 1                     ! Is tasks window invalid?
692        bne     good_task_window
693
694        /*
695         *  The following code is the same as a 1 position left rotate of WIM.
696         */
697
698        sll     %l4, 1, %l5                ! l5 = WIM << 1
699        srl     %l4, SPARC_NUMBER_OF_REGISTER_WINDOWS-1 , %l4
700                                           ! l4 = WIM >> (Number Windows - 1)
701        or      %l4, %l5, %l4              ! l4 = (WIM << 1) |
702                                           !      (WIM >> (Number Windows - 1))
703
704        /*
705         *  Now restore the window just as if we underflowed to it.
706         */
707
708        wr      %l4, 0, %wim               ! WIM = new WIM
709        nop                                ! must delay after writing WIM
710        nop
711        nop
712        restore                            ! now into the tasks window
713
714        ldd     [%g1 + CPU_STACK_FRAME_L0_OFFSET], %l0
715        ldd     [%g1 + CPU_STACK_FRAME_L2_OFFSET], %l2
716        ldd     [%g1 + CPU_STACK_FRAME_L4_OFFSET], %l4
717        ldd     [%g1 + CPU_STACK_FRAME_L6_OFFSET], %l6
718        ldd     [%g1 + CPU_STACK_FRAME_I0_OFFSET], %i0
719        ldd     [%g1 + CPU_STACK_FRAME_I2_OFFSET], %i2
720        ldd     [%g1 + CPU_STACK_FRAME_I4_OFFSET], %i4
721        ldd     [%g1 + CPU_STACK_FRAME_I6_FP_OFFSET], %i6
722                                           ! reload of sp clobbers ISF
723        save                               ! Back to ISR dispatch window
724
725good_task_window:
726
727        mov     %l0, %psr                  !  **** DISABLE TRAPS ****
728        nop; nop; nop
729                                           !  and restore condition codes.
730        ld      [%g1 + ISF_G1_OFFSET], %g1 ! restore g1
731        jmp     %l1                        ! transfer control and
732        rett    %l2                        ! go back to tasks window
733
734/* end of file */
Note: See TracBrowser for help on using the repository browser.