cachepc-linux

Fork of AMDESE/linux with modifications for CachePC side-channel attack
git clone https://git.sinitax.com/sinitax/cachepc-linux
Log | Files | Refs | README | LICENSE | sfeed.txt

wof.S (12094B)


      1/* SPDX-License-Identifier: GPL-2.0 */
      2/*
      3 * wof.S: Sparc window overflow handler.
      4 *
      5 * Copyright (C) 1995 David S. Miller (davem@caip.rutgers.edu)
      6 */
      7
      8#include <asm/contregs.h>
      9#include <asm/page.h>
     10#include <asm/ptrace.h>
     11#include <asm/psr.h>
     12#include <asm/smp.h>
     13#include <asm/asi.h>
     14#include <asm/winmacro.h>
     15#include <asm/asmmacro.h>
     16#include <asm/thread_info.h>
     17
     18/* WARNING: This routine is hairy and _very_ complicated, but it
     19 *          must be as fast as possible as it handles the allocation
     20 *          of register windows to the user and kernel.  If you touch
     21 *          this code be _very_ careful as many other pieces of the
     22 *          kernel depend upon how this code behaves.  You have been
     23 *          duly warned...
     24 */
     25
     26/* We define macro's for registers which have a fixed
     27 * meaning throughout this entire routine.  The 'T' in
     28 * the comments mean that the register can only be
     29 * accessed when in the 'trap' window, 'G' means
     30 * accessible in any window.  Do not change these registers
     31 * after they have been set, until you are ready to return
     32 * from the trap.
     33 */
     34#define t_psr       l0 /* %psr at trap time                     T */
     35#define t_pc        l1 /* PC for trap return                    T */
     36#define t_npc       l2 /* NPC for trap return                   T */
     37#define t_wim       l3 /* %wim at trap time                     T */
     38#define saved_g5    l5 /* Global save register                  T */
     39#define saved_g6    l6 /* Global save register                  T */
     40#define curptr      g6 /* Gets set to 'current' then stays      G */
     41
     42/* Now registers whose values can change within the handler.      */
     43#define twin_tmp    l4 /* Temp reg, only usable in trap window  T */
     44#define glob_tmp    g5 /* Global temporary reg, usable anywhere G */
     45
     46	.text
     47	.align	4
     48	/* BEGINNING OF PATCH INSTRUCTIONS */
     49	/* On a 7-window Sparc the boot code patches spnwin_*
     50	 * instructions with the following ones.
     51	 */
     52	.globl	spnwin_patch1_7win, spnwin_patch2_7win, spnwin_patch3_7win
     53spnwin_patch1_7win:	sll	%t_wim, 6, %glob_tmp
     54spnwin_patch2_7win:	and	%glob_tmp, 0x7f, %glob_tmp
     55spnwin_patch3_7win:	and	%twin_tmp, 0x7f, %twin_tmp
     56	/* END OF PATCH INSTRUCTIONS */
     57
     58	/* The trap entry point has done the following:
     59	 *
     60	 * rd    %psr, %l0
     61	 * rd    %wim, %l3
     62	 * b     spill_window_entry
     63	 * andcc %l0, PSR_PS, %g0
     64	 */
     65
     66	/* Datum current_thread_info->uwinmask contains at all times a bitmask
     67	 * where if any user windows are active, at least one bit will
     68	 * be set in to mask.  If no user windows are active, the bitmask
     69	 * will be all zeroes.
     70	 */
     71	.globl	spill_window_entry 
     72	.globl	spnwin_patch1, spnwin_patch2, spnwin_patch3
     73spill_window_entry:
     74	/* LOCATION: Trap Window */
     75
     76	mov	%g5, %saved_g5		! save away global temp register
     77	mov	%g6, %saved_g6		! save away 'current' ptr register
     78
     79	/* Compute what the new %wim will be if we save the
     80	 * window properly in this trap handler.
     81	 *
     82	 * newwim = ((%wim>>1) | (%wim<<(nwindows - 1)));
     83	 */
     84		srl	%t_wim, 0x1, %twin_tmp
     85spnwin_patch1:	sll	%t_wim, 7, %glob_tmp
     86		or	%glob_tmp, %twin_tmp, %glob_tmp
     87spnwin_patch2:	and	%glob_tmp, 0xff, %glob_tmp
     88
     89	/* The trap entry point has set the condition codes
     90	 * up for us to see if this is from user or kernel.
     91	 * Get the load of 'curptr' out of the way.
     92	 */
     93	LOAD_CURRENT(curptr, twin_tmp)
     94
     95	andcc	%t_psr, PSR_PS, %g0
     96	be,a	spwin_fromuser				! all user wins, branch
     97	 save	%g0, %g0, %g0				! Go where saving will occur
     98	
     99	/* See if any user windows are active in the set. */
    100	ld	[%curptr + TI_UWINMASK], %twin_tmp	! grab win mask
    101	orcc	%g0, %twin_tmp, %g0			! check for set bits
    102	bne	spwin_exist_uwins			! yep, there are some
    103	 andn	%twin_tmp, %glob_tmp, %twin_tmp		! compute new uwinmask
    104
    105	/* Save into the window which must be saved and do it.
    106	 * Basically if we are here, this means that we trapped
    107	 * from kernel mode with only kernel windows in the register
    108	 * file.
    109	 */
    110	save	%g0, %g0, %g0		! save into the window to stash away
    111	wr	%glob_tmp, 0x0, %wim	! set new %wim, this is safe now
    112
    113spwin_no_userwins_from_kernel:
    114	/* LOCATION: Window to be saved */
    115
    116	STORE_WINDOW(sp)		! stash the window
    117	restore	%g0, %g0, %g0		! go back into trap window
    118
    119	/* LOCATION: Trap window */
    120	mov	%saved_g5, %g5		! restore %glob_tmp
    121	mov	%saved_g6, %g6		! restore %curptr
    122	wr	%t_psr, 0x0, %psr	! restore condition codes in %psr
    123	WRITE_PAUSE			! waste some time
    124	jmp	%t_pc			! Return from trap
    125	rett	%t_npc			! we are done
    126
    127spwin_exist_uwins:
    128	/* LOCATION: Trap window */
    129
    130	/* Wow, user windows have to be dealt with, this is dirty
    131	 * and messy as all hell.  And difficult to follow if you
    132	 * are approaching the infamous register window trap handling
    133	 * problem for the first time. DON'T LOOK!
    134	 *
    135	 * Note that how the execution path works out, the new %wim
    136	 * will be left for us in the global temporary register,
    137	 * %glob_tmp.  We cannot set the new %wim first because we
    138	 * need to save into the appropriate window without inducing
    139	 * a trap (traps are off, we'd get a watchdog wheee)...
    140	 * But first, store the new user window mask calculated
    141	 * above.
    142	 */
    143	st	%twin_tmp, [%curptr + TI_UWINMASK]
    144	save	%g0, %g0, %g0		! Go to where the saving will occur
    145
    146spwin_fromuser:
    147	/* LOCATION: Window to be saved */
    148	wr	%glob_tmp, 0x0, %wim	! Now it is safe to set new %wim
    149
    150	/* LOCATION: Window to be saved */
    151
    152	/* This instruction branches to a routine which will check
    153	 * to validity of the users stack pointer by whatever means
    154	 * are necessary.  This means that this is architecture
    155	 * specific and thus this branch instruction will need to
    156	 * be patched at boot time once the machine type is known.
    157	 * This routine _shall not_ touch %curptr under any
    158	 * circumstances whatsoever!  It will branch back to the
    159	 * label 'spwin_good_ustack' if the stack is ok but still
    160	 * needs to be dumped (SRMMU for instance will not need to
    161	 * do this) or 'spwin_finish_up' if the stack is ok and the
    162	 * registers have already been saved.  If the stack is found
    163	 * to be bogus for some reason the routine shall branch to
    164	 * the label 'spwin_user_stack_is_bolixed' which will take
    165	 * care of things at that point.
    166	 */
    167	b	spwin_srmmu_stackchk
    168	 andcc	%sp, 0x7, %g0
    169
    170spwin_good_ustack:
    171	/* LOCATION: Window to be saved */
    172
    173	/* The users stack is ok and we can safely save it at
    174	 * %sp.
    175	 */
    176	STORE_WINDOW(sp)
    177
    178spwin_finish_up:
    179	restore	%g0, %g0, %g0		/* Back to trap window. */
    180
    181	/* LOCATION: Trap window */
    182
    183	/* We have spilled successfully, and we have properly stored
    184	 * the appropriate window onto the stack.
    185	 */
    186
    187	/* Restore saved globals */
    188	mov	%saved_g5, %g5
    189	mov	%saved_g6, %g6
    190
    191	wr	%t_psr, 0x0, %psr
    192	WRITE_PAUSE
    193	jmp	%t_pc
    194	rett	%t_npc
    195
    196spwin_user_stack_is_bolixed:
    197	/* LOCATION: Window to be saved */
    198
    199	/* Wheee, user has trashed his/her stack.  We have to decide
    200	 * how to proceed based upon whether we came from kernel mode
    201	 * or not.  If we came from kernel mode, toss the window into
    202	 * a special buffer and proceed, the kernel _needs_ a window
    203	 * and we could be in an interrupt handler so timing is crucial.
    204	 * If we came from user land we build a full stack frame and call
    205	 * c-code to gun down the process.
    206	 */
    207	rd	%psr, %glob_tmp
    208	andcc	%glob_tmp, PSR_PS, %g0
    209	bne	spwin_bad_ustack_from_kernel
    210	 nop
    211
    212	/* Oh well, throw this one window into the per-task window
    213	 * buffer, the first one.
    214	 */
    215	st	%sp, [%curptr + TI_RWIN_SPTRS]
    216	STORE_WINDOW(curptr + TI_REG_WINDOW)
    217	restore	%g0, %g0, %g0
    218
    219	/* LOCATION: Trap Window */
    220
    221	/* Back in the trap window, update winbuffer save count. */
    222	mov	1, %twin_tmp
    223	st	%twin_tmp, [%curptr + TI_W_SAVED]
    224
    225		/* Compute new user window mask.  What we are basically
    226		 * doing is taking two windows, the invalid one at trap
    227		 * time and the one we attempted to throw onto the users
    228		 * stack, and saying that everything else is an ok user
    229		 * window.  umask = ((~(%t_wim | %wim)) & valid_wim_bits)
    230		 */
    231		rd	%wim, %twin_tmp
    232		or	%twin_tmp, %t_wim, %twin_tmp
    233		not	%twin_tmp
    234spnwin_patch3:	and	%twin_tmp, 0xff, %twin_tmp	! patched on 7win Sparcs
    235		st	%twin_tmp, [%curptr + TI_UWINMASK]
    236
    237#define STACK_OFFSET (THREAD_SIZE - TRACEREG_SZ - STACKFRAME_SZ)
    238
    239	sethi	%hi(STACK_OFFSET), %sp
    240	or	%sp, %lo(STACK_OFFSET), %sp
    241	add	%curptr, %sp, %sp
    242
    243	/* Restore the saved globals and build a pt_regs frame. */
    244	mov	%saved_g5, %g5
    245	mov	%saved_g6, %g6
    246	STORE_PT_ALL(sp, t_psr, t_pc, t_npc, g1)
    247
    248	sethi	%hi(STACK_OFFSET), %g6
    249	or	%g6, %lo(STACK_OFFSET), %g6
    250	sub	%sp, %g6, %g6		! curptr
    251
    252	/* Turn on traps and call c-code to deal with it. */
    253	wr	%t_psr, PSR_ET, %psr
    254	nop
    255	call	window_overflow_fault
    256	 nop
    257
    258	/* Return from trap if C-code actually fixes things, if it
    259	 * doesn't then we never get this far as the process will
    260	 * be given the look of death from Commander Peanut.
    261	 */
    262	b	ret_trap_entry
    263	 clr	%l6
    264
    265spwin_bad_ustack_from_kernel:
    266	/* LOCATION: Window to be saved */
    267
    268	/* The kernel provoked a spill window trap, but the window we
    269	 * need to save is a user one and the process has trashed its
    270	 * stack pointer.  We need to be quick, so we throw it into
    271	 * a per-process window buffer until we can properly handle
    272	 * this later on.
    273	 */
    274	SAVE_BOLIXED_USER_STACK(curptr, glob_tmp)
    275	restore	%g0, %g0, %g0
    276
    277	/* LOCATION: Trap window */
    278
    279	/* Restore globals, condition codes in the %psr and
    280	 * return from trap.  Note, restoring %g6 when returning
    281	 * to kernel mode is not necessarily these days. ;-)
    282	 */
    283	mov	%saved_g5, %g5
    284	mov	%saved_g6, %g6
    285
    286	wr	%t_psr, 0x0, %psr
    287	WRITE_PAUSE
    288
    289	jmp	%t_pc
    290	rett	%t_npc
    291
    292/* Undefine the register macros which would only cause trouble
    293 * if used below.  This helps find 'stupid' coding errors that
    294 * produce 'odd' behavior.  The routines below are allowed to
    295 * make usage of glob_tmp and t_psr so we leave them defined.
    296 */
    297#undef twin_tmp
    298#undef curptr
    299#undef t_pc
    300#undef t_npc
    301#undef t_wim
    302#undef saved_g5
    303#undef saved_g6
    304
    305/* Now come the per-architecture window overflow stack checking routines.
    306 * As noted above %curptr cannot be touched by this routine at all.
    307 */
    308
    309	/* This is a generic SRMMU routine.  As far as I know this
    310	 * works for all current v8/srmmu implementations, we'll
    311	 * see...
    312	 */
    313	.globl	spwin_srmmu_stackchk
    314spwin_srmmu_stackchk:
    315	/* LOCATION: Window to be saved on the stack */
    316
    317	/* Because of SMP concerns and speed we play a trick.
    318	 * We disable fault traps in the MMU control register,
    319	 * Execute the stores, then check the fault registers
    320	 * to see what happens.  I can hear Linus now
    321	 * "disgusting... broken hardware...".
    322	 *
    323	 * But first, check to see if the users stack has ended
    324	 * up in kernel vma, then we would succeed for the 'wrong'
    325	 * reason... ;(  Note that the 'sethi' below assumes the
    326	 * kernel is page aligned, which should always be the case.
    327	 */
    328	/* Check results of callers andcc %sp, 0x7, %g0 */
    329	bne	spwin_user_stack_is_bolixed
    330	 sethi   %hi(PAGE_OFFSET), %glob_tmp
    331	cmp	%glob_tmp, %sp
    332	bleu	spwin_user_stack_is_bolixed
    333	 mov	AC_M_SFSR, %glob_tmp
    334
    335	/* Clear the fault status and turn on the no_fault bit. */
    336LEON_PI(lda	[%glob_tmp] ASI_LEON_MMUREGS, %g0)	! eat SFSR
    337SUN_PI_(lda	[%glob_tmp] ASI_M_MMUREGS, %g0)		! eat SFSR
    338
    339LEON_PI(lda	[%g0] ASI_LEON_MMUREGS, %glob_tmp)	! read MMU control
    340SUN_PI_(lda	[%g0] ASI_M_MMUREGS, %glob_tmp)		! read MMU control
    341	or	%glob_tmp, 0x2, %glob_tmp		! or in no_fault bit
    342LEON_PI(sta	%glob_tmp, [%g0] ASI_LEON_MMUREGS)	! set it
    343SUN_PI_(sta	%glob_tmp, [%g0] ASI_M_MMUREGS)		! set it
    344
    345	/* Dump the registers and cross fingers. */
    346	STORE_WINDOW(sp)
    347
    348	/* Clear the no_fault bit and check the status. */
    349	andn	%glob_tmp, 0x2, %glob_tmp
    350LEON_PI(sta	%glob_tmp, [%g0] ASI_LEON_MMUREGS)
    351SUN_PI_(sta	%glob_tmp, [%g0] ASI_M_MMUREGS)
    352
    353	mov	AC_M_SFAR, %glob_tmp
    354LEON_PI(lda	[%glob_tmp] ASI_LEON_MMUREGS, %g0)
    355SUN_PI_(lda	[%glob_tmp] ASI_M_MMUREGS, %g0)
    356
    357	mov	AC_M_SFSR, %glob_tmp
    358LEON_PI(lda	[%glob_tmp] ASI_LEON_MMUREGS, %glob_tmp)
    359SUN_PI_(lda	[%glob_tmp] ASI_M_MMUREGS, %glob_tmp)
    360	andcc	%glob_tmp, 0x2, %g0			! did we fault?
    361	be,a	spwin_finish_up + 0x4			! cool beans, success
    362	 restore %g0, %g0, %g0
    363
    364	rd	%psr, %glob_tmp
    365	b	spwin_user_stack_is_bolixed + 0x4	! we faulted, ugh
    366	 nop