source: rtems/cpukit/score/cpu/sparc/cpu_asm.S @ 6d42b4c6

4.115
Last change on this file since 6d42b4c6 was 6d42b4c6, checked in by Joel Sherrill <joel.sherrill@…>, on 06/29/10 at 00:34:00

2010-06-28 Joel Sherrill <joel.sherrill@…>

PR 1573/cpukit

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