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

wuf.S (8614B)


      1/* SPDX-License-Identifier: GPL-2.0 */
      2/*
      3 * wuf.S: Window underflow trap handler for the Sparc.
      4 *
      5 * Copyright (C) 1995 David S. Miller
      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/* Just like the overflow handler we define macros for registers
     19 * with fixed meanings in this routine.
     20 */
     21#define t_psr       l0
     22#define t_pc        l1
     23#define t_npc       l2
     24#define t_wim       l3
     25/* Don't touch the above registers or else you die horribly... */
     26
     27/* Now macros for the available scratch registers in this routine. */
     28#define twin_tmp1    l4
     29#define twin_tmp2    l5
     30
     31#define curptr       g6
     32
     33	.text
     34	.align	4
     35
     36	/* The trap entry point has executed the following:
     37	 *
     38	 * rd    %psr, %l0
     39	 * rd    %wim, %l3
     40	 * b     fill_window_entry
     41	 * andcc %l0, PSR_PS, %g0
     42	 */
     43
     44	/* Datum current_thread_info->uwinmask contains at all times a bitmask
     45	 * where if any user windows are active, at least one bit will
     46	 * be set in to mask.  If no user windows are active, the bitmask
     47	 * will be all zeroes.
     48	 */
     49
     50	/* To get an idea of what has just happened to cause this
     51	 * trap take a look at this diagram:
     52	 *
     53	 *      1  2  3  4     <--  Window number
     54	 *      ----------
     55	 *      T  O  W  I     <--  Symbolic name
     56	 *
     57	 *      O == the window that execution was in when
     58	 *           the restore was attempted
     59	 *
     60	 *      T == the trap itself has save'd us into this
     61	 *           window
     62	 *
     63	 *      W == this window is the one which is now invalid
     64	 *           and must be made valid plus loaded from the
     65	 *           stack
     66	 *
     67	 *      I == this window will be the invalid one when we
     68	 *           are done and return from trap if successful
     69	 */
     70
     71	/* BEGINNING OF PATCH INSTRUCTIONS */
     72
     73	/* On 7-window Sparc the boot code patches fnwin_patch1
     74	 * with the following instruction.
     75	 */
     76	.globl	fnwin_patch1_7win, fnwin_patch2_7win
     77fnwin_patch1_7win:	srl	%t_wim, 6, %twin_tmp2
     78fnwin_patch2_7win:	and	%twin_tmp1, 0x7f, %twin_tmp1
     79	/* END OF PATCH INSTRUCTIONS */
     80
     81	.globl	fill_window_entry, fnwin_patch1, fnwin_patch2
     82fill_window_entry:
     83	/* LOCATION: Window 'T' */
     84
     85	/* Compute what the new %wim is going to be if we retrieve
     86	 * the proper window off of the stack.
     87	 */
     88		sll	%t_wim, 1, %twin_tmp1
     89fnwin_patch1:	srl	%t_wim, 7, %twin_tmp2
     90		or	%twin_tmp1, %twin_tmp2, %twin_tmp1
     91fnwin_patch2:	and	%twin_tmp1, 0xff, %twin_tmp1
     92
     93	wr	%twin_tmp1, 0x0, %wim	/* Make window 'I' invalid */
     94
     95	andcc	%t_psr, PSR_PS, %g0
     96	be	fwin_from_user
     97	 restore	%g0, %g0, %g0		/* Restore to window 'O' */
     98
     99	/* Trapped from kernel, we trust that the kernel does not
    100	 * 'over restore' sorta speak and just grab the window
    101	 * from the stack and return.  Easy enough.
    102	 */
    103fwin_from_kernel:
    104	/* LOCATION: Window 'O' */
    105
    106	restore %g0, %g0, %g0
    107
    108	/* LOCATION: Window 'W' */
    109
    110	LOAD_WINDOW(sp)	                /* Load it up */
    111
    112	/* Spin the wheel... */
    113	save	%g0, %g0, %g0
    114	save	%g0, %g0, %g0
    115	/* I'd like to buy a vowel please... */
    116
    117	/* LOCATION: Window 'T' */
    118
    119	/* Now preserve the condition codes in %psr, pause, and
    120	 * return from trap.  This is the simplest case of all.
    121	 */
    122	wr	%t_psr, 0x0, %psr
    123	WRITE_PAUSE
    124
    125	jmp	%t_pc
    126	rett	%t_npc
    127
    128fwin_from_user:
    129	/* LOCATION: Window 'O' */
    130
    131	restore	%g0, %g0, %g0		/* Restore to window 'W' */
    132
    133	/* LOCATION: Window 'W' */
    134
    135	/* Branch to the stack validation routine */
    136	b	srmmu_fwin_stackchk
    137	 andcc	%sp, 0x7, %g0
    138
    139#define STACK_OFFSET (THREAD_SIZE - TRACEREG_SZ - STACKFRAME_SZ)
    140
    141fwin_user_stack_is_bolixed:
    142	/* LOCATION: Window 'W' */
    143
    144	/* Place a pt_regs frame on the kernel stack, save back
    145	 * to the trap window and call c-code to deal with this.
    146	 */
    147	LOAD_CURRENT(l4, l5)
    148
    149	sethi	%hi(STACK_OFFSET), %l5
    150	or	%l5, %lo(STACK_OFFSET), %l5
    151	add	%l4, %l5, %l5
    152
    153	/* Store globals into pt_regs frame. */
    154	STORE_PT_GLOBALS(l5)
    155	STORE_PT_YREG(l5, g3)
    156
    157	/* Save current in a global while we change windows. */
    158	mov	%l4, %curptr
    159
    160	save	%g0, %g0, %g0
    161
    162	/* LOCATION: Window 'O' */
    163
    164	rd	%psr, %g3		/* Read %psr in live user window */
    165	mov	%fp, %g4		/* Save bogus frame pointer. */
    166
    167	save	%g0, %g0, %g0
    168
    169	/* LOCATION: Window 'T' */
    170
    171	sethi	%hi(STACK_OFFSET), %l5
    172	or	%l5, %lo(STACK_OFFSET), %l5
    173	add	%curptr, %l5, %sp
    174
    175	/* Build rest of pt_regs. */
    176	STORE_PT_INS(sp)
    177	STORE_PT_PRIV(sp, t_psr, t_pc, t_npc)
    178
    179	/* re-set trap time %wim value */
    180	wr	%t_wim, 0x0, %wim
    181
    182	/* Fix users window mask and buffer save count. */
    183	mov	0x1, %g5
    184	sll	%g5, %g3, %g5
    185	st	%g5, [%curptr + TI_UWINMASK]		! one live user window still
    186	st	%g0, [%curptr + TI_W_SAVED]		! no windows in the buffer
    187
    188	wr	%t_psr, PSR_ET, %psr			! enable traps
    189	nop
    190	call	window_underflow_fault
    191	 mov	%g4, %o0
    192
    193	b	ret_trap_entry
    194	 clr	%l6
    195
    196fwin_user_stack_is_ok:
    197	/* LOCATION: Window 'W' */
    198
    199	/* The users stack area is kosher and mapped, load the
    200	 * window and fall through to the finish up routine.
    201	 */
    202	LOAD_WINDOW(sp)
    203
    204	/* Round and round she goes... */
    205	save	%g0, %g0, %g0		/* Save to window 'O' */
    206	save	%g0, %g0, %g0		/* Save to window 'T' */
    207	/* Where she'll trap nobody knows... */
    208
    209	/* LOCATION: Window 'T' */
    210
    211fwin_user_finish_up:
    212	/* LOCATION: Window 'T' */
    213
    214	wr	%t_psr, 0x0, %psr
    215	WRITE_PAUSE	
    216
    217	jmp	%t_pc
    218	rett	%t_npc
    219
    220	/* Here come the architecture specific checks for stack.
    221	 * mappings.  Note that unlike the window overflow handler
    222	 * we only need to check whether the user can read from
    223	 * the appropriate addresses.  Also note that we are in
    224	 * an invalid window which will be loaded, and this means
    225	 * that until we actually load the window up we are free
    226	 * to use any of the local registers contained within.
    227	 *
    228	 * On success these routine branch to fwin_user_stack_is_ok
    229	 * if the area at %sp is user readable and the window still
    230	 * needs to be loaded, else fwin_user_finish_up if the
    231	 * routine has done the loading itself.  On failure (bogus
    232	 * user stack) the routine shall branch to the label called
    233	 * fwin_user_stack_is_bolixed.
    234	 *
    235	 * Contrary to the arch-specific window overflow stack
    236	 * check routines in wof.S, these routines are free to use
    237	 * any of the local registers they want to as this window
    238	 * does not belong to anyone at this point, however the
    239	 * outs and ins are still verboten as they are part of
    240	 * 'someone elses' window possibly.
    241	 */
    242
    243	.globl	srmmu_fwin_stackchk
    244srmmu_fwin_stackchk:
    245	/* LOCATION: Window 'W' */
    246
    247	/* Caller did 'andcc %sp, 0x7, %g0' */
    248	bne	fwin_user_stack_is_bolixed
    249	 sethi   %hi(PAGE_OFFSET), %l5
    250
    251	/* Check if the users stack is in kernel vma, then our
    252	 * trial and error technique below would succeed for
    253	 * the 'wrong' reason.
    254	 */
    255	mov	AC_M_SFSR, %l4
    256	cmp	%l5, %sp
    257	bleu	fwin_user_stack_is_bolixed
    258LEON_PI( lda	[%l4] ASI_LEON_MMUREGS, %g0)	! clear fault status
    259SUN_PI_( lda	[%l4] ASI_M_MMUREGS, %g0)	! clear fault status
    260
    261	/* The technique is, turn off faults on this processor,
    262	 * just let the load rip, then check the sfsr to see if
    263	 * a fault did occur.  Then we turn on fault traps again
    264	 * and branch conditionally based upon what happened.
    265	 */
    266LEON_PI(lda	[%g0] ASI_LEON_MMUREGS, %l5)	! read mmu-ctrl reg
    267SUN_PI_(lda	[%g0] ASI_M_MMUREGS, %l5)	! read mmu-ctrl reg
    268	or	%l5, 0x2, %l5			! turn on no-fault bit
    269LEON_PI(sta	%l5, [%g0] ASI_LEON_MMUREGS)	! store it
    270SUN_PI_(sta	%l5, [%g0] ASI_M_MMUREGS)	! store it
    271
    272	/* Cross fingers and go for it. */
    273	LOAD_WINDOW(sp)
    274
    275	/* A penny 'saved'... */
    276	save	%g0, %g0, %g0
    277	save	%g0, %g0, %g0
    278	/* Is a BADTRAP earned... */
    279
    280	/* LOCATION: Window 'T' */
    281
    282LEON_PI(lda	[%g0] ASI_LEON_MMUREGS, %twin_tmp1)	! load mmu-ctrl again
    283SUN_PI_(lda	[%g0] ASI_M_MMUREGS, %twin_tmp1)	! load mmu-ctrl again
    284	andn	%twin_tmp1, 0x2, %twin_tmp1		! clear no-fault bit
    285LEON_PI(sta	%twin_tmp1, [%g0] ASI_LEON_MMUREGS)	! store it
    286SUN_PI_(sta	%twin_tmp1, [%g0] ASI_M_MMUREGS)	! store it
    287
    288	mov	AC_M_SFAR, %twin_tmp2
    289LEON_PI(lda	[%twin_tmp2] ASI_LEON_MMUREGS, %g0)	! read fault address
    290SUN_PI_(lda	[%twin_tmp2] ASI_M_MMUREGS, %g0)	! read fault address
    291
    292	mov	AC_M_SFSR, %twin_tmp2
    293LEON_PI(lda	[%twin_tmp2] ASI_LEON_MMUREGS, %twin_tmp2) ! read fault status
    294SUN_PI_(lda	[%twin_tmp2] ASI_M_MMUREGS, %twin_tmp2)	   ! read fault status
    295	andcc	%twin_tmp2, 0x2, %g0			   ! did fault occur?
    296
    297	bne	1f					   ! yep, cleanup
    298	 nop
    299
    300	wr	%t_psr, 0x0, %psr
    301	nop
    302	b	fwin_user_finish_up + 0x4
    303	 nop
    304
    305	/* Did I ever tell you about my window lobotomy?
    306	 * anyways... fwin_user_stack_is_bolixed expects
    307	 * to be in window 'W' so make it happy or else
    308	 * we watchdog badly.
    309	 */
    3101:
    311	restore	%g0, %g0, %g0
    312	b	fwin_user_stack_is_bolixed	! oh well
    313	 restore	%g0, %g0, %g0