rtld_machine.c revision 1.37
1/*	$OpenBSD: rtld_machine.c,v 1.37 2017/06/04 14:20:12 naddy 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/mman.h>
70#include <sys/syscall.h>
71#include <sys/unistd.h>
72
73#include <nlist.h>
74#include <link.h>
75
76#include "syscall.h"
77#include "archdep.h"
78#include "resolve.h"
79
80int64_t pcookie __attribute__((section(".openbsd.randomdata"))) __dso_hidden;
81
82/*
83 * The following table holds for each relocation type:
84 *	- the width in bits of the memory location the relocation
85 *	  applies to (not currently used)
86 *	- the number of bits the relocation value must be shifted to the
87 *	  right (i.e. discard least significant bits) to fit into
88 *	  the appropriate field in the instruction word.
89 *	- flags indicating whether
90 *		* the relocation involves a symbol
91 *		* the relocation is relative to the current position
92 *		* the relocation is for a GOT entry
93 *		* the relocation is relative to the load address
94 *
95 */
96#define _RF_S		0x80000000		/* Resolve symbol */
97#define _RF_A		0x40000000		/* Use addend */
98#define _RF_P		0x20000000		/* Location relative */
99#define _RF_G		0x10000000		/* GOT offset */
100#define _RF_B		0x08000000		/* Load address relative */
101#define _RF_U		0x04000000		/* Unaligned */
102#define _RF_SZ(s)	(((s) & 0xff) << 8)	/* memory target size */
103#define _RF_RS(s)	((s) & 0xff)		/* right shift */
104static int reloc_target_flags[] = {
105	0,							/* NONE */
106	_RF_S|_RF_A|		_RF_SZ(32) | _RF_RS(0),		/* RELOC_32*/
107	_RF_S|_RF_A|_RF_P|	_RF_SZ(32) | _RF_RS(0),		/* PC32 */
108	_RF_G|			_RF_SZ(32) | _RF_RS(00),	/* GOT32 */
109	      _RF_A|		_RF_SZ(32) | _RF_RS(0),		/* PLT32 */
110	_RF_S|			_RF_SZ(32) | _RF_RS(0),		/* COPY */
111	_RF_S|_RF_A|		_RF_SZ(32) | _RF_RS(0),		/* GLOB_DAT */
112	_RF_S|			_RF_SZ(32) | _RF_RS(0),		/* JUMP_SLOT */
113	      _RF_A|	_RF_B|	_RF_SZ(32) | _RF_RS(0),		/* RELATIVE */
114	0,							/* GOTOFF XXX */
115	0,							/* GOTPC XXX */
116	0,							/* DUMMY 11 */
117	0,							/* DUMMY 12 */
118	0,							/* DUMMY 13 */
119	0,							/* DUMMY 14 */
120	0,							/* DUMMY 15 */
121	0,							/* DUMMY 16 */
122	0,							/* DUMMY 17 */
123	0,							/* DUMMY 18 */
124	0,							/* DUMMY 19 */
125	_RF_S|_RF_A|		_RF_SZ(16) | _RF_RS(0),		/* RELOC_16 */
126	_RF_S|_RF_A|_RF_P|	_RF_SZ(16) | _RF_RS(0),		/* PC_16 */
127	_RF_S|_RF_A|		_RF_SZ(8) | _RF_RS(0),		/* RELOC_8 */
128	_RF_S|_RF_A|_RF_P|	_RF_SZ(8) | _RF_RS(0),		/* RELOC_PC8 */
129};
130
131#define RELOC_RESOLVE_SYMBOL(t)		((reloc_target_flags[t] & _RF_S) != 0)
132#define RELOC_PC_RELATIVE(t)		((reloc_target_flags[t] & _RF_P) != 0)
133#define RELOC_BASE_RELATIVE(t)		((reloc_target_flags[t] & _RF_B) != 0)
134#define RELOC_UNALIGNED(t)		((reloc_target_flags[t] & _RF_U) != 0)
135#define RELOC_USE_ADDEND(t)		((reloc_target_flags[t] & _RF_A) != 0)
136#define RELOC_TARGET_SIZE(t)		((reloc_target_flags[t] >> 8) & 0xff)
137#define RELOC_VALUE_RIGHTSHIFT(t)	(reloc_target_flags[t] & 0xff)
138
139static long reloc_target_bitmask[] = {
140#define _BM(x)	(~(-(1ULL << (x))))
141	0,		/* NONE */
142	_BM(32),	/* RELOC_32*/
143	_BM(32),	/* PC32 */
144	_BM(32),	/* GOT32 */
145	_BM(32),	/* PLT32 */
146	0,		/* COPY */
147	_BM(32),	/* GLOB_DAT */
148	_BM(32),	/* JUMP_SLOT */
149	_BM(32),	/* RELATIVE */
150	0,		/* GOTOFF XXX */
151	0,		/* GOTPC XXX */
152	0,		/* DUMMY 11 */
153	0,		/* DUMMY 12 */
154	0,		/* DUMMY 13 */
155	0,		/* DUMMY 14 */
156	0,		/* DUMMY 15 */
157	0,		/* DUMMY 16 */
158	0,		/* DUMMY 17 */
159	0,		/* DUMMY 18 */
160	0,		/* DUMMY 19 */
161	_BM(16),	/* RELOC_16 */
162	_BM(8),		/* PC_16 */
163	_BM(8),		/* RELOC_8 */
164	_BM(8),		/* RELOC_PC8 */
165#undef _BM
166};
167#define RELOC_VALUE_BITMASK(t)	(reloc_target_bitmask[t])
168
169void _dl_reloc_plt(Elf_Addr *where, Elf_Addr value);
170
171int
172_dl_md_reloc(elf_object_t *object, int rel, int relsz)
173{
174	long	i;
175	long	numrel;
176	long	relrel;
177	int	fails = 0;
178	Elf_Addr loff;
179	Elf_Addr prev_value = 0;
180	const Elf_Sym *prev_sym = NULL;
181	Elf_Rel *rels;
182	struct load_list *llist;
183
184	loff = object->obj_base;
185	numrel = object->Dyn.info[relsz] / sizeof(Elf32_Rel);
186	relrel = rel == DT_REL ? object->relcount : 0;
187	rels = (Elf32_Rel *)(object->Dyn.info[rel]);
188	if (rels == NULL)
189		return(0);
190
191	if (relrel > numrel)
192		_dl_die("relcount > numrel: %ld > %ld", relrel, numrel);
193
194	/*
195	 * unprotect some segments if we need it.
196	 */
197	if ((object->dyn.textrel == 1) && (rel == DT_REL || rel == DT_RELA)) {
198		for (llist = object->load_list; llist != NULL; llist = llist->next) {
199			if (!(llist->prot & PROT_WRITE))
200				_dl_mprotect(llist->start, llist->size,
201				    PROT_READ | PROT_WRITE);
202		}
203	}
204
205	/* tight loop for leading RELATIVE relocs */
206	for (i = 0; i < relrel; i++, rels++) {
207		Elf_Addr *where;
208
209#ifdef DEBUG
210		if (ELF_R_TYPE(rels->r_info) != R_TYPE(RELATIVE))
211			_dl_die("RELCOUNT wrong");
212#endif
213		where = (Elf_Addr *)(rels->r_offset + loff);
214		*where += loff;
215	}
216	for (; i < numrel; i++, rels++) {
217		Elf_Addr *where, value, ooff, mask;
218		Elf_Word type;
219		const Elf_Sym *sym, *this;
220		const char *symn;
221
222		type = ELF_R_TYPE(rels->r_info);
223
224		if (type == R_TYPE(NONE))
225			continue;
226
227		if (type == R_TYPE(JUMP_SLOT) && rel != DT_JMPREL)
228			continue;
229
230		where = (Elf_Addr *)(rels->r_offset + loff);
231
232		if (RELOC_USE_ADDEND(type))
233			value = *where & RELOC_VALUE_BITMASK(type);
234		else
235			value = 0;
236
237		sym = NULL;
238		symn = NULL;
239		if (RELOC_RESOLVE_SYMBOL(type)) {
240			sym = object->dyn.symtab;
241			sym += ELF_R_SYM(rels->r_info);
242			symn = object->dyn.strtab + sym->st_name;
243
244			if (sym->st_shndx != SHN_UNDEF &&
245			    ELF_ST_BIND(sym->st_info) == STB_LOCAL) {
246				value += loff;
247			} else if (sym == prev_sym) {
248				value += prev_value;
249			} else {
250				this = NULL;
251				ooff = _dl_find_symbol_bysym(object,
252				    ELF_R_SYM(rels->r_info), &this,
253				    SYM_SEARCH_ALL|SYM_WARNNOTFOUND|
254				    ((type == R_TYPE(JUMP_SLOT))?
255					SYM_PLT:SYM_NOTPLT),
256				    sym, NULL);
257				if (this == NULL) {
258resolve_failed:
259					if (ELF_ST_BIND(sym->st_info) !=
260					    STB_WEAK)
261						fails++;
262					continue;
263				}
264				prev_sym = sym;
265				prev_value = (Elf_Addr)(ooff + this->st_value);
266				value += prev_value;
267			}
268		}
269
270		if (type == R_TYPE(JUMP_SLOT)) {
271			_dl_reloc_plt((Elf_Word *)where, value);
272			continue;
273		}
274
275		if (type == R_TYPE(COPY)) {
276			void *dstaddr = where;
277			const void *srcaddr;
278			const Elf_Sym *dstsym = sym, *srcsym = NULL;
279			size_t size = dstsym->st_size;
280			Elf_Addr soff;
281
282			soff = _dl_find_symbol(symn, &srcsym,
283			    SYM_SEARCH_OTHER|SYM_WARNNOTFOUND|SYM_NOTPLT,
284			    sym, object, NULL);
285			if (srcsym == NULL)
286				goto resolve_failed;
287
288			srcaddr = (void *)(soff + srcsym->st_value);
289			_dl_bcopy(srcaddr, dstaddr, size);
290			continue;
291		}
292
293		if (RELOC_PC_RELATIVE(type))
294			value -= (Elf_Addr)where;
295		if (RELOC_BASE_RELATIVE(type))
296			value += loff;
297
298		mask = RELOC_VALUE_BITMASK(type);
299		value >>= RELOC_VALUE_RIGHTSHIFT(type);
300		value &= mask;
301
302		if (RELOC_UNALIGNED(type)) {
303			/* Handle unaligned relocations. */
304			Elf_Addr tmp = 0;
305			char *ptr = (char *)where;
306			int i, size = RELOC_TARGET_SIZE(type)/8;
307
308			/* Read it in one byte at a time. */
309			for (i=0; i<size; i++)
310				tmp = (tmp << 8) | ptr[i];
311
312			tmp &= ~mask;
313			tmp |= value;
314
315			/* Write it back out. */
316			for (i=0; i<size; i++)
317				ptr[i] = ((tmp >> (8*i)) & 0xff);
318		} else if (RELOC_TARGET_SIZE(type) > 32) {
319			*where &= ~mask;
320			*where |= value;
321		} else {
322			Elf32_Addr *where32 = (Elf32_Addr *)where;
323
324			*where32 &= ~mask;
325			*where32 |= value;
326		}
327	}
328
329	/* reprotect the unprotected segments */
330	if ((object->dyn.textrel == 1) && (rel == DT_REL || rel == DT_RELA)) {
331		for (llist = object->load_list; llist != NULL; llist = llist->next) {
332			if (!(llist->prot & PROT_WRITE))
333				_dl_mprotect(llist->start, llist->size,
334				    llist->prot);
335		}
336	}
337
338	return (fails);
339}
340
341#if 0
342struct jmpslot {
343	u_short opcode;
344	u_short addr[2];
345	u_short reloc_index;
346#define JMPSLOT_RELOC_MASK	0xffff
347};
348#define JUMP			0xe990	/* NOP + JMP opcode */
349#endif
350
351void
352_dl_reloc_plt(Elf_Addr *where, Elf_Addr value)
353{
354	*where = value;
355}
356
357/*
358 * Resolve a symbol at run-time.
359 */
360Elf_Addr
361_dl_bind(elf_object_t *object, int index)
362{
363	Elf_Rel *rel;
364	const Elf_Sym *sym, *this;
365	const char *symn;
366	const elf_object_t *sobj;
367	Elf_Addr ooff;
368	uint64_t cookie = pcookie;
369	struct {
370		struct __kbind param;
371		Elf_Addr newval;
372	} buf;
373
374	rel = (Elf_Rel *)(object->Dyn.info[DT_JMPREL]);
375
376	rel += index/sizeof(Elf_Rel);
377
378	sym = object->dyn.symtab;
379	sym += ELF_R_SYM(rel->r_info);
380	symn = object->dyn.strtab + sym->st_name;
381
382	this = NULL;
383	ooff = _dl_find_symbol(symn, &this,
384	    SYM_SEARCH_ALL|SYM_WARNNOTFOUND|SYM_PLT, sym, object, &sobj);
385	if (this == NULL)
386		_dl_die("lazy binding failed!");
387
388	buf.newval = ooff + this->st_value;
389
390	if (__predict_false(sobj->traced) && _dl_trace_plt(sobj, symn))
391		return (buf.newval);
392
393	buf.param.kb_addr = (Elf_Word *)(object->obj_base + rel->r_offset);
394	buf.param.kb_size = sizeof(Elf_Addr);
395
396	/* directly code the syscall, so that it's actually inline here */
397	{
398		register long syscall_num __asm("eax") = SYS_kbind;
399
400		__asm volatile("lea %3, %%edx; pushl 4(%%edx);"
401		    " pushl (%%edx); pushl %2; pushl %1;"
402		    " push %%eax; int $0x80; addl $20, %%esp" :
403		    "+a" (syscall_num) : "r" (&buf), "i" (sizeof(buf)),
404		    "m" (cookie) : "edx", "cc", "memory");
405	}
406
407	return (buf.newval);
408}
409
410int
411_dl_md_reloc_got(elf_object_t *object, int lazy)
412{
413	extern void _dl_bind_start(void);	/* XXX */
414	int	fails = 0;
415	Elf_Addr *pltgot = (Elf_Addr *)object->Dyn.info[DT_PLTGOT];
416	int i, num;
417	Elf_Rel *rel;
418
419	if (pltgot == NULL)
420		return (0); /* it is possible to have no PLT/GOT relocations */
421
422	if (object->Dyn.info[DT_PLTREL] != DT_REL)
423		return (0);
424
425	if (object->traced)
426		lazy = 1;
427
428	if (!lazy) {
429		fails = _dl_md_reloc(object, DT_JMPREL, DT_PLTRELSZ);
430	} else {
431		pltgot[1] = (Elf_Addr)object;
432		pltgot[2] = (Elf_Addr)&_dl_bind_start;
433
434		rel = (Elf_Rel *)(object->Dyn.info[DT_JMPREL]);
435		num = (object->Dyn.info[DT_PLTRELSZ]);
436		for (i = 0; i < num/sizeof(Elf_Rel); i++, rel++) {
437			Elf_Addr *where;
438			where = (Elf_Addr *)(rel->r_offset + object->obj_base);
439			*where += object->obj_base;
440		}
441	}
442
443	/* mprotect the GOT */
444	_dl_protect_segment(object, 0, "__got_start", "__got_end", PROT_READ);
445
446	return (fails);
447}
448