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