rtld_machine.c revision 1.49
1/*	$OpenBSD: rtld_machine.c,v 1.49 2022/01/08 06:49:42 guenther Exp $ */
2
3/*
4 * Copyright (c) 2002 Dale Rahn
5 * Copyright (c) 2001 Niklas Hallqvist
6 * Copyright (c) 2001 Artur Grabowski
7 *
8 * Redistribution and use in source and binary forms, with or without
9 * modification, are permitted provided that the following conditions
10 * are met:
11 * 1. Redistributions of source code must retain the above copyright
12 *    notice, this list of conditions and the following disclaimer.
13 * 2. Redistributions in binary form must reproduce the above copyright
14 *    notice, this list of conditions and the following disclaimer in the
15 *    documentation and/or other materials provided with the distribution.
16 *
17 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS
18 * OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
19 * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
20 * ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY
21 * DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
22 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
23 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
24 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
25 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
26 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
27 * SUCH DAMAGE.
28 */
29/*-
30 * Copyright (c) 2000 Eduardo Horvath.
31 * Copyright (c) 1999 The NetBSD Foundation, Inc.
32 * All rights reserved.
33 *
34 * This code is derived from software contributed to The NetBSD Foundation
35 * by Paul Kranenburg.
36 *
37 * Redistribution and use in source and binary forms, with or without
38 * modification, are permitted provided that the following conditions
39 * are met:
40 * 1. Redistributions of source code must retain the above copyright
41 *    notice, this list of conditions and the following disclaimer.
42 * 2. Redistributions in binary form must reproduce the above copyright
43 *    notice, this list of conditions and the following disclaimer in the
44 *    documentation and/or other materials provided with the distribution.
45 * 3. All advertising materials mentioning features or use of this software
46 *    must display the following acknowledgement:
47 *	This product includes software developed by the NetBSD
48 *	Foundation, Inc. and its contributors.
49 * 4. Neither the name of The NetBSD Foundation nor the names of its
50 *    contributors may be used to endorse or promote products derived
51 *    from this software without specific prior written permission.
52 *
53 * THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
54 * ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
55 * TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
56 * PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE FOUNDATION OR CONTRIBUTORS
57 * BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
58 * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
59 * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
60 * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
61 * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
62 * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
63 * POSSIBILITY OF SUCH DAMAGE.
64 */
65
66#define _DYN_LOADER
67
68#include <sys/types.h>
69#include <sys/exec_elf.h>
70#include <sys/syscall.h>
71#include <sys/unistd.h>
72
73#include <machine/reloc.h>
74
75#include "util.h"
76#include "resolve.h"
77
78int64_t pcookie __attribute__((section(".openbsd.randomdata"))) __dso_hidden;
79
80/*
81 * The following table holds for each relocation type:
82 *	- the width in bits of the memory location the relocation
83 *	  applies to (not currently used)
84 *	- the number of bits the relocation value must be shifted to the
85 *	  right (i.e. discard least significant bits) to fit into
86 *	  the appropriate field in the instruction word.
87 *	- flags indicating whether
88 *		* the relocation involves a symbol
89 *		* the relocation is relative to the current position
90 *		* the relocation is for a GOT entry
91 *		* the relocation is relative to the load address
92 *
93 */
94#define _RF_S		0x80000000		/* Resolve symbol */
95#define _RF_A		0x40000000		/* Use addend */
96#define _RF_P		0x20000000		/* Location relative */
97#define _RF_G		0x10000000		/* GOT offset */
98#define _RF_B		0x08000000		/* Load address relative */
99#define _RF_SZ(s)	(((s) & 0xff) << 8)	/* memory target size */
100#define _RF_RS(s)	((s) & 0xff)		/* right shift */
101static const int reloc_target_flags[] = {
102	0,							/* NONE */
103	_RF_S|_RF_A|		_RF_SZ(32) | _RF_RS(0),		/* RELOC_32*/
104	_RF_S|_RF_A|_RF_P|	_RF_SZ(32) | _RF_RS(0),		/* PC32 */
105	_RF_G|			_RF_SZ(32) | _RF_RS(00),	/* GOT32 */
106	      _RF_A|		_RF_SZ(32) | _RF_RS(0),		/* PLT32 */
107	_RF_S|			_RF_SZ(32) | _RF_RS(0),		/* COPY */
108	_RF_S|_RF_A|		_RF_SZ(32) | _RF_RS(0),		/* GLOB_DAT */
109	_RF_S|			_RF_SZ(32) | _RF_RS(0),		/* JUMP_SLOT */
110	      _RF_A|	_RF_B|	_RF_SZ(32) | _RF_RS(0),		/* RELATIVE */
111	0,							/* GOTOFF XXX */
112	0,							/* GOTPC XXX */
113	0,							/* DUMMY 11 */
114	0,							/* DUMMY 12 */
115	0,							/* DUMMY 13 */
116	0,							/* DUMMY 14 */
117	0,							/* DUMMY 15 */
118	0,							/* DUMMY 16 */
119	0,							/* DUMMY 17 */
120	0,							/* DUMMY 18 */
121	0,							/* DUMMY 19 */
122	_RF_S|_RF_A|		_RF_SZ(16) | _RF_RS(0),		/* RELOC_16 */
123	_RF_S|_RF_A|_RF_P|	_RF_SZ(16) | _RF_RS(0),		/* PC_16 */
124	_RF_S|_RF_A|		_RF_SZ(8) | _RF_RS(0),		/* RELOC_8 */
125	_RF_S|_RF_A|_RF_P|	_RF_SZ(8) | _RF_RS(0),		/* RELOC_PC8 */
126};
127
128#define RELOC_RESOLVE_SYMBOL(t)		((reloc_target_flags[t] & _RF_S) != 0)
129#define RELOC_PC_RELATIVE(t)		((reloc_target_flags[t] & _RF_P) != 0)
130#define RELOC_BASE_RELATIVE(t)		((reloc_target_flags[t] & _RF_B) != 0)
131#define RELOC_USE_ADDEND(t)		((reloc_target_flags[t] & _RF_A) != 0)
132#define RELOC_TARGET_SIZE(t)		((reloc_target_flags[t] >> 8) & 0xff)
133#define RELOC_VALUE_RIGHTSHIFT(t)	(reloc_target_flags[t] & 0xff)
134
135static const long reloc_target_bitmask[] = {
136#define _BM(x)	(~(-(1ULL << (x))))
137	0,		/* NONE */
138	_BM(32),	/* RELOC_32*/
139	_BM(32),	/* PC32 */
140	_BM(32),	/* GOT32 */
141	_BM(32),	/* PLT32 */
142	0,		/* COPY */
143	_BM(32),	/* GLOB_DAT */
144	_BM(32),	/* JUMP_SLOT */
145	_BM(32),	/* RELATIVE */
146	0,		/* GOTOFF XXX */
147	0,		/* GOTPC XXX */
148	0,		/* DUMMY 11 */
149	0,		/* DUMMY 12 */
150	0,		/* DUMMY 13 */
151	0,		/* DUMMY 14 */
152	0,		/* DUMMY 15 */
153	0,		/* DUMMY 16 */
154	0,		/* DUMMY 17 */
155	0,		/* DUMMY 18 */
156	0,		/* DUMMY 19 */
157	_BM(16),	/* RELOC_16 */
158	_BM(8),		/* PC_16 */
159	_BM(8),		/* RELOC_8 */
160	_BM(8),		/* RELOC_PC8 */
161#undef _BM
162};
163#define RELOC_VALUE_BITMASK(t)	(reloc_target_bitmask[t])
164
165void _dl_reloc_plt(Elf_Addr *where, Elf_Addr value);
166
167int
168_dl_md_reloc(elf_object_t *object, int rel, int relsz)
169{
170	long	i;
171	long	numrel;
172	long	relrel;
173	int	fails = 0;
174	Elf_Addr loff;
175	Elf_Addr prev_value = 0;
176	const Elf_Sym *prev_sym = NULL;
177	Elf_Rel *rels;
178
179	loff = object->obj_base;
180	numrel = object->Dyn.info[relsz] / sizeof(Elf_Rel);
181	relrel = rel == DT_REL ? object->relcount : 0;
182	rels = (Elf_Rel *)(object->Dyn.info[rel]);
183	if (rels == NULL)
184		return 0;
185
186	if (relrel > numrel)
187		_dl_die("relcount > numrel: %ld > %ld", relrel, numrel);
188
189	/* tight loop for leading RELATIVE relocs */
190	for (i = 0; i < relrel; i++, rels++) {
191		Elf_Addr *where;
192
193		where = (Elf_Addr *)(rels->r_offset + loff);
194		*where += loff;
195	}
196	for (; i < numrel; i++, rels++) {
197		Elf_Addr *where, value, mask;
198		Elf_Word type;
199		const Elf_Sym *sym;
200		const char *symn;
201
202		type = ELF_R_TYPE(rels->r_info);
203
204		if (type == R_TYPE(NONE))
205			continue;
206
207		if (type == R_TYPE(JUMP_SLOT) && rel != DT_JMPREL)
208			continue;
209
210		where = (Elf_Addr *)(rels->r_offset + loff);
211
212		if (RELOC_USE_ADDEND(type))
213			value = *where & RELOC_VALUE_BITMASK(type);
214		else
215			value = 0;
216
217		sym = NULL;
218		symn = NULL;
219		if (RELOC_RESOLVE_SYMBOL(type)) {
220			sym = object->dyn.symtab;
221			sym += ELF_R_SYM(rels->r_info);
222			symn = object->dyn.strtab + sym->st_name;
223
224			if (sym->st_shndx != SHN_UNDEF &&
225			    ELF_ST_BIND(sym->st_info) == STB_LOCAL) {
226				value += loff;
227			} else if (sym == prev_sym) {
228				value += prev_value;
229			} else {
230				struct sym_res sr;
231
232				sr = _dl_find_symbol(symn,
233				    SYM_SEARCH_ALL|SYM_WARNNOTFOUND|
234				    ((type == R_TYPE(JUMP_SLOT))?
235					SYM_PLT:SYM_NOTPLT), sym, object);
236				if (sr.sym == NULL) {
237resolve_failed:
238					if (ELF_ST_BIND(sym->st_info) !=
239					    STB_WEAK)
240						fails++;
241					continue;
242				}
243				prev_sym = sym;
244				prev_value = (Elf_Addr)(sr.obj->obj_base +
245				    sr.sym->st_value);
246				value += prev_value;
247			}
248		}
249
250		if (type == R_TYPE(JUMP_SLOT)) {
251			_dl_reloc_plt((Elf_Word *)where, value);
252			continue;
253		}
254
255		if (type == R_TYPE(COPY)) {
256			void *dstaddr = where;
257			const void *srcaddr;
258			const Elf_Sym *dstsym = sym;
259			struct sym_res sr;
260
261			sr = _dl_find_symbol(symn,
262			    SYM_SEARCH_OTHER|SYM_WARNNOTFOUND|SYM_NOTPLT,
263			    dstsym, object);
264			if (sr.sym == NULL)
265				goto resolve_failed;
266
267			srcaddr = (void *)(sr.obj->obj_base + sr.sym->st_value);
268			_dl_bcopy(srcaddr, dstaddr, dstsym->st_size);
269			continue;
270		}
271
272		if (RELOC_PC_RELATIVE(type))
273			value -= (Elf_Addr)where;
274		if (RELOC_BASE_RELATIVE(type))
275			value += loff;
276
277		mask = RELOC_VALUE_BITMASK(type);
278		value >>= RELOC_VALUE_RIGHTSHIFT(type);
279		value &= mask;
280
281		*where &= ~mask;
282		*where |= value;
283	}
284
285	return fails;
286}
287
288#if 0
289struct jmpslot {
290	u_short opcode;
291	u_short addr[2];
292	u_short reloc_index;
293#define JMPSLOT_RELOC_MASK	0xffff
294};
295#define JUMP			0xe990	/* NOP + JMP opcode */
296#endif
297
298void
299_dl_reloc_plt(Elf_Addr *where, Elf_Addr value)
300{
301	*where = value;
302}
303
304/*
305 * Resolve a symbol at run-time.
306 */
307Elf_Addr
308_dl_bind(elf_object_t *object, int index)
309{
310	Elf_Rel *rel;
311	const Elf_Sym *sym;
312	const char *symn;
313	struct sym_res sr;
314	uint64_t cookie = pcookie;
315	struct {
316		struct __kbind param;
317		Elf_Addr newval;
318	} buf;
319
320	rel = (Elf_Rel *)(object->Dyn.info[DT_JMPREL]);
321
322	rel += index/sizeof(Elf_Rel);
323
324	sym = object->dyn.symtab;
325	sym += ELF_R_SYM(rel->r_info);
326	symn = object->dyn.strtab + sym->st_name;
327
328	sr = _dl_find_symbol(symn, SYM_SEARCH_ALL|SYM_WARNNOTFOUND|SYM_PLT,
329	    sym, object);
330	if (sr.sym == NULL)
331		_dl_die("lazy binding failed!");
332
333	buf.newval = sr.obj->obj_base + sr.sym->st_value;
334
335	if (__predict_false(sr.obj->traced) && _dl_trace_plt(sr.obj, symn))
336		return buf.newval;
337
338	buf.param.kb_addr = (Elf_Word *)(object->obj_base + rel->r_offset);
339	buf.param.kb_size = sizeof(Elf_Addr);
340
341	/* directly code the syscall, so that it's actually inline here */
342	{
343		register long syscall_num __asm("eax") = SYS_kbind;
344
345		__asm volatile("lea %3, %%edx; pushl 4(%%edx);"
346		    " pushl (%%edx); pushl %2; pushl %1;"
347		    " push %%eax; int $0x80; addl $20, %%esp" :
348		    "+a" (syscall_num) : "r" (&buf), "i" (sizeof(buf)),
349		    "m" (cookie) : "edx", "cc", "memory");
350	}
351
352	return buf.newval;
353}
354
355int
356_dl_md_reloc_got(elf_object_t *object, int lazy)
357{
358	extern void _dl_bind_start(void);	/* XXX */
359	int	fails = 0;
360	Elf_Addr *pltgot = (Elf_Addr *)object->Dyn.info[DT_PLTGOT];
361	int i, num;
362	Elf_Rel *rel;
363
364	if (pltgot == NULL)
365		return 0; /* it is possible to have no PLT/GOT relocations */
366
367	if (object->Dyn.info[DT_PLTREL] != DT_REL)
368		return 0;
369
370	if (!lazy) {
371		fails = _dl_md_reloc(object, DT_JMPREL, DT_PLTRELSZ);
372	} else {
373		pltgot[1] = (Elf_Addr)object;
374		pltgot[2] = (Elf_Addr)&_dl_bind_start;
375
376		rel = (Elf_Rel *)(object->Dyn.info[DT_JMPREL]);
377		num = (object->Dyn.info[DT_PLTRELSZ]);
378		for (i = 0; i < num/sizeof(Elf_Rel); i++, rel++) {
379			Elf_Addr *where;
380			where = (Elf_Addr *)(rel->r_offset + object->obj_base);
381			*where += object->obj_base;
382		}
383	}
384
385	return fails;
386}
387