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

phys2virt.S (7924B)


      1/* SPDX-License-Identifier: GPL-2.0-only */
      2/*
      3 *  Copyright (C) 1994-2002 Russell King
      4 *  Copyright (c) 2003, 2020 ARM Limited
      5 *  All Rights Reserved
      6 */
      7
      8#include <linux/init.h>
      9#include <linux/linkage.h>
     10#include <asm/assembler.h>
     11#include <asm/page.h>
     12
     13#ifdef __ARMEB__
     14#define LOW_OFFSET	0x4
     15#define HIGH_OFFSET	0x0
     16#else
     17#define LOW_OFFSET	0x0
     18#define HIGH_OFFSET	0x4
     19#endif
     20
     21/*
     22 * __fixup_pv_table - patch the stub instructions with the delta between
     23 *                    PHYS_OFFSET and PAGE_OFFSET, which is assumed to be
     24 *                    2 MiB aligned.
     25 *
     26 * Called from head.S, which expects the following registers to be preserved:
     27 *   r1 = machine no, r2 = atags or dtb,
     28 *   r8 = phys_offset, r9 = cpuid, r10 = procinfo
     29 */
     30	__HEAD
     31ENTRY(__fixup_pv_table)
     32	mov	r0, r8, lsr #PAGE_SHIFT	@ convert to PFN
     33	str_l	r0, __pv_phys_pfn_offset, r3
     34
     35	adr_l	r0, __pv_offset
     36	subs	r3, r8, #PAGE_OFFSET	@ PHYS_OFFSET - PAGE_OFFSET
     37	mvn	ip, #0
     38	strcc	ip, [r0, #HIGH_OFFSET]	@ save to __pv_offset high bits
     39	str	r3, [r0, #LOW_OFFSET]	@ save to __pv_offset low bits
     40
     41	mov	r0, r3, lsr #21		@ constant for add/sub instructions
     42	teq	r3, r0, lsl #21 	@ must be 2 MiB aligned
     43	bne	0f
     44
     45	adr_l	r4, __pv_table_begin
     46	adr_l	r5, __pv_table_end
     47	b	__fixup_a_pv_table
     48
     490:	mov	r0, r0			@ deadloop on error
     50	b	0b
     51ENDPROC(__fixup_pv_table)
     52
     53	.text
     54__fixup_a_pv_table:
     55	adr_l	r6, __pv_offset
     56	ldr	r0, [r6, #HIGH_OFFSET]	@ pv_offset high word
     57	ldr	r6, [r6, #LOW_OFFSET]	@ pv_offset low word
     58	cmn	r0, #1
     59#ifdef CONFIG_THUMB2_KERNEL
     60	@
     61	@ The Thumb-2 versions of the patchable sequences are
     62	@
     63	@ phys-to-virt:			movw	<reg>, #offset<31:21>
     64	@				lsl	<reg>, #21
     65	@				sub	<VA>, <PA>, <reg>
     66	@
     67	@ virt-to-phys (non-LPAE):	movw	<reg>, #offset<31:21>
     68	@				lsl	<reg>, #21
     69	@				add	<PA>, <VA>, <reg>
     70	@
     71	@ virt-to-phys (LPAE):		movw	<reg>, #offset<31:21>
     72	@				lsl	<reg>, #21
     73	@				adds	<PAlo>, <VA>, <reg>
     74	@				mov	<PAhi>, #offset<39:32>
     75	@				adc	<PAhi>, <PAhi>, #0
     76	@
     77	@ In the non-LPAE case, all patchable instructions are MOVW
     78	@ instructions, where we need to patch in the offset into the
     79	@ second halfword of the opcode (the 16-bit immediate is encoded
     80	@ as imm4:i:imm3:imm8)
     81	@
     82	@       15       11 10  9           4 3    0  15  14  12 11 8 7    0
     83	@      +-----------+---+-------------+------++---+------+----+------+
     84	@ MOVW | 1 1 1 1 0 | i | 1 0 0 1 0 0 | imm4 || 0 | imm3 | Rd | imm8 |
     85	@      +-----------+---+-------------+------++---+------+----+------+
     86	@
     87	@ In the LPAE case, we also need to patch in the high word of the
     88	@ offset into the immediate field of the MOV instruction, or patch it
     89	@ to a MVN instruction if the offset is negative. In this case, we
     90	@ need to inspect the first halfword of the opcode, to check whether
     91	@ it is MOVW or MOV/MVN, and to perform the MOV to MVN patching if
     92	@ needed. The encoding of the immediate is rather complex for values
     93	@ of i:imm3 != 0b0000, but fortunately, we never need more than 8 lower
     94	@ order bits, which can be patched into imm8 directly (and i:imm3
     95	@ cleared)
     96	@
     97	@      15       11 10  9        5         0  15  14  12 11 8 7    0
     98	@     +-----------+---+---------------------++---+------+----+------+
     99	@ MOV | 1 1 1 1 0 | i | 0 0 0 1 0 0 1 1 1 1 || 0 | imm3 | Rd | imm8 |
    100	@ MVN | 1 1 1 1 0 | i | 0 0 0 1 1 0 1 1 1 1 || 0 | imm3 | Rd | imm8 |
    101	@     +-----------+---+---------------------++---+------+----+------+
    102	@
    103	moveq	r0, #0x200000		@ set bit 21, mov to mvn instruction
    104	lsrs	r3, r6, #29		@ isolate top 3 bits of displacement
    105	ubfx	r6, r6, #21, #8		@ put bits 28:21 into the MOVW imm8 field
    106	bfi	r6, r3, #12, #3		@ put bits 31:29 into the MOVW imm3 field
    107	b	.Lnext
    108.Lloop:	add	r7, r4
    109	adds	r4, #4			@ clears Z flag
    110#ifdef CONFIG_ARM_LPAE
    111	ldrh	ip, [r7]
    112ARM_BE8(rev16	ip, ip)
    113	tst	ip, #0x200		@ MOVW has bit 9 set, MVN has it clear
    114	bne	0f			@ skip to MOVW handling (Z flag is clear)
    115	bic	ip, #0x20		@ clear bit 5 (MVN -> MOV)
    116	orr	ip, ip, r0, lsr #16	@ MOV -> MVN if offset < 0
    117ARM_BE8(rev16	ip, ip)
    118	strh	ip, [r7]
    119	@ Z flag is set
    1200:
    121#endif
    122	ldrh	ip, [r7, #2]
    123ARM_BE8(rev16	ip, ip)
    124	and	ip, #0xf00		@ clear everything except Rd field
    125	orreq	ip, r0			@ Z flag set -> MOV/MVN -> patch in high bits
    126	orrne	ip, r6			@ Z flag clear -> MOVW -> patch in low bits
    127ARM_BE8(rev16	ip, ip)
    128	strh	ip, [r7, #2]
    129#else
    130#ifdef CONFIG_CPU_ENDIAN_BE8
    131@ in BE8, we load data in BE, but instructions still in LE
    132#define PV_BIT24	0x00000001
    133#define PV_IMM8_MASK	0xff000000
    134#define PV_IMMR_MSB	0x00080000
    135#else
    136#define PV_BIT24	0x01000000
    137#define PV_IMM8_MASK	0x000000ff
    138#define PV_IMMR_MSB	0x00000800
    139#endif
    140
    141	@
    142	@ The ARM versions of the patchable sequences are
    143	@
    144	@ phys-to-virt:			sub	<VA>, <PA>, #offset<31:24>, lsl #24
    145	@				sub	<VA>, <PA>, #offset<23:16>, lsl #16
    146	@
    147	@ virt-to-phys (non-LPAE):	add	<PA>, <VA>, #offset<31:24>, lsl #24
    148	@				add	<PA>, <VA>, #offset<23:16>, lsl #16
    149	@
    150	@ virt-to-phys (LPAE):		movw	<reg>, #offset<31:20>
    151	@				adds	<PAlo>, <VA>, <reg>, lsl #20
    152	@				mov	<PAhi>, #offset<39:32>
    153	@				adc	<PAhi>, <PAhi>, #0
    154	@
    155	@ In the non-LPAE case, all patchable instructions are ADD or SUB
    156	@ instructions, where we need to patch in the offset into the
    157	@ immediate field of the opcode, which is emitted with the correct
    158	@ rotation value. (The effective value of the immediate is imm12<7:0>
    159	@ rotated right by [2 * imm12<11:8>] bits)
    160	@
    161	@      31   28 27      23 22  20 19  16 15  12 11    0
    162	@      +------+-----------------+------+------+-------+
    163	@  ADD | cond | 0 0 1 0 1 0 0 0 |  Rn  |  Rd  | imm12 |
    164	@  SUB | cond | 0 0 1 0 0 1 0 0 |  Rn  |  Rd  | imm12 |
    165	@  MOV | cond | 0 0 1 1 1 0 1 0 |  Rn  |  Rd  | imm12 |
    166	@  MVN | cond | 0 0 1 1 1 1 1 0 |  Rn  |  Rd  | imm12 |
    167	@      +------+-----------------+------+------+-------+
    168	@
    169	@ In the LPAE case, we use a MOVW instruction to carry the low offset
    170	@ word, and patch in the high word of the offset into the immediate
    171	@ field of the subsequent MOV instruction, or patch it to a MVN
    172	@ instruction if the offset is negative. We can distinguish MOVW
    173	@ instructions based on bits 23:22 of the opcode, and ADD/SUB can be
    174	@ distinguished from MOV/MVN (all using the encodings above) using
    175	@ bit 24.
    176	@
    177	@      31   28 27      23 22  20 19  16 15  12 11    0
    178	@      +------+-----------------+------+------+-------+
    179	@ MOVW | cond | 0 0 1 1 0 0 0 0 | imm4 |  Rd  | imm12 |
    180	@      +------+-----------------+------+------+-------+
    181	@
    182	moveq	r0, #0x400000		@ set bit 22, mov to mvn instruction
    183	mov	r3, r6, lsr #16		@ put offset bits 31-16 into r3
    184	mov	r6, r6, lsr #24		@ put offset bits 31-24 into r6
    185	and	r3, r3, #0xf0		@ only keep offset bits 23-20 in r3
    186	b	.Lnext
    187.Lloop:	ldr	ip, [r7, r4]
    188#ifdef CONFIG_ARM_LPAE
    189	tst	ip, #PV_BIT24		@ ADD/SUB have bit 24 clear
    190	beq	1f
    191ARM_BE8(rev	ip, ip)
    192	tst	ip, #0xc00000		@ MOVW has bits 23:22 clear
    193	bic	ip, ip, #0x400000	@ clear bit 22
    194	bfc	ip, #0, #12		@ clear imm12 field of MOV[W] instruction
    195	orreq	ip, ip, r6, lsl #4	@ MOVW -> mask in offset bits 31-24
    196	orreq	ip, ip, r3, lsr #4	@ MOVW -> mask in offset bits 23-20
    197	orrne	ip, ip, r0		@ MOV  -> mask in offset bits 7-0 (or bit 22)
    198ARM_BE8(rev	ip, ip)
    199	b	2f
    2001:
    201#endif
    202	tst	ip, #PV_IMMR_MSB		@ rotation value >= 16 ?
    203	bic	ip, ip, #PV_IMM8_MASK
    204	orreq	ip, ip, r6 ARM_BE8(, lsl #24)	@ mask in offset bits 31-24
    205	orrne	ip, ip, r3 ARM_BE8(, lsl #24)	@ mask in offset bits 23-20
    2062:
    207	str	ip, [r7, r4]
    208	add	r4, r4, #4
    209#endif
    210
    211.Lnext:
    212	cmp	r4, r5
    213	ldrcc	r7, [r4]		@ use branch for delay slot
    214	bcc	.Lloop
    215	ret	lr
    216ENDPROC(__fixup_a_pv_table)
    217
    218ENTRY(fixup_pv_table)
    219	stmfd	sp!, {r4 - r7, lr}
    220	mov	r4, r0			@ r0 = table start
    221	add	r5, r0, r1		@ r1 = table size
    222	bl	__fixup_a_pv_table
    223	ldmfd	sp!, {r4 - r7, pc}
    224ENDPROC(fixup_pv_table)
    225
    226	.data
    227	.align	2
    228	.globl	__pv_phys_pfn_offset
    229	.type	__pv_phys_pfn_offset, %object
    230__pv_phys_pfn_offset:
    231	.word	0
    232	.size	__pv_phys_pfn_offset, . -__pv_phys_pfn_offset
    233
    234	.globl	__pv_offset
    235	.type	__pv_offset, %object
    236__pv_offset:
    237	.quad	0
    238	.size	__pv_offset, . -__pv_offset