1/*	$NetBSD: mips_reloc.c,v 1.61 2011/03/15 07:40:52 matt Exp $	*/
2
3/*
4 * Copyright 1997 Michael L. Hitch <mhitch@montana.edu>
5 * Portions copyright 2002 Charles M. Hannum <root@ihack.net>
6 * All rights reserved.
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 * 3. The name of the author may not be used to endorse or promote products
17 *    derived from this software without specific prior written permission.
18 *
19 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
20 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
21 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
22 * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
23 * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
24 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
25 * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
26 * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
27 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
28 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
29 */
30
31#include <sys/cdefs.h>
32#ifndef lint
33__RCSID("$NetBSD: mips_reloc.c,v 1.61 2011/03/15 07:40:52 matt Exp $");
34#endif /* not lint */
35
36#include <sys/types.h>
37#include <sys/endian.h>
38#include <sys/tls.h>
39
40#include <stdlib.h>
41#include <string.h>
42
43#include "debug.h"
44#include "rtld.h"
45
46#ifdef __mips_o32
47#define SUPPORT_OLD_BROKEN_LD
48#endif
49
50void _rtld_bind_start(void);
51void _rtld_relocate_nonplt_self(Elf_Dyn *, Elf_Addr);
52caddr_t _rtld_bind(Elf_Word, Elf_Addr, Elf_Addr, Elf_Addr);
53
54/*
55 * It is possible for the compiler to emit relocations for unaligned data.
56 * We handle this situation with these inlines.
57 */
58
59#if ELFSIZE == 64
60/*
61 * ELF64 MIPS encodes the relocs uniquely.  The first 32-bits of info contain
62 * the symbol index.  The top 32-bits contain three relocation types encoded
63 * in big-endian integer with first relocation in LSB.  This means for little
64 * endian we have to byte swap that interger (r_type).
65 */
66#define	Elf_Sxword			Elf64_Sxword
67#define	ELF_R_NXTTYPE_64_P(r_type)	((((r_type) >> 8) & 0xff) == R_TYPE(64))
68#if BYTE_ORDER == LITTLE_ENDIAN
69#undef ELF_R_SYM
70#undef ELF_R_TYPE
71#define ELF_R_SYM(r_info)		((r_info) & 0xffffffff)
72#define ELF_R_TYPE(r_info)		bswap32((r_info) >> 32)
73#endif
74#else
75#define	ELF_R_NXTTYPE_64_P(r_type)	(0)
76#define	Elf_Sxword			Elf32_Sword
77#endif
78#define	GOT1_MASK			(~(Elf_Addr)0 >> 1)
79
80static inline Elf_Sxword
81load_ptr(void *where, size_t len)
82{
83	Elf_Sxword val;
84
85	if (__predict_true(((uintptr_t)where & (len - 1)) == 0)) {
86#if ELFSIZE == 64
87		if (len == sizeof(Elf_Sxword))
88			return *(Elf_Sxword *)where;
89#endif
90		return *(Elf_Sword *)where;
91	}
92
93	val = 0;
94#if BYTE_ORDER == LITTLE_ENDIAN
95	(void)memcpy(&val, where, len);
96#endif
97#if BYTE_ORDER == BIG_ENDIAN
98	(void)memcpy((uint8_t *)((&val)+1) - len, where, len);
99#endif
100	return (len == sizeof(Elf_Sxword)) ? val : (Elf_Sword)val;
101}
102
103static inline void
104store_ptr(void *where, Elf_Sxword val, size_t len)
105{
106	if (__predict_true(((uintptr_t)where & (len - 1)) == 0)) {
107#if ELFSIZE == 64
108		if (len == sizeof(Elf_Sxword)) {
109			*(Elf_Sxword *)where = val;
110			return;
111		}
112#endif
113		*(Elf_Sword *)where = val;
114		return;
115	}
116#if BYTE_ORDER == LITTLE_ENDIAN
117	(void)memcpy(where, &val, len);
118#endif
119#if BYTE_ORDER == BIG_ENDIAN
120	(void)memcpy(where, (const uint8_t *)((&val)+1) - len, len);
121#endif
122}
123
124
125void
126_rtld_setup_pltgot(const Obj_Entry *obj)
127{
128	obj->pltgot[0] = (Elf_Addr) &_rtld_bind_start;
129	/* XXX only if obj->pltgot[1] & 0x80000000 ?? */
130	obj->pltgot[1] |= (Elf_Addr) obj;
131}
132
133void
134_rtld_relocate_nonplt_self(Elf_Dyn *dynp, Elf_Addr relocbase)
135{
136	const Elf_Rel *rel = 0, *rellim;
137	Elf_Addr relsz = 0;
138	void *where;
139	const Elf_Sym *symtab = NULL, *sym;
140	Elf_Addr *got = NULL;
141	Elf_Word local_gotno = 0, symtabno = 0, gotsym = 0;
142	size_t i;
143
144	for (; dynp->d_tag != DT_NULL; dynp++) {
145		switch (dynp->d_tag) {
146		case DT_REL:
147			rel = (const Elf_Rel *)(relocbase + dynp->d_un.d_ptr);
148			break;
149		case DT_RELSZ:
150			relsz = dynp->d_un.d_val;
151			break;
152		case DT_SYMTAB:
153			symtab = (const Elf_Sym *)(relocbase + dynp->d_un.d_ptr);
154			break;
155		case DT_PLTGOT:
156			got = (Elf_Addr *)(relocbase + dynp->d_un.d_ptr);
157			break;
158		case DT_MIPS_LOCAL_GOTNO:
159			local_gotno = dynp->d_un.d_val;
160			break;
161		case DT_MIPS_SYMTABNO:
162			symtabno = dynp->d_un.d_val;
163			break;
164		case DT_MIPS_GOTSYM:
165			gotsym = dynp->d_un.d_val;
166			break;
167		}
168	}
169
170	i = (got[1] & 0x80000000) ? 2 : 1;
171	/* Relocate the local GOT entries */
172	got += i;
173	for (; i < local_gotno; i++)
174		*got++ += relocbase;
175	sym = symtab + gotsym;
176	/* Now do the global GOT entries */
177	for (i = gotsym; i < symtabno; i++) {
178		*got = sym->st_value + relocbase;
179		++sym;
180		++got;
181	}
182
183	rellim = (const Elf_Rel *)((uintptr_t)rel + relsz);
184	for (; rel < rellim; rel++) {
185		Elf_Word r_symndx, r_type;
186
187		where = (void *)(relocbase + rel->r_offset);
188
189		r_symndx = ELF_R_SYM(rel->r_info);
190		r_type = ELF_R_TYPE(rel->r_info);
191
192		switch (r_type & 0xff) {
193		case R_TYPE(REL32): {
194			const size_t rlen =
195			    ELF_R_NXTTYPE_64_P(r_type)
196				? sizeof(Elf_Sxword)
197				: sizeof(Elf_Sword);
198			Elf_Sxword old = load_ptr(where, rlen);
199			Elf_Sxword val = old;
200#if ELFSIZE == 64
201			assert(r_type == R_TYPE(REL32)
202			    || r_type == (R_TYPE(REL32)|(R_TYPE(64) << 8)));
203#endif
204			assert(r_symndx < gotsym);
205			sym = symtab + r_symndx;
206			assert(ELF_ST_BIND(sym->st_info) == STB_LOCAL);
207			val += relocbase;
208			store_ptr(where, val, sizeof(Elf_Sword));
209			rdbg(("REL32/L(%p) %p -> %p in <self>",
210			    where, (void *)old, (void *)val));
211			store_ptr(where, val, rlen);
212			break;
213		}
214
215		case R_TYPE(GPREL32):
216		case R_TYPE(NONE):
217			break;
218
219
220		default:
221			abort();
222		}
223	}
224}
225
226int
227_rtld_relocate_nonplt_objects(Obj_Entry *obj)
228{
229	const Elf_Rel *rel;
230	Elf_Addr *got = obj->pltgot;
231	const Elf_Sym *sym, *def;
232	const Obj_Entry *defobj;
233	Elf_Word i;
234#ifdef SUPPORT_OLD_BROKEN_LD
235	int broken;
236#endif
237
238#ifdef SUPPORT_OLD_BROKEN_LD
239	broken = 0;
240	sym = obj->symtab;
241	for (i = 1; i < 12; i++)
242		if (sym[i].st_info == ELF_ST_INFO(STB_LOCAL, STT_NOTYPE))
243			broken = 1;
244	dbg(("%s: broken=%d", obj->path, broken));
245#endif
246
247	i = (got[1] & 0x80000000) ? 2 : 1;
248	/* Relocate the local GOT entries */
249	got += i;
250	for (; i < obj->local_gotno; i++)
251		*got++ += (Elf_Addr)obj->relocbase;
252	sym = obj->symtab + obj->gotsym;
253	/* Now do the global GOT entries */
254	for (i = obj->gotsym; i < obj->symtabno; i++) {
255		rdbg((" doing got %d sym %p (%s, %lx)", i - obj->gotsym, sym,
256		    sym->st_name + obj->strtab, (u_long) *got));
257
258#ifdef SUPPORT_OLD_BROKEN_LD
259		if (ELF_ST_TYPE(sym->st_info) == STT_FUNC &&
260		    broken && sym->st_shndx == SHN_UNDEF) {
261			/*
262			 * XXX DANGER WILL ROBINSON!
263			 * You might think this is stupid, as it intentionally
264			 * defeats lazy binding -- and you'd be right.
265			 * Unfortunately, for lazy binding to work right, we
266			 * need to a way to force the GOT slots used for
267			 * function pointers to be resolved immediately.  This
268			 * is supposed to be done automatically by the linker,
269			 * by not outputting a PLT slot and setting st_value
270			 * to 0 if there are non-PLT references, but older
271			 * versions of GNU ld do not do this.
272			 */
273			def = _rtld_find_symdef(i, obj, &defobj, false);
274			if (def == NULL)
275				return -1;
276			*got = def->st_value + (Elf_Addr)defobj->relocbase;
277		} else
278#endif
279		if (ELF_ST_TYPE(sym->st_info) == STT_FUNC &&
280		    sym->st_value != 0 && sym->st_shndx == SHN_UNDEF) {
281			/*
282			 * If there are non-PLT references to the function,
283			 * st_value should be 0, forcing us to resolve the
284			 * address immediately.
285			 *
286			 * XXX DANGER WILL ROBINSON!
287			 * The linker is not outputting PLT slots for calls to
288			 * functions that are defined in the same shared
289			 * library.  This is a bug, because it can screw up
290			 * link ordering rules if the symbol is defined in
291			 * more than one module.  For now, if there is a
292			 * definition, we fail the test above and force a full
293			 * symbol lookup.  This means that all intra-module
294			 * calls are bound immediately.  - mycroft, 2003/09/24
295			 */
296			*got = sym->st_value + (Elf_Addr)obj->relocbase;
297		} else if (sym->st_info == ELF_ST_INFO(STB_GLOBAL, STT_SECTION)) {
298			/* Symbols with index SHN_ABS are not relocated. */
299			if (sym->st_shndx != SHN_ABS)
300				*got = sym->st_value +
301				    (Elf_Addr)obj->relocbase;
302		} else {
303			def = _rtld_find_symdef(i, obj, &defobj, false);
304			if (def == NULL)
305				return -1;
306			*got = def->st_value + (Elf_Addr)defobj->relocbase;
307		}
308
309		rdbg(("  --> now %lx", (u_long) *got));
310		++sym;
311		++got;
312	}
313
314	got = obj->pltgot;
315	for (rel = obj->rel; rel < obj->rellim; rel++) {
316		Elf_Word	r_symndx, r_type;
317		void		*where;
318
319		where = obj->relocbase + rel->r_offset;
320		r_symndx = ELF_R_SYM(rel->r_info);
321		r_type = ELF_R_TYPE(rel->r_info);
322
323		switch (r_type & 0xff) {
324		case R_TYPE(NONE):
325			break;
326
327		case R_TYPE(REL32): {
328			/* 32-bit PC-relative reference */
329			const size_t rlen =
330			    ELF_R_NXTTYPE_64_P(r_type)
331				? sizeof(Elf_Sxword)
332				: sizeof(Elf_Sword);
333			Elf_Sxword old = load_ptr(where, rlen);
334			Elf_Sxword val = old;
335
336			def = obj->symtab + r_symndx;
337
338			if (r_symndx >= obj->gotsym) {
339				val += got[obj->local_gotno + r_symndx - obj->gotsym];
340				rdbg(("REL32/G(%p) %p --> %p (%s) in %s",
341				    where, (void *)old, (void *)val,
342				    obj->strtab + def->st_name,
343				    obj->path));
344			} else {
345				/*
346				 * XXX: ABI DIFFERENCE!
347				 *
348				 * Old NetBSD binutils would generate shared
349				 * libs with section-relative relocations being
350				 * already adjusted for the start address of
351				 * the section.
352				 *
353				 * New binutils, OTOH, generate shared libs
354				 * with the same relocations being based at
355				 * zero, so we need to add in the start address
356				 * of the section.
357				 *
358				 * --rkb, Oct 6, 2001
359				 */
360
361				if (def->st_info ==
362				    ELF_ST_INFO(STB_LOCAL, STT_SECTION)
363#ifdef SUPPORT_OLD_BROKEN_LD
364				    && !broken
365#endif
366				    )
367					val += (Elf_Addr)def->st_value;
368
369				val += (Elf_Addr)obj->relocbase;
370
371				rdbg(("REL32/L(%p) %p -> %p (%s) in %s",
372				    where, (void *)old, (void *)val,
373				    obj->strtab + def->st_name, obj->path));
374			}
375			store_ptr(where, val, rlen);
376			break;
377		}
378
379#if ELFSIZE == 64
380		case R_TYPE(TLS_DTPMOD64):
381#else
382		case R_TYPE(TLS_DTPMOD32):
383#endif
384		{
385			Elf_Addr old = load_ptr(where, ELFSIZE / 8);
386			Elf_Addr val = old;
387
388			def = _rtld_find_symdef(r_symndx, obj, &defobj, false);
389			if (def == NULL)
390				return -1;
391
392			val += (Elf_Addr)defobj->tlsindex;
393
394			store_ptr(where, val, ELFSIZE / 8);
395			rdbg(("DTPMOD %s in %s --> %p in %s",
396			    obj->strtab + obj->symtab[r_symndx].st_name,
397			    obj->path, (void *)old, defobj->path));
398			break;
399		}
400
401#if ELFSIZE == 64
402		case R_TYPE(TLS_DTPREL64):
403#else
404		case R_TYPE(TLS_DTPREL32):
405#endif
406		{
407			Elf_Addr old = load_ptr(where, ELFSIZE / 8);
408			Elf_Addr val = old;
409
410			def = _rtld_find_symdef(r_symndx, obj, &defobj, false);
411			if (def == NULL)
412				return -1;
413
414			if (!defobj->tls_done && _rtld_tls_offset_allocate(obj))
415				return -1;
416
417			val += (Elf_Addr)def->st_value - TLS_DTV_OFFSET;
418			store_ptr(where, val, ELFSIZE / 8);
419
420			rdbg(("DTPREL %s in %s --> %p in %s",
421			    obj->strtab + obj->symtab[r_symndx].st_name,
422			    obj->path, (void *)old, defobj->path));
423			break;
424		}
425
426#if ELFSIZE == 64
427		case R_TYPE(TLS_TPREL64):
428#else
429		case R_TYPE(TLS_TPREL32):
430#endif
431		{
432			Elf_Addr old = load_ptr(where, ELFSIZE / 8);
433			Elf_Addr val = old;
434
435			def = _rtld_find_symdef(r_symndx, obj, &defobj, false);
436			if (def == NULL)
437				return -1;
438
439			if (!defobj->tls_done && _rtld_tls_offset_allocate(obj))
440				return -1;
441
442			val += (Elf_Addr)(def->st_value + defobj->tlsoffset
443			    - TLS_TP_OFFSET);
444			store_ptr(where, val, ELFSIZE / 8);
445
446			rdbg(("TPREL %s in %s --> %p in %s",
447			    obj->strtab + obj->symtab[r_symndx].st_name,
448			    obj->path, (void *)*where, defobj->path));
449			break;
450		}
451
452		default:
453			rdbg(("sym = %lu, type = %lu, offset = %p, "
454			    "contents = %p, symbol = %s",
455			    (u_long)r_symndx, (u_long)ELF_R_TYPE(rel->r_info),
456			    (void *)rel->r_offset,
457			    (void *)load_ptr(where, sizeof(Elf_Sword)),
458			    obj->strtab + obj->symtab[r_symndx].st_name));
459			_rtld_error("%s: Unsupported relocation type %ld "
460			    "in non-PLT relocations",
461			    obj->path, (u_long) ELF_R_TYPE(rel->r_info));
462			return -1;
463		}
464	}
465
466	return 0;
467}
468
469int
470_rtld_relocate_plt_lazy(const Obj_Entry *obj)
471{
472	/* PLT fixups were done above in the GOT relocation. */
473	return 0;
474}
475
476static inline int
477_rtld_relocate_plt_object(const Obj_Entry *obj, Elf_Word sym, Elf_Addr *tp)
478{
479	Elf_Addr *got = obj->pltgot;
480	const Elf_Sym *def;
481	const Obj_Entry *defobj;
482	Elf_Addr new_value;
483
484	def = _rtld_find_plt_symdef(sym, obj, &defobj, tp != NULL);
485	if (__predict_false(def == NULL))
486		return -1;
487	if (__predict_false(def == &_rtld_sym_zero))
488		return 0;
489
490	new_value = (Elf_Addr)(defobj->relocbase + def->st_value);
491	rdbg(("bind now/fixup in %s --> new=%p",
492	    defobj->strtab + def->st_name, (void *)new_value));
493	got[obj->local_gotno + sym - obj->gotsym] = new_value;
494
495	if (tp)
496		*tp = new_value;
497	return 0;
498}
499
500caddr_t
501_rtld_bind(Elf_Word a0, Elf_Addr a1, Elf_Addr a2, Elf_Addr a3)
502{
503	Elf_Addr *got = (Elf_Addr *)(a2 - 0x7ff0);
504	const Obj_Entry *obj = (Obj_Entry *)(got[1] & GOT1_MASK);
505	Elf_Addr new_value = 0;	/* XXX gcc */
506	int err;
507
508	_rtld_shared_enter();
509	err = _rtld_relocate_plt_object(obj, a0, &new_value);
510	if (err)
511		_rtld_die();
512	_rtld_shared_exit();
513
514	return (caddr_t)new_value;
515}
516
517int
518_rtld_relocate_plt_objects(const Obj_Entry *obj)
519{
520	const Elf_Sym *sym = obj->symtab + obj->gotsym;
521	Elf_Word i;
522
523	for (i = obj->gotsym; i < obj->symtabno; i++, sym++) {
524		if (ELF_ST_TYPE(sym->st_info) == STT_FUNC)
525			if (_rtld_relocate_plt_object(obj, i, NULL) < 0)
526				return -1;
527	}
528
529	return 0;
530}
531