1169689Skan/* ARM EABI compliant unwinding routines.
2169689Skan   Copyright (C) 2004, 2005 Free Software Foundation, Inc.
3169689Skan   Contributed by Paul Brook
4169689Skan
5169689Skan   This file is free software; you can redistribute it and/or modify it
6169689Skan   under the terms of the GNU General Public License as published by the
7169689Skan   Free Software Foundation; either version 2, or (at your option) any
8169689Skan   later version.
9169689Skan
10169689Skan   In addition to the permissions in the GNU General Public License, the
11169689Skan   Free Software Foundation gives you unlimited permission to link the
12169689Skan   compiled version of this file into combinations with other programs,
13169689Skan   and to distribute those combinations without any restriction coming
14169689Skan   from the use of this file.  (The General Public License restrictions
15169689Skan   do apply in other respects; for example, they cover modification of
16169689Skan   the file, and distribution when not linked into a combine
17169689Skan   executable.)
18169689Skan
19169689Skan   This file is distributed in the hope that it will be useful, but
20169689Skan   WITHOUT ANY WARRANTY; without even the implied warranty of
21169689Skan   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
22169689Skan   General Public License for more details.
23169689Skan
24169689Skan   You should have received a copy of the GNU General Public License
25169689Skan   along with this program; see the file COPYING.  If not, write to
26169689Skan   the Free Software Foundation, 51 Franklin Street, Fifth Floor,
27169689Skan   Boston, MA 02110-1301, USA.  */
28169689Skan#include "unwind.h"
29169689Skan
30169689Skan/* We add a prototype for abort here to avoid creating a dependency on
31169689Skan   target headers.  */
32169689Skanextern void abort (void);
33169689Skan
34169689Skan/* Definitions for C++ runtime support routines.  We make these weak
35169689Skan   declarations to avoid pulling in libsupc++ unnecessarily.  */
36169689Skantypedef unsigned char bool;
37169689Skan
38169689Skantypedef struct _ZSt9type_info type_info; /* This names C++ type_info type */
39169689Skan
40169689Skanvoid __attribute__((weak)) __cxa_call_unexpected(_Unwind_Control_Block *ucbp);
41169689Skanbool __attribute__((weak)) __cxa_begin_cleanup(_Unwind_Control_Block *ucbp);
42169689Skanbool __attribute__((weak)) __cxa_type_match(_Unwind_Control_Block *ucbp,
43169689Skan					    const type_info *rttip,
44169689Skan					    void **matched_object);
45169689Skan
46169689Skan_Unwind_Ptr __attribute__((weak))
47169689Skan__gnu_Unwind_Find_exidx (_Unwind_Ptr, int *);
48169689Skan
49169689Skan/* Misc constants.  */
50169689Skan#define R_IP	12
51169689Skan#define R_SP	13
52169689Skan#define R_LR	14
53169689Skan#define R_PC	15
54169689Skan
55169689Skan#define EXIDX_CANTUNWIND 1
56169689Skan#define uint32_highbit (((_uw) 1) << 31)
57169689Skan
58169689Skan#define UCB_FORCED_STOP_FN(ucbp) ((ucbp)->unwinder_cache.reserved1)
59169689Skan#define UCB_PR_ADDR(ucbp) ((ucbp)->unwinder_cache.reserved2)
60169689Skan#define UCB_SAVED_CALLSITE_ADDR(ucbp) ((ucbp)->unwinder_cache.reserved3)
61169689Skan#define UCB_FORCED_STOP_ARG(ucbp) ((ucbp)->unwinder_cache.reserved4)
62169689Skan
63169689Skanstruct core_regs
64169689Skan{
65169689Skan  _uw r[16];
66169689Skan};
67169689Skan
68169689Skan/* We use normal integer types here to avoid the compiler generating
69169689Skan   coprocessor instructions.  */
70169689Skanstruct vfp_regs
71169689Skan{
72169689Skan  _uw64 d[16];
73169689Skan  _uw pad;
74169689Skan};
75169689Skan
76169689Skanstruct fpa_reg
77169689Skan{
78169689Skan  _uw w[3];
79169689Skan};
80169689Skan
81169689Skanstruct fpa_regs
82169689Skan{
83169689Skan  struct fpa_reg f[8];
84169689Skan};
85169689Skan
86169689Skan/* Unwind descriptors.  */
87169689Skan
88169689Skantypedef struct
89169689Skan{
90169689Skan  _uw16 length;
91169689Skan  _uw16 offset;
92169689Skan} EHT16;
93169689Skan
94169689Skantypedef struct
95169689Skan{
96169689Skan  _uw length;
97169689Skan  _uw offset;
98169689Skan} EHT32;
99169689Skan
100169689Skan/* The ABI specifies that the unwind routines may only use core registers,
101169689Skan   except when actually manipulating coprocessor state.  This allows
102169689Skan   us to write one implementation that works on all platforms by
103169689Skan   demand-saving coprocessor registers.
104169689Skan
105169689Skan   During unwinding we hold the coprocessor state in the actual hardware
106169689Skan   registers and allocate demand-save areas for use during phase1
107169689Skan   unwinding.  */
108169689Skan
109169689Skantypedef struct
110169689Skan{
111169689Skan  /* The first fields must be the same as a phase2_vrs.  */
112169689Skan  _uw demand_save_flags;
113169689Skan  struct core_regs core;
114169689Skan  _uw prev_sp; /* Only valid during forced unwinding.  */
115169689Skan  struct vfp_regs vfp;
116169689Skan  struct fpa_regs fpa;
117169689Skan} phase1_vrs;
118169689Skan
119169689Skan#define DEMAND_SAVE_VFP 1
120169689Skan
121169689Skan/* This must match the structure created by the assembly wrappers.  */
122169689Skantypedef struct
123169689Skan{
124169689Skan  _uw demand_save_flags;
125169689Skan  struct core_regs core;
126169689Skan} phase2_vrs;
127169689Skan
128169689Skan
129169689Skan/* An exception index table entry.  */
130169689Skan
131169689Skantypedef struct __EIT_entry
132169689Skan{
133169689Skan  _uw fnoffset;
134169689Skan  _uw content;
135169689Skan} __EIT_entry;
136169689Skan
137169689Skan/* Assembly helper functions.  */
138169689Skan
139169689Skan/* Restore core register state.  Never returns.  */
140169689Skanvoid __attribute__((noreturn)) restore_core_regs (struct core_regs *);
141169689Skan
142169689Skan
143169689Skan/* Coprocessor register state manipulation functions.  */
144169689Skan
145169689Skanvoid __gnu_Unwind_Save_VFP (struct vfp_regs * p);
146169689Skanvoid __gnu_Unwind_Restore_VFP (struct vfp_regs * p);
147169689Skan
148169689Skan/* Restore coprocessor state after phase1 unwinding.  */
149169689Skanstatic void
150169689Skanrestore_non_core_regs (phase1_vrs * vrs)
151169689Skan{
152169689Skan  if ((vrs->demand_save_flags & DEMAND_SAVE_VFP) == 0)
153169689Skan    __gnu_Unwind_Restore_VFP (&vrs->vfp);
154169689Skan}
155169689Skan
156169689Skan/* A better way to do this would probably be to compare the absolute address
157169689Skan   with a segment relative relocation of the same symbol.  */
158169689Skan
159169689Skanextern int __text_start;
160169689Skanextern int __data_start;
161169689Skan
162169689Skan/* The exception index table location.  */
163169689Skanextern __EIT_entry __exidx_start;
164169689Skanextern __EIT_entry __exidx_end;
165169689Skan
166169689Skan/* ABI defined personality routines.  */
167169689Skanextern _Unwind_Reason_Code __aeabi_unwind_cpp_pr0 (_Unwind_State,
168169689Skan    _Unwind_Control_Block *, _Unwind_Context *);// __attribute__((weak));
169169689Skanextern _Unwind_Reason_Code __aeabi_unwind_cpp_pr1 (_Unwind_State,
170169689Skan    _Unwind_Control_Block *, _Unwind_Context *) __attribute__((weak));
171169689Skanextern _Unwind_Reason_Code __aeabi_unwind_cpp_pr2 (_Unwind_State,
172169689Skan    _Unwind_Control_Block *, _Unwind_Context *) __attribute__((weak));
173169689Skan
174169689Skan/* ABI defined routine to store a virtual register to memory.  */
175169689Skan
176169689Skan_Unwind_VRS_Result _Unwind_VRS_Get (_Unwind_Context *context,
177169689Skan				    _Unwind_VRS_RegClass regclass,
178169689Skan				    _uw regno,
179169689Skan				    _Unwind_VRS_DataRepresentation representation,
180169689Skan				    void *valuep)
181169689Skan{
182169689Skan  phase1_vrs *vrs = (phase1_vrs *) context;
183169689Skan
184169689Skan  switch (regclass)
185169689Skan    {
186169689Skan    case _UVRSC_CORE:
187169689Skan      if (representation != _UVRSD_UINT32
188169689Skan	  || regno > 15)
189169689Skan	return _UVRSR_FAILED;
190169689Skan      *(_uw *) valuep = vrs->core.r[regno];
191169689Skan      return _UVRSR_OK;
192169689Skan
193169689Skan    case _UVRSC_VFP:
194169689Skan    case _UVRSC_FPA:
195169689Skan    case _UVRSC_WMMXD:
196169689Skan    case _UVRSC_WMMXC:
197169689Skan      return _UVRSR_NOT_IMPLEMENTED;
198169689Skan
199169689Skan    default:
200169689Skan      return _UVRSR_FAILED;
201169689Skan    }
202169689Skan}
203169689Skan
204169689Skan
205169689Skan/* ABI defined function to load a virtual register from memory.  */
206169689Skan
207169689Skan_Unwind_VRS_Result _Unwind_VRS_Set (_Unwind_Context *context,
208169689Skan				    _Unwind_VRS_RegClass regclass,
209169689Skan				    _uw regno,
210169689Skan				    _Unwind_VRS_DataRepresentation representation,
211169689Skan				    void *valuep)
212169689Skan{
213169689Skan  phase1_vrs *vrs = (phase1_vrs *) context;
214169689Skan
215169689Skan  switch (regclass)
216169689Skan    {
217169689Skan    case _UVRSC_CORE:
218169689Skan      if (representation != _UVRSD_UINT32
219169689Skan	  || regno > 15)
220169689Skan	return _UVRSR_FAILED;
221169689Skan
222169689Skan      vrs->core.r[regno] = *(_uw *) valuep;
223169689Skan      return _UVRSR_OK;
224169689Skan
225169689Skan    case _UVRSC_VFP:
226169689Skan    case _UVRSC_FPA:
227169689Skan    case _UVRSC_WMMXD:
228169689Skan    case _UVRSC_WMMXC:
229169689Skan      return _UVRSR_NOT_IMPLEMENTED;
230169689Skan
231169689Skan    default:
232169689Skan      return _UVRSR_FAILED;
233169689Skan    }
234169689Skan}
235169689Skan
236169689Skan
237169689Skan/* ABI defined function to pop registers off the stack.  */
238169689Skan
239169689Skan_Unwind_VRS_Result _Unwind_VRS_Pop (_Unwind_Context *context,
240169689Skan				    _Unwind_VRS_RegClass regclass,
241169689Skan				    _uw discriminator,
242169689Skan				    _Unwind_VRS_DataRepresentation representation)
243169689Skan{
244169689Skan  phase1_vrs *vrs = (phase1_vrs *) context;
245169689Skan
246169689Skan  switch (regclass)
247169689Skan    {
248169689Skan    case _UVRSC_CORE:
249169689Skan      {
250169689Skan	_uw *ptr;
251169689Skan	_uw mask;
252169689Skan	int i;
253169689Skan
254169689Skan	if (representation != _UVRSD_UINT32)
255169689Skan	  return _UVRSR_FAILED;
256169689Skan
257169689Skan	mask = discriminator & 0xffff;
258169689Skan	ptr = (_uw *) vrs->core.r[R_SP];
259169689Skan	/* Pop the requested registers.  */
260169689Skan	for (i = 0; i < 16; i++)
261169689Skan	  {
262169689Skan	    if (mask & (1 << i))
263169689Skan	      vrs->core.r[i] = *(ptr++);
264169689Skan	  }
265169689Skan	/* Writeback the stack pointer value if it wasn't restored.  */
266169689Skan	if ((mask & (1 << R_SP)) == 0)
267169689Skan	  vrs->core.r[R_SP] = (_uw) ptr;
268169689Skan      }
269169689Skan      return _UVRSR_OK;
270169689Skan
271169689Skan    case _UVRSC_VFP:
272169689Skan      {
273169689Skan	_uw start = discriminator >> 16;
274169689Skan	_uw count = discriminator & 0xffff;
275169689Skan	struct vfp_regs tmp;
276169689Skan	_uw *sp;
277169689Skan	_uw *dest;
278169689Skan
279169689Skan	if ((representation != _UVRSD_VFPX && representation != _UVRSD_DOUBLE)
280169689Skan	    || start + count > 16)
281169689Skan	  return _UVRSR_FAILED;
282169689Skan
283169689Skan	if (vrs->demand_save_flags & DEMAND_SAVE_VFP)
284169689Skan	  {
285169689Skan	    /* Demand-save resisters for stage1.  */
286169689Skan	    vrs->demand_save_flags &= ~DEMAND_SAVE_VFP;
287169689Skan	    __gnu_Unwind_Save_VFP (&vrs->vfp);
288169689Skan	  }
289169689Skan
290169689Skan	/* Restore the registers from the stack.  Do this by saving the
291169689Skan	   current VFP registers to a memory area, moving the in-memory
292169689Skan	   values into that area, and restoring from the whole area.
293169689Skan	   For _UVRSD_VFPX we assume FSTMX standard format 1.  */
294169689Skan	__gnu_Unwind_Save_VFP (&tmp);
295169689Skan
296169689Skan	/* The stack address is only guaranteed to be word aligned, so
297169689Skan	   we can't use doubleword copies.  */
298169689Skan	sp = (_uw *) vrs->core.r[R_SP];
299169689Skan	dest = (_uw *) &tmp.d[start];
300169689Skan	count *= 2;
301169689Skan	while (count--)
302169689Skan	  *(dest++) = *(sp++);
303169689Skan
304169689Skan	/* Skip the pad word */
305169689Skan	if (representation == _UVRSD_VFPX)
306169689Skan	  sp++;
307169689Skan
308169689Skan	/* Set the new stack pointer.  */
309169689Skan	vrs->core.r[R_SP] = (_uw) sp;
310169689Skan
311169689Skan	/* Reload the registers.  */
312169689Skan	__gnu_Unwind_Restore_VFP (&tmp);
313169689Skan      }
314169689Skan      return _UVRSR_OK;
315169689Skan
316169689Skan    case _UVRSC_FPA:
317169689Skan    case _UVRSC_WMMXD:
318169689Skan    case _UVRSC_WMMXC:
319169689Skan      return _UVRSR_NOT_IMPLEMENTED;
320169689Skan
321169689Skan    default:
322169689Skan      return _UVRSR_FAILED;
323169689Skan    }
324169689Skan}
325169689Skan
326169689Skan
327169689Skan/* Core unwinding functions.  */
328169689Skan
329169689Skan/* Calculate the address encoded by a 31-bit self-relative offset at address
330169689Skan   P.  */
331169689Skanstatic inline _uw
332169689Skanselfrel_offset31 (const _uw *p)
333169689Skan{
334169689Skan  _uw offset;
335169689Skan
336169689Skan  offset = *p;
337169689Skan  /* Sign extend to 32 bits.  */
338169689Skan  if (offset & (1 << 30))
339169689Skan    offset |= 1u << 31;
340169689Skan  else
341169689Skan    offset &= ~(1u << 31);
342169689Skan
343169689Skan  return offset + (_uw) p;
344169689Skan}
345169689Skan
346169689Skan
347169689Skan/* Perform a binary search for RETURN_ADDRESS in TABLE.  The table contains
348169689Skan   NREC entries.  */
349169689Skan
350169689Skanstatic const __EIT_entry *
351169689Skansearch_EIT_table (const __EIT_entry * table, int nrec, _uw return_address)
352169689Skan{
353169689Skan  _uw next_fn;
354169689Skan  _uw this_fn;
355169689Skan  int n, left, right;
356169689Skan
357169689Skan  if (nrec == 0)
358169689Skan    return (__EIT_entry *) 0;
359169689Skan
360169689Skan  left = 0;
361169689Skan  right = nrec - 1;
362169689Skan
363169689Skan  while (1)
364169689Skan    {
365169689Skan      n = (left + right) / 2;
366169689Skan      this_fn = selfrel_offset31 (&table[n].fnoffset);
367169689Skan      if (n != nrec - 1)
368169689Skan	next_fn = selfrel_offset31 (&table[n + 1].fnoffset) - 1;
369169689Skan      else
370169689Skan	next_fn = (_uw)0 - 1;
371169689Skan
372169689Skan      if (return_address < this_fn)
373169689Skan	{
374169689Skan	  if (n == left)
375169689Skan	    return (__EIT_entry *) 0;
376169689Skan	  right = n - 1;
377169689Skan	}
378169689Skan      else if (return_address <= next_fn)
379169689Skan	return &table[n];
380169689Skan      else
381169689Skan	left = n + 1;
382169689Skan    }
383169689Skan}
384169689Skan
385169689Skan/* Find the exception index table eintry for the given address.
386169689Skan   Fill in the relevant fields of the UCB.
387169689Skan   Returns _URC_FAILURE if an error occurred, _URC_OK on success.  */
388169689Skan
389169689Skanstatic _Unwind_Reason_Code
390169689Skanget_eit_entry (_Unwind_Control_Block *ucbp, _uw return_address)
391169689Skan{
392169689Skan  const __EIT_entry * eitp;
393169689Skan  int nrec;
394169689Skan
395169689Skan  /* The return address is the address of the instruction following the
396169689Skan     call instruction (plus one in thumb mode).  If this was the last
397169689Skan     instruction in the function the address will lie in the following
398169689Skan     function.  Subtract 2 from the address so that it points within the call
399169689Skan     instruction itself.  */
400169689Skan  return_address -= 2;
401169689Skan
402169689Skan  if (__gnu_Unwind_Find_exidx)
403169689Skan    {
404169689Skan      eitp = (const __EIT_entry *) __gnu_Unwind_Find_exidx (return_address,
405169689Skan							    &nrec);
406169689Skan      if (!eitp)
407169689Skan	{
408169689Skan	  UCB_PR_ADDR (ucbp) = 0;
409169689Skan	  return _URC_FAILURE;
410169689Skan	}
411169689Skan    }
412169689Skan  else
413169689Skan    {
414169689Skan      eitp = &__exidx_start;
415169689Skan      nrec = &__exidx_end - &__exidx_start;
416169689Skan    }
417169689Skan
418169689Skan  eitp = search_EIT_table (eitp, nrec, return_address);
419169689Skan
420169689Skan  if (!eitp)
421169689Skan    {
422169689Skan      UCB_PR_ADDR (ucbp) = 0;
423169689Skan      return _URC_FAILURE;
424169689Skan    }
425169689Skan  ucbp->pr_cache.fnstart = selfrel_offset31 (&eitp->fnoffset);
426169689Skan
427169689Skan  /* Can this frame be unwound at all?  */
428169689Skan  if (eitp->content == EXIDX_CANTUNWIND)
429169689Skan    {
430169689Skan      UCB_PR_ADDR (ucbp) = 0;
431169689Skan      return _URC_END_OF_STACK;
432169689Skan    }
433169689Skan
434169689Skan  /* Obtain the address of the "real" __EHT_Header word.  */
435169689Skan
436169689Skan  if (eitp->content & uint32_highbit)
437169689Skan    {
438169689Skan      /* It is immediate data.  */
439169689Skan      ucbp->pr_cache.ehtp = (_Unwind_EHT_Header *)&eitp->content;
440169689Skan      ucbp->pr_cache.additional = 1;
441169689Skan    }
442169689Skan  else
443169689Skan    {
444169689Skan      /* The low 31 bits of the content field are a self-relative
445169689Skan	 offset to an _Unwind_EHT_Entry structure.  */
446169689Skan      ucbp->pr_cache.ehtp =
447169689Skan	(_Unwind_EHT_Header *) selfrel_offset31 (&eitp->content);
448169689Skan      ucbp->pr_cache.additional = 0;
449169689Skan    }
450169689Skan
451169689Skan  /* Discover the personality routine address.  */
452169689Skan  if (*ucbp->pr_cache.ehtp & (1u << 31))
453169689Skan    {
454169689Skan      /* One of the predefined standard routines.  */
455169689Skan      _uw idx = (*(_uw *) ucbp->pr_cache.ehtp >> 24) & 0xf;
456169689Skan      if (idx == 0)
457169689Skan	UCB_PR_ADDR (ucbp) = (_uw) &__aeabi_unwind_cpp_pr0;
458169689Skan      else if (idx == 1)
459169689Skan	UCB_PR_ADDR (ucbp) = (_uw) &__aeabi_unwind_cpp_pr1;
460169689Skan      else if (idx == 2)
461169689Skan	UCB_PR_ADDR (ucbp) = (_uw) &__aeabi_unwind_cpp_pr2;
462169689Skan      else
463169689Skan	{ /* Failed */
464169689Skan	  UCB_PR_ADDR (ucbp) = 0;
465169689Skan	  return _URC_FAILURE;
466169689Skan	}
467169689Skan    }
468169689Skan  else
469169689Skan    {
470169689Skan      /* Execute region offset to PR */
471169689Skan      UCB_PR_ADDR (ucbp) = selfrel_offset31 (ucbp->pr_cache.ehtp);
472169689Skan    }
473169689Skan  return _URC_OK;
474169689Skan}
475169689Skan
476169689Skan
477169689Skan/* Perform phase2 unwinding.  VRS is the initial virtual register state.  */
478169689Skan
479169689Skanstatic void __attribute__((noreturn))
480169689Skanunwind_phase2 (_Unwind_Control_Block * ucbp, phase2_vrs * vrs)
481169689Skan{
482169689Skan  _Unwind_Reason_Code pr_result;
483169689Skan
484169689Skan  do
485169689Skan    {
486169689Skan      /* Find the entry for this routine.  */
487169689Skan      if (get_eit_entry (ucbp, vrs->core.r[R_PC]) != _URC_OK)
488169689Skan	abort ();
489169689Skan
490169689Skan      UCB_SAVED_CALLSITE_ADDR (ucbp) = vrs->core.r[R_PC];
491169689Skan
492169689Skan      /* Call the pr to decide what to do.  */
493169689Skan      pr_result = ((personality_routine) UCB_PR_ADDR (ucbp))
494169689Skan	(_US_UNWIND_FRAME_STARTING, ucbp, (_Unwind_Context *) vrs);
495169689Skan    }
496169689Skan  while (pr_result == _URC_CONTINUE_UNWIND);
497169689Skan
498169689Skan  if (pr_result != _URC_INSTALL_CONTEXT)
499169689Skan    abort();
500169689Skan
501169689Skan  restore_core_regs (&vrs->core);
502169689Skan}
503169689Skan
504169689Skan/* Perform phase2 forced unwinding.  */
505169689Skan
506169689Skanstatic _Unwind_Reason_Code
507169689Skanunwind_phase2_forced (_Unwind_Control_Block *ucbp, phase2_vrs *entry_vrs,
508169689Skan		      int resuming)
509169689Skan{
510169689Skan  _Unwind_Stop_Fn stop_fn = (_Unwind_Stop_Fn) UCB_FORCED_STOP_FN (ucbp);
511169689Skan  void *stop_arg = (void *)UCB_FORCED_STOP_ARG (ucbp);
512169689Skan  _Unwind_Reason_Code pr_result = 0;
513169689Skan  /* We use phase1_vrs here even though we do not demand save, for the
514169689Skan     prev_sp field.  */
515169689Skan  phase1_vrs saved_vrs, next_vrs;
516169689Skan
517169689Skan  /* Save the core registers.  */
518169689Skan  saved_vrs.core = entry_vrs->core;
519169689Skan  /* We don't need to demand-save the non-core registers, because we
520169689Skan     unwind in a single pass.  */
521169689Skan  saved_vrs.demand_save_flags = 0;
522169689Skan
523169689Skan  /* Unwind until we reach a propagation barrier.  */
524169689Skan  do
525169689Skan    {
526169689Skan      _Unwind_State action;
527169689Skan      _Unwind_Reason_Code entry_code;
528169689Skan      _Unwind_Reason_Code stop_code;
529169689Skan
530169689Skan      /* Find the entry for this routine.  */
531169689Skan      entry_code = get_eit_entry (ucbp, saved_vrs.core.r[R_PC]);
532169689Skan
533169689Skan      if (resuming)
534169689Skan	{
535169689Skan	  action = _US_UNWIND_FRAME_RESUME | _US_FORCE_UNWIND;
536169689Skan	  resuming = 0;
537169689Skan	}
538169689Skan      else
539169689Skan	action = _US_UNWIND_FRAME_STARTING | _US_FORCE_UNWIND;
540169689Skan
541169689Skan      if (entry_code == _URC_OK)
542169689Skan	{
543169689Skan	  UCB_SAVED_CALLSITE_ADDR (ucbp) = saved_vrs.core.r[R_PC];
544169689Skan
545169689Skan	  next_vrs = saved_vrs;
546169689Skan
547169689Skan	  /* Call the pr to decide what to do.  */
548169689Skan	  pr_result = ((personality_routine) UCB_PR_ADDR (ucbp))
549169689Skan	    (action, ucbp, (void *) &next_vrs);
550169689Skan
551169689Skan	  saved_vrs.prev_sp = next_vrs.core.r[R_SP];
552169689Skan	}
553169689Skan      else
554169689Skan	{
555169689Skan	  /* Treat any failure as the end of unwinding, to cope more
556169689Skan	     gracefully with missing EH information.  Mixed EH and
557169689Skan	     non-EH within one object will usually result in failure,
558169689Skan	     because the .ARM.exidx tables do not indicate the end
559169689Skan	     of the code to which they apply; but mixed EH and non-EH
560169689Skan	     shared objects should return an unwind failure at the
561169689Skan	     entry of a non-EH shared object.  */
562169689Skan	  action |= _US_END_OF_STACK;
563169689Skan
564169689Skan	  saved_vrs.prev_sp = saved_vrs.core.r[R_SP];
565169689Skan	}
566169689Skan
567169689Skan      stop_code = stop_fn (1, action, ucbp->exception_class, ucbp,
568169689Skan			   (void *)&saved_vrs, stop_arg);
569169689Skan      if (stop_code != _URC_NO_REASON)
570169689Skan	return _URC_FAILURE;
571169689Skan
572169689Skan      if (entry_code != _URC_OK)
573169689Skan	return entry_code;
574169689Skan
575169689Skan      saved_vrs = next_vrs;
576169689Skan    }
577169689Skan  while (pr_result == _URC_CONTINUE_UNWIND);
578169689Skan
579169689Skan  if (pr_result != _URC_INSTALL_CONTEXT)
580169689Skan    {
581169689Skan      /* Some sort of failure has occurred in the pr and probably the
582169689Skan	 pr returned _URC_FAILURE.  */
583169689Skan      return _URC_FAILURE;
584169689Skan    }
585169689Skan
586169689Skan  restore_core_regs (&saved_vrs.core);
587169689Skan}
588169689Skan
589169689Skan/* This is a very limited implementation of _Unwind_GetCFA.  It returns
590169689Skan   the stack pointer as it is about to be unwound, and is only valid
591169689Skan   while calling the stop function during forced unwinding.  If the
592169689Skan   current personality routine result is going to run a cleanup, this
593169689Skan   will not be the CFA; but when the frame is really unwound, it will
594169689Skan   be.  */
595169689Skan
596169689Skan_Unwind_Word
597169689Skan_Unwind_GetCFA (_Unwind_Context *context)
598169689Skan{
599169689Skan  return ((phase1_vrs *) context)->prev_sp;
600169689Skan}
601169689Skan
602169689Skan/* Perform phase1 unwinding.  UCBP is the exception being thrown, and
603169689Skan   entry_VRS is the register state on entry to _Unwind_RaiseException.  */
604169689Skan
605169689Skan_Unwind_Reason_Code
606169689Skan__gnu_Unwind_RaiseException (_Unwind_Control_Block *, phase2_vrs *);
607169689Skan
608169689Skan_Unwind_Reason_Code
609169689Skan__gnu_Unwind_RaiseException (_Unwind_Control_Block * ucbp,
610169689Skan			     phase2_vrs * entry_vrs)
611169689Skan{
612169689Skan  phase1_vrs saved_vrs;
613169689Skan  _Unwind_Reason_Code pr_result;
614169689Skan
615169689Skan  /* Set the pc to the call site.  */
616169689Skan  entry_vrs->core.r[R_PC] = entry_vrs->core.r[R_LR];
617169689Skan
618169689Skan  /* Save the core registers.  */
619169689Skan  saved_vrs.core = entry_vrs->core;
620169689Skan  /* Set demand-save flags.  */
621169689Skan  saved_vrs.demand_save_flags = ~(_uw) 0;
622169689Skan
623169689Skan  /* Unwind until we reach a propagation barrier.  */
624169689Skan  do
625169689Skan    {
626169689Skan      /* Find the entry for this routine.  */
627169689Skan      if (get_eit_entry (ucbp, saved_vrs.core.r[R_PC]) != _URC_OK)
628169689Skan	return _URC_FAILURE;
629169689Skan
630169689Skan      /* Call the pr to decide what to do.  */
631169689Skan      pr_result = ((personality_routine) UCB_PR_ADDR (ucbp))
632169689Skan	(_US_VIRTUAL_UNWIND_FRAME, ucbp, (void *) &saved_vrs);
633169689Skan    }
634169689Skan  while (pr_result == _URC_CONTINUE_UNWIND);
635169689Skan
636169689Skan  /* We've unwound as far as we want to go, so restore the original
637169689Skan     register state.  */
638169689Skan  restore_non_core_regs (&saved_vrs);
639169689Skan  if (pr_result != _URC_HANDLER_FOUND)
640169689Skan    {
641169689Skan      /* Some sort of failure has occurred in the pr and probably the
642169689Skan	 pr returned _URC_FAILURE.  */
643169689Skan      return _URC_FAILURE;
644169689Skan    }
645169689Skan
646169689Skan  unwind_phase2 (ucbp, entry_vrs);
647169689Skan}
648169689Skan
649169689Skan/* Resume unwinding after a cleanup has been run.  UCBP is the exception
650169689Skan   being thrown and ENTRY_VRS is the register state on entry to
651169689Skan   _Unwind_Resume.  */
652169689Skan_Unwind_Reason_Code
653169689Skan__gnu_Unwind_ForcedUnwind (_Unwind_Control_Block *,
654169689Skan			   _Unwind_Stop_Fn, void *, phase2_vrs *);
655169689Skan
656169689Skan_Unwind_Reason_Code
657169689Skan__gnu_Unwind_ForcedUnwind (_Unwind_Control_Block *ucbp,
658169689Skan			   _Unwind_Stop_Fn stop_fn, void *stop_arg,
659169689Skan			   phase2_vrs *entry_vrs)
660169689Skan{
661169689Skan  UCB_FORCED_STOP_FN (ucbp) = (_uw) stop_fn;
662169689Skan  UCB_FORCED_STOP_ARG (ucbp) = (_uw) stop_arg;
663169689Skan
664169689Skan  /* Set the pc to the call site.  */
665169689Skan  entry_vrs->core.r[R_PC] = entry_vrs->core.r[R_LR];
666169689Skan
667169689Skan  return unwind_phase2_forced (ucbp, entry_vrs, 0);
668169689Skan}
669169689Skan
670169689Skan_Unwind_Reason_Code
671169689Skan__gnu_Unwind_Resume (_Unwind_Control_Block *, phase2_vrs *);
672169689Skan
673169689Skan_Unwind_Reason_Code
674169689Skan__gnu_Unwind_Resume (_Unwind_Control_Block * ucbp, phase2_vrs * entry_vrs)
675169689Skan{
676169689Skan  _Unwind_Reason_Code pr_result;
677169689Skan
678169689Skan  /* Recover the saved address.  */
679169689Skan  entry_vrs->core.r[R_PC] = UCB_SAVED_CALLSITE_ADDR (ucbp);
680169689Skan
681169689Skan  if (UCB_FORCED_STOP_FN (ucbp))
682169689Skan    {
683169689Skan      unwind_phase2_forced (ucbp, entry_vrs, 1);
684169689Skan
685169689Skan      /* We can't return failure at this point.  */
686169689Skan      abort ();
687169689Skan    }
688169689Skan
689169689Skan  /* Call the cached PR.  */
690169689Skan  pr_result = ((personality_routine) UCB_PR_ADDR (ucbp))
691169689Skan	(_US_UNWIND_FRAME_RESUME, ucbp, (_Unwind_Context *) entry_vrs);
692169689Skan
693169689Skan  switch (pr_result)
694169689Skan    {
695169689Skan    case _URC_INSTALL_CONTEXT:
696169689Skan      /* Upload the registers to enter the landing pad.  */
697169689Skan      restore_core_regs (&entry_vrs->core);
698169689Skan
699169689Skan    case _URC_CONTINUE_UNWIND:
700169689Skan      /* Continue unwinding the next frame.  */
701169689Skan      unwind_phase2 (ucbp, entry_vrs);
702169689Skan
703169689Skan    default:
704169689Skan      abort ();
705169689Skan    }
706169689Skan}
707169689Skan
708169689Skan_Unwind_Reason_Code
709169689Skan__gnu_Unwind_Resume_or_Rethrow (_Unwind_Control_Block *, phase2_vrs *);
710169689Skan
711169689Skan_Unwind_Reason_Code
712169689Skan__gnu_Unwind_Resume_or_Rethrow (_Unwind_Control_Block * ucbp,
713169689Skan				phase2_vrs * entry_vrs)
714169689Skan{
715169689Skan  if (!UCB_FORCED_STOP_FN (ucbp))
716169689Skan    return __gnu_Unwind_RaiseException (ucbp, entry_vrs);
717169689Skan
718169689Skan  /* Set the pc to the call site.  */
719169689Skan  entry_vrs->core.r[R_PC] = entry_vrs->core.r[R_LR];
720169689Skan  /* Continue unwinding the next frame.  */
721169689Skan  return unwind_phase2_forced (ucbp, entry_vrs, 0);
722169689Skan}
723169689Skan
724169689Skan/* Clean up an exception object when unwinding is complete.  */
725169689Skanvoid
726169689Skan_Unwind_Complete (_Unwind_Control_Block * ucbp __attribute__((unused)))
727169689Skan{
728169689Skan}
729169689Skan
730169689Skan
731169689Skan/* Get the _Unwind_Control_Block from an _Unwind_Context.  */
732169689Skan
733169689Skanstatic inline _Unwind_Control_Block *
734169689Skanunwind_UCB_from_context (_Unwind_Context * context)
735169689Skan{
736169689Skan  return (_Unwind_Control_Block *) _Unwind_GetGR (context, R_IP);
737169689Skan}
738169689Skan
739169689Skan
740169689Skan/* Free an exception.  */
741169689Skan
742169689Skanvoid
743169689Skan_Unwind_DeleteException (_Unwind_Exception * exc)
744169689Skan{
745169689Skan  if (exc->exception_cleanup)
746169689Skan    (*exc->exception_cleanup) (_URC_FOREIGN_EXCEPTION_CAUGHT, exc);
747169689Skan}
748169689Skan
749169689Skan
750169689Skan/* Common implementation for ARM ABI defined personality routines.
751169689Skan   ID is the index of the personality routine, other arguments are as defined
752169689Skan   by __aeabi_unwind_cpp_pr{0,1,2}.  */
753169689Skan
754169689Skanstatic _Unwind_Reason_Code
755169689Skan__gnu_unwind_pr_common (_Unwind_State state,
756169689Skan			_Unwind_Control_Block *ucbp,
757169689Skan			_Unwind_Context *context,
758169689Skan			int id)
759169689Skan{
760169689Skan  __gnu_unwind_state uws;
761169689Skan  _uw *data;
762169689Skan  _uw offset;
763169689Skan  _uw len;
764169689Skan  _uw rtti_count;
765169689Skan  int phase2_call_unexpected_after_unwind = 0;
766169689Skan  int in_range = 0;
767169689Skan  int forced_unwind = state & _US_FORCE_UNWIND;
768169689Skan
769169689Skan  state &= _US_ACTION_MASK;
770169689Skan
771169689Skan  data = (_uw *) ucbp->pr_cache.ehtp;
772169689Skan  uws.data = *(data++);
773169689Skan  uws.next = data;
774169689Skan  if (id == 0)
775169689Skan    {
776169689Skan      uws.data <<= 8;
777169689Skan      uws.words_left = 0;
778169689Skan      uws.bytes_left = 3;
779169689Skan    }
780169689Skan  else
781169689Skan    {
782169689Skan      uws.words_left = (uws.data >> 16) & 0xff;
783169689Skan      uws.data <<= 16;
784169689Skan      uws.bytes_left = 2;
785169689Skan      data += uws.words_left;
786169689Skan    }
787169689Skan
788169689Skan  /* Restore the saved pointer.  */
789169689Skan  if (state == _US_UNWIND_FRAME_RESUME)
790169689Skan    data = (_uw *) ucbp->cleanup_cache.bitpattern[0];
791169689Skan
792169689Skan  if ((ucbp->pr_cache.additional & 1) == 0)
793169689Skan    {
794169689Skan      /* Process descriptors.  */
795169689Skan      while (*data)
796169689Skan	{
797169689Skan	  _uw addr;
798169689Skan	  _uw fnstart;
799169689Skan
800169689Skan	  if (id == 2)
801169689Skan	    {
802169689Skan	      len = ((EHT32 *) data)->length;
803169689Skan	      offset = ((EHT32 *) data)->offset;
804169689Skan	      data += 2;
805169689Skan	    }
806169689Skan	  else
807169689Skan	    {
808169689Skan	      len = ((EHT16 *) data)->length;
809169689Skan	      offset = ((EHT16 *) data)->offset;
810169689Skan	      data++;
811169689Skan	    }
812169689Skan
813169689Skan	  fnstart = ucbp->pr_cache.fnstart + (offset & ~1);
814169689Skan	  addr = _Unwind_GetGR (context, R_PC);
815169689Skan	  in_range = (fnstart <= addr && addr < fnstart + (len & ~1));
816169689Skan
817169689Skan	  switch (((offset & 1) << 1) | (len & 1))
818169689Skan	    {
819169689Skan	    case 0:
820169689Skan	      /* Cleanup.  */
821169689Skan	      if (state != _US_VIRTUAL_UNWIND_FRAME
822169689Skan		  && in_range)
823169689Skan		{
824169689Skan		  /* Cleanup in range, and we are running cleanups.  */
825169689Skan		  _uw lp;
826169689Skan
827169689Skan		  /* Landing pad address is 31-bit pc-relative offset.  */
828169689Skan		  lp = selfrel_offset31 (data);
829169689Skan		  data++;
830169689Skan		  /* Save the exception data pointer.  */
831169689Skan		  ucbp->cleanup_cache.bitpattern[0] = (_uw) data;
832169689Skan		  if (!__cxa_begin_cleanup (ucbp))
833169689Skan		    return _URC_FAILURE;
834169689Skan		  /* Setup the VRS to enter the landing pad.  */
835169689Skan		  _Unwind_SetGR (context, R_PC, lp);
836169689Skan		  return _URC_INSTALL_CONTEXT;
837169689Skan		}
838169689Skan	      /* Cleanup not in range, or we are in stage 1.  */
839169689Skan	      data++;
840169689Skan	      break;
841169689Skan
842169689Skan	    case 1:
843169689Skan	      /* Catch handler.  */
844169689Skan	      if (state == _US_VIRTUAL_UNWIND_FRAME)
845169689Skan		{
846169689Skan		  if (in_range)
847169689Skan		    {
848169689Skan		      /* Check for a barrier.  */
849169689Skan		      _uw rtti;
850169689Skan		      void *matched;
851169689Skan
852169689Skan		      /* Check for no-throw areas.  */
853169689Skan		      if (data[1] == (_uw) -2)
854169689Skan			return _URC_FAILURE;
855169689Skan
856169689Skan		      /* The thrown object immediately follows the ECB.  */
857169689Skan		      matched = (void *)(ucbp + 1);
858169689Skan		      if (data[1] != (_uw) -1)
859169689Skan			{
860169689Skan			  /* Match a catch specification.  */
861169689Skan			  rtti = _Unwind_decode_target2 ((_uw) &data[1]);
862169689Skan			  if (!__cxa_type_match (ucbp, (type_info *) rtti,
863169689Skan						 &matched))
864169689Skan			    matched = (void *)0;
865169689Skan			}
866169689Skan
867169689Skan		      if (matched)
868169689Skan			{
869169689Skan			  ucbp->barrier_cache.sp =
870169689Skan			    _Unwind_GetGR (context, R_SP);
871169689Skan			  ucbp->barrier_cache.bitpattern[0] = (_uw) matched;
872169689Skan			  ucbp->barrier_cache.bitpattern[1] = (_uw) data;
873169689Skan			  return _URC_HANDLER_FOUND;
874169689Skan			}
875169689Skan		    }
876169689Skan		  /* Handler out of range, or not matched.  */
877169689Skan		}
878169689Skan	      else if (ucbp->barrier_cache.sp == _Unwind_GetGR (context, R_SP)
879169689Skan		       && ucbp->barrier_cache.bitpattern[1] == (_uw) data)
880169689Skan		{
881169689Skan		  /* Matched a previous propagation barrier.  */
882169689Skan		  _uw lp;
883169689Skan
884169689Skan		  /* Setup for entry to the handler.  */
885169689Skan		  lp = selfrel_offset31 (data);
886169689Skan		  _Unwind_SetGR (context, R_PC, lp);
887169689Skan		  _Unwind_SetGR (context, 0, (_uw) ucbp);
888169689Skan		  return _URC_INSTALL_CONTEXT;
889169689Skan		}
890169689Skan	      /* Catch handler not matched.  Advance to the next descriptor.  */
891169689Skan	      data += 2;
892169689Skan	      break;
893169689Skan
894169689Skan	    case 2:
895169689Skan	      rtti_count = data[0] & 0x7fffffff;
896169689Skan	      /* Exception specification.  */
897169689Skan	      if (state == _US_VIRTUAL_UNWIND_FRAME)
898169689Skan		{
899169689Skan		  if (in_range && (!forced_unwind || !rtti_count))
900169689Skan		    {
901169689Skan		      /* Match against the exception specification.  */
902169689Skan		      _uw i;
903169689Skan		      _uw rtti;
904169689Skan		      void *matched;
905169689Skan
906169689Skan		      for (i = 0; i < rtti_count; i++)
907169689Skan			{
908169689Skan			  matched = (void *)(ucbp + 1);
909169689Skan			  rtti = _Unwind_decode_target2 ((_uw) &data[i + 1]);
910169689Skan			  if (__cxa_type_match (ucbp, (type_info *) rtti,
911169689Skan						&matched))
912169689Skan			    break;
913169689Skan			}
914169689Skan
915169689Skan		      if (i == rtti_count)
916169689Skan			{
917169689Skan			  /* Exception does not match the spec.  */
918169689Skan			  ucbp->barrier_cache.sp =
919169689Skan			    _Unwind_GetGR (context, R_SP);
920169689Skan			  ucbp->barrier_cache.bitpattern[0] = (_uw) matched;
921169689Skan			  ucbp->barrier_cache.bitpattern[1] = (_uw) data;
922169689Skan			  return _URC_HANDLER_FOUND;
923169689Skan			}
924169689Skan		    }
925169689Skan		  /* Handler out of range, or exception is permitted.  */
926169689Skan		}
927169689Skan	      else if (ucbp->barrier_cache.sp == _Unwind_GetGR (context, R_SP)
928169689Skan		       && ucbp->barrier_cache.bitpattern[1] == (_uw) data)
929169689Skan		{
930169689Skan		  /* Matched a previous propagation barrier.  */
931169689Skan		  _uw lp;
932169689Skan		  /* Record the RTTI list for __cxa_call_unexpected.  */
933169689Skan		  ucbp->barrier_cache.bitpattern[1] = rtti_count;
934169689Skan		  ucbp->barrier_cache.bitpattern[2] = 0;
935169689Skan		  ucbp->barrier_cache.bitpattern[3] = 4;
936169689Skan		  ucbp->barrier_cache.bitpattern[4] = (_uw) &data[1];
937169689Skan
938169689Skan		  if (data[0] & uint32_highbit)
939169689Skan		    phase2_call_unexpected_after_unwind = 1;
940169689Skan		  else
941169689Skan		    {
942169689Skan		      data += rtti_count + 1;
943169689Skan		      /* Setup for entry to the handler.  */
944169689Skan		      lp = selfrel_offset31 (data);
945169689Skan		      data++;
946169689Skan		      _Unwind_SetGR (context, R_PC, lp);
947169689Skan		      _Unwind_SetGR (context, 0, (_uw) ucbp);
948169689Skan		      return _URC_INSTALL_CONTEXT;
949169689Skan		    }
950169689Skan		}
951169689Skan	      if (data[0] & uint32_highbit)
952169689Skan		data++;
953169689Skan	      data += rtti_count + 1;
954169689Skan	      break;
955169689Skan
956169689Skan	    default:
957169689Skan	      /* Should never happen.  */
958169689Skan	      return _URC_FAILURE;
959169689Skan	    }
960169689Skan	  /* Finished processing this descriptor.  */
961169689Skan	}
962169689Skan    }
963169689Skan
964169689Skan  if (__gnu_unwind_execute (context, &uws) != _URC_OK)
965169689Skan    return _URC_FAILURE;
966169689Skan
967169689Skan  if (phase2_call_unexpected_after_unwind)
968169689Skan    {
969169689Skan      /* Enter __cxa_unexpected as if called from the call site.  */
970169689Skan      _Unwind_SetGR (context, R_LR, _Unwind_GetGR (context, R_PC));
971169689Skan      _Unwind_SetGR (context, R_PC, (_uw) &__cxa_call_unexpected);
972169689Skan      return _URC_INSTALL_CONTEXT;
973169689Skan    }
974169689Skan
975169689Skan  return _URC_CONTINUE_UNWIND;
976169689Skan}
977169689Skan
978169689Skan
979169689Skan/* ABI defined personality routine entry points.  */
980169689Skan
981169689Skan_Unwind_Reason_Code
982169689Skan__aeabi_unwind_cpp_pr0 (_Unwind_State state,
983169689Skan			_Unwind_Control_Block *ucbp,
984169689Skan			_Unwind_Context *context)
985169689Skan{
986169689Skan  return __gnu_unwind_pr_common (state, ucbp, context, 0);
987169689Skan}
988169689Skan
989169689Skan_Unwind_Reason_Code
990169689Skan__aeabi_unwind_cpp_pr1 (_Unwind_State state,
991169689Skan			_Unwind_Control_Block *ucbp,
992169689Skan			_Unwind_Context *context)
993169689Skan{
994169689Skan  return __gnu_unwind_pr_common (state, ucbp, context, 1);
995169689Skan}
996169689Skan
997169689Skan_Unwind_Reason_Code
998169689Skan__aeabi_unwind_cpp_pr2 (_Unwind_State state,
999169689Skan			_Unwind_Control_Block *ucbp,
1000169689Skan			_Unwind_Context *context)
1001169689Skan{
1002169689Skan  return __gnu_unwind_pr_common (state, ucbp, context, 2);
1003169689Skan}
1004169689Skan
1005169689Skan/* These two should never be used.  */
1006169689Skan_Unwind_Ptr
1007169689Skan_Unwind_GetDataRelBase (_Unwind_Context *context __attribute__ ((unused)))
1008169689Skan{
1009169689Skan  abort ();
1010169689Skan}
1011169689Skan
1012169689Skan_Unwind_Ptr
1013169689Skan_Unwind_GetTextRelBase (_Unwind_Context *context __attribute__ ((unused)))
1014169689Skan{
1015169689Skan  abort ();
1016169689Skan}
1017